| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Inferno.Types.Type
Documentation
Constructors
| TInt | |
| TDouble | |
| TWord16 | |
| TWord32 | |
| TWord64 | |
| TText | |
| TTime | |
| TTimeDiff | |
| TResolution | |
| TEnum Text (Set Ident) |
Instances
Constructors
| ImplType (Map ExtIdent InfernoType) InfernoType |
Instances
| FromJSON ImplType Source # | |
| ToJSON ImplType Source # | |
Defined in Inferno.Types.Type | |
| Data ImplType Source # | |
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 # | |
| Show ImplType Source # | |
| Eq ImplType Source # | |
| Ord ImplType Source # | |
Defined in Inferno.Types.Type | |
| Substitutable ImplType Source # | |
| VCHashUpdate ImplType Source # | |
| Pretty ImplType Source # | |
Defined in Inferno.Types.Type | |
| type Rep ImplType Source # | |
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))) | |
Constructors
| FunNamespace Ident | |
| OpNamespace Ident | |
| EnumNamespace Ident | |
| ModuleNamespace ModuleName | |
| TypeNamespace Ident |
Instances
Instances
Instances
| Arbitrary TV Source # | |
| FromJSON TV Source # | |
| FromJSONKey TV Source # | |
Defined in Inferno.Types.Syntax | |
| ToJSON TV Source # | |
Defined in Inferno.Types.Syntax | |
| ToJSONKey TV Source # | |
Defined in Inferno.Types.Syntax | |
| Data TV Source # | |
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 # 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 # | |
| Show TV Source # | |
| Serialize TV Source # | |
| NFData TV Source # | |
Defined in Inferno.Types.Syntax | |
| Eq TV Source # | |
| Ord TV Source # | |
| Hashable TV Source # | |
Defined in Inferno.Types.Syntax | |
| VCHashUpdate TV Source # | |
| Pretty TV Source # | |
Defined in Inferno.Types.Syntax | |
| ToADTArbitrary TV Source # | |
Defined in Inferno.Types.Syntax Methods toADTArbitrarySingleton :: Proxy TV -> Gen (ADTArbitrarySingleton TV) # toADTArbitrary :: Proxy TV -> Gen (ADTArbitrary TV) # | |
| type Rep TV Source # | |
Defined in Inferno.Types.Syntax | |
data InfernoType Source #
Constructors
| TVar TV | |
| TBase BaseType | |
| TArr InfernoType InfernoType | |
| TArray InfernoType | |
| TSeries InfernoType | |
| TOptional InfernoType | |
| TTuple (TList InfernoType) | |
| TRep InfernoType |
Instances
Constructors
| TypeClass | |
Fields
| |
Instances
| FromJSON TypeClass Source # | |
| ToJSON TypeClass Source # | |
Defined in Inferno.Types.Type | |
| Data TypeClass Source # | |
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 # | |
| Show TypeClass Source # | |
| Eq TypeClass Source # | |
| Ord TypeClass Source # | |
| Substitutable TypeClass Source # | |
| VCHashUpdate TypeClass Source # | |
| Pretty TypeClass Source # | |
Defined in Inferno.Types.Type | |
| type Rep TypeClass Source # | |
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 #
Constructors
| TypeClassShape TypeClass |
Instances
| Pretty TypeClassShape Source # | |
Defined in Inferno.Types.Type | |
data TypeMetadata ty Source #
Instances
class Substitutable a where Source #
Instances
Constructors
| Subst (Map TV InfernoType) |
Instances
| FromJSON Scheme Source # | |
| ToJSON Scheme Source # | |
Defined in Inferno.Types.Type | |
| Data Scheme Source # | |
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 # | |
| Show Scheme Source # | |
| Eq Scheme Source # | |
| Ord Scheme Source # | |
| Pretty Scheme Source # | |
Defined in Inferno.Types.Type | |
| type Rep Scheme Source # | |
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))) | |
(.->) :: InfernoType -> InfernoType -> InfernoType infixr 3 Source #
sch :: InfernoType -> Scheme Source #
var :: Int -> InfernoType Source #
namespaceToIdent :: Namespace -> Ident Source #