Re: [Haskell-cafe] How to understand `|` in this code snippet ?

2010-02-27 Thread Lee Duhem
On Sat, Feb 27, 2010 at 5:07 PM, zaxis z_a...@163.com wrote:

 xxxMain = do
    timeout - getEnv xxx_TIMEOUT
    case timeout of
        Just str | [(t, _)] - reads str - do
            addTimeout t (hPutStrLn stderr *** TIMEOUT  _exit 1)
            return ()
        _ - return ()
 ...

 What does the `|` mean in Just str | [(t, _)] - reads str ?
 Is it a logical `or` ?

It's part of a case expression, see
http://www.haskell.org/onlinereport/exps.html#sect3.13

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


Re: [Haskell-cafe] A Reader Monad Tutorial

2009-06-28 Thread Lee Duhem
On Sun, Jun 28, 2009 at 12:41 AM, Henry Laxennadine.and.he...@pobox.com wrote:
 Dear Group,

 If any of you are struggling with understanding monads, I've tried to put
 together a pretty through explanation of what is behind the Reader monad.  If
 you're interested, have a look at:

 http://www.maztravel.com/haskell/readerMonad.html


Nice post.

I didn't find how to add comments on your blog, so I post them here:

Areas of Confusion

  1. What is the relationship between the Reader on the left hand side of the 
 equals sign in the newtype definition and the Reader on the right hand side?
   2. Why is there a Record field on the right hand side?
   3. What is that r - a doing there?

1) Reader on the left hand side be called a type constructor, Reader
on the right hand side be called a data constructor,
in Haskell 98 Report. You call them type definition and instance
constructor, respectively, I'm not sure it's a good idea, or
it is right.

bug in the explanation:
what you use to make something and instance of a Reader (left hand side)
- what you use to make something an instance of a Reader (left hand side)

2) runReader be called a selector function in Haskell 98 Report.

3) (-) is a type constructor, so r - a is  a function type.

I used found 'instance Monad ((-) r)' hard to understand, but by
follow the hit given by Brent Yorgey, i.e. the data constructor for
type constructor (-) is called lambda abstraction, I found I can
understand them by type inference. I have written a post about how I
figure
it out, maybe you want take a look:
http://leeduhem.wordpress.com/2009/06/07/understanding-monad-instance-by-type-inference/

bug in the explanation after  (Reader f1) = f2  = Reader $ \e -
runReader (Reader b) e:
Reader b is a function that takes and e and returns a c,
- Reader b is a function that takes an e and returns a c,

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


Re: [Haskell-cafe] Re: Need some help with an infinite list - Ouch

2009-06-18 Thread Lee Duhem
On Wed, Jun 17, 2009 at 7:30 PM, GüŸnther Schmidtgue.schm...@web.de wrote:
 Hi all,

 you have come up with so many solutions it's embarrassing to admit that I
 didn't come up with even one.

I have the similarly difficulties, but I found to understand some of
these answers,
equational reasoning is a very useful tool, I have prepared a blog post for how
I worked out some of these answers, here is the draft of it, I hope it
can help you
too.

Oh, if it doesn't help you at all, please let know why :-)

lee



Understanding Functions Which Use 'instance Monad []' by Equational Reasoning

GüŸnther Schmidt asked in Haskell-Cafe how to get a stream like this:

[a, ... , z, aa, ... , az, ba, ... , bz, ... ]

and people in Haskell-Cafe offer some interesting answer for this question.
On the one hand, these answers show the power of Haskell and GHC base libraries,
but on the other hand, understanding them is a challenge for Haskell
newbie like me.
But I found to understand these answers, equational reasoning is very helpful,
here is why I think so.

Answer 1 (by Matthew Brecknell):

concat $ tail $ iterate (map (:) ['a' .. 'z'] *) [[]]

Well, how does this expression do what we want? concat, tail, iterate,
map, are easy,
looks like the magic is in (*).

What's this operator mean? (*) comes from class Applicative of
Control.Applicative,

class Functor f = Applicative f where
-- | Lift a value.
pure :: a - f a

-- | Sequential application.
(*) :: f (a - b) - f a - f b

and 'instance Applicative []' is

instance Applicative [] where
pure = return
(*) = ap

ap comes from Control.Monad

ap :: (Monad m) = m (a - b) - m a - m b
ap =  liftM2 id

liftM2  :: (Monad m) = (a1 - a2 - r) - m a1 - m a2 - m r
liftM2 f m1 m2 = do { x1 - m1; x2 - m2; return (f x1 x2) }

so the key to understand (*) is understanding the meaning of liftM2.

liftM2 uses, hum, do-notation, so by Haskell 98 report, this can be
translated to

  liftM2 f m1 m2
(1.0)   = m1 = \x1 -
  m2 = \x2 -
  return (f x1 x2)

When it is applied to list (you can convince yourself of this by type
inference),
wee need 'instance Monad []'

