clafer-0.4.4: Compiles Clafer models to other formats: Alloy, JavaScript, JSON, 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

ParseErr

Error generated by the parser

Fields

SemanticErr

Error generated by semantic analysis

Fields

Instances

Show p => Show (CErr p) Source # 

Methods

showsPrec :: Int -> CErr p -> ShowS #

show :: CErr p -> String #

showList :: [CErr p] -> ShowS #

ClaferErrPos p => Throwable (CErr p) Source # 

Methods

toErr :: CErr p -> Monad m -> ClaferT m ClaferErr Source #

data CErrs p Source #

Clafer keeps track of multiple errors.

Constructors

ClaferErrs 

Fields

Instances

Show p => Show (CErrs p) Source # 

Methods

showsPrec :: Int -> CErrs p -> ShowS #

show :: CErrs p -> String #

showList :: [CErrs p] -> ShowS #

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

ErrFragSpan 

Fields

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

ErrModelSpan 

Fields

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 #

Minimal complete definition

toErr

Methods

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

Instances

ClaferErrPos p => Throwable (CErr p) Source # 

Methods

toErr :: CErr p -> Monad m -> ClaferT m ClaferErr Source #

data Span Source #

Constructors

Span Pos Pos 

Instances

Eq Span Source # 

Methods

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

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

Data Span Source # 

Methods

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

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

toConstr :: Span -> Constr #

dataTypeOf :: Span -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Span Source # 

Methods

compare :: Span -> Span -> Ordering #

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

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

(>) :: Span -> Span -> Bool #

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

max :: Span -> Span -> Span #

min :: Span -> Span -> Span #

Read Span Source # 
Show Span Source # 

Methods

showsPrec :: Int -> Span -> ShowS #

show :: Span -> String #

showList :: [Span] -> ShowS #

Generic Span Source # 

Associated Types

type Rep Span :: * -> * #

Methods

from :: Span -> Rep Span x #

to :: Rep Span x -> Span #

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

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 #