{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}
module Types.Builtin (
ExpressionValue(..),
PrimitiveType(..),
boolRequiredValue,
charRequiredValue,
emptyType,
floatRequiredValue,
formattedRequiredValue,
intRequiredValue,
isIdentifierRequiredValue,
isPointerRequiredValue,
isOpaqueMulti,
orderOptionalValue,
requiredStaticTypes,
stringRequiredValue,
) where
import qualified Data.Set as Set
import Base.GeneralType
import Base.MergeTree (reduceMergeTree)
import Base.Positional
import Types.TypeInstance
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 forall a b. (a -> b) -> a -> b
$ forall a. (Eq a, Ord a) => a -> GeneralType a
singleType forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance CategoryName
BuiltinOrder (forall a. [a] -> Positional a
Positional [GeneralInstance
t])
isPointerRequiredValue :: ValueType -> Bool
isPointerRequiredValue :: ValueType -> Bool
isPointerRequiredValue (ValueType StorageType
RequiredValue GeneralInstance
t) = Maybe TypeInstanceOrParam -> Bool
check forall a b. (a -> b) -> a -> b
$ GeneralInstance -> Maybe (T GeneralInstance)
extractSingle GeneralInstance
t where
check :: Maybe TypeInstanceOrParam -> Bool
check (Just (JustTypeInstance (TypeInstance CategoryName
BuiltinPointer (Positional [GeneralInstance
_])))) = Bool
True
check Maybe TypeInstanceOrParam
_ = Bool
False
extractSingle :: GeneralInstance -> Maybe (T GeneralInstance)
extractSingle = forall a b.
PreserveMerge a =>
([b] -> b) -> ([b] -> b) -> (T a -> b) -> a -> b
reduceMergeTree (forall a b. a -> b -> a
const forall a. Maybe a
Nothing) (forall a b. a -> b -> a
const forall a. Maybe a
Nothing) forall a. a -> Maybe a
Just
isPointerRequiredValue ValueType
_ = Bool
False
isIdentifierRequiredValue :: ValueType -> Bool
isIdentifierRequiredValue :: ValueType -> Bool
isIdentifierRequiredValue (ValueType StorageType
RequiredValue GeneralInstance
t) = Maybe TypeInstanceOrParam -> Bool
check forall a b. (a -> b) -> a -> b
$ GeneralInstance -> Maybe (T GeneralInstance)
extractSingle GeneralInstance
t where
check :: Maybe TypeInstanceOrParam -> Bool
check (Just (JustTypeInstance (TypeInstance CategoryName
BuiltinIdentifier (Positional [GeneralInstance
_])))) = Bool
True
check Maybe TypeInstanceOrParam
_ = Bool
False
extractSingle :: GeneralInstance -> Maybe (T GeneralInstance)
extractSingle = forall a b.
PreserveMerge a =>
([b] -> b) -> ([b] -> b) -> (T a -> b) -> a -> b
reduceMergeTree (forall a b. a -> b -> a
const forall a. Maybe a
Nothing) (forall a b. a -> b -> a
const forall a. Maybe a
Nothing) forall a. a -> Maybe a
Just
isIdentifierRequiredValue ValueType
_ = Bool
False
emptyType :: ValueType
emptyType :: ValueType
emptyType = StorageType -> GeneralInstance -> ValueType
ValueType StorageType
OptionalValue forall a. Bounded a => a
minBound
data PrimitiveType =
PrimBool |
PrimChar |
PrimInt |
PrimFloat |
PrimString |
PrimPointer |
PrimIdentifier
deriving (PrimitiveType -> PrimitiveType -> Bool
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
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)
data ExpressionValue =
OpaqueMulti String |
WrappedSingle String |
UnwrappedSingle String |
BoxedPrimitive PrimitiveType String |
UnboxedPrimitive PrimitiveType String |
LazySingle ExpressionValue
deriving (Int -> ExpressionValue -> ShowS
[ExpressionValue] -> ShowS
ExpressionValue -> String
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)
isOpaqueMulti :: ExpressionValue -> Bool
isOpaqueMulti :: ExpressionValue -> Bool
isOpaqueMulti (OpaqueMulti String
_) = Bool
True
isOpaqueMulti ExpressionValue
_ = Bool
False
requiredStaticTypes :: Set.Set CategoryName
#ifdef darwin_HOST_OS
requiredStaticTypes = Set.fromList [
BuiltinBool,
BuiltinChar,
BuiltinInt,
BuiltinFloat,
BuiltinPointer,
BuiltinIdentifier
]
#else
requiredStaticTypes :: Set CategoryName
requiredStaticTypes = forall a. Set a
Set.empty
#endif