License | MIT (see the LICENSE file) |
---|---|
Maintainer | Felix Klein (klein@react.uni-saarland.de) |
Safe Haskell | None |
Language | Haskell2010 |
Syfco Library Interface.
- data Configuration = Configuration {
- inputFiles :: [FilePath]
- outputFile :: Maybe FilePath
- outputFormat :: WriteFormat
- outputMode :: WriteMode
- partFile :: Maybe String
- busDelimiter :: String
- primeSymbol :: String
- atSymbol :: String
- fromStdin :: Bool
- owSemantics :: Maybe Semantics
- owTarget :: Maybe Target
- owParameter :: [(String, Int)]
- simplifyWeak :: Bool
- simplifyStrong :: Bool
- negNormalForm :: Bool
- pushGlobally :: Bool
- pushFinally :: Bool
- pushNext :: Bool
- pullGlobally :: Bool
- pullFinally :: Bool
- pullNext :: Bool
- noWeak :: Bool
- noRelease :: Bool
- noFinally :: Bool
- noGlobally :: Bool
- noDerived :: Bool
- cGR :: Bool
- check :: Bool
- pTitle :: Bool
- pDesc :: Bool
- pSemantics :: Bool
- pTarget :: Bool
- pTags :: Bool
- pParameters :: Bool
- pInputs :: Bool
- pOutputs :: Bool
- pInfo :: Bool
- pVersion :: Bool
- pHelp :: Bool
- pReadme :: Bool
- pReadmeMd :: Bool
- saveConfig :: [FilePath]
- data WriteFormat
- data WriteMode
- data Semantics
- data Target
- data Specification
- data Error
- defaultCfg :: Configuration
- update :: Configuration -> String -> Either Error Configuration
- verify :: Configuration -> Either Error ()
- source :: Specification -> String
- title :: Specification -> String
- description :: Specification -> String
- semantics :: Specification -> Semantics
- target :: Specification -> Target
- tags :: Specification -> [String]
- parameters :: Specification -> [String]
- signals :: Configuration -> Specification -> Either Error ([String], [String])
- inputs :: Configuration -> Specification -> Either Error [String]
- outputs :: Configuration -> Specification -> Either Error [String]
- symboltable :: Specification -> String
- fromTLSF :: String -> Either Error Specification
- apply :: Configuration -> Specification -> Either Error String
- checkGR :: Specification -> Either Error Int
- version :: [Char]
Data Structures
data Configuration Source #
The data type contains all flags and settings that can be adjusted to influence the behavior of the library:
Configuration | |
|
Eq Configuration Source # | |
Ord Configuration Source # | |
Convertible Configuration String Source # | Creates the content of a parsable configuration file restricted to supported configuration file parameters. |
data WriteFormat Source #
Supported writer formats.
UTF8 | human readable output using UTF8 symbols |
FULL | full format including all extensions |
BASIC | basic format restricted to pure LTL formulas |
WRING | |
PROMELA | |
UNBEAST | |
LTLXBA | LTL2BA / LTL3BA input format |
LILY | Lily input format |
ACACIA | Acacia / Acacia+ input format |
ACACIASPECS | Acacia input format with spec units |
SLUGS | https://github.com/VerifiableRobotics/slugs/blob/master/doc/input_formats.md#structuredslugs |
SLUGSIN | https://github.com/VerifiableRobotics/slugs/blob/master/doc/input_formats.md#slugsin |
PSL | https://en.wikipedia.org/wiki/Property_Specification_Language |
SMV | SMV file format |
BOSY |
Eq WriteFormat Source # | |
Ord WriteFormat Source # | |
Show WriteFormat Source # | Human readable names of the formats, which may include spaces or other special characters. |
Convertible String WriteFormat Source # | |
Convertible WriteFormat String Source # | |
There are two writing modes currently supported:
Semantic types.
SemanticsMealy | Standard Mealy machine semantics. |
SemanticsMoore | Standard Moore machine semantics. |
SemanticsStrictMealy | Mealy machine semantics with strict envionment assumptions. |
SemanticsStrictMoore | Moore machine semantics with strict envionment assumptions. |
Target types.
TargetMealy | Mealy machine target |
TargetMoore | Moore machine target |
data Specification Source #
Internal representation of a specification.
Configurations
defaultCfg :: Configuration Source #
inputFiles = [] outputFile = Nothing outputFormat = FULL outputMode = Pretty partFile = Nothing busDelimiter = "_" primeSymbol = "'" atSymbol = "@" fromStdin = False owSemantics = Nothing owTarget = Nothing owParameter = [] simplifyWeak = False simplifyStrong = False negNormalForm = False pushGlobally = False pushFinally = False pushNext = False pullGlobally = False pullFinally = False pullNext = False noWeak = False noRelease = False noFinally = False noGlobally = False noDerived = False cGR = False check = False pTitle = False pDesc = False pSemantics = False pTarget = False pTags = False pParameters = False pInputs = False pOutputs = False pInfo = False pVersion = False pHelp = False pReadme = False pReadmeMd = False saveConfig = []
update :: Configuration -> String -> Either Error Configuration Source #
Parses configuration parameters from the content of a configuration file and updates the respective entries in the provided configuration.
verify :: Configuration -> Either Error () Source #
Verifies that a configuration does not contain invalid parameter combinations.
Specifcations
source :: Specification -> String Source #
Returns the TSLF source of a specification.
title :: Specification -> String Source #
Returns the title of a specification.
description :: Specification -> String Source #
Returns the description of a specification.
semantics :: Specification -> Semantics Source #
Returns the semantics of a specification.
target :: Specification -> Target Source #
Returns the target flag of a specification.
tags :: Specification -> [String] Source #
Returns the tag list of a specification.
parameters :: Specification -> [String] Source #
Returns the parameters of a specification.
signals :: Configuration -> Specification -> Either Error ([String], [String]) Source #
Returns the signals of a specification using the format as implied by the given configuration.
inputs :: Configuration -> Specification -> Either Error [String] Source #
Returns the input signals of a specification using the format as implied by the given configuration.
outputs :: Configuration -> Specification -> Either Error [String] Source #
Returns the ouputs signals of a specification using the format as implied by the given configuration.
symboltable :: Specification -> String Source #
Returns the symbol table of a specification in CSV format.
apply :: Configuration -> Specification -> Either Error String Source #
Applies the parameters of in the configuration and turns the given specification into the desired target format.
Fragment Detection
checkGR :: Specification -> Either Error Int Source #
Checks whether a given specification is in the Generalized
Reactivity fragment. If this is the case, the reactivity level is
returned. Otherwise, the check returns "-1
".