1
Fork 0
mirror of https://git.cs.ou.nl/joshua.moerman/mealy-decompose.git synced 2025-04-30 02:07:44 +02:00

moved the other commands as well so that everything goes via main

This commit is contained in:
Joshua Moerman 2025-04-22 11:53:39 +02:00
parent 8da20fdbad
commit c14d24a13c
8 changed files with 86 additions and 81 deletions

View file

@ -27,7 +27,6 @@ decomposeInputOptionsParser :: Parser DecomposeInputOptions
decomposeInputOptionsParser =
DecomposeInputOptions
<$> argument str (help "Filename to read (dot format)" <> metavar "FILE")
<**> helper
-- Interleaving composition of restriction to subalphabets
-- precondition: alph1 and alph2 have no common elements

View file

@ -37,7 +37,6 @@ decomposeOutputOptionsParser =
DecomposeOutputOptions
<$> argument str (help "Filename to read (dot format)" <> metavar "FILE")
<*> option auto (long "components" <> short 'c' <> help "Number of components" <> metavar "NUM" <> showDefault <> value 2)
<**> helper
mainDecomposeOutput :: DecomposeOutputOptions -> CommonOptions -> IO ()
mainDecomposeOutput DecomposeOutputOptions{..} CommonOptions{..} = do

51
hs/app/HsiMethod.hs Normal file
View file

@ -0,0 +1,51 @@
module HsiMethod where
import Data.Trie qualified as Trie
import DotParser (readDotFile)
import Mealy (MealyMachine (..))
import SplittingTree (initialPRState, refine)
import StateIdentifiers (stateIdentifierFor)
import Control.Monad.Trans.State (evalStateT)
import Data.Map.Strict qualified as Map
import Options.Applicative
newtype HsiMethodOptions = HsiMethodOptions
{ filename :: FilePath
}
deriving Show
hsiMethodOptionsParser :: Parser HsiMethodOptions
hsiMethodOptionsParser =
HsiMethodOptions
<$> argument str (help "Filename to read (dot format)" <> metavar "FILE")
mainHsiMethod :: HsiMethodOptions -> IO ()
mainHsiMethod HsiMethodOptions{..} = do
let dotFile = filename
print dotFile
machine <- readDotFile dotFile
-- convert to mealy
let
MealyMachine{..} = machine
outputFuns = [(i, fun) | i <- inputs, let fun s = fst (behaviour s i)]
reverseTransitionMaps i = Map.fromListWith (++) [(t, [s]) | s <- states, let t = snd (behaviour s i)]
reverseFuns = [(i, fun) | i <- inputs, let m = reverseTransitionMaps i, let fun s = Map.findWithDefault [] s m]
(partition, splittingTree) <- evalStateT (refine print outputFuns reverseFuns) (initialPRState states)
putStrLn "\nPARTITION"
print partition
putStrLn "\nTREE"
print splittingTree
let
siFor s = stateIdentifierFor s partition splittingTree
putStrLn "\nHARMONISED STATE IDENTIFIERS"
sis <- mapM (\s -> let si = siFor s in print (Trie.toList si) >> return si) states
putStrLn "\nW-SET"
print (Trie.toList . foldr Trie.union Trie.empty $ sis)

View file

@ -1,4 +1,4 @@
module Main where
module LStarMain where
import Bisimulation (bisimulation2)
import DotParser (readDotFile)
@ -9,19 +9,25 @@ import Control.Monad (when)
import Control.Monad.Trans.Class
import Control.Monad.Trans.State.Strict
import Data.Map.Strict qualified as Map
import System.Environment
import Options.Applicative
debugOutput :: Bool
debugOutput = False
data LStarOptions = LStarOptions
{ filename :: FilePath
, debugOutput :: Bool
}
deriving Show
semanticsForState :: MealyMachine s i o -> s -> [i] -> o
semanticsForState _ _ [] = error ""
semanticsForState MealyMachine{..} q [a] = fst (behaviour q a)
semanticsForState m@MealyMachine{..} q (a : w) = semanticsForState m (snd (behaviour q a)) w
lStarOptionsParser :: Parser LStarOptions
lStarOptionsParser =
LStarOptions
<$> argument str (help "Filename to read (dot format)" <> metavar "FILE")
<*> switch (long "verbose" <> short 'v' <> help "Enable extra debugging output")
mainLStar :: LStarOptions -> IO ()
mainLStar LStarOptions{..} = do
let
dotFile = filename
main :: IO ()
main = do
[dotFile] <- getArgs
print dotFile
machine <- readDotFile dotFile
@ -62,3 +68,8 @@ main = do
putStrLn $ "Size: " <> show a
putStrLn $ "MQs: " <> show b
semanticsForState :: MealyMachine s i o -> s -> [i] -> o
semanticsForState _ _ [] = error ""
semanticsForState MealyMachine{..} q [a] = fst (behaviour q a)
semanticsForState m@MealyMachine{..} q (a : w) = semanticsForState m (snd (behaviour q a)) w

