sslang-0.1.0.0
Safe HaskellNone
LanguageHaskell2010

IR.Types.Type

Description

Definitions of and related to the sslang IR's type system.

Synopsis

Documentation

data Type Source #

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

Instances details
Eq Type Source # 
Instance details

Defined in IR.Types.Type

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Data Type Source # 
Instance details

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 #

toConstr :: Type -> Constr #

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 # 
Instance details

Defined in IR.Types.Type

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Pretty Type Source # 
Instance details

Defined in IR.Types.Type

Methods

pretty :: Type -> Doc ann

prettyList :: [Type] -> Doc ann

Dumpy Type Source # 
Instance details

Defined in IR.Types.Type

Methods

dumpy :: Type -> Doc ann Source #

HasType Type Source # 
Instance details

Defined in IR.Types.Type

Methods

getType :: Type -> Type Source #

HasFreeVars Type TVarId Source # 
Instance details

Defined in IR.Types.Type

Pretty (Alt Type) 
Instance details

Defined in IR.Pretty

Methods

pretty :: Alt Type -> Doc ann

prettyList :: [Alt Type] -> Doc ann

Pretty (Expr Type) 
Instance details

Defined in IR.Pretty

Methods

pretty :: Expr Type -> Doc ann

prettyList :: [Expr Type] -> Doc ann

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

Instance details

Defined in IR.Pretty

Methods

pretty :: Program Type -> Doc ann

prettyList :: [Program Type] -> Doc ann

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

Instances details
Eq Constraint Source # 
Instance details

Defined in IR.Types.Type

Data Constraint Source # 
Instance details

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 # 
Instance details

Defined in IR.Types.Type

data SchemeOf t Source #

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

Instances details
Functor SchemeOf Source # 
Instance details

Defined in IR.Types.Type

Methods

fmap :: (a -> b) -> SchemeOf a -> SchemeOf b #

(<$) :: a -> SchemeOf b -> SchemeOf a #

Foldable SchemeOf Source # 
Instance details

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 #

toList :: SchemeOf a -> [a] #

null :: SchemeOf a -> Bool #

length :: SchemeOf a -> Int #

elem :: Eq a => a -> SchemeOf a -> Bool #

maximum :: Ord a => SchemeOf a -> a #

minimum :: Ord a => SchemeOf a -> a #

sum :: Num a => SchemeOf a -> a #

product :: Num a => SchemeOf a -> a #

Traversable SchemeOf Source # 
Instance details

Defined in IR.Types.Type

Methods

traverse :: Applicative f => (a -> f b) -> SchemeOf a -> f (SchemeOf b) #

sequenceA :: Applicative f => SchemeOf (f a) -> f (SchemeOf a) #

mapM :: Monad m => (a -> m b) -> SchemeOf a -> m (SchemeOf b) #

sequence :: Monad m => SchemeOf (m a) -> m (SchemeOf a) #

Eq t => Eq (SchemeOf t) Source # 
Instance details

Defined in IR.Types.Type

Methods

(==) :: SchemeOf t -> SchemeOf t -> Bool #

(/=) :: SchemeOf t -> SchemeOf t -> Bool #

Data t => Data (SchemeOf t) Source # 
Instance details

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 # 
Instance details

Defined in IR.Types.Type

Methods

showsPrec :: Int -> SchemeOf t -> ShowS #

show :: SchemeOf t -> String #

showList :: [SchemeOf t] -> ShowS #

unScheme :: SchemeOf t -> t Source #

Unwrap a scheme and obtain the underlying type.

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.

newtype Scheme Source #

Schemes over Type.

Constructors

Scheme (SchemeOf Type) 

Instances

Instances details
Eq Scheme Source # 
Instance details

Defined in IR.Types.Type

Methods

(==) :: Scheme -> Scheme -> Bool #

(/=) :: Scheme -> Scheme -> Bool #

Data Scheme Source # 
Instance details

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 # 
Instance details

Defined in IR.Types.Type

Pretty Scheme Source # 
Instance details

Defined in IR.Types.Type

Methods

pretty :: Scheme -> Doc ann

prettyList :: [Scheme] -> Doc ann

Dumpy Scheme Source # 
Instance details

Defined in IR.Types.Type

Methods

dumpy :: Scheme -> Doc ann Source #

HasType Scheme Source # 
Instance details

Defined in IR.Types.Type

Methods

getType :: Scheme -> Type Source #

HasFreeVars Scheme TVarId Source # 
Instance details

Defined in IR.Types.Type

data Annotation Source #

