purescript-0.15.6: PureScript Programming Language Compiler
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.PureScript.Errors

Synopsis

Documentation

data PPEOptions Source #

Constructors

PPEOptions 

Fields

data Level Source #

How critical the issue is

Constructors

Error 
Warning 

Instances

Instances details
Show Level Source # 
Instance details

Defined in Language.PureScript.Errors

Methods

showsPrec :: Int -> Level -> ShowS #

show :: Level -> String #

showList :: [Level] -> ShowS #

data TypeMap Source #

A map from rigid type variable name/unknown variable pairs to new variables.

Constructors

TypeMap 

Fields

Instances

Instances details
Show TypeMap Source # 
Instance details

Defined in Language.PureScript.Errors

data SimpleErrorMessage Source #

A type of error messages

Constructors

InternalCompilerError Text Text 
ModuleNotFound ModuleName 
ErrorParsingFFIModule FilePath (Maybe ErrorMessage) 
ErrorParsingCSTModule ParserError 
WarningParsingCSTModule ParserWarning 
MissingFFIModule ModuleName 
UnnecessaryFFIModule ModuleName FilePath 
MissingFFIImplementations ModuleName [Ident] 
UnusedFFIImplementations ModuleName [Ident] 
InvalidFFIIdentifier ModuleName Text 
DeprecatedFFIPrime ModuleName Text 
DeprecatedFFICommonJSModule ModuleName FilePath 
UnsupportedFFICommonJSExports ModuleName [Text] 
UnsupportedFFICommonJSImports ModuleName [Text] 
FileIOError Text IOError

A description of what we were trying to do, and the error which occurred

