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:  Recursive update of Records with IO (Alia)
   2. Re:  Recursive update of Records with IO (Alia)
   3. Re:  Recursive update of Records with IO (Gnani)
   4.  help for the lhs2Tex install (kolli kolli)
   5. Re:  help for the lhs2Tex install (Brandon Allbery)


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

Message: 1
Date: Mon, 10 Oct 2011 06:35:29 -0700 (PDT)
From: Alia <alia_kho...@yahoo.com>
Subject: Re: [Haskell-beginners] Recursive update of Records with IO
To: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Cc: "beginners@haskell.org" <beginners@haskell.org>
Message-ID:
        <1318253729.60711.yahoomail...@web65702.mail.ac4.yahoo.com>
Content-Type: text/plain; charset="us-ascii"


<snip awesome explanation>

Dear Daniel,

I very much appreciate your quick and excellent reply, which is exactly what 
the doctor ordered. The revised update works like a charm and I will be 
henceforth spending more time in Control.Monad (-:

Many thanks indeed!

Alia
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111010/a65e7cef/attachment-0001.htm>

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

Message: 2
Date: Mon, 10 Oct 2011 06:59:32 -0700 (PDT)
From: Alia <alia_kho...@yahoo.com>
Subject: Re: [Haskell-beginners] Recursive update of Records with IO
To: "beginners@haskell.org" <beginners@haskell.org>
Message-ID:
        <1318255172.74483.yahoomail...@web65702.mail.ac4.yahoo.com>
Content-Type: text/plain; charset=iso-8859-1

For the sake of good order, I am posting the different solutions as per Daniel 
Fischer's suggestions
in a tested module: 


<TestIO.hs>

module TestIO

where

import Control.Monad

data Person = Person {name :: String, age :: Int} deriving Show


-- operator version of apply
infix 0 |>

(|>) :: a -> (a -> b) -> b
x |> f = f x

-- verbal version of (|>) operator
apply :: a -> (a -> b) -> b
apply x f = f x

setName :: String -> Person -> IO Person
setName s p = do
??? putStrLn "setting name"
??? return p {name=s}

setAge :: Int -> Person -> IO Person
setAge i p = do
??? putStrLn "setting age"
??? return p {age=i}


-- first way: using recursion
update :: [Person -> IO Person] -> Person -> IO Person
update [] p???? = return p
update (f:fs) p = do
??? p' <- f p
??? update fs p'

-- second way: using foldm and (|>) operator
update1 :: [Person -> IO Person] -> Person -> IO Person
update1 fs p = foldM (|>) p fs

-- third way: (|>) is now function apply
update2 :: [Person -> IO Person] -> Person -> IO Person
update2 fs p = foldM apply p fs

p1 = Person {name="alia", age=12}
p2 = update [(setName "sam"), (setAge 32)] p1
p3 = update1 [(setName "sue"), (setAge 40)] p1
p4 = update2 [(setName "jo"), (setAge 55)] p1


</TestIO.hs>



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

Message: 3
Date: Mon, 10 Oct 2011 22:43:28 +0800
From: Gnani <gnani.sw...@gmail.com>
Subject: Re: [Haskell-beginners] Recursive update of Records with IO
To: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Cc: Alia <alia_kho...@yahoo.com>,       "beginners@haskell.org"
        <beginners@haskell.org>
Message-ID: <7ac6d141-17ce-4caf-b5a3-8b7e9b17e...@gmail.com>
Content-Type: text/plain;       charset=us-ascii

Daniel,

Excellent explanation. Thanks a lot.

Mohan.

Sent from my iPad

On Oct 10, 2011, at 20:50, Daniel Fischer <daniel.is.fisc...@googlemail.com> 
wrote:

> On Monday 10 October 2011, 13:53:17, Alia wrote:
>> Hi folks,
>> 
>> 
>> 
>> (Apologies if there is duplication, I didn't see my post archived so I
>> assumed I had to subscribe to be able to post)
>> 
>> 
>> In the hope of tapping the collective wisdom, I'd like to share a
>> problem which seems to be worth sharing: how to recursively update a
>> single record instance with a list of IO tainted functions.
>> 
>> A simple pure IO-less version of what I am trying to do is probably the
>> best way to explain this:
>> 
>> <pure_version>
>> 
>> module Test
>> 
>> where
>> 
>> data Person = Person {name :: String, age :: Int} deriving Show
>> 
>> setName :: String -> Person -> Person
>> setName s p = p {name=s}
>> 
>> setAge :: Int -> Person -> Person
>> setAge i p = p {age=i}
>> 
>> update :: [Person -> Person] -> Person -> Person
>> update [] p  = p
> 
>> update
>> [f] p = f p
> 
> This clause is unnecessary, you can omit it.
> 
>> update (f:fs) p = update fs p'
>>    where
>>        p' = f p
>> 
>> p1 = Person {name="sue", age=12}
>> p2 = update [(setName "sam"), (setAge 32)] p1
>> 
>> </pure_version>
>> 
>> This works very nicely.
> 
> Note that update is a special case of a very general pattern, a fold.
> In this case a left fold, since you're combining the functions with the 
> person in the order the functions appear in the list.
> 
> Prelude> :t foldl
> foldl :: (a -> b -> a) -> a -> [b] -> a
> 
> The type of your list elements is b = (Person -> Person),
> the initial value has type a = Person.
> 
> So what's missing to use foldl is the function of type
> (a -> b -> a), here (Person -> (Person -> Person) -> Person).
> Now, to combine a Person with a (Person -> Person) function to yield a 
> Person, there are two obvious choices,
> 1. const: const p f = p  -- obviously not what we want here
> 2. application: app p f = f p -- i.e. app = flip ($).
> 
> We can define a pretty operator for that,
> 
> infixl 0 |>
> 
> (|>) :: a -> (a -> b) -> b
> x |> f = f x
> 
> and get
> 
> update fs p = foldl (|>) p fs
> 
> Note: foldl is almost never what you want, instead you want foldl' from 
> Data.List, see e.g.
> http://www.haskell.org/haskellwiki/Foldr_Foldl_Foldl%27
> But it doesn't matter here, as Person is defined, foldl' won't give you 
> enough strictness if the list of functions is long; but the list of person-
> updaters will surely be short in general.
> 
> For completeness, the type of the right-fold, foldr:
> 
> Prelude> :t foldr
> foldr :: (a -> b -> b) -> b -> [a] -> b
> 
>> 
>> Now if the setter functions involve some IO, I believe the type
>> signatures should probably look like this:
>> 
>> setName :: String -> Person -> IO Person
>> setAge :: Int -> Person -> IO Person
>> update :: [Person -> IO Person] -> Person -> IO Person
>> 
>> and the setter functions should look like this for example:
>> 
>> setName :: String -> Person -> IO Person
>> setName s p = do
>>    putStrLn "setting name"
>>    return p {name=s}
>> 
>> setAge :: Int -> Person -> IO Person
>> setAge i p = do
>>    putStrLn "setting age"
>>    return p {age=i}
>> 
>> but I'm stuck on how
>> the update function would look.. Any help would be much appreciated.
> 
> We can closely follow the pure case,
> 
> update [] p = return p  -- nothing else we could do
> update (f:fs) p = do
>  p' <- f p
>  update fs p'
> 
> The main difference is that instead of binding the updated person with a 
> where or let, as in the pure case, we bind it in the IO-monad, since that's 
> f's result type.
> 
> Instead of coding the recursion ourselves, we can also use a standard 
> combinator here,
> 
> Prelude Control.Monad> :i foldM
> foldM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a
>        -- Defined in Control.Monad
> 
> The Monad here is IO, a again is Person, and b is now
> (Person -> IO Person).
> 
> For the combinator
> Person -> (Person -> IO Person) -> IO Person
> there are again two obvious possibilities,
> 1. return -- analogous to const
> 2. application, (|>)
> 
> and the IO-version becomes
> 
> import Control.Monad
> 
> update fs p = foldM (|>) p fs
> 
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners



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

Message: 4
Date: Mon, 10 Oct 2011 14:24:40 -0600
From: kolli kolli <nammukoll...@gmail.com>
Subject: [Haskell-beginners] help for the lhs2Tex install
To: beginners@haskell.org
Message-ID:
        <cae7d9k55o-n5sirjtuwcm6msihxuehhb9cebfwm_bjg77ro...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

hi,
when I am trying to install lhs2tex on my machine(windows).I am getting the
following error.Can you please me install lhs2tex....

Microsoft Windows [Version 6.1.7601]
Copyright (c) 2009 Microsoft Corporation.  All rights reserved.

C:\Users\namratha>cabal install lhs2Tex
Resolving dependencies...
[1 of 1] Compiling Main             (
C:\Users\namratha\AppData\Local\Temp\lhs2t
ex-1.171640\lhs2tex-1.17\Setup.hs,
C:\Users\namratha\AppData\Local\Temp\lhs2tex-
1.171640\lhs2tex-1.17\dist\setup\Main.o )
Linking
C:\Users\namratha\AppData\Local\Temp\lhs2tex-1.171640\lhs2tex-1.17\dist\
setup\setup.exe ...
Configuring lhs2tex-1.17...
setup.exe: kpsewhich command not found
cabal: Error: some packages failed to install:
lhs2tex-1.17 failed during the configure step. The exception was:
ExitFailure 1
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111010/689ce6c4/attachment-0001.htm>

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

Message: 5
Date: Mon, 10 Oct 2011 16:30:32 -0400
From: Brandon Allbery <allber...@gmail.com>
Subject: Re: [Haskell-beginners] help for the lhs2Tex install
To: kolli kolli <nammukoll...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <CAKFCL4W4rd1iODz2rr3_jKbfFabn6LE0T=svr0_po2auyp9...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Mon, Oct 10, 2011 at 16:24, kolli kolli <nammukoll...@gmail.com> wrote:

> when I am trying to install lhs2tex on my machine(windows).I am getting the
> following error.Can you please me install lhs2tex....
>

You need to have a TeX/LaTeX distribution of some kind already installed and
in %PATH%; the installer is looking for kpsewhich, which reports the
location of various TeX library directories.

-- 
brandon s allbery                                      allber...@gmail.com
wandering unix systems administrator (available)     (412) 475-9364 vm/sms
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111010/3ddb6f20/attachment-0001.htm>

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

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


End of Beginners Digest, Vol 40, Issue 14
*****************************************

Reply via email to