instance  Monad []  where
m = k = foldr ((++) . k) [] m
m  k  = foldr ((++) . (\ _ - k)) [] m
return x= [x]
fail _  = []

so
  liftM2 f m1 m2
= m1 = \x1 -
  m2 = \x2 -
  return (f x1 x2)

let
  f1
=\x1 -
  m2 = \x2 -
  return (f x1 x2)

  f2
= \x2 - return (f x1 x2)

we can write

  m1 = f1
= foldr ((++) . f1) [] m1

  m2 = f2
= foldr ((++) . f2) [] m2

Now we can see for list m1, m2, how does 'liftM2 f m1 m2' work

z1 = []
foreach x1 in (reverse m1); do  -- foldr ((++) . f1) [] m1
z2 = []
foreach x2 in (reverse m2); do  -- foldr ((++) . f2) [] m2
z2 = [f x1 x2] ++ z2
done
z1 = z2 ++ z1
done

Now we are ready to see how to apply (*):

  map (:) ['a' .. 'z'] * [[]]
= (map (:) ['a' .. 'z']) * [[]]
= [('a':), ..., ('z':)] * [[]]-- misuse of [...] notation
= ap [('a':), ..., ('z':)] [[]]
= liftM2 id [('a':), ..., ('z':)] [[]]
= [('a':), ..., ('z':)] = \x1 -
  [[]]  = \x2 -
  return (id x1 x2)

Here x1 bind to ('z':), ..., ('a':) in turn, x2 always bind to [], and
noticed that

  return (id ('z':) []) -- f = id; x1 = ('a':); x2 = []
= return (('z':) [])
= return ((:) 'z' [])
= return z
= [z]

we have
  map (:) ['a', .., 'z'] * [[]]
= liftM2 id [('a':), ..., ('z':)] [[]]
= [a, ..., z]

(If you can't follow the this, work through the definition of foldr
step by step will be very helpful.)

  map (:) ['a', .., 'z'] * (map (:) ['a', .., 'z'] * [[]])
= map (:) ['a', .., 'z'] * [a, .., z]
= liftM2 id [('a':), ..., ('z':)] [a, ..., z]
= [aa, ..., az, ba, ..., bz, ..., za, ..., zz]

Now it's easy to know what we get from

  iterate (map (:) ['a' .. 'z'] *) [[]]
= [[], f [[]], f (f [[]]), ...] -- f = map (:) ['a' .. 'z'] *

so
concat $ tail $ iterate (map (:) ['a' .. 'z'] *) [[]]

is exactly what we want.

Understanding Haskell codes by equational reasoning could be a very
tedious process, but it's also
a very helpful and instructive process for the beginners, because it
make you think slowly, check
the computation process step by step, just like the compiler does. And
in my opinion, this is exactly
what a debugger does.

Answer 2 (by Reid Barton):

concatMap (\n - replicateM n ['a'..'z']) 

Re: [Haskell-cafe] Re: Need some help with an infinite list

2009-06-18 Thread Lee Duhem
On Fri, Jun 19, 2009 at 6:17 AM, Matthew Brecknellhask...@brecknell.org wrote:
 On Thu, 2009-06-18 at 23:57 +0800, Lee Duhem wrote:
 [...] I have prepared a blog post for how
 I worked out some of these answers, here is the draft of it, I hope it
 can help you too.

 Nice post! Certainly, pen-and-paper reasoning like this is a very good
 way to develop deeper intuitions.

       Answer 1 (by Matthew Brecknell):

       concat $ tail $ iterate (map (:) ['a' .. 'z'] *) [[]]

 I actually said tail $ concat $ iterate ..., because I think the
 initial empty string is logically part of the sequence. Tacking tail
 on the front then produces the subsequence requested by the OP.

Yes, I changed your solution from tail $ concat $ iterate ... to
concat $ tail $ iterate ..., because I think cut useless part out early
is good idea, forgot to mention that, sorry.


 I should have given more credit to Reid for this solution. I'm always
 delighted to see people using monadic combinators (like replicateM) in
 the list monad, because I so rarely think to use them this way. Sadly,
 my understanding of these combinators is still somewhat stuck in IO,
 where I first learned them. I never would have thought to use * this
 way if I had not seen Reid's solution first.

Actually, I first figure out how Reid's solution works, then figure out yours.
After that, I found, for me, your solution's logic is easier to understand,
so I take it as my first example. As I said at the end, or as I'll
said at the end,
Reid' solution and yours are the same (except effective)

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


Re: [Haskell-cafe] Type families in export lists

