[Haskell-cafe] local loops

2004-12-14 Thread Per Larsson
I often use local loops in monadic code, e.g.

main = do
  ...
 let loop = do 
  ...
  if cond then loop else return () 
 loop

It seems that I can encode this idiom slightly more concise with the 'fix' 
operator (from Control.Monad.Fix), i.e.

main = do
   ...
   fix (\loop - do 
  ...
  if ...)

But is it really semantically equivalent? Is it as efficient? 

Per



  

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


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

2004-12-14 Thread Andres Loeh
 Date: Tue, 14 Dec 2004 10:24:15 -0500
 From: Andrew Pimlott [EMAIL PROTECTED]
 Subject: Re: [Haskell-cafe] The difference between ($) and application
 
 On Tue, Dec 14, 2004 at 11:23:24AM +0100, Henning Thielemann wrote:
  
  On Tue, 14 Dec 2004, Andrew Pimlott wrote:
  
   (Of course, it's still useful, by itself or in a slice, as a higher-order
   operator.)
  
  You can also use 'id' in this cases, right?
 
 I'm thinking of things like
 
 zipWith ($)
 map ($ x)

You can indeed use

zipWith id
map (`id` x)

instead. Look at the types:

id  :: a -  a
($) :: (a - b)  -  (a - b)

The function ($) is the identity function, 
restricted to functions.

Nevertheless, I find using ($) in such a situation 
more descriptive than using id.

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


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

2004-12-14 Thread Marcin 'Qrczak' Kowalczyk
Andres Loeh [EMAIL PROTECTED] writes:

 The function ($) is the identity function, restricted to functions.

Almost. With the standard definition of
   f $ x = f x
it happens that
   ($) undefined `seq` () = ()
   id  undefined `seq` () = undefined

-- 
   __( Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-12-14 Thread Derek Elkins
  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.
 
 I've recently been playing with making, for each class C, a
 interface datatype IC (appropriately universally and existentially
 qualified so as to include a dictionary for class C), and then making
 this IC an instance of class C.  Then I can wrap any instance of C up
 in an IC, and make a list of those.
 
 The casts get a bit annoying, though; the compiler can't figure out
 that this IC is in some sense the maximum type in class C, and so
 can't resolve things like
 
 f :: MyClass a = [a] - b
 f = ...
 
 upcast :: MyClass a = a - IMyClass  -- usually defined as an
 instance of class Cast upcast x = IMyClass x
 
 f [upcast a, upcast b]  -- yields type error
 
 Instead, you have to redefine f as follows:
 
 f' :: [IMyClass] - b
 
 which is a bit annoying.
 
 HTH.
 
 --KW 8-)

Not surprisingly, the wiki
(http://www.haskell.org/hawiki/ExistentialTypes) has some discussion
about this as well, though not too much to add to what has been said.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-12-14 Thread Ben Rudiak-Gould
Derek Elkins wrote:
Andrew Pimlott wrote:
I think this post should go under the heading ($) considered
harmful. I've been bitten by this, and I never use ($) anymore in
place of parentheses because it's too tempting to think of it as
syntax.

I find this position ridiculous. [...] If you ever make a mistake
one way the type checker will tell you.
For what it's worth, this is not true in the presence of implicit 
parameters:

   f :: ((?p :: Int) = Int) - Int
   f g = let ?p = 1 in g
   x,y :: Int
   x = let ?p = 2 in (f ?p)   == 1
   y = let ?p = 2 in (f $ ?p) == 2
I wouldn't mind ($) being magical, along the lines of the magical runST 
in a rank-1 type system. It would be nice to be able to use it in 
patterns too.

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


Re: [Haskell-cafe] Sound library?

2004-12-14 Thread Jeremy Shaw
At Fri, 03 Dec 2004 10:40:45 -0800,
Jeremy Shaw wrote:
 
 At Fri, 03 Dec 2004 10:56:24 -0500,
 Jason Bailey wrote:
  
  
  Would anyone know of packages out there for Haskell that support mp3's 
  or ogg files?
 
 I have some haskell bindings to libmad somewhere ... I don't remember
 how complete they are, but I think i got them to the point that I
 could decode and play an mp3. 

Sorry for the delay, I found a copy of my code that compiles, it is
now online at:

http://www.n-heptane.com/nhlab/

I think it might even work...

Right now I only have a low-level binding, and a sample application
that decodes an mp3. But, the low-level bindings to mad are pretty low
-- there really needs to be a higher level library, but I have not
written one yet ;)

The MadTest stuff is a bit hack-ish and should probably be updated to
use NewBinary.

Jeremy Shaw.
--