View file

@ -5,6 +5,8 @@ module Main where
import CommonOptions
import DecomposeInput
import DecomposeOutput
import HsiMethod
import LStarMain
import RandomGen
import Options.Applicative
@ -23,6 +25,8 @@ main = do
case optCommand of
DecomposeOutput options -> mainDecomposeOutput options commonOptions
DecomposeInput options -> mainDecomposeInput options commonOptions
HsiMethod options -> mainHsiMethod options
LStar options -> mainLStar options
RandomGen options -> mainRandomGen options
data Options = Options
@ -36,16 +40,21 @@ optionsParser =
<$> commandParser
<*> commonOptionsParser
<**> helper
<**> simpleVersioner "0.4.0.0"
data Command
= DecomposeOutput DecomposeOutputOptions
| DecomposeInput DecomposeInputOptions
| HsiMethod HsiMethodOptions
| LStar LStarOptions
| RandomGen RandomGenOptions
deriving Show
commandParser =
subparser
hsubparser
( command "decompose-output" (info (DecomposeOutput <$> decomposeOutputOptionsParser) (progDesc "decompose based on output"))
<> command "decompose-input" (info (DecomposeInput <$> decomposeInputOptionsParser) (progDesc "decompose based on independent inputs"))
<> command "hsi-method" (info (HsiMethod <$> hsiMethodOptionsParser) (progDesc "construct HSI test suite from specification dot file"))
<> command "lstar" (info (LStar <$> lStarOptionsParser) (progDesc "little l* playground"))
<> command "random-gen" (info (RandomGen <$> randomGenOptionsParser) (progDesc "generate random parallel compositions"))
)

View file

@ -1,51 +0,0 @@
module Main where
import Data.Trie qualified as Trie
import DotParser (readDotFile)
import Mealy (MealyMachine (..))
import SplittingTree (initialPRState, refine)
import StateIdentifiers (stateIdentifierFor)
import Control.Monad.Trans.State (evalStateT)
import Data.Map.Strict qualified as Map
import System.Environment (getArgs)
main :: IO ()
main = do
args <- getArgs
case args of
("HSI" : ls) -> mainHSI ls
_ -> putStrLn "Please provide one of [HSI, InputDecomp]"
mainHSI :: [String] -> IO ()
mainHSI args = case args of
[dotFile] -> run dotFile
_ -> putStrLn "Please provide a dot file"
where
run dotFile = do
print dotFile
machine <- readDotFile dotFile
-- convert to mealy
let
MealyMachine{..} = machine
outputFuns = [(i, fun) | i <- inputs, let fun s = fst (behaviour s i)]
reverseTransitionMaps i = Map.fromListWith (++) [(t, [s]) | s <- states, let t = snd (behaviour s i)]
reverseFuns = [(i, fun) | i <- inputs, let m = reverseTransitionMaps i, let fun s = Map.findWithDefault [] s m]
(partition, splittingTree) <- evalStateT (refine print outputFuns reverseFuns) (initialPRState states)
putStrLn "\nPARTITION"
print partition
putStrLn "\nTREE"
print splittingTree
let
siFor s = stateIdentifierFor s partition splittingTree
putStrLn "\nHARMONISED STATE IDENTIFIERS"
sis <- mapM (\s -> let si = siFor s in print (Trie.toList si) >> return si) states
putStrLn "\nW-SET"
print (Trie.toList . foldr Trie.union Trie.empty $ sis)

View file

@ -25,7 +25,6 @@ randomGenOptionsParser =
RandomGenOptions
<$> option auto (long "states" <> short 'n' <> help "Number of states per component (max)" <> metavar "NUM" <> showDefault <> value 10)
<*> option auto (long "components" <> short 'c' <> help "Number of components" <> metavar "COMP" <> showDefault <> value 2)
<**> helper
genTransitions :: _ => Int -> [Char] -> [Char] -> RandT _ _ _
genTransitions size inputs outputs = do

View file

@ -1,6 +1,6 @@
cabal-version: 2.2
name: mealy-decompose
version: 0.3.0.0
version: 0.4.0.0
license: EUPL-1.2
license-file: LICENSE
author: Joshua Moerman
@ -53,24 +53,12 @@ executable mealy-decompose-main
CommonOptions,
DecomposeInput,
DecomposeOutput,
HsiMethod,
LStarMain,
RandomGen
default-extensions:
OverloadedStrings
executable mealy-decompose-lstar
import: stuff
hs-source-dirs: app
main-is: LStarMain.hs
build-depends:
mealy-decompose
executable mealy-decompose-playground
import: stuff
hs-source-dirs: app
main-is: Playground.hs
build-depends:
mealy-decompose
test-suite mealy-decompose-test
import: stuff
hs-source-dirs: test