Re: [Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-10-03 Thread Ketil Malde
On Tue, 2007-10-02 at 14:32 -0700, Stefan O'Rear wrote:

 UTF-8 supports CJK languages too.  The only question is efficiency, and
 I believe CJK is still a relatively uncommon case compared to English
 and other Latin-alphabet languages.  (That said, I live in a country all
 of whose dominant languages use the Latin alphabet)

As for space efficiency, I guess the argument could be made that since
an ideogram typically conveys a whole word, it is reasonably to spend
more bits for it.

Anyway, I am unsure if I should take part in this discussion, as I'm not
really dealing with text as such in multiple languages.  Most of my data
is in ASCII, and when they are not, I'm happy to treat it (treat here
meaning mostly ignore) as Latin1 bytes (current ByteString) or UTF-8.
The only thing I miss is the ability to use String syntactic sugar --
but IIUC, that's coming?

However, increased space usage is not acceptable, and I also don't want
any conversion layer which could conceivably modify my data (e.g. by
normalizing or error handling).

-k


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


Re: [Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-10-03 Thread Ketil Malde
On Tue, 2007-10-02 at 21:45 -0400, Brandon S. Allbery KF8NH wrote:

  Due to the additional complexity of handling UTF-8 -- EVEN IF the  
  actual text processed happens all to be US-ASCII -- will UTF-8  
  perhaps be less efficient than UTF-16, or only as fast?

 UTF8 will be very slightly faster in the all-ASCII case, but quickly  
 blows chunks if you have *any* characters that require multibyte.   

What benchmarks are you basing this on?  Doubling your data size is
going to cost you if you are doing simple operations (searching, say),
but I don't see UTF-8 being particularly expensive - somebody (forget
who) implemented UTF-8 on top of ByteString, and IIRC, the benchmarks
numbers didn't change all that much from the regular Char8.

-k


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


[Haskell-cafe] Parsing R5RS Scheme with Parsec

2007-10-03 Thread Pasqualino 'Titto' Assini
Hi Alex,

I hope not to spoil your fun but have you had a look at this:

Write Yourself a Scheme in 48 Hours
http://halogen.note.amherst.edu/~jdtang/scheme_in_48/tutorial/overview.html

Regards,

  titto



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


Re: [Haskell-cafe] Assignment, Substitution or what?

2007-10-03 Thread Jules Bean

PR Stanley wrote:

Yes and thanks for the reply.
When a function is declared in C the argument variable has an address 
somewhere in the memory:

int f ( int x ) {
return x * x;
}

any value passed to f() is assigned to x. x is the identifier for a real 
slot in the memory (the stack most likely) made available for f().

Is this also what happens in Haskell?


It is not, in my opinion, an unreasonable intuition.

What's interesting to note is that because haskell values are immutable, 
there is no need for this to be a *new* memory location. In fact, in a 
typical simple haskell implementation what f is actually passed is a 
pointer to to the existing memory location. Procedure call in haskell 
doesn't normally involve argument copying, because with immutability 
there is no need for copying.


Of course 'x*x' is a new value, so new memory is definitely allocated 
for that.


The next epiphany of understanding is when you realise that what 
actually goes into that new memory is a code pointer, rather than a 
value. Instead of calculating 'x*x' the compiler simply chucks a pointer 
to the code which, when called, will calculate x*x. This code is only 
called if needed.


Jules


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


[Haskell-cafe] GLFW for WinHugs

2007-10-03 Thread Peter Verswyvelen
The latest version of SOE comes with a wrapper for a nice GLFW library. This
library comes with a demo of a 3D bouncing Amiga ball so it must be the
best library in the world ;-) ;-)

 

Since I'm letting my students play with WinHugs, I would prefer to have a
WinHugs compatible version of that library. I tried to convert it, but I got
stuck when ffihugs complained about not finding RTS.h, which seems to be a
GHC-only include file. 

 

Would it be possible to convert this library to WinHugs? I guess similar
work has been done for other libraries, so any hints are welcome.

 

Thanks,

Peter

 

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


[Haskell-cafe] Curry and uncurry

2007-10-03 Thread PR Stanley

Hi
The following is from the Hutton book:

Without looking at the standard prelude, define the
higher-order library function curry that converts a function
on pairs into a curried
function, and conversely, the function uncurry
that converts a curried
function with two arguments into a function on pairs.
Hint: first write down the types of the two functions.

I didn't even know about the curry and uncurry functions. I'm not 
looking for the answer but some guidance would be much appreciated.

Thanks, Paul

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


Re: [Haskell-cafe] Parsing R5RS Scheme with Parsec

2007-10-03 Thread Alex Queiroz
Hallo,

On 10/3/07, Pasqualino 'Titto' Assini [EMAIL PROTECTED] wrote:
 Hi Alex,

 I hope not to spoil your fun but have you had a look at this:

 Write Yourself a Scheme in 48 Hours
 http://halogen.note.amherst.edu/~jdtang/scheme_in_48/tutorial/overview.html


 Yes, I'm actually using it as a basis. But it doesn't parse the
whole R5RS grammar.

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


[Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-10-03 Thread Stephane Bortzmeyer
On Wed, Oct 03, 2007 at 12:01:50AM +0200,
 Twan van Laarhoven [EMAIL PROTECTED] wrote 
 a message of 24 lines which said:

 Lots of people wrote:
  I want a UTF-8 bikeshed!
  No, I want a UTF-16 bikeshed!

Personnally, I want an UTF-32 bikeshed. UTF-16 is as lousy as UTF-8
(for both of them, characters have different sizes, unlike what
happens in UTF-32).
 
 What the heck does it matter what encoding the library uses
 internally? 

+1 It can even use a non-standard encoding scheme if it wants.

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


Re: [Haskell-cafe] Curry and uncurry

2007-10-03 Thread Stuart Cook
On 10/3/07, PR Stanley [EMAIL PROTECTED] wrote:
 Without looking at the standard prelude, define the
 higher-order library function curry that converts a function
 on pairs into a curried
 function, and conversely, the function uncurry
 that converts a curried
 function with two arguments into a function on pairs.

In other words, take a function like[1]

  add a b = a + b

and make the following possible:

  (uncurry add) (2, 3)

Conversely, take a function like

  sub' (a, b) = a - b

and make the following possible:

  (curry sub') 4 1


 Hint: first write down the types of the two functions.

This, I think, is the key part, and it's a useful technique for
Haskell in general.

First, write down the (general) type of a curried function, and the
type of the corresponding uncurried function. Use those types to
figure out what types curry and uncurry should have. Once you've done
that, the implementation (which is pretty straightforward) should
reveal itself.


Stuart

[1] I realise that add is just (+), and sub' is just (uncurry (-)),
and some of my parens are unnecessary; I've written it this way to
make the point of the exercise clearer.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-10-03 Thread Johan Tibell
  What the heck does it matter what encoding the library uses
  internally?

 +1 It can even use a non-standard encoding scheme if it wants.

Sounds good to me. I (think) one of my initial questions was if the
encoding should be visible in the type of the UnicodeString type or
not. My gut feeling is that having the type visible might make it hard
to change the internal representation but I haven't yet got a good
example to prove this.

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


Re: [Haskell-cafe] Curry and uncurry

2007-10-03 Thread Derek Elkins
On Wed, 2007-10-03 at 22:31 +1000, Stuart Cook wrote:
 On 10/3/07, PR Stanley [EMAIL PROTECTED] wrote:
  Without looking at the standard prelude, define the
  higher-order library function curry that converts a function
  on pairs into a curried
  function, and conversely, the function uncurry
  that converts a curried
  function with two arguments into a function on pairs.
 
 In other words, take a function like[1]
 
   add a b = a + b
 
 and make the following possible:
 
   (uncurry add) (2, 3)
 
 Conversely, take a function like
 
   sub' (a, b) = a - b
 
 and make the following possible:
 
   (curry sub') 4 1
 
 
  Hint: first write down the types of the two functions.
 
 This, I think, is the key part, and it's a useful technique for
 Haskell in general.
 
 First, write down the (general) type of a curried function, and the
 type of the corresponding uncurried function. Use those types to
 figure out what types curry and uncurry should have. Once you've done
 that, the implementation (which is pretty straightforward) should
 reveal itself.

Indeed, modulo bottom, the implementation of these functions is
-completely- determined by the types.  Djinn, for example, can
automatically generate the implementations from the types.

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


[Haskell-cafe] with and preserving for local state

2007-10-03 Thread Jules Bean
Lots of external libraries contain state, but one that really contains a 
*lot* of state is the OpenGL libraries, since OpenGL is specified as a 
statemachine.


This means that when you're writing structured code you quite often want 
to save and restore chunks of state 'automatically'. For the very most 
common case (coordinate transformations) Sven gives us 
'preservingMatrix' which is extremely handy. Unless I've missed 
something there's no similar API for saving/restoring arbitrary state 
variables. It's not hard to write:


 {-# OPTIONS -fglasgow-exts #-}
 import Graphics.Rendering.OpenGL
 import Graphics.UI.GLUT

 preserving :: (HasSetter g, HasGetter g) = g a - IO t - IO t
 preserving var act = do old - get var
 ret - act
 var $= old
 return ret


This enables us to write

preserving lighting $ do .

Note that, since IORef is an instance of HasGetter and HasSetter, you 
can do 'preserving' on any old IORef, not just an openGL StateVar.
Also note that the 'makeStateVar' interface that 
Graphics.Rendering.OpenGL.GL.StateVar exports allows you to make a 
statevar out of any appropriate action pair (not entirely unrelated to 
http://twan.home.fmf.nl/blog/haskell/overloading-functional-references.details)



Sometimes you don't only want to preserve a value, but set a specific 
temporary value, so:



 with :: (HasSetter g, HasGetter g) = g a - a - IO t - IO t
 with var val act = do old - get var
   var $= val
   ret - act
   var $= old
   return ret

with lighting Enabled $ do 

(of course, with could be written as

with var val act = preserving var $ var $= val  act
)

But this gets really clumsy if you have multiple variables to 
save/restore, which is really what lead me to write this message in the 
first place. A cute syntax for doing multiple save/restores at once is 
given by an existential:


 data TemporaryValue = forall a g.
   (HasGetter g,HasSetter g) =
   g a := a

 with' :: [TemporaryValue] - IO t - IO t
 with' tvs act = do olds - mapM (\(a := b) - do old - get a
  return (a := old))
   tvs
ret - act
mapM_ (\(a := b) - a $= b) tvs
return ret

so we can then write:

with' [lighting := Enabled, currentColor := Color4 1 0 1 0] $ do ...

and have a type safe list of temporary assignments passed as an 
argument. And, amazingly, you get decent error messages too:


*Main :t with' [lighting := Enabled, currentColor := Color4 1 0 1 0]
with' [lighting := Enabled, currentColor := Color4 1 0 1 0] :: IO t - IO t
*Main :t with' [lighting := Enabled, currentColor := Foo]

interactive:1:44:
Couldn't match expected type `Color4 GLfloat'
   against inferred type `[Char]'
In the second argument of `(:=)', namely `Foo'
In the expression: currentColor := Foo
In the first argument of `with'', namely
`[lighting := Enabled, currentColor := Foo]'


Hope someone else finds that useful,

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


[Haskell-cafe] Hugs, dotnet, C#...

2007-10-03 Thread Peter Verswyvelen

In the (Win)Hugs documentation, I found

Only the ccall, stdcall and *dotnet *calling conventions are supported. 
All others are flagged as errors.


However, I fail to find any more information on how to invoke dotnet 
methods. This might be really handy for me, as I'm very familiar with 
the dotnet framework.


For example, yesterday I rewrote and extended a program that I wanted to 
develop in Haskell in just 3 hours using dotnet, while I spend weeks 
trying do this in Haskell. Of course, I'm a Haskell newbie and a dotnet 
expert, so this is not a fair comparison. However, I got a strange 
feeling, which I want to share with you :) First of all, it was a 
*horrible* experience to program C# again; I needed to type at least 3 
times the amount of code, much of which was boilerplate code, and the 
code is not elegant. Haskell really changed my point of view on this; 
before I knew Haskell, I found C# (I'm talking C# 3.0 here) a really 
neat and nice language. On the other hand, the great Visual Studio IDE 
and Resharper addin made it at least 3 times faster to type, navigate, 
refactor, and debug the code... Somehow, I get things done really really 
really fast in C#, albeit in an ugly way. Once again, I just wish 
Haskell had such an IDE... And yes, I know of the existance of Visual 
Haskell, EclipseFP, Haskell Mode for Emacs (which I'm using), VIM, YI, 
but still, these do not compare with the experience I have when using 
Visual Studio/Resharper (or Eclipse or IntelliJ/IDEA for Java). But that 
might just be me of course...


A slightly frustrated Peter ;-)

BTW: I don't want to bring up the IDE discussion again, no really ;-)


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


Re: [Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-10-03 Thread Jonathan Cast
On Wed, 2007-10-03 at 14:15 +0200, Stephane Bortzmeyer wrote:
 On Wed, Oct 03, 2007 at 12:01:50AM +0200,
  Twan van Laarhoven [EMAIL PROTECTED] wrote 
  a message of 24 lines which said:
 
  Lots of people wrote:
   I want a UTF-8 bikeshed!
   No, I want a UTF-16 bikeshed!
 
 Personnally, I want an UTF-32 bikeshed. UTF-16 is as lousy as UTF-8
 (for both of them, characters have different sizes, unlike what
 happens in UTF-32).

+1

  What the heck does it matter what encoding the library uses
  internally? 
 
 +1 It can even use a non-standard encoding scheme if it wants.

+3

jcc


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


[Haskell-cafe] Haskell FFI and finalizers

2007-10-03 Thread Maxime Henrion
Hello all,



I have recently developed a small set of bindings for a C library, and
encountered a problem that I think could be interesting to others.

My problem was that the C function I was writing bindings to expects to
be passed a FILE *.  So, I had basically two possibles routes to take:

1) Mimic the C API and have the haskell function take a Handle.

Unfortunately, I can see no way to go from a Handle to a Ptr CFile, at
least no portable way, so I discarded this option.

2) Deviate from the C API slightly and have the haskell function take a
FilePath instead of a Handle.

This is the option I chose, and this is where things get interesting.

In order to pass a Ptr CFile (FILE *) to the C function, I had to call
fopen() myself, using a usual FFI binding:

foreign import ccall unsafe fopen
  fopen :: CString - CString - IO (Ptr CFile)

That's the easy part.  Now my problem was that I had to find a way to
automatically close this FILE * when it isn't used anymore, in order not
to leak FILE structures (and thus fds, etc).  A finalizer is typically
what I need, but unfortunately, a finalizer has a very strict shape:

type FinalizerPtr a = FunPtr (Ptr a - IO ())

That is, a finalizer can only be a pointer to a foreign function, and
the foreign function itself needs a quite specific shape.

And then I discovered Foreign.Concurrent, which allows one to associate
a plain Haskell IO action to a pointer.  The 'Foreign.Concurrent' name
is a bit misleading to me; it seems this module is named so because it
needs concurrency itself, rather than providing stuff for concurrency.

So, in the end, I've got this code:

import Foreign
import Foreign.C
import qualified Foreign.Concurrent as FC

...

data PlayerStruct
type Player = ForeignPtr PlayerStruct

...

foreign import ccall unsafe dd_newPlayer_file
  dd_newPlayer_file :: Ptr CFile - Ptr ImageStruct - IO (Ptr PlayerStruct)
foreign import ccall unsafe dd_destroyPlayer
  destroyPlayerFinal :: FunPtr (Ptr PlayerStruct - IO ())

foreign import ccall unsafe fopen
  fopen :: CString - CString - IO (Ptr CFile)
foreign import ccall unsafe fclose
  fclose :: Ptr CFile - IO CInt

...

mkFinalizedPlayer :: Ptr PlayerStruct - IO Player
mkFinalizedPlayer = newForeignPtr destroyPlayerFinal

newPlayerFile :: FilePath - Image - IO Player
newPlayerFile path image = do
  withCString path $ \cpath - do
withCString rb $ \cmode - do
  file - throwErrnoIfNull fopen:  (fopen cpath cmode)
  withForeignPtr image $ \ptr - do
player - dd_newPlayer_file file ptr = mkFinalizedPlayer
FC.addForeignPtrFinalizer player (fclose file  return ())
return player

So I'm adding the usual finalizer, and with the help of
Foreign.Concurrent, I can add a second free-form one (fclose file 
return ()), in order to close the file I opened at an appropriate time.

I'm looking forward hearing about other people's opinions, and wether
this is a correct solution to the initial problem or not.

I think there is another way to solve this, which is to provide the
finalizer still in haskell code, but export the haskell code using FFI,
so that I can use it as a plain, normal finalizer.  I'm still unsure
about this.

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


Re: [Haskell-cafe] Curry and uncurry

2007-10-03 Thread Justin Bailey
On 10/3/07, PR Stanley [EMAIL PROTECTED] wrote:

 I didn't even know about the curry and uncurry functions. I'm not
 looking for the answer but some guidance would be much appreciated.
 Thanks, Paul


You can look at the types without seeing the implementation, too. Just start
up GHCI and type:

  :t curry

or

  :t uncurry

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


Re: [Haskell-cafe] Haskell FFI and finalizers

2007-10-03 Thread Bulat Ziganshin
Hello Maxime,

Wednesday, October 3, 2007, 7:57:58 PM, you wrote:

 And then I discovered Foreign.Concurrent, which allows one to associate
 a plain Haskell IO action to a pointer.  The 'Foreign.Concurrent' name
 is a bit misleading to me; it seems this module is named so because it
 needs concurrency itself, rather than providing stuff for concurrency.

such finalizer cannot be run w/o concurrency support. you can find
explanations in module docs. shortly speaking, finalizing occurs at
time of GC and there is no way to run Haskell code at this moment
except than using another Haskell thread

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Function composition

2007-10-03 Thread Tiago Miguel Laureano Alves

Hi,

I'm playing a little bit with pointfree and function composition and  
I would like to ask you if the following is theoretical correct and  
how can I express it in haskell.


Imagine that I have the following functions
   f :: a - b - c - d
   g :: d - e

I want to compose these two functions such that:
   (g . f) :: a - b - c - e
in which a, b and c are arguments of the composition. Is this  
theoretically correct?


I tried this in haskell and ghc gives me an error saying that the  
function g should be of type b - c - d.
With this I assume that when I specify f :: a - b - c - d I'm  
really specifying f :: a - (b - c - d) and such the composition  
doesn't work, but is it possible to overcome this?


Kind regards,
  Tiago

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


Re: [Haskell-cafe] Haskell FFI and finalizers

2007-10-03 Thread Ryan Ingram
I think you want to use wrapper functions from the FFI:

type HsPlayerFinalizer = Ptr PlayerStruct - IO ()
foreign import ccall wrapper mkPlayerFinalizer :: HsPlayerFinalizer
- IO (FunPtr HsPlayerFinalizer)

You can then make an arbitrary Haskell function (including a partially
applied function with closure state) into a FunPtr.  You call
freeHaskellFunPtr when you are done with the function pointer.

I believe it's safe to do this from the finalizer itself; you can use
something like

mkFinalizerPlayer ptr file = mdo
finalizer - mkPlayerFinalizer (createFinalizer finalizer file)
newForeignPtr finalizer ptr
  where
createFinalizer finalizer file player = do
destroyPlayer player
fclose file
freeHaskellFunPtr finalizer

   -- ryan


On 10/3/07, Maxime Henrion [EMAIL PROTECTED] wrote:
Hello all,



 I have recently developed a small set of bindings for a C library, and
 encountered a problem that I think could be interesting to others.

 My problem was that the C function I was writing bindings to expects to
 be passed a FILE *.  So, I had basically two possibles routes to take:

 1) Mimic the C API and have the haskell function take a Handle.

 Unfortunately, I can see no way to go from a Handle to a Ptr CFile, at
 least no portable way, so I discarded this option.

 2) Deviate from the C API slightly and have the haskell function take a
 FilePath instead of a Handle.

 This is the option I chose, and this is where things get interesting.

 In order to pass a Ptr CFile (FILE *) to the C function, I had to call
 fopen() myself, using a usual FFI binding:

 foreign import ccall unsafe fopen
  fopen :: CString - CString - IO (Ptr CFile)

 That's the easy part.  Now my problem was that I had to find a way to
 automatically close this FILE * when it isn't used anymore, in order not
 to leak FILE structures (and thus fds, etc).  A finalizer is typically
 what I need, but unfortunately, a finalizer has a very strict shape:

 type FinalizerPtr a = FunPtr (Ptr a - IO ())

 That is, a finalizer can only be a pointer to a foreign function, and
 the foreign function itself needs a quite specific shape.

 And then I discovered Foreign.Concurrent, which allows one to associate
 a plain Haskell IO action to a pointer.  The 'Foreign.Concurrent' name
 is a bit misleading to me; it seems this module is named so because it
 needs concurrency itself, rather than providing stuff for concurrency.

 So, in the end, I've got this code:

 import Foreign
 import Foreign.C
 import qualified Foreign.Concurrent as FC

 ...

 data PlayerStruct
 type Player = ForeignPtr PlayerStruct

 ...

 foreign import ccall unsafe dd_newPlayer_file
  dd_newPlayer_file :: Ptr CFile - Ptr ImageStruct - IO (Ptr PlayerStruct)
 foreign import ccall unsafe dd_destroyPlayer
  destroyPlayerFinal :: FunPtr (Ptr PlayerStruct - IO ())

 foreign import ccall unsafe fopen
  fopen :: CString - CString - IO (Ptr CFile)
 foreign import ccall unsafe fclose
  fclose :: Ptr CFile - IO CInt

 ...

 mkFinalizedPlayer :: Ptr PlayerStruct - IO Player
 mkFinalizedPlayer = newForeignPtr destroyPlayerFinal

 newPlayerFile :: FilePath - Image - IO Player
 newPlayerFile path image = do
  withCString path $ \cpath - do
