Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type PsWarning = PsMessage
- type PsError = PsMessage
- data PsHeaderMessage
- data PsMessage
- = PsUnknownMessage UnknownDiagnostic
- | PsHeaderMessage !PsHeaderMessage
- | PsWarnBidirectionalFormatChars (NonEmpty (PsLoc, Char, String))
- | PsWarnTab !Word
- | PsWarnTransitionalLayout !TransLayoutReason
- | PsWarnUnrecognisedPragma !String ![String]
- | PsWarnMisplacedPragma !FileHeaderPragmaType
- | PsWarnHaddockInvalidPos
- | PsWarnHaddockIgnoreMulti
- | PsWarnStarBinder
- | PsWarnStarIsType
- | PsWarnImportPreQualified
- | PsWarnOperatorWhitespaceExtConflict !OperatorWhitespaceSymbol
- | PsWarnOperatorWhitespace !FastString !OperatorWhitespaceOccurrence
- | PsErrLambdaCase
- | PsErrEmptyLambda
- | PsErrNumUnderscores !NumUnderscoreReason
- | PsErrPrimStringInvalidChar
- | PsErrMissingBlock
- | PsErrLexer !LexErr !LexErrKind
- | PsErrSuffixAT
- | PsErrParse !String !PsErrParseDetails
- | PsErrCmmLexer
- | PsErrUnsupportedBoxedSumExpr !(SumOrTuple (HsExpr GhcPs))
- | PsErrUnsupportedBoxedSumPat !(SumOrTuple (PatBuilder GhcPs))
- | PsErrUnexpectedQualifiedConstructor !RdrName
- | PsErrTupleSectionInPat
- | PsErrIllegalBangPattern !(Pat GhcPs)
- | PsErrOpFewArgs !StarIsType !RdrName
- | PsErrImportQualifiedTwice
- | PsErrImportPostQualified
- | PsErrIllegalExplicitNamespace
- | PsErrVarForTyCon !RdrName
- | PsErrIllegalPatSynExport
- | PsErrMalformedEntityString
- | PsErrDotsInRecordUpdate
- | PsErrPrecedenceOutOfRange !Int
- | PsErrOverloadedRecordDotInvalid
- | PsErrOverloadedRecordUpdateNotEnabled
- | PsErrOverloadedRecordUpdateNoQualifiedFields
- | PsErrInvalidDataCon !(HsType GhcPs)
- | PsErrInvalidInfixDataCon !(HsType GhcPs) !RdrName !(HsType GhcPs)
- | PsErrIllegalPromotionQuoteDataCon !RdrName
- | PsErrUnpackDataCon
- | PsErrUnexpectedKindAppInDataCon !DataConBuilder !(HsType GhcPs)
- | PsErrInvalidRecordCon !(PatBuilder GhcPs)
- | PsErrIllegalUnboxedStringInPat !(HsLit GhcPs)
- | PsErrIllegalUnboxedFloatingLitInPat !(HsLit GhcPs)
- | PsErrDoNotationInPat
- | PsErrIfThenElseInPat
- | PsErrLambdaCaseInPat LamCaseVariant
- | PsErrCaseInPat
- | PsErrLetInPat
- | PsErrLambdaInPat
- | PsErrArrowExprInPat !(HsExpr GhcPs)
- | PsErrArrowCmdInPat !(HsCmd GhcPs)
- | PsErrArrowCmdInExpr !(HsCmd GhcPs)
- | PsErrViewPatInExpr !(LHsExpr GhcPs) !(LHsExpr GhcPs)
- | PsErrTypeAppWithoutSpace !RdrName !(LHsExpr GhcPs)
- | PsErrLazyPatWithoutSpace !(LHsExpr GhcPs)
- | PsErrBangPatWithoutSpace !(LHsExpr GhcPs)
- | PsErrUnallowedPragma !(HsPragE GhcPs)
- | PsErrQualifiedDoInCmd !ModuleName
- | PsErrInvalidInfixHole
- | PsErrSemiColonsInCondExpr !(HsExpr GhcPs) !Bool !(HsExpr GhcPs) !Bool !(HsExpr GhcPs)
- | PsErrSemiColonsInCondCmd !(HsExpr GhcPs) !Bool !(HsCmd GhcPs) !Bool !(HsCmd GhcPs)
- | PsErrAtInPatPos
- | PsErrLambdaCmdInFunAppCmd !(LHsCmd GhcPs)
- | PsErrCaseCmdInFunAppCmd !(LHsCmd GhcPs)
- | PsErrLambdaCaseCmdInFunAppCmd !LamCaseVariant !(LHsCmd GhcPs)
- | PsErrIfCmdInFunAppCmd !(LHsCmd GhcPs)
- | PsErrLetCmdInFunAppCmd !(LHsCmd GhcPs)
- | PsErrDoCmdInFunAppCmd !(LHsCmd GhcPs)
- | PsErrDoInFunAppExpr !(Maybe ModuleName) !(LHsExpr GhcPs)
- | PsErrMDoInFunAppExpr !(Maybe ModuleName) !(LHsExpr GhcPs)
- | PsErrLambdaInFunAppExpr !(LHsExpr GhcPs)
- | PsErrCaseInFunAppExpr !(LHsExpr GhcPs)
- | PsErrLambdaCaseInFunAppExpr !LamCaseVariant !(LHsExpr GhcPs)
- | PsErrLetInFunAppExpr !(LHsExpr GhcPs)
- | PsErrIfInFunAppExpr !(LHsExpr GhcPs)
- | PsErrProcInFunAppExpr !(LHsExpr GhcPs)
- | PsErrMalformedTyOrClDecl !(LHsType GhcPs)
- | PsErrIllegalWhereInDataDecl
- | PsErrIllegalDataTypeContext !(LHsContext GhcPs)
- | PsErrParseErrorOnInput !OccName
- | PsErrMalformedDecl !SDoc !RdrName
- | PsErrUnexpectedTypeAppInDecl !(LHsType GhcPs) !SDoc !RdrName
- | PsErrNotADataCon !RdrName
- | PsErrRecordSyntaxInPatSynDecl !(LPat GhcPs)
- | PsErrEmptyWhereInPatSynDecl !RdrName
- | PsErrInvalidWhereBindInPatSynDecl !RdrName !(HsDecl GhcPs)
- | PsErrNoSingleWhereBindInPatSynDecl !RdrName !(HsDecl GhcPs)
- | PsErrDeclSpliceNotAtTopLevel !(SpliceDecl GhcPs)
- | PsErrInferredTypeVarNotAllowed
- | PsErrMultipleNamesInStandaloneKindSignature [LIdP GhcPs]
- | PsErrIllegalImportBundleForm
- | PsErrIllegalRoleName !FastString [Role]
- | PsErrInvalidTypeSignature !(LHsExpr GhcPs)
- | PsErrUnexpectedTypeInDecl !(LHsType GhcPs) !SDoc !RdrName [LHsTypeArg GhcPs] !SDoc
- | PsErrExpectedHyphen
- | PsErrSpaceInSCC
- | PsErrEmptyDoubleQuotes !Bool
- | PsErrInvalidPackageName !FastString
- | PsErrInvalidRuleActivationMarker
- | PsErrLinearFunction
- | PsErrMultiWayIf
- | PsErrExplicitForall !Bool
- | PsErrIllegalQualifiedDo !SDoc
- | PsErrCmmParser !CmmParserError
- | PsErrIllegalTraditionalRecordSyntax !SDoc
- | PsErrParseErrorInCmd !SDoc
- | PsErrInPat !(PatBuilder GhcPs) !PsErrInPatDetails
- | PsErrParseRightOpSectionInPat !RdrName !(PatBuilder GhcPs)
- | PsErrIllegalGadtRecordMultiplicity !(HsArrow GhcPs)
- | PsErrInvalidCApiImport
- | PsErrMultipleConForNewtype !RdrName !Int
- | PsErrUnicodeCharLooksLike Char Char String
- data PsErrParseDetails = PsErrParseDetails {}
- data PatIsRecursive
- data PatIncompleteDoBlock
- data ParseContext = ParseContext {}
- data PsErrInPatDetails
- noParseContext :: ParseContext
- incompleteDoBlock :: ParseContext
- fromParseContext :: ParseContext -> PsErrInPatDetails
- data NumUnderscoreReason
- data LexErrKind
- data LexErr
- data CmmParserError
- data TransLayoutReason
- data FileHeaderPragmaType
Documentation
data PsHeaderMessage Source #
PsErrParseLanguagePragma | |
PsErrUnsupportedExt !String ![String] | |
PsErrParseOptionsPragma !String | |
PsErrUnknownOptionsPragma !String | PsErrUnsupportedOptionsPragma is an error that occurs when an unknown OPTIONS_GHC pragma is supplied is found. Example(s): {-# OPTIONS_GHC foo #-} Test case(s): testssafeHaskellflags/SafeFlags28 testssafeHaskellflags/SafeFlags19 testssafeHaskellflags/SafeFlags29 testsparsershould_fail/T19923c testsparsershould_fail/T19923b testsparsershould_fail/readFail044 testsdriverT2499 |
Instances
PsUnknownMessage UnknownDiagnostic | An "unknown" message from the parser. This type constructor allows arbitrary messages to be embedded. The typical use case would be GHC plugins willing to emit custom diagnostics. |
PsHeaderMessage !PsHeaderMessage | A group of parser messages emitted in |
PsWarnBidirectionalFormatChars (NonEmpty (PsLoc, Char, String)) | PsWarnBidirectionalFormatChars is a warning (controlled by the -Wwarn-bidirectional-format-characters flag) that occurs when unicode bi-directional format characters are found within in a file The |
PsWarnTab | PsWarnTab is a warning (controlled by the -Wwarn-tabs flag) that occurs when tabulations (tabs) are found within a file. Test case(s): parsershould_failT12610 parsershould_compileT9723b parsershould_compileT9723a parsershould_compileread043 parsershould_failT16270 warningsshould_compileT9230 |
| |
PsWarnTransitionalLayout !TransLayoutReason | PsWarnTransitionalLayout is a warning (controlled by the -Walternative-layout-rule-transitional flag) that occurs when pipes ('|') or 'where' are at the same depth of an implicit layout block. Example(s): f :: IO () f | True = do let x = () y = () return () | True = return () Test case(s): layout/layout006 layout/layout003 layout/layout001 |
PsWarnUnrecognisedPragma !String ![String] | Unrecognised pragma. First field is the actual pragma name which might be empty. Second field is the set of valid candidate pragmas. |
PsWarnMisplacedPragma !FileHeaderPragmaType | |
PsWarnHaddockInvalidPos | Invalid Haddock comment position |
PsWarnHaddockIgnoreMulti | Multiple Haddock comment for the same entity |
PsWarnStarBinder | Found binding occurrence of "*" while StarIsType is enabled |
PsWarnStarIsType | Using "*" for Type without StarIsType enabled |
PsWarnImportPreQualified | Pre qualified import with |
PsWarnOperatorWhitespaceExtConflict !OperatorWhitespaceSymbol | |
PsWarnOperatorWhitespace !FastString !OperatorWhitespaceOccurrence | |
PsErrLambdaCase | LambdaCase syntax used without the extension enabled |
PsErrEmptyLambda | A lambda requires at least one parameter |
PsErrNumUnderscores !NumUnderscoreReason | Underscores in literals without the extension enabled |
PsErrPrimStringInvalidChar | Invalid character in primitive string |
PsErrMissingBlock | Missing block |
PsErrLexer !LexErr !LexErrKind | Lexer error |
PsErrSuffixAT | Suffix occurrence of |
PsErrParse !String !PsErrParseDetails | Parse errors |
PsErrCmmLexer | Cmm lexer error |
PsErrUnsupportedBoxedSumExpr !(SumOrTuple (HsExpr GhcPs)) | Unsupported boxed sum in expression |
PsErrUnsupportedBoxedSumPat !(SumOrTuple (PatBuilder GhcPs)) | Unsupported boxed sum in pattern |
PsErrUnexpectedQualifiedConstructor !RdrName | Unexpected qualified constructor |
PsErrTupleSectionInPat | Tuple section in pattern context |
PsErrIllegalBangPattern !(Pat GhcPs) | Bang-pattern without BangPattterns enabled |
PsErrOpFewArgs !StarIsType !RdrName | Operator applied to too few arguments |
PsErrImportQualifiedTwice | Import: multiple occurrences of |
PsErrImportPostQualified | Post qualified import without |
PsErrIllegalExplicitNamespace | Explicit namespace keyword without |
PsErrVarForTyCon !RdrName | Expecting a type constructor but found a variable |
PsErrIllegalPatSynExport | Illegal export form allowed by PatternSynonyms |
PsErrMalformedEntityString | Malformed entity string |
PsErrDotsInRecordUpdate | Dots used in record update |
PsErrPrecedenceOutOfRange !Int | Precedence out of range |
PsErrOverloadedRecordDotInvalid | Invalid use of record dot syntax |
PsErrOverloadedRecordUpdateNotEnabled |
|
PsErrOverloadedRecordUpdateNoQualifiedFields | Can't use qualified fields when OverloadedRecordUpdate is enabled. |
PsErrInvalidDataCon !(HsType GhcPs) | Cannot parse data constructor in a data/newtype declaration |
PsErrInvalidInfixDataCon !(HsType GhcPs) !RdrName !(HsType GhcPs) | Cannot parse data constructor in a data/newtype declaration |
PsErrIllegalPromotionQuoteDataCon !RdrName | Illegal DataKinds quote mark in data/newtype constructor declaration |
PsErrUnpackDataCon | UNPACK applied to a data constructor |
PsErrUnexpectedKindAppInDataCon !DataConBuilder !(HsType GhcPs) | Unexpected kind application in data/newtype declaration |
PsErrInvalidRecordCon !(PatBuilder GhcPs) | Not a record constructor |
PsErrIllegalUnboxedStringInPat !(HsLit GhcPs) | Illegal unboxed string literal in pattern |
PsErrIllegalUnboxedFloatingLitInPat !(HsLit GhcPs) | Illegal primitive floating point literal in pattern |
PsErrDoNotationInPat | Do-notation in pattern |
PsErrIfThenElseInPat | If-then-else syntax in pattern |
PsErrLambdaCaseInPat LamCaseVariant | Lambda-case in pattern |
PsErrCaseInPat | case..of in pattern |
PsErrLetInPat | let-syntax in pattern |
PsErrLambdaInPat | Lambda-syntax in pattern |
PsErrArrowExprInPat !(HsExpr GhcPs) | Arrow expression-syntax in pattern |
PsErrArrowCmdInPat !(HsCmd GhcPs) | Arrow command-syntax in pattern |
PsErrArrowCmdInExpr !(HsCmd GhcPs) | Arrow command-syntax in expression |
PsErrViewPatInExpr !(LHsExpr GhcPs) !(LHsExpr GhcPs) | View-pattern in expression |
PsErrTypeAppWithoutSpace !RdrName !(LHsExpr GhcPs) | Type-application without space before |
PsErrLazyPatWithoutSpace !(LHsExpr GhcPs) | Lazy-pattern ( |
PsErrBangPatWithoutSpace !(LHsExpr GhcPs) | Bang-pattern ( |
PsErrUnallowedPragma !(HsPragE GhcPs) | Pragma not allowed in this position |
PsErrQualifiedDoInCmd !ModuleName | Qualified do block in command |
PsErrInvalidInfixHole | Invalid infix hole, expected an infix operator |
PsErrSemiColonsInCondExpr | Unexpected semi-colons in conditional expression |
PsErrSemiColonsInCondCmd | Unexpected semi-colons in conditional command |
PsErrAtInPatPos | @-operator in a pattern position |
PsErrLambdaCmdInFunAppCmd !(LHsCmd GhcPs) | Unexpected lambda command in function application |
PsErrCaseCmdInFunAppCmd !(LHsCmd GhcPs) | Unexpected case command in function application |
PsErrLambdaCaseCmdInFunAppCmd !LamCaseVariant !(LHsCmd GhcPs) | Unexpected case(s) command in function application |
PsErrIfCmdInFunAppCmd !(LHsCmd GhcPs) | Unexpected if command in function application |
PsErrLetCmdInFunAppCmd !(LHsCmd GhcPs) | Unexpected let command in function application |
PsErrDoCmdInFunAppCmd !(LHsCmd GhcPs) | Unexpected do command in function application |
PsErrDoInFunAppExpr !(Maybe ModuleName) !(LHsExpr GhcPs) | Unexpected do block in function application |
PsErrMDoInFunAppExpr !(Maybe ModuleName) !(LHsExpr GhcPs) | Unexpected mdo block in function application |
PsErrLambdaInFunAppExpr !(LHsExpr GhcPs) | Unexpected lambda expression in function application |
PsErrCaseInFunAppExpr !(LHsExpr GhcPs) | Unexpected case expression in function application |
PsErrLambdaCaseInFunAppExpr !LamCaseVariant !(LHsExpr GhcPs) | Unexpected case(s) expression in function application |
PsErrLetInFunAppExpr !(LHsExpr GhcPs) | Unexpected let expression in function application |
PsErrIfInFunAppExpr !(LHsExpr GhcPs) | Unexpected if expression in function application |
PsErrProcInFunAppExpr !(LHsExpr GhcPs) | Unexpected proc expression in function application |
PsErrMalformedTyOrClDecl !(LHsType GhcPs) | Malformed head of type or class declaration |
PsErrIllegalWhereInDataDecl | Illegal 'where' keyword in data declaration |
PsErrIllegalDataTypeContext !(LHsContext GhcPs) | Illegal datatype context |
PsErrParseErrorOnInput !OccName | Parse error on input |
PsErrMalformedDecl !SDoc !RdrName | Malformed ... declaration for ... |
PsErrUnexpectedTypeAppInDecl !(LHsType GhcPs) !SDoc !RdrName | Unexpected type application in a declaration |
PsErrNotADataCon !RdrName | Not a data constructor |
PsErrRecordSyntaxInPatSynDecl !(LPat GhcPs) | Record syntax used in pattern synonym declaration |
PsErrEmptyWhereInPatSynDecl !RdrName | Empty 'where' clause in pattern-synonym declaration |
PsErrInvalidWhereBindInPatSynDecl !RdrName !(HsDecl GhcPs) | Invalid binding name in 'where' clause of pattern-synonym declaration |
PsErrNoSingleWhereBindInPatSynDecl !RdrName !(HsDecl GhcPs) | Multiple bindings in 'where' clause of pattern-synonym declaration |
PsErrDeclSpliceNotAtTopLevel !(SpliceDecl GhcPs) | Declaration splice not a top-level |
PsErrInferredTypeVarNotAllowed | Inferred type variables not allowed here |
PsErrMultipleNamesInStandaloneKindSignature [LIdP GhcPs] | Multiple names in standalone kind signatures |
PsErrIllegalImportBundleForm | Illegal import bundle form |
PsErrIllegalRoleName !FastString [Role] | Illegal role name |
PsErrInvalidTypeSignature !(LHsExpr GhcPs) | Invalid type signature |
PsErrUnexpectedTypeInDecl !(LHsType GhcPs) !SDoc !RdrName [LHsTypeArg GhcPs] !SDoc | Unexpected type in declaration |
PsErrExpectedHyphen | Expected a hyphen |
PsErrSpaceInSCC | Found a space in a SCC |
PsErrEmptyDoubleQuotes | Found two single quotes |
| |
PsErrInvalidPackageName !FastString | Invalid package name |
PsErrInvalidRuleActivationMarker | Invalid rule activation marker |
PsErrLinearFunction | Linear function found but LinearTypes not enabled |
PsErrMultiWayIf | Multi-way if-expression found but MultiWayIf not enabled |
PsErrExplicitForall | Explicit forall found but no extension allowing it is enabled |
| |
PsErrIllegalQualifiedDo !SDoc | Found qualified-do without QualifiedDo enabled |
PsErrCmmParser !CmmParserError | Cmm parser error |
PsErrIllegalTraditionalRecordSyntax !SDoc | Illegal traditional record syntax TODO: distinguish errors without using SDoc |
PsErrParseErrorInCmd !SDoc | Parse error in command TODO: distinguish errors without using SDoc |
PsErrInPat !(PatBuilder GhcPs) !PsErrInPatDetails | Parse error in pattern |
PsErrParseRightOpSectionInPat !RdrName !(PatBuilder GhcPs) | Parse error in right operator section pattern TODO: embed the proper operator, if possible |
PsErrIllegalGadtRecordMultiplicity !(HsArrow GhcPs) | Illegal linear arrow or multiplicity annotation in GADT record syntax |
PsErrInvalidCApiImport | |
PsErrMultipleConForNewtype !RdrName !Int | |
PsErrUnicodeCharLooksLike | |
Instances
data PsErrParseDetails Source #
Extra details about a parse error, which helps us in determining which should be the hints to suggest.
PsErrParseDetails | |
|
data PatIncompleteDoBlock Source #
Instances
Eq PatIncompleteDoBlock Source # | |
Defined in GHC.Parser.Errors.Types (==) :: PatIncompleteDoBlock -> PatIncompleteDoBlock -> Bool # (/=) :: PatIncompleteDoBlock -> PatIncompleteDoBlock -> Bool # |
data ParseContext Source #
Extra information for the expression GHC is currently inspecting/parsing. It can be used to generate more informative parser diagnostics and hints.
ParseContext | |
|
Instances
Eq ParseContext Source # | |
Defined in GHC.Parser.Errors.Types (==) :: ParseContext -> ParseContext -> Bool # (/=) :: ParseContext -> ParseContext -> Bool # |
data PsErrInPatDetails Source #
PEIP_NegApp | Negative application pattern? |
PEIP_TypeArgs [HsConPatTyArg GhcPs] | The list of type arguments for the pattern |
PEIP_RecPattern | |
| |
PEIP_OtherPatDetails !ParseContext |
fromParseContext :: ParseContext -> PsErrInPatDetails Source #
Builds a PsErrInPatDetails
with the information provided by the ParseContext
.
data NumUnderscoreReason Source #
Instances
Show NumUnderscoreReason Source # | |
Defined in GHC.Parser.Errors.Types | |
Eq NumUnderscoreReason Source # | |
Defined in GHC.Parser.Errors.Types (==) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # (/=) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # | |
Ord NumUnderscoreReason Source # | |
Defined in GHC.Parser.Errors.Types compare :: NumUnderscoreReason -> NumUnderscoreReason -> Ordering # (<) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # (<=) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # (>) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # (>=) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # max :: NumUnderscoreReason -> NumUnderscoreReason -> NumUnderscoreReason # min :: NumUnderscoreReason -> NumUnderscoreReason -> NumUnderscoreReason # |
data LexErrKind Source #
LexErrKind_EOF | End of input |
LexErrKind_UTF8 | UTF-8 decoding error |
LexErrKind_Char !Char | Error at given character |
Instances
Show LexErrKind Source # | |
Defined in GHC.Parser.Errors.Types | |
Eq LexErrKind Source # | |
Defined in GHC.Parser.Errors.Types (==) :: LexErrKind -> LexErrKind -> Bool # (/=) :: LexErrKind -> LexErrKind -> Bool # | |
Ord LexErrKind Source # | |
Defined in GHC.Parser.Errors.Types compare :: LexErrKind -> LexErrKind -> Ordering # (<) :: LexErrKind -> LexErrKind -> Bool # (<=) :: LexErrKind -> LexErrKind -> Bool # (>) :: LexErrKind -> LexErrKind -> Bool # (>=) :: LexErrKind -> LexErrKind -> Bool # max :: LexErrKind -> LexErrKind -> LexErrKind # min :: LexErrKind -> LexErrKind -> LexErrKind # |
LexError | Lexical error |
LexUnknownPragma | Unknown pragma |
LexErrorInPragma | Lexical error in pragma |
LexNumEscapeRange | Numeric escape sequence out of range |
LexStringCharLit | Lexical error in string/character literal |
LexStringCharLitEOF | Unexpected end-of-file in string/character literal |
LexUnterminatedComment | Unterminated `{-' |
LexUnterminatedOptions | Unterminated OPTIONS pragma |
LexUnterminatedQQ | Unterminated quasiquotation |
data CmmParserError Source #
Errors from the Cmm parser
CmmUnknownPrimitive !FastString | Unknown Cmm primitive |
CmmUnknownMacro !FastString | Unknown macro |
CmmUnknownCConv !String | Unknown calling convention |
CmmUnrecognisedSafety !String | Unrecognised safety |
CmmUnrecognisedHint !String | Unrecognised hint |
data TransLayoutReason Source #
TransLayout_Where | "`where' clause at the same depth as implicit layout block" |
TransLayout_Pipe | "`|' at the same depth as implicit layout block") |