| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
IR.Types.Type
Description
Definitions of and related to the sslang IR's type system.
Synopsis
- data Type
- data Constraint = CTrue
- data SchemeOf t = Forall (Set TVarId) Constraint t
- unScheme :: SchemeOf t -> t
- forall :: (Functor l, Foldable l) => l TVarId -> t -> SchemeOf t
- schemeOf :: Type -> Scheme
- newtype Scheme = Scheme (SchemeOf Type)
- data Annotation
- newtype Annotations = Annotations [Annotation]
- unAnnotations :: Annotations -> [Annotation]
- fromAnnotations :: Annotations -> Type
- class HasType a where
- pattern Hole :: Type
- pattern Arrow :: Type -> Type -> Type
- unfoldArrow :: Type -> ([Type], Type)
- foldArrow :: ([Type], Type) -> Type
- pattern Unit :: Type
- pattern Ref :: Type -> Type
- pattern List :: Type -> Type
- pattern Time :: Type
- pattern I64 :: Type
- pattern U64 :: Type
- pattern I32 :: Type
- pattern U32 :: Type
- pattern I16 :: Type
- pattern U16 :: Type
- pattern I8 :: Type
- pattern U8 :: Type
- isInt :: Type -> Bool
- isUInt :: Type -> Bool
- isNum :: Type -> Bool
- tuple :: [Type] -> Type
- tupleId :: Identifiable v => Int -> v
- type Kind = Int
- builtinKinds :: Map TConId Kind
Documentation
Encoding of sslang types.
Structurally speaking, these are very simple. Types are either type variables or type constructors applied to some other types.
Builtin types (and type constructors) include Arrow, Unit, Ref, List,
and various sizes of tuples; for convenience, those are defined elsewhere using
the GHC PatternSynonyms extension.
Constructors
| TCon TConId [Type] | Type constructor, applied to zero or more types |
| TVar TVarId | Type variable (may be implicitly quantified) |
Instances
| Eq Type Source # | |
| Data Type Source # | |
Defined in IR.Types.Type Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type -> c Type # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Type # dataTypeOf :: Type -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Type) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type) # gmapT :: (forall b. Data b => b -> b) -> Type -> Type # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r # gmapQ :: (forall d. Data d => d -> u) -> Type -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Type -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Type -> m Type # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type # | |
| Show Type Source # | |
| Pretty Type Source # | |
Defined in IR.Types.Type | |
| Dumpy Type Source # | |
| HasType Type Source # | |
| HasFreeVars Type TVarId Source # | |
| Pretty (Alt Type) | |
| Pretty (Expr Type) | |
| Pretty (Program Type) | Pretty Typeclass: pretty print the IR Adds * indentation and line breaks * some parens (not minimal parens, but fewer than around every node) Omits * let _ = * type annotations Reverts * curried funcs of one arg back to multiple arg funcs |
data Constraint Source #
Constraints on a type scheme.
For now, we only support trivial constraints.
Constructors
| CTrue | The trivial constraint, i.e., always satisfied. |
Instances
| Eq Constraint Source # | |
Defined in IR.Types.Type | |
| Data Constraint Source # | |
Defined in IR.Types.Type Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Constraint -> c Constraint # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Constraint # toConstr :: Constraint -> Constr # dataTypeOf :: Constraint -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Constraint) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Constraint) # gmapT :: (forall b. Data b => b -> b) -> Constraint -> Constraint # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Constraint -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Constraint -> r # gmapQ :: (forall d. Data d => d -> u) -> Constraint -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Constraint -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Constraint -> m Constraint # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Constraint -> m Constraint # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Constraint -> m Constraint # | |
| Show Constraint Source # | |
Defined in IR.Types.Type Methods showsPrec :: Int -> Constraint -> ShowS # show :: Constraint -> String # showList :: [Constraint] -> ShowS # | |
Schemes quantify over Type variables and impose some Constraint.
SchemeOf is implemented as functor over some kind of type so we can easily
substitute in Type vs UType when performing type inference/unification.
Constructors
| Forall (Set TVarId) Constraint t |
Instances
| Functor SchemeOf Source # | |
| Foldable SchemeOf Source # | |
Defined in IR.Types.Type Methods fold :: Monoid m => SchemeOf m -> m # foldMap :: Monoid m => (a -> m) -> SchemeOf a -> m # foldMap' :: Monoid m => (a -> m) -> SchemeOf a -> m # foldr :: (a -> b -> b) -> b -> SchemeOf a -> b # foldr' :: (a -> b -> b) -> b -> SchemeOf a -> b # foldl :: (b -> a -> b) -> b -> SchemeOf a -> b # foldl' :: (b -> a -> b) -> b -> SchemeOf a -> b # foldr1 :: (a -> a -> a) -> SchemeOf a -> a # foldl1 :: (a -> a -> a) -> SchemeOf a -> a # elem :: Eq a => a -> SchemeOf a -> Bool # maximum :: Ord a => SchemeOf a -> a # minimum :: Ord a => SchemeOf a -> a # | |
| Traversable SchemeOf Source # | |
| Eq t => Eq (SchemeOf t) Source # | |
| Data t => Data (SchemeOf t) Source # | |
Defined in IR.Types.Type Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SchemeOf t -> c (SchemeOf t) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SchemeOf t) # toConstr :: SchemeOf t -> Constr # dataTypeOf :: SchemeOf t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (SchemeOf t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (SchemeOf t)) # gmapT :: (forall b. Data b => b -> b) -> SchemeOf t -> SchemeOf t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SchemeOf t -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SchemeOf t -> r # gmapQ :: (forall d. Data d => d -> u) -> SchemeOf t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SchemeOf t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SchemeOf t -> m (SchemeOf t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SchemeOf t -> m (SchemeOf t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SchemeOf t -> m (SchemeOf t) # | |
| Show t => Show (SchemeOf t) Source # | |
forall :: (Functor l, Foldable l) => l TVarId -> t -> SchemeOf t Source #
Construct a scheme with quantified type variables and a trivial constraint.
schemeOf :: Type -> Scheme Source #
Construct a scheme from all free type variables and a trivial constraint.
Schemes over Type.
Instances
| Eq Scheme Source # | |
| Data Scheme Source # | |
Defined in IR.Types.Type Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Scheme -> c Scheme # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Scheme # toConstr :: Scheme -> Constr # dataTypeOf :: Scheme -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Scheme) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scheme) # gmapT :: (forall b. Data b => b -> b) -> Scheme -> Scheme # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r # gmapQ :: (forall d. Data d => d -> u) -> Scheme -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Scheme -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme # | |
| Show Scheme Source # | |
| Pretty Scheme Source # | |
Defined in IR.Types.Type | |
| Dumpy Scheme Source # | |
| HasType Scheme Source # | |
| HasFreeVars Scheme TVarId Source # | |
data Annotation Source #
An annotation records the annotated portion of a pattern.
Constructors
| AnnType Type | A basic |
| AnnDCon DConId [Annotation] | Annotations collected from patterns |
| AnnArrows [Annotation] Annotation | Annotations collected from fun args |
Instances
| Eq Annotation Source # | |
Defined in IR.Types.Type | |
| Data Annotation Source # | |
Defined in IR.Types.Type Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Annotation -> c Annotation # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Annotation # toConstr :: Annotation -> Constr # dataTypeOf :: Annotation -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Annotation) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Annotation) # gmapT :: (forall b. Data b => b -> b) -> Annotation -> Annotation # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Annotation -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Annotation -> r # gmapQ :: (forall d. Data d => d -> u) -> Annotation -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Annotation -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation # | |
| Show Annotation Source # | |
Defined in IR.Types.Type Methods showsPrec :: Int -> Annotation -> ShowS # show :: Annotation -> String # showList :: [Annotation] -> ShowS # | |
| Pretty Annotation Source # | |
Defined in IR.Types.Type | |
| Dumpy Annotation Source # | |
Defined in IR.Types.Type Methods dumpy :: Annotation -> Doc ann Source # | |
newtype Annotations Source #
Expressions are annotated with a (potentially empty) list of Annotation.
Constructors
| Annotations [Annotation] |
Instances
unAnnotations :: Annotations -> [Annotation] Source #
Unwrap the Annotations data constructor.
fromAnnotations :: Annotations -> Type Source #
Unroll an annotation into a type. FIXME: get rid of this.
pattern List :: Type -> Type Source #
The builtin list Type, created using list syntax, e.g., [a, b].
tupleId :: Identifiable v => Int -> v Source #
Construct the type constructor of a builtin tuple of given arity (>= 2).