withCString rb $ \cmode - do
  file - throwErrnoIfNull fopen:  (fopen cpath cmode)
  withForeignPtr image $ \ptr - do
player - dd_newPlayer_file file ptr = mkFinalizedPlayer
FC.addForeignPtrFinalizer player (fclose file  return ())
return player

 So I'm adding the usual finalizer, and with the help of
 Foreign.Concurrent, I can add a second free-form one (fclose file 
 return ()), in order to close the file I opened at an appropriate time.

 I'm looking forward hearing about other people's opinions, and wether
 this is a correct solution to the initial problem or not.

 I think there is another way to solve this, which is to provide the
 finalizer still in haskell code, but export the haskell code using FFI,
 so that I can use it as a plain, normal finalizer.  I'm still unsure
 about this.

 Cheers,
 Maxime
 ___
 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: bizarre memory usage with data.binary

2007-10-03 Thread Spencer Janssen
On Tuesday 02 October 2007 19:51:47 Anatoly Yakovenko wrote:
  If its specifically the list instance, where we currently trade laziness
  for efficiency of encoding (which may or may not be the right thing),
  I'd suggest a fully lazy encoding instance?

 Its not really a list, its more of a tree that has shared nodes, so
 something like this:

 A
  / \
 B  C
   \   /
D
  /   \
 EF

 I suspect that maybe after encode/decode i end up with something like

 A
  / \
 B  C
