inferno-types-0.1.0.0: Core types for Inferno
Safe HaskellSafe-Inferred
LanguageHaskell2010

Inferno.Types.Type

Documentation

data BaseType Source #

Instances

Instances details
Arbitrary BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

FromJSON BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Data BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: BaseType -> Constr #

dataTypeOf :: BaseType -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep BaseType :: Type -> Type #

Methods

from :: BaseType -> Rep BaseType x #

to :: Rep BaseType x -> BaseType #

Show BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Serialize BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

NFData BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

rnf :: BaseType -> () #

Eq BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Ord BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Hashable BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

hashWithSalt :: Int -> BaseType -> Int #

hash :: BaseType -> Int #

VCHashUpdate BaseType Source # 
Instance details

Defined in Inferno.Types.VersionControl

Pretty BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

pretty :: BaseType -> Doc ann #

prettyList :: [BaseType] -> Doc ann #

ToADTArbitrary BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep BaseType = D1 ('MetaData "BaseType" "Inferno.Types.Syntax" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'False) (((C1 ('MetaCons "TInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TDouble" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TWord16" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TWord32" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TWord64" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "TText" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TTime" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TTimeDiff" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TResolution" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TEnum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set Ident)))))))

data ImplType Source #

Instances

Instances details
FromJSON ImplType Source # 
Instance details

Defined in Inferno.Types.Type

ToJSON ImplType Source # 
Instance details

Defined in Inferno.Types.Type

Data ImplType Source # 
Instance details

Defined in Inferno.Types.Type

Methods

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

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

toConstr :: ImplType -> Constr #

dataTypeOf :: ImplType -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ImplType Source # 
Instance details

Defined in Inferno.Types.Type

Associated Types

type Rep ImplType :: Type -> Type #

Methods

from :: ImplType -> Rep ImplType x #

to :: Rep ImplType x -> ImplType #

Show ImplType Source # 
Instance details

Defined in Inferno.Types.Type

Eq ImplType Source # 
Instance details

Defined in Inferno.Types.Type

Ord ImplType Source # 
Instance details

Defined in Inferno.Types.Type

Substitutable ImplType Source # 
Instance details

Defined in Inferno.Types.Type

VCHashUpdate ImplType Source # 
Instance details

Defined in Inferno.Types.VersionControl

Pretty ImplType Source # 
Instance details

Defined in Inferno.Types.Type

Methods

pretty :: ImplType -> Doc ann #

prettyList :: [ImplType] -> Doc ann #

type Rep ImplType Source # 
Instance details

Defined in Inferno.Types.Type

type Rep ImplType = D1 ('MetaData "ImplType" "Inferno.Types.Type" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'False) (C1 ('MetaCons "ImplType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map ExtIdent InfernoType)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InfernoType)))

data Namespace Source #

Instances

Instances details
Arbitrary Namespace Source # 
Instance details

Defined in Inferno.Types.Type

FromJSON Namespace Source # 
Instance details

Defined in Inferno.Types.Type

ToJSON Namespace Source # 
Instance details

Defined in Inferno.Types.Type

Generic Namespace Source # 
Instance details

Defined in Inferno.Types.Type

Associated Types

type Rep Namespace :: Type -> Type #

Show Namespace Source # 
Instance details

Defined in Inferno.Types.Type

Eq Namespace Source # 
Instance details

Defined in Inferno.Types.Type

Ord Namespace Source # 
Instance details

Defined in Inferno.Types.Type

VCHashUpdate Namespace Source # 
Instance details

Defined in Inferno.Types.VersionControl

Pretty Namespace Source # 
Instance details

Defined in Inferno.Types.Type

Methods

pretty :: Namespace -> Doc ann #

prettyList :: [Namespace] -> Doc ann #

ToADTArbitrary Namespace Source # 
Instance details

Defined in Inferno.Types.Type

type Rep Namespace Source # 
Instance details

Defined in Inferno.Types.Type

data TCScheme Source #

Constructors

ForallTC [TV] (Set TypeClass) ImplType 

Instances

Instances details
FromJSON TCScheme Source # 
Instance details

Defined in Inferno.Types.Type

ToJSON TCScheme Source # 
Instance details

Defined in Inferno.Types.Type

Data TCScheme Source # 
Instance details

Defined in Inferno.Types.Type

Methods

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

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

toConstr :: TCScheme -> Constr #

dataTypeOf :: TCScheme -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic TCScheme Source # 
Instance details

Defined in Inferno.Types.Type

Associated Types

type Rep TCScheme :: Type -> Type #

Methods

from :: TCScheme -> Rep TCScheme x #

to :: Rep TCScheme x -> TCScheme #

Show TCScheme Source # 
Instance details

Defined in Inferno.Types.Type

Eq TCScheme Source # 
Instance details

Defined in Inferno.Types.Type

Ord TCScheme Source # 
Instance details

Defined in Inferno.Types.Type

Substitutable TCScheme Source # 
Instance details

Defined in Inferno.Types.Type

VCHashUpdate TCScheme Source # 
Instance details

Defined in Inferno.Types.VersionControl

Pretty TCScheme Source # 
Instance details

Defined in Inferno.Types.Type

Methods

pretty :: TCScheme -> Doc ann #

prettyList :: [TCScheme] -> Doc ann #

type Rep TCScheme Source # 
Instance details

Defined in Inferno.Types.Type

newtype TV Source #

Constructors

TV 

Fields

Instances

Instances details
Arbitrary TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

arbitrary :: Gen TV #

shrink :: TV -> [TV] #

FromJSON TV Source # 
Instance details

Defined in Inferno.Types.Syntax

FromJSONKey TV Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON TV Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSONKey TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Data TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: TV -> Constr #

dataTypeOf :: TV -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep TV :: Type -> Type #

Methods

from :: TV -> Rep TV x #

to :: Rep TV x -> TV #

Show TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

showsPrec :: Int -> TV -> ShowS #

show :: TV -> String #

showList :: [TV] -> ShowS #

Serialize TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

put :: Putter TV #

get :: Get TV #

NFData TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

rnf :: TV -> () #

Eq TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

Ord TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

compare :: TV -> TV -> Ordering #

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

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

(>) :: TV -> TV -> Bool #

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

max :: TV -> TV -> TV #

min :: TV -> TV -> TV #

Hashable TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

hashWithSalt :: Int -> TV -> Int #

hash :: TV -> Int #

VCHashUpdate TV Source # 
Instance details

Defined in Inferno.Types.VersionControl

Pretty TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

pretty :: TV -> Doc ann #

prettyList :: [TV] -> Doc ann #

ToADTArbitrary TV Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep TV Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep TV = D1 ('MetaData "TV" "Inferno.Types.Syntax" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'True) (C1 ('MetaCons "TV" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTV") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data InfernoType Source #

Instances

Instances details
Arbitrary InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

FromJSON InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Data InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: InfernoType -> Constr #

dataTypeOf :: InfernoType -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep InfernoType :: Type -> Type #

Show InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Serialize InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

NFData InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

rnf :: InfernoType -> () #

Eq InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Ord InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Hashable InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Substitutable InfernoType Source # 
Instance details

Defined in Inferno.Types.Type

VCHashUpdate InfernoType Source # 
Instance details

Defined in Inferno.Types.VersionControl

Pretty InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

pretty :: InfernoType -> Doc ann #

prettyList :: [InfernoType] -> Doc ann #

ToADTArbitrary InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep InfernoType = D1 ('MetaData "InfernoType" "Inferno.Types.Syntax" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'False) (((C1 ('MetaCons "TVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TV)) :+: C1 ('MetaCons "TBase" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BaseType))) :+: (C1 ('MetaCons "TArr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InfernoType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InfernoType)) :+: C1 ('MetaCons "TArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InfernoType)))) :+: ((C1 ('MetaCons "TSeries" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InfernoType)) :+: C1 ('MetaCons "TOptional" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InfernoType))) :+: (C1 ('MetaCons "TTuple" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TList InfernoType))) :+: C1 ('MetaCons "TRep" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InfernoType)))))

data TypeClass Source #

Constructors

TypeClass 

Fields

Instances

Instances details
FromJSON TypeClass Source # 
Instance details

Defined in Inferno.Types.Type

ToJSON TypeClass Source # 
Instance details

Defined in Inferno.Types.Type

Data TypeClass Source # 
Instance details

Defined in Inferno.Types.Type

Methods

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

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

toConstr :: TypeClass -> Constr #

dataTypeOf :: TypeClass -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic TypeClass Source # 
Instance details

Defined in Inferno.Types.Type

Associated Types

type Rep TypeClass :: Type -> Type #

Show TypeClass Source # 
Instance details

Defined in Inferno.Types.Type

Eq TypeClass Source # 
Instance details

Defined in Inferno.Types.Type

Ord TypeClass Source # 
Instance details

Defined in Inferno.Types.Type

Substitutable TypeClass Source # 
Instance details

Defined in Inferno.Types.Type

VCHashUpdate TypeClass Source # 
Instance details

Defined in Inferno.Types.VersionControl

Pretty TypeClass Source # 
Instance details

Defined in Inferno.Types.Type

Methods

pretty :: TypeClass -> Doc ann #

prettyList :: [TypeClass] -> Doc ann #

type Rep TypeClass Source # 
Instance details

Defined in Inferno.Types.Type

type Rep TypeClass = D1 ('MetaData "TypeClass" "Inferno.Types.Type" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'False) (C1 ('MetaCons "TypeClass" 'PrefixI 'True) (S1 ('MetaSel ('Just "className") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "params") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [InfernoType])))

newtype TypeClassShape Source #

Instances

Instances details
Pretty TypeClassShape Source # 
Instance details

Defined in Inferno.Types.Type

Methods

pretty :: TypeClassShape -> Doc ann #

prettyList :: [TypeClassShape] -> Doc ann #

data TypeMetadata ty Source #

Constructors

TypeMetadata 

Fields

Instances

Instances details
FromJSON ty => FromJSON (TypeMetadata ty) Source # 
Instance details

Defined in Inferno.Types.Type

ToJSON ty => ToJSON (TypeMetadata ty) Source # 
Instance details

Defined in Inferno.Types.Type

Data ty => Data (TypeMetadata ty) Source # 
Instance details

Defined in Inferno.Types.Type

Methods

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

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

toConstr :: TypeMetadata ty -> Constr #

dataTypeOf :: TypeMetadata ty -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (TypeMetadata ty) Source # 
Instance details

Defined in Inferno.Types.Type

Associated Types

type Rep (TypeMetadata ty) :: Type -> Type #

Methods

from :: TypeMetadata ty -> Rep (TypeMetadata ty) x #

to :: Rep (TypeMetadata ty) x -> TypeMetadata ty #

Show ty => Show (TypeMetadata ty) Source # 
Instance details

Defined in Inferno.Types.Type

Eq ty => Eq (TypeMetadata ty) Source # 
Instance details

Defined in Inferno.Types.Type

Methods

(==) :: TypeMetadata ty -> TypeMetadata ty -> Bool #

(/=) :: TypeMetadata ty -> TypeMetadata ty -> Bool #

VCHashUpdate ty => VCHashUpdate (TypeMetadata ty) Source # 
Instance details

Defined in Inferno.Types.VersionControl

type Rep (TypeMetadata ty) Source # 
Instance details

Defined in Inferno.Types.Type

type Rep (TypeMetadata ty) = D1 ('MetaData "TypeMetadata" "Inferno.Types.Type" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'False) (C1 ('MetaCons "TypeMetadata" 'PrefixI 'True) (S1 ('MetaSel ('Just "identExpr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr () ())) :*: (S1 ('MetaSel ('Just "docs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "ty") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ty))))

class Substitutable a where Source #

Methods

apply :: Subst -> a -> a Source #

ftv :: a -> Set TV Source #

Instances

Instances details
Substitutable InfernoType Source # 
Instance details

Defined in Inferno.Types.Type

Substitutable ImplType Source # 
Instance details

Defined in Inferno.Types.Type

Substitutable TCScheme Source # 
Instance details

Defined in Inferno.Types.Type

Substitutable TypeClass Source # 
Instance details

Defined in Inferno.Types.Type

Substitutable a => Substitutable [a] Source # 
Instance details

Defined in Inferno.Types.Type

Methods

apply :: Subst -> [a] -> [a] Source #

ftv :: [a] -> Set TV Source #

newtype Subst Source #

Constructors

Subst (Map TV InfernoType) 

Instances

Instances details
Monoid Subst Source # 
Instance details

Defined in Inferno.Types.Type

Methods

mempty :: Subst #

mappend :: Subst -> Subst -> Subst #

mconcat :: [Subst] -> Subst #

Semigroup Subst Source # 
Instance details

Defined in Inferno.Types.Type

Methods

(<>) :: Subst -> Subst -> Subst #

sconcat :: NonEmpty Subst -> Subst #

stimes :: Integral b => b -> Subst -> Subst #

Show Subst Source # 
Instance details

Defined in Inferno.Types.Type

Methods

showsPrec :: Int -> Subst -> ShowS #

show :: Subst -> String #

showList :: [Subst] -> ShowS #

Eq Subst Source # 
Instance details

Defined in Inferno.Types.Type

Methods

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

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

Ord Subst Source # 
Instance details

Defined in Inferno.Types.Type

Methods

compare :: Subst -> Subst -> Ordering #

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

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

(>) :: Subst -> Subst -> Bool #

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

max :: Subst -> Subst -> Subst #

min :: Subst -> Subst -> Subst #

data Scheme Source #

Constructors

Forall [TV] ImplType 

Instances

Instances details
FromJSON Scheme Source # 
Instance details

Defined in Inferno.Types.Type

ToJSON Scheme Source # 
Instance details

Defined in Inferno.Types.Type

Data Scheme Source # 
Instance details

Defined in Inferno.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 #

Generic Scheme Source # 
Instance details

Defined in Inferno.Types.Type

Associated Types

type Rep Scheme :: Type -> Type #

Methods

from :: Scheme -> Rep Scheme x #

to :: Rep Scheme x -> Scheme #

Show Scheme Source # 
Instance details

Defined in Inferno.Types.Type

Eq Scheme Source # 
Instance details

Defined in Inferno.Types.Type

Methods

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

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

Ord Scheme Source # 
Instance details

Defined in Inferno.Types.Type

Pretty Scheme Source # 
Instance details

Defined in Inferno.Types.Type

Methods

pretty :: Scheme -> Doc ann #

prettyList :: [Scheme] -> Doc ann #

type Rep Scheme Source # 
Instance details

Defined in Inferno.Types.Type

type Rep Scheme = D1 ('MetaData "Scheme" "Inferno.Types.Type" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'False) (C1 ('MetaCons "Forall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TV]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ImplType)))

tySig :: [Doc ann] -> [Doc ann] Source #

punctuate' :: Doc ann -> [Doc ann] -> [Doc ann] Source #