mirror of
https://git.cs.ou.nl/joshua.moerman/mealy-decompose.git
synced 2025-04-29 17:57:44 +02:00
added some copyrgiht info
This commit is contained in:
parent
244e150665
commit
9b6a050bda
9 changed files with 74 additions and 1 deletions
|
@ -1,3 +1,5 @@
|
||||||
|
-- | Copyright: (c) 2024-2025 Joshua Moerman, Open Universiteit
|
||||||
|
-- SPDX-License-Identifier: EUPL-1.2
|
||||||
module CommonOptions where
|
module CommonOptions where
|
||||||
|
|
||||||
import Options.Applicative
|
import Options.Applicative
|
||||||
|
|
|
@ -1,3 +1,5 @@
|
||||||
|
-- | Copyright: (c) 2024-2025 Joshua Moerman, Open Universiteit
|
||||||
|
-- SPDX-License-Identifier: EUPL-1.2
|
||||||
module DecomposeInput where
|
module DecomposeInput where
|
||||||
|
|
||||||
import Bisimulation (bisimulation2)
|
import Bisimulation (bisimulation2)
|
||||||
|
|
|
@ -1,6 +1,8 @@
|
||||||
{-# LANGUAGE PartialTypeSignatures #-}
|
{-# LANGUAGE PartialTypeSignatures #-}
|
||||||
{-# OPTIONS_GHC -Wno-partial-type-signatures #-}
|
{-# OPTIONS_GHC -Wno-partial-type-signatures #-}
|
||||||
|
|
||||||
|
-- | Copyright: (c) 2024-2025 Joshua Moerman, Open Universiteit
|
||||||
|
-- SPDX-License-Identifier: EUPL-1.2
|
||||||
module DecomposeOutput where
|
module DecomposeOutput where
|
||||||
|
|
||||||
import CommonOptions
|
import CommonOptions
|
||||||
|
|
54
hs/app/DecomposeTemp.hs
Normal file
54
hs/app/DecomposeTemp.hs
Normal file
|
@ -0,0 +1,54 @@
|
||||||
|
-- | Copyright: (c) 2025 Joshua Moerman, Open Universiteit
|
||||||
|
-- SPDX-License-Identifier: EUPL-1.2
|
||||||
|
module DecomposeTemp where
|
||||||
|
|
||||||
|
import DotParser (readDotFile)
|
||||||
|
import Mealy
|
||||||
|
|
||||||
|
import Control.Monad (unless)
|
||||||
|
import Data.List (nub, sort)
|
||||||
|
import Data.Maybe (mapMaybe)
|
||||||
|
import Data.Set qualified as Set
|
||||||
|
import Data.Text (Text)
|
||||||
|
import Options.Applicative
|
||||||
|
|
||||||
|
-- Nog een experiment
|
||||||
|
|
||||||
|
data DecomposeTempOptions = DecomposeTempOptions
|
||||||
|
{ filename :: FilePath
|
||||||
|
, quiescence :: Text
|
||||||
|
, numComponents :: Int
|
||||||
|
}
|
||||||
|
deriving Show
|
||||||
|
|
||||||
|
decomposeTempOptionsParser :: Parser DecomposeTempOptions
|
||||||
|
decomposeTempOptionsParser =
|
||||||
|
DecomposeTempOptions
|
||||||
|
<$> argument str (help "Filename to read (dot format)" <> metavar "FILE")
|
||||||
|
<*> option str (long "quiescence" <> help "String denoting empty output" <> showDefault <> value "quiescence")
|
||||||
|
<*> option auto (long "components" <> short 'c' <> help "Number of components" <> metavar "NUM" <> showDefault <> value 2)
|
||||||
|
|
||||||
|
mainDecomposeTemp :: DecomposeTempOptions -> IO ()
|
||||||
|
mainDecomposeTemp DecomposeTempOptions{..} = do
|
||||||
|
putStrLn $ "reading " <> filename <> " and quiescence=" <> show quiescence
|
||||||
|
MealyMachine{..} <- readDotFile filename
|
||||||
|
|
||||||
|
let
|
||||||
|
quiescenceTransitions s = mapMaybe (\i -> let (o, t) = behaviour s i in if o == quiescence then Just (s, t) else Nothing) inputs
|
||||||
|
valid = all (uncurry (==)) . quiescenceTransitions
|
||||||
|
|
||||||
|
unless (all valid states) $ do
|
||||||
|
putStrLn "WARNING: Not all quiescence-transistions are self-loops!"
|
||||||
|
|
||||||
|
let
|
||||||
|
definedTransitions s = mapMaybe (\i -> let (o, t) = behaviour s i in if o /= quiescence || s /= t then Just (s, i, o, t) else Nothing) inputs
|
||||||
|
showState s trns = putStrLn $ show s <> ": " <> show (fmap (\(_, i, _, _) -> i) trns)
|
||||||
|
|
||||||
|
bfs [] _ = []
|
||||||
|
bfs (x : todo) visited
|
||||||
|
| x `Set.member` visited = bfs todo visited
|
||||||
|
| otherwise =
|
||||||
|
let trns = definedTransitions x
|
||||||
|
in (x, sort trns) : bfs (todo <> nub (fmap (\(_, _, _, t) -> t) trns)) (Set.insert x visited)
|
||||||
|
|
||||||
|
mapM_ (uncurry showState) (bfs [initialState] Set.empty)
|
|
@ -1,3 +1,5 @@
|
||||||
|
-- | Copyright: (c) 2024-2025 Joshua Moerman, Open Universiteit
|
||||||
|
-- SPDX-License-Identifier: EUPL-1.2]
|
||||||
module HsiMethod where
|
module HsiMethod where
|
||||||
|
|
||||||
import Data.Trie qualified as Trie
|
import Data.Trie qualified as Trie
|
||||||
|
|
|
@ -1,3 +1,5 @@
|
||||||
|
-- | Copyright: (c) 2024-2025 Joshua Moerman, Open Universiteit
|
||||||
|
-- SPDX-License-Identifier: EUPL-1.2
|
||||||
module LStarMain where
|
module LStarMain where
|
||||||
|
|
||||||
import Bisimulation (bisimulation2)
|
import Bisimulation (bisimulation2)
|
||||||
|
|
|
@ -1,10 +1,13 @@
|
||||||
{-# OPTIONS_GHC -Wno-missing-signatures #-}
|
{-# OPTIONS_GHC -Wno-missing-signatures #-}
|
||||||
|
|
||||||
|
-- | Copyright: (c) 2025 Joshua Moerman, Open Universiteit
|
||||||
|
-- SPDX-License-Identifier: EUPL-1.2
|
||||||
module Main where
|
module Main where
|
||||||
|
|
||||||
import CommonOptions
|
import CommonOptions
|
||||||
import DecomposeInput
|
import DecomposeInput
|
||||||
import DecomposeOutput
|
import DecomposeOutput
|
||||||
|
import DecomposeTemp
|
||||||
import HsiMethod
|
import HsiMethod
|
||||||
import LStarMain
|
import LStarMain
|
||||||
import RandomGen
|
import RandomGen
|
||||||
|
@ -25,6 +28,7 @@ main = do
|
||||||
case optCommand of
|
case optCommand of
|
||||||
DecomposeOutput options -> mainDecomposeOutput options commonOptions
|
DecomposeOutput options -> mainDecomposeOutput options commonOptions
|
||||||
DecomposeInput options -> mainDecomposeInput options commonOptions
|
DecomposeInput options -> mainDecomposeInput options commonOptions
|
||||||
|
DecomposeTemp options -> mainDecomposeTemp options
|
||||||
HsiMethod options -> mainHsiMethod options
|
HsiMethod options -> mainHsiMethod options
|
||||||
LStar options -> mainLStar options
|
LStar options -> mainLStar options
|
||||||
RandomGen options -> mainRandomGen options
|
RandomGen options -> mainRandomGen options
|
||||||
|
@ -45,6 +49,7 @@ optionsParser =
|
||||||
data Command
|
data Command
|
||||||
= DecomposeOutput DecomposeOutputOptions
|
= DecomposeOutput DecomposeOutputOptions
|
||||||
| DecomposeInput DecomposeInputOptions
|
| DecomposeInput DecomposeInputOptions
|
||||||
|
| DecomposeTemp DecomposeTempOptions
|
||||||
| HsiMethod HsiMethodOptions
|
| HsiMethod HsiMethodOptions
|
||||||
| LStar LStarOptions
|
| LStar LStarOptions
|
||||||
| RandomGen RandomGenOptions
|
| RandomGen RandomGenOptions
|
||||||
|
@ -54,6 +59,7 @@ commandParser =
|
||||||
hsubparser
|
hsubparser
|
||||||
( command "decompose-output" (info (DecomposeOutput <$> decomposeOutputOptionsParser) (progDesc "decompose based on output"))
|
( command "decompose-output" (info (DecomposeOutput <$> decomposeOutputOptionsParser) (progDesc "decompose based on output"))
|
||||||
<> command "decompose-input" (info (DecomposeInput <$> decomposeInputOptionsParser) (progDesc "decompose based on independent inputs"))
|
<> command "decompose-input" (info (DecomposeInput <$> decomposeInputOptionsParser) (progDesc "decompose based on independent inputs"))
|
||||||
|
<> command "decompose-temp" (info (DecomposeTemp <$> decomposeTempOptionsParser) (progDesc "temporary experiment"))
|
||||||
<> command "hsi-method" (info (HsiMethod <$> hsiMethodOptionsParser) (progDesc "construct HSI test suite from specification dot file"))
|
<> 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 "lstar" (info (LStar <$> lStarOptionsParser) (progDesc "little l* playground"))
|
||||||
<> command "random-gen" (info (RandomGen <$> randomGenOptionsParser) (progDesc "generate random parallel compositions"))
|
<> command "random-gen" (info (RandomGen <$> randomGenOptionsParser) (progDesc "generate random parallel compositions"))
|
||||||
|
|
|
@ -1,6 +1,8 @@
|
||||||
{-# LANGUAGE PartialTypeSignatures #-}
|
{-# LANGUAGE PartialTypeSignatures #-}
|
||||||
{-# OPTIONS_GHC -Wno-partial-type-signatures #-}
|
{-# OPTIONS_GHC -Wno-partial-type-signatures #-}
|
||||||
|
|
||||||
|
-- | Copyright: (c) 2024-2025 Joshua Moerman, Open Universiteit
|
||||||
|
-- SPDX-License-Identifier: EUPL-1.2
|
||||||
module RandomGen where
|
module RandomGen where
|
||||||
|
|
||||||
import Data.Partition (Block (..))
|
import Data.Partition (Block (..))
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
cabal-version: 2.2
|
cabal-version: 2.2
|
||||||
name: mealy-decompose
|
name: mealy-decompose
|
||||||
version: 0.4.0.0
|
version: 0.4.1.0
|
||||||
license: EUPL-1.2
|
license: EUPL-1.2
|
||||||
license-file: LICENSE
|
license-file: LICENSE
|
||||||
author: Joshua Moerman
|
author: Joshua Moerman
|
||||||
|
@ -53,6 +53,7 @@ executable mealy-decompose-main
|
||||||
CommonOptions,
|
CommonOptions,
|
||||||
DecomposeInput,
|
DecomposeInput,
|
||||||
DecomposeOutput,
|
DecomposeOutput,
|
||||||
|
DecomposeTemp,
|
||||||
HsiMethod,
|
HsiMethod,
|
||||||
LStarMain,
|
LStarMain,
|
||||||
RandomGen
|
RandomGen
|
||||||
|
|
Loading…
Add table
Reference in a new issue