/  \
   D   D
  /   \/   \
 EFE F

That is correct, binary doesn't attempt to share substructures.  If you'd like
to do this, you'll need to do it by hand.


Cheers,
Spencer Janssen

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


Re: [Haskell-cafe] Function composition

2007-10-03 Thread Ryan Ingram
On 10/3/07, Tiago Miguel Laureano Alves [EMAIL PROTECTED] wrote:
 Imagine that I have the following functions
f :: a - b - c - d
g :: d - e

 I want to compose these two functions such that:
(g . f) :: a - b - c - e

Here's a pointfree derivation of the composition function you are talking about:

compose g f a b c = g (f a b c)
 = g ((f a b) c)
 = (g . (f a b)) c
compose g f a b = g . f a b
 = (.) g (f a b)
 = ((.) g) ((f a) b)
 = ((.) g . f a) b
compose g f a = ((.) g) . f a
 = (.) ((.) g) (f a)
 = ((.) ((.) g) . f) a
compose g f = (.) ((.) g) . f
 = (.) (g .) . f
 = ((g .) .) . f

In ghci:
Prelude :set -fglasgow-exts
Prelude :t ((?g .) .) . ?f
((?g .) .) . ?f :: forall b c a a1 a2.
(?g::b - c, ?f::a2 - a1 - a - b) =
a2 - a1 - a - c

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


