language-dickinson-1.3.0.0: A language for generative literature
Safe HaskellNone
LanguageHaskell2010

Language.Dickinson

Description

This module contains some bits and pieces to work with Dickinson code.

Synopsis

Parser

data ParseError a #

Constructors

Unexpected (Token a) 
LexErr String 

Instances

Instances details
Pretty a => Show (ParseError a) 
Instance details

Defined in Language.Dickinson.Parser

Generic (ParseError a) 
Instance details

Defined in Language.Dickinson.Parser

Associated Types

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

Methods

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

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

(Pretty a, Typeable a) => Exception (ParseError a) 
Instance details

Defined in Language.Dickinson.Parser

NFData a => NFData (ParseError a) 
Instance details

Defined in Language.Dickinson.Parser

Methods

rnf :: ParseError a -> () #

Pretty a => Pretty (ParseError a) 
Instance details

Defined in Language.Dickinson.Parser

Methods

pretty :: ParseError a -> Doc ann

prettyList :: [ParseError a] -> Doc ann

type Rep (ParseError a) 
Instance details

Defined in Language.Dickinson.Parser

type Rep (ParseError a) = D1 ('MetaData "ParseError" "Language.Dickinson.Parser" "language-dickinson-1.3.0.0-inplace-dickinson" 'False) (C1 ('MetaCons "Unexpected" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Token a))) :+: C1 ('MetaCons "LexErr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

Lexer

data AlexPosn #

Instances

Instances details
Eq AlexPosn 
Instance details

Defined in Language.Dickinson.Lexer

Data AlexPosn 
Instance details

Defined in Language.Dickinson.Lexer

Methods

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

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

toConstr :: AlexPosn -> Constr #

dataTypeOf :: AlexPosn -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AlexPosn 
Instance details

Defined in Language.Dickinson.Lexer

Generic AlexPosn 
Instance details

Defined in Language.Dickinson.Lexer

Associated Types

type Rep AlexPosn :: Type -> Type #

Methods

from :: AlexPosn -> Rep AlexPosn x #

to :: Rep AlexPosn x -> AlexPosn #

Binary AlexPosn 
Instance details

Defined in Language.Dickinson.Lexer

Methods

put :: AlexPosn -> Put #

get :: Get AlexPosn #

putList :: [AlexPosn] -> Put #

NFData AlexPosn 
Instance details

Defined in Language.Dickinson.Lexer

Methods

rnf :: AlexPosn -> () #

Pretty AlexPosn 
Instance details

Defined in Language.Dickinson.Lexer

Methods

pretty :: AlexPosn -> Doc ann

prettyList :: [AlexPosn] -> Doc ann

type Rep AlexPosn 
Instance details

Defined in Language.Dickinson.Lexer

type Rep AlexPosn = D1 ('MetaData "AlexPosn" "Language.Dickinson.Lexer" "language-dickinson-1.3.0.0-inplace-dickinson" 'False) (C1 ('MetaCons "AlexPn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int))))

data Token a #

Constructors

EOF 

Fields

TokIdent 

Fields

TokTyCons 

Fields

TokDouble 

Fields

TokStrChunk 

Fields

TokString 

Fields

TokKeyword 

Fields

  • loc :: a
     
  • kw :: Keyword
     
TokSym 

Fields

TokBuiltin 

Fields

Instances

Instances details
Eq a => Eq (Token a) 
Instance details

Defined in Language.Dickinson.Lexer

Methods

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

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

Generic (Token a) 
Instance details

Defined in Language.Dickinson.Lexer

Associated Types

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

Methods

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

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

NFData a => NFData (Token a) 
Instance details

Defined in Language.Dickinson.Lexer

Methods

rnf :: Token a -> () #

Pretty (Token a) 
Instance details

Defined in Language.Dickinson.Lexer

Methods

pretty :: Token a -> Doc ann

prettyList :: [Token a] -> Doc ann

type Rep (Token a) 
Instance details

Defined in Language.Dickinson.Lexer

type Rep (Token a) = D1 ('MetaData "Token" "Language.Dickinson.Lexer" "language-dickinson-1.3.0.0-inplace-dickinson" 'False) (((C1 ('MetaCons "EOF" 'PrefixI 'True) (S1 ('MetaSel ('Just "loc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "TokIdent" 'PrefixI 'True) (S1 ('MetaSel ('Just "loc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "ident") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name a)))) :+: (C1 ('MetaCons "TokTyCons" 'PrefixI 'True) (S1 ('MetaSel ('Just "loc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "tyIdent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TyName a))) :+: C1 ('MetaCons "TokDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "loc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "double") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))) :+: ((C1 ('MetaCons "TokStrChunk" 'PrefixI 'True) (S1 ('MetaSel ('Just "loc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "str") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "TokString" 'PrefixI 'True) (S1 ('MetaSel ('Just "loc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "str") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :+: (C1 ('MetaCons "TokKeyword" 'PrefixI 'True) (S1 ('MetaSel ('Just "loc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "kw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Keyword)) :+: (C1 ('MetaCons "TokSym" 'PrefixI 'True) (S1 ('MetaSel ('Just "loc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "sym") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Sym)) :+: C1 ('MetaCons "TokBuiltin" 'PrefixI 'True) (S1 ('MetaSel ('Just "loc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "builtin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Builtin))))))

AST

data Dickinson a #

Instances

Instances details
Functor Dickinson 
Instance details

Defined in Language.Dickinson.Type

Methods

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

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

Show a => Show (Dickinson a) 
Instance details

Defined in Language.Dickinson.Type

Generic (Dickinson a) 
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 #

Binary a => Binary (Dickinson a) 
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) 
Instance details

Defined in Language.Dickinson.Type

Methods

rnf :: Dickinson a -> () #

Pretty (Dickinson a) 
Instance details

Defined in Language.Dickinson.Type

Methods

pretty :: Dickinson a -> Doc ann

prettyList :: [Dickinson a] -> Doc ann

type Rep (Dickinson a) 
Instance details

Defined in Language.Dickinson.Type

type Rep (Dickinson a) = D1 ('MetaData "Dickinson" "Language.Dickinson.Type" "language-dickinson-1.3.0.0-inplace-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 #

Constructors

Define 

Fields

TyDecl 

Fields

Instances

Instances details
Functor Declaration 
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) 
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) #

Show a => Show (Declaration a) 
Instance details

Defined in Language.Dickinson.Type

Generic (Declaration a) 
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 #

Binary a => Binary (Declaration a) 
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) 
Instance details

Defined in Language.Dickinson.Type

Methods

rnf :: Declaration a -> () #

Pretty (Declaration a) 
Instance details

Defined in Language.Dickinson.Type

Methods

pretty :: Declaration a -> Doc ann

prettyList :: [Declaration a] -> Doc ann

type Rep (Declaration a) 
Instance details

Defined in Language.Dickinson.Type

type Rep (Declaration a) = D1 ('MetaData "Declaration" "Language.Dickinson.Type" "language-dickinson-1.3.0.0-inplace-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 Expression a #

Constructors

Literal 

Fields

StrChunk 

Fields

Choice 

Fields

Let 

Fields

Var 

Fields

Interp 

Fields

MultiInterp 

Fields

Lambda 
Apply 

Fields

Concat 

Fields

Tuple 

Fields

Match 
Flatten 

Fields

Annot 

Fields

Constructor 

Fields

BuiltinFn 

Fields

Instances

Instances details
Functor Expression 
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) 
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) #

Show a => Show (Expression a) 
Instance details

Defined in Language.Dickinson.Type

Generic (Expression a) 
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 #

Binary a => Binary (Expression a) 
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) 
Instance details

Defined in Language.Dickinson.Type

Methods

rnf :: Expression a -> () #

Pretty (Expression a) 
Instance details

Defined in Language.Dickinson.Type

Methods

pretty :: Expression a -> Doc ann

prettyList :: [Expression a] -> Doc ann

type Rep (Expression a) 
Instance details

Defined in Language.Dickinson.Type

type Rep (Expression a) = D1 ('MetaData "Expression" "Language.Dickinson.Type" "language-dickinson-1.3.0.0-inplace-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 "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))))))

data Builtin #

Instances

Instances details
Eq Builtin 
Instance details

Defined in Language.Dickinson.Lexer

Methods

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

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

Data Builtin 
Instance details

Defined in Language.Dickinson.Lexer

Methods

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

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

toConstr :: Builtin -> Constr #

dataTypeOf :: Builtin -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Builtin 
Instance details

Defined in Language.Dickinson.Lexer

Generic Builtin 
Instance details

Defined in Language.Dickinson.Lexer

Associated Types

type Rep Builtin :: Type -> Type #

Methods

from :: Builtin -> Rep Builtin x #

to :: Rep Builtin x -> Builtin #

Binary Builtin 
Instance details

Defined in Language.Dickinson.Lexer

Methods

put :: Builtin -> Put #

get :: Get Builtin #

putList :: [Builtin] -> Put #

NFData Builtin 
Instance details

Defined in Language.Dickinson.Lexer

Methods

rnf :: Builtin -> () #

Pretty Builtin 
Instance details

Defined in Language.Dickinson.Lexer

Methods

pretty :: Builtin -> Doc ann

prettyList :: [Builtin] -> Doc ann

type Rep Builtin 
Instance details

Defined in Language.Dickinson.Lexer

type Rep Builtin = D1 ('MetaData "Builtin" "Language.Dickinson.Lexer" "language-dickinson-1.3.0.0-inplace-dickinson" 'False) ((C1 ('MetaCons "Capitalize" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AllCaps" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Titlecase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Oulipo" 'PrefixI 'False) (U1 :: Type -> Type)))

data Pattern a #

Constructors

PatternVar 

Fields

PatternTuple 

Fields

PatternCons 

Fields

Wildcard 

Fields

OrPattern 

Fields

Instances

Instances details
Functor Pattern 
Instance details

Defined in Language.Dickinson.Type

Methods

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

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

Eq a => Eq (Pattern a) 
Instance details

Defined in Language.Dickinson.Type

Methods

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

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

Data a => Data (Pattern a) 
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) #

Show a => Show (Pattern a) 
Instance details

Defined in Language.Dickinson.Type

Methods

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

show :: Pattern a -> String #

showList :: [Pattern a] -> ShowS #

Generic (Pattern a) 
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 #

Binary a => Binary (Pattern a) 
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) 
Instance details

Defined in Language.Dickinson.Type

Methods

rnf :: Pattern a -> () #

Pretty (Pattern a) 
Instance details

Defined in Language.Dickinson.Type

Methods

pretty :: Pattern a -> Doc ann

prettyList :: [Pattern a] -> Doc ann

Debug (Pattern a) 
Instance details

Defined in Language.Dickinson.Type

Methods

debug :: Pattern a -> Doc b

type Rep (Pattern a) 
Instance details

Defined in Language.Dickinson.Type

data DickinsonTy a #

Constructors

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

Instances

Instances details
Functor DickinsonTy 
Instance details

Defined in Language.Dickinson.Type

Methods

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

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

Eq (DickinsonTy a) 
Instance details

Defined in Language.Dickinson.Type

Data a => Data (DickinsonTy a) 
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) #

Show a => Show (DickinsonTy a) 
Instance details

Defined in Language.Dickinson.Type

Generic (DickinsonTy a) 
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 #

Binary a => Binary (DickinsonTy a) 
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) 
Instance details

Defined in Language.Dickinson.Type

Methods

rnf :: DickinsonTy a -> () #

Pretty (DickinsonTy a) 
Instance details

Defined in Language.Dickinson.Type

Methods

pretty :: DickinsonTy a -> Doc ann

prettyList :: [DickinsonTy a] -> Doc ann

type Rep (DickinsonTy a) 
Instance details

Defined in Language.Dickinson.Type

data Name a #

Instances

Instances details
Functor Name 
Instance details

Defined in Language.Dickinson.Name

Methods

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

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

Eq (Name a) 
Instance details

Defined in Language.Dickinson.Name

Methods

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

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

Data a => Data (Name a) 
Instance details

Defined in Language.Dickinson.Name

Methods

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

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

toConstr :: Name a -> Constr #

dataTypeOf :: Name a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord (Name a) 
Instance details

Defined in Language.Dickinson.Name

Methods

compare :: Name a -> Name a -> Ordering #

(<) :: Name a -> Name a -> Bool #

(<=) :: Name a -> Name a -> Bool #

(>) :: Name a -> Name a -> Bool #

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

max :: Name a -> Name a -> Name a #

min :: Name a -> Name a -> Name a #

Show a => Show (Name a) 
Instance details

Defined in Language.Dickinson.Name

Methods

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

show :: Name a -> String #

showList :: [Name a] -> ShowS #

Generic (Name a) 
Instance details

Defined in Language.Dickinson.Name

Associated Types

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

Methods

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

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

Binary a => Binary (Name a) 
Instance details

Defined in Language.Dickinson.Name

Methods

put :: Name a -> Put #

get :: Get (Name a) #

putList :: [Name a] -> Put #

NFData a => NFData (Name a) 
Instance details

Defined in Language.Dickinson.Name

Methods

rnf :: Name a -> () #

Pretty (Name a) 
Instance details

Defined in Language.Dickinson.Name

Methods

pretty :: Name a -> Doc ann

prettyList :: [Name a] -> Doc ann

Debug (Name a) 
Instance details

Defined in Language.Dickinson.Name

Methods

debug :: Name a -> Doc b

type Rep (Name a) 
Instance details

Defined in Language.Dickinson.Name

type Rep (Name a) = D1 ('MetaData "Name" "Language.Dickinson.Name" "language-dickinson-1.3.0.0-inplace-dickinson" 'False) (C1 ('MetaCons "Name" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Text)) :*: (S1 ('MetaSel ('Just "unique") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Unique) :*: S1 ('MetaSel ('Just "loc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))

type TyName a = Name a #

Renamer

class HasRenames a where #

Methods

rename :: Lens' a Renames #

Instances

Instances details
HasRenames Renames 
Instance details

Defined in Language.Dickinson.Rename

Methods

rename :: Lens' Renames Renames #

HasRenames AmalgamateSt 
Instance details

Defined in Language.Dickinson.File

Methods

rename :: Lens' AmalgamateSt Renames #

HasRenames (EvalSt a) 
Instance details

Defined in Language.Dickinson.Eval

Methods

rename :: Lens' (EvalSt a) Renames #

Imports

Version info