This message contains information which may be confidential and privileged. 
Unless you are the 
addressee (or authorized to receive for the addressee), you may not use, copy 
or disclose to anyone 
the message or any information contained in the message. If you have received 
the message in error, 
please advise the sender and delete the message.  Thank you.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-12-14 Thread Andrew Pimlott
On Tue, Dec 14, 2004 at 01:49:57PM -0500, Derek Elkins wrote:
  On Mon, Dec 13, 2004 at 07:49:00PM -0800, oleg at pobox.com wrote:
   The operator ($) is often considered an application operator of a
   lower precedence. Modulo precedence, there seem to be no difference
   between ($) and `the white space', and so one can quickly get used
   to treat these operators as being semantically the same. However,
   they are not the same in all circumstances. I'd like to observe an
   important case where replacing the application with ($) in a
   fully-parenthesized expression can lead to a type error.
  
  I think this post should go under the heading ($) considered
  harmful.
 
 I find this position ridiculous.

By considered harmful, I mean roughly shouldn't be taught to
beginners.  Something that doesn't seem problematic at first, but
almost inevitably leads to trouble.  I think ($) fits this description.

When I first saw the use of ($), I automatically thought of it as
syntax.  When I saw its definition, I thought it was cool that I could
create syntax in this way.  This is a precarious position.  It didn't
bite me for a long time, but when it finally did, it took a while to
figure out what went wrong, and I had to disband an old idea.  To
continue using it when it is safe, I would either have to keep thinking
of it as syntax, which could lead me into another mistake, or repeatedly
verify that it is safe, which would be a drag.  Even if I were happy
with one of those alternatives, I might be setting a trap for anyone
reading my code.  So I think ($) as syntax shoud generally be avoided.

 I don't recall anyone ever posting a
 message about this (though I'd be far from surprised if someone did). 

I believe I first learned about this issue from a posting.  If I hadn't,
I may have had even more trouble diagnosing it when it happened to me!

 It seems that the people who decide they need higher-rank types are
 capable of handling type errors involving them, and they certainly
 don't confuse ($) for syntax.

I doubt that's true.  Applications of higher-rank types are pretty
common, and I think many people start using them without understanding
all the implications.

On Tue, Dec 14, 2004 at 07:27:51PM +, Ben Rudiak-Gould wrote:
 I wouldn't mind ($) being magical, along the lines of the magical runST 
 in a rank-1 type system.

That would be fine.  I like a touch of syntactic sugar when it's pure
sugar.

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


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

2004-12-14 Thread Tom Pledger
[EMAIL PROTECTED] wrote:
[...]
However, if we try
t2' = W $ id
we get an error:
/tmp/t1.hs:13:
   Inferred type is less polymorphic than expected
Quantified type variable `a' escapes
Expected type: (a - a) - b
Inferred type: (forall a1. a1 - a1) - W
   In the first argument of `($)', namely `W'
   In the definition of `t2'': t2' = W $ id
Incidentally, Hugs -98 gives a quite bizarre error message
ERROR /tmp/t1.hs:13 - Use of W requires at least 1 argument
This is also the reason we write
   runST (do ...)
instead of
   runST $ do ...
isn't it?
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] special term describing f :: (Monad m) = (a - m b) ?

2004-12-14 Thread Ralf Hinze
 I can understand how calling this kind of function effectual makes 
 sense in the magic IO monad, or perhaps even in the ST and State 
 monads, because the term seems to imply side-effects.  However, it is a 
 misnomer for eg, the Error, List and Cont monads.

It depends a bit on how wide you interpret the term effectfull.
For me, exceptions or partiality (Error), non-determinisms or
backtracking (List) and continuations (Cont) are certainly effects.

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


[Haskell-cafe] special term describing f :: (Monad m) = (a - m b)?

2004-12-14 Thread Derek Elkins
 What is a function of the followning type called:
 
 f :: (Monad m) = (a - m b) 
 
 Is there a special term describing such a function (a function into a
 monad)?
 
 For f in
 a = f
 is en example.
 
 Need it for an article/report.
 
 Regards/Henning

Well, formally, it's called a Kleisli arrow (or morphism).  A less
formal term commonly used for values of type a - m b and m b, is
'computation' or'action' (though 'action' is usually used for the
specific case of IO). In Notions of Computation and Monads
Moggi calls them 'commands'.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-12-14 Thread Derek Elkins
 Derek Elkins wrote:
  Andrew Pimlott wrote:
  I think this post should go under the heading ($) considered
  harmful. I've been bitten by this, and I never use ($) anymore in
  place of parentheses because it's too tempting to think of it as
  syntax.
  
  I find this position ridiculous. [...] If you ever make a mistake
  one way the type checker will tell you.
 
 For what it's worth, this is not true in the presence of implicit 
 parameters:
 
 f :: ((?p :: Int) = Int) - Int
 f g = let ?p = 1 in g
 
 x,y :: Int
 x = let ?p = 2 in (f ?p)   == 1
 y = let ?p = 2 in (f $ ?p) == 2
 
 I wouldn't mind ($) being magical, along the lines of the magical
 runST in a rank-1 type system. It would be nice to be able to use it
 in patterns too.
 
 -- Ben

Moral of the story, and if I'm not mistaken, in your opinion, is not to
use implicit parameters (as currently formulated).  I.e. the
consensus seems to be that this is implicit parameters' fault not ($)'s.

Personally, I would mind ($) being magical.  One of the nice things
about Haskell is there is practically no magic.  The last thing I want
is Haskerl (http://www.dcs.gla.ac.uk/~partain/haskerl.html).  runST
simply had a rank-2 type that is not expressible in Haskell 98, it seems
getting ($) to work would be qualitatively different.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] local loops

2004-12-14 Thread Jon Cast
Per Larsson [EMAIL PROTECTED] wrote:
 I often use local loops in monadic code, e.g.
 
 main = do
   ...
  let loop = do 
   ...
   if cond then loop else return () 
  loop
 
 It seems that I can encode this idiom slightly more concise with the 'fix' 
 operator (from Control.Monad.Fix), i.e.
 
 main = do
...
fix (\loop - do 
   ...
   if ...)
 
 But is it really semantically equivalent? Is it as efficient? 
 
 Per

It is semantically equivalent.  I don't know if it is as efficient;
looking at the source code, I would expect GHC to inline fix anywhere it
occurs, which yields your original version.

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


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

2004-12-14 Thread Jon Cast

Derek Elkins [EMAIL PROTECTED] wrote:

 Personally, I would mind ($) being magical.  One of the nice things
 about Haskell is there is practically no magic.  The last thing I want
 is Haskerl (http://www.dcs.gla.ac.uk/~partain/haskerl.html).  runST
 simply had a rank-2 type that is not expressible in Haskell 98, it
 seems getting ($) to work would be qualitatively different.

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.

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