Re: [Haskell-cafe] Re: bizarre memory usage with data.binary

2007-10-03 Thread Jules Bean

Spencer Janssen wrote:

On Tuesday 02 October 2007 19:51:47 Anatoly Yakovenko wrote:

If its specifically the list instance, where we currently trade laziness
for efficiency of encoding (which may or may not be the right thing),
I'd suggest a fully lazy encoding instance?

Its not really a list, its more of a tree that has shared nodes, so
something like this:

A
 / \
B  C
  \   /
   D
 /   \
EF

I suspect that maybe after encode/decode i end up with something like

A
 / \
B  C
   /  \
  D   D
 /   \/   \
EFE F


That is correct, binary doesn't attempt to share substructures.  If you'd like
to do this, you'll need to do it by hand.


...and indeed it can't be done, except by the naive brute-force method 
of comparing every subtree, possibly optimised by cryptographically 
hashing a representation of every subtree, since sharing isn't an 
observable property.


Of course, hashing doesn't actually observe the real sharing present, 
rather, it computes maximal sharing. There are some applications where 
this could be a worthwhile win.


Jules

PS Well, except unsafePtrEquality but I don't really want to go there...

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


Re: [Haskell-cafe] Function composition

2007-10-03 Thread Jorge Marques Pelizzoni

