Foreign.StablePtr: nullPtr double-free questions

2013-03-08 Thread Remi Turk
Good night everyone,

I have two questions with regards to some details of the
Foreign.StablePtr module. [1]

1) The documentation suggests, but does not explicitly state, that
  castStablePtrToPtr `liftM` newStablePtr x
will never yield a nullPtr. Is this guaranteed to be the case or not?
It would conveniently allow me to store a Maybe for free, using
nullPtr for Nothing, but I am hesitant about relying on something that
isn't actually guaranteed by the documentation.

2) If I read the documentation correctly, when using StablePtr it is
actually quite difficult to avoid undefined behaviour, at least in
GHC(i). In particular, a double-free on a StablePtr yields undefined
behaviour. However, when called twice on the same value, newStablePtr
yields the same StablePtr in GHC(i).
E.g.:

module Main where

import Foreign

foo x y = do
p1 - newStablePtr x
p2 - newStablePtr y
print $ castStablePtrToPtr p1 == castStablePtrToPtr p2
freeStablePtr p1
freeStablePtr p2 -- potential double free!

main = let x = Hello, world! in foo x x -- undefined behaviour!

prints True under GHC(i), False from Hugs. Considering that foo
and main might be in different packages written by different authors,
this makes correct use rather complicated. Is this behaviour (and the
consequential undefinedness) intentional?

With kind regards,

Remi Turk

[1] 
http://www.haskell.org/ghc/docs/latest/html/libraries/base-4.6.0.1/Foreign-StablePtr.html

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] ANNOUNCE: cinvoke 0.1 released

2011-03-10 Thread Remi Turk
On Wed, Mar 09, 2011 at 05:50:12PM +0100, Gábor Lehel wrote:
 On Wed, Mar 9, 2011 at 5:26 PM, Remi Turk rt...@science.uva.nl wrote:
  Count on it having at least an order of magnitude more overhead.
  I did some simple test of calling the following three trivial
  functions (with constant arguments, and ignoring the return
  values, 2M times) and got the following timings:
 
   int blub0() { return 42; }
   int blub1(int a) { return 42; }
   int blub5(int a, int b, int c, int d, int e) { return 42; }
 
         Unsafe FFI   Safe FFI   Safe dynamic FFI   CInvoke
  blub0   0.03         0.19       0.20               1.62
  blub1   0.03         0.20       0.20               2.44
  blub5   0.04         0.20       0.20               4.35
 
  It's not that bad for functions that actually (try to) do
  something though. For example, trying to remove a non-existent
  file:
 
  unlink  3.06         3.04       3.27               7.15
 
  If I remember correctly, libffi was slightly faster, but mostly
  thanks to the fact that I didn't make it exception safe yet.
 
  So if you care about performance and are able to directly use the
  FFI, you clearly should.
 
 That describes my situation. Thanks!
 
 For the record, what units were your measurements in?
 
 (I notice that the overhead of safe FFI calls seems to be pretty
 smallish, which is also quite heartening.)

Everything is in seconds. So for example, 2 million unsafe calls
to blub0 take 0.03 seconds: ~15ns or ~42 cycles per call
(including replicateM_ overhead).

I just noticed in my little non-scientific benchmark that the
overhead for safe calls is significantly higher when compiling
with -threaded:

       Unsafe FFI   Safe FFI   Safe dynamic FFI   CInvoke
blub0   0.04 0.36   0.35   2.27
blub1   0.05 0.36   0.36   3.52
blub5   0.05 0.37   0.37   5.72

unlink  3.26 3.21   3.56   8.41

Groeten, Remi

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] [Haskell-cafe] ANNOUNCE: cinvoke 0.1 released

2011-03-09 Thread Remi Turk
On Tue, Mar 08, 2011 at 01:01:58PM +0100, Gábor Lehel wrote:
 On Sun, Mar 6, 2011 at 2:38 PM, Remi Turk rt...@science.uva.nl wrote:
  Where?
  Hackage: http://hackage.haskell.org/package/cinvoke
 
  Cheers, Remi
 
  [1] http://www.nongnu.org/cinvoke/
 
 Is there any information on how this (and libffi I guess) compare to
 GHC's FFI in terms of performance? Is it equivalent? Once you've
 loaded a function with loadSymbol and are cinvoking it with various
 arguments, versus a plain foreign import of the same.

Count on it having at least an order of magnitude more overhead.
I did some simple test of calling the following three trivial
functions (with constant arguments, and ignoring the return
values, 2M times) and got the following timings:

  int blub0() { return 42; }
  int blub1(int a) { return 42; }
  int blub5(int a, int b, int c, int d, int e) { return 42; }

Unsafe FFI   Safe FFI   Safe dynamic FFI   CInvoke
blub0   0.03 0.19   0.20   1.62
blub1   0.03 0.20   0.20   2.44
blub5   0.04 0.20   0.20   4.35

It's not that bad for functions that actually (try to) do
something though. For example, trying to remove a non-existent
file:

unlink  3.06 3.04   3.27   7.15

If I remember correctly, libffi was slightly faster, but mostly
thanks to the fact that I didn't make it exception safe yet.

So if you care about performance and are able to directly use the
FFI, you clearly should.

 (Also, I assume cinvoke corresponds to the FFI's 'unsafe'
 calls, i.e. if the function tries to call back into the GHC
 runtime then Bad Things will happen, and it'll block threads on
 the same 'Capability' if it runs too long?)

Actually, it doesn't: Considering the rather large overhead of
CInvoke itself, I just import everything 'safe'.
Though to be honest I didn't actually test any callbacks into Haskell.

Cheers, Remi

___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell-cafe] ANNOUNCE: cinvoke 0.1 released

2011-03-09 Thread Remi Turk
On Tue, Mar 08, 2011 at 01:01:58PM +0100, Gábor Lehel wrote:
 On Sun, Mar 6, 2011 at 2:38 PM, Remi Turk rt...@science.uva.nl wrote:
  Where?
  Hackage: http://hackage.haskell.org/package/cinvoke
 
  Cheers, Remi
 
  [1] http://www.nongnu.org/cinvoke/
 
 Is there any information on how this (and libffi I guess) compare to
 GHC's FFI in terms of performance? Is it equivalent? Once you've
 loaded a function with loadSymbol and are cinvoking it with various
 arguments, versus a plain foreign import of the same.

Count on it having at least an order of magnitude more overhead.
I did some simple test of calling the following three trivial
functions (with constant arguments, and ignoring the return
values, 2M times) and got the following timings:

  int blub0() { return 42; }
  int blub1(int a) { return 42; }
  int blub5(int a, int b, int c, int d, int e) { return 42; }

Unsafe FFI   Safe FFI   Safe dynamic FFI   CInvoke
blub0   0.03 0.19   0.20   1.62
blub1   0.03 0.20   0.20   2.44
blub5   0.04 0.20   0.20   4.35

It's not that bad for functions that actually (try to) do
something though. For example, trying to remove a non-existent
file:

unlink  3.06 3.04   3.27   7.15

If I remember correctly, libffi was slightly faster, but mostly
thanks to the fact that I didn't make it exception safe yet.

So if you care about performance and are able to directly use the
FFI, you clearly should.

 (Also, I assume cinvoke corresponds to the FFI's 'unsafe'
 calls, i.e. if the function tries to call back into the GHC
 runtime then Bad Things will happen, and it'll block threads on
 the same 'Capability' if it runs too long?)

Actually, it doesn't: Considering the rather large overhead of
CInvoke itself, I just import everything 'safe'.
Though to be honest I didn't actually test any callbacks into Haskell.

Cheers, Remi

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: cinvoke 0.1 released

2011-03-08 Thread Remi Turk
On Tue, Mar 08, 2011 at 01:15:26AM +, Felipe Almeida Lessa wrote:
 On Mon, Mar 7, 2011 at 6:32 PM, Remi Turk rt...@science.uva.nl wrote:
  - If you need to pass C structs (by value), you'll have to use
   libffi: cinvoke doesn't support them at all.
 
 What about CInvStructure[1]?  I was just glancing at the documentation
 when I saw this.

That's a part of cinvoke I have not implemented (and probably
won't, just like callbacks and a few other things, at least until
there is some demand for them).
However, the CInvStructure functions are used to construct
descriptions and instances of C structures at run-time. (think
alignment issues...)
Passing structures to functions using cinvoke can only be done
using pointers though.[1]

Cheers, Remi

[1] 
http://www.nongnu.org/cinvoke/doc/cinvoke_8h.html#4d288cacc9bde484cad7d8ed1b76c1a5

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: cinvoke 0.1 released

2011-03-07 Thread Remi Turk
On Mon, Mar 07, 2011 at 09:41:27AM +, Max Bolingbroke wrote:
 Hi Remi,
 
 On 6 March 2011 13:38, Remi Turk rt...@science.uva.nl wrote:
  I am happy to finally announce cinvoke 0.1, a binding to the
  C library cinvoke[1], allowing functions to be loaded and called
  whose names and types are not known before run-time.
 
 As the author of the libffi package
 (http://hackage.haskell.org/package/libffi-0.1) which does a similar
 thing, could you say when it would be appropriate to use one or the
 other package?
 
 Cheers,
 Max

Of course:

- libffi doesn't do library/function loading; you'll need to use
  System.Posix.DynamicLinker or System.Win32.DLL for that.
  cinvoke will not only load your libraries and functions,
  but even collect the garbage afterwards.
- Things seem to have changed, but back when I first looked at
  cinvoke, getting libffi to run under windows didn't seem too
  realistic.
- If you need to pass C structs (by value), you'll have to use
  libffi: cinvoke doesn't support them at all.
- The current version of libffi is not exception safe (I do have
  some code lying around here though...)
- cinvoke is actually haddockized (although hackage still hasn't
  generated the docs, apparently).

Groeten, Remi

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: cinvoke 0.1 released

2011-03-07 Thread Remi Turk
On Mon, Mar 07, 2011 at 10:00:47PM +0100, Daniel Fischer wrote:
 On Monday 07 March 2011 21:42:16, Gábor Lehel wrote:
  
  It's reporting a build failure.
 
 
 Missing C library.

cinvoke (the C library) is obviously not installed on the testing machine.
Does that really mean no library with uncommon C dependencies
gets documentation on hackage?

Remi

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: cinvoke 0.1 released

2011-03-07 Thread Remi Turk
On Mon, Mar 07, 2011 at 10:31:25PM +0100, Daniel Fischer wrote:
 On Monday 07 March 2011 22:14:38, Remi Turk wrote:
  cinvoke (the C library) is obviously not installed on the testing
  machine. Does that really mean no library with uncommon C dependencies
  gets documentation on hackage?
  
  Remi
 
 Basically, yes. As far as I know, documentation is only built for libraries 
 that build on hackage.
 
 Maybe it would be a good idea to have the opportunity to upload haddock 
 bundles to hackage too for such libraries.

That sucks :(
Uploading haddock bundles could solve the problem, though I don't
currently understand why being able to successfully configure a
package is a prerequisite to generating the docs.

Anyway, I just put the docs online somewhere else with a link
from the homepage: http://haskell.org/haskellwiki/Library/cinvoke

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell] ANNOUNCE: cinvoke 0.1 released

2011-03-06 Thread Remi Turk
I am happy to finally announce cinvoke 0.1, a binding to the
C library cinvoke[1], allowing functions to be loaded and called
whose names and types are not known before run-time.

Why?

Sometimes you can't use the Haskell foreign function interface
because you parse the type of the function from somewhere else,
i.e. you're writing an interpreter for a language that has an FFI
itself.

What?

The main function it exports is:

  cinvoke :: Symbol - RetType b - [Arg] - IO b

And because code is worth a thousand words, here's a small program
that uses libc to write a 1Gb buffer of random garbage to a file:

 module Main where
  
 import Foreign.CInvoke
 
 main = do
 cxt - newContext
 libc - loadLibrary cxt libc.so.6
 malloc - loadSymbol libc malloc
 creat  - loadSymbol libc creat
 write  - loadSymbol libc write
 free   - loadSymbol libc free
 let sz = 2^30
 buf - cinvoke malloc (retPtr retVoid)
 [argCSize sz]
 fd  - cinvoke creat  retCInt   [argString /tmp/test, argCUInt 0o644]
 n   - cinvoke write  retCSize  [argCInt fd, argPtr buf, argCSize sz]
 cinvoke free (retPtr retVoid) [argPtr buf]

It hopefully works on any machine on which cinvoke works,
but has only been tested on linux x86_64.
As the current version of cinvoke only installs a static library,
it does not work from GHCi at the moment (without hacking cinvoke
to build a shared library).
More interesting examples are included in examples/ in the
package.

Where?
Hackage: http://hackage.haskell.org/package/cinvoke

Cheers, Remi

[1] http://www.nongnu.org/cinvoke/

___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell-cafe] ANNOUNCE: cinvoke 0.1 released

2011-03-06 Thread Remi Turk
I am happy to finally announce cinvoke 0.1, a binding to the
C library cinvoke[1], allowing functions to be loaded and called
whose names and types are not known before run-time.

Why?

Sometimes you can't use the Haskell foreign function interface
because you parse the type of the function from somewhere else,
i.e. you're writing an interpreter for a language that has an FFI
itself.

What?

The main function it exports is:

  cinvoke :: Symbol - RetType b - [Arg] - IO b

And because code is worth a thousand words, here's a small program
that uses libc to write a 1Gb buffer of random garbage to a file:

 module Main where
  
 import Foreign.CInvoke
 
 main = do
 cxt - newContext
 libc - loadLibrary cxt libc.so.6
 malloc - loadSymbol libc malloc
 creat  - loadSymbol libc creat
 write  - loadSymbol libc write
 free   - loadSymbol libc free
 let sz = 2^30
 buf - cinvoke malloc (retPtr retVoid)
 [argCSize sz]
 fd  - cinvoke creat  retCInt   [argString /tmp/test, argCUInt 0o644]
 n   - cinvoke write  retCSize  [argCInt fd, argPtr buf, argCSize sz]
 cinvoke free (retPtr retVoid) [argPtr buf]

It hopefully works on any machine on which cinvoke works,
but has only been tested on linux x86_64.
As the current version of cinvoke only installs a static library,
it does not work from GHCi at the moment (without hacking cinvoke
to build a shared library).
More interesting examples are included in examples/ in the
package.

Where?
Hackage: http://hackage.haskell.org/package/cinvoke

Cheers, Remi

[1] http://www.nongnu.org/cinvoke/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell] ANNOUNCE: libffi 0.1 released

2009-03-17 Thread Remi Turk
I am happy to announce libffi 0.1, binding to the C library
libffi, allowing C functions to be called whose types are not
known before run-time.

Why?

Sometimes you can't use the haskell foreign function interface
because you parse the type of the function from somewhere else,
i.e. you're writing an interpreter for a language that has an FFI
itself.

What?

The main function it exports is:

  callFFI :: FunPtr a - RetType b - [Arg] - IO b

And because code is worth a thousand words, here a small program
that uses C to write a 1Gb buffer of random garbage to a file:

 import System.Posix.DynamicLinker
 import Foreign.LibFFI
 
 main = do
 malloc - dlsym Default malloc
 creat  - dlsym Default creat
 write  - dlsym Default write
 let sz = 2 ^ 30
 buf - callFFI malloc (retPtr retVoid) [argCSize sz]
 fd  - callFFI creat  retCInt  [argString /tmp/test, argCUInt 
 0o644]
 n   - callFFI write  retCSize [argCInt fd, argPtr buf, argCSize 
 sz]
 putStrLn $ show n ++  bytes written

It should work on any 32/64bits machine on which libffi works,
but has been primarily tested on linux x86_64.
The current libffi is not exception-safe (exception = memory leak)
and callFFI has quite some overhead that would be unnecessary
with another api. 
It is, however, very easy to use :)

More interesting examples are included in examples/ in the
package.

Where?
Hackage: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/libffi
Module docs: http://www.science.uva.nl/~rturk/doc/libffi-0.1

Cheers, Remi
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell-cafe] ANNOUNCE: libffi 0.1 released

2009-03-17 Thread Remi Turk
I am happy to announce libffi 0.1, binding to the C library
libffi, allowing C functions to be called whose types are not
known before run-time.

Why?

Sometimes you can't use the haskell foreign function interface
because you parse the type of the function from somewhere else,
i.e. you're writing an interpreter for a language that has an FFI
itself.

What?

The main function it exports is:

  callFFI :: FunPtr a - RetType b - [Arg] - IO b

And because code is worth a thousand words, here a small program
that uses C to write a 1Gb buffer of random garbage to a file:

 import System.Posix.DynamicLinker
 import Foreign.LibFFI
 
 main = do
 malloc - dlsym Default malloc
 creat  - dlsym Default creat
 write  - dlsym Default write
 let sz = 2 ^ 30
 buf - callFFI malloc (retPtr retVoid) [argCSize sz]
 fd  - callFFI creat  retCInt  [argString /tmp/test, argCUInt 
 0o644]
 n   - callFFI write  retCSize [argCInt fd, argPtr buf, argCSize 
 sz]
 putStrLn $ show n ++  bytes written

It should work on any 32/64bits machine on which libffi works,
but has been primarily tested on linux x86_64.
The current libffi is not exception-safe (exception = memory leak)
and callFFI has quite some overhead that would be unnecessary
with another api. 
It is, however, very easy to use :)

More interesting examples are included in examples/ in the
package.

Where?
Hackage: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/libffi
Module docs: http://www.science.uva.nl/~rturk/doc/libffi-0.1

Cheers, Remi
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: :info features

2009-02-14 Thread Remi Turk
On Thu, Feb 12, 2009 at 08:47:36AM +, Simon Marlow wrote:
 Remi Turk wrote:
 On Tue, Feb 10, 2009 at 01:31:24PM +, Simon Marlow wrote:
 My vote would be:

 :info class Show
 :info type Show
 :info instance Show

 where

 :info Show

 displays information about everything called Show

 I know that classes and types share the same namespace currently, but 
 it  might not always be so.

 Sounds good in principle, and has the advantage of being 100%
 backward compatible, but :i class Show for the common case
 (ahum, _my_ common case at least ;) still seems rather verbose,
 so how to abbreviate that?

 How about a macro?

 :def ic return . (:info class  ++)

Ah of course, I keep forgetting about :def :)

Note that when classes and types would stop sharing their namespace,
:info instance Show would again be ambiguous though..

Groeten, Remi
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: :info features

