[Haskell-cafe] Re: Mystery Parse Error in LHS file

Iæfai jptdrake at gmail.com
Thu May 6 11:42:46 EDT 2010


I can certainly see the parse error there, yes. Might file a bug then,
it should work, despite John's logic that there is no reason to.

On May 6, 11:35 am, Daniel Fischer <daniel.is.fisc... at web.de> wrote:
> On Thursday 06 May 2010 17:02:59, Iæfai wrote:
>
> > I have an lhs file, 'starsystem.lhs' that is not compiling because of
> > a parse error.
>
> > I cannot figure out what the problem here is.
>
> Apparently, unlit doesn't manage to cope with mixed LaTeX and bird-track.http://haskell.org/onlinereport/syntax-iso.html#sect9.4says:
> "It is not advisable to mix these two styles in the same file."
>
> The output of unlit looks like:
> ----------------------------------------------------------------------
> #line 1 "parseErr.lhs"
>   {-# LANGUAGE ForeignFunctionInterface #-}
>
>   import Graphics.Rendering.OpenGL as GL
>   import Graphics.UI.GLFW as GLFW
>
>   foreign import ccall unsafe "unbundled" c_unbundled :: IO ()
>
>   data Action = Action (IO Action)
>
> main :: IO ()
> main = do
>   c_unbundled
>   GLFW.initialize
>   -- open window
> ----------------------------------------------------------------------
>
> (snipped most). You can see the parse error there, can't you?
>
> Maybe file a GHC bug/feature request?
>
> > I have tried it in a
> > regular hs file and it works. I have posted full source here:
> >http://hpaste.org/fastcgi/hpaste.fcgi/view?id=25352#a25352
>
> > Any thoughts would be welcome.
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
>
> --
> You received this message because you are subscribed to the Google Groups "Haskell-cafe" group.
> To post to this group, send email to haskell-cafe at googlegroups.com.
> To unsubscribe from this group, send email to haskell-cafe+unsubscribe at googlegroups.com.
> For more options, visit this group athttp://groups.google.com/group/haskell-cafe?hl=en.


More information about the Haskell-Cafe mailing list