Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Right-associating infix application operators
      (Daniel Fischer)
   2. Re:  Right-associating infix application operators (Tom Hobbs)
   3. Re:  Right-associating infix application operators
      (Daniel Fischer)
   4.  Dynamic Programming in Haskell (Ali Razavi)


----------------------------------------------------------------------

Message: 1
Date: Tue, 6 Jul 2010 13:19:06 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Right-associating infix application
        operators
To: beginners@haskell.org
Message-ID: <201007061319.06346.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="utf-8"

On Tuesday 06 July 2010 13:00:33, Tom Hobbs wrote:
> In people's responses to my serialization questions, I've seen them
> using $.
>
> I didn't know what it was so I've looked it up.  Can someone please
> confirm my understanding of what it does, please?
>
> According to http://en.wikibooks.org/wiki/Haskell/Practical_monads,
> after the second code sample in the "Return Values" section, it seems to
> suggest that $ is only used to avoid using so many brackets.  Which

"only" is an exaggeration, make it "mostly".

Other common uses are

map ($ 3) functionList

and

zipWith ($) functions arguments

it's not necessary, you can get the second from

zipWith id functions arguments

(even using one keystroke less!) and the first from

map (flip id 3) functionList

or

map (\f -> f 3) functionList

As for the zipWith, there's a slight advantage in that ($) stands out more 
than id, without blacking out the rest.
As for the map, well, it takes beginners some time usually to figure out 
what flip id does (and causes surprise that it's even possible, because
flip :: (a -> b -> c) -> b -> a -> c
id :: t -> t
doesn't make it obvious). And the lambda-expression isn't too beautiful 
either.

> seems to make sense, but looking at it's definition in Prelude I really
> can't see why it's useful.
>
> Yitz gave me the code;
>
> fmap (runGet $ readNames n) $ L.hGetContents h
>
> So can I rewrite this without the $ like this?
>
> fmap (runGet (readNames n)) (L.hGetContents h)
>

Yes, that's equivalent.
But with deeper nesting, judicious use of ($) can make the code much more 
readable.

> Is there any additional benefit to using $ than just not having to write
> as many brackets?

See above, it can make things more readable in several ways.
But it shouldn't be overused.

res = f . g . h . i $ j x

is better (IMO) than

res = f $ g $ h $ i $ j $ x

>
> Thanks,
>
> Tom



------------------------------

Message: 2
Date: Tue, 6 Jul 2010 12:59:08 +0100
From: Tom Hobbs <tvho...@googlemail.com>
Subject: Re: [Haskell-beginners] Right-associating infix application
        operators
To: Daniel Fischer <daniel.is.fisc...@web.de>, beginners@haskell.org
Message-ID:
        <aanlktil8ukzgszuvhwnfvkhg5zf3vw9qgev10rz5c...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Right, a bit of playing around and I think understand.  Maybe.

In your example;

map ($ 3) functionList

I'm assuming that this is Haskel's way of saying "Give the value 3 as an
argument to each function in functionList".  Playing in Hugs seems to
suggest that this is the case;

Hugs> map ($ 3) [(4 +), (5 +), (6 +)]
[7,8,9]

That makes sense.  The first arg to map is expecting a function, so we give
it a function and a value which just returns the value.  I can see why that
works.

Rewriting using "flip id" has me stumped though.

Hugs> map (flip id 3) [(4 +), (5 +), (6 +)]
[7,8,9]

So this is saying,

Actually, I don't know.  Working it out in my head I would say "id 3"
returns 3.  But "flip 3" causes an error in Hugs, so this code doesn't work
- but clearly it does.

Hugs> :t flip id 3
flip id 3 :: Num a => (a -> b) -> b

Hugs> :t ($ 3)
flip ($) 3 :: Num a => (a -> b) -> b

Is presumably why it works, but I can't work out how to create the type
signature of "flip id 3" from the sigs of flip and id.

Help?

Thanks.

Tom


On Tue, Jul 6, 2010 at 12:19 PM, Daniel Fischer <daniel.is.fisc...@web.de>wrote:

> On Tuesday 06 July 2010 13:00:33, Tom Hobbs wrote:
> > In people's responses to my serialization questions, I've seen them
> > using $.
> >
> > I didn't know what it was so I've looked it up.  Can someone please
> > confirm my understanding of what it does, please?
> >
> > According to http://en.wikibooks.org/wiki/Haskell/Practical_monads,
> > after the second code sample in the "Return Values" section, it seems to
> > suggest that $ is only used to avoid using so many brackets.  Which
>
> "only" is an exaggeration, make it "mostly".
>
> Other common uses are
>
> map ($ 3) functionList
>
> and
>
> zipWith ($) functions arguments
>
> it's not necessary, you can get the second from
>
> zipWith id functions arguments
>
> (even using one keystroke less!) and the first from
>
> map (flip id 3) functionList
>
> or
>
> map (\f -> f 3) functionList
>
> As for the zipWith, there's a slight advantage in that ($) stands out more
> than id, without blacking out the rest.
> As for the map, well, it takes beginners some time usually to figure out
> what flip id does (and causes surprise that it's even possible, because
> flip :: (a -> b -> c) -> b -> a -> c
> id :: t -> t
> doesn't make it obvious). And the lambda-expression isn't too beautiful
> either.
>
> > seems to make sense, but looking at it's definition in Prelude I really
> > can't see why it's useful.
> >
> > Yitz gave me the code;
> >
> > fmap (runGet $ readNames n) $ L.hGetContents h
> >
> > So can I rewrite this without the $ like this?
> >
> > fmap (runGet (readNames n)) (L.hGetContents h)
> >
>
> Yes, that's equivalent.
> But with deeper nesting, judicious use of ($) can make the code much more
> readable.
>
> > Is there any additional benefit to using $ than just not having to write
> > as many brackets?
>
> See above, it can make things more readable in several ways.
> But it shouldn't be overused.
>
> res = f . g . h . i $ j x
>
> is better (IMO) than
>
> res = f $ g $ h $ i $ j $ x
>
> >
> > Thanks,
> >
> > Tom
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100706/19107e62/attachment-0001.html

------------------------------

Message: 3
Date: Tue, 6 Jul 2010 14:31:29 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Right-associating infix application
        operators
To: Tom Hobbs <tvho...@googlemail.com>
Cc: beginners@haskell.org
Message-ID: <201007061431.29408.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="utf-8"

On Tuesday 06 July 2010 13:59:08, Tom Hobbs wrote:
> Right, a bit of playing around and I think understand.  Maybe.
>
> In your example;
>
> map ($ 3) functionList
>
> I'm assuming that this is Haskel's way of saying "Give the value 3 as an
> argument to each function in functionList".

Right. ($ 3) is a right-section of ($), and like (^3) n ~> n^3, 
($ 3) f ~> f $ 3 -- (= f 3).

> Playing in Hugs seems to
> suggest that this is the case;
>
> Hugs> map ($ 3) [(4 +), (5 +), (6 +)]
> [7,8,9]
>
> That makes sense.  The first arg to map is expecting a function, so we
> give it a function and a value which just returns the value.  I can see
> why that works.
>
> Rewriting using "flip id" has me stumped though.
>
> Hugs> map (flip id 3) [(4 +), (5 +), (6 +)]
> [7,8,9]
>
> So this is saying,
>
> Actually, I don't know.  Working it out in my head I would say "id 3"
> returns 3.  But "flip 3" causes an error in Hugs, so this code doesn't
> work - but clearly it does.

Wrong parentheses.

flip id 3 = (flip id) 3

so

(flip id) 3 f 
~> (id f) 3
~> f 3

See,

flip :: (a -> b -> c) -> b -> a -> c
id :: t -> t

to make flip id typecheck, only a subset of all possible types of id can be 
used here, namely, t must be a function type,

t ~ (u -> v)

then

id :: (u -> v) -> u -> v
---------a--------b----c

(remember that (->) associates to the right, so (u -> v) -> (u -> v) is the 
same as (u -> v) -> u -> v)

and

flip id :: u -> (u -> v) -> v

then

flip id 3 :: Num n => (n -> v) -> v

>
> Hugs> :t flip id 3
> flip id 3 :: Num a => (a -> b) -> b

You should have tried without the 3,

Prelude> :t flip id
flip id :: b -> (b -> c) -> c

I did mention that it's confusing for beginners, as you saw, it really is.
But I hope your thinking about it makes the explanation more effectful than 
if I had given it right away.

>
> Hugs> :t ($ 3)
> flip ($) 3 :: Num a => (a -> b) -> b
>
> Is presumably why it works, but I can't work out how to create the type
> signature of "flip id 3" from the sigs of flip and id.
>
> Help?
>
> Thanks.
>
> Tom
>

Cheers,
Daniel


------------------------------

Message: 4
Date: Tue, 6 Jul 2010 12:45:47 -0400
From: Ali Razavi <ali.raz...@gmail.com>
Subject: [Haskell-beginners] Dynamic Programming in Haskell
To: beginners@haskell.org
Message-ID:
        <aanlktin0k9bekzizfvgoiwq1wbwy6qdl7zrphef-p...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

In order to practice Haskell, I decided to program some algorithms from the
CLRS book. Particularly, I tried to implement the Matrix Chain Order from
Chapter 15 on Dynamic Programming.
Here is my code. It seems to work, however, it looks ugly and it was a
nightmare to debug. I appreciate comments about a more elegant solution, and
generally the best way to implement these kinds of algorithms in Haskell.
Style improvement suggestions are also welcome.

Best,
Ali


import Data.Array


pp = [30,35,15,5,10,20,25]

para p = let n = length p - 1
             msij =  array ((1,1),(n,n))
                           ([((i,j), (0,0)) | i <-[1..n], j <-[1..n]] ++
                            [((i,j), (m, s))| l<-[2..n]
                                                     , i<-[1..n-l+1]
                                                     , let j = i + l - 1
                                                     , let qs =
[q|k<-[i..j-1]
                                                                   , let q =
fst (msij!(i,k)) + fst (msij!(k+1, j)) + p!!(i-1)*p!!k*p!!j]
                                                     , let (m, s, c) =
foldl (\(mz,sz,ind) x-> if x < mz then (x,ind,ind+1) else (mz,sz,ind+1))
(head qs, i, i) qs ])
         in msij



chainSolve p = let sol = para p
                   n = length p - 1 in
                do
                    print $ fst $ sol!(1,n)
                    putStrLn $ printSol sol 1 n ""
                where
                    printSol s i j o =
                        if i == j then
                            o ++ "A" ++ (show i)
                        else
                            o ++ "(" ++
                            (printSol s i (snd (s!(i,j))) o) ++
                            (printSol s ((snd (s!(i,j)))+1) j o) ++ ")"
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100706/ab16e5f5/attachment-0001.html

------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 25, Issue 20
*****************************************

Reply via email to