2009-02-11 Thread Remi Turk
On Tue, Feb 10, 2009 at 01:31:24PM +, Simon Marlow wrote:
 Remi Turk wrote:
 On Sat, Feb 07, 2009 at 12:39:03AM -0500, Brandon S. Allbery KF8NH wrote:
 On 2009 Feb 5, at 5:49, Remi Turk wrote:
 SPJ agreed with the idea itself, but suggested an alternative set 
 of  commands:

   :info Show-- See class definition only
   :instances Show   -- See instances of Show
 (...)
 However, it would make :i ambiguous, which is rather sad.
 :class Show -- unique prefix :cl, already many such collisions
 :instance Show

 That could work, but then how to get information about types as
 opposed to classes? Its not in the above example, but Show
 actually stands for an arbitrary typeclass _or type_.

 However, as igloo pointed out on the ticket, abbreviations don't
 actually have to be unique:

  For example, :b means :break even though we also have :back, :browse and 
 :browse!.  [1]

 That would personally lead me to prefer the :info/:instances
 combo, with :i as an abbreviation of :info.

 My vote would be:

 :info class Show
 :info type Show
 :info instance Show

 where

 :info Show

 displays information about everything called Show

 I know that classes and types share the same namespace currently, but it  
 might not always be so.

Sounds good in principle, and has the advantage of being 100%
backward compatible, but :i class Show for the common case
(ahum, _my_ common case at least ;) still seems rather verbose,
so how to abbreviate that?

Remi
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: :info features

2009-02-09 Thread Remi Turk
On Sat, Feb 07, 2009 at 12:39:03AM -0500, Brandon S. Allbery KF8NH wrote:
 On 2009 Feb 5, at 5:49, Remi Turk wrote:
 SPJ agreed with the idea itself, but suggested an alternative set of  
 commands:

   :info Show-- See class definition only
   :instances Show   -- See instances of Show
 (...)
 However, it would make :i ambiguous, which is rather sad.

 :class Show -- unique prefix :cl, already many such collisions
 :instance Show

That could work, but then how to get information about types as
opposed to classes? Its not in the above example, but Show
actually stands for an arbitrary typeclass _or type_.

However, as igloo pointed out on the ticket, abbreviations don't
actually have to be unique:

 For example, :b means :break even though we also have :back, :browse and 
:browse!.  [1]

That would personally lead me to prefer the :info/:instances
combo, with :i as an abbreviation of :info.

Groeten, Remi

[1] http://hackage.haskell.org/trac/ghc/ticket/2986#comment:4
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: :info features

2009-02-06 Thread Remi Turk
On Thu, Feb 05, 2009 at 12:35:43PM +0100, Peter Hercek wrote:
 Remi Turk wrote:
 SPJ agreed with the idea itself, but suggested an alternative set of 
 commands:

:info Show-- See class definition only
:instances Show   -- See instances of Show

 Hi Remi,

 If you do not want to wait till this is implemented you can do it  
 yourself using ghci scripting.

Thank you Peter, but in this case it won't be of much help:
I am already running a patched GHCi:
http://hackage.haskell.org/trac/ghc/attachment/ticket/2986/ghci-info-no-instances.patch
But I may use it for something else later, so thanks anyway!

Cheers, Remi
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


:info features

2009-02-05 Thread Remi Turk
One of my most used GHCi commands is :info, but quite often
the type or class definitions that I'm interested in get drowned
in lots of instances.

So a week ago I wrote a feature request and a little patch that
allowed the following:

   :info Show -- See class definition and instances
   :info -Show-- See class definition only

SPJ agreed with the idea itself, but suggested an alternative set of commands:

   :info Show-- See class definition only
   :instances Show   -- See instances of Show

This would have the advantage of making it easier to later add
additional features:

   :instances Show (Tree _)   -- See instances of form (Show (Tree ...))

However, it would make :i ambiguous, which is rather sad.