Here is a generalized version, using type classes and some extensions.
Tiago, in order to compile this you'll have to use:

-fglasgow-exts -fallow-undecidable-instances -fallow-overlapping-instances

Cheers,

Jorge.

-
module Main where

class Pipeline t1 t2 t3 | t1 t2 - t3 where
pipeline::t1 - t2 - t3

instance Pipeline t1 t2 t3 = Pipeline (a - t1) t2 (a - t3) where
pipeline f g a = pipeline (f a) g
-- same as: pipeline f g = \a - pipeline (f a) g

instance Pipeline (a - b) (b - c) (a - c) where
pipeline = flip (.)

f a b c = even (a+b+c)

h = pipeline f not

main = do
putStrLn . show $ h 1 2 3



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


Re: [Haskell-cafe] Haskell FFI and finalizers

2007-10-03 Thread Stefan O'Rear
On Wed, Oct 03, 2007 at 05:57:58PM +0200, Maxime Henrion wrote:
 I have recently developed a small set of bindings for a C library, and
 encountered a problem that I think could be interesting to others.
 
 My problem was that the C function I was writing bindings to expects to
 be passed a FILE *.  So, I had basically two possibles routes to take:

 That's the easy part.  Now my problem was that I had to find a way to
 automatically close this FILE * when it isn't used anymore, in order not
 to leak FILE structures (and thus fds, etc).  A finalizer is typically
 what I need, but unfortunately, a finalizer has a very strict shape:
 
 type FinalizerPtr a = FunPtr (Ptr a - IO ())
 
 That is, a finalizer can only be a pointer to a foreign function, and
 the foreign function itself needs a quite specific shape.
 
 And then I discovered Foreign.Concurrent, which allows one to associate
 a plain Haskell IO action to a pointer.  The 'Foreign.Concurrent' name
 is a bit misleading to me; it seems this module is named so because it
 needs concurrency itself, rather than providing stuff for concurrency.

NOOO!  Foreign.Concurrent, as its name implies, works by forking
threads, and it should be avoided at almost any cost.  The correct
solution is:

void close_file_finalizer(FILE *file) {
if (fclose(file)  0) {
/* do something sensible here */
}
}

 I think there is another way to solve this, which is to provide the
 finalizer still in haskell code, but export the haskell code using FFI,
 so that I can use it as a plain, normal finalizer.  I'm still unsure
 about this.

Calling Haskell code from the garbage collector is essentially
impossible to do efficiently and correctly.  Don't even try it, your
sanity is not worth saving 3 lines of C coding.

Stefan


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


[Haskell-cafe] GHC doesn't work

2007-10-03 Thread Andrew Coppin

Greetings.

I have a PC that had GHC 6.6 running on it. Worked fine. Then I 
uninstalled 6.6 and installed 6.6.1, and now it doesn't appear to work 
at all. Any attempt to run GHC results in a message that says


 The entry point OpenThread could not be found in KERNEL32.dll.

or something very similar to that.

Is this likely to be because GHC 6.6.1 doesn't support Windows NT, or 
because my PC is messed up?


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


[Haskell-cafe] Why not assign a type to unsafePerformIO?

2007-10-03 Thread Justin Bailey
One of the holes in real-world Haskell is you never know if a
library/function is calling unsafePerformIO and you have to trust the
library author. I recognize the necessity of the function, but should it
announce itself? unsafePerformIO has this type:

  unsafePerformIO :: IO a - a

Would there be any value to making it have a type that can be stripped off,
like some other monads? For example, providing a runUnsafe or similar:

  data UnsafePerformIO a = Unsafe a

  runUnsafe :: UnsafePerformIO a - a
  runUnsafe (Unsafe o) = o

and changing unsafePerformIO to have the type:

  unsafePerformIO :: IO a - UnsafePerformIO a

It seems it would be valuable to have functions announce when they use
unsafePerformIO, but additionally allow it to be stripped off. So the
classic

  launchMissiles :: a -- Uses unsafePerfomIO!

Would become

  launchMissiles :: UnsafePerformIO a

Which could be stripped off it you wanted:

  evilDictatator :: a
  evilDictator = runUnsafe $ launchMissiles

But doesn't have to be:

  incompetentDictator :: a
  incompetentDictator = launchMissiles -- Doesn't type check!

I doubt this is original - does it buy anything?

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


Re: [Haskell-cafe] Re: bizarre memory usage with data.binary

2007-10-03 Thread Anatoly Yakovenko
 ...and indeed it can't be done, except by the naive brute-force method
 of comparing every subtree, possibly optimized by cryptographically
 hashing a representation of every subtree, since sharing isn't an
 observable property.

