module ProjectM36.DataTypes.Primitive where
import ProjectM36.Base
primitiveTypeConstructorMapping :: TypeConstructorMapping
primitiveTypeConstructorMapping :: TypeConstructorMapping
primitiveTypeConstructorMapping = (TypeConstructorDef, [DataConstructorDef])
boolMapping forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map (\(TypeVarName
name, AtomType
aType) ->
(TypeVarName -> AtomType -> TypeConstructorDef
PrimitiveTypeConstructorDef TypeVarName
name AtomType
aType, [])) [(TypeVarName, AtomType)]
prims
where
prims :: [(TypeVarName, AtomType)]
prims = [(TypeVarName
"Integer", AtomType
IntegerAtomType),
(TypeVarName
"Int", AtomType
IntAtomType),
(TypeVarName
"Text", AtomType
TextAtomType),
(TypeVarName
"Double", AtomType
DoubleAtomType),
(TypeVarName
"UUID", AtomType
UUIDAtomType),
(TypeVarName
"ByteString", AtomType
ByteStringAtomType),
(TypeVarName
"DateTime", AtomType
DateTimeAtomType),
(TypeVarName
"Day", AtomType
DayAtomType)
]
boolMapping :: (TypeConstructorDef, [DataConstructorDef])
boolMapping = (TypeVarName -> AtomType -> TypeConstructorDef
PrimitiveTypeConstructorDef TypeVarName
"Bool" AtomType
BoolAtomType,
[TypeVarName -> [DataConstructorDefArg] -> DataConstructorDef
DataConstructorDef TypeVarName
"True" [],
TypeVarName -> [DataConstructorDefArg] -> DataConstructorDef
DataConstructorDef TypeVarName
"False" []])
intTypeConstructor :: TypeConstructor
intTypeConstructor :: TypeConstructor
intTypeConstructor = forall a. TypeVarName -> AtomType -> TypeConstructorBase a
PrimitiveTypeConstructor TypeVarName
"Int" AtomType
IntAtomType
doubleTypeConstructor :: TypeConstructor
doubleTypeConstructor :: TypeConstructor
doubleTypeConstructor = forall a. TypeVarName -> AtomType -> TypeConstructorBase a
PrimitiveTypeConstructor TypeVarName
"Double" AtomType
DoubleAtomType
textTypeConstructor :: TypeConstructor
textTypeConstructor :: TypeConstructor
textTypeConstructor = forall a. TypeVarName -> AtomType -> TypeConstructorBase a
PrimitiveTypeConstructor TypeVarName
"Text" AtomType
TextAtomType
dayTypeConstructor :: TypeConstructor
dayTypeConstructor :: TypeConstructor
dayTypeConstructor = forall a. TypeVarName -> AtomType -> TypeConstructorBase a
PrimitiveTypeConstructor TypeVarName
"Day" AtomType
DayAtomType
dateTimeTypeConstructor :: TypeConstructor
dateTimeTypeConstructor :: TypeConstructor
dateTimeTypeConstructor = forall a. TypeVarName -> AtomType -> TypeConstructorBase a
PrimitiveTypeConstructor TypeVarName
"DateTime" AtomType
DayAtomType
uUIDTypeConstructor :: TypeConstructor
uUIDTypeConstructor :: TypeConstructor
uUIDTypeConstructor = forall a. TypeVarName -> AtomType -> TypeConstructorBase a
PrimitiveTypeConstructor TypeVarName
"UUID" AtomType
UUIDAtomType
atomTypeForAtom :: Atom -> AtomType
atomTypeForAtom :: Atom -> AtomType
atomTypeForAtom (IntAtom Int
_) = AtomType
IntAtomType
atomTypeForAtom (IntegerAtom Integer
_) = AtomType
IntegerAtomType
atomTypeForAtom (ScientificAtom Scientific
_) = AtomType
ScientificAtomType
atomTypeForAtom (DoubleAtom Double
_) = AtomType
DoubleAtomType
atomTypeForAtom (TextAtom TypeVarName
_) = AtomType
TextAtomType
atomTypeForAtom (DayAtom Day
_) = AtomType
DayAtomType
atomTypeForAtom (DateTimeAtom UTCTime
_) = AtomType
DateTimeAtomType
atomTypeForAtom (ByteStringAtom ByteString
_) = AtomType
ByteStringAtomType
atomTypeForAtom (BoolAtom Bool
_) = AtomType
BoolAtomType
atomTypeForAtom (UUIDAtom UUID
_) = AtomType
UUIDAtomType
atomTypeForAtom (RelationAtom (Relation Attributes
attrs RelationTupleSet
_)) = Attributes -> AtomType
RelationAtomType Attributes
attrs
atomTypeForAtom (ConstructedAtom TypeVarName
_ AtomType
aType [Atom]
_) = AtomType
aType
atomTypeForAtom (RelationalExprAtom RelationalExpr
_) = AtomType
RelationalExprAtomType
atomTypeForAtom (SubrelationFoldAtom Relation
_ TypeVarName
_) = AtomType -> AtomType
SubrelationFoldAtomType (TypeVarName -> AtomType
TypeVariableType TypeVarName
"a")