Another potential addition to :info (or another command) would be
evaluating types to their normal form, that is, expanding
(associated) type synonyms. E.g.:

   :typeeval Plus (Suc Zero) (Suc Zero)   -- (Suc (Suc (Suc (Suc Zero

Again, the question is whether this is really useful
(or reasonably easy to implement, SPJ?) and if so, what interface
is to be preferred?

So what's your favourite syntax? One of these options or something else?
Or are these features completely unnecessary?

Oh, the ticket can be found at
http://hackage.haskell.org/trac/ghc/ticket/2986#comment:3

Groeten, Remi
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-12 Thread Remi Turk
On Tue, Mar 11, 2008 at 01:43:36AM -0400, Brandon S. Allbery KF8NH wrote:
 On Mar 11, 2008, at 0:20 , Chaddaï Fouché wrote:
 2008/3/11, David Menendez [EMAIL PROTECTED]:
 I think Adrian is just arguing that a == b should imply f a == f b,
  for all definable f, in which case it doesn't *matter* which of two
  equal elements you choose, because there's no semantic difference.

 I completely agree that this propriety should be true for all Eq
 instance exported by a public module. I don't care if it is not the
 case in a isolated code, but libraries shouldn't break expected
 invariant (or at least be very cautious and warn the user). Even Eq
 Double respects this propriety as far as I know.

 I wouldn't want to bet on that (Eq Double, that is).  Floating point's just 
 *evil*.

I wouldn't bet on it either:

Prelude 0.0 == -0.0
True
Prelude isNegativeZero 0.0 == isNegativeZero (-0.0)
False

Although isNegativeZero might be considered a ``private,
internal interface that exposes implementation details.''

Groeten, Remi
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE / POST MORTEM: hswm, version ()

2007-10-28 Thread Remi Turk
Hi everyone,

HSWM was my attempt at a Haskell Window Manager, mostly written
during the first half of 2006 as a personal research project, and
out of frustration with some not to be named other window
managers. Although I have been running it myself for almost two
years, I never got around to polishing it into something
releasable due to lack of time. [1]
Since, as of today, its number of users is officially back to zero [2],
this seems like a good moment to release version () of HSWM:
The first and last version of my own window manager.

Features are:
- includes a lambda mouse cursor
- multiple desktops
- sticky windows
- about 2300 lines, about half of which is X boilerplate and user
  configuration
- somewhat based on evilwm
- still regularly dies due to unhandled X errors, so a script to
  automatically restart in that case is included
- my first Xlib program ever

The basic idea is an event loop inside an X monad
providing three services to plugins:
- registering X Event handlers
- registering X Error handlers
- registering/requesting services, to be used by other
  plugins (a global registry of named Dynamics, basically)

Compared to XMonad:
- no tiling
- much less stable
- no extensions
- needs no external libs

So you might want to look at it, but even _I_ don't use it anymore.

HSWM only was its working name, so if anybody ever feels like
writing another window manager and calling it HSWM,
I certainly won't mind.

The BSD-licensed code:

darcs get http://student.science.uva.nl/~rturk/hswm/

`make' compiles, and that's it.

Greetings, Remi

[1] Technical detail: The one feature I really wanted before releasing it,
but never got around to implementing, is having the WM add a
frame for each managed window and reparenting the window
below that frame. This way, focusing windows can go right even
when the WM dies, among others.

[2] It once had 3 users: Me at home, me at the University of
Amsterdam and me at Utrecht University.
Utrecht now runs KDE and the rest xmonad.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: type families not advertised for 6.8

2007-10-20 Thread Remi Turk
On Fri, Oct 19, 2007 at 08:25:22AM +0100, Simon Peyton-Jones wrote:
 | What does this imply for 6.8 support for FD's, as they now use
 | the same type-coercions?
 
 Actually FDs do not use type coercions, in GHC at least.  As Mark

Excuse me, it turns out I didn't look carefully enough: It's not
functional dependencies, it's classes-with-only-one-method:

module Bar where

bar = fmap id []

Compiles to the following Core with 6.8.0.20071002:

Bar.bar :: forall a_a5M. [a_a5M]
[GlobalId]
[]
Bar.bar =
  \ (@ a_a5M) -
(GHC.Base.$f8
 `cast` ((GHC.Base.:Co:TFunctor) []
 :: (GHC.Base.:TFunctor) []
  ~
forall a_a5G b_a5H. (a_a5G - b_a5H) - [a_a5G] - [b_a5H]))
  @ a_a5M @ a_a5M (GHC.Base.id @ a_a5M) (GHC.Base.[] @ a_a5M)


Or does this simply mean that only type-functions (the type/axiom
stuff) is not supported in 6.8, but type coercions (~ and cast) are supported
(although perhaps not at the source level)?

Cheers, Remi

 originally described them, FDs guide inference; and in
 particular, they give rise to some unifications that would not
 otherwise occur.  In terms of the intermediate language, that
 means there is no evidence associated with a FD; it's just the
 type checker's business. That means that various
 potentially-useful things can't be expressed, notably when FDs
 are combined with existentials or GADTs, that involve *local*
 equalities, which were beyond the scope of Marks's original
 paper.
 
 As the recent thread about FDs shows, FDs are quite tricky, at
 least if one goes beyond the well-behaved definition that Mark
 originally gave.  (And FDs are much more useful if you go
 beyond.)
 
 Our current plan is to regard FDs as syntactic sugar for indexed
 type families.  We think this can be done -- see our IFL workshop
 paper http://research.microsoft.com/%7Esimonpj/papers/assoc-types
 
 No plans to remove them, however.  After all, we do not have much
 practical experience with indexed type families yet, so it's too
 early to draw many judgements about type families vs FDs.
 
 I recommend Iavor's thesis incidentally, which has an interesting
 chapter about FDs, including some elegant (but I think
 unpublished) syntactic sugar that makes a FD look more like a
 function.  I don't think it's online, but I'm sure he can rectify
 that.
 
 Simon
 
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: type families not advertised for 6.8

2007-10-18 Thread Remi Turk
On Thu, Oct 18, 2007 at 02:58:21AM +0100, Simon Peyton-Jones wrote:
 |  Absolutely not; quite the reverse.  It means that some of the *code* for
 | type functions happens to be in the 6.8 release --- but that code has bugs.
 | It's only in 6.8 for our convenience (to avoid too great a divergence 
 between
 | the HEAD and 6.8), but we do not plan to *support* type functions in 6.8.
 | Doing that would delay 6.8 by 3 months.
 |
 | Do you make any difference between associated type synonyms and type
 | functions in this respect?
 
 No difference: both are in the 6.8 code base, but we won't
 support them there.  Both are in the HEAD, and we will support
 them there.
What does this imply for 6.8 support for FD's, as they now use
the same type-coercions?

Groeten, Remi
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] forall and a parse error

2006-11-15 Thread Remi Turk
Probably unrelated, but this thread is what triggered it for me.
There is a minor bug in showing impredicative types without
-fglasgow-exts: *hope I got that right*

Prelude let x = [] :: [forall a. a]

interactive:1:23:
Warning: Accepting non-standard infix type constructor `.'
 Use -fglasgow-exts to avoid this warning
Prelude :t x
x :: [. (forall a) a]

 

When -fglasgow-exts is set it shows what it should:

Prelude :t x
x :: [forall a. a]

Groetjes, Remi

On Tue, Jul 04, 2006 at 04:55:49PM +0100, Simon Peyton-Jones wrote:
 It's a parsing infelicity.  (Inside square brackets the parser knows not
 to expect a forall, whereas inside round parens it might.)  Perhaps it
 should be more accepting in square brackets, and reject later.
 
 Which the current HEAD does -- actually [forall a. a-a] is ok in the
 HEAD, see our ICFP06 paper.
 
 Simon
 
 | -Original Message-
 | From: [EMAIL PROTECTED]
 [mailto:[EMAIL PROTECTED] On Behalf Of Neil
 | Mitchell
 | Sent: 03 July 2006 19:44
 | To: Haskell Cafe
 | Subject: [Haskell-cafe] forall and a parse error
 | 
 | Hi,
 | 
 | I was experimenting with forall and higher rank types briefly, in
 particular:
 | 
 | x :: [forall a . a]
 | 
 | This is illegal because of:
 |
 http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.
 html#universal-quantification
 | 
 | Which is fine, however its surprising to compare the error messages:
 | 
 | [forall a . a]
 | parse error on input `forall'
 | 
 | [(forall a . a)]
 | Illegal polymorphic or qualified type: forall a. a
 | In the type signature: lst :: [(forall a. a)]
 | 
 | In normal Haskell, I tend to view [x] as equivalent to [(x)] (provided
 | that x is not a tuple) but in this case it has a different meaning -
 | albeit both are erronous meanings.
 | 
 | When running the example with Hugs, they both come out as syntax
 | errors - the first on the forall, the second on the closing square
 | bracket.
 | 
 | Thanks
 | 
 | Neil
 | ___
 | Haskell-Cafe mailing list
 | Haskell-Cafe@haskell.org
 | http://www.haskell.org/mailman/listinfo/haskell-cafe
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] RE: module names

2005-12-29 Thread Remi Turk
On Fri, Dec 16, 2005 at 07:55:50AM -0800, Scherrer, Chad wrote:
 From: S Koray Can [mailto:[EMAIL PROTECTED]
 Why not do this: name none of those modules Main.hs, and have an empty 
 module Main.hs with only import MainDeJour and main = 
 MainDeJour.main so you can just edit just that file.
 
 Cheers,
 Koray
 
 --
 Yeah, I like that approach. That saves me from having to remember which 
 file I most recent used as main. Seems easy enough to even set it up so
 that
 load MainDuJour
 writes the file Main.hs with
 
 import MainDuJour
 main = MainDuJour.main

A rather late reply I realize, but this slightly less verbose
version also works:

 module Main where

 import MainDuJour

Remi
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] PROPOSAL: class aliases (revised)

2005-10-14 Thread Remi Turk
On Thu, Oct 13, 2005 at 05:53:15PM -0700, John Meacham wrote:
 I have revised the proposal and put it on the web here:
 
  http://repetae.net/john/recent/out/classalias.html
 
 changes include a new, clearer syntax, some typo fixes, and a new
 section describing how class aliases interact with superclasses.
 
 I will update that web page with any new devolpments.
 
 John

Hi,

it sounds like a great idea. And as I don't really have anything
more fundamental to say about it, I'll invoke Wadlers Law now:

What about

 class Eq a = alias Num a = (Additive a, Multiplicative a)
or perhaps
 class alias Eq a = Num a = (Additive a, Multiplicative a)

instead of

 class alias Num a = Eq a = (Additive a, Multiplicative a)

If Eq a, then Num a is an alias for ...


Groeten,

Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell-cafe] wxHaskell: getting a checkbox state

2005-09-16 Thread Remi Turk
On Fri, Sep 16, 2005 at 12:12:50AM +0200, Sebastian Sylvan wrote:
 On 9/14/05, Mark Carter [EMAIL PROTECTED] wrote:
  The problem I was having before was that I was trying to create a
  separate function onCbEdit, thus:
 cbEdit - checkBox p1 [text := Edit Mode, on command :=  onCbEdit
  textlog   ]
  This had the problem that onCbEdit basically needed to have its control
  passed in (i.e. cbEdit) as a parameter in order to inspect its state. So
  I wanted to do something like:
 cbEdit - checkBox p1 [text := Edit Mode, on command :=  onCbEdit
  textlog   cbEdit ]
  Except you can't do that, because  cbEdit isn't yet defined. But your
  suggestion gets 'round that. In the main loop, I now do:
cbEdit - checkBox p1 [text := Edit Mode ]
set cbEdit [ on command :=  onCbEdit textlog  cbEdit ]
 
 Some extension (I think) to GHC allows mdo-notation (recursive do). So
 you can do this:
 mdo -- yadayada
cbEdit - checBox p1 [text := Edit Mode, on comand :=
 onCbEdit textlog cbEdit]
-- yadayada...

No extensions are needed, actually:

  cbEdit - checBox p1 [text := Edit Mode, on comand ::= onCbEdit textlog]
   ^^^
   Note the double colon.

Prelude Graphics.UI.WX :t (:=)
(:=) :: Attr w a - a - Prop w

Prelude Graphics.UI.WX :t (::=)
(::=) :: Attr w a - (w - a) - Prop w

Prelude Graphics.UI.WX :t (:~)
(:~) :: Attr w a - (a - a) - Prop w

Prelude Graphics.UI.WX :t (::~)
(::~) :: Attr w a - (w - a - a) - Prop w

Happy hacking,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] FunDeps and MArray

2005-09-05 Thread Remi Turk
On Mon, Sep 05, 2005 at 11:31:00AM -0700, Scherrer, Chad wrote:
 I keep getting this error in GHCi:
 
 Illegal instance declaration for `PlusEq (a i e) (a i e) (m ())'
 (the instance types do not agree with the functional dependencies of the 
 class)
 In the instance declaration for `PlusEq (a i e) (a i e) (m ())'
 Failed, modules loaded: none.
 
 Looking at GHC's documentation for MArray, the definition starts out
 
 class (HasBounds a, Monad m) = MArray a e m where
 ...
 
 It seems to me if MArray were written using fundeps (something like
 MArray a e m | a e - m) things may work out. Is there a reason it's not
 written this way? If so, is there another way to do what I'm trying to
 do? Thanks.

I don't know the actual reason, but if it were MArray a e m | a e - m
it would be impossible to define an MArray instance of STArray
for both the strict and the lazy ST monad.
(There isn't currently an instance for the lazy ST monad, but
right now it can easily be defined:
http://www.mail-archive.com/haskell-cafe@haskell.org/msg09404.html)

Groetjes,

Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.


pgpkLDaGjahzX.pgp
Description: PGP signature
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell-cafe] How to use STArray?

2005-08-27 Thread Remi Turk
On Fri, Aug 26, 2005 at 08:27:43PM -0400, ChrisK wrote:
 to figure out since there was no Data.Array.ST.Lazy.  Does anyone know
 why it was left out?  I'll put a note on the HaskellTwo page about that...

Some time ago when I wanted a lazy hashtable I came up with this,
which, after minimal testing, seemed to work:
(Lazy STRef's are implemented in exactly the same way, btw)

\begin{code}

{-# OPTIONS -fglasgow-exts #-}
module MArrayLazyST (
STArray,
module Data.Array.MArray
) where

import Control.Monad.ST.Lazy
import Data.Array.Base
import Data.Array.ST
import Data.Array.MArray

instance MArray (STArray s) e (ST s) where
newArray range e = strictToLazyST (newArray range e)
newArray_ range = strictToLazyST (newArray_ range)
unsafeRead arr i = strictToLazyST (unsafeRead arr i)
unsafeWrite arr i e = strictToLazyST (unsafeWrite arr i e)

\end{code}


Cheers,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] Re: ST/STRef vs. IO/IORef

2005-08-05 Thread Remi Turk
On Fri, Aug 05, 2005 at 08:04:53AM +0200, Till Mossakowski wrote:
 Sebastian Sylvan wrote:
 Hmmm... Wasn't that what he said?
 
 I disagree with the equation primitives = unsafe that
 is implicit in sentence

  to be implemented _efficiently_, also needs
  something like unsafePerformIO (or even lower-level unsafe
  mutable state primitives).
 
 The point is that ST uses *safe* primitives, and not something
 like unsafePerformIO.

Ah, I think I understand what we're disagreeing about exactly
now. We're understanding primitive to mean different things :)

You're seeing runST, newSTRef, writeSTRef etc as primitives, is
that correct? I see them as the public interface to something
which is implemented in something else. That is, just like
the memo function (deprecated, from the package util) is a safe
interface (memo is nicely referentially transparant) to a piece
of functionality implemented using unsafe primitives
(unsafePerformIO), the ST monad a perfectly safe abstraction
built on top of not-so-safe primitives. And with primitives I
mean unsafePerformIO in my previously attached implementation. In
GHC's implementation, this is even more clear:

  writeSTRef :: STRef s a - a - ST s ()
  writeSTRef (STRef var#) val = ST $ \s1# -
  case writeMutVar# var# val s1#  of { s2# -
  (# s2#, () #) }
(fptools/libraries/base/GHC/STRef.lhs)
  
  {-# INLINE runST #-}
  runST :: (forall s. ST s a) - a
  runST st = runSTRep (case st of { ST st_rep - st_rep })
  
  {-# NOINLINE runSTRep #-}
  runSTRep :: (forall s. STRep s a) - a
  runSTRep st_rep = case st_rep realWorld# of (# _, r #) - r
(fptools/libraries/base/GHC/ST.lhs)

There is a lot of messing around with state here. Actually,
runST(Rep) is remarkably similiar to unsafePerformIO:

  {-# NOINLINE unsafePerformIO #-}
  unsafePerformIO   :: IO a - a
  unsafePerformIO (IO m) = case m realWorld# of (# _, r #)   - r
(fptools/libraries/base/GHC/IOBase.lhs)

On Fri, Aug 05, 2005 at 08:12:36AM +0200, Till Mossakowski wrote:
 Remi Turk wrote:
 
 In a final attempt to convince someone of I'm not exactly sure
 what, I attached a simple implementation of the ST monad in
 terms of unsafePerformIO + IORef + IOArray.
 
 OK, but you have to reason about this implementation to show that
 it is safe (which may be difficult because unsafePerformIO makes
 reasoning extremely difficult), while the primitives of ST are
 more easily proved to be safe.

Though it's certainly not a formal proof, it seems to be ok by
both the can you imagine an alternative, possibly horribly slow,
but pure implementation and by the does it perform no observable
side-effects and does it always yield the same value criteria.

However, this is almost what I meant: Assume you'd really like to
have (1) the efficient histogram function from my previous message
and (2) an efficient implementation of ixmap.

You could implement both using unsafePerformIO + IOArray's and
still be perfectly safe. However, you'd have to prove it's safe
_twice_, both for (1) and for (2).

The superior alternative is to first implement the ST monad using
unsafePerformIO + IOArray's, proof that to be safe, and then
implement (1) and (2) using ST without having to think about
safety anymore.

Happy hacking,

Remi We're probably agreeing 99.9% anyway Turk

-- 
Nobody can be exactly like me. Even I have trouble doing it.


pgpLwRZRd1woq.pgp
Description: PGP signature
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Re: ST/STRef vs. IO/IORef

2005-08-05 Thread Remi Turk
On Fri, Aug 05, 2005 at 01:13:06PM +0400, Bulat Ziganshin wrote:
 Hello Till,
 
 Friday, August 05, 2005, 10:04:53 AM, you wrote:
 
 TMMonadState  IOArray IOArray  ST
 TMwithwith with
 TMFiniteMap   unsafePerformIO  MutArr
 
 TM safe   yesyes noyes
 
 TM efficient  no yes yes   yes
 
 
 afaik, ST efficient only with small enough arrays. one time i tried
 STArray of about 100 000 elements and seen that things goes much worse
 than in IO monad with IOArray. on small arrays STArray performs good
 enough
 
 (i was trying to create sorting routine. afair, it was an insert sort)

It might have been caused by a recently fixed (in CVS) unfeature/bug,
described on
http://sourceforge.net/tracker/index.php?func=detailaid=1019758group_id=8032atid=108032

IIRC, if the same code could be used both for ST s a and for
IO a, GHC could fail to specialize the ST s a version because
it had a typevariable too much.

Groeten,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.


pgpGhGRrLbEhN.pgp
Description: PGP signature
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Re: ST/STRef vs. IO/IORef

2005-08-04 Thread Remi Turk
On Thu, Aug 04, 2005 at 10:09:06AM +0100, Axel Simon wrote:
 On Thu, 2005-08-04 at 10:58 +0200, Wolfgang Jeltsch wrote:
  Am Donnerstag, 4. August 2005 10:21 schrieb Axel Simon:
   [...]
  
   Nowadays, you can use one of the MonadState monad
  
  State transformer monads like State and StateT can be implemented without 
  using special language features.  So there was always the opportunity to 
  implement something like State or StateT.  So, in a way, we always could 
  use 
  the MonadState monads.  If ST could be replaced by MonadState monads, ST 
  had 
  never been included in the libraries, I suppose.
 
 Well, MonadState needs multi-parameter type classes, and hence, require
 much more than ST. 

MonadState needs multi-parameter type classes, State and StateT
don't. And ST needs rank-2 types (or at least one rank-2
constant) and, to be implemented _efficiently_, also needs
something like unsafePerformIO (or even lower-level unsafe
mutable state primitives).

   if you want lazy computation (on top of which you can implement state read
   and write accesses similar to IORefs) or IO-enabled computation (if you 
   use
   MonadState.StateT and embed an IO monad at the core).
  
  The point is that the MonadState monads don't give you update-in-place.  
  Update-in-place is exactly the reason why ST is there.
 
 Ok, granted. In particular I take your point about array accesses.
 However, I am not quite convinced that using ST has any advantages over
 using IO directly. Of course, one could claim that programmers wants to
 protect themselves from themselves by disallowing arbitrary IO. But if
 that is the only advantage then I'd rather go for the flexibility to
 use arbitrary IO later on without having to rewrite my whole program.

Some algorithms are more naturally written imperatively and some
programs are more efficient when written imperatively. The ST
monad makes it possible to write programs which look imperative
and actually _are_ imperative too but still could have been
purely functional (given rank-2 types).

I think one could call the ST monad a safe yet still efficient
variant of unsafePerformIO + IORef's + IOArray's.

Groeten,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.


pgpdbRWCXxOSn.pgp
Description: PGP signature
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Re: ST/STRef vs. IO/IORef

2005-08-04 Thread Remi Turk
On Thu, Aug 04, 2005 at 10:40:01PM +0200, Till Mossakowski wrote:
 Remi Turk wrote:
 MonadState needs multi-parameter type classes, State and StateT
 don't. And ST needs rank-2 types (or at least one rank-2
 constant) and, to be implemented _efficiently_, also needs
 something like unsafePerformIO (or even lower-level unsafe
 mutable state primitives).
 
 I think one could call the ST monad a safe yet still efficient
 variant of unsafePerformIO + IORef's + IOArray's.
 
 No, the point of ST is that it is safe (as opposed to unsafePerformIO),
 but still has the advantages of being both efficient and allowing
 purely functional encapsulation via runST (as oppesed to IORefs
 and IOArrays). The only price is that you need rank-2 polymorphism
 and new language primitives for creating, reading and writing
 references. But using these primitives is much better than using
 unsafePerformIO - the latter entails a lot of harmful things.

As I agree with everything after the No I guess there is a new
misunderstanding in the world :) I'll try to clarify what I
meant:

Occasionally, one would like to write a piece of code which
performs updates in place. As an example I'll use a function
hist :: [Char] - [(Char, Int)]
which returns a histogram of (lowercase) letters. The most
efficient (and to many also most obvious) way to implement this
function is using an mutable array of letters to occurrence
counts.
One way to implement hist is then something like:

hist str = unsafePerformIO (do
arr - newArray ...
mapM_ (\x - ...) str
getAssocs arr
)

which is safe, as it does not have observable side-effects and
always yields the same value for a given argument.
Still, the proof obligation that it actually is safe lies with
the programmer, each time he implements something like hist.

In general, if some IO-action foo is pure except for its use of
IORef's and IOArray's, and it only uses ones it created itself,
and doesn't return any of them, it _cannot_ have observable
side-effects and will always yield the same value and hence
unsafePerformIO foo _will always be safe_.

This can be abstracted into a design pattern ;), called the ST
monad, thus only requiring the programmer to give a this use of
unsafePerformIO is safe-proof once for runST, instead of each
time he implements a hist-like function. (See attached modules.)

Hm, I'm not sure whether this can meaningfully be called a
clarification. Oh well :)

In a final attempt to convince someone of I'm not exactly sure
what, I attached a simple implementation of the ST monad in terms
of unsafePerformIO + IORef + IOArray.

And as a really-I-mean-it final remark,
 I think one could call the ST monad a safe yet still efficient
 variant of unsafePerformIO + IORef's + IOArray's.
, could probably be phrased better as the ST monad can be seen
as a safe subset of the functionality of unsafePerformIO +
IORef + IOArray.

Cheers,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
{-# OPTIONS_GHC -fglasgow-exts #-}
module MyST (ST, runST
,STRef, newSTRef, readSTRef, writeSTRef
,STArray
,module Data.Array.MArray
) where

import Monad
import Data.IORef
import Data.Array.Base (unsafeRead, unsafeWrite)
import Data.Array.MArray
import Data.Array.IO (IOArray)
import System.IO.Unsafe (unsafePerformIO)

--- ST ---

newtype ST s a = ST {unST :: IO a}

runST :: (forall s. ST s a) - a
runST = unsafePerformIO . unST

instance Monad (ST s) where
return = ST . return
ST a = f = ST (a = unST . f)

--- STRef ---

newtype STRef s a = STRef {unSTRef :: IORef a}

newSTRef :: a - ST s (STRef s a)
newSTRef = ST . liftM STRef . newIORef

readSTRef :: STRef s a - ST s a
readSTRef = ST . readIORef . unSTRef

writeSTRef :: STRef s a - a - ST s ()
writeSTRef r = ST . writeIORef (unSTRef r)

--- STArray ---

newtype STArray s i e = STArray {unSTArray :: IOArray i e}

instance HasBounds (STArray s) where
bounds = bounds . unSTArray

instance MArray (STArray s) e (ST s) where
newArray b = ST . liftM STArray . newArray b
unsafeRead a = ST . unsafeRead (unSTArray a)
unsafeWrite a i = ST . unsafeWrite (unSTArray a) i
module Foo where

import Monad
import System.IO.Unsafe (unsafePerformIO)
import Data.Array.MArray
import Data.Array.IO

import MyST

hist f xs = do
arr - f $ newArray ('a','z') 0
flip mapM_ xs $ \x - do
n - readArray arr x
writeArray arr x (n+1)
filter ((/=0) . snd) `liftM` getAssocs arr

idSTArray :: ST s (STArray s i e) - ST s (STArray s i e)
idSTArray = id

idIOArray :: IO (IOArray i e) - IO (IOArray i e)
idIOArray = id

histST, histIO :: [Char] - [(Char, Int)]
histST xs = runST   (hist idSTArray xs)
histIO xs = unsafePerformIO (hist idIOArray xs)


pgpTLIudH9wsD.pgp
Description: PGP signature
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: STM and unsafePerformIO

2005-08-03 Thread Remi Turk
On Wed, Aug 03, 2005 at 12:50:54PM +0200, Robert van Herk wrote:
 Hello All,
 
 I think I've read somewhere that STM doesn't like unsafePerformIO. 
 However, I would like to use a global STM variable. Something like this:
 
 module Main where
 import GHC.Conc
 import System.IO.Unsafe
 
 tSid = unsafePerformIO (atomically (newTVar 0))
 
 tickSessionID :: STM Int
 tickSessionID =
  do sid - readTVar tSid
 writeTVar tSid (sid + 1)
 return sid
 
 main = atomically tickSessionID
 
 
 
 But, when I try this, the evaluation of main causes a segmentation 
 fault. Is there a workaround for this bug?
 
 Regards,
 Robert

It probably dies not because of unsafePerformIO per se, but
because STM doesn't understand nested transactions, and
unsafePerformIO here results in a nested transaction. Using the
following main works for me, as it forces both atomically's to
be evaluated sequentially:

main = tSid `seq` atomically tickSessionID


See also
http://haskell.org/pipermail/glasgow-haskell-users/2005-June/008615.html
and
http://sourceforge.net/tracker/index.php?func=detailaid=1235728group_id=8032atid=108032

Happy hacking,
Remi

P.S. Could you find out (and fix) what inserts those spurious *'s in your code?

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Proposal: deriving ShallowEq?

2005-07-19 Thread Remi Turk
On Tue, Jul 19, 2005 at 08:16:35PM +1000, Ben Lippmeier wrote:
 Bulat Ziganshin wrote:
 
 reading GHC sources is always very interesting :)
 that is from GHC/Base.hs :
 
 getTag :: a - Int#
 getTag x = x `seq` dataToTag# x
 
 ! This is just what I was looking for, thankyou.
 
 My shallowEq function is now simply:
 
 shallowEq :: a - a - Bool
 shallowEq a b = getTag a ==# getTag b
 
 My project is already totally reliant on GHC, and this will save me the 
 heartache of hacking DrIFT (which I was in the process of setting up 
 when I saw this mail) into my makefile.
 
 Portability be damned!
 
 Ben.

You might increase portability a bit by using

import Data.Generics

shallowEq :: Data a = a - a - Bool
shallowEq x y = toConstr x == toConstr y

it does introduce a dependency on Data though

Groeten,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.


pgpyTyB9kylSx.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


unsafeInterleaveIO + Ctrl-C/killThread related segfault.

2005-06-28 Thread Remi Turk
Good evening,

I just stumbled across a segfault caused when running the
following small program. (During an attempt to implement
single-assignment variables.)

 module Main where
 
 import Control.Concurrent
 import System.IO.Unsafe (unsafeInterleaveIO)
 
 main = do
 v - newEmptyMVar
 a - unsafeInterleaveIO (readMVar v)
 t - forkIO (print a)
 threadDelay (1000*1000)
 killThread t
 forkIO (print a)
 putMVar v ()

The crucial part about it seems to be the interruption of the
lazy IO. Typing Ctl-c while running the first print a by hand
from ghci instead of the forkIO+killThread doesn't change
behaviour:

 Prelude System.IO.Unsafe Control.Concurrent v - newEmptyMVar
 Prelude System.IO.Unsafe Control.Concurrent a -
 unsafeInterleaveIO (readMVar v)
 Prelude System.IO.Unsafe Control.Concurrent print a
 Interrupted.
 Prelude System.IO.Unsafe Control.Concurrent forkIO (print a)
 Prelude System.IO.Unsafe Control.Concurrent putMVar v ()
 zsh: segmentation fault (core dumped)  ghci

Both 6.4 and 6.2.1 crash when running main from ghci.
When running it as a compiled executable everything is fine.

Although I'm pretty sure I've seen 6.2.1 crashing 
on it when run with -e main, I cannot reproduce it anymore. 6.4
certainly happily runs it with -e main. (A serious lack of sleep
the last week may play a role too.. :-/)

Whether the module is compiled before being loaded into ghci has
no effect.

Core-dumps etc can of course be sent if necessary.

Good night,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.


pgp0yqAd3iNbi.pgp
Description: PGP signature
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: unsafeness of unsafeInterleaveIO

2005-06-10 Thread Remi Turk
On Fri, Jun 10, 2005 at 07:32:42PM +0200, Lennart Augustsson wrote:
 Andre Pang wrote:
 G'day all,
 
 Just looking at the documentation for System.IO.unsafeInterleaveIO,  
 what exactly is unsafe about it?
 You pick. :)
 
 It can break referential transparency.  It can break type safety.
 
   -- Lennart
 

Are you sure you're not talking about unsafePerformIO?

System.IO.Unsafe.unsafePerformIO:: IO a - a
System.IO.Unsafe.unsafeInterleaveIO :: IO a - IO a

As far as I know unsafeInterleaveIO in general isn't any unsafer
than it's special cases getContents / hGetContents / readFile /
getChanContents.  Although fighting lazy IO might occasionally
drive someone mad, which could arguably be called unsafe.

Cheers,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.


pgpxOF8lzrZuS.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: unsafeness of unsafeInterleaveIO

2005-06-10 Thread Remi Turk
On Sat, Jun 11, 2005 at 01:55:57AM +0200, Thomas Jäger wrote:
  Just looking at the documentation for System.IO.unsafeInterleaveIO,
  what exactly is unsafe about it?
 
 It can create pure values that trigger side effects during their
 evaluation. This can be abused to do IO outside of an IO monad
 (actually, hGetContents can already be used for that purpose).
 
 In the worst case, it can even crash the RTS:
  import Control.Concurrent.STM
  import System.IO.Unsafe
  
  main :: IO ()
  main = atomically = unsafeInterleaveIO (atomically $ return $ return ())
 
 Thomas

Stares at a core-dump.
I wonder whether this would be worth a bug-report, or perhaps a
warning in STM's docs about (understandable) undefined behaviour
in this case. Interestingly, Tomasz Zielonka's FakeSTM [1]
survives it.

Groeten,
Remi

[1]
http://www.haskell.org/pipermail/haskell-cafe/2005-March/009389.html
darcs get http://www.uncurry.com/repos/FakeSTM/

-- 
Nobody can be exactly like me. Even I have trouble doing it.


pgpKdFyzGrO2R.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: foldr f (head xs) xs is not the same as foldr1 f xs

2005-05-08 Thread Remi Turk
On Sun, May 08, 2005 at 08:14:30PM +0200, David Sabel wrote:
 Hi!
 
 A small example for the claim mentioned in the subject:
 
 Prelude let x = 1:undefined in foldr (curry fst) (head x) x
 1
 Prelude let x = 1:undefined in foldr1 (curry fst)  x
 *** Exception: Prelude.undefined
 
 Perhaps it would be better to change the implementation of foldr1?

Why? *wonders what he's missing* It sounds like a rather silly
claim to me. When changed to

  foldr f (head xs) (tail xs)  is not the same as foldr1 f xs
^

I would be more interested to see examples...

Greetings,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


-O causing a 7x slowdown (Map of IORef's)

2005-04-23 Thread Remi Turk
Good afternoon,

the attached program is about 7 times slower when compiled
_with_ -O using ghc 6.4. Using ghc 6.2.1 with ddata's Map gives
the same behaviour.

Happy hacking,
Remi


% make

ghc --make -no-recompMain.hs -o nor
Chasing modules from: Main.hs
Compiling Main ( Main.hs, Main.o )
Linking ...

ghc --make -no-recomp -O Main.hs -o opt
Chasing modules from: Main.hs
Compiling Main ( Main.hs, Main.o )
Linking ...

time -p ./nor
real 1.77
user 1.75
sys 0.00

time -p ./opt
real 13.05
user 12.45
sys 0.06

-- 
Nobody can be exactly like me. Even I have trouble doing it.
module Main (main) where

import Data.Map (Map, fromList, (!))
import Control.Monad(replicateM_, liftM)
import Data.IORef   (IORef, newIORef, readIORef)

main = do
mc - fromList `liftM` mapM new [1..1000]
replicateM_ 1 $ mapM_ (get mc) [1..1000]
where
new :: Integer - IO (Integer, IORef Integer)
new k   = do r - newIORef 0; return (k, r)

get :: Map Integer (IORef Integer) - Integer - IO Integer
get mc k= readIORef (mc ! k)
.PHONY: all

all:
ghc --make -no-recompMain.hs -o nor
ghc --make -no-recomp -O Main.hs -o opt
time -p ./nor
time -p ./opt
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: ANNOUNCE: GHC version 6.4

2005-03-11 Thread Remi Turk
On Fri, Mar 11, 2005 at 12:25:04PM -, Simon Marlow wrote:
 
=
 The (Interactive) Glasgow Haskell Compiler -- version 6.4
=
 
 The GHC Team is delighted to announce a new major release of GHC.  It
 has been a long time since the last major release (Dec 2003!), and a
 lot has happened:

It's great to hear that *my computer isn't going to get much
sleep tonight* :)

And there's a funny typo which left me wondering why? for a few
seconds on
http://haskell.org/ghc/docs/6.4/html/users_guide/release-6-4.html

o Debug.QuickCheck is now Text.QuickCheck

Groetjes,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


[Haskell] Re: ANNOUNCE: GHC version 6.4

2005-03-11 Thread Remi Turk
On Fri, Mar 11, 2005 at 12:25:04PM -, Simon Marlow wrote:
 
=
 The (Interactive) Glasgow Haskell Compiler -- version 6.4
=
 
 The GHC Team is delighted to announce a new major release of GHC.  It
 has been a long time since the last major release (Dec 2003!), and a
 lot has happened:

It's great to hear that *my computer isn't going to get much
sleep tonight* :)

And there's a funny typo which left me wondering why? for a few
seconds on
http://haskell.org/ghc/docs/6.4/html/users_guide/release-6-4.html

o Debug.QuickCheck is now Text.QuickCheck

Groetjes,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


{-# SPECIALIZE, IO vs ST s

2005-03-10 Thread Remi Turk
Hello again,

first of all, I'm not sure whether this is actually a bug-report
or a feature-request.

The three line summary is that in the following program, no
specialized version for ST s is created by at least 6.2.1,
6.4.20050304, and 6.4.20050308.

  {-# OPTIONS -fno-implicit-prelude #-}
  module MHashTable () where
  
  import GHC.Base ( RealWorld, Monad, return )
  import GHC.IOBase   ( IO )
  import Control.Monad.ST ( ST )
  
  {-# SPECIALIZE bucketIndex :: ST s () #-}
  {-# SPECIALIZE bucketIndex :: IO () #-}
  
  bucketIndex :: Monad m = m ()
  bucketIndex = return ()

Practically any other specialization, including Maybe, [] and ST RealWorld
_are_ actually performed.

What GHC has to say about it:

  % /var/tmp/ghc/bin/ghc -O --make -ddump-rules MHashTable.hs
  Chasing modules from: MHashTable.hs
  Compiling MHashTable   ( MHashTable.hs, MHashTable.o )
  
  
   Top-level specialisations 
  SPEC MHashTable.bucketIndex __forall {$dMonad :: {GHC.Base.Monad 
GHC.IOBase.IO}}
MHashTable.bucketIndex @ GHC.IOBase.IO $dMonad
= $sbucketIndex ;

In case anyone is wondering what's the point, it'll get inlined
anyway, I'm trying to enhance Data.HashTable to work both with
IO and ST s without duplicating the whole module or flushing
performance down the drain, and the real functions are quite a
bit bigger, hence won't be inlined.

Right now, I have four versions:
Data.HashTable, STHashTable (specialized for ST s), and
MHashTable which works with a typeclass for both IO and ST s.
The first two, and MHashTable instantiated on IO are about
equally fast, but as SPECIALIZE doesn't seem to have much effect
on ST s, MHashTable instantiated on ST s is about two times
slower.

Greetings,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: infix type operators

2005-03-09 Thread Remi Turk
[warning: Very Vague message  possible bug-report follow]

Though I cannot claim any real-world experience with arrows, I'm
not sure I like this, and I hope they'll at least remain
experimental (may be removed next release kind of thing) for a
while.

- I doubt whether the difference between Arrow a = a b c and
  Arrow (~) = b ~ c is all that great. Or even, whether the
  perhaps slightly improved readability of b ~ c makes up for
  the IMO slightly decreased readability of Arrow (~).
- When one really needs to do it infix, one can always write
  Arrow a = b `a` c.
- It's one thing more to learn. The difference between types and
  typevariables (upper/lowercase) is better visible than the
  difference between operator(variables) and infix-types (Does
  it start with a colon?) Which, I have to admit, is more of a
  vague feeling than anything like a fact.
- We already have the special case of - as a _type_, not
  a typevariable, and having - as a type, :- as a type and -:
  as a typevariable doesn't sound too great. Of course, as - is
  special in expression context too, that may not be convincing
  either :(

So I guess I'll have to end this mail with there is at least one
person not feeling entirely comfortable about it :)

Would it at least be possible to make it a seperate flag from
-fglasgow-exts? (I'm slightly worried about people needing one
extension and then using the rest too just because they're
already enabled, so actually this doesn't apply only to this
particular feature.)

Groetjes,
Remi


On Wed, Mar 09, 2005 at 05:06:03PM -, Simon Peyton-Jones wrote:
 OK, it's done for 6.4
 
 SImon
 
 | -Original Message-
 | From: [EMAIL PROTECTED]
 [mailto:glasgow-haskell-users-
 | [EMAIL PROTECTED] On Behalf Of Ross Paterson
 | Sent: 08 March 2005 16:29
 | To: glasgow-haskell-users@haskell.org
 | Subject: infix type operators
 | 
 | The User's Guide says:
 | 
 | The only thing that differs between operators in types and
 | operators in expressions is that ordinary non-constructor
 | operators, such as + and * are not allowed in types.  Reason:
 | the uniform thing to do would be to make them type variables,
 | but that's not very useful.  A less uniform but more useful
 thing
 | would be to allow them to be type constructors.  But that gives
 | trouble in export lists.  So for now we just exclude them.
 | 
 | Conal has pointed out that the uniform thing would be useful for
 | general arrow combinators:
 | 
 | liftA2 :: Arrow (~) =
 | (a - b - c) - (e ~ a) - (e ~ b) - (e ~ c)

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: 6.4.20050304 RULES panic from CgMonad.lhs other nastiness

2005-03-07 Thread Remi Turk
On Mon, Mar 07, 2005 at 05:07:05PM -, Simon Peyton-Jones wrote:
 Excellent bug.  It's been there a long time.   You seem to have a talent
 for finding dark corners in GHC!
 
 Anyway, it's fixed, and a test added.
 
 SImon

I'll probably build a new release candidate tomorrow, so stay
tuned ;)
One question though: MHashTable.hs (simpl011.hs) itself builds ok
(well, doesn't crash), it's only when Main.hs imports  uses it
that GHC dies, so will
testsuite/tests/ghc-regress/simplCore/should_compile/simpl011.hs
actually catch the bug?

Cheers,
Remi

 | -Original Message-
 | From: [EMAIL PROTECTED]
 [mailto:glasgow-haskell-bugs-
 | [EMAIL PROTECTED] On Behalf Of Remi Turk
 | Sent: 07 March 2005 00:41
 | To: glasgow-haskell-bugs@haskell.org
 | Subject: 6.4.20050304 RULES panic from CgMonad.lhs  other nastiness
 | 
 | Hi,
 | 
 | while still trying to get Data.HashTable to work both in ST and
 | IO (I'll probably start complaining about optimizations not
 | performed once this is fixed ;), I bumped into the following
 | nastiness.
 | 
 | Comments interleaved with shell copy-paste-work.
 | 
 | 
 |% make clean
 |rm -f *.o *.hi a.out
 | 
 | 
 |% /var/tmp/ghc/bin/ghc --make -O Main.hs
 |Chasing modules from: Main.hs
 |Compiling MHashTable   ( ./MHashTable.hs, ./MHashTable.o )
 |Compiling Main ( Main.hs, Main.o )
 |ghc-6.4.20050304: panic! (the `impossible' happened, GHC version
 6.4.20050304):
 | cgPanic
 |zdfMutHashSTArray{v a1ip}
 |static binds for:
 |local binds for:
 |SRT labelghc-6.4.20050304: panic! (the `impossible' happened,
 GHC version 6.4.20050304):
 | initC: srt
 | 
 | Okay, it dies. Almost any new change in the source makes this one
 | go away. The next panic is probably partly a consequence of this
 | one: MHashTable.o already exists and GHC can't cope with that for
 | some reason. That reason may of course be that MHashTable.o
 | contains garbage due to the previous bug.
 | 
 | 
 |% /var/tmp/ghc/bin/ghc --make -O Main.hs
 |Chasing modules from: Main.hs
 |Skipping  MHashTable   ( ./MHashTable.hs, ./MHashTable.o )
 |ghc-6.4.20050304: panic! (the `impossible' happened, GHC version
 6.4.20050304):
 | tcIfaceGlobal (local): not found:
 |MHashTable.updateST{v r87}
 |[(rr, Identifier `MHashTable.zdfMutHashSTArray{v rr}'),
 | (rs, Type constructor `MHashTable.HT{tc rs}'),
 | (rt, Identifier `MHashTable.dir{v rt}'),
 | (ru, Data constructor `MHashTable.HT{d ru}'),
 | (rv, Identifier `MHashTable.HT{v rv}'),
 | (rw, Type constructor `MHashTable.HashTable{tc rw}'),
 | (rx, Data constructor `MHashTable.HashTable{d rx}'),
 | (ry, Identifier `MHashTable.zdWHashTable{v ry}'),
 | (rz, Type constructor `MHashTable.STHashTable{tc rz}'),
 | (rA, Class `MHashTable.MutHash{tc rA}'),
 | (rB, Type constructor `MHashTable.ZCTMutHash{tc rB}'),
 | (rC, Data constructor `MHashTable.ZCDMutHash{d rC}'),
 | (rD, Identifier `MHashTable.ZCDMutHash{v rD}'),
 | (rE, Identifier `MHashTable.newMHArray{v rE}'),
 | (rF, Identifier `MHashTable.readMHArray{v rF}'),
 | (rG, Identifier `MHashTable.writeMHArray{v rG}'),
 | (rH, Identifier `MHashTable.newMHRef{v rH}'),
 | (rI, Identifier `MHashTable.readMHRef{v rI}'),
 | (rJ, Identifier `MHashTable.writeMHRef{v rJ}'),
 | (rK, Identifier `MHashTable.zdp1MutHash{v rK}'),
 | (rL, Identifier `MHashTable.new{v rL}'),
 | (rM, Identifier `MHashTable.update{v rM}'),
 | (rN, Identifier `MHashTable.zdwpolyzuwriteMHArray{v rN}'),
 | (rO, Identifier `MHashTable.polyzuwriteMHArray{v rO}'),
 | (rP, Identifier `MHashTable.lit{v rP}'),
 | (rQ, Identifier `MHashTable.lvl{v rQ}'),
 | (rR, Identifier `MHashTable.zdwnew{v rR}')]
 | 
 | 
 |% make clean
 |rm -f *.o *.hi a.out
 | 
 | Removing all generated files: A Fresh Start with another
 | definition of new (see attachment):
 | 
 | 
 |% /var/tmp/ghc/bin/ghc --make -Dnew_undef -no-recomp -O Main.hs
 |Chasing modules from: Main.hs
 |Compiling MHashTable   ( ./MHashTable.hs, ./MHashTable.o )
 |Compiling Main ( Main.hs, Main.o )
 |Linking ...
 |Main.o(.text+0x57): undefined reference to
 `MHashTable_updateST_closure'
 |Main.o(.rodata+0x0): undefined reference to
 `MHashTable_updateST_closure'
 |collect2: ld returned 1 exit status
 | 
 | 
 | Finally, executing the previous command again gives _another_
 | error, which is rather weird given that -no-recomp is given...
 | 
 | 
 |% /var/tmp/ghc/bin/ghc --make -Dnew_undef -no-recomp -O Main.hs
 |Chasing modules from: Main.hs
 |Compiling MHashTable   ( ./MHashTable.hs, ./MHashTable.o )
 |Compiling Main ( Main.hs, Main.o )
 |ghc-6.4.20050304: panic! (the `impossible' happened, GHC version

Re: [Haskell-cafe] tuples and Show in GHC

2005-03-07 Thread Remi Turk
On Mon, Mar 07, 2005 at 12:05:41AM +, Keean Schupke wrote:
 Daniel Fischer wrote:
 
 The Show instances for tuples aren't automatically derived, they are 
 defined in GHC.Show. So somewhere there must be an end, probably the 
 author(s) thought that larger tuples than quintuples aren't used often 
 enough to bother. That's not a principled reason but a practical one, but 
 it's good enough for me.
 If you need them frequently and don't want to define your own instances, 
 complain.
 BTW, tuples are defined in Data.Tuple up to 62-tuples and Eq and Ord 
 instances are derived up to 15-tuples.
 In Hugs, apparently they are only provided up to quintuples.
 
 Has there been any work done on declaring instances over all tuples? It 
 seems the pattern occurs fairly often, and is quite simple to abstract.
 
Keean.

Which almost sounds like a hint to replace the current tuples by
HLists in Haskell 2? ;)

Something like:

infixr 5 :*:
data HNil = HNil
data HList b = a :*: b = a :*: !b deriving (Eq, Ord)

-- type () = HNil
type (a,b) = a :*: b :*: HNil
type (a,b,c) = a :*: b :*: c :*: HNil

fst :: HList b = (a :*: b) - a
fst (a:*:b) = a

Where (x,y,z) is syntactic sugar for x :*: y :*: z :*: HNil in
much the same way [x,y,z] is syntactic sugar for x:y:z:[]...

It might even be (almost?) backward compatible AFAICS.

Groeten,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


6.4.20050304 RULES panic from CgMonad.lhs other nastiness

2005-03-06 Thread Remi Turk
Hi,

while still trying to get Data.HashTable to work both in ST and
IO (I'll probably start complaining about optimizations not
performed once this is fixed ;), I bumped into the following
nastiness.

Comments interleaved with shell copy-paste-work.


   % make clean
   rm -f *.o *.hi a.out
   
   
   % /var/tmp/ghc/bin/ghc --make -O Main.hs
   Chasing modules from: Main.hs
   Compiling MHashTable   ( ./MHashTable.hs, ./MHashTable.o )
   Compiling Main ( Main.hs, Main.o )
   ghc-6.4.20050304: panic! (the `impossible' happened, GHC version 
6.4.20050304):
cgPanic
   zdfMutHashSTArray{v a1ip}
   static binds for:
   local binds for:
   SRT labelghc-6.4.20050304: panic! (the `impossible' happened, GHC 
version 6.4.20050304):
initC: srt

Okay, it dies. Almost any new change in the source makes this one
go away. The next panic is probably partly a consequence of this
one: MHashTable.o already exists and GHC can't cope with that for
some reason. That reason may of course be that MHashTable.o
contains garbage due to the previous bug.


   % /var/tmp/ghc/bin/ghc --make -O Main.hs
   Chasing modules from: Main.hs
   Skipping  MHashTable   ( ./MHashTable.hs, ./MHashTable.o )
   ghc-6.4.20050304: panic! (the `impossible' happened, GHC version 
6.4.20050304):
tcIfaceGlobal (local): not found:
   MHashTable.updateST{v r87}
   [(rr, Identifier `MHashTable.zdfMutHashSTArray{v rr}'),
(rs, Type constructor `MHashTable.HT{tc rs}'),
(rt, Identifier `MHashTable.dir{v rt}'),
(ru, Data constructor `MHashTable.HT{d ru}'),
(rv, Identifier `MHashTable.HT{v rv}'),
(rw, Type constructor `MHashTable.HashTable{tc rw}'),
(rx, Data constructor `MHashTable.HashTable{d rx}'),
(ry, Identifier `MHashTable.zdWHashTable{v ry}'),
(rz, Type constructor `MHashTable.STHashTable{tc rz}'),
(rA, Class `MHashTable.MutHash{tc rA}'),
(rB, Type constructor `MHashTable.ZCTMutHash{tc rB}'),
(rC, Data constructor `MHashTable.ZCDMutHash{d rC}'),
(rD, Identifier `MHashTable.ZCDMutHash{v rD}'),
(rE, Identifier `MHashTable.newMHArray{v rE}'),
(rF, Identifier `MHashTable.readMHArray{v rF}'),
(rG, Identifier `MHashTable.writeMHArray{v rG}'),
(rH, Identifier `MHashTable.newMHRef{v rH}'),
(rI, Identifier `MHashTable.readMHRef{v rI}'),
(rJ, Identifier `MHashTable.writeMHRef{v rJ}'),
(rK, Identifier `MHashTable.zdp1MutHash{v rK}'),
(rL, Identifier `MHashTable.new{v rL}'),
(rM, Identifier `MHashTable.update{v rM}'),
(rN, Identifier `MHashTable.zdwpolyzuwriteMHArray{v rN}'),
(rO, Identifier `MHashTable.polyzuwriteMHArray{v rO}'),
(rP, Identifier `MHashTable.lit{v rP}'),
(rQ, Identifier `MHashTable.lvl{v rQ}'),
(rR, Identifier `MHashTable.zdwnew{v rR}')]
   
   
   % make clean
   rm -f *.o *.hi a.out

Removing all generated files: A Fresh Start with another
definition of new (see attachment):


   % /var/tmp/ghc/bin/ghc --make -Dnew_undef -no-recomp -O Main.hs
   Chasing modules from: Main.hs
   Compiling MHashTable   ( ./MHashTable.hs, ./MHashTable.o )
   Compiling Main ( Main.hs, Main.o )
   Linking ...
   Main.o(.text+0x57): undefined reference to `MHashTable_updateST_closure'
   Main.o(.rodata+0x0): undefined reference to `MHashTable_updateST_closure'
   collect2: ld returned 1 exit status


Finally, executing the previous command again gives _another_
error, which is rather weird given that -no-recomp is given...


   % /var/tmp/ghc/bin/ghc --make -Dnew_undef -no-recomp -O Main.hs
   Chasing modules from: Main.hs
   Compiling MHashTable   ( ./MHashTable.hs, ./MHashTable.o )
   Compiling Main ( Main.hs, Main.o )
   ghc-6.4.20050304: panic! (the `impossible' happened, GHC version 
6.4.20050304):
lookupVers1 MHashTable updateST{v}

Good night,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
{-# OPTIONS -fglasgow-exts -cpp #-}
module MHashTable (STHashTable, new, update) where

import Data.Int (Int32)
import Control.Monad.ST (ST)
import Data.STRef   (STRef)
import Data.Array.ST(STArray)
import Data.Array.MArray(writeArray)

class Monad m = MutHash arr ref m | arr - m, ref - m
   , arr - ref, ref - arr where
newMHArray  :: (Int32, Int32) - a - m (arr Int32 a)
readMHArray :: arr Int32 a - Int32 - m a
writeMHArray:: arr Int32 a - Int32 - a - m ()

newMHRef:: a - m (ref a)
readMHRef   :: ref a - m a
writeMHRef  :: ref a - a - m ()

instance MutHash (STArray s) (STRef s) (ST s) where
newMHArray  = undefined
readMHArray = undefined
writeMHArray= writeArray

newMHRef= undefined
readMHRef   = undefined
writeMHRef  = undefined

type STHashTable s key val = HashTable key val (STArray s) (STRef s) (ST s)

newtype 

Re: 6.4.20050215: panic: lookupVers1 MHashTable HT{d}

2005-02-28 Thread Remi Turk
On Mon, Feb 28, 2005 at 03:01:53AM -, Simon Peyton-Jones wrote:
 Ah, this one we fixed a few days ago.  Works for me with the head.
 
 Thanks for your well-boiled-down bug reports; they are a lot faster to
 fix.
 
 Simon

Thanks, it's nice to hear that. Though I consider it a fair
deal: I'm spending more time on bug-boiling, and you're
spending more time on the parts I still consider as being above
my head ;)

Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: segfault/massive memory use when using Data.Bits.shiftL

2005-02-28 Thread Remi Turk
On Mon, Feb 28, 2005 at 02:55:56PM +, Ganesh Sittampalam wrote:
 Hi,
 
 The following either eats memory until killed or segfaults (I can't pin
 down a reason for the difference). Tested with GHC 6.2.2 and 6.4.20050212,
 with various different libgmp3s under various Redhat and Debian platforms,
 and WinXP.
 
 Prelude :m +Data.Bits
 Prelude Data.Bits 18446658724119492593 `shiftL` (-3586885994363551744) ::
 Integer
 
 Cheers,
 
 Ganesh

shiftL for Integer is defined in fptools/libraries/base/Data/Bits.hs:

class Num a = Bits a where
shiftL   :: a - Int - a
x `shiftL` i = x `shift`  i

instance Bits Integer where
   shift x i | i = 0= x * 2^i
 | otherwise = x `div` 2^(-i)

IOW, for y  0:
x `shiftL` y
  = x `shift` y
  = x `div` 2^(-y)

and calculating, in your case, 2^3586885994363551744 is not
something your computer is going to like...
as it's probably a number which doesn't fit in our universe :)
Still, a segfault might point at a bug, which I unfortunately
won't be able to say much about. (Due to lack of knowledge 
information.)

Greetings,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: segfault/massive memory use when using Data.Bits.shiftL

2005-02-28 Thread Remi Turk
On Mon, Feb 28, 2005 at 10:59:32PM +, Ganesh Sittampalam wrote:
 On Mon, 28 Feb 2005, Remi Turk wrote:
 
  On Mon, Feb 28, 2005 at 02:55:56PM +, Ganesh Sittampalam wrote:
  
   Prelude :m +Data.Bits
   Prelude Data.Bits 18446658724119492593 `shiftL` (-3586885994363551744) ::
   Integer
 
  and calculating, in your case, 2^3586885994363551744 is not
  something your computer is going to like...
  as it's probably a number which doesn't fit in our universe :)
 
 Hmm, good point. I hadn't thought about the fact that the number of digits
 in the answer would be rather large...
Actually, the final answer will be 0: It's only the intermediate
value that gets ridiculously large.

  Still, a segfault might point at a bug, which I unfortunately
  won't be able to say much about. (Due to lack of knowledge 
  information.)
 
 My googling suggests that gmp is prone to segfaulting when things get too
 large for it, so I'll just chalk it up to that.
 
 I apologise for thinking this was a bug :-)

No need to apologize. Segfaults _are_ IMHO almost always bugs.
And in this case too, though the fault isn't GHCs.

Groeten,
Remi

 Cheers,
 
 Ganesh

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


6.4.20050215 inferred types incorrect

2005-02-27 Thread Remi Turk
Hi,

6.4 appears to incorrectly infer some types in the attached code
when asking with :info in GHCi.
Both 6.2.1 and 6.4.20050215 inferrings (is there a nice english
word for that?) are added and commented out.

Greetings,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
{-# OPTIONS -fglasgow-exts -cpp #-}
module Foo where

import Random
import Data.Int
import Maybe

data HTCmd k v  = Ins k v

instance (Random k, Random v) = Random (HTCmd k v) where
random g= error Not Implemented
randomR (f,t) g = error Not Implemented

-- Wrong 6.4 inferred type (:t)
#if 0
exec :: (Monad m) =
(t - k - v - m a) - t - (a, HTCmd k v) - m (Maybe a1)
#endif

-- Correct 6.2 inferred type (:t)
#if 0
exec :: (Monad m) =
(t - k - v - m a) - t - (t1, HTCmd k v) - m (Maybe a1)
#endif

exec insert ht (i, cmd)
= case cmd of Ins k v - insert ht k v return Nothing

-- Wrong 6.4 inferred type (:t)
#if 0
test :: (Monad m, Num a, Random a, RandomGen g, Random (HTCmd k v)) =
(t - k - v - m a2)
- ([(a, a)] - m t)
- (t - m a1)
- g
- m (a1, [a1])
#endif

-- Correct 6.2 inferred type (:t)
#if 0
test :: (Monad m, Num t, Random a, RandomGen g, Random (HTCmd k v)) =
(t1 - k - v - m a2)
- ([(t, a)] - m t1) - (t1 - m t2) - g - m (t2, [a1])
#endif
test insert fromList toList g = do
ht - fromList ini
rs - mapM (exec insert ht) cmds
l - toList ht
return (l, catMaybes rs)
where
ini = [(1, fst $ random g)]
cmds= [(1, fst $ random g)]

data HashTable a b

fromList:: (Eq key)
= (key - Int32) - [(key, val)]
- IO (HashTable key val)
fromList= undefined

update  :: HashTable key val - key - val - IO Bool
update  = undefined

toList  :: HashTable key val - IO [(key, val)]
toList  = undefined

testHT  :: RandomGen g = g - IO ([(Int, Int)], [(Integer, Maybe Int)])
testHT g= test update (fromList fromIntegral) toList g
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


:i EmptyClass shows a superfluous where

2005-02-26 Thread Remi Turk
Hi,

it's not going to cause World War III, but it does seem to be a
tiny regression since 6.2:

with an empty class, 6.4.20050215 gives:

*Main :i EmptyClass
class EmptyClass a where-- Defined at foo.hs:1:6
   ^

where 6.2.1 gave:

*Main :i EmptyClass
-- EmptyClass is a class, defined at foo.hs:1
class EmptyClass a
   ^

Groeten,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


labeled field update kind-error in ghc 6.4.20050215

2005-02-26 Thread Remi Turk
Hello again,

while trying to get HashTable to work both in IO and in ST I
hit the following probable bug in 6.4.20050215.
6.2.1 does accept it, and the #ifdeffed-out version works in
both. When the typesignature is removed 6.4 does accept it.

Cheers,
Remi

{-# OPTIONS -cpp -fglasgow-exts #-}
module Foo where

data HT (ref :: * - *)
  = HT { kcount :: Int }

#if 1
set_kcount :: Int - HT ref - HT ref
#endif

#if 1
set_kcount kc ht = ht{kcount=kc}
#else
set_kcount kcount (HT _) = (HT kcount)
#endif


foo.hs:12:19:
Couldn't match kind `*' against `* - *'
When matching the kinds of `t :: *' and `ref :: * - *'
  Expected type: HT t
  Inferred type: HT ref
In the record update: ht {kcount = kc}
Failed, modules loaded: none.

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


6.4.20050215: panic: lookupVers1 MHashTable HT{d}

2005-02-26 Thread Remi Turk
Hi,

while trying to modify Data.HashTable to support both IO and ST
without simply copying it, 6.4.20050215 again decided it doesn't
like me:

/tmp/test% touch *.hs
/tmp/test% /var/tmp/ghc/bin/ghc -O -c MHashTable.hs
/tmp/test% /var/tmp/ghc/bin/ghc -O --make CompatHashTable.hs
Chasing modules from: CompatHashTable.hs
Skipping  MHashTable   ( ./MHashTable.hs, ./MHashTable.o )
Compiling CompatHashTable  ( CompatHashTable.hs, CompatHashTable.o )
ghc-6.4.20050215: panic! (the `impossible' happened, GHC version 6.4.20050215):
lookupVers1 MHashTable HT{d}

To trigger it, compilation must actually be performed in two
seperate steps, and the second one must be done using --make.
-O is also a vital ingredient for the panic.

The killing code is attached.

Happy Hacking,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
module CompatHashTable where

import MHashTable (new, HashTable)
import GHC.IOBase (IOArray, IORef)

new' :: IO (HashTable IOArray IORef IO)
new' = new
{-# OPTIONS -fglasgow-exts #-}
module MHashTable ( new, HashTable ) where

import GHC.IOBase   ( IOArray, newIOArray, IORef, newIORef )

class Monad m = MutHash arr ref m | arr - m, ref - m
   , arr - ref, ref - arr where
newMHArray  :: (Int, Int) - a - m (arr Int a)
newMHRef:: a - m (ref a)

instance MutHash IOArray IORef IO where
newMHArray  = newIOArray
newMHRef= newIORef

newtype HashTable arr ref m = HashTable (ref (HT arr ref m))
data HT arr (ref :: * - *) (m :: * - *) = HT { dir :: !(arr Int Int) }

new :: (MutHash arr ref m) = m (HashTable arr ref m)
new = do
  dir - newMHArray (0,42) undefined
  table - newMHRef HT { dir=dir }
  return (HashTable table)
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


ghci `Probable fix' non-exhaustive pattern exception

2005-02-20 Thread Remi Turk
Good evening,

the following says it all:

~% /var/tmp/ghc/bin/ghci /tmp/foo.hs
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 6.4.20050215, for Haskell 
98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base-1.0 ... linking ... done.
Compiling Main ( /tmp/foo.hs, interpreted )

/tmp/foo.hs:64:6:
No instance for (Show c)
  arising from use of `show' at /tmp/foo.hs:64:6-9
Probable fix:*** Exception: typecheck/TcSimplify.lhs:2389:8-82: 
Non-exhaustive patterns in function add_ors

 


The work-in-progress source causing it is attached.

Happy hacking,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}
-- static Peano constructors and numerals

data Zero   = Zero deriving Show
data One= One deriving Show
infixl 9 :@
data (Number a, Digit b) = a :@ b = a :@ b deriving Show

class Digit a
instance Digit Zero
instance Digit One

class Number a
instance Number Zero
instance Number One
instance (Number a, Digit b) = Number (a :@ b)

--- Pretty printing of numbers ---
class PrettyNum a where
prettyNum   :: a - String

instance PrettyNum Zero where
prettyNum _ = 0

instance PrettyNum One where
prettyNum _ = 1

instance (Number a, Digit b, PrettyNum a, PrettyNum b)
  = PrettyNum (a :@ b) where
prettyNum ~(a:@b)
= prettyNum a ++ prettyNum b

--- Digit addition ---
class (Number a, Digit b, Number c)
   = AddDigit a b c | a b - c where
addDigit:: a - b - c
addDigit= undefined

instance Number a = AddDigit a Zero a
instance AddDigit Zero One One
instance AddDigit One One (One:@Zero)
instance Number a = AddDigit (a:@Zero) One (a:@One)
instance AddDigit a One a'
  = AddDigit (a:@One) One (a':@Zero)

--- Addition ---
class (Number a, Number b, Number c)
   = Add a b c | a b - c where
add :: a - b - c
add = undefined

instance Number n = Add n Zero n
instance Add Zero One One
instance Add One One (One:@One)
instance Number n
  = Add (n:@Zero) One (n:@One)
instance AddDigit n One r'
  = Add (n:@One) One (r':@Zero)
instance (Number n1, Digit d1, Number n2, Digit n2
 ,Add n1 n2 nr', AddDigit (d1:@nr') d2 r)
  = Add (n1:@d1) (n2:@d2) r


foo = show $ add (One:@Zero) (One:@One)
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Infix typeconstructors shown as prefix

2005-02-20 Thread Remi Turk
Hi,

with the following definitions

{-# OPTIONS -fglasgow-exts #-}
data a :++: b
class a :--: b

ghci prints the infix type(classe)s as prefix:

*Main :i :++:
data :++: a b   -- Defined at foo.hs:2:7

*Main :i :--:
class :--: a b where-- Defined at foo.hs:3:8

or (a real-world example):

*Main :t fac (One:@Zero:@Zero)
fac (One:@Zero:@Zero) :: :@ (:@ (:@ (:@ One One) Zero) Zero) Zero

Is this a bug, a feature or just Not Implemented Yet(TM)?

Groeten,
Remi

P.S. Are infix class-names a documented extension at all?

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


make install dies due to empty INSTALL_LIBS

2005-02-17 Thread Remi Turk
Hi,

the subject almost already says it. In line 767 of mk/target.mk
from ghc-6.4.20050215, make install dies because INSTALL_LIBS is
  instead of , causing a shell syntax error:

make[1]: Entering directory `/var/tmp/ghc-6.4.20050215/ghc'
for i in  ; do \
^
[snip]
/bin/sh: -c: line 1: syntax error near unexpected token `;'

Greetings,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


compiling GHC with a custom path to GCC

2005-02-17 Thread Remi Turk
Hi,

when compiling the new ghc pre-releases made my gcc 2.95.3 die
with internal compiler error, I tried to compile it with gcc
3.4.3 (or rather, I thought it compiled with 3.4.1, and when that
died, compiled+installed gcc 3.4.3, tried again, say it die again
and only then noticed it was actually still using 2.95.3 ;) but
had quite some difficulty to actually get it to compile with, in
my case, /usr/local/bin/gcc3

When using the following command-line

CC=gcc3 CXX=g++3 nice ./configure --enable-hopengl --prefix=/var/tmp/ghc 
--with-gcc=/usr/local/bin/gcc3

stage1 still used gcc 2.95.3 to compile stage2 (okay, for --with-gcc that's 
documented)

I had to prepend a custom directory with `gcc' a symlink to
`/usr/local/bin/gcc3' to its PATH to be able to compile the thing.

Is there any other/better way?

Groetjes,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: compiling GHC with a custom path to GCC

2005-02-17 Thread Remi Turk
On Thu, Feb 17, 2005 at 04:48:54AM -0700, Seth Kurtzberg wrote:
 Simon Marlow wrote:
 
 On 17 February 2005 11:12, Remi Turk wrote:
 
  
 
 when compiling the new ghc pre-releases made my gcc 2.95.3 die
 with internal compiler error, I tried to compile it with gcc
 3.4.3 (or rather, I thought it compiled with 3.4.1, and when that
 died, compiled+installed gcc 3.4.3, tried again, say it die again
 and only then noticed it was actually still using 2.95.3 ;) but
 had quite some difficulty to actually get it to compile with, in
 my case, /usr/local/bin/gcc3
 
 When using the following command-line
 
 CC=gcc3 CXX=g++3 nice ./configure --enable-hopengl
 --prefix=/var/tmp/ghc --with-gcc=/usr/local/bin/gcc3 
 
 stage1 still used gcc 2.95.3 to compile stage2 (okay, for --with-gcc
 that's documented) 

 
 
 Really?  --with-gcc should set the gcc for stage1, AFAIK.  Is there a
 bug here?
 
 I've noticed gcc 2.95 crashing on my FreeBSD box too.  I should look
 into whether there's a workaround, otherwise we're hosed on FreeBSD 4.x.
  
 
 This is a known problem in all the 3.x compilers, and also occurs, 
 although less often, with 2.9x versions.  I've seen no difference in 
 frequency comparing FreeBSD to Linux and NetBSD.
 
 The only solution, which is of course highly annoying, is to simply 
 restart the make.  For whatever reason this always works, sometimes 
 until the end of the build, and sometimes until some other crash.  My 
 theory is that it is related to the temporary files that gcc creates, 
 mostly for templates. 
 
 While a royal PITA, the resulting code is correct.
 
 Cheers,
  Simon

I'm afraid finding a workaround for compilers dying on
compiler-generated code isn't going to be much fun...

Anyway, I just replaced a
ifneq $(INSTALL_LIBS) 
by
ifneq $(strip $(INSTALL_LIBS)) 
(see my glasgow-haskell-bugs message of today, this usage is
recommended in make's info for strip.)

Now I could install ghc, remove the build-tree and get enough
free space to start compiling again.
This time I'll log everything and come back when I'm sure what
exactly is going on. (As I remember that 1) --with-gcc doesn't
do what it should and 2) the gcc-2.95-crash on linux seems to be
repeatable.)

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: compiling GHC with a custom path to GCC

2005-02-17 Thread Remi Turk
On Thu, Feb 17, 2005 at 05:05:18AM -0700, Seth Kurtzberg wrote:
 Remi Turk wrote:
 I'm afraid finding a workaround for compilers dying on
 compiler-generated code isn't going to be much fun...
 
 Anyway, I just replaced a
ifneq $(INSTALL_LIBS) 
 by
ifneq $(strip $(INSTALL_LIBS)) 
 (see my glasgow-haskell-bugs message of today, this usage is
 recommended in make's info for strip.)
 
 Now I could install ghc, remove the build-tree and get enough
 free space to start compiling again.
 This time I'll log everything and come back when I'm sure what
 exactly is going on. (As I remember that 1) --with-gcc doesn't
 do what it should and 2) the gcc-2.95-crash on linux seems to be
 repeatable.)
 
  
 
 I'm not positive about 2.95, but I know that on 3.x it crashes in 
 different places, and even compiling different source files.  With each 
 3.x release, they fix some of them, but others pop up to take their 
 place.  Clearly the gcc people don't know what's going on.

Sounds like it just was about time to get a C-- backend ;o)

[off-topic] Btw, how bad is it to get Bad eta expand warnings
during compilation of GHC?

Greetings,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: compiling GHC with a custom path to GCC

2005-02-17 Thread Remi Turk
On Thu, Feb 17, 2005 at 11:29:41AM -, Simon Marlow wrote:
 On 17 February 2005 11:12, Remi Turk wrote:
 
  when compiling the new ghc pre-releases made my gcc 2.95.3 die
  with internal compiler error, I tried to compile it with gcc
  3.4.3 (or rather, I thought it compiled with 3.4.1, and when that
  died, compiled+installed gcc 3.4.3, tried again, say it die again
  and only then noticed it was actually still using 2.95.3 ;) but
  had quite some difficulty to actually get it to compile with, in
  my case, /usr/local/bin/gcc3
  
  When using the following command-line
  
  CC=gcc3 CXX=g++3 nice ./configure --enable-hopengl
  --prefix=/var/tmp/ghc --with-gcc=/usr/local/bin/gcc3 
  
  stage1 still used gcc 2.95.3 to compile stage2 (okay, for --with-gcc
  that's documented) 
 
 Really?  --with-gcc should set the gcc for stage1, AFAIK.  Is there a
 bug here?
 
 I've noticed gcc 2.95 crashing on my FreeBSD box too.  I should look
 into whether there's a workaround, otherwise we're hosed on FreeBSD 4.x.
 
 Cheers,
   Simon

I seem to have been mistaken. When configuring with --with-gcc it
does use gcc 3.4.3. I'm letting it continue till completion to be
entirely sure. (As IIRC the compiler-errors came rather late in
the build and it's only compiling for about an hour now.)

I'll try to reproduce the 2.95 internal compiler error later.

Btw, at first I misunderstood the following comment in
docs/building/building.xml to mean that --with-gcc only specified
the compiler for actual .c files in the ghc-distribution. (Which
explains my (okay, for --with-gcc that's documented))

termliteral--with-gcc=parameterpath/parameter/literal
  
indextermprimaryliteral--with-gcc/literal/primary/indexterm
/term
listitem
  paraSpecifies the path to the installed GCC. This
  compiler will be used to compile all C files,
  emphasisexcept/emphasis any generated by the
  installed Haskell compiler, which will have its own
  idea of which C compiler (if any) to use.  The
  default is to use literalgcc/literal./para
/listitem

To be more precisely, to me the installed Haskell compiler was
the (stage[12] of the) Haskell compiler to be installed once
it's compiled.

Groeten,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: compiling GHC with a custom path to GCC

2005-02-17 Thread Remi Turk
[Resent, with a few #ifdef FOO's removed from the body (still in
the attachement, and using gzip instead of bzip2 to prevent
awaiting moderation ;)]

On Thu, Feb 17, 2005 at 11:29:41AM -, Simon Marlow wrote:
 On 17 February 2005 11:12, Remi Turk wrote:
 
  when compiling the new ghc pre-releases made my gcc 2.95.3 die
  with internal compiler error, I tried to compile it with gcc
  3.4.3 (or rather, I thought it compiled with 3.4.1, and when that
  died, compiled+installed gcc 3.4.3, tried again, say it die again
  and only then noticed it was actually still using 2.95.3 ;) but
  had quite some difficulty to actually get it to compile with, in
  my case, /usr/local/bin/gcc3
  
  When using the following command-line
  
  CC=gcc3 CXX=g++3 nice ./configure --enable-hopengl
  --prefix=/var/tmp/ghc --with-gcc=/usr/local/bin/gcc3 
  
  stage1 still used gcc 2.95.3 to compile stage2 (okay, for --with-gcc
  that's documented) 
 
 Really?  --with-gcc should set the gcc for stage1, AFAIK.  Is there a
 bug here?
 
 I've noticed gcc 2.95 crashing on my FreeBSD box too.  I should look
 into whether there's a workaround, otherwise we're hosed on FreeBSD 4.x.
 
 Cheers,
   Simon

In case you've got nothing else left to do.. ;)

The ghc command which perfectly repeatable kills gcc:

make[2]: Entering directory `/var/tmp/ghc-6.4.20050216/ghc/compiler'
../../ghc/compiler/stage1/ghc-inplace -H16m -O  -istage2/utils  
-istage2/basicTypes  -istage2/types  -istage2/hsSyn  -istage2/prelude  
-istage2/rename  -istage2/typecheck  -istage2/deSugar  -istage2/coreSyn  
-istage2/specialise  -istage2/simplCore  -istage2/stranal  -istage2/stgSyn  
-istage2/simplStg  -istage2/codeGen  -istage2/main  -istage2/profiling  
-istage2/parser  -istage2/cprAnalysis  -istage2/compMan  -istage2/ndpFlatten  
-istage2/iface  -istage2/cmm  -istage2/nativeGen  -istage2/ghci -Istage2 -DGHCI 
-package template-haskell -package unix -package readline -DUSE_READLINE 
-package Cabal -cpp -fglasgow-exts -fno-generics -Rghc-timing -I. -IcodeGen 
-InativeGen -Iparser -recomp -Rghc-timing  -H16M '-#include hschooks.h'-c 
cmm/MachOp.hs -o stage2/cmm/MachOp.o  -ohi stage2/cmm/MachOp.hi
/tmp/ghc32662.hc: In function `s5dU_ret':
/tmp/ghc32662.hc:11210: Internal compiler error in `build_insn_chain', at 
global.c:1756

The dying gcc command:

gcc -x c cmm/MachOp.hc -o /tmp/ghc15388.raw_s -DDONT_WANT_WIN32_DLL_SUPPORT 
-fno-defer-pop -fomit-frame-pointer -fno-builtin -DSTOLEN_X86_REGS=4 -S 
-Wimplicit -O -D__GLASGOW_HASKELL__=604 -ffloat-store -I cmm -I stage2 -I . -I 
codeGen -I nativeGen -I parser -I 
/var/tmp/ghc-6.4.20050216/libraries/readline/include -I 
/var/tmp/ghc-6.4.20050216/libraries/unix/include -I 
/var/tmp/ghc-6.4.20050216/libraries/base/include -I 
/var/tmp/ghc-6.4.20050216/ghc/includes

The (naively) relevant part of the generated HC-file appears to
be the next function (with some code which doesn't seem to
matter for the crash removed). I have no idea whether this is of any
help for nailing this kind of nastiness down, so I'm not going to
spend more of my night on it ;)

I did attach the complete failing HC-file.

Greetings,
Remi

// compile The Killing Line
#define BAR 1
IF_(s5dU_ret) {
W_ _c5ec;
FB_
#if BAR
if (_c5ec  0x5) goto _c5en;
#endif
_c5eo:
_c5eu:
R1.p = (P_)(W_)GHCziBase_True_closure;
Sp=Sp+1;
JMP_((*((P_)((*Sp) + (-0x14 + (*Sp));
_c5en:
switch (_c5ec) {
case 0x0: goto _c5eo;
case 0x1: goto _c5eo;
case 0x2: goto _c5eu;
case 0x3: goto _c5eo;
case 0x4: goto _c5eo;
}
FE_
}

-- 
Nobody can be exactly like me. Even I have trouble doing it.


MachOp.hc.bz2
Description: Binary data
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.4 release candidates available

2005-02-16 Thread Remi Turk
On Thu, Feb 10, 2005 at 01:11:48PM -, Simon Marlow wrote:
 We are finally at the release candidate stage for GHC 6.4.  Snapshots
 with versions 6.4.20050209 and later should be considered release
 candidates for 6.4.
 
 Source and Linux binary distributions are avaiable here:
 
   http://www.haskell.org/ghc/dist/stable/dist/
 
 Please test if you're able to, and give us feedback.
 
 Thanks!
 
 Simons  the GHC team

Hi,

I just noticed that in GHC.PArr, productP is defined wrongly

productP :: (Num a) = [:a:] - a
productP  = foldP (*) 0

in (the likely) case that PArr is deprecated, you may want to add
a DEPRECATED-pragma.

Groetjes,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell] sugar for extensible types (was: class associated types, via GADTs.)

2005-02-16 Thread Remi Turk
On Wed, Feb 16, 2005 at 12:38:45PM -, Simon Marlow wrote:
 
 test = do
   x `catch` (\(IOException e)- print e)
 `catch` (\(ArithException e) - print e)

Although slightly off-topic, and though you probably already
realized it, beware that this is comparable to 

try {
try {
x
} catch (IOException e) {
print e
}
} catch (ArithException e) {
print e
}

instead of the usual

try {
x
} catch (IOException e) {
print e
} catch (ArithException e) {
print e
}

which wasn't immediately obvious to me at first.

Groeten,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell-cafe] Showable mutually recursive (fixed-point) datatypes

2005-02-16 Thread Remi Turk
[WARNING: braindamag(ed|ing) experience following]

Hi all,

a few days ago I decided I desperately needed a set which could
contain (among others) itself. My first idea was

 module Main where

 import List
 import Monad

 data Elem s a = V a | R (s (Elem s a))

Now, a self-containing list can be defined as

 l :: [Elem [] Integer]
 l = [V 42, R [V 6, V 7], R l]

As my brain could handle that, and I noticed quite some
similiarity between Elem and Either, I decided to try to abstract
the thing a little. This is what I ultimately came up with

 newtype Comp f g x  = Comp (f (g x))
 newtype Rec f   = In (f (Rec f))

The idea is that `Elem s a' is basically just `Either a (s
SELF)'. Then, instead of defining a special-purpose
mutually-recursive fixed-point type, another type `Comp' is
defined to compose two types into one, to enable the standard
Fix/Mu/Rec type to be used.

 type RecCont s a= s (Either a (RecElem s a))

A recursive container is a container with simple elements
(Left a) and recursive container-elements (Right (RecElem s a))

 type RecElem s a= Rec (Comp s (Either a))

And a recursive container-element is, err, a slightly obscured
recursive container. (s (Either a SELF))

 el  :: a - Either a (RecElem s a)
 el  = Left

 rec :: RecCont s a - Either a (RecElem s a)
 rec = Right . In . Comp

 unRec   :: RecElem s a - RecCont s a
 unRec (In (Comp f)) = f

And indeed, a list (or set, or whatever) which contains itself is
easily defined.

 s :: RecCont [] Integer
 s = [el 42, rec [el 6, el 7], rec s]

The next step was to try to get it an instance of Show. Funny
enough, around that time, Shin-Cheng Mu posed the question of how
to make Rec an instance of Show[1], the (Haskell98) solution of
which I had just found on the HaWiki.[2]

 class RecShow f where
 recShow :: Show a = f a - String

 instance RecShow f = Show (Rec f) where
 show (In f) = (In ( ++ recShow f ++ ))

 instance Show a = RecShow (Either a)  where recShow = show

However, I didn't just want some `Rec f' to be an instance of
Show, I wanted `Rec (Comp f g)' to be an instance of Show.
Which turned out not to be all that easy.

My best solution works, but I hope someone has a better idea...?

 class CompShow f where
 compShow :: (Show a, RecShow g) = f (g a) - String

 instance (CompShow f, RecShow g, Show a) = Show (Comp f g a) where
 show (Comp f)= (Comp ( ++ compShow f ++ ))

 instance CompShow [] where
 compShow l = [ ++ (concat $ intersperse , $ map recShow l) ++ ]

 instance (CompShow f, RecShow g)
 = RecShow (Comp f g)  where recShow = show

Anyway, once this worked I just had to find some use for it ;)

 flatten :: (Monad s, Functor s) = RecCont s a - s a
 flatten = join . fmap (either return (flatten . unRec))

 noI'mNotEvil:: Num a = a - RecCont IO a
 noI'mNotEvil n  = do
 putStrLn $ showString Attempt # $ shows n
  $ : Hi, what's The Answer?
 s - getLine
 return $ if s == 42
 then el n
 else rec (noI'mNotEvil (n+1))

 main = do
   n - flatten (noI'mNotEvil 1)
   if n  1
   then putStrLn Did that really have to take so long?
   else putStrLn Well done!


[1] http://www.haskell.org//pipermail/haskell/2005-February/015325.html
[2] http://www.haskell.org/hawiki/PreludeExts

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] Re: help with some basic code that doesn't work

2005-02-14 Thread Remi Turk
On Mon, Feb 14, 2005 at 02:31:54PM +0900, Shin-Cheng Mu wrote:
 Malcolm Wallace [EMAIL PROTECTED] wrote:
 Just a comment, since a couple of people have made similar statements.
 Haskell will derive Eq for arbitrarily complex types - there is no
 restriction to simple types, whatever they might be.
 
 Now that this topic is brought up...
 
 Occasionally I would need to define recursive datatypes
 using an explicit fixed-point operator, such as:
 
  data Fix f = In (f (Fix f))  deriving (Show, Eq)
  data L a x = Nil | Cons a x  deriving (Show, Eq)
 
 However, Haskell was not able to  derive from Fix f any
 instances.

[snip]
 
 This is rather unsatisfactory, because I would not be able
 to inspect values of type Fix f in the interpreter. Is there
 a way to get around this?
 
 sincerely,
 Shin

Funny this comes up at this time, as Fix was on-topic yesterday
at #haskell. One way to make Fix an instance of Show/Eq is this
(based on http://www.haskell.org/hawiki/PreludeExts, where Fix is
called Rec):

class RecShow f where
recShow :: Show a = f a - String

instance (RecShow f) = Show (Rec f) where
 show (In x) = (In ( ++ recShow x ++ ))
instance   RecShow Maybe   where recShow = show
instance   RecShow []  where recShow = show
instance Show a = RecShow (Either a)  where recShow = show

Happy Hacking,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Remi Turk
On Mon, Feb 14, 2005 at 03:55:01PM +0100, Lennart Augustsson wrote:
 Any definition can be made point free if you have a
 complete combinator base at your disposal, e.g., S and K.
 
 Haskell has K (called const), but lacks S.  S could be
 defined as
   spread f g x = f x (g x)
 
 Given that large set of Haskell prelude functions I would
 not be surprised if spread could already be defined point
 free in Haskell. :)
 
   -- Lennart

I hope this won't be considered cheating...

import Control.Monad.Reader

k :: a - b - a
k = return

s :: (a - r - b) - (a - r) - a - b
s = flip (=) . flip

Greetings,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What is MonadPlus good for?

2005-02-13 Thread Remi Turk
On Sun, Feb 13, 2005 at 08:58:29AM -0500, David Roundy wrote:
 I've been working on a typeclass that derives from MonadPlus which will
 encapsulate certain kinds of IO.  With MonadPlus, you can write monadic
 code with exceptions and everything that may not be executed in the IO
 monad.  You just use fail to throw exceptions, and mplus to catch them.
 
 class MonadPlus m = ReadableDirectory m where
 mInCurrentDirectory :: FilePath - m a - m a
 mGetDirectoryContents :: m [FilePath]
 mReadFilePS :: FilePath - m PackedString
 mReadFilePSs :: FilePath - m [PackedString]
 mReadFilePSs f = linesPS `liftM` mReadFilePS f
 
 One instance of this class is IO, but I can also have instances for
 in-memory data structures (outside the IO monad) or (or example) for
 reading a tarball from disk--which would be a monad that acts within the IO
 monad.

According to http://www.haskell.org/hawiki/MonadPlus (see also
the recent thread about MonadPlus) a MonadPlus instance
should obey m  mzero === mzero, which IO doesn't. IOW, the
MonadPlus instance for IO (defined in Control.Monad.Error)
probably shouldn't be there.

Groeten,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What is MonadPlus good for?

2005-02-13 Thread Remi Turk
On Sun, Feb 13, 2005 at 01:31:56PM -0500, David Roundy wrote:
 On Sun, Feb 13, 2005 at 04:57:46PM +0100, Remi Turk wrote:
  According to http://www.haskell.org/hawiki/MonadPlus (see also
  the recent thread about MonadPlus) a MonadPlus instance
  should obey m  mzero === mzero, which IO doesn't. IOW, the
  MonadPlus instance for IO (defined in Control.Monad.Error)
  probably shouldn't be there.
 
 True.  In the IO monad there are side effects that don't get erased when
 a later action raises an exception as that law would suggest.  But any
 IO-like monad that I'm likely to implement will have the same discrepancy,
 and in any IO code that catches enough exceptions to be bug-free will be
 immune to this issue.
 
 Basically, the issue is that
 
do { writeFile foo bar; writeFile bar foo } `catch`
\_ - putStr Couldn't create file\m
 
 may reach the putStr with or without the file foo existing, and there's
 no way to know whether or not it was created.  But that just means the code
 was written sloppily--that is, if the existence of that foo file is
 important.
 
 In my uses of MonadPlus, I'd have other schemes essentially immitating IO,
 so they'd duplicate this behavior (later errors don't undo earlier
 actions), and well-written functions would depend on that.

But what if `instance MonadPlus IO' disappears from the libraries
some day? (which it should, IMO)

 It might be interesting to write a backtracking IO-like monad which
 obeyed m  mzero === mzero.  I imagine you could do it for something like
 an ACID database, if you define === as meaning has the same final result
 on the database, which of course would only be useful if the database had
 sufficient locking that it couldn't have been read between the original m
 and the later mzero.

You might be interested in the recent STM monad then
(Control.Concurrent.STM in GHC-6.4): `T' for Transactional.
However, though it supports both MonadPlus and exceptions, it
doesn't use MonadPlus for exceptions: It's used for
blocking/retrying a thread/transaction.

I never used it, so I'm not sure whether it makes any sense, but
wouldn't MonadError be a better candidate class to base it upon?

Greetings,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What is MonadPlus good for?

2005-02-13 Thread Remi Turk
On Sun, Feb 13, 2005 at 09:28:18PM +0100, Tomasz Zielonka wrote:
 On Sun, Feb 13, 2005 at 08:06:36PM +0100, Remi Turk wrote:
  You might be interested in the recent STM monad then
  (Control.Concurrent.STM in GHC-6.4): `T' for Transactional.
  However, though it supports both MonadPlus and exceptions, it
  doesn't use MonadPlus for exceptions: It's used for
  blocking/retrying a thread/transaction.
 
 And for non-deterministic choice.
 
 BTW, I have an implementation of STM based entirely on old concurrency
 primitives, which means that it will work in older GHC and probably in
 other Haskell compilers. I am going to put it on my web site, when I get
 one.
 
 Best regards
 Tomasz

Cool :)
Is it actually race/deadlock/othergeneralnastiness-free?
(as the paper claims that e.g. mergeIO :: [IO a] - IO a is
unimplementable in anything built on mutexes and condition
variables.)

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What is MonadPlus good for?

2005-02-13 Thread Remi Turk
On Sun, Feb 13, 2005 at 10:33:06PM +0100, Tomasz Zielonka wrote:
 On Sun, Feb 13, 2005 at 10:25:49PM +0100, Remi Turk wrote:
   BTW, I have an implementation of STM based entirely on old concurrency
   primitives, which means that it will work in older GHC and probably in
   other Haskell compilers. I am going to put it on my web site, when I get
   one.
  
  Cool :)
  Is it actually race/deadlock/othergeneralnastiness-free?
 
 It should be, but there may be bugs of course.
 I know there are some possible space leaks, but that's also fixable.
 
  (as the paper claims that e.g. mergeIO :: [IO a] - IO a is
  unimplementable in anything built on mutexes and condition
  variables.)
 
 My STM monad is not IO, it has the same restrictions as STM in the
 paper. The paper doesn't claim you can't implement mergeSTM :: [STM a]
 - STM a mergeSTM = msum

Ugh, I should've read what I copied...
*nitpick* in the paper merge is defined using foldr1, which
errors when given an empty list, as opposed to msum, which merely
retries.

 Also, the STM in GHC 6.4 is written in C. Do you think that Haskell's 
 IO monad lacks some things needed to write this thing? I can tell you
 there are some problems with types, but they can be solved in a more or
 less standard way.
 
 Best regards
 Tomasz

I don't, though I'm probably not qualified to vote ;)

Groeten,
Remi

P.S. And don't forget to post a link when you put it online.

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What is MonadPlus good for?

2005-02-12 Thread Remi Turk
On Sat, Feb 12, 2005 at 01:08:59PM -0500, Benjamin Pierce wrote:
 I have seen lots of examples that show how it's useful to make some type
 constructor into an instance of Monad.
 
 Where can I find examples showing why it's good to take the trouble to show
 that something is also a MonadPlus?  (I know there are many examples of
 things that *are* MonadPluses; what I want to know is why this is
 interesting. :-)
 
 Thanks,
 
  - Benjamin

As a start, free access to countless general functions as soon as
you define a MonadPlus instance for your datatype. (Errr, `guard'
and `msum', as long as one stays within the Haskell98 standard
libraries ;)

Groeten,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What is MonadPlus good for?

2005-02-12 Thread Remi Turk
On Sat, Feb 12, 2005 at 01:47:06PM -0500, Benjamin Pierce wrote:
  As a start, free access to countless general functions as soon as
  you define a MonadPlus instance for your datatype. (Errr, `guard'
  and `msum', as long as one stays within the Haskell98 standard
  libraries ;)
 
 Yes, those are good examples.  (But I'd still be interested to see some of
 the countless others... :-)
 
 Thanks,
 
 - Benjamin

Network.URI and Data.Generics also define a few functions
which require MonadPlus instances. Can't find anything else right
now. Nor do I know of the (countless? ;)) more theoretical
reasons to define instances.

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Things to avoid (Was: Top 20 ``things'' to know in Haskell)

2005-02-12 Thread Remi Turk
On Fri, Feb 11, 2005 at 11:14:40AM +0100, Henning Thielemann wrote:
 
 On Fri, 11 Feb 2005, Remi Turk wrote:
 
  1) It's talking about the compiler having difficulty with some
 warnings when using guards.
 
 http://www.haskell.org//pipermail/haskell-cafe/2005-January/008290.html

Simon Peyton-Jones wrote in 
http://www.haskell.org//pipermail/haskell-cafe/2005-January/008290.html
 GHC has -fwarn-incomplete-patterns and -fwarn-overlapped-patterns.  But
 the code implementing these checks is old and crufty, and the warnings
 are sometimes a bit wrong -- at least when guards and numeric literals
 are involved.  I think they are accurate when you are just using
 ordinary pattern matching.

Does anyone know nice examples where it goes wrong? (And which
could be added to the wiki.) I found the following case where GHC
wrongly gives two warnings, but 1) it's a rather convoluted
example and 2) it's - in general - probably undecidable anyway
(fromInteger might execute arbitrary code):

data Foo = Foo | Bar deriving (Eq, Show)

instance Num Foo where
fromInteger _ = Foo

f   :: Foo - Bool
f 0 = True
f Bar = False

foo.hs:14:
Warning: Pattern match(es) are overlapped
 In the definition of `f': f Bar = ...

foo.hs:14:
Warning: Pattern match(es) are non-exhaustive
 In the definition of `f':
 Patterns not matched: #x with #x `notElem` [0]
   
BTW, what exactly does this mean?

 f x | odd x  = ...
 | even x = ...
 
 GHC does complain. I would also call it Bad Code,
 but if it's what you mean, _this_ example should be in the
 wiki.
 
 Yes, your example is better.

If no-one complains I'll remove the isPrime-part (which IMO
doesn't demonstrate any guard-problems) and collapse it with the
factorial-example (which does).

  2) foo xs | length xs == 1 = bar (head xs)
 As already said in Don't ask for the length of a list, if you
 don't need it, this usage of length is bad in itself, and
 doesn't really help the argument against patterns IMO.
 
 I have seen it similarly in the example I give below at that page. So I
 found it worth noting that some guards can nicely be replaced by simple
 patterns. More examples are welcome. May be we should replace it by
 
 foo xs | not (null xs) = bar (head xs)
 
 vs.
 
 foo (x:_) = bar x
Done.

 This example might be useful, too:
 
 foo x | x == 0 = blub
 x /= 0 = bla
 
 vs.
 
 foo 0 = blub
 foo _ = bla

I agree, and so did Stephan Hohe, who added the factorial example ;)

  3) the pattern guards extension.
 I have two objections against this one. First, I don't think
 it's a good idea to talk about a non-standard extension like
 pattern guards in a wiki about newbie-problems.
 
 It was given to me as a good example why Guards are invaluable:
  http://www.haskell.org//pipermail/haskell-cafe/2005-January/008320.html

Ouch, that hurts. Though I hope I'm not blaspheming when I say
I'd rather do without if-then-else (which I'm not using all that
often and could easily replace by a function `if') than without
guards.

  P.P.S. Does a piece about Avoid explicit lambda's stand any
 chance of not being removed?
 (Basically about \x y - x + y vs (+), and when it
 gets more complicated it probably deserves a name.)
 
 Nice!
Done too.

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Things to avoid (Was: Top 20 ``things'' to know in Haskell)

2005-02-10 Thread Remi Turk
On Wed, Feb 09, 2005 at 02:54:12PM +0100, Henning Thielemann wrote:
 On Wed, 9 Feb 2005, Henning Thielemann wrote:
  Is there also a Wiki page about things you should avoid?
 
 Since I couldn't find one, I started one on my own:
 
 http://www.haskell.org/hawiki/ThingsToAvoid
 
 I consider 'length', guards and proper recursion anchors.

Oops, I just forgot a comment to my latest update: I added an
example to illustrate the fromInteger-in-a-pattern case.

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Things to avoid (Was: Top 20 ``things'' to know in Haskell)

2005-02-10 Thread Remi Turk
On Wed, Feb 09, 2005 at 02:54:12PM +0100, Henning Thielemann wrote:
 
 On Wed, 9 Feb 2005, Henning Thielemann wrote:
  Is there also a Wiki page about things you should avoid?
 
 Since I couldn't find one, I started one on my own:
 
 http://www.haskell.org/hawiki/ThingsToAvoid
 
 I consider 'length', guards and proper recursion anchors.

Okay, I still definitely have some problems with the part about
guards, and I'm going on bothering you about it because it's The
HaWiki, and not just your site ;)

First of all, I rarely combine multiple-defs with guards, and
even more rarely omit an otherwise- or all-variables-and-no-guard
case, so I may just have avoided all stated problems that way.

Second, I don't have much experience with Haskell-newbies
(besides my own (hopefully) past and the ones on the mailing
lists), so my assumptions about common pitfalls may well be
wrong.

That said, the points I don't agree with:

1) It's talking about the compiler having difficulty with some
   warnings when using guards. In none of the examples given (the
   primes) I got any warnings, and from a quick made up example
   it appears that at least GHC is quite capable of detecting
   non-exhaustive patterns even when combining patterns and
   guards. In case you're talking about something like this:

   f x | odd x  = ...
   | even x = ...

   GHC does complain. I would also call it Bad Code,
   but if it's what you mean, _this_ example should be in the
   wiki. (As in: blahblah, it actually _is_ exhaustive, but in
   general requires solving the halting-problem to prove or
   something like that ;)

   Also, when compiling them (even _without_ optimizations) the
   three examples yield _exactly_ the same code, except for the
   fact that the if-then-else example moves the n == 2
   comparision to the RHS of the expression. This move can just
   as easy be done on the guarded version, which removes any
   difference in generated code/warnings.

2) foo xs | length xs == 1 = bar (head xs)
   As already said in Don't ask for the length of a list, if you
   don't need it, this usage of length is bad in itself, and
   doesn't really help the argument against patterns IMO.

3) the pattern guards extension.
   I have two objections against this one. First, I don't think
   it's a good idea to talk about a non-standard extension like
   pattern guards in a wiki about newbie-problems. (Unless in the
   sense of there are some compiler extensions which you
   probably won't need anytime soon.) Second, it's just horrible
   code: A useless violation of DRY (Don't Repeat Yourself).
   
Groeten,
Remi


P.S.   I _do_ agree with most of the other points ;)

P.P.S. Does a piece about Avoid explicit lambda's stand any
   chance of not being removed?
   (Basically about \x y - x + y vs (+), and when it
   gets more complicated it probably deserves a name.)

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: STM check/MonadPlus

2005-02-07 Thread Remi Turk
On Mon, Feb 07, 2005 at 10:53:36AM -, Simon Peyton-Jones wrote:
 Thanks for the typo.  Yes, for Haskell guys 'guard' is fine; but the
 main audience for the paper is non-haskell folk, so we have to spell out
 the defn.
 
 S

Hm, what about calling it `guard' and adding a footnote saying
that in Haskell its type is actually more general? It smells a
bit like namespace pollution to me right now. (Says he who hasn't
even compiled 6.3 since STM got in ;)

Groetjes,
Remi
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] FiniteMap-like module for unordered keys?

2004-11-10 Thread Remi Turk
Ugh, replying to myself...
Obviously, the following contains a few mistakes...:

On Wed, Nov 10, 2004 at 11:34:32AM +0100, R. Turk wrote:
 {-# OPTIONS -fglasgow-exts #-}
 {- I want a Hashable instance for String ;) -}
 import Data.FiniteMap
 import Data.HashTable (hashInt, hashString)
 import Data.Int (Int32)
 
 class Hashable a where hash :: a - Hash
 instance Hashable Int where hash = hashInt
 instance Hashable String where hash = hashString
 
 type Hash = Int32
 newtype HashTable a b = HT (FiniteMap Hash [b])
newtype HashTable a b = HT (FiniteMap Hash [(a,b)])

 
 emptyHT :: HashTable a b
 emptyHT = HT emptyFM
 
 addToHT :: (Hashable a) = HashTable a b - a - b - HashTable a b
 addToHT (HT m) k v
 = HT $ addToFM_C (flip (++)) m (hash k) [v]
addToHT (HT m) k v
= HT $ addToFM_C (flip (++)) m (hash k) [(k,v)]

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Arrows and Haskell

2004-11-07 Thread Remi Turk
On Sat, Nov 06, 2004 at 11:49:45PM +0100, Peter Simons wrote:
 Plus, powerful abstractions that make the code look simple
 and elegant _always_ come at a price. An Arrow-based stream
 processor that performs the same task as my monadic BlockIO
 library does, for instance, results in a module that has
 half the size the StateT version does. Which is cool. But it
 is, as of now, also 10 times slower than the monadic version
 is. Which is not cool at all.

That's indeed a rather high cost. Although I suspect that a lot
more effort has gone into optimizing Monads than into optimizing
Arrows...

Cheers,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Making MVar and Chan Instances of Typeable

2004-11-05 Thread Remi Turk
On Fri, Nov 05, 2004 at 01:57:53PM +0100, Benjamin Franksen wrote:
 Hello Experts,
 
 I need MVar and Chan to be instances of Typeable. Any hint on how this is most 
 easily done would be greatly appreciated. I could change the libraries and 
 add 'deriving Typeable' but I hesitate to do so.
 
 Cheers,
 Ben

It can be done in Haskell 98 the same way `asTypeOf' is defined
in the Report:

instance Typeable a = Typeable (MVar a) where
typeOf v= mkAppTy (mkTyCon Control.Concurrent.MVar.MVar)
[typeOf (t v)]
where
t   :: a b - b
t   = undefined

Groetjes,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Data.List.partition on infinite lists

2004-10-31 Thread Remi Turk
On Sun, Oct 31, 2004 at 06:37:20PM +0100, Lemming wrote:
 I encountered that the implementation of 'partition' in GHC 6.2.1 fails
 on infinite lists:
 
 partition :: (a - Bool) - [a] - ([a],[a])
 partition p xs = foldr (select p) ([],[]) xs
 
 select p x (ts,fs) | p x   = (x:ts,fs)
| otherwise = (ts, x:fs)

Ah, IIRC one of my very first haskell-posts was about this :)

Actually, AFAICS this isn't just a could-be-better, but a real
Bug(TM). According to The Report the definition is:

partition p xs = (filter p xs, filter (not . p) xs)

which doesn't have any trouble with infinite lists.

 With the following definition we don't have this problem:
 
 partition :: (a - Bool) - [a] - ([a], [a])
 partition _ [] = ([],[])
 partition p (x:xs) =
let (y,z) = partition p xs
in  if p x then (x : y, z)
   else (y, x : z)

Cheers,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: getUserEntryForName weirdness

2004-10-29 Thread Remi Turk
On Fri, Oct 29, 2004 at 06:29:52PM +0200, Peter Simons wrote:
 Is anyone else seeing this on his system?
 
   getUserEntryForName [] = print . userName
   wasabi
 
 wasabi happens to be the last entry in the /etc/passwd
 file, and that is what I get every time I query for an user
 that doesn't exist. The source code promises an exception,
 but I don't get one. 
 
 Peter

Prelude System.Posix.User getUserEntryForName [] = print .  userName
*** Exception: getUserEntryForName: does not exist (No such file
or directory)

linux 2.4.26, ghc 6.2.1, compiled with gcc 3.4.1 IIRC.

Groeten,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Are handles garbage-collected?

2004-10-25 Thread Remi Turk
On Mon, Oct 25, 2004 at 08:46:41AM +0200, Ketil Malde wrote:
 Remi Turk [EMAIL PROTECTED] writes:
 
  IMO, [bracket] does indeed have those same drawbacks. (Although the
  traditional explicit memory management model is alloc/free,
  which is much worse than bracket/withFile)
 
 Isn't bracket more like stack allocated memory?  And most problems
 with explicit memory management related to heap (as you indicate)?

I think you're right. (WRT usage (only): AFAICS even
Foreign.Marshal.Alloc.alloca doesn't actually use the stack.)

  The theoretical solution (and probably _only_ theoretical) is
  implementing a lot of garbage collectors: one for memory, one for
  open files, one for sockets, one for 3D polygon meshes etc etc...
 
 ...or have a number of available file handles that is limited by
 memory? :-)

Would be nice if OSes actually worked that way.
Then again, I don't think _everything_ can be made dependent only
on available memory.

Groetjes,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Are handles garbage-collected?

2004-10-25 Thread Remi Turk
On Mon, Oct 25, 2004 at 02:14:28PM +0100, Simon Marlow wrote:
 On 24 October 2004 20:51, Sven Panne wrote:
 
  IMHO it would be best to use explicit bracketing where possible, and
  hope for the RTS/GC to try its best when one runs out of a given
  resource. Admittedly the current Haskell implementations could be
  improved a little bit in the last respect.
 
 Indeed, GHC could/should try to free up file descriptors when they run
 out.  It's a bit tricky though.
Hm, I'm not sure about the should. Garbage collection is meant
for memory, and anything making that less clear makes people
more likely to depend on incorrect assumptions.
And redefining GC to be a collection of _all_ garbage, instead of
just memory doesn't sound so fantastic either.

 At the moment performGC doesn't actually run any finalizers.  It
 schedules a thread to run the finalizers, and you hope the thread runs
 soon.  So if you're running performGC for the purposes of finalization,
 then almost certainly (performGC  yield) is better.  I've been
 wondering whether having a more synchronous kind of finalizer would be a
 good thing.
Synchronous finalizers seem to be difficult to implement in e.g.
the JVM, so may make a JVM-backend more difficult. (I'm thinking
about how CPython vs Jython go about closing file-handles...
CPython uses (primarily) reference-counting, so files get closed
as soon as they aren't referenced anymore, which lots of people
now depend on. Jython uses Java-GC, so some CPython programs
may suddenly fail...)

 Nevertheless, I agree with the general sentiment on this thread that
 file descriptors shouldn't be treated as a resource in the same way as
 memory.

 Cheers,
   Simon

Groeten,
Remi

P.S. Why do so many people (including me) seem to come to Haskell
 from Python? It can't be just the indentation, can it? ;)

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Are handles garbage-collected?

2004-10-25 Thread Remi Turk
On Mon, Oct 25, 2004 at 09:28:23PM +0200, Tomasz Zielonka wrote:
 On Mon, Oct 25, 2004 at 08:55:46PM +0200, Remi Turk wrote:
  P.S. Why do so many people (including me) seem to come to Haskell
   from Python? It can't be just the indentation, can it? ;)
 
 How many? I don't.
 
 Best regards,
 Tom

At least one. (Me) And, judging from the amount of references to
Python in these mailing-lists, I really doubt I'm the only one.

I actually met Haskell mostly by reading about it in the python
mailinglist/newsgroup. (in e.g. Alex Martelli's posts)

Someone else (who shall remain anonymous. SCNR) wrote:
 Speculation I'm afraid to post:  People are drawn to Python because they
 hear it is a clean language, but slowly find that it's really pretty
 messy internally.  Haskell is beautiful on the outside and the inside.
 :-)

The last sentence I can definitely agree with, but I'm not so
sure Python really is that messy. (Messier-than-Haskell sure, but
messy? ;o)

Groetjes,
Remi

P.S. Hm, it _is_ haskell-cafe, but maybe it's about time for a
 [Off-topic] note? ;)

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Are handles garbage-collected?

2004-10-24 Thread Remi Turk
On Sun, Oct 24, 2004 at 12:19:59PM -0700, Conal Elliott wrote:
 I'm puzzled why explicit bracketing is seen as an acceptable solution.
 It seems to me that bracketing has the same drawbacks as explicit memory
 management, namely that it sometimes retains the resource (e.g., memory
 or file descriptor) longer than necessary (resource leak) and sometimes
 not long enough (potentially disastrous programmer error).  Whether the
 resource is system RAM, file descriptors, video memory, fonts, brushes,
 bitmaps, graphics contexts, 3D polygon meshes, or whatever, I'd like GC
 to track the resource use and free unused resources correctly and
 efficiently.
 
 Cheers,
 
  - Conal

IMO, it does indeed have those same drawbacks. (Although the
traditional explicit memory management model is alloc/free,
which is much worse than bracket/withFile)
However, Garbage Collection is usually based only on memory.
Using GC for file-handle-closing therefore means that one will
close garbage file-handles when memory is getting low, instead of
when file-handles are almost used up...
The theoretical solution (and probably _only_ theoretical) is
implementing a lot of garbage collectors: one for memory, one for
open files, one for sockets, one for 3D polygon meshes etc etc...

Greetings,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Module Initialisation? (was Re: [Haskell] (no subject))

2004-10-17 Thread Remi Turk
On Sun, Oct 17, 2004 at 01:53:22PM +0100, Ben Rudiak-Gould wrote:
[snip]
  Since a lot of the concerns expressed about this seem to centre
  around possible abuse of arbitrary IO operations in these top level
  constructions, maybe the problem could be addressed by insisting
  that a restricted monad was used, call it SafeIO say.
 
 How about (forall s. ST s)?
 
 We can require module init actions to have a type (forall s. ST s a) 
 instead of IO a. The compiler or RTS wraps the actions with stToIO 
 (which is a safe function) before executing them.
 
 Benefits:
 
* It's just as easy as before to allocate global refs (and global 
 mutable arrays).
* It's still possible to perform arbitrary IO actions (e.g. FFI 
 calls), but you have to wrap them in unsafeIOToST -- a good thing since 
 they really are unsafe. unsafeIOToST is much safer than unsafePerformIO 
 when used in this way.
 
 Problems:
 
* stToIO (newSTRef 'x') doesn't have type IO (IORef Char).
 
 This problem can be solved by adopting a reform that I've wanted for a 
 long time anyway: make IO, IORef, etc. aliases for (ST RealWorld), 
 (STRef RealWorld), etc. instead of completely different types. Then 
 stToIO is the identity function and we only need a single set of 
 state-thread functions instead of the parallel IO and ST equivalents 
 that we have currently.

It definitely sounds nice, but is it actually possible to
generalize e.g. MVar from RealWorld to forall s or are we
always going to have to say:

v - unsafeIOToST (newMVar / newChan ... )

GHC's definition:
data MVar a = MVar (MVar# RealWorld a)


-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Module Initialisation? (was Re: [Haskell] (no subject))

2004-10-17 Thread Remi Turk
On Sun, Oct 17, 2004 at 05:11:02PM +0100, Ben Rudiak-Gould wrote:
 Remi Turk wrote:
 
 It definitely sounds nice, but is it actually possible to generalize e.g. 
 MVar from RealWorld to forall s or are we always going to have to say:
 
 v - unsafeIOToST (newMVar / newChan ... )
  
 
 I hadn't thought of that, but I don't think there's any problem with
 
type MVar = STMVar RealWorld
 
newMVar  :: a - ST s (STMVar s a)
withMVar :: STMVar s a - (a - ST s b) - ST s b
...
 
 For that matter it seems like we could (should?) have
 
forkST :: ST s () - ST s (STThreadId s)
forkIO = forkST
 
 and so on.
 
 -- Ben

But what semantics would they have?
It cannot be the normal concurrency as
AFAIK runST is supposed to be deterministic.

Groetjes,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Module Initialisation? (was Re: [Haskell] (no subject))

2004-10-17 Thread Remi Turk
On Sun, Oct 17, 2004 at 07:20:28PM +0100, Ben Rudiak-Gould wrote:
 Remi Turk wrote:
 
  On Sun, Oct 17, 2004 at 05:11:02PM +0100, Ben Rudiak-Gould wrote:
 
  I don't think there's any problem with
 
  type MVar = STMVar RealWorld
 
  newMVar :: a - ST s (STMVar s a)
  withMVar :: STMVar s a - (a - ST s b) - ST s b ...
 
  For that matter it seems like we could (should?) have
 
  forkST :: ST s () - ST s (STThreadId s) forkIO = forkST
 
  But what semantics would they have? It cannot be the normal
  concurrency as AFAIK runST is supposed to be deterministic.
 
 Okay, so I'm being silly. Forget forkST then. But STMVar is still okay, 
 isn't it? The only MVars you could use in a state thread would be those 

I won't ever remind you of your being silly if you tell me about
the current state of your implicit-(parameter|return)-IO story ;)

STMVar does indeed still seem okay, except that I have no idea if
it actually makes any sense outside of IO.
(That is: newSTMVar x = unsafeIOToST (newMVar x) seems a bit
pointless and might be the actual way it needs to be implemented.
Has a vague feeling of being silly too now...)

By the way, I'm still in favour of `type IO a = ST RealWorld a':
It just seems wrong to either let's just make it IO or having
to sprinkle stToIO's around...

 you'd created in the same state thread, and without forkST they can't be 
 accessed in a nondeterministic way. Their presence is pointless, true, 
 but at least not unsafe.
 
 It does seem a bit of a hack, but it still seems preferable to the other 
 alternatives currently on the table (namely unrestricted IO, a new 
 SafeIO, or unsafeIOToST.newMVar).
 
 -- Ben

I'm waiting to be convinced either way ;)

Groetjes,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell-cafe] Subsequence near solved hopefully

2004-10-17 Thread Remi Turk
On Sun, Oct 17, 2004 at 07:16:51AM -0700, Peter Stranney wrote:
 equalString :: String - String - Bool
 equalString [] [] = True
 equalString [] (c':s') = False
 equalString(c:s) [] = False
 equalString(c:s)(c':s') = equalChar c c'^ equalString s s'
   ^^
  
 this function is to see if one string is equal to another.
  
 but when i compile this i get the error;
 - Instance of Integral Bool required for definition of equalString

You are using the raise-to-the-power-of operator, which requires
it's second parameter to be Integral...

(^) :: (Integral b, Num a) = a - b - a

You might also want to look at the earlier `any prefix of tails'
suggestion, as it makes the solution a rather simple one-liner.

Good luck,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Subsequence near solved hopefully

2004-10-17 Thread Remi Turk
On Sun, Oct 17, 2004 at 08:05:09PM +0200, Ketil Malde wrote:
 Remi Turk [EMAIL PROTECTED] writes:
 
  You might also want to look at the earlier `any prefix of tails'
  suggestion, as it makes the solution a rather simple one-liner.
 
 Wouldn't that be looking for a sub*string*, and not a (general)
 sub*sequence* (which I think does not have to be contigous?)

Hm, not substring as in String at least, but that solution does
give the following results:

Prelude List sub ell hello
True
Prelude List sub [3..5] [1..10]
True
Prelude List sub [2,4] [1..5]
False
Prelude List sub [2..6] [1..5]
False

Do you mean subset with subsequence?

Groetjes,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Subsequence near solved hopefully

2004-10-17 Thread Remi Turk
On Sun, Oct 17, 2004 at 11:41:59AM -0700, Peter Stranney wrote:
 Thanks guys for all your help, finally through code, sweat and tears i have found 
 the solution;
  
 isSubStrand:: String - String - Bool
 isSubStrand [] [] = True
 isSubStrand [] (y:ys) = False
 isSubStrand (x:xs) [] = False
 isSubStrand (x:xs) (y:ys)
| length(x:xs)length(y:ys) = False
| take (length (x:xs)) (y:ys)==(x:xs) = True
| otherwise = isSubStrand (x:xs) ys
 
 thanks again
 Peter Stranney

Now that you found it, we might as well tell you the other
solution:

import List

-- Point-free (beware of the monomorphism-restriction)
isSubStrand' :: Eq a = [a] - [a] - Bool
isSubStrand' = flip (.) tails . any . isPrefixOf

-- and point-full
isSubStrand'' x y = any (x`isPrefixOf`) (tails y)

Groetjes,
Remi feeling mean Turk

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Subsequence near solved hopefully

2004-10-17 Thread Remi Turk
On Sun, Oct 17, 2004 at 10:10:44PM +0200, Ketil Malde wrote:
 Remi Turk [EMAIL PROTECTED] writes:
  Do you mean subset with subsequence?
 
 No, since a set isn't ordered.  
 
 I would say a subset needs to contain some of the elements of the
 superset, a subsequence needs to contain some elements of the
 supersequence in the same order, and a substring (for lack of a better
 term) is a contigous subsequence.
 
 But I may be wrong.

Agreeing on terminology is always nice :D

at least http://en.wikipedia.org/wiki/Subsequence seems to agree
with you. In which case both Peter Stranney's and my solutions
fail.

Groetjes,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Subsequence near solved hopefully

2004-10-17 Thread Remi Turk
On Sun, Oct 17, 2004 at 10:53:37PM +0100, Sam Mason wrote:
 Peter Simons wrote:
 This version should do it:
 
 isSubSeq :: (Eq a) = [a] - [a] - Bool
 isSubSeq   [] _= True
 isSubSeq   _ []= False
 isSubSeq (x:xs) (y:ys)
   | x == y= isSubSeq xs ys
  
 
 I think you want to refer to List.isPrefixOf here - your version is a
 sort of ordered subset test.  I.e. I get:
 
abc  `isSubSeq`  .a.b.c.   ===   True

as Ketil pointed out, this subsequence test may be exactly what
the OP meant.

 My version would've been:
 
   isSubSeq x = any (isPrefixOf x) . tails
 
 But Remi beat me to it (and for that I'll never forgive him! :-).
 
   Sam

But I only gave the point-free and the point-wise version: You
did the half-of-a-point version ;) (which I would actually have
used myself too) *ducks and runs*[1]

Groetjes,
Remi


[1] and falls asleep


-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] is $ a no-op?

2004-10-13 Thread Remi Turk
On Wed, Oct 13, 2004 at 01:00:05PM -0400, Jacques Carette wrote:
  -- |Apply list of functions to some value, returning list of results.
  --  It's kind of like an converse map.
  flist :: [a-b] - a - [b]
  flist fs a = map ($ a) fs
 
 I have attempted, unsuccessfully, to write flist above in a point-free
 manner.  Is it possible?
 
 Jacques

Of course it is, but why?

flist = flip (map . flip ($))

Groeten,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell-cafe] puzzle: prove this floorSqrt correct

2004-08-12 Thread Remi Turk
On Thu, Aug 12, 2004 at 06:59:26PM +0200, Christian Sievers wrote:
 [EMAIL PROTECTED] wrote:
 
  -- Here's the discrete version of Newton's method for finding
  -- the square root.  Does it always work?  Any literature?
 
 I recently used, without range check,
 
 sqrtInt n = help n where
 help x = let y = ((x + (n `div` x)) `div` 2)
  in if yx then help y else x
I usually (each time I urgently need to calculate primes ;)) use
a simple intSqrt = floor . sqrt . fromIntegral
(which will indeed give wrong answers for big numbers)

 following p. 38f of Henri Cohen, A Course in Computational Algebraic Number
 Theory, where a proof and a suggestion for improvement (choose a better start
 value) is given.
 Your version should be correct as well.
 
 As far as I know, ghc uses gmp, so I wonder if there is access to functions
 like mpz_sqrt or mpz_perfect_square_p.
there isn't.

And on glasgow-haskell-users there is a thread about (a.o.) that
subject right now :)

Greetings,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] puzzle: prove this floorSqrt correct

2004-08-12 Thread Remi Turk
On Thu, Aug 12, 2004 at 09:01:03PM +0200, Henning Thielemann wrote:
 
 On Thu, 12 Aug 2004, Remi Turk wrote:
  I usually (each time I urgently need to calculate primes ;)) use
  a simple intSqrt = floor . sqrt . fromIntegral
  (which will indeed give wrong answers for big numbers)
 
 If I urgently need factors of an integer I check factor*factor  n
 rather than factor  intSqrt n. :-]

but you'll have to (^2) once every iteration.
The following code only has to sqrt once.
Oh, the joy of premature optimization. Or even premature coding ;)

-- Will lie when given stupid questions
isPrime 1   = False
isPrime 2   = True
isPrime n   = not $ any (n`isDivBy`) (2:[3,5..intSqrt n])
where
n `isDivBy` d   = n `rem` d == 0
intSqrt = floor . sqrt . fromIntegral

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: GHCI/FFI/GMP/Me madness

2004-08-11 Thread Remi Turk
On Wed, Aug 11, 2004 at 02:27:19PM +0100, Simon Marlow wrote:
 On 10 August 2004 16:04, Remi Turk wrote:
  http://www.haskell.org/pipermail/glasgow-haskell-users/2004-June/006767.html
 
 Hmm yes, I now realise that it's not quite as easy as I implied in that
 message.  The problem is the memory allocation.  If a GMP function
 allocates some memory, we have to swizzle the pointer that comes back
 (where swizzle(p) { return p-sizeof(StgArrWords) }).  Unfortunately you
 have to do this without giving the GC a chance to run, and there's no
 way to get this atomicity in plain Haskell+FFI, which is why the primops
 are still necessary.
 
 Perhaps one way to do it would be to define generic Integer primop
 wrappers - i.e. one wrapper for an mpz function that takes two arguments
 and returns one, etc.  The primop implementations already work like
 this, except that the wrappers are CPP macros.  If the wrapper were
 lifted to the level of a primop itself, then you could easily use
 different mpz functions by calling the appropriate primop passing the
 address of the mpz function.

Ah, the shockingly inefficient family of GMP_TAKEx_RETy macros ;)
(I understand the swizzle-talk only partly, so I'll ignore it and
hope my words won't turn out to be utter nonsense..)

But as long as GMP doesn't mind about being abused the way my
most recent util.c does, I can get away with the
mp_set_memory_functions-trick, can't I?
(*Be sure to call `mp_set_memory_functions' only when there are no
active GMP objects allocated using the previous memory functions!
Usually that means calling it before any other GMP function.*,
and using undocumented features)

And with this trick and a ffi GMP-binding implement a working Mpz
datatype.

And when (if?) this is done, drop in a type Mpz = Integer, rip
out all Integer-primops, remove the mp_set_memory_functions-trick
and start benchmarking?
(Conveniently forgetting that fromInteger :: Integer - Integer
most certainly has to stay a primop anyway...)

Or is the rts using Integers in such a way that any (standard
malloc) allocations are forbidden while e.g. (*) :: Integer -
Integer - Integer is running?

 Cheers,   
   Simon

Greetings,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHCI/FFI/GMP/Me madness

2004-08-10 Thread Remi Turk
On Tue, Aug 10, 2004 at 12:59:46PM +0100, Simon Marlow wrote:
 GHC's use of GMP does cause problems if you want to use GMP for your own
 purposes, or if you link with external code that wants to use GMP.  The
 real problem is that GMP has internal state, which means it can't be
 used in a modular way.  But there's not much we can do about that.
 
 Possibilities:
 
   - Rename all the symbols in our GMP to be unique. (sounds hard)
and ugly

   - Replace GMP with something else (someone is working on this, 
 I believe).
Do you have a pointer? It sounds interesting. *see below*

   - try to get two copies of GMP into your program by pre-linking
 the RTS with one copy, then linking the rest of the program
 with the other copy.  I'm being intentionally vague here - I
 feel that this ought to be possible, but it's an ugly hack
 at best.
I'm not sure I share your feelings about that ;) It sounds like
symbol-clash-hell. But quite possibly I'm just being ignorant.

   - reset GMP's memory allocators before calling it from your code,
 and set them back to the RTS allocators afterward.  Slow, but it
 should work.  It doesn't solve the problem properly though: external
 libraries which use GMP are still broken.
It does indeed seem to work, after a quick test. (new util.c attached)

And it does solve _my_ immediate problem: I can surround every
gmp-operation with a gmp_begin()/gmp_end() and pretend to be
happy. (and anyway, I'm just messing around, failure merely means
I've got yet another unfinished project ;))

Part of the reason for all this messy FFIing is your post:
http://www.haskell.org/pipermail/glasgow-haskell-users/2004-June/006767.html

If Integers where implemented via the FFI that would make it
quite a bit easier to special-case e.g. (^) and Show for Integer.
(IIRC, GMP's mpz-to-string recently got a huge speedup, it would
be nice if GHC would automagically profit of that..)

 Cheers,
   Simon
 

Happy hacking  keep up the good work ;)
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHCI/FFI/GMP/Me madness

2004-08-10 Thread Remi Turk
On Tue, Aug 10, 2004 at 01:09:03PM +0100, Simon Marlow wrote:
 On 10 August 2004 13:03, MR K P SCHUPKE wrote:
 
  Re GMP, Why not provide more GMP functions as primitives on the
  Integer type, and avoid the need to call out to GMP via the FFI?
 
 Show us the code! :-p

Or implement Integers via the FFI, and make it much easier to
provide more GMP functions as primitives (that is: simple
foreign imports)

Which is what I was trying, until I bumped into those weird
memory problems I had almost forgotten existed ;)

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


GHCI/FFI/GMP/Me madness

2004-08-09 Thread Remi Turk
Hi all,

I recently tried to create a ffi-binding to gmp in ghc, and
failed miserably. After a few days of debugging, simplifying the
code and tearing my hear out, I'm slightly completely stumped,
and crying for help ;)

In short: calling gmp-functions from GHCI *with a prompt between*
them seems to do Really Bad Things. (read: memory corruption)


The long story:
---

mpz_t p;

str_test()
{
gmp_printf(%Zd\n, p);
}

void mpz_new()
{
mpz_init_set_si(p, 1);
}

foreign import ccall mpz_new:: IO ()
foreign import ccall str_test   :: IO ()


Prelude Main mpz_new
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
1
Prelude Main str_test
142833060
Prelude Main str_test
142833060


Using other flags, importing extra modules, using CVS 6.3 (a few
weeks old) or not compiling it before loading it in GHCI slightly
changes the symptoms (other wrong numbers or make it happen
later/earlier) but copypasting the code from main some 10 to 20
times seems to be a sure way to reproduce it.

Simply running main doesn't seem to expose the problem.
Now of course, GHCI uses Integer-ops during it's REPL, which I
suspect is exactly what causes/exposes the problem.

Am I doing (Un)Officially Forbidden Things? Is it time for a
bug-report? Do I finally have to learn drinking coffee? ;)
I'd be delighted to know.

The full code is attached.

TIA,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
.PHONY: clean ghci

CC=gcc
CFLAGS=-Wall -g
GHCFLAGS=util.o -\#include util.h

main_src=PrimMpz.hs

ghci: util.o
ghci $(GHCFLAGS) $(main_src)

exe: util.o
ghc --make $(GHCFLAGS) $(main_src)

util.o: util.c
$(CC) $(CFLAGS) -c $

clean:
rm -f a.out *.o *.hi
{-# OPTIONS -fffi #-}
module Main where

foreign import ccall mpz_new:: IO ()
foreign import ccall str_test   :: IO ()

main= do
mpz_new
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
str_test
#include stdio.h

#include util.h

mpz_t p;

void str_test()
{
gmp_printf(%Zd\n, p);
}

void mpz_new()
{
mpz_init_set_si(p, 1);
}
#ifndef _UTIL_H
#define _UTIL_H

#include gmp.h

void str_test();
void mpz_new();

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


Re: GHCI/FFI/GMP/Me madness

2004-08-09 Thread Remi Turk
On Sun, Aug 08, 2004 at 07:34:04AM -0700, Sigbjorn Finne wrote:
 Hi,
 
 please be aware that the RTS uses GMP as well, and upon
 initialisation it sets GMP's 'memory functions' to allocate memory
 from the RTS' heap. So, in the code below, the global variable
 'p' will end up having components pointing into the heap.
 Which is fine, until a GC occurs and the pointed-to
 GMP allocated value is eventually stomped on by the storage
 manager for some other purpose.
 
 I'm _guessing_ that's the reason for the behaviour you're seeing.

Hm, I _was_ aware of mp_set_memory_functions being used by the RTS.
I've seen it often enough in ltrace's ;)
It does indeed sound rather plausible (and making big allocations
and such does indeed cause it to happen earlier).

At which point my next question is: what now? I don't feel really
confident about my GHC-hacking skills (huh? skills? where? ;) so
does that mean I'm out of luck?
*looks* Am I correct that I'd have to copy any GMP-allocated
memory to my own memory before returning from C and vice-versa?
I hope not :(

Happy hacking,
Remi 3212th unfinished project Turk

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


  1   2   >