Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data DeclarationException = DeclarationException {}
- data DeclarationException'
- = MultipleEllipses Pattern
- | InvalidName Name
- | DuplicateDefinition Name
- | DuplicateAnonDeclaration Range
- | MissingWithClauses Name LHS
- | WrongDefinition Name DataRecOrFun DataRecOrFun
- | DeclarationPanic String
- | WrongContentBlock KindOfBlock Range
- | AmbiguousFunClauses LHS (List1 Name)
- | AmbiguousConstructor Range Name [Name]
- | InvalidMeasureMutual Range
- | UnquoteDefRequiresSignature (List1 Name)
- | BadMacroDef NiceDeclaration
- | UnfoldingOutsideOpaque KwRange
- | OpaqueInMutual KwRange
- | DisallowedInterleavedMutual KwRange String (List1 Name)
- data DeclarationWarning = DeclarationWarning {}
- data DeclarationWarning'
- = EmptyAbstract KwRange
- | EmptyConstructor KwRange
- | EmptyField KwRange
- | EmptyGeneralize KwRange
- | EmptyInstance KwRange
- | EmptyMacro KwRange
- | EmptyMutual KwRange
- | EmptyPostulate KwRange
- | EmptyPrivate KwRange
- | EmptyPrimitive KwRange
- | HiddenGeneralize Range
- | InvalidCatchallPragma Range
- | InvalidConstructor Range
- | InvalidConstructorBlock Range
- | InvalidCoverageCheckPragma Range
- | InvalidNoPositivityCheckPragma Range
- | InvalidNoUniverseCheckPragma Range
- | InvalidTerminationCheckPragma Range
- | MissingDeclarations [(Name, Range)]
- | MissingDefinitions [(Name, Range)]
- | NotAllowedInMutual Range String
- | OpenPublicPrivate KwRange
- | OpenPublicAbstract KwRange
- | PolarityPragmasButNotPostulates [Name]
- | PragmaNoTerminationCheck Range
- | PragmaCompiled Range
- | SafeFlagEta Range
- | SafeFlagInjective Range
- | SafeFlagNoCoverageCheck Range
- | SafeFlagNoPositivityCheck Range
- | SafeFlagNoUniverseCheck Range
- | SafeFlagNonTerminating Range
- | SafeFlagPolarity Range
- | SafeFlagTerminating Range
- | ShadowingInTelescope (List1 (Name, List2 Range))
- | UnknownFixityInMixfixDecl [Name]
- | UnknownNamesInFixityDecl [Name]
- | UnknownNamesInPolarityPragmas [Name]
- | UselessAbstract KwRange
- | UselessInstance KwRange
- | UselessMacro KwRange
- | UselessPrivate KwRange
- declarationWarningName :: DeclarationWarning -> WarningName
- declarationWarningName' :: DeclarationWarning' -> WarningName
- unsafeDeclarationWarning :: DeclarationWarning -> Bool
- unsafeDeclarationWarning' :: DeclarationWarning' -> Bool
- unsafePragma :: CMaybe DeclarationWarning' m => Pragma -> m
Documentation
data DeclarationException Source #
Exception with internal source code callstack
Instances
HasRange DeclarationException Source # | |
Defined in Agda.Syntax.Concrete.Definitions.Errors getRange :: DeclarationException -> Range Source # | |
MonadError DeclarationException Nice | |
Defined in Agda.Syntax.Concrete.Definitions.Monad throwError :: DeclarationException -> Nice a catchError :: Nice a -> (DeclarationException -> Nice a) -> Nice a |
data DeclarationException' Source #
The exception type.
MultipleEllipses Pattern | |
InvalidName Name | |
DuplicateDefinition Name | |
DuplicateAnonDeclaration Range | |
MissingWithClauses Name LHS | |
WrongDefinition Name DataRecOrFun DataRecOrFun | |
DeclarationPanic String | |
WrongContentBlock KindOfBlock Range | |
AmbiguousFunClauses LHS (List1 Name) | In a mutual block, a clause could belong to any of the ≥2 type signatures ( |
AmbiguousConstructor Range Name [Name] | In an interleaved mutual block, a constructor could belong to any of the data signatures ( |
InvalidMeasureMutual Range | In a mutual block, all or none need a MEASURE pragma.
|
UnquoteDefRequiresSignature (List1 Name) | |
BadMacroDef NiceDeclaration | |
UnfoldingOutsideOpaque KwRange | An unfolding declaration was not the first declaration contained in an opaque block. |
OpaqueInMutual KwRange |
|
DisallowedInterleavedMutual KwRange String (List1 Name) | A declaration that breaks an implicit mutual block (named by the String argument) was present while the given lone type signatures were still without their definitions. |
Instances
Pretty DeclarationException' Source # | |
Defined in Agda.Syntax.Concrete.Definitions.Errors pretty :: DeclarationException' -> Doc Source # prettyPrec :: Int -> DeclarationException' -> Doc Source # prettyList :: [DeclarationException'] -> Doc Source # | |
HasRange DeclarationException' Source # | |
Defined in Agda.Syntax.Concrete.Definitions.Errors | |
Show DeclarationException' Source # | |
Defined in Agda.Syntax.Concrete.Definitions.Errors showsPrec :: Int -> DeclarationException' -> ShowS show :: DeclarationException' -> String showList :: [DeclarationException'] -> ShowS |
data DeclarationWarning Source #
Instances
Pretty DeclarationWarning Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors pretty :: DeclarationWarning -> Doc Source # prettyPrec :: Int -> DeclarationWarning -> Doc Source # prettyList :: [DeclarationWarning] -> Doc Source # | |||||
HasRange DeclarationWarning Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors getRange :: DeclarationWarning -> Range Source # | |||||
EmbPrj DeclarationWarning Source # | |||||
Defined in Agda.TypeChecking.Serialise.Instances.Errors icode :: DeclarationWarning -> S Int32 Source # icod_ :: DeclarationWarning -> S Int32 Source # value :: Int32 -> R DeclarationWarning Source # | |||||
NFData DeclarationWarning Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors rnf :: DeclarationWarning -> () | |||||
Generic DeclarationWarning Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors
from :: DeclarationWarning -> Rep DeclarationWarning x to :: Rep DeclarationWarning x -> DeclarationWarning | |||||
Show DeclarationWarning Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors showsPrec :: Int -> DeclarationWarning -> ShowS show :: DeclarationWarning -> String showList :: [DeclarationWarning] -> ShowS | |||||
type Rep DeclarationWarning Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors type Rep DeclarationWarning = D1 ('MetaData "DeclarationWarning" "Agda.Syntax.Concrete.Definitions.Errors" "Agda-2.6.20240714-inplace" 'False) (C1 ('MetaCons "DeclarationWarning" 'PrefixI 'True) (S1 ('MetaSel ('Just "dwLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CallStack) :*: S1 ('MetaSel ('Just "dwWarning") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DeclarationWarning'))) |
data DeclarationWarning' Source #
Non-fatal errors encountered in the Nicifier.
EmptyAbstract KwRange | Empty |
EmptyConstructor KwRange | Empty |
EmptyField KwRange | Empty |
EmptyGeneralize KwRange | Empty |
EmptyInstance KwRange | Empty |
EmptyMacro KwRange | Empty |
EmptyMutual KwRange | Empty |
EmptyPostulate KwRange | Empty |
EmptyPrivate KwRange | Empty |
EmptyPrimitive KwRange | Empty |
HiddenGeneralize Range | A |
InvalidCatchallPragma Range | A {-# CATCHALL #-} pragma that does not precede a function clause. |
InvalidConstructor Range | Invalid definition in a constructor block |
InvalidConstructorBlock Range | Invalid constructor block (not inside an interleaved mutual block) |
InvalidCoverageCheckPragma Range | A {-# NON_COVERING #-} pragma that does not apply to any function. |
InvalidNoPositivityCheckPragma Range | A {-# NO_POSITIVITY_CHECK #-} pragma that does not apply to any data or record type. |
InvalidNoUniverseCheckPragma Range | A {-# NO_UNIVERSE_CHECK #-} pragma that does not apply to a data or record type. |
InvalidTerminationCheckPragma Range | A {-# TERMINATING #-} and {-# NON_TERMINATING #-} pragma that does not apply to any function. |
MissingDeclarations [(Name, Range)] | Definitions (e.g. constructors or functions) without a declaration. |
MissingDefinitions [(Name, Range)] | Declarations (e.g. type signatures) without a definition. |
NotAllowedInMutual Range String | |
OpenPublicPrivate KwRange |
|
OpenPublicAbstract KwRange |
|
PolarityPragmasButNotPostulates [Name] | |
PragmaNoTerminationCheck Range | Pragma |
PragmaCompiled Range |
|
SafeFlagEta Range |
|
SafeFlagInjective Range |
|
SafeFlagNoCoverageCheck Range |
|
SafeFlagNoPositivityCheck Range |
|
SafeFlagNoUniverseCheck Range |
|
SafeFlagNonTerminating Range |
|
SafeFlagPolarity Range |
|
SafeFlagTerminating Range |
|
ShadowingInTelescope (List1 (Name, List2 Range)) | |
UnknownFixityInMixfixDecl [Name] | |
UnknownNamesInFixityDecl [Name] | |
UnknownNamesInPolarityPragmas [Name] | |
UselessAbstract KwRange |
|
UselessInstance KwRange |
|
UselessMacro KwRange |
|
UselessPrivate KwRange |
|
Instances
Pretty DeclarationWarning' Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors pretty :: DeclarationWarning' -> Doc Source # prettyPrec :: Int -> DeclarationWarning' -> Doc Source # prettyList :: [DeclarationWarning'] -> Doc Source # | |||||
HasRange DeclarationWarning' Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors getRange :: DeclarationWarning' -> Range Source # | |||||
EmbPrj DeclarationWarning' Source # | |||||
Defined in Agda.TypeChecking.Serialise.Instances.Errors icode :: DeclarationWarning' -> S Int32 Source # icod_ :: DeclarationWarning' -> S Int32 Source # value :: Int32 -> R DeclarationWarning' Source # | |||||
NFData DeclarationWarning' Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors rnf :: DeclarationWarning' -> () | |||||
Generic DeclarationWarning' Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors
from :: DeclarationWarning' -> Rep DeclarationWarning' x to :: Rep DeclarationWarning' x -> DeclarationWarning' | |||||
Show DeclarationWarning' Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors showsPrec :: Int -> DeclarationWarning' -> ShowS show :: DeclarationWarning' -> String showList :: [DeclarationWarning'] -> ShowS | |||||
type Rep DeclarationWarning' Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors type Rep DeclarationWarning' = D1 ('MetaData "DeclarationWarning'" "Agda.Syntax.Concrete.Definitions.Errors" "Agda-2.6.20240714-inplace" 'False) (((((C1 ('MetaCons "EmptyAbstract" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange)) :+: C1 ('MetaCons "EmptyConstructor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange))) :+: (C1 ('MetaCons "EmptyField" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange)) :+: (C1 ('MetaCons "EmptyGeneralize" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange)) :+: C1 ('MetaCons "EmptyInstance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange))))) :+: ((C1 ('MetaCons "EmptyMacro" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange)) :+: C1 ('MetaCons "EmptyMutual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange))) :+: (C1 ('MetaCons "EmptyPostulate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange)) :+: (C1 ('MetaCons "EmptyPrivate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange)) :+: C1 ('MetaCons "EmptyPrimitive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange)))))) :+: (((C1 ('MetaCons "HiddenGeneralize" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: C1 ('MetaCons "InvalidCatchallPragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range))) :+: (C1 ('MetaCons "InvalidConstructor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: (C1 ('MetaCons "InvalidConstructorBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: C1 ('MetaCons "InvalidCoverageCheckPragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range))))) :+: ((C1 ('MetaCons "InvalidNoPositivityCheckPragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: (C1 ('MetaCons "InvalidNoUniverseCheckPragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: C1 ('MetaCons "InvalidTerminationCheckPragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)))) :+: (C1 ('MetaCons "MissingDeclarations" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Name, Range)])) :+: (C1 ('MetaCons "MissingDefinitions" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Name, Range)])) :+: C1 ('MetaCons "NotAllowedInMutual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))) :+: ((((C1 ('MetaCons "OpenPublicPrivate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange)) :+: C1 ('MetaCons "OpenPublicAbstract" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange))) :+: (C1 ('MetaCons "PolarityPragmasButNotPostulates" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name])) :+: (C1 ('MetaCons "PragmaNoTerminationCheck" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: C1 ('MetaCons "PragmaCompiled" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range))))) :+: ((C1 ('MetaCons "SafeFlagEta" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: C1 ('MetaCons "SafeFlagInjective" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range))) :+: (C1 ('MetaCons "SafeFlagNoCoverageCheck" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: (C1 ('MetaCons "SafeFlagNoPositivityCheck" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: C1 ('MetaCons "SafeFlagNoUniverseCheck" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)))))) :+: (((C1 ('MetaCons "SafeFlagNonTerminating" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: C1 ('MetaCons "SafeFlagPolarity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range))) :+: (C1 ('MetaCons "SafeFlagTerminating" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: (C1 ('MetaCons "ShadowingInTelescope" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (List1 (Name, List2 Range)))) :+: C1 ('MetaCons "UnknownFixityInMixfixDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]))))) :+: ((C1 ('MetaCons "UnknownNamesInFixityDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name])) :+: (C1 ('MetaCons "UnknownNamesInPolarityPragmas" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name])) :+: C1 ('MetaCons "UselessAbstract" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange)))) :+: (C1 ('MetaCons "UselessInstance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange)) :+: (C1 ('MetaCons "UselessMacro" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange)) :+: C1 ('MetaCons "UselessPrivate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange)))))))) |
unsafeDeclarationWarning :: DeclarationWarning -> Bool Source #
Nicifier warnings turned into errors in --safe
mode.
unsafeDeclarationWarning' :: DeclarationWarning' -> Bool Source #
unsafePragma :: CMaybe DeclarationWarning' m => Pragma -> m Source #
Pragmas not allowed in --safe
mode produce an unsafeDeclarationWarning
.