2009-05-31 Thread Lee Duhem
On Sun, May 31, 2009 at 7:10 PM, Manuel M T Chakravarty
c...@cse.unsw.edu.au wrote:
 Lee Duhem:

 On Sat, May 30, 2009 at 7:35 PM, Maurí cio briqueabra...@yahoo.com
 wrote:

 Hi,

 How do I include type families (used as associated
 types) in a module export list? E.g.:

 class MyClass a where
   type T a :: *
   coolFunction :: Ta - a
   (...)

 If I just include MyClass and its functions in the
 list, instances in other modules complain they don't
 know T, but I wasn't able to find how (where) to
 include T in the list.


 In export list, you can treat 'type T a' as normal type declaration, ie,
 write
 T(..)  in export list.

 There is also special syntax to export associated types.  You can write

  MyClass (type T)

 in the export list; cf,

  http://haskell.org/haskellwiki/GHC/Type_families#Import_and_export


This is a better way.

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


Re: [Haskell-cafe] Type families in export lists

2009-05-30 Thread Lee Duhem
On Sat, May 30, 2009 at 7:35 PM, Maurí­cio briqueabra...@yahoo.com wrote:
 Hi,

 How do I include type families (used as associated
 types) in a module export list? E.g.:

 class MyClass a where
    type T a :: *
    coolFunction :: Ta - a
    (...)

 If I just include MyClass and its functions in the
 list, instances in other modules complain they don't
 know T, but I wasn't able to find how (where) to
 include T in the list.


In export list, you can treat 'type T a' as normal type declaration, ie, write
T(..)  in export list.

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


Re: [Haskell-cafe] Re: What's the problem with iota's type signature?

2009-05-28 Thread Lee Duhem
On Thu, May 28, 2009 at 5:19 PM, Gracjan Polak gracjanpo...@gmail.com wrote:
 You don't have to guess then, Haskell compiler can do the guessing for you.

It isn't guess, Haskell compiler (like GHC) gets these types by (type)
inference, as you said :-)

lee

 It is called type inference.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What's the problem with iota's type signature?

2009-05-27 Thread Lee Duhem
On Thu, May 28, 2009 at 10:33 AM, michael rice nowg...@yahoo.com wrote:
 Still exploring monads. I don't understand why the type signature for double
 is OK, but not the one for iota.

 Michael

 =

 --double :: (Int a) = a - Maybe b
 --double x = Just (x + x)

Prelude let double x = Just $ x + x
Prelude Just 2 = double
Just 4

You can define double as
double x = return $ x + x

Prelude let double x = return $ x + x
Prelude Just 2 = double
Just 4


 iota :: (Int a) = a - [b]
 iota  n = [1..n]

 --usage: [3,4,5] = iota
 --should produce [1,2,3,1,2,3,4,1,2,3,4,5]

I did.
Prelude let iota n = [1..n]
Prelude [3,4,5] = iota
[1,2,3,1,2,3,4,1,2,3,4,5]

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


Re: [Haskell-cafe] Design in Haskell?

2009-05-26 Thread Lee Duhem
On Wed, May 27, 2009 at 6:50 AM, Michael Steele mikesteel...@gmail.com wrote:

 I've recently found Brent Yorgey's The Typeclassopedia very helpful.
 You can find it in The Monad.Reader Issue 13.

It's great, thank you Michael.

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


Re: [Haskell-cafe] Design in Haskell?

2009-05-25 Thread Lee Duhem
On Mon, May 25, 2009 at 4:22 PM, Dan danielkc...@gmail.com wrote:

 Are there any suggestions of wikis, books or particularly
 well-architected and readable projects I could look at to about learn
 larger-scale design in Haskell?

XMonad is pretty good, see
http://xmonad.org/

For its design and implementation, you may want to see
http://www.cse.unsw.edu.au/~dons/talks/xmonad-hw07.pdf

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


Re: [Haskell-cafe] what's the definition of satisfy and ? ?

2009-05-21 Thread Lee Duhem
On Thu, May 21, 2009 at 2:10 PM, z_a...@163.com z_a...@163.com wrote:
 I cannot understand the following code very well as i donot know the
 definition of satisfy and ?.

Did you check out the document of parsec? You can find definitions for 'satisty'
and '?' in Text.ParserCombinators.Parsec.Char and Text.ParserCombinators.Prim,
respectively.

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


Re: Re: [Haskell-cafe] what's the definition of satisfy and ? ?

2009-05-21 Thread Lee Duhem
On Thu, May 21, 2009 at 6:48 PM, z_axis z_a...@163.com wrote:
 Sorry! I am a haskell newbie.   then i will have a look at
 Text.ParserCombinators.Parsec.Char

Don't forget to CC your reply to the list, so other people on the thread
will see your reply.

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


Re: [Haskell-cafe] How i use GHC.Word.Word8 wit Int ?

2009-05-19 Thread Lee Duhem
2009/5/20 Bernie Pope florbit...@gmail.com:
 Oh right. I didn't see your proposal (did it get sent to the list?).

Yes, I just push the Replay button, not the

 Sorry for the confusion.

It's my fault, sorry.

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