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

Language.Dickinson.Lexer

Documentation

scdInitState :: [ScdState] Source #

data AlexPosn Source #

Constructors

AlexPn !Int !Int !Int 

Instances

Instances details
Data AlexPosn Source # 
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 #

Generic AlexPosn Source # 
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 #

Show AlexPosn Source # 
Instance details

Defined in Language.Dickinson.Lexer

Binary AlexPosn Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

put :: AlexPosn -> Put #

get :: Get AlexPosn #

putList :: [AlexPosn] -> Put #

NFData AlexPosn Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

rnf :: AlexPosn -> () #

Eq AlexPosn Source # 
Instance details

Defined in Language.Dickinson.Lexer

Pretty AlexPosn Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

pretty :: AlexPosn -> Doc ann #

prettyList :: [AlexPosn] -> Doc ann #

type Rep AlexPosn Source # 
Instance details

Defined in Language.Dickinson.Lexer

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

newtype Alex a Source #

Constructors

Alex 

Fields

Instances

Instances details
MonadFail Alex Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

fail :: String -> Alex a #

Applicative Alex Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

pure :: a -> Alex a #

(<*>) :: Alex (a -> b) -> Alex a -> Alex b #

liftA2 :: (a -> b -> c) -> Alex a -> Alex b -> Alex c #

(*>) :: Alex a -> Alex b -> Alex b #

(<*) :: Alex a -> Alex b -> Alex a #

Functor Alex Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

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

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

Monad Alex Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

(>>=) :: Alex a -> (a -> Alex b) -> Alex b #

(>>) :: Alex a -> Alex b -> Alex b #

return :: a -> Alex a #

data Token a Source #

Constructors

EOF 

Fields

TokIdent 

Fields

TokTyCons 

Fields

TokDouble 

Fields

TokStrChunk 

Fields

TokString 

Fields

TokKeyword 

Fields

TokSym 

Fields

TokBuiltin 

Fields

Instances

Instances details
Generic (Token a) Source # 
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) Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

rnf :: Token a -> () #

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

Defined in Language.Dickinson.Lexer

Methods

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

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

Pretty (Token a) Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

pretty :: Token a -> Doc ann #

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

type Rep (Token a) Source # 
Instance details

Defined in Language.Dickinson.Lexer

type Rep (Token a) = D1 ('MetaData "Token" "Language.Dickinson.Lexer" "language-dickinson-1.4.3.0-u4JKvBug5L7Xak6MfKGcR-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))))))

data Keyword Source #

Instances

Instances details
Generic Keyword Source # 
Instance details

Defined in Language.Dickinson.Lexer

Associated Types

type Rep Keyword :: Type -> Type #

Methods

from :: Keyword -> Rep Keyword x #

to :: Rep Keyword x -> Keyword #

NFData Keyword Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

rnf :: Keyword -> () #

Eq Keyword Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

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

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

Pretty Keyword Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

pretty :: Keyword -> Doc ann #

prettyList :: [Keyword] -> Doc ann #

type Rep Keyword Source # 
Instance details

Defined in Language.Dickinson.Lexer

type Rep Keyword = D1 ('MetaData "Keyword" "Language.Dickinson.Lexer" "language-dickinson-1.4.3.0-u4JKvBug5L7Xak6MfKGcR-dickinson" 'False) (((C1 ('MetaCons "KwDef" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KwLet" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwBranch" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KwOneof" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KwInclude" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwLambda" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KwText" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KwMatch" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwFlatten" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KwTyDecl" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KwRand" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwBind" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Sym Source #

Instances

Instances details
Generic Sym Source # 
Instance details

Defined in Language.Dickinson.Lexer

Associated Types

type Rep Sym :: Type -> Type #

Methods

from :: Sym -> Rep Sym x #

to :: Rep Sym x -> Sym #

NFData Sym Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

rnf :: Sym -> () #

Eq Sym Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

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

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

Pretty Sym Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

pretty :: Sym -> Doc ann #

prettyList :: [Sym] -> Doc ann #

type Rep Sym Source # 
Instance details

Defined in Language.Dickinson.Lexer

type Rep Sym = D1 ('MetaData "Sym" "Language.Dickinson.Lexer" "language-dickinson-1.4.3.0-u4JKvBug5L7Xak6MfKGcR-dickinson" 'False) ((((C1 ('MetaCons "LParen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RParen" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "VBar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LSqBracket" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "RSqBracket" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RBracket" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BeginInterp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EndInterp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StrBegin" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "StrEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MultiStrBegin" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MultiStrEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Arrow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DollarSign" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Comma" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Underscore" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Colon" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DeclBreak" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Eq" 'PrefixI 'False) (U1 :: Type -> Type))))))

data Builtin Source #

Constructors

Capitalize 
AllCaps 
Titlecase 
Oulipo

Filter all es from text.

Instances

Instances details
Data Builtin Source # 
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 #

Generic Builtin Source # 
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 #

Show Builtin Source # 
Instance details

Defined in Language.Dickinson.Lexer

Binary Builtin Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

put :: Builtin -> Put #

get :: Get Builtin #

putList :: [Builtin] -> Put #

NFData Builtin Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

rnf :: Builtin -> () #

Eq Builtin Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

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

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

Pretty Builtin Source # 
Instance details

Defined in Language.Dickinson.Lexer

Methods

pretty :: Builtin -> Doc ann #

prettyList :: [Builtin] -> Doc ann #

type Rep Builtin Source # 
Instance details

Defined in Language.Dickinson.Lexer

type Rep Builtin = D1 ('MetaData "Builtin" "Language.Dickinson.Lexer" "language-dickinson-1.4.3.0-u4JKvBug5L7Xak6MfKGcR-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)))

class HasLexerState a where Source #

Instances

Instances details
HasLexerState (EvalSt a) Source # 
Instance details

Defined in Language.Dickinson.Eval