Safe Haskell | None |
---|
Top-level interface to the Clafer compiler
Normal usage:
t :: InputModel -> InputModel -> Either [ClaferErr] [String] t a b = runClafer defaultClaferArgs $ do addModuleFragment a addModuleFragment b parse compile generateFragments
Example of compiling a model consisting of one fragment:
compileOneFragment :: ClaferArgs -> InputModel -> Either ClaferErr CompilerResult compileOneFragment args model = runClafer args $ do addModuleFragment model parse compile generate
Use generateFragments instead to generate output based on their fragments.
compileTwoFragments :: ClaferArgs -> InputModel -> InputModel -> Either ClaferErr [String] compileTwoFragments args frag1 frag2 = runClafer args $ do addModuleFragment frag1 addModuleFragment frag2 parse compile generateFragments
Use throwErr to halt execution:
runClafer args $ when (notValid args) $ throwErr (ClaferErr "Invalid arguments.")
Use catchErrs to catch the errors.
- addModuleFragment :: Monad m => InputModel -> ClaferT m ()
- compile :: Monad m => ClaferT m ()
- parse :: Monad m => ClaferT m ()
- generate :: Monad m => ClaferT m (Map ClaferMode CompilerResult)
- generateHtml :: ClaferEnv -> Module -> String
- generateFragments :: Monad m => ClaferT m [String]
- runClaferT :: Monad m => ClaferArgs -> ClaferT m a -> m (Either [ClaferErr] a)
- runClafer :: ClaferArgs -> ClaferM a -> Either [ClaferErr] a
- type ClaferErr = CErr ErrPos
- getEnv :: Monad m => ClaferT m ClaferEnv
- putEnv :: Monad m => ClaferEnv -> ClaferT m ()
- data CompilerResult
- = CompilerResult {
- extension :: String
- outputCode :: String
- statistics :: String
- claferEnv :: ClaferEnv
- mappingToAlloy :: [(Span, IrTrace)]
- stringMap :: Map Int String
- scopesList :: [(UID, Integer)]
- | NoCompilerResult {
- reason :: String
- = CompilerResult {
- claferIRXSD :: String
- type VerbosityL = Int
- type InputModel = String
- data Token
- data Module
- data GEnv
- data IModule
- voidf :: Monad m => m t -> m ()
- data ClaferEnv = ClaferEnv {
- args :: ClaferArgs
- modelFrags :: [String]
- cAst :: Maybe Module
- cIr :: Maybe (IModule, GEnv, Bool)
- frags :: [Pos]
- irModuleTrace :: Map Span [Ir]
- astModuleTrace :: Map Span [Ast]
- getIr :: Monad m => ClaferT m (IModule, GEnv, Bool)
- getAst :: Monad m => ClaferT m Module
- makeEnv :: ClaferArgs -> ClaferEnv
- data Pos = Pos Integer Integer
- data IrTrace
- module Language.Clafer.ClaferArgs
- module Language.Clafer.Front.ErrM
Documentation
addModuleFragment :: Monad m => InputModel -> ClaferT m ()Source
Add a new fragment to the model. Fragments should be added in order.
parse :: Monad m => ClaferT m ()Source
Parses the model into AST. Adding more fragments beyond this point will have no effect.
generate :: Monad m => ClaferT m (Map ClaferMode CompilerResult)Source
Generates outputs for the given IR.
generateHtml :: ClaferEnv -> Module -> StringSource
Splits the AST into their fragments, and generates the output for each fragment.
generateFragments :: Monad m => ClaferT m [String]Source
Splits the IR into their fragments, and generates the output for each fragment. | Might not generate the entire output (for example, Alloy scope and run commands) because | they do not belong in fragments.
runClaferT :: Monad m => ClaferArgs -> ClaferT m a -> m (Either [ClaferErr] a)Source
Uses the ErrorT convention: | Left is for error (a string containing the error message) | Right is for success (with the result)
runClafer :: ClaferArgs -> ClaferM a -> Either [ClaferErr] aSource
Convenience
putEnv :: Monad m => ClaferEnv -> ClaferT m ()Source
Set the ClaferEnv. Remember to set the env after every change.
data CompilerResult Source
Result of generation for a given mode
CompilerResult | |
| |
NoCompilerResult | |
|
Show CompilerResult |
claferIRXSD :: StringSource
The XML Schema of the IR
type VerbosityL = IntSource
type InputModel = StringSource
each file contains exactly one mode. A module is a list of declarations
ClaferEnv | |
|
Show ClaferEnv |
makeEnv :: ClaferArgs -> ClaferEnvSource
Pos Integer Integer |
module Language.Clafer.ClaferArgs
module Language.Clafer.Front.ErrM