| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Language.Clafer.Intermediate.TypeSystem
- rootTClafer :: IType
 - claferTClafer :: IType
 - numeric :: IType -> Bool
 - isTInteger :: IType -> Bool
 - isTString :: IType -> Bool
 - isTBoolean :: IType -> Bool
 - getTClafer :: IClafer -> IType
 - getTClaferByUID :: UIDIClaferMap -> UID -> Maybe IType
 - getTClaferFromIExp :: UIDIClaferMap -> IExp -> Maybe IType
 - getDrefTMap :: IClafer -> Maybe IType
 - getDrefTMapByUID :: UIDIClaferMap -> UID -> Maybe IType
 - hierarchy :: Monad m => UIDIClaferMap -> UID -> m [IClafer]
 - hierarchyMap :: Monad m => UIDIClaferMap -> (IClafer -> a) -> UID -> m [a]
 - unionType :: IType -> [String]
 - fromUnionType :: [String] -> Maybe IType
 - (+++) :: IType -> IType -> IType
 - collapseUnion :: IType -> IType
 - intersection :: Monad m => UIDIClaferMap -> IType -> IType -> m (Maybe IType)
 - getIfThenElseType :: Monad m => UIDIClaferMap -> IType -> IType -> m (Maybe IType)
 - composition :: Monad m => UIDIClaferMap -> IType -> IType -> m (Maybe IType)
 - addHierarchy :: UIDIClaferMap -> IType -> IType
 - closure :: Monad m => UIDIClaferMap -> [String] -> m [String]
 - getTMaps :: UIDIClaferMap -> IType -> [IType]
 - getTClafers :: UIDIClaferMap -> IType -> [IType]
 - coerce :: IType -> IType -> IType
 - coerceRight :: IType -> IType -> Maybe IType
 
Documentation
>>>:m + Control.Monad.List
TClafer >>> let tClaferPerson = TClafer [ Person ] >>> let tClaferDOB = TClafer [ DOB ] >>> let tClaferStudent = TClafer [ Student, Person ] >>> let tClaferStudentID = TClafer [ StudentID ] >>> let tClaferEmployee = TClafer [ Employee, Person ] >>> let tClaferEmplID = TClafer [ EmplID ] >>> let tClaferAlice = TClafer [ Alice, Student, Person ] >>> let tClaferBob = TClafer [ Bob, Employee, Person ] >>> let tClaferAliceAndBob = TClafer [ AliceAndBob ] >>> let tClaferAliceAndBob2 = TClafer [ AliceAndBob2 ]
TUnion >>> let tUnionAliceBob = TUnion [ tClaferAlice, tClaferBob ]
TMap >>> let tMapDOB = TMap tClaferPerson tClaferDOB >>> let tDrefMapDOB = TMap tClaferDOB TInteger >>> let tMapStudentID = TMap tClaferStudent tClaferStudentID >>> let tDrefMapStudentID = TMap tClaferStudentID TString >>> let tMapEmplID = TMap tClaferEmplID tClaferEmplID >>> let tDrefMapEmplID = TMap tClaferEmplID TInteger >>> let tDrefMapAliceAndBob = TMap tClaferAliceAndBob tClaferPerson >>> let tDrefMapAliceAndBob2 = TMap tClaferAliceAndBob tUnionAliceBob
constants >>> let t1990 = TInteger >>> let t123Alice = TString >>> let t345 = TInteger
Sing
Obj
isTInteger :: IType -> Bool Source
isTBoolean :: IType -> Bool Source
getTClafer :: IClafer -> IType Source
Get TClafer for a given Clafer can only be called after inheritance resolver
getTClaferByUID :: UIDIClaferMap -> UID -> Maybe IType Source
Get TClafer for a given Clafer by its UID can only be called after inheritance resolver
getTClaferFromIExp :: UIDIClaferMap -> IExp -> Maybe IType Source
Get TClafer for a given Clafer by its UID can only be called after inheritance resolver
getDrefTMap :: IClafer -> Maybe IType Source
Get TMap for a given reference Clafer. Nothing for non-reference clafers. can only be called after inheritance resolver
getDrefTMapByUID :: UIDIClaferMap -> UID -> Maybe IType Source
Get TMap for a given Clafer by its UID. Nothing for non-reference clafers. can only be called after inheritance resolver
hierarchyMap :: Monad m => UIDIClaferMap -> (IClafer -> a) -> UID -> m [a] Source
fromUnionType :: [String] -> Maybe IType Source
(+++) :: IType -> IType -> IType Source
Union the two given types >>> TString +++ TString TString
Unions with only one type should be collapsed. >>> TUnion [TString] +++ TString TString
>>>TString +++ TIntegerTUnion {_un = [TString,TInteger]}
>>>TString +++ TUnion [TInteger]TUnion {_un = [TString,TInteger]}
>>>TUnion [TString] +++ TIntegerTUnion {_un = [TString,TInteger]}
>>>TUnion [TString] +++ TUnion[TInteger]TUnion {_un = [TString,TInteger]}
>>>TUnion [TString] +++ TUnion[TInteger] +++ TInteger +++ TStringTUnion {_un = [TString,TInteger]}
Should return TUnion {_un = [TClafer {_hi = [Alice,Student,Person]},TClafer {_hi = [Bob,Employee,Person]}]} >>> tClaferAlice +++ tClaferBob TClafer {_hi = [Alice,Student,Person,Bob,Employee]}
>>>tClaferAlice +++ tClaferAliceTClafer {_hi = ["Alice","Student","Person"]}
collapseUnion :: IType -> IType Source
intersection :: Monad m => UIDIClaferMap -> IType -> IType -> m (Maybe IType) Source
Intersection of two types. >>> runListT $ intersection undefined TString TString [Just TString]
>>>runListT $ intersection undefined TInteger TString[Nothing]
>>>runListT $ intersection undefined TInteger TReal[Just TReal]
>>>runListT $ intersection undefined tDrefMapDOB TInteger[Just TInteger]
Cannot assign a TReal to a map to TInteger >>> runListT $ intersection undefined tDrefMapDOB TReal [Nothing]
Cannot assign a TReal to a map to TInteger >>> runListT $ intersection undefined TReal tDrefMapDOB [Nothing]
getIfThenElseType :: Monad m => UIDIClaferMap -> IType -> IType -> m (Maybe IType) Source
This function is similar to intersection, but takes into account more ancestors to be able to combine
 clafers of different types, but with a common ancestor:
 Inputs:
 t1 is of type B
 t2 is of type C
 B : A
 C : A
 Outputs:
 the resulting type is: A, and the type combination is valid
