| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Agda.Syntax.Concrete.Definitions.Errors
Synopsis
- data DeclarationException = DeclarationException {}
- data DeclarationException'
- = MultipleEllipses Pattern
- | DuplicateDefinition Name
- | DuplicateAnonDeclaration Range
- | MissingWithClauses Name LHS
- | WrongDefinition Name DataRecOrFun DataRecOrFun
- | 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)
- declarationExceptionString :: DeclarationException' -> String
- 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
- | EmptyPolarityPragma Range
- | HiddenGeneralize Range
- | InvalidCatchallPragma Range
- | InvalidConstructorBlock Range
- | InvalidCoverageCheckPragma Range
- | InvalidNoPositivityCheckPragma Range
- | InvalidNoUniverseCheckPragma Range
- | InvalidTerminationCheckPragma Range
- | MissingDataDeclaration Name
- | MissingDefinitions (List1 (Name, Range))
- | NotAllowedInMutual Range String
- | OpenImportPrivate Range KwRange KwRange OpenOrImport
- | OpenImportAbstract Range KwRange OpenOrImport
- | PolarityPragmasButNotPostulates (Set1 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 (Set1 Name)
- | UnknownNamesInFixityDecl (Set1 Name)
- | UnknownNamesInPolarityPragmas (Set1 Name)
- | UselessAbstract KwRange
- | UselessInstance KwRange
- | UselessMacro KwRange
- | UselessPrivate KwRange
- data OpenOrImport
- 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
Constructors
| DeclarationException | |
Fields | |
Instances
| HasRange DeclarationException Source # | |
Defined in Agda.Syntax.Concrete.Definitions.Errors Methods getRange :: DeclarationException -> Range Source # | |
| MonadError DeclarationException Nice Source # | |
Defined in Agda.Syntax.Concrete.Definitions.Monad Methods throwError :: DeclarationException -> Nice a # catchError :: Nice a -> (DeclarationException -> Nice a) -> Nice a # | |
data DeclarationException' Source #
The exception type.
Constructors
| MultipleEllipses Pattern | |
| DuplicateDefinition Name | |
| DuplicateAnonDeclaration Range | |
| MissingWithClauses Name LHS | |
| WrongDefinition Name DataRecOrFun DataRecOrFun | |
| 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
declarationExceptionString :: DeclarationException' -> String Source #
The name of the error.
data DeclarationWarning Source #
Constructors
| DeclarationWarning | |
Fields | |
Instances
| Pretty DeclarationWarning Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors Methods pretty :: DeclarationWarning -> Doc Source # prettyPrec :: Int -> DeclarationWarning -> Doc Source # prettyList :: [DeclarationWarning] -> Doc Source # | |||||
| HasRange DeclarationWarning Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors Methods getRange :: DeclarationWarning -> Range Source # | |||||
| EmbPrj DeclarationWarning Source # | |||||
Defined in Agda.TypeChecking.Serialise.Instances.Errors | |||||
| NFData DeclarationWarning Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors Methods rnf :: DeclarationWarning -> () # | |||||
| Generic DeclarationWarning Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors Associated Types
Methods from :: DeclarationWarning -> Rep DeclarationWarning x # to :: Rep DeclarationWarning x -> DeclarationWarning # | |||||
| Show DeclarationWarning Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors Methods 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.7.20250510-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.
Constructors
| 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 |
| EmptyPolarityPragma Range | POLARITY pragma without any polarities. |
| HiddenGeneralize Range | A |
| InvalidCatchallPragma Range | A {-# CATCHALL #-} pragma that does not precede a function clause. |
| 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. |
| MissingDataDeclaration Name | A |
| MissingDefinitions (List1 (Name, Range)) | Declarations (e.g. type signatures) without a definition. |
| NotAllowedInMutual Range String | |
| OpenImportPrivate Range KwRange KwRange OpenOrImport |
|
| OpenImportAbstract Range KwRange OpenOrImport |
|
| PolarityPragmasButNotPostulates (Set1 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 (Set1 Name) | Public mixfix identifiers without a fixity declaration. |
| UnknownNamesInFixityDecl (Set1 Name) | |
| UnknownNamesInPolarityPragmas (Set1 Name) | |
| UselessAbstract KwRange |
|
| UselessInstance KwRange |
|
| UselessMacro KwRange |
|
| UselessPrivate KwRange |
|
Instances
| Pretty DeclarationWarning' Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors Methods pretty :: DeclarationWarning' -> Doc Source # prettyPrec :: Int -> DeclarationWarning' -> Doc Source # prettyList :: [DeclarationWarning'] -> Doc Source # | |||||
| HasRange DeclarationWarning' Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors Methods getRange :: DeclarationWarning' -> Range Source # | |||||
| EmbPrj DeclarationWarning' Source # | |||||
Defined in Agda.TypeChecking.Serialise.Instances.Errors | |||||
| NFData DeclarationWarning' Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors Methods rnf :: DeclarationWarning' -> () # | |||||
| Generic DeclarationWarning' Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors Associated Types
Methods from :: DeclarationWarning' -> Rep DeclarationWarning' x # to :: Rep DeclarationWarning' x -> DeclarationWarning' # | |||||
| Show DeclarationWarning' Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors Methods 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.7.20250510-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 "EmptyPolarityPragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: 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 "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 "MissingDataDeclaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: (C1 ('MetaCons "MissingDefinitions" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (List1 (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 "OpenImportPrivate" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OpenOrImport))) :+: C1 ('MetaCons "OpenImportAbstract" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KwRange) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OpenOrImport)))) :+: (C1 ('MetaCons "PolarityPragmasButNotPostulates" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set1 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 (Set1 Name)))))) :+: ((C1 ('MetaCons "UnknownNamesInFixityDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set1 Name))) :+: (C1 ('MetaCons "UnknownNamesInPolarityPragmas" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set1 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)))))))) | |||||
data OpenOrImport Source #
open or import
Constructors
| OpenNotImport |
|
| ImportMayOpen |
|
Instances
| Pretty OpenOrImport Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors Methods pretty :: OpenOrImport -> Doc Source # prettyPrec :: Int -> OpenOrImport -> Doc Source # prettyList :: [OpenOrImport] -> Doc Source # | |||||
| EmbPrj OpenOrImport Source # | |||||
Defined in Agda.TypeChecking.Serialise.Instances.Errors | |||||
| NFData OpenOrImport Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors Methods rnf :: OpenOrImport -> () # | |||||
| Bounded OpenOrImport Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors | |||||
| Enum OpenOrImport Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors Methods succ :: OpenOrImport -> OpenOrImport # pred :: OpenOrImport -> OpenOrImport # toEnum :: Int -> OpenOrImport # fromEnum :: OpenOrImport -> Int # enumFrom :: OpenOrImport -> [OpenOrImport] # enumFromThen :: OpenOrImport -> OpenOrImport -> [OpenOrImport] # enumFromTo :: OpenOrImport -> OpenOrImport -> [OpenOrImport] # enumFromThenTo :: OpenOrImport -> OpenOrImport -> OpenOrImport -> [OpenOrImport] # | |||||
| Generic OpenOrImport Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors Associated Types
| |||||
| Show OpenOrImport Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors Methods showsPrec :: Int -> OpenOrImport -> ShowS # show :: OpenOrImport -> String # showList :: [OpenOrImport] -> ShowS # | |||||
| type Rep OpenOrImport Source # | |||||
Defined in Agda.Syntax.Concrete.Definitions.Errors | |||||
unsafeDeclarationWarning :: DeclarationWarning -> Bool Source #
Nicifier warnings turned into errors in --safe mode.
unsafePragma :: CMaybe DeclarationWarning' m => Pragma -> m Source #
Pragmas not allowed in --safe mode produce an unsafeDeclarationWarning.