An annotation records the annotated portion of a pattern.

Constructors

AnnType Type

A basic Type annotation

AnnDCon DConId [Annotation]

Annotations collected from patterns

AnnArrows [Annotation] Annotation

Annotations collected from fun args

Instances

Instances details
Eq Annotation Source # 
Instance details

Defined in IR.Types.Type

Data Annotation Source # 
Instance details

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 # 
Instance details

Defined in IR.Types.Type

Pretty Annotation Source # 
Instance details

Defined in IR.Types.Type

Methods

pretty :: Annotation -> Doc ann

prettyList :: [Annotation] -> Doc ann

Dumpy Annotation Source # 
Instance details

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

Instances details
Eq Annotations Source # 
Instance details

Defined in IR.Types.Type

Data Annotations Source # 
Instance details

Defined in IR.Types.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Annotations -> c Annotations #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Annotations #

toConstr :: Annotations -> Constr #

dataTypeOf :: Annotations -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Annotations) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Annotations) #

gmapT :: (forall b. Data b => b -> b) -> Annotations -> Annotations #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Annotations -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Annotations -> r #

gmapQ :: (forall d. Data d => d -> u) -> Annotations -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Annotations -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Annotations -> m Annotations #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotations -> m Annotations #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotations -> m Annotations #

Show Annotations Source # 
Instance details

Defined in IR.Types.Type

Semigroup Annotations Source # 
Instance details

Defined in IR.Types.Type

Monoid Annotations Source # 
Instance details

Defined in IR.Types.Type

Pretty Annotations Source # 
Instance details

Defined in IR.Types.Type

Methods

pretty :: Annotations -> Doc ann

prettyList :: [Annotations] -> Doc ann

Dumpy Annotations Source # 
Instance details

Defined in IR.Types.Type

Methods

dumpy :: Annotations -> Doc ann Source #

unAnnotations :: Annotations -> [Annotation] Source #

Unwrap the Annotations data constructor.

fromAnnotations :: Annotations -> Type Source #

Unroll an annotation into a type. FIXME: get rid of this.

class HasType a where Source #

Some data type that contains a sslang Type.

Methods

getType :: a -> Type Source #

Instances

Instances details
HasType Scheme Source # 
Instance details

Defined in IR.Types.Type

Methods

getType :: Scheme -> Type Source #

HasType Type Source # 
Instance details

Defined in IR.Types.Type

Methods

getType :: Type -> Type Source #

pattern Hole :: Type Source #

A fresh, free type variable; may appear in type annotations.

pattern Arrow :: Type -> Type -> Type Source #

The type constructor for function arrows.

unfoldArrow :: Type -> ([Type], Type) Source #

Unfold an Arrow Type into a list of argument types and a return type.

foldArrow :: ([Type], Type) -> Type Source #

Fold a list of argument types and a return type into an Arrow Type.

pattern Unit :: Type Source #

The builtin singleton Type, whose only data constructor is just ().

pattern Ref :: Type -> Type Source #

The builtin reference Type, created using new.

pattern List :: Type -> Type Source #

The builtin list Type, created using list syntax, e.g., [a, b].

pattern Time :: Type Source #

The builtin 64-bit timestamp Type.

pattern I64 :: Type Source #

Builtin Type for signed 64-bit integers.

pattern U64 :: Type Source #

Builtin Type for unsigned 64-bit integers.

pattern I32 :: Type Source #

Builtin Type for signed 32-bit integers.

pattern U32 :: Type Source #

Builtin Type for unsigned 32-bit integers.

pattern I16 :: Type Source #

Builtin Type for signed 16-bit integers.

pattern U16 :: Type Source #

Builtin Type for unsigned 16-bit integers.

pattern I8 :: Type Source #

Builtin Type for signed 8-bit integers.

pattern U8 :: Type Source #

Builtin Type for unsigned 8-bit integers.

isInt :: Type -> Bool Source #

Test whether a Type is one of the builtin signed integers.

isUInt :: Type -> Bool Source #

Test whether a Type is one of the builtin unsigned integers.

isNum :: Type -> Bool Source #

Test whether a Type is one of the builtin numeric types.

tuple :: [Type] -> Type Source #

Construct a builtin tuple type out of a list of at least 2 types.

tupleId :: Identifiable v => Int -> v Source #

Construct the type constructor of a builtin tuple of given arity (>= 2).

type Kind = Int Source #

Kinds are just the arity of type constructors.

builtinKinds :: Map TConId Kind Source #

Map to help us look up the kinds of builtin types.