{-# LANGUAGE Safe #-}
module Types.Builtin (
ExpressionValue(..),
PrimitiveType(..),
boolRequiredValue,
charRequiredValue,
defaultCategories,
defaultCategoryDeps,
emptyType,
floatRequiredValue,
formattedRequiredValue,
intRequiredValue,
isPrimitiveType,
orderOptionalValue,
stringRequiredValue,
) where
import qualified Data.Map as Map
import qualified Data.Set as Set
import Base.GeneralType
import Base.Positional
import Types.TypeCategory
import Types.TypeInstance
defaultCategories :: CategoryMap c
defaultCategories :: CategoryMap c
defaultCategories = CategoryMap c
forall k a. Map k a
Map.empty
defaultCategoryDeps :: Set.Set CategoryName
defaultCategoryDeps :: Set CategoryName
defaultCategoryDeps = [CategoryName] -> Set CategoryName
forall a. Ord a => [a] -> Set a
Set.fromList []
boolRequiredValue :: ValueType
boolRequiredValue :: ValueType
boolRequiredValue = CategoryName -> ValueType
requiredSingleton CategoryName
BuiltinBool
stringRequiredValue :: ValueType
stringRequiredValue :: ValueType
stringRequiredValue = CategoryName -> ValueType
requiredSingleton CategoryName
BuiltinString
charRequiredValue :: ValueType
charRequiredValue :: ValueType
charRequiredValue = CategoryName -> ValueType
requiredSingleton CategoryName
BuiltinChar
intRequiredValue :: ValueType
intRequiredValue :: ValueType
intRequiredValue = CategoryName -> ValueType
requiredSingleton CategoryName
BuiltinInt
floatRequiredValue :: ValueType
floatRequiredValue :: ValueType
floatRequiredValue = CategoryName -> ValueType
requiredSingleton CategoryName
BuiltinFloat
formattedRequiredValue :: ValueType
formattedRequiredValue :: ValueType
formattedRequiredValue = CategoryName -> ValueType
requiredSingleton CategoryName
BuiltinFormatted
orderOptionalValue :: GeneralInstance -> ValueType
orderOptionalValue :: GeneralInstance -> ValueType
orderOptionalValue GeneralInstance
t = StorageType -> GeneralInstance -> ValueType
ValueType StorageType
OptionalValue (GeneralInstance -> ValueType) -> GeneralInstance -> ValueType
forall a b. (a -> b) -> a -> b
$ TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance CategoryName
BuiltinOrder ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [GeneralInstance
t])
emptyType :: ValueType
emptyType :: ValueType
emptyType = StorageType -> GeneralInstance -> ValueType
ValueType StorageType
OptionalValue GeneralInstance
forall a. Bounded a => a
minBound
data PrimitiveType =
PrimBool |
PrimString |
PrimChar |
PrimInt |
PrimFloat
deriving (PrimitiveType -> PrimitiveType -> Bool
(PrimitiveType -> PrimitiveType -> Bool)
-> (PrimitiveType -> PrimitiveType -> Bool) -> Eq PrimitiveType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrimitiveType -> PrimitiveType -> Bool
$c/= :: PrimitiveType -> PrimitiveType -> Bool
== :: PrimitiveType -> PrimitiveType -> Bool
$c== :: PrimitiveType -> PrimitiveType -> Bool
Eq,Int -> PrimitiveType -> ShowS
[PrimitiveType] -> ShowS
PrimitiveType -> String
(Int -> PrimitiveType -> ShowS)
-> (PrimitiveType -> String)
-> ([PrimitiveType] -> ShowS)
-> Show PrimitiveType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PrimitiveType] -> ShowS
$cshowList :: [PrimitiveType] -> ShowS
show :: PrimitiveType -> String
$cshow :: PrimitiveType -> String
showsPrec :: Int -> PrimitiveType -> ShowS
$cshowsPrec :: Int -> PrimitiveType -> ShowS
Show)
isPrimitiveType :: ValueType -> Bool
isPrimitiveType :: ValueType -> Bool
isPrimitiveType ValueType
t
| ValueType
t ValueType -> ValueType -> Bool
forall a. Eq a => a -> a -> Bool
== ValueType
boolRequiredValue = Bool
True
| ValueType
t ValueType -> ValueType -> Bool
forall a. Eq a => a -> a -> Bool
== ValueType
intRequiredValue = Bool
True
| ValueType
t ValueType -> ValueType -> Bool
forall a. Eq a => a -> a -> Bool
== ValueType
floatRequiredValue = Bool
True
| ValueType
t ValueType -> ValueType -> Bool
forall a. Eq a => a -> a -> Bool
== ValueType
charRequiredValue = Bool
True
| Bool
otherwise = Bool
False
data ExpressionValue =
OpaqueMulti String |
WrappedSingle String |
UnwrappedSingle String |
BoxedPrimitive PrimitiveType String |
UnboxedPrimitive PrimitiveType String |
LazySingle ExpressionValue
deriving (Int -> ExpressionValue -> ShowS
[ExpressionValue] -> ShowS
ExpressionValue -> String
(Int -> ExpressionValue -> ShowS)
-> (ExpressionValue -> String)
-> ([ExpressionValue] -> ShowS)
-> Show ExpressionValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExpressionValue] -> ShowS
$cshowList :: [ExpressionValue] -> ShowS
show :: ExpressionValue -> String
$cshow :: ExpressionValue -> String
showsPrec :: Int -> ExpressionValue -> ShowS
$cshowsPrec :: Int -> ExpressionValue -> ShowS
Show)