i was thinking that instead of having a reference to a node, each node
just holds an index from an array of nodes.  Traversal would take an
extra step, but it should fix the problem with encode/decode.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why not assign a type to unsafePerformIO?

2007-10-03 Thread Justin Bailey
On 10/3/07, Victor Nazarov [EMAIL PROTECTED] wrote:

 But how would you know that evil dictator uses unsafePerformIO???


You don't. unsafePerformIO  can't be taken it away (there are legitimate
reasons to strip IO), which is why I wonder if it's useful at all.

p.s. CC'ed to haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why not assign a type to unsafePerformIO?

2007-10-03 Thread Jonathan Cast
On Wed, 2007-10-03 at 14:47 -0700, Justin Bailey wrote:
 One of the holes in real-world Haskell is you never know if a
 library/function is calling unsafePerformIO and you have to trust the
 library author. I recognize the necessity of the function, but should
 it announce itself? unsafePerformIO has this type:
 
   unsafePerformIO :: IO a - a
 
 Would there be any value to making it have a type that can be stripped
 off, like some other monads? For example, providing a runUnsafe or
 similar: 
 
   data UnsafePerformIO a = Unsafe a 
 
   runUnsafe :: UnsafePerformIO a - a
   runUnsafe (Unsafe o) = o
 
 and changing unsafePerformIO to have the type:
 
   unsafePerformIO :: IO a - UnsafePerformIO a 
 
 It seems it would be valuable to have functions announce when they use
 unsafePerformIO, but additionally allow it to be stripped off. So the
 classic
 
   launchMissiles :: a -- Uses unsafePerfomIO!
 
 Would become 
 
   launchMissiles :: UnsafePerformIO a 
 
 Which could be stripped off it you wanted:
 
   evilDictatator :: a
   evilDictator = runUnsafe $ launchMissiles
 
 But doesn't have to be:
 
   incompetentDictator :: a 
   incompetentDictator = launchMissiles -- Doesn't type check!
 
 I doubt this is original - does it buy anything? 
 
This already exists.  The monad is called IO, the unsafePerformIO
implementation is called id, and runUnsafe is called unsafePerformIO.  I
really don't see how another set of aliases buys anything.

jcc


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


Re: [Haskell-cafe] Haskell FFI and finalizers

2007-10-03 Thread Maxime Henrion
Stefan O'Rear wrote:
 On Wed, Oct 03, 2007 at 05:57:58PM +0200, Maxime Henrion wrote:
  I have recently developed a small set of bindings for a C library, and
  encountered a problem that I think could be interesting to others.
  
  My problem was that the C function I was writing bindings to expects to
  be passed a FILE *.  So, I had basically two possibles routes to take:
 
  That's the easy part.  Now my problem was that I had to find a way to
  automatically close this FILE * when it isn't used anymore, in order not
  to leak FILE structures (and thus fds, etc).  A finalizer is typically
  what I need, but unfortunately, a finalizer has a very strict shape:
  
  type FinalizerPtr a = FunPtr (Ptr a - IO ())
  
  That is, a finalizer can only be a pointer to a foreign function, and
  the foreign function itself needs a quite specific shape.
  
  And then I discovered Foreign.Concurrent, which allows one to associate
  a plain Haskell IO action to a pointer.  The 'Foreign.Concurrent' name
  is a bit misleading to me; it seems this module is named so because it
  needs concurrency itself, rather than providing stuff for concurrency.
 
 NOOO!  Foreign.Concurrent, as its name implies, works by forking
 threads, and it should be avoided at almost any cost.  The correct
 solution is:
 
 void close_file_finalizer(FILE *file) {
 if (fclose(file)  0) {
 /* do something sensible here */
 }
 }

That wouldn't work; my problem is that this finalizer for closing the
FILE * needs to be called when another pointer gets garbage collected.
This is because I'm opening the file in order to pass to some function
which creates an objet and returns it to me.

To parody the situation:

struct foo *foo_new(FILE *);
void foo_destroy(struct foo *);

When writing the binding for foo_new(), I need to open a file with
fopen() to pass it the FILE *.  Then I get a struct foo * that I can
easily associate the the foo_destroy() finalizer.  However, when
finalizing the struct foo * object, I want to also close the FILE *
handle.

If I write a small C function for doing the finalizer myself, I still
wouldn't get passed the FILE * to close, only the struct foo * pointer
which is of no use.

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


Re: [Haskell-cafe] Why not assign a type to unsafePerformIO?

2007-10-03 Thread Victor Nazarov
On 10/4/07, Justin Bailey [EMAIL PROTECTED] wrote:
 On 10/3/07, Victor Nazarov [EMAIL PROTECTED] wrote:
  But how would you know that evil dictator uses unsafePerformIO???

 You don't. unsafePerformIO  can't be taken it away (there are legitimate
 reasons to strip IO), which is why I wonder if it's useful at all.

 p.s. CC'ed to haskell-cafe


May be you should be interested in Tom Mortel's example of using
unsafeInterleaveIO:
http://blog.moertel.com/articles/2007/03/28/directory-tree-printing-in-haskell-part-three-lazy-i-o

