sslang-0.1.0.0
Safe HaskellNone
LanguageHaskell2010

IR.Constraint.Canonical

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 Scheme Source #

SCHEMES

Constructors

Forall FreeVars 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 #

type Kind = Int Source #

KINDS

schemeOf :: Type -> Scheme Source #

Construct a scheme from all free type variables and a trivial constraint.

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

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

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

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

(-->) :: Type -> Type -> Type infixr 0 Source #

HELPERS

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.

tuple :: [Type] -> Type Source #

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

unAnnotations :: Annotations -> [Annotation] Source #

Unwrap the Annotations data constructor.

annToType :: Annotation -> Type Source #

ANNOTATION

builtinKinds :: Map TConId Kind Source #

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