clafer-0.3.10: clafer compiles Clafer models to other formats, such as Alloy, XML, HTML, Dot.

Safe HaskellNone
LanguageHaskell2010

Language.ClaferT

Description

This is in a separate module from the module Language.Clafer so that other modules that require ClaferEnv can just import this module without all the parsingcompilinegenerating functionality.

Synopsis

Documentation

irModuleTrace :: ClaferEnv -> Map Span [Ir] Source

This simulates a field in the ClaferEnv that will always recompute the map, since the IR always changes and the map becomes obsolete

uidIClaferMap :: ClaferEnv -> UIDIClaferMap Source

This simulates a field in the ClaferEnv that will always recompute the map, since the IR always changes and the map becomes obsolete maps from a UID to an IClafer with the given UID

type ClaferM = ClaferT Identity Source

Monad for using Clafer.

type ClaferT m = ExceptT ClaferErrs (StateT ClaferEnv m) Source

Monad Transformer for using Clafer.

data CErr p Source

Possible errors that can occur when using Clafer | Generate errors using throwErr/throwErrs:

Constructors

ClaferErr

Generic error

Fields

msg :: String
 
ParseErr

Error generated by the parser

Fields

pos :: p

Position of the error

msg :: String
 
SemanticErr

Error generated by semantic analysis

Fields

pos :: p

Position of the error

msg :: String
 

Instances

Show p => Show (CErr p) 
ClaferErrPos p => Throwable (CErr p) 

data CErrs p Source

Clafer keeps track of multiple errors.

Constructors

ClaferErrs 

Fields

errs :: [CErr p]
 

Instances

Show p => Show (CErrs p) 

data ErrPos Source

Constructors

ErrPos 

Fields

fragId :: Int

The fragment where the error occurred.

fragPos :: Pos

Error positions are relative to their fragments. | For example an error at (Pos 2 3) means line 2 column 3 of the fragment, not the entire model.

modelPos :: Pos

The error position relative to the model.

Instances

data PartialErrPos Source

The full ErrPos requires lots of information that needs to be consistent. Every time we throw an error, | we need BOTH the (fragId, fragPos) AND modelPos. This makes it easier for developers using ClaferT so they | only need to provide part of the information and the rest is automatically calculated. The code using | ClaferT is more concise and less error-prone. | | modelPos <- modelPosFromFragPos fragdId fragPos | throwErr $ ParserErr (ErrPos fragId fragPos modelPos) | | vs | | throwErr $ ParseErr (ErrFragPos fragId fragPos) | | Hopefully making the error handling easier will make it more universal.

Constructors

ErrFragPos

Position relative to the start of the fragment. Will calculate model position automatically. | fragId starts at 0 | The position is relative to the start of the fragment.

Fields

pFragId :: Int
 
pFragPos :: Pos
 
ErrFragSpan 

Fields

pFragId :: Int
 
pFragSpan :: Span
 
ErrModelPos

Position relative to the start of the complete model. Will calculate fragId and fragPos automatically. | The position is relative to the entire complete model.

Fields

pModelPos :: Pos
 
ErrModelSpan 

Fields

pModelSpan :: Span
 

Instances

throwErrs :: (Monad m, Throwable t) => [t] -> ClaferT m a Source

Throw many errors.

throwErr :: (Monad m, Throwable t) => t -> ClaferT m a Source

Throw one error.

catchErrs :: Monad m => ClaferT m a -> ([ClaferErr] -> ClaferT m a) -> ClaferT m a Source

Catch errors

getEnv :: Monad m => ClaferT m ClaferEnv Source

Get the ClaferEnv

getsEnv :: Monad m => (ClaferEnv -> a) -> ClaferT m a Source

modifyEnv :: Monad m => (ClaferEnv -> ClaferEnv) -> ClaferT m () Source

Modify the ClaferEnv

putEnv :: Monad m => ClaferEnv -> ClaferT m () Source

Set the ClaferEnv. Remember to set the env after every change.

runClafer :: ClaferArgs -> ClaferM a -> Either [ClaferErr] a Source

Convenience

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)

class Throwable t where Source

Methods

toErr :: t -> Monad m => ClaferT m ClaferErr Source

Instances

ClaferErrPos p => Throwable (CErr p) 

data Span Source

Constructors

Span Pos Pos 

data Pos Source

Constructors

Pos Integer Integer