composition :: Monad m => UIDIClaferMap -> IType -> IType -> m (Maybe IType) Source
Compute the type of sequential composition of two types >>> runListT $ composition undefined TString TString [Nothing]
>>>runListT $ composition undefined TInteger TString[Nothing]
>>>runListT $ composition undefined TInteger TReal[Nothing]
>>>runListT $ composition undefined tDrefMapDOB TInteger[Just (TMap {_so = TClafer {_hi = ["DOB"]}, _ta = TInteger})]
Cannot assign a TReal to a map to TInteger, should return [Nothing] >>> runListT $ composition undefined tDrefMapDOB TReal [Just (TMap {_so = TClafer {_hi = [DOB]}, _ta = TReal})]
Cannot assign a TInteger to a map to TInteger >>> runListT $ composition undefined TInteger tDrefMapDOB [Nothing]
Cannot assign a TReal to a map to TInteger >>> runListT $ composition undefined TReal tDrefMapDOB [Nothing]
>>>runListT $ composition undefined tDrefMapDOB (TMap TReal TString)[Just (TMap {_so = TClafer {_hi = ["DOB"]}, _ta = TString})]
The following should return [Nothing] >>> runListT $ composition undefined (TMap TString TReal) (TMap TInteger TString) [Just (TMap {_so = TString, _ta = TString})]
addHierarchy :: UIDIClaferMap -> IType -> IType Source
getTMaps :: UIDIClaferMap -> IType -> [IType] Source
getTClafers :: UIDIClaferMap -> IType -> [IType] Source
coerceRight :: IType -> IType -> Maybe IType Source
Return the type if it's possible to coerce the right type
coerceRight TString TInteger Nothing
>>>coerceRight TInteger TIntegerJust TInteger
>>>coerceRight TDouble TIntegerJust TDouble
>>>coerceRight TReal TDoubleJust TReal
>>>coerceRight TInteger TDoubleNothing
>>>coerceRight TDouble TRealNothing