Re: [Haskell-cafe] Named function fields vs. type classes

2004-12-15 Thread Keean Schupke
See the HList library (http://www.cwi.ni/~ralf/HList) and use an HList
constrained by your interface.
   Keean.
John Goerzen wrote:
Hi,
I often have a situation where I'm designing specialized components to
do a more general task.   Examples could include mail folder code (maildir,
mbox, etc), configuration file parsing, protocol handlers for URL
accesses, logging backends, etc.
For some of these, I've used a data object with named fields, each one
of them being a function that performs various tasks (open connection to
the URL, read data, whatever.)  So, I get a standard interface.  The
advantage of this approach is that I can build a list containing all
sorts of different data objects in it.
For others, I've used typeclasses, and made the different specialized
components a member of the typeclass.  This seems to provide a cleaner
interface, and one that is more readily extended (maybe I want to
support IMAP folders, and support all its searching capabilities too).
On the other hand, it's difficult or impossible to make a list of a
bunch of different types of things that have nothing in common save
being members of the class.
Is there any advice on the best way to do these things?
Thanks,
John
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
 

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] convergence of functions of Complex variables

2004-12-15 Thread Ross Paterson
On Wed, Dec 15, 2004 at 02:07:10AM -0800, William Lee Irwin III wrote:
 This does not work as expected on Complex numbers due to some odd
 typechecking hassles apparently associated with abs. How do I get this
 to typecheck for both real (e.g. Double) and Complex arguments?

abs :: Num a = a - a, whereas you want something that returns a Double.
You could define

class Norm a where
norm :: a - Double

instance Norm Float where
norm = realToFrac . abs

instance Norm Double where
norm = abs

instance RealFloat a = Norm (Complex a) where
norm = realToFrac . magnitude

and use norm instead of abs.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] convergence of functions of Complex variables

2004-12-15 Thread William Lee Irwin III
On Wed, Dec 15, 2004 at 02:07:10AM -0800, William Lee Irwin III wrote:
 This does not work as expected on Complex numbers due to some odd
 typechecking hassles apparently associated with abs. How do I get this
 to typecheck for both real (e.g. Double) and Complex arguments?

On Wed, Dec 15, 2004 at 10:28:18AM +, Ross Paterson wrote:
 abs :: Num a = a - a, whereas you want something that returns a Double.
 You could define
 class Norm a where
 norm :: a - Double
 instance Norm Float where
 norm = realToFrac . abs
 instance Norm Double where
 norm = abs
 instance RealFloat a = Norm (Complex a) where
 norm = realToFrac . magnitude
 and use norm instead of abs.

Thanks; this appears to do the trick for me. Something of this kind
would be useful to have in the std. libraries, at least for me.


-- wli
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FFI woes!

2004-12-15 Thread David Roundy
On Wed, Dec 15, 2004 at 04:09:04AM +0100, Sebastian Sylvan wrote:
 FMUSIC_MODULE * F_API FMUSIC_LoadSong(
 const char *name
 );
 
 By doing this in Haskell:
 
 data MusicModule = MusicModule
 
 foreign import ccall fmod.h FMUSIC_LoadSong fmusic_LoadSong ::
 CString - IO ForeignPtr MusicModule)
 
 I assume that this is how the ForeignPtr is meant to be used (with a
 dummy data type).

No, a ForeignPtr is a purely haskell object.  The C function returns a
Ptr.  You could create a ForeignPtr from the Ptr if you want it to be
automatically freed (calling somesort of FreeSong, presumably) when it gets
garbage collected.
-- 
David Roundy
http://www.darcs.net
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] convergence of functions of Complex variables

2004-12-15 Thread Jerzy Karczmarczuk
William Lee Irwin III wrote:
This does not work as expected on Complex numbers due to some odd
typechecking hassles apparently associated with abs. ...
Ross Paterson wrote:
 

abs :: Num a = a - a, whereas you want something that returns a Double.
You could define
class Norm a where
   norm :: a - Double
instance Norm Float where
   norm = realToFrac . abs
instance Norm Double where
   norm = abs
instance RealFloat a = Norm (Complex a) where
   norm = realToFrac . magnitude
and use norm instead of abs.
   

Thanks; this appears to do the trick for me. Something of this kind
would be useful to have in the std. libraries, at least for me.
 

Provided you work only with one type for norms, say, Double.
In general, the construction of, say Normed Vector Spaces with
any type for the ('carrier') elements, and any norm compatible
with the elements would require multi-parametric classes.
With dependencies, of course...
Since they are not *so* old, and the numerics in Haskell have
been frozen a long time ago, Haskell libraries from the math
point of view evolve slowly. But people are interested in that, and
the work will continue.
Jerzy Karczmarczuk
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FFI woes!

