-
Notifications
You must be signed in to change notification settings - Fork 146
Closed
Labels
Description
The following code compiles with frege3.23.888-g4e22ab6
(and ghc with XRankNTypes and small syntax changes), but doesn’t compile with 3.24.61
.
module ParsecCompileBug2 where
makeTokenParser :: LanguageDef st -> TokenParser st
makeTokenParser languageDef
= TokenParser{ lexeme = lexeme
, whiteSpace = whiteSpace
, natural = natural
, integer = integer }
where
lexeme :: forall a st. CharParser st a -> CharParser st a
lexeme p = do { x <- p; whiteSpace; return x }
whiteSpace :: forall st. CharParser st ()
whiteSpace
| noLine && noMulti = undefined
| noLine = undefined
where
noLine = null []
noMulti = null (languageDef.commentStart)
integer = lexeme int
natural = lexeme nat
int = undefined
nat = undefined
-- Necessary Definitions
data LanguageDef st = LanguageDef { commentStart :: String }
data TokenParser st = TokenParser { whiteSpace :: CharParser st ()
, lexeme :: forall a. CharParser st a -> CharParser st a
, integer :: CharParser st Integer
, natural :: CharParser st Integer }
type CharParser st a = GenParser Char st a
type Parser a = GenParser Char () a
data GenParser tok st a = Parser (State tok st -> Consumed (Reply tok st a))
data Consumed a = Consumed a
data State tok st = State
data Reply tok st a = Ok a (State tok st) String
instance Monad (GenParser tok st) where
pure x = undefined
p >>= f = undefined
W ParsecCompileBug2.fr:17: guard (noLine) may evaluate to false.
calling: javac -cp /home/mabre/Downloads/frege/frege3.24.61.jar:/tmp/ -d /tmp/ -sourcepath . -encoding UTF-8 /tmp//ParsecCompileBug2.java
/tmp/ParsecCompileBug2.java:1059: error: incompatible types: TLanguageDef<st#1> cannot be converted to TLanguageDef<st#2>
if (noLine$7628 && PreludeList.IListView_StringJ.<Character>$null(TLanguageDef.<st>commentStart(arg$1.call()))) {
^
where st#1,st#2 are type-variables:
st#1 extends Object declared in method <st#1>makeTokenParser(Lazy<TLanguageDef<st#1>>)
st#2 extends Object declared in method <st#2>whiteSpace$7621()
/tmp/ParsecCompileBug2.java:1093: error: cannot find symbol
let$8183.lexeme$7620
^
symbol: variable lexeme$7620
location: variable let$8183 of type Let$8183
Note: Some messages have been simplified; recompile with -Xdiags:verbose to get full output
2 errors
E ParsecCompileBug2.fr:44: java compiler errors are
most likely caused by erroneous native definitions
When removing the type annotations for lexeme
and whiteSpace
(which still compiles with ghc and matched the original parsec code), I get type errors instead:
E ParsecCompileBug2.fr:22: type `Integer` is not as
polymorphic as suggested in the annotation where just
`a` is announced.
E ParsecCompileBug2.fr:22: type error in expression lexeme undefined
type is : CharParser t1 a
expected: CharParser t1 Integer
E ParsecCompileBug2.fr:23: type `Integer` is not as
polymorphic as suggested in the annotation where just
`a` is announced.
E ParsecCompileBug2.fr:23: type error in expression lexeme undefined
type is : CharParser t1 a
expected: CharParser t1 Integer
When adding type annotations for integer
and natural
(CharParser st Integer
), the errors are these:
E ParsecCompileBug2.fr:23: type `st` is not as polymorphic as
suggested in the annotation where just `st` is
announced.
E ParsecCompileBug2.fr:23: type error in expression lexeme int
type is : CharParser st Integer
expected: CharParser st Integer
E ParsecCompileBug2.fr:5: type `Integer` is not as
polymorphic as suggested in the annotation where just
`a` is announced.
E ParsecCompileBug2.fr:5: type error in expression lexeme
type is : CharParser st a
expected: CharParser st Integer
E ParsecCompileBug2.fr:5: type `Integer` is not as
polymorphic as suggested in the annotation where just
`a` is announced.
E ParsecCompileBug2.fr:5: type error in expression lexeme
type is : CharParser st Integer
expected: CharParser st a
E ParsecCompileBug2.fr:5: type `st` is not as polymorphic as
suggested in the annotation where just `st` is
announced.
E ParsecCompileBug2.fr:5: type error in expression TokenParser whiteSpace lexeme integer natural
type is : TokenParser st
expected: TokenParser st
E ParsecCompileBug2.fr:5: type `st` is not as polymorphic as
suggested in the annotation where just `st` is
announced.
E ParsecCompileBug2.fr:5: type error in expression let integer=lexeme int in ...
type is : TokenParser st
expected: TokenParser st
E ParsecCompileBug2.fr:5: type `st` is not as polymorphic as
suggested in the annotation where just `st` is
announced.
E ParsecCompileBug2.fr:5: type error in expression let natural=lexeme nat in ...
type is : TokenParser st
expected: TokenParser st
E ParsecCompileBug2.fr:5: type `st` is not as polymorphic as
suggested in the annotation where just `st` is
announced.
E ParsecCompileBug2.fr:5: type error in expression let lexeme=λp -> >>= p (λx -> >> whiteSpace (return x)) in ...
type is : TokenParser st
expected: TokenParser st
E ParsecCompileBug2.fr:5: type `st` is not as polymorphic as
suggested in the annotation where just `st` is
announced.
E ParsecCompileBug2.fr:5: type error in expression let whiteSpace=let noLine=null [] in ... in ...
type is : TokenParser st
expected: TokenParser st
E ParsecCompileBug2.fr:5: type `st` is not as polymorphic as
suggested in the annotation where just `st` is
announced.
E ParsecCompileBug2.fr:5: type error in expression let int=undefined in ...
type is : TokenParser st
expected: TokenParser st
E ParsecCompileBug2.fr:5: type `st` is not as polymorphic as
suggested in the annotation where just `st` is
announced.
E ParsecCompileBug2.fr:5: type error in expression let nat=undefined in ...
type is : TokenParser st
expected: TokenParser st
E ParsecCompileBug2.fr:4: type `st` is not as polymorphic as
suggested in the annotation where just `st` is
announced.
E ParsecCompileBug2.fr:4: type error in expression λlanguageDef -> let nat=undefined in ...
type is : TokenParser st
expected: TokenParser st
(The messages where type is
= expected
are not very helpful.)
Ingo60