Skip to content
Snippets Groups Projects
Commit 786abddc authored by Hans-Peter Deifel's avatar Hans-Peter Deifel
Browse files

random-dfa: Allow to output a single DFA in multiple formats

This is required to compare the running time of different
applications: Since the DFAs are generated randomly, we get a new one
each run and so we have to have a way of outputting multiple formats
in one run.
parent a7e466cf
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
module Main (main) where module Main (main) where
import Control.Applicative import Control.Applicative
import Control.Monad ( forM_ )
import Data.Maybe ( listToMaybe )
import qualified Data.List.NonEmpty as NE
import qualified Data.Text.Lazy.IO as TL import qualified Data.Text.Lazy.IO as TL
import qualified Data.Text.Lazy.Builder as Build import qualified Data.Text.Lazy.Builder as Build
...@@ -44,9 +48,8 @@ instance Show OutputFormat where ...@@ -44,9 +48,8 @@ instance Show OutputFormat where
data Options = Options data Options = Options
{ _optStates :: Int { _optStates :: Int
, _optLetters :: Int , _optLetters :: Int
, _optFile :: Maybe FilePath , _optOutputs :: [(OutputFormat, Maybe (NE.NonEmpty Char))]
, _optOutputFormat :: OutputFormat } deriving (Show)
}
makeLensesWith abbreviatedFields ''Options makeLensesWith abbreviatedFields ''Options
...@@ -61,20 +64,11 @@ options = ...@@ -61,20 +64,11 @@ options =
OptParse.auto OptParse.auto
(OptParse.metavar "M" <> OptParse.help "Size of the alphabet") (OptParse.metavar "M" <> OptParse.help "Size of the alphabet")
) )
<*> optional <*> some
(OptParse.strArgument (OptParse.argument
(OptParse.metavar "OUTPUT_FILE" <> OptParse.help readOutput
"Name of the file where the output should be written." ( OptParse.metavar "FORMAT:[OUTPUT_FILE]..."
) <> OptParse.help "FORMAT can be 'dot', 'ma' or 'valmari'"
)
<*> (OptParse.option
readFormat
( OptParse.long "output-format"
<> OptParse.metavar "FORMAT"
<> OptParse.value MA
<> OptParse.help
"Syntax used for the output. Posible values are 'ma', 'valmari' or 'dot'."
<> OptParse.showDefault
) )
) )
...@@ -87,6 +81,18 @@ readFormat = OptParse.maybeReader $ \case ...@@ -87,6 +81,18 @@ readFormat = OptParse.maybeReader $ \case
_ -> Nothing _ -> Nothing
readOutput :: OptParse.ReadM (OutputFormat, Maybe (NE.NonEmpty Char))
readOutput = OptParse.eitherReader $ \s -> case span (/= sep) s of
([] , _ ) -> Left "a"
(_ , []) -> Left "b"
(format, _ : file) -> (, NE.nonEmpty file) <$> case format of
"ma" -> Right MA
"dot" -> Right Dot
"valmari" -> Right Valmari
_ -> Left "c"
where sep = ':'
main :: IO () main :: IO ()
main = do main = do
opts <- OptParse.execParser opts <- OptParse.execParser
...@@ -97,16 +103,17 @@ main = do ...@@ -97,16 +103,17 @@ main = do
) )
) )
let builder = case opts ^. outputFormat of dfa <- randomDFA (opts ^. states) (opts ^. letters)
forM_ (opts ^. outputs) $ \(outputFormat, outputFile) -> do
let builder = case outputFormat of
MA -> coalgB MA -> coalgB
Dot -> dotB Dot -> dotB
Valmari -> valmariB Valmari -> valmariB
dfa <- randomDFA (opts ^. states) (opts ^. letters)
let text = Build.toLazyText (builder dfa) let text = Build.toLazyText (builder dfa)
case opts ^. file of case outputFile of
Nothing -> TL.putStr text Nothing -> TL.putStr text
Just filename -> TL.writeFile filename text Just filename -> TL.writeFile (NE.toList filename) text
return () return ()
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment