[jhc] progress in compiling hopengl via jhc
John Meacham
john at repetae.net
Mon Mar 30 20:21:19 EDT 2009
Hmm.. I'll have to look at that one more carefully. but to translate the
error message, it is saying
type '()' does not match type 'a -> IO b' on line 100 of BeginEnd.hs_pre
cleaning up those error messages would be a useful thing, I have a bug
listed for it.
John
On Tue, Mar 31, 2009 at 01:50:04AM +0200, Csaba Hruska wrote:
> Thanks!
> I've added this code as a new module.
>
> It fixed that error.
> Anyway here the error message:
>
> *[ 96 of 166] Graphics.Rendering.OpenGL.GL.BeginEnd
> Determining Exports/Imports: [Graphics.Rendering.OpenGL.GL.BeginEnd]
> Typing: ["Graphics.Rendering.OpenGL.GL.BeginEnd"]
> Kind inference
> Type inference
> .....user error (
> What: failure
> Why: boxyMatch failure: (Jhc.Prim.IO Jhc.Basics.()) (s17 -> Jhc.Prim.IOs18)
> Where: on line 100 in BeginEnd.hs_pre
> in the application
> Graphics.Rendering.OpenGL.GL.BeginEnd.renderPrim
> Control.Exception.bracket_
> in the declaration
> Graphics.Rendering.OpenGL.GL.BeginEnd.renderPrimitive
> = Graphics.Rendering.OpenGL.GL.BeginEnd.renderPrim
> Control.Exception.bracket_ {- on line 100 -}
> in the explicitly typed
> Graphics.Rendering.OpenGL.GL.BeginEnd.renderPrimitive
> = Graphics.Rendering.OpenGL.GL.BeginEnd.renderPrim
> Control.Exception.bracket_ {- on line 100 -})
> *
>
> 2009/3/31 John Meacham <john at repetae.net>
>
> > Hi, thanks for the bug report, I don't have time to work on it at the
> > moment, but a quick fix would be to create a module like the following
> > and include it in your program. I'll add a cleaner fix to the repo at
> > some point.
> >
> > > module FunPtrInstance where
> > >
> > > import Jhc.Addr
> > >
> > > instance Eq (FunPtr a) where
> > > FunPtr a == FunPtr b = a == b
> > > FunPtr a /= FunPtr b = a /= b
> > >
> > > instance Ord (FunPtr a) where
> > > compare (FunPtr a) (FunPtr b) = compare a b
> > > FunPtr a <= FunPtr b = a <= b
> > > FunPtr a < FunPtr b = a < b
> > > FunPtr a > FunPtr b = a > b
> > > FunPtr a >= FunPtr b = a >= b
> >
> >
> > John
> >
> >
> > --
> > John Meacham - ⑆repetae.net⑆john⑈
> > _______________________________________________
> > jhc mailing list
> > jhc at haskell.org
> > http://www.haskell.org/mailman/listinfo/jhc
> >
> --
> jhc mailing list
> jhc at haskell.org
> http://www.haskell.org/mailman/listinfo/jhc
--
John Meacham - ⑆repetae.net⑆john⑈
More information about the jhc
mailing list