Re: brain explosion in polymorphic state monad

2002-10-10 Thread Hal Daume III

I'm not sure why it's doing that, but you can see (and fix!) the same
problem in a simpler case:

data Foo a = forall b . Foo a b

foo (Foo a _) f = 
let Foo _ b = f a
in  Foo a b

This causes the same error.  Presumably this has to do with the compiler
worrying about escaping variables or something.  I'm not sure.  There's a
workaround, though, which I bet will work in your case.  First we define:

refoo (Foo a _) (Foo _ b) = Foo a b

Then we redefine the foo function using this:

foo x@(Foo a _) f = refoo x (f a)

and we have a semantically identical, but now acceptable, function.

HTH

 - Hal

--
Hal Daume III

 "Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume

On Thu, 10 Oct 2002, mathieu wrote:

> Hello,
> 
> I am trying to define a polymorphic state monad using glasgow extensions and I got a 
>brain explosion of ghc when i try to compile it.
> 
> Here is the code :
> 
> newtype StateT s m a = MkStateT (s -> m (a, s))
> 
> instance Monad m => Monad (StateT s m) where
>   return x = MkStateT (\s -> return (x, s))
>   MkStateT m1 >>= k =
> MkStateT
> (\s0 -> do (a, s1) <- m1 s0
>let MkStateT m2 = k a
>m2 s1 )
> 
> data Thread a = forall b . MkThread (StateT (Thread b) [] a)
> 
> instance Monad Thread where
>   return = MkThread . return
>   MkThread p >>= k = MkThread ( do x <- p
>let MkThread p' = k x 
>p' )
> 
> I got this error :
>My brain just exploded.
> I can't handle pattern bindings for existentially-quantified constructors.
> In the binding group
> MkThread p' = k x
> In the first argument of `MkThread', namely
> `(do
> x <- p
> let MkThread p' = k x
> p')'
> In the definition of `>>=':
> MkThread (do
> x <- p
> let MkThread p' = k x
> p')
> 
> How can i define (>>=) for my thread monad ?
> 
> Thanks in advance for any piece of advice,
> Mathieu
> 
> -- 
> There are only 10 types of people in the world:
> Those who understand binary and those who don't.
> ___
> Glasgow-haskell-users mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> 

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



brain explosion in polymorphic state monad

2002-10-10 Thread mathieu

Hello,

I am trying to define a polymorphic state monad using glasgow extensions and I got a 
brain explosion of ghc when i try to compile it.

Here is the code :

newtype StateT s m a = MkStateT (s -> m (a, s))

instance Monad m => Monad (StateT s m) where
  return x = MkStateT (\s -> return (x, s))
  MkStateT m1 >>= k =
MkStateT
(\s0 -> do (a, s1) <- m1 s0
   let MkStateT m2 = k a
   m2 s1 )

data Thread a = forall b . MkThread (StateT (Thread b) [] a)

instance Monad Thread where
  return = MkThread . return
  MkThread p >>= k = MkThread ( do x <- p
   let MkThread p' = k x 
   p' )

I got this error :
   My brain just exploded.
I can't handle pattern bindings for existentially-quantified constructors.
In the binding group
MkThread p' = k x
In the first argument of `MkThread', namely
`(do
x <- p
let MkThread p' = k x
p')'
In the definition of `>>=':
MkThread (do
x <- p
let MkThread p' = k x
p')

How can i define (>>=) for my thread monad ?

Thanks in advance for any piece of advice,
Mathieu

-- 
There are only 10 types of people in the world:
Those who understand binary and those who don't.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



non-termination during compilation

2002-10-10 Thread Christian Maeder

Hi,

the following example causes ghc to loop (or run rather long):

--- snip ---

data U = MkU (U -> Bool)
 
russel :: U -> Bool
russel u@(MkU p) = not $ p u

x :: Bool
x = russel (MkU russel)

--- snip ---

I think, a compiler should always terminate, shouldn't it!?

Compilation succeeds for "russel $ MkU russel" instead of "russel (MkU
russel)".
(Surely, x is bottom and therefore the example is senseless)

Regards Christian
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: ObjectIO Library

2002-10-10 Thread Sigbjorn Finne
Hi there,

leaving it out of the 5.04.1 installer was unintended, esp. since
5.04 had it included. I'll make sure it makes a re-appearance
in 5.04.2 (or whatever the next GHC release ends up being
named.)

--sigbjorn

- Original Message -
From: Alfonso
To: [EMAIL PROTECTED]
Sent: Tuesday, October 08, 2002 09:03
Subject: ObjectIO Library


Hello:
 I have the information that The  library ObjectIO is included in  the
ghc.5.0.4 version, unfortunately I download the msi file for windows
(ghc-5-04-1.msi) and the library does not appear in the imports directory
after the installation.
Have I the wrong information?  Do I need to download another msi ? How can I
use objectIO with version 5.04.1?
thank you
Alfonso



___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ghc --make and static libraries (SOLUTION)

2002-10-10 Thread Martin Norbäck

tor 2002-10-10 klockan 14.02 skrev Martin Norbäck:
> How do I go about linking to a static library when using --make?
> 
> If i do
> 
> ghc --make Module libmodulelib.a
> 
> then ghc syas:
> 
> chasing modules from Module,libmodulelib.a and complains about not being
> able to find the _module_ modulelib.a. Likewise on windows, if I do
> 
> ghc --make Module modulelib.dll
> 
> it also complains about not finding the _module_ modulelib.dll.
> 
> If I specify the object files that makes up modulelib then there are no
> complaints, likewise, if I link without --make, ghc uses the library
> just fine.
> 
> Is this the intended behaviour, and if it is, how do I go about linking
> with libraries when using --make?

Thanks for those who replied. I found a solution:

use -optllibmodulelib.a and -optmodulelib.dll and they will be ignored
and just passed on to the linker as they should be.

Regards,

Martin




signature.asc
Description: Detta =?ISO-8859-1?Q?=E4r?= en digitalt signeradmeddelandedel


RE: ObjectIO Library

2002-10-10 Thread Simon Peyton-Jones









 I have the information that
The 
library ObjectIO is included in  the ghc.5.0.4
version, unfortunately I download the msi
file for windows 
(ghc-5-04-1.msi) and the library does not
appear in the imports directory after the installation. 
Have I the wrong information?  Do I need to
download another msi ? How can I use objectIO with version 5.04.1? 

 

The message below is the
most recent I know about for ObjectIO.  It’s not yet included as a
standard part of the GHC distribution, though I hope it will become so in due
course.

Simon

 

-Original Message-
From: Krasimir Angelov [mailto:[EMAIL PROTECTED]] 
Sent: 04 September 2002 19:01
To: haskell
Cc: [EMAIL PROTECTED]
Subject: ANN: ObjectIO update
for GHC-5.04

 

  
Hi, Haskellers

 

 
An update is available for ObjectIO for GHC-5.04.

Just
extract the package over the GHC directory to

update
the library. 

 

More
information:

http://haskell.cs.yale.edu/ObjectIO

 

This
is the package:

http://haskell.cs.yale.edu/ObjectIO/ObjectIO_update.zip

 

Krasimir

 

 








ghc --make and static libraries

2002-10-10 Thread Martin Norbäck

How do I go about linking to a static library when using --make?

If i do

ghc --make Module libmodulelib.a

then ghc syas:

chasing modules from Module,libmodulelib.a and complains about not being
able to find the _module_ modulelib.a. Likewise on windows, if I do

ghc --make Module modulelib.dll

it also complains about not finding the _module_ modulelib.dll.

If I specify the object files that makes up modulelib then there are no
complaints, likewise, if I link without --make, ghc uses the library
just fine.

Is this the intended behaviour, and if it is, how do I go about linking
with libraries when using --make?

Regards,

Martin



signature.asc
Description: Detta =?ISO-8859-1?Q?=E4r?= en digitalt signeradmeddelandedel


Re: Building Both "Regular" and "Profiling" Libraries

2002-10-10 Thread Ashley Yakeley

At 2002-10-10 01:23, Ketil Z. Malde wrote:

>Ashley Yakeley <[EMAIL PROTECTED]> writes:
>
>> I did notice that for -osuf you seem to need the '.' but for -hisuf you 
>> don't...
>
>Weird, I've never seen that behavior (GHC 5.02 and 5.04, x86-Linux and
>Sparc-Solaris).  I just checked with 5.04 on my Linux box, and 5.02 on
>a Sun, just to make sure.
>
>What system and compiler version are you using?

My mistake, I'm using -o, which overrides -osuf...

-- 
Ashley Yakeley, Seattle WA

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Building Both "Regular" and "Profiling" Libraries

2002-10-10 Thread Ketil Z. Malde

Ashley Yakeley <[EMAIL PROTECTED]> writes:

> I did notice that for -osuf you seem to need the '.' but for -hisuf you 
> don't...

Weird, I've never seen that behavior (GHC 5.02 and 5.04, x86-Linux and
Sparc-Solaris).  I just checked with 5.04 on my Linux box, and 5.02 on
a Sun, just to make sure.

What system and compiler version are you using?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users