clafer-0.4.4: Compiles Clafer models to other formats: Alloy, JavaScript, JSON, HTML, Dot.

Safe HaskellNone
LanguageHaskell2010

Language.Clafer

Description

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
      iModule <- desugar ""
      compile iModule
      generate

Example of compiling a model consisting of one fragment:

compileOneFragment :: ClaferArgs -> InputModel -> Either ClaferErr CompilerResult
compileOneFragment args model =
  runClafer args $
    do
      addModuleFragment model
      parse
      iModule <- desugar "http://mydomain.org/mymodel.cfr"
      compile iModule
      generate
compileTwoFragments :: ClaferArgs -> InputModel -> InputModel -> Either ClaferErr [String]
compileTwoFragments args frag1 frag2 =
  runClafer args $
   do
     addModuleFragment frag1
     addModuleFragment frag2
     parse
     iModule <- desugar ""
     compile iModule
     generate

Use "throwErr" to halt execution:

runClafer args $
  when (notValid args) $ throwErr (ClaferErr "Invalid arguments.")

Use "catchErrs" to catch the errors.

Synopsis

Documentation

runCompiler :: Maybe URL -> ClaferArgs -> InputModel -> IO () Source #

Run the Clafer compiler. mURL = Nothing means compile the top-level module mURL = Just url means compile an imported module from the given url

addModuleFragment :: Monad m => InputModel -> ClaferT m () Source #

Add a new fragment to the model. Fragments should be added in order.

compile :: Monad m => IModule -> ClaferT m () Source #

Compiles the AST into IR.

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 -> String Source #

Splits the AST into their fragments, and generates the output for each fragment.

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] a Source #

Convenience

getEnv :: Monad m => ClaferT m ClaferEnv Source #

Get the ClaferEnv

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

Constructors

CompilerResult 

Fields

NoCompilerResult 

Fields

data Token Source #

Instances

Eq Token Source # 

Methods

(==) :: Token -> Token -> Bool #

(/=) :: Token -> Token -> Bool #

Ord Token Source # 

Methods

compare :: Token -> Token -> Ordering #

(<) :: Token -> Token -> Bool #

(<=) :: Token -> Token -> Bool #

(>) :: Token -> Token -> Bool #

(>=) :: Token -> Token -> Bool #

max :: Token -> Token -> Token #

min :: Token -> Token -> Token #

Show Token Source # 

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

data Module Source #

Instances

Eq Module Source # 

Methods

(==) :: Module -> Module -> Bool #

(/=) :: Module -> Module -> Bool #

Data Module Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Module -> c Module #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Module #

toConstr :: Module -> Constr #

dataTypeOf :: Module -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Module) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module) #

gmapT :: (forall b. Data b => b -> b) -> Module -> Module #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r #

gmapQ :: (forall d. Data d => d -> u) -> Module -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Module -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Module -> m Module #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module #

Ord Module Source # 
Read Module Source # 
Show Module Source # 
Generic Module Source # 

Associated Types

type Rep Module :: * -> * #

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

Spannable Module Source # 

Methods

getSpan :: Module -> Span Source #

Print Module Source # 

Methods

prt :: Int -> Module -> Doc Source #

prtList :: Int -> [Module] -> Doc Source #

type Rep Module Source # 
type Rep Module = D1 (MetaData "Module" "Language.Clafer.Front.AbsClafer" "clafer-0.4.4-XeevqZMpf33nmyUG80V8x" False) (C1 (MetaCons "Module" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Declaration]))))

data GEnv Source #

Instances

Eq GEnv Source # 

Methods

(==) :: GEnv -> GEnv -> Bool #

(/=) :: GEnv -> GEnv -> Bool #

Show GEnv Source # 

Methods

showsPrec :: Int -> GEnv -> ShowS #

show :: GEnv -> String #

showList :: [GEnv] -> ShowS #

data IModule Source #

each file contains exactly one mode. A module is a list of declarations

Instances

Eq IModule Source # 

Methods

(==) :: IModule -> IModule -> Bool #

(/=) :: IModule -> IModule -> Bool #

Data IModule Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IModule -> c IModule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IModule #

toConstr :: IModule -> Constr #

dataTypeOf :: IModule -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c IModule) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IModule) #

gmapT :: (forall b. Data b => b -> b) -> IModule -> IModule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IModule -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IModule -> r #

gmapQ :: (forall d. Data d => d -> u) -> IModule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IModule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IModule -> m IModule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IModule -> m IModule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IModule -> m IModule #

Ord IModule Source # 
Show IModule Source # 
ToJSON IModule Source # 
Plated IModule Source # 

data Pos Source #

Constructors

Pos Integer Integer 

Instances

Eq Pos Source # 

Methods

(==) :: Pos -> Pos -> Bool #

(/=) :: Pos -> Pos -> Bool #

Data Pos Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pos -> c Pos #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pos #

toConstr :: Pos -> Constr #

dataTypeOf :: Pos -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Pos) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pos) #

gmapT :: (forall b. Data b => b -> b) -> Pos -> Pos #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r #

gmapQ :: (forall d. Data d => d -> u) -> Pos -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pos -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pos -> m Pos #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pos -> m Pos #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pos -> m Pos #

Ord Pos Source # 

Methods

compare :: Pos -> Pos -> Ordering #

(<) :: Pos -> Pos -> Bool #

(<=) :: Pos -> Pos -> Bool #

(>) :: Pos -> Pos -> Bool #

(>=) :: Pos -> Pos -> Bool #

max :: Pos -> Pos -> Pos #

min :: Pos -> Pos -> Pos #

Read Pos Source # 
Show Pos Source # 

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Generic Pos Source # 

Associated Types

type Rep Pos :: * -> * #

Methods

from :: Pos -> Rep Pos x #

to :: Rep Pos x -> Pos #

type Rep Pos Source # 

data IrTrace Source #

Constructors

IrPExp 

Fields

LowerCard 

Fields

UpperCard 

Fields

ExactCard 

Fields

NoTrace