language-dickinson-1.4.3.0: A language for generative literature
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Dickinson.Type

Contents

Synopsis

Documentation

data Dickinson a Source #

Constructors

Dickinson 

Fields

Instances

Instances details
Functor Dickinson Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

fmap :: (a -> b) -> Dickinson a -> Dickinson b #

(<$) :: a -> Dickinson b -> Dickinson a #

Generic (Dickinson a) Source # 
Instance details

Defined in Language.Dickinson.Type

Associated Types

type Rep (Dickinson a) :: Type -> Type #

Methods

from :: Dickinson a -> Rep (Dickinson a) x #

to :: Rep (Dickinson a) x -> Dickinson a #

Show a => Show (Dickinson a) Source # 
Instance details

Defined in Language.Dickinson.Type

Binary a => Binary (Dickinson a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

put :: Dickinson a -> Put #

get :: Get (Dickinson a) #

putList :: [Dickinson a] -> Put #

NFData a => NFData (Dickinson a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

rnf :: Dickinson a -> () #

Pretty (Dickinson a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

pretty :: Dickinson a -> Doc ann #

prettyList :: [Dickinson a] -> Doc ann #

type Rep (Dickinson a) Source # 
Instance details

Defined in Language.Dickinson.Type

type Rep (Dickinson a) = D1 ('MetaData "Dickinson" "Language.Dickinson.Type" "language-dickinson-1.4.3.0-u4JKvBug5L7Xak6MfKGcR-dickinson" 'False) (C1 ('MetaCons "Dickinson" 'PrefixI 'True) (S1 ('MetaSel ('Just "modImports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Import a]) :*: S1 ('MetaSel ('Just "modDefs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Declaration a])))

data Declaration a Source #

Constructors

Define 

Fields

TyDecl 

Fields

Instances

Instances details
Functor Declaration Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

fmap :: (a -> b) -> Declaration a -> Declaration b #

(<$) :: a -> Declaration b -> Declaration a #

Data a => Data (Declaration a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

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

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

toConstr :: Declaration a -> Constr #

dataTypeOf :: Declaration a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Declaration a) Source # 
Instance details

Defined in Language.Dickinson.Type

Associated Types

type Rep (Declaration a) :: Type -> Type #

Methods

from :: Declaration a -> Rep (Declaration a) x #

to :: Rep (Declaration a) x -> Declaration a #

Show a => Show (Declaration a) Source # 
Instance details

Defined in Language.Dickinson.Type

Binary a => Binary (Declaration a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

put :: Declaration a -> Put #

get :: Get (Declaration a) #

putList :: [Declaration a] -> Put #

NFData a => NFData (Declaration a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

rnf :: Declaration a -> () #

Pretty (Declaration a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

pretty :: Declaration a -> Doc ann #

prettyList :: [Declaration a] -> Doc ann #

type Rep (Declaration a) Source # 
Instance details

Defined in Language.Dickinson.Type

type Rep (Declaration a) = D1 ('MetaData "Declaration" "Language.Dickinson.Type" "language-dickinson-1.4.3.0-u4JKvBug5L7Xak6MfKGcR-dickinson" 'False) (C1 ('MetaCons "Define" 'PrefixI 'True) (S1 ('MetaSel ('Just "declAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "defName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name a)) :*: S1 ('MetaSel ('Just "defExpr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :+: C1 ('MetaCons "TyDecl" 'PrefixI 'True) (S1 ('MetaSel ('Just "declAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "tyName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name a)) :*: S1 ('MetaSel ('Just "tyCons") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (TyName a))))))

data Import a Source #

Constructors

Import 

Fields

Instances

Instances details
Functor Import Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

fmap :: (a -> b) -> Import a -> Import b #

(<$) :: a -> Import b -> Import a #

Generic (Import a) Source # 
Instance details

Defined in Language.Dickinson.Type

Associated Types

type Rep (Import a) :: Type -> Type #

Methods

from :: Import a -> Rep (Import a) x #

to :: Rep (Import a) x -> Import a #

Show a => Show (Import a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

showsPrec :: Int -> Import a -> ShowS #

show :: Import a -> String #

showList :: [Import a] -> ShowS #

Binary a => Binary (Import a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

put :: Import a -> Put #

get :: Get (Import a) #

putList :: [Import a] -> Put #

NFData a => NFData (Import a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

rnf :: Import a -> () #

Pretty (Import a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

pretty :: Import a -> Doc ann #

prettyList :: [Import a] -> Doc ann #

type Rep (Import a) Source # 
Instance details

Defined in Language.Dickinson.Type

type Rep (Import a) = D1 ('MetaData "Import" "Language.Dickinson.Type" "language-dickinson-1.4.3.0-u4JKvBug5L7Xak6MfKGcR-dickinson" 'False) (C1 ('MetaCons "Import" 'PrefixI 'True) (S1 ('MetaSel ('Just "importAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "declMod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name a))))

data Expression a Source #

Constructors

Literal 

Fields

StrChunk 

Fields

Choice 

Fields

Let 

Fields

Bind 

Fields

Var 

Fields

Interp 

Fields

MultiInterp 

Fields

Lambda 
Apply 

Fields

Concat 

Fields

Tuple 

Fields

Match 
Flatten 

Fields

Annot 

Fields

Constructor 

Fields

BuiltinFn 

Fields

Random 

Fields

Instances

Instances details
Functor Expression Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

fmap :: (a -> b) -> Expression a -> Expression b #

(<$) :: a -> Expression b -> Expression a #

Data a => Data (Expression a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

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

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

toConstr :: Expression a -> Constr #

dataTypeOf :: Expression a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Expression a) Source # 
Instance details

Defined in Language.Dickinson.Type

Associated Types

type Rep (Expression a) :: Type -> Type #

Methods

from :: Expression a -> Rep (Expression a) x #

to :: Rep (Expression a) x -> Expression a #

Show a => Show (Expression a) Source # 
Instance details

Defined in Language.Dickinson.Type

Binary a => Binary (Expression a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

put :: Expression a -> Put #

get :: Get (Expression a) #

putList :: [Expression a] -> Put #

NFData a => NFData (Expression a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

rnf :: Expression a -> () #

Pretty (Expression a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

pretty :: Expression a -> Doc ann #

prettyList :: [Expression a] -> Doc ann #

type Rep (Expression a) Source # 
Instance details

Defined in Language.Dickinson.Type

type Rep (Expression a) = D1 ('MetaData "Expression" "Language.Dickinson.Type" "language-dickinson-1.4.3.0-u4JKvBug5L7Xak6MfKGcR-dickinson" 'False) ((((C1 ('MetaCons "Literal" 'PrefixI 'True) (S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "litText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "StrChunk" 'PrefixI 'True) (S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "chunkText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :+: (C1 ('MetaCons "Choice" 'PrefixI 'True) (S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "choices") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (Double, Expression a)))) :+: C1 ('MetaCons "Let" 'PrefixI 'True) (S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "letBinds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (Name a, Expression a))) :*: S1 ('MetaSel ('Just "letExpr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))))) :+: ((C1 ('MetaCons "Bind" 'PrefixI 'True) (S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "letBinds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (Name a, Expression a))) :*: S1 ('MetaSel ('Just "letExpr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :+: C1 ('MetaCons "Var" 'PrefixI 'True) (S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "exprVar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name a)))) :+: (C1 ('MetaCons "Interp" 'PrefixI 'True) (S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "exprInterp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Expression a])) :+: (C1 ('MetaCons "MultiInterp" 'PrefixI 'True) (S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "exprMultiInterp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Expression a])) :+: C1 ('MetaCons "Lambda" 'PrefixI 'True) ((S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "lambdaVar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name a))) :*: (S1 ('MetaSel ('Just "lambdaTy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DickinsonTy a)) :*: S1 ('MetaSel ('Just "lambdaExpr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))))))) :+: (((C1 ('MetaCons "Apply" 'PrefixI 'True) (S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "exprFun") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Just "exprArg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :+: C1 ('MetaCons "Concat" 'PrefixI 'True) (S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "exprConcats") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Expression a]))) :+: (C1 ('MetaCons "Tuple" 'PrefixI 'True) (S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "exprTup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (Expression a)))) :+: C1 ('MetaCons "Match" 'PrefixI 'True) (S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "exprMatch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Just "exprBranch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (Pattern a, Expression a))))))) :+: ((C1 ('MetaCons "Flatten" 'PrefixI 'True) (S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "exprFlat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a))) :+: C1 ('MetaCons "Annot" 'PrefixI 'True) (S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "expr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Just "exprTy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DickinsonTy a))))) :+: (C1 ('MetaCons "Constructor" 'PrefixI 'True) (S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "constructorName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TyName a))) :+: (C1 ('MetaCons "BuiltinFn" 'PrefixI 'True) (S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "exprBuiltin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Builtin)) :+: C1 ('MetaCons "Random" 'PrefixI 'True) (S1 ('MetaSel ('Just "exprAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "tySelName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name a))))))))

data Pattern a Source #

Constructors

PatternVar 

Fields

PatternTuple 

Fields

PatternCons 

Fields

Wildcard 

Fields

OrPattern 

Fields

Instances

Instances details
Functor Pattern Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

fmap :: (a -> b) -> Pattern a -> Pattern b #

(<$) :: a -> Pattern b -> Pattern a #

Data a => Data (Pattern a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

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

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

toConstr :: Pattern a -> Constr #

dataTypeOf :: Pattern a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Pattern a) Source # 
Instance details

Defined in Language.Dickinson.Type

Associated Types

type Rep (Pattern a) :: Type -> Type #

Methods

from :: Pattern a -> Rep (Pattern a) x #

to :: Rep (Pattern a) x -> Pattern a #

Show a => Show (Pattern a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

showsPrec :: Int -> Pattern a -> ShowS #

show :: Pattern a -> String #

showList :: [Pattern a] -> ShowS #

Binary a => Binary (Pattern a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

put :: Pattern a -> Put #

get :: Get (Pattern a) #

putList :: [Pattern a] -> Put #

NFData a => NFData (Pattern a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

rnf :: Pattern a -> () #

Eq a => Eq (Pattern a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

(==) :: Pattern a -> Pattern a -> Bool #

(/=) :: Pattern a -> Pattern a -> Bool #

Debug (Pattern a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

debug :: Pattern a -> Doc b Source #

Pretty (Pattern a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

pretty :: Pattern a -> Doc ann #

prettyList :: [Pattern a] -> Doc ann #

type Rep (Pattern a) Source # 
Instance details

Defined in Language.Dickinson.Type

type Rep (Pattern a) = D1 ('MetaData "Pattern" "Language.Dickinson.Type" "language-dickinson-1.4.3.0-u4JKvBug5L7Xak6MfKGcR-dickinson" 'False) ((C1 ('MetaCons "PatternVar" 'PrefixI 'True) (S1 ('MetaSel ('Just "patAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "patName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name a))) :+: C1 ('MetaCons "PatternTuple" 'PrefixI 'True) (S1 ('MetaSel ('Just "patAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "patTup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (Pattern a))))) :+: (C1 ('MetaCons "PatternCons" 'PrefixI 'True) (S1 ('MetaSel ('Just "patAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "patCons") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TyName a))) :+: (C1 ('MetaCons "Wildcard" 'PrefixI 'True) (S1 ('MetaSel ('Just "patAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "OrPattern" 'PrefixI 'True) (S1 ('MetaSel ('Just "patAnn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "patOr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (Pattern a)))))))

data DickinsonTy a Source #

Constructors

TyText a 
TyFun a (DickinsonTy a) (DickinsonTy a) 
TyTuple a (NonEmpty (DickinsonTy a)) 
TyNamed a (Name a) 

Instances

Instances details
Functor DickinsonTy Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

fmap :: (a -> b) -> DickinsonTy a -> DickinsonTy b #

(<$) :: a -> DickinsonTy b -> DickinsonTy a #

Data a => Data (DickinsonTy a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

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

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

toConstr :: DickinsonTy a -> Constr #

dataTypeOf :: DickinsonTy a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (DickinsonTy a) Source # 
Instance details

Defined in Language.Dickinson.Type

Associated Types

type Rep (DickinsonTy a) :: Type -> Type #

Methods

from :: DickinsonTy a -> Rep (DickinsonTy a) x #

to :: Rep (DickinsonTy a) x -> DickinsonTy a #

Show a => Show (DickinsonTy a) Source # 
Instance details

Defined in Language.Dickinson.Type

Binary a => Binary (DickinsonTy a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

put :: DickinsonTy a -> Put #

get :: Get (DickinsonTy a) #

putList :: [DickinsonTy a] -> Put #

NFData a => NFData (DickinsonTy a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

rnf :: DickinsonTy a -> () #

Eq (DickinsonTy a) Source # 
Instance details

Defined in Language.Dickinson.Type

Pretty (DickinsonTy a) Source # 
Instance details

Defined in Language.Dickinson.Type

Methods

pretty :: DickinsonTy a -> Doc ann #

prettyList :: [DickinsonTy a] -> Doc ann #

type Rep (DickinsonTy a) Source # 
Instance details

Defined in Language.Dickinson.Type

Accesors