2004-12-15 Thread Sebastian Sylvan
On Wed, 15 Dec 2004 06:04:37 -0500, David Roundy
[EMAIL PROTECTED] wrote:
 On Wed, Dec 15, 2004 at 04:09:04AM +0100, Sebastian Sylvan wrote:
  FMUSIC_MODULE * F_API FMUSIC_LoadSong(
  const char *name
  );
 
  By doing this in Haskell:
 
  data MusicModule = MusicModule
 
  foreign import ccall fmod.h FMUSIC_LoadSong fmusic_LoadSong ::
  CString - IO ForeignPtr MusicModule)
 
  I assume that this is how the ForeignPtr is meant to be used (with a
  dummy data type).
 
 No, a ForeignPtr is a purely haskell object.  The C function returns a
 Ptr.  You could create a ForeignPtr from the Ptr if you want it to be
 automatically freed (calling somesort of FreeSong, presumably) when it gets
 garbage collected.

Ah. Thanks.

Another problem!
When a handle is not being referenced I don't want it to be garbage
collected if the isPlaying function returns True (in other words I
want the song to finish playing even if it's not being referenced
anymore).

The current plan of attack is to have the finalizer fork off a thread
which does nothing but check the status of the song every 500ms or so
and when it's finished, releases it. But since I really only need to
check it every time the garbage collector wants to release it maybe
there's a better way?
So I want to annotate the ForeignPtr with a function which can defer
it's release based on the status of the handle. Is there a way to do
this?

Sadly the C library doesn't seem to provide a callback for when the
song has finished playing which would be ideal.

/S

-- 
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] convergence of functions of Complex variables

2004-12-15 Thread William Lee Irwin III
This does not work as expected on Complex numbers due to some odd
typechecking hassles apparently associated with abs. How do I get this
to typecheck for both real (e.g. Double) and Complex arguments?

\begin{code}
module Jacobi (sn, cn, dn, sd, cd, nd, cs, ds, ns, sc, dc, nc) where

