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

Language.Dickinson.Error

Documentation

data DickinsonError a Source #

Instances

Instances details
(Pretty a, Typeable a) => Exception (DickinsonError a) Source # 
Instance details

Defined in Language.Dickinson.Error

Generic (DickinsonError a) Source # 
Instance details

Defined in Language.Dickinson.Error

Associated Types

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

Pretty a => Show (DickinsonError a) Source # 
Instance details

Defined in Language.Dickinson.Error

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

Defined in Language.Dickinson.Error

Methods

rnf :: DickinsonError a -> () #

Pretty a => Pretty (DickinsonError a) Source # 
Instance details

Defined in Language.Dickinson.Error

Methods

pretty :: DickinsonError a -> Doc ann #

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

type Rep (DickinsonError a) Source # 
Instance details

Defined in Language.Dickinson.Error

type Rep (DickinsonError a) = D1 ('MetaData "DickinsonError" "Language.Dickinson.Error" "language-dickinson-1.4.3.0-u4JKvBug5L7Xak6MfKGcR-dickinson" 'False) (((C1 ('MetaCons "UnfoundName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name a))) :+: (C1 ('MetaCons "NoText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "ParseErr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ParseError a))))) :+: (C1 ('MetaCons "ModuleNotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name a))) :+: (C1 ('MetaCons "TypeMismatch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DickinsonTy a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DickinsonTy a)))) :+: C1 ('MetaCons "PatternTypeMismatch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pattern a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DickinsonTy a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DickinsonTy a))))))) :+: ((C1 ('MetaCons "ExpectedLambda" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DickinsonTy a))) :+: (C1 ('MetaCons "MultiBind" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pattern a)))) :+: C1 ('MetaCons "MalformedTuple" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))) :+: ((C1 ('MetaCons "UnfoundConstructor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TyName a))) :+: C1 ('MetaCons "UnfoundType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name a)))) :+: (C1 ('MetaCons "PatternFail" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a))) :+: C1 ('MetaCons "SuspectPattern" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pattern a)))))))

data DickinsonWarning a Source #

Instances

Instances details
(Pretty a, Typeable a) => Exception (DickinsonWarning a) Source # 
Instance details

Defined in Language.Dickinson.Error

Generic (DickinsonWarning a) Source # 
Instance details

Defined in Language.Dickinson.Error

Associated Types

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

Pretty a => Show (DickinsonWarning a) Source # 
Instance details

Defined in Language.Dickinson.Error

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

Defined in Language.Dickinson.Error

Methods

rnf :: DickinsonWarning a -> () #

Pretty a => Pretty (DickinsonWarning a) Source # 
Instance details

Defined in Language.Dickinson.Error

Methods

pretty :: DickinsonWarning a -> Doc ann #

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

type Rep (DickinsonWarning a) Source # 
Instance details

Defined in Language.Dickinson.Error

maybeThrow :: MonadError e m => Maybe e -> m () Source #