Safe Haskell | Safe-Infered |
---|
This module contains a data type to represent (plain) types, some basic functionality for types, and an instance for Show.
- type Tps = [Tp]
- data Tp
- intType, stringType, boolType, floatType, charType :: Tp
- (.->.) :: Tp -> Tp -> Tp
- listType :: Tp -> Tp
- ioType :: Tp -> Tp
- tupleType :: Tps -> Tp
- voidType :: Tp
- variablesInType :: Tp -> [Int]
- constantsInType :: Tp -> [String]
- leftSpine :: Tp -> (Tp, Tps)
- functionSpine :: Tp -> (Tps, Tp)
- functionSpineOfLength :: Int -> Tp -> (Tps, Tp)
- arityOfTp :: Tp -> Int
- priorityOfType :: Tp -> Int
- freezeVariablesInType :: Tp -> Tp
- unfreezeVariablesInType :: Tp -> Tp
- isTVar :: Tp -> Bool
- isTCon :: Tp -> Bool
- isTApp :: Tp -> Bool
- isFunctionType :: Tp -> Bool
- isTupleConstructor :: String -> Bool
- isIOType :: Tp -> Bool
- tpParser :: String -> [(Tp, String)]
- class HasTypes a where
- getTypes :: a -> Tps
- changeTypes :: (Tp -> Tp) -> a -> a
Data type definition
A data type to represent monotypes. Note that Type
is already in use
in the Unified Haskell Architecture (UHA) which is used in the Helium compiler
Common types
(.->.) :: Tp -> Tp -> TpSource
Constructs a function type from one type to another. This operator is left associative.
A cathesian product of zero or more Top.Types. For instance,
(tupleType [])
represents ()
, and (tupleType [charType, stringType])
represents (Char,String)
Basic functionality
variablesInType :: Tp -> [Int]Source
Returns the list of type variables of a type. (no duplicates)
constantsInType :: Tp -> [String]Source
Returns the list of type constants of a type. (no duplicates)
leftSpine :: Tp -> (Tp, Tps)Source
Returns the left spine of a type. For instance, if type t
is Either Bool [Int]
, then leftSpine t
is (Either,[Bool,[Int]])
.
functionSpine :: Tp -> (Tps, Tp)Source
Returns the right spine of a function type. For instance,
if type t
is Int -> (Bool -> String)
, then functionSpine t
is ([Int,Bool],String)
.
functionSpineOfLength :: Int -> Tp -> (Tps, Tp)Source
Returns the right spine of a function type of a maximal length.
priorityOfType :: Tp -> IntSource
The priority of a type, primarily used for the insertion of parentheses in pretty printing.
freezeVariablesInType :: Tp -> TpSource
All the type variables in a type are frozen by turning them into a type constant. The integer numeral is prefixed with an underscore ('_').
unfreezeVariablesInType :: Tp -> TpSource
Recover the type variables that are frozen in a type.
Predicates on types
isFunctionType :: Tp -> BoolSource