scd x k | abs k  1e-14 = (sin x, cos x, 1)
| otherwise = ((1+m)*s/(1+m*s^2), c*d/(1+m*s^2),
(1 - m*s^2)/(1+m*s^2))
where
k' = cos $ asin k
m = -tanh(log(k')/2)
(s, c, d) = scd (x/(1+m)) m

sn x k = let (s,_,_) = scd x k in s
cn x k = let (_,c,_) = scd x k in c
dn x k = let (_,_,d) = scd x k in d
sd x k = (sn x k)/(dn x k)
cd x k = (cn x k)/(dn x k)
nd x k = 1/(dn x k)
cs x k = (cn x k)/(sn x k)
ds x k = (dn x k)/(sn x k)
ns x k = 1/(sn x k)
sc x k = (sn x k)/(cn x k)
dc x k = (dn x k)/(cn x k)
nc x k = 1/(cn x k)
\end{code}
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FFI woes!

2004-12-15 Thread David Roundy
On Wed, Dec 15, 2004 at 01:13:19PM +0100, Sebastian Sylvan wrote:
 Another problem!
 When a handle is not being referenced I don't want it to be garbage
 collected if the isPlaying function returns True (in other words I
 want the song to finish playing even if it's not being referenced
 anymore).

 The current plan of attack is to have the finalizer fork off a thread
 which does nothing but check the status of the song every 500ms or so
 and when it's finished, releases it. But since I really only need to
 check it every time the garbage collector wants to release it maybe
 there's a better way?
 So I want to annotate the ForeignPtr with a function which can defer
 it's release based on the status of the handle. Is there a way to do
 this?

If you're going to determine when to release the pointer manually (which is
probably best anyways), then there's no need to mess with a ForeignPtr.
Just stick with a Ptr, and spawn your thread to decide when to fall the
free function.  I presume that you really do want to play the song
asynchronously, rather than just returning when the song is over?

 Sadly the C library doesn't seem to provide a callback for when the
 song has finished playing which would be ideal.

Indeed.
-- 
David Roundy
http://www.darcs.net
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FFI woes!

2004-12-15 Thread Ben Lippmeier
System.Mem.performGC?
Sebastian Sylvan wrote:
Another question!
Is there a way to force the garbage collector to kick in?
I''m trying to find out if my finalizer gets called correctly but I
don't know if the garbage collector is run.
/S

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The difference between ($) and application

2004-12-15 Thread Peter G. Hancock

 Jon Cast wrote (on Tue, 14 Dec 2004 at 22:02):

 No.  All that is needed for ($) to work is impredicativity (or, more
 precisely, for the foralls in ($)'s type to be impredicative).  That is
 something that could easily be implemented in a compiler.  I'm not clear
 on why it hasn't been, but the type system, in relation to an
 arbitrary-rank predicative system, is no more of a jump that higher-rank
 types were.

This sounds interesting and I'd like to understand it. 

* The rank of a type is the nesting depth of quantifiers
  over types, isn't it?  Nested quantifiers can be understood
  either predicatively (with ramified universe types) or impredicatively. 

* ($) is the identity function restricted to functions-in-general ie
  the type FIG = forall a, b . (a - b) - a - b 

You are saying (?) 

* The type of ($) cannot be expressed predicatively.  
  (It seems perfectly expressed by FIG.  But you could
  say that FIG is really (forall a, b :: V_n .   ...)
  which is not a type because it contains a parameter.
  But there is really no parameter, the subscripts are just a way
  of ensuring the formula is properly stratified. 

  Or something to do with ($) being self applicable??

* ?? What we have in implemented type systems is arbitrary-rank
  predicative type quantification. (Strewth!) 

* It would have been easy instead to implement impredicative 
  quantification over types.

Sorry if this is hopelessly wrong. 

Peter Hancock
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] convergence of functions of Complex variables

2004-12-15 Thread Henning Thielemann

On Wed, 15 Dec 2004, William Lee Irwin III wrote:

 On Wed, Dec 15, 2004 at 10:28:18AM +, Ross Paterson wrote:
  abs :: Num a = a - a, whereas you want something that returns a Double.
  You could define
  class Norm a where
  norm :: a - Double
  instance Norm Float where
  norm = realToFrac . abs
  instance Norm Double where
  norm = abs
  instance RealFloat a = Norm (Complex a) where
  norm = realToFrac . magnitude
  and use norm instead of abs.
 
 Thanks; this appears to do the trick for me. Something of this kind
 would be useful to have in the std. libraries, at least for me.

http://cvs.haskell.org/darcs/numericprelude/physunit/Normalization.hs

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parse text difficulty

2004-12-15 Thread Thomas Johnsson
  printastable :: [([Int],Word)] - String
 
  printastable l = concat $ map (\(xs,w) - (show xs) ++   ++ w ++
  \n) l

 I'd use

 [ c | (xs,w) - l, c - (show xs) ++   ++ w ++ \n ]

 instead -- after all, list comprehensions provide a much nicer
 syntax for map, filter and concat.

 I try to stay away from list comprehension because I can't memorize in
 which order the conditions are processed and I have to introduce new
 variables. [..]

I find it helpful to compare list comprehensions to nested loops  ifs
in imperative languages, so that eg

   [ E | v1 - E1, pred2, v3 - E3 ]

'does the same thing as'

   for( v1 - E1 ){
  if( pred2 ){
 for( v3 - E3){
put-elem-in-resulting-list( E )
 }
  }
   }

-- Thomas


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FFI woes!

2004-12-15 Thread Sebastian Sylvan
On Wed, 15 Dec 2004 22:58:53 -0500, Robert Dockins
[EMAIL PROTECTED] wrote:
 On Thu, 2004-12-16 at 01:05 +0100, Sebastian Sylvan wrote:
  Another question!
 
  Is there a way to force the garbage collector to kick in?
 
  I''m trying to find out if my finalizer gets called correctly but I
  don't know if the garbage collector is run.
 
 I'm kind of surprised no one has yet mentioned this, so I will.  Relying
 on finalizers to perform significant clean up actions (ie, anything
 besides memory deallocation) is rather frowned upon.  I think that
 spawing a thread and doing other heavy-duty actions inside a finalizer
 is a bad idea, for several reasons:
 
 1) Finalizers are not (some say cannot) be guaranteed to run, even on
 normal program termination, even if you force GC before exiting.

I only need a guarantee that it will be run if the Ptr is no longer
being referenced.

 2) Finalizers can run when the RTS is in a bizarre state (eg, STDOUT
 might not be avaliable, because it has already been finalized)

Fair enough.



 I would suggest you find some way to accomplish what you want without
 using finalizers.

That would require the user to manually free up resources once they're
not needed anymore. Something which I believe is a bit too low-level
for my tastes.
I basically want the user to be able to just create a sound resource
and then play it, without having to do any book-keeping as to when the
sound resource is not used anymore and can be released.
If there was a way to simply defer GC (like you attatch a function to
an object which can simply deny the GC the right to remove it
depending on its state) then I wouldn't have to do anything
significant in the finalizer. I haven't found a way to do this though,
so the plan is instead to extract the parts of the object which needs
to be kept alive and then keep them alive just long enough to finish
playback and then release them.


/S

-- 
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe