Parse error on input [GHC-58481]
This is a generic error, indicating that GHC could not parse the code.
GHC contains many more explicit parsing errors with more verbose descriptions of the problem.
However if the error is not separately defined there, a problem with parsing is reported with error code GHC-58481
.
There may be many different reasons why the error GHC-58481
was emitted, ranging from incorrect syntax that requires additional language extensions, to an expression mistakenly put in the same line as another.
Below are some examples of code that generate this generic parsing error. Please be encouraged to report more or contribute via error-messages github.
Examples
Parse error expression
Error in expression - module
keyword should not be used in the same line as an expression declaration.
Error Message
error: [GHC-58481]
parse error on input ‘module’
|
5 | foo = 123456 module
| ^^^^^^
Example.hs
module Example where
foo = 123456 module
module Example where
foo = 123456
Parse error in OPAQUE pragma
OPAQUE pragma is incorectly parsed.
Error Message
error: [GHC-58481]
parse error on input ‘[’
|
4 | {-# OPAQUE[1] f #-}
| ^
OpaqueParseFail1.hs
module OpaqueParseFail1 where
f = id
{-# OPAQUE[1] f #-}
module OpaqueParseFail1 where
f = id
{-# OPAQUE f #-}
Incorrect syntax of ($) operator usage
When TemplateHaskell is not enabled, then $
denotes function application, but must be followed with a space character: "$ "
.
When TemplateHaskell is enabled, $
denotes a splice operator. Used in this context, there must be no space between the “$” and the expression.
Error Message
warning: [-Woperator-whitespace-ext-conflict] [GHC-47082]
The prefix use of a ‘$’ would denote an untyped splice
were the TemplateHaskell extension enabled.
Suggested fix: Add whitespace after the ‘$’.
|
3 | f = $(x)
| ^
error: [GHC-58481]
parse error on input ‘$’
Suggested fix: Perhaps you intended to use TemplateHaskell
|
3 | f = $(x)
| ^
Data.hs
{-# LANGUAGE TemplateHaskell #-}
module Data where
import Language.Haskell.TH
x :: Int
x = 42
static :: Q Exp
static = [| x |]
NoHeader.hs
module NoHeader where
f = $(static)
{-# LANGUAGE TemplateHaskell #-}
module NoHeader where
import Data (static)
f = $(static)
Use of pattern synonyms without enabled language extension
In this example the user declared a pattern synonym without enabling the PatternSynonym
extension, which leads to this generic parsing error.
messages/GHC-58481/example4/before/Pattern.hs:3:16: error: [GHC-58481]
parse error on input ‘<-’
Suggested fix: Possibly caused by a missing 'do'?
|
3 | pattern Head x <- x:xs
| ^^
Pattern.hs
module Pattern where
pattern Head x <- x:xs
{-# LANGUAGE PatternSynonyms #-}
module Pattern where
pattern Head x <- x:xs