If you don't mean anything like this, I don't understand your intent.

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


Re: [Haskell-cafe] Haskell FFI and finalizers

2007-10-03 Thread Stefan O'Rear
On Thu, Oct 04, 2007 at 12:55:41AM +0200, Maxime Henrion wrote:
 When writing the binding for foo_new(), I need to open a file with
 fopen() to pass it the FILE *.  Then I get a struct foo * that I can
 easily associate the the foo_destroy() finalizer.  However, when
 finalizing the struct foo * object, I want to also close the FILE *
 handle.
 
 If I write a small C function for doing the finalizer myself, I still
 wouldn't get passed the FILE * to close, only the struct foo * pointer
 which is of no use.

Ah, yes, this does make the situation more interesting.

Looks like newForeignPtrEnv is maybe what you want?

Stefan


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


[Haskell-cafe] The Exp - Term a problem (again), how to dynamically create (polymorphic) typed terms in Haskell ??

2007-10-03 Thread Pasqualino 'Titto' Assini
Hi, 

I am trying to write an interpreter for a little functional language but I am 
finding very problematic to dynamically create a typed representations of the 
language terms.
 
I have googled around and found a few solutions but none seem to solve the 
problem.
 

This is the example code: 

 {-# OPTIONS -fglasgow-exts #-}
 module Eval where 

These are my untyped terms (what I get from my parser):

 data Exp =  EDouble Double | EString String | EPrim String | EApp Exp Exp 
deriving (Show)

And these are the typed terms:

 data Term a where
   Num :: Double - Term Double
   Str :: String - Term String
   App :: Term (a-b) - Term a - Term b
   Fun :: (a-b) - Term (a-b)  

The problem is to write a function that converts between Exp and Term t as in:

 test :: Term Double
 test = typecheck $ EApp (EPrim inc) (EDouble 10.0)

So this is the conversion function:

 class TypeCheck t where
typecheck :: Exp - Term t

A few primitives:

 instance TypeCheck (String-String) where
typecheck (EPrim rev)  = Fun reverse
typecheck (EPrim show)  = Fun show  

 instance TypeCheck (Double-Double) where
typecheck (EPrim inc)   = Fun ((+1) :: Double - Double) 

 instance TypeCheck (Double-String) where
typecheck (EPrim show)  = Fun show  

 instance TypeCheck Double where
typecheck (EDouble x) = Num x 

 instance TypeCheck String where
typecheck (EString x) = Str x

The problem arises in the conversion of the function application (EApp). 

It does not seem to be possible to define typecheck on EApp in a generic way
and is also not possible to distinguish between the different cases:  

typecheck (EApp f a) = App (typecheck f :: Term (String-String)) 
(typecheck a:: Term String)

The following pattern overlaps the previous one:

typecheck (EApp f a) = App (typecheck f :: Term (Double-String)) 
(typecheck a:: Term Double)


To avoid this problem I could split my untyped terms in different data types 
as in:

data EDouble = EDouble Double
data App a b c = App a b c 
...

and define TypeCheck separetely on every data type.

However, in that case what would be the type of my parser??

parser :: String - ?? 


Any suggestion woud be very welcome indeed,

   titto






 








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


[Haskell-cafe] Space and time leaks

2007-10-03 Thread Ronald Guida

I need some help with space and time leaks.

I know of two types of space leak.  The first type of leak occurs when
a function uses unnecessary stack or heap space.

GHCi sum [1..10^6]
*** Exception: stack overflow

Apparently, the default definition for sum has a space leak.
I can define my own sum in terms of strict foldl ...

 sum' xs = foldl' (+) 0 xs

... and it doesn't overflow the stack.

GHCi sum' [1..10^6]
5050
(0.27 secs, 112403416 bytes)

GHCi sum' [1..10^7]
500500
(2.73 secs, 1161223384 bytes)

GHCi sum' [1..10^8]
50005000
(27.83 secs, 11645261144 bytes)

I think there's still a space leak; I don't understand why GHCi using
10^8, 10^9, 10^10 bytes of memory for these calculations.

The other type of space leak I know of is when I have a chunk of data
in memory that I no longer need, such that the data is still being
referenced somewhere.  Since, in theory, I might still access the
data, the garbage collector can't reclaim the memory.  I'm not sure
how to construct an example though.

Regarding time leaks, I only know of one kind of leak.  If I have a
calculation that accumulates data over time, and I don't ask for any
results until the end, then, due to laziness, that calculation might
accumulate a chain of unevaluated thunks.  When I get the the end and
demand the final result, I have to wait for it while the RTS
evaluates a long chain of thunks.

The chain of unevaluated thunks is a space leak.  The time leak occurs
because the capture process and the accumulate process are supposed to
be interleaved, such that I perform some computations after I capture
each piece of data.  If I have to wait around at the end, then it
means the capture process and the accumulate process happened in
sequence.

As far as I know, every time leak has a companion space leak; it's not
possible to create a time leak without a space leak to go with it.  Is
this really true?

Now for the hard questions.
1. How do I go about detecting space and time leaks?
2. Once I find a leak, how do I fix it?
3. Are there any programming techniques I can use to avoid leaks?

-- Ron

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