InfiniteType SourceType 
InfiniteKind SourceType 
MultipleValueOpFixities (OpName 'ValueOpName) 
MultipleTypeOpFixities (OpName 'TypeOpName) 
OrphanTypeDeclaration Ident 
OrphanKindDeclaration (ProperName 'TypeName) 
OrphanRoleDeclaration (ProperName 'TypeName) 
RedefinedIdent Ident 
OverlappingNamesInLet 
UnknownName (Qualified Name) 
UnknownImport ModuleName Name 
UnknownImportDataConstructor ModuleName (ProperName 'TypeName) (ProperName 'ConstructorName) 
UnknownExport Name 
UnknownExportDataConstructor (ProperName 'TypeName) (ProperName 'ConstructorName) 
ScopeConflict Name [ModuleName] 
ScopeShadowing Name (Maybe ModuleName) [ModuleName] 
DeclConflict Name Name 
ExportConflict (Qualified Name) (Qualified Name) 
DuplicateModule ModuleName 
DuplicateTypeClass (ProperName 'ClassName) SourceSpan 
DuplicateInstance Ident SourceSpan 
DuplicateTypeArgument Text 
InvalidDoBind 
InvalidDoLet 
CycleInDeclaration Ident 
CycleInTypeSynonym (NonEmpty (ProperName 'TypeName)) 
CycleInTypeClassDeclaration (NonEmpty (Qualified (ProperName 'ClassName))) 
CycleInKindDeclaration (NonEmpty (Qualified (ProperName 'TypeName))) 
CycleInModules (NonEmpty ModuleName) 
NameIsUndefined Ident 
UndefinedTypeVariable (ProperName 'TypeName) 
PartiallyAppliedSynonym (Qualified (ProperName 'TypeName)) 
EscapedSkolem Text (Maybe SourceSpan) SourceType 
TypesDoNotUnify SourceType SourceType 
KindsDoNotUnify SourceType SourceType 
ConstrainedTypeUnified SourceType SourceType 
OverlappingInstances (Qualified (ProperName 'ClassName)) [SourceType] [Qualified (Either SourceType Ident)] 
NoInstanceFound 

Fields

AmbiguousTypeVariables SourceType [(Text, Int)] 
UnknownClass (Qualified (ProperName 'ClassName)) 
PossiblyInfiniteInstance (Qualified (ProperName 'ClassName)) [SourceType] 
PossiblyInfiniteCoercibleInstance 
CannotDerive (Qualified (ProperName 'ClassName)) [SourceType] 
InvalidDerivedInstance (Qualified (ProperName 'ClassName)) [SourceType] Int 
ExpectedTypeConstructor (Qualified (ProperName 'ClassName)) [SourceType] SourceType 
InvalidNewtypeInstance (Qualified (ProperName 'ClassName)) [SourceType] 
MissingNewtypeSuperclassInstance (Qualified (ProperName 'ClassName)) (Qualified (ProperName 'ClassName)) [SourceType] 
UnverifiableSuperclassInstance (Qualified (ProperName 'ClassName)) (Qualified (ProperName 'ClassName)) [SourceType] 
CannotFindDerivingType (ProperName 'TypeName) 
DuplicateLabel Label (Maybe Expr) 
DuplicateValueDeclaration Ident 
ArgListLengthsDiffer Ident 
OverlappingArgNames (Maybe Ident) 
MissingClassMember (NonEmpty (Ident, SourceType)) 
ExtraneousClassMember Ident (Qualified (ProperName 'ClassName)) 
ExpectedType SourceType SourceType 
IncorrectConstructorArity (Qualified (ProperName 'ConstructorName)) Int Int

constructor name, expected argument count, actual argument count

ExprDoesNotHaveType Expr SourceType 
PropertyIsMissing Label 
AdditionalProperty Label 
OrphanInstance Ident (Qualified (ProperName 'ClassName)) (Set ModuleName) [SourceType] 
InvalidNewtype (ProperName 'TypeName) 
InvalidInstanceHead SourceType 
TransitiveExportError DeclarationRef [DeclarationRef] 
TransitiveDctorExportError DeclarationRef [ProperName 'ConstructorName] 
HiddenConstructors DeclarationRef (Qualified (ProperName 'ClassName)) 
ShadowedName Ident 
ShadowedTypeVar Text 
UnusedTypeVar Text 
UnusedName Ident 
UnusedDeclaration Ident 
WildcardInferredType SourceType Context 
HoleInferredType Text SourceType Context (Maybe TypeSearch) 
MissingTypeDeclaration Ident SourceType 
MissingKindDeclaration KindSignatureFor (ProperName 'TypeName) SourceType 
OverlappingPattern [[Binder]] Bool 
IncompleteExhaustivityCheck 
ImportHidingModule ModuleName 
UnusedImport ModuleName (Maybe ModuleName) 
UnusedExplicitImport ModuleName [Name] (Maybe ModuleName) [DeclarationRef] 
UnusedDctorImport ModuleName (ProperName 'TypeName) (Maybe ModuleName) [DeclarationRef] 
UnusedDctorExplicitImport ModuleName (ProperName 'TypeName) [ProperName 'ConstructorName] (Maybe ModuleName) [DeclarationRef] 
DuplicateSelectiveImport ModuleName 
DuplicateImport ModuleName ImportDeclarationType (Maybe ModuleName) 
DuplicateImportRef Name 
DuplicateExportRef Name 
IntOutOfRange Integer Text Integer Integer 
ImplicitQualifiedImport ModuleName ModuleName [DeclarationRef] 
ImplicitQualifiedImportReExport ModuleName ModuleName [DeclarationRef] 
ImplicitImport ModuleName [DeclarationRef] 
HidingImport ModuleName [DeclarationRef] 
CaseBinderLengthDiffers Int [Binder] 
IncorrectAnonymousArgument 
InvalidOperatorInBinder (Qualified (OpName 'ValueOpName)) (Qualified Ident) 
CannotGeneralizeRecursiveFunction Ident SourceType 
CannotDeriveNewtypeForData (ProperName 'TypeName) 
ExpectedWildcard (ProperName 'TypeName) 
CannotUseBindWithDo Ident 
ClassInstanceArityMismatch Ident (Qualified (ProperName 'ClassName)) Int Int

instance name, type class, expected argument count, actual argument count

UserDefinedWarning SourceType

a user-defined warning raised by using the Warn type class

UnusableDeclaration Ident [[Text]]

a declaration couldn't be used because it contained free variables

CannotDefinePrimModules ModuleName 
MixedAssociativityError (NonEmpty (Qualified (OpName 'AnyOpName), Associativity)) 
NonAssociativeError (NonEmpty (Qualified (OpName 'AnyOpName))) 
QuantificationCheckFailureInKind Text 
QuantificationCheckFailureInType [Int] SourceType 
VisibleQuantificationCheckFailureInType Text 
UnsupportedTypeInKind SourceType 
RoleMismatch

Declared role was more permissive than inferred.

Fields

  • Text

    Type variable in question

  • Role

    inferred role

  • Role

    declared role

InvalidCoercibleInstanceDeclaration [SourceType] 
UnsupportedRoleDeclaration 
RoleDeclarationArityMismatch (ProperName 'TypeName) Int Int 
DuplicateRoleDeclaration (ProperName 'TypeName) 
CannotDeriveInvalidConstructorArg (Qualified (ProperName 'ClassName)) 

errorSpan :: ErrorMessage -> Maybe (NonEmpty SourceSpan) Source #

Get the source span for an error

errorModule :: ErrorMessage -> Maybe ModuleName Source #

Get the module name for an error

stripModuleAndSpan :: ErrorMessage -> ErrorMessage Source #

Remove the module name and span hints from an error

errorCode :: ErrorMessage -> Text Source #

Get the error code for a particular error type

nonEmpty :: MultipleErrors -> Bool Source #

Check whether a collection of errors is empty or not.

errorMessage :: SimpleErrorMessage -> MultipleErrors Source #

Create an error set from a single simple error message

errorMessage' :: SourceSpan -> SimpleErrorMessage -> MultipleErrors Source #

Create an error set from a single simple error message and source annotation

errorMessage'' :: NonEmpty SourceSpan -> SimpleErrorMessage -> MultipleErrors Source #

Create an error set from a single simple error message and source annotations

errorMessage''' :: [SourceSpan] -> SimpleErrorMessage -> MultipleErrors Source #

Create an error from multiple (possibly empty) source spans, reversed sorted.

singleError :: ErrorMessage -> MultipleErrors Source #

Create an error set from a single error message

onErrorMessages :: (ErrorMessage -> ErrorMessage) -> MultipleErrors -> MultipleErrors Source #

Lift a function on ErrorMessage to a function on MultipleErrors

addHint :: ErrorMessageHint -> MultipleErrors -> MultipleErrors Source #

Add a hint to an error message

addHints :: [ErrorMessageHint] -> MultipleErrors -> MultipleErrors Source #

Add hints to an error message

unwrapErrorMessage :: ErrorMessage -> SimpleErrorMessage Source #

Extract nested error messages from wrapper errors

defaultCodeColor :: (ColorIntensity, Color) Source #

Default color intensity and color for code

defaultPPEOptions :: PPEOptions Source #

Default options for PPEOptions

prettyPrintSingleError :: PPEOptions -> ErrorMessage -> Box Source #

Pretty print a single error, simplifying if necessary

prettyPrintMultipleErrors :: PPEOptions -> MultipleErrors -> String Source #

Pretty print multiple errors

prettyPrintMultipleWarnings :: PPEOptions -> MultipleErrors -> String Source #

Pretty print multiple warnings

prettyPrintMultipleWarningsBox :: PPEOptions -> MultipleErrors -> [Box] Source #

Pretty print warnings as a Box

prettyPrintMultipleErrorsBox :: PPEOptions -> MultipleErrors -> [Box] Source #

Pretty print errors as a Box

indent :: Box -> Box Source #

Indent to the right, and pad on top and bottom.

rethrow :: MonadError e m => (e -> e) -> m a -> m a Source #

Rethrow an error with a more detailed error message in the case of failure

warnAndRethrow :: (MonadError e m, MonadWriter e m) => (e -> e) -> m a -> m a Source #

rethrowWithPosition :: MonadError MultipleErrors m => SourceSpan -> m a -> m a Source #

Rethrow an error with source position information

escalateWarningWhen :: (MonadWriter MultipleErrors m, MonadError MultipleErrors m) => (ErrorMessage -> Bool) -> m a -> m a Source #

Runs a computation listening for warnings and then escalating any warnings that match the predicate to error status.

parU :: forall m a b. MonadError MultipleErrors m => [a] -> (a -> m b) -> m [b] Source #

Collect errors in in parallel