curry-frontend-1.0.4: Compile the functional logic language Curry to several intermediate formats

Copyright(c) 2002 - 2004 Wolfgang Lux
Martin Engelke
2015 Jan Tikovsky
2016 Finn Teegen
LicenseBSD-3-clause
Maintainerbjp@informatik.uni-kiel.de
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Base.Types

Contents

Description

This module modules provides the definitions for the internal representation of types in the compiler along with some helper functions.

Synopsis

Representation of types

data Type Source #

Instances
Eq Type Source # 
Instance details

Defined in Base.Types

Methods

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

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

Ord Type Source # 
Instance details

Defined in Base.Types

Methods

compare :: Type -> Type -> Ordering #

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

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

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

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

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

Show Type Source # 
Instance details

Defined in Base.Types

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Pretty Type Source # 
Instance details

Defined in Base.PrettyTypes

Methods

pPrint :: Type -> Doc #

pPrintPrec :: Int -> Type -> Doc #

pPrintList :: [Type] -> Doc #

IsType Type Source # 
Instance details

Defined in Base.Types

Methods

typeVars :: Type -> [Int] Source #

ValueType Type Source # 
Instance details

Defined in Env.Value

ExpandAliasType Type Source # 
Instance details

Defined in Base.TypeSubst

Methods

expandAliasType :: [Type] -> Type -> Type Source #

SubstType Type Source # 
Instance details

Defined in Base.TypeSubst

Methods

subst :: TypeSubst -> Type -> Type Source #

Typeable Type Source # 
Instance details

Defined in Base.Typing

Methods

typeOf :: Type -> Type Source #

class IsType t where Source #

Methods

typeVars :: t -> [Int] Source #

Instances
IsType TypeScheme Source # 
Instance details

Defined in Base.Types

Methods

typeVars :: TypeScheme -> [Int] Source #

IsType PredType Source # 
Instance details

Defined in Base.Types

Methods

typeVars :: PredType -> [Int] Source #

IsType Pred Source # 
Instance details

Defined in Base.Types

Methods

typeVars :: Pred -> [Int] Source #

IsType Type Source # 
Instance details

Defined in Base.Types

Methods

typeVars :: Type -> [Int] Source #

(IsType a, Ord a) => IsType (Set a) Source # 
Instance details

Defined in Base.Types

Methods

typeVars :: Set a -> [Int] Source #

Representation of predicate, predicate sets and predicated types

data Pred Source #

Constructors

Pred QualIdent Type 
Instances
Eq Pred Source # 
Instance details

Defined in Base.Types

Methods

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

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

Ord Pred Source # 
Instance details

Defined in Base.Types

Methods

compare :: Pred -> Pred -> Ordering #

(<) :: Pred -> Pred -> Bool #

(<=) :: Pred -> Pred -> Bool #

(>) :: Pred -> Pred -> Bool #

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

max :: Pred -> Pred -> Pred #

min :: Pred -> Pred -> Pred #

Show Pred Source # 
Instance details

Defined in Base.Types

Methods

showsPrec :: Int -> Pred -> ShowS #

show :: Pred -> String #

showList :: [Pred] -> ShowS #

Pretty Pred Source # 
Instance details

Defined in Base.PrettyTypes

Methods

pPrint :: Pred -> Doc #

pPrintPrec :: Int -> Pred -> Doc #

pPrintList :: [Pred] -> Doc #

IsType Pred Source # 
Instance details

Defined in Base.Types

Methods

typeVars :: Pred -> [Int] Source #

ExpandAliasType Pred Source # 
Instance details

Defined in Base.TypeSubst

Methods

expandAliasType :: [Type] -> Pred -> Pred Source #

SubstType Pred Source # 
Instance details

Defined in Base.TypeSubst

Methods

subst :: TypeSubst -> Pred -> Pred Source #

data PredType Source #

Constructors

PredType PredSet Type 
Instances
Eq PredType Source # 
Instance details

Defined in Base.Types

Show PredType Source # 
Instance details

Defined in Base.Types

Pretty PredType Source # 
Instance details

Defined in Base.PrettyTypes

IsType PredType Source # 
Instance details

Defined in Base.Types

Methods

typeVars :: PredType -> [Int] Source #

ValueType PredType Source # 
Instance details

Defined in Env.Value

ExpandAliasType PredType Source # 
Instance details

Defined in Base.TypeSubst

SubstType PredType Source # 
Instance details

Defined in Base.TypeSubst

Typeable PredType Source # 
Instance details

Defined in Base.Typing

Methods

typeOf :: PredType -> Type Source #

Representation of data constructors

data DataConstr Source #

Instances
Eq DataConstr Source # 
Instance details

Defined in Base.Types

Show DataConstr Source # 
Instance details

Defined in Base.Types

Pretty DataConstr Source # 
Instance details

Defined in Base.PrettyTypes

Representation of class methods

data ClassMethod Source #

Instances
Eq ClassMethod Source # 
Instance details

Defined in Base.Types

Show ClassMethod Source # 
Instance details

Defined in Base.Types

Pretty ClassMethod Source # 
Instance details

Defined in Base.PrettyTypes

Representation of quantification

data TypeScheme Source #

Constructors

ForAll Int PredType 
Instances
Eq TypeScheme Source # 
Instance details

Defined in Base.Types

Show TypeScheme Source # 
Instance details

Defined in Base.Types

Pretty TypeScheme Source # 
Instance details

Defined in Base.PrettyTypes

IsType TypeScheme Source # 
Instance details

Defined in Base.Types

Methods

typeVars :: TypeScheme -> [Int] Source #

SubstType TypeScheme Source # 
Instance details

Defined in Base.TypeSubst

Predefined types