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

Safe HaskellNone

Language.Clafer.Generator.Alloy

Description

Generates Alloy4.1 or 4.2 code for a Clafer model

Synopsis

Documentation

data Concat Source

representation of strings in chunks (for line/column numbering)

Constructors

CString String 
Concat 

Fields

srcPos :: IrTrace
 
nodes :: [Concat]
 

Instances

Eq Concat 
Show Concat 

data IrTrace Source

Constructors

IrPExp 

Fields

pUid :: String
 
LowerCard 

Fields

pUid :: String
 
isGroup :: Bool
 
UpperCard 

Fields

pUid :: String
 
isGroup :: Bool
 
ExactCard 

Fields

pUid :: String
 
isGroup :: Bool
 
NoTrace 

Instances

Eq IrTrace 
Show IrTrace 

mkConcat :: IrTrace -> String -> ConcatSource

flatten :: Concat -> StringSource

isNull :: Concat -> BoolSource

genModule :: ClaferArgs -> (IModule, GEnv) -> [(UID, Integer)] -> (Result, [(Span, IrTrace)])Source

Alloy code generation 07th Mayo 2012 Rafael Olaechea Added Logic to print a goal block in case there is at least one goal.

header :: ClaferArgs -> [(UID, Integer)] -> ConcatSource

genScope :: (UID, Integer) -> StringSource

mkMetric :: String -> Concat -> ConcatSource

genRelName :: String -> StringSource

genRel :: String -> IClafer -> String -> StringSource

genAlloyRel :: String -> String -> String -> StringSource

mkCard :: String -> Bool -> String -> (Integer, Integer) -> ConcatSource

genPathConst :: ClaferArgs -> String -> [String] -> IClafer -> ConcatSource

genCard :: String -> Maybe Interval -> ConcatSource

genCardCrude :: Maybe Interval -> StringSource

genInterval :: String -> Bool -> String -> Interval -> ConcatSource

cardConcat :: String -> Bool -> [Concat] -> ConcatSource

cardLowerConcat :: String -> Bool -> [Concat] -> ConcatSource

cardUpperConcat :: String -> Bool -> [Concat] -> ConcatSource

genExInteger :: String -> Interval -> Integer -> Maybe ResultSource

genPExp :: ClaferArgs -> [String] -> PExp -> ConcatSource

genPExp' :: ClaferArgs -> [String] -> PExp -> ConcatSource

genIFunExp :: String -> ClaferArgs -> [String] -> IExp -> ConcatSource

optBrArg :: ClaferArgs -> [String] -> PExp -> ConcatSource

brArg :: (a -> Concat) -> a -> ConcatSource

genOp :: Bool -> String -> [String]Source

adjustPExp :: [String] -> PExp -> PExpSource

adjustIExp :: [String] -> IExp -> IExpSource

adjustNav :: [String] -> IExp -> (IExp, [String])Source

genQuant :: IQuant -> StringSource

genDecl :: ClaferArgs -> [String] -> IDecl -> ConcatSource

genDisj :: Bool -> StringSource

data AlloyEnv Source

Constructors

AlloyEnv 

Fields

lineCol :: (LineNo, ColNo)
 
mapping :: [(Span, IrTrace)]
 

Instances

Eq AlloyEnv 
Show AlloyEnv 

addCode :: MonadState AlloyEnv m => String -> m ()Source

countLeading :: String -> String -> IntegerSource

countTrailing :: String -> String -> IntegerSource

lineno :: (Integer, ColNo) -> String -> (Integer, ColNo)Source