Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type Result = String
- transIdent :: PosIdent -> String
- mkIdent :: String -> PosIdent
- mkInteger :: Read a => PosInteger -> a
- type Ident = PosIdent
- getSuper :: IClafer -> [String]
- getReference :: IClafer -> [String]
- getSuperAndReference :: IClafer -> [String]
- getSuperId :: PExp -> String
- isEqClaferId :: String -> IClafer -> Bool
- mkPLClaferId :: CName -> Bool -> ClaferBinding -> PExp
- pExpDefPidPos :: IExp -> PExp
- pExpDefPid :: Span -> IExp -> PExp
- pExpDef :: String -> Span -> IExp -> PExp
- isParent :: PExp -> Bool
- isClaferName :: PExp -> Bool
- isClaferName' :: PExp -> Bool
- getClaferName :: PExp -> String
- isTopLevel :: IClafer -> Bool
- elemToClafer :: IElement -> Maybe IClafer
- toClafers :: [IElement] -> [IClafer]
- type UIDIClaferMap = StringMap IClafer
- createUidIClaferMap :: IModule -> UIDIClaferMap
- findIClafer :: UIDIClaferMap -> UID -> Maybe IClafer
- findHierarchy :: (IClafer -> [String]) -> UIDIClaferMap -> IClafer -> [IClafer]
- mapHierarchy :: (IClafer -> b) -> (IClafer -> [String]) -> UIDIClaferMap -> IClafer -> [b]
- findUIDinSupers :: UIDIClaferMap -> UID -> IClafer -> Maybe IClafer
- findUIDinParents :: UIDIClaferMap -> UID -> IClafer -> Maybe IClafer
- data NestedInheritanceMatch = NestedInheritanceMatch {}
- isProperNesting :: UIDIClaferMap -> Maybe NestedInheritanceMatch -> Bool
- isProperRefinement :: UIDIClaferMap -> Maybe NestedInheritanceMatch -> (Bool, Bool, Bool)
- isRedefinition :: Maybe NestedInheritanceMatch -> Bool
- matchNestedInheritance :: UIDIClaferMap -> IClafer -> Maybe NestedInheritanceMatch
- apply :: forall t t1. (t -> t1) -> t -> (t, t1)
- bfs :: forall b b1. (b1 -> (b, [b1])) -> [b1] -> [b]
- toNodeShallow :: IClafer -> (IClafer, [IClafer])
- getSubclafers :: [IElement] -> [IClafer]
- bfsClafers :: [IClafer] -> [IClafer]
- lurry :: forall t t1. ([t1] -> t) -> t1 -> t1 -> t
- fst3 :: forall t t1 t2. (t, t1, t2) -> t
- snd3 :: forall t t1 t2. (t, t1, t2) -> t1
- trd3 :: forall t t1 t2. (t, t1, t2) -> t2
- toTriple :: forall t t1 t2. t -> (t1, t2) -> (t, t1, t2)
- toMTriple :: forall t t1 t2. t -> (t1, t2) -> Maybe (t, t1, t2)
- iNot :: String
- iCSet :: String
- iMin :: String
- iGMax :: String
- iGMin :: String
- iSumSet :: String
- iProdSet :: String
- unOps :: [String]
- iIff :: String
- iImpl :: String
- iOr :: String
- iXor :: String
- iAnd :: String
- logBinOps :: [String]
- iLt :: String
- iGt :: String
- iEq :: String
- iLte :: String
- iGte :: String
- iNeq :: String
- iIn :: String
- iNin :: String
- relGenBinOps :: [String]
- relSetBinOps :: [String]
- relBinOps :: [String]
- iPlus :: String
- iSub :: String
- iMul :: String
- iDiv :: String
- iRem :: String
- iSumSet' :: String
- arithBinOps :: [String]
- iUnion :: String
- iDifference :: String
- iIntersection :: String
- iDomain :: String
- iRange :: String
- iJoin :: String
- setBinOps :: [String]
- binOps :: [String]
- iIfThenElse :: String
- mkIFunExp :: String -> [IExp] -> IExp
- toLowerS :: String -> String
- rootIdent :: String
- rootUID :: String
- thisIdent :: String
- parentIdent :: String
- refIdent :: String
- childrenIdent :: String
- specialNames :: [String]
- isSpecial :: String -> Bool
- stringType :: String
- intType :: String
- integerType :: String
- realType :: String
- booleanType :: String
- baseClafer :: String
- modSep :: String
- primitiveTypes :: [String]
- isPrimitive :: String -> Bool
- keywordIdents :: [String]
- data GEnv = GEnv {
- identCountMap :: Map String Int
- expCount :: Int
- stable :: Map UID [[UID]]
- sClafers :: [IClafer]
- uidClaferMap :: UIDIClaferMap
- voidf :: Monad m => m t -> m ()
- safeTail :: [a] -> [a]
Documentation
transIdent :: PosIdent -> String Source
mkInteger :: Read a => PosInteger -> a Source
getReference :: IClafer -> [String] Source
Returns only [] or [_]
getSuperAndReference :: IClafer -> [String] Source
Returns only [] or [_] or [_, _]
getSuperId :: PExp -> String Source
isEqClaferId :: String -> IClafer -> Bool Source
mkPLClaferId :: CName -> Bool -> ClaferBinding -> PExp Source
pExpDefPidPos :: IExp -> PExp Source
pExpDefPid :: Span -> IExp -> PExp Source
isClaferName :: PExp -> Bool Source
isClaferName' :: PExp -> Bool Source
getClaferName :: PExp -> String Source
isTopLevel :: IClafer -> Bool Source
elemToClafer :: IElement -> Maybe IClafer Source
type UIDIClaferMap = StringMap IClafer Source
findIClafer :: UIDIClaferMap -> UID -> Maybe IClafer Source
findHierarchy :: (IClafer -> [String]) -> UIDIClaferMap -> IClafer -> [IClafer] Source
Finds all super clafers according to sFun
mapHierarchy :: (IClafer -> b) -> (IClafer -> [String]) -> UIDIClaferMap -> IClafer -> [b] Source
Finds hierarchy and transforms each element
findUIDinSupers :: UIDIClaferMap -> UID -> IClafer -> Maybe IClafer Source
traverse the inheritance hierarchy upwards to find a clafer with the given uidToFind
findUIDinParents :: UIDIClaferMap -> UID -> IClafer -> Maybe IClafer Source
traverse the containment hierarchy upwards to find a clafer with the given uidToFind
data NestedInheritanceMatch Source
NestedInheritanceMatch | |
|
isProperNesting :: UIDIClaferMap -> Maybe NestedInheritanceMatch -> Bool Source
assumes that isProperNesting m == True
This represents a match of this shape
superClafersParent / <> ?1| * parentsSuperClafer / [=] superClafer --*-> superClafersTarget *| parentClafer | |?2 <> *| [=] targetsSuperClafer * | / | *| headClafer -----*-----> targetClafer
The clafers are obtained by navigating from the headClafer by following the links marked by * The link marked by ?1 is checked for correctness of nesting (isProperNesting): - _uid parentsSuperClafer == _parentUID superClafer The link marked by ?2 is checked for correctness of redefinition (isProperRefinement): - proper subtyping, bag to set, proper cardinality restriction Redefinition occurs when the name of headClafer is the same as the name of superClafer (isProperRedefinition): - isProperNesting && isProperRefinement && (_ident headClafer) == (_ident superClafer)
isProperRefinement :: UIDIClaferMap -> Maybe NestedInheritanceMatch -> (Bool, Bool, Bool) Source
assumes that isProperNesting m == True and isProperRefinement m == (True, True, True)
:: Maybe NestedInheritanceMatch | |
-> Bool | whether the name of headClafer is the same as superClafer |
try to match the nested inheritance pattern ^ only available after the parentUIDs were computed
toNodeShallow :: IClafer -> (IClafer, [IClafer]) Source
getSubclafers :: [IElement] -> [IClafer] Source
bfsClafers :: [IClafer] -> [IClafer] Source
relGenBinOps :: [String] Source
relSetBinOps :: [String] Source
arithBinOps :: [String] Source
specialNames :: [String] Source
primitiveTypes :: [String] Source
isPrimitive :: String -> Bool Source
keywordIdents :: [String] Source
reserved keywords which cannot be used as clafer identifiers
GEnv | |
|