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.  Recursive update of Records with IO (Alia)
   2.  What's the difference between "operator" and     "function"?
      (Costello, Roger L.)
   3. Re:  How would you improve this program? (Daniel Fischer)
   4. Re:  What's the difference between "operator"     and "function"?
      (Christopher Done)
   5. Re:  What's the difference between "operator"     and "function"?
      (yi huang)
   6. Re:  Recursive update of Records with IO (Daniel Fischer)
   7. Re:  quickCheck generation question (Christian Maeder)


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

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

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
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. 

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.

Best,

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

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

Message: 2
Date: Mon, 10 Oct 2011 12:08:21 +0000
From: "Costello, Roger L." <coste...@mitre.org>
Subject: [Haskell-beginners] What's the difference between "operator"
        and     "function"?
To: "beginners@haskell.org" <beginners@haskell.org>
Message-ID:
        <b5fee00b53cf054aa8439027e8fe1775011...@imcmbx04.mitre.org>
Content-Type: text/plain; charset="us-ascii"

Hi Folks,

In a book that I am reading the author distinguishes between "operator" and 
"function."

Example: The "+" is an operator. The "map" is a function.

What's the difference between operator and function?

/Roger



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

Message: 3
Date: Mon, 10 Oct 2011 14:11:29 +0200
From: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Subject: Re: [Haskell-beginners] How would you improve this program?
To: beginners@haskell.org
Message-ID: <201110101411.29905.daniel.is.fisc...@googlemail.com>
Content-Type: Text/Plain;  charset="utf-8"

On Monday 10 October 2011, 10:13:45, Lorenzo Bolla wrote:
> A part from style, is there any reason why one should prefer "where"
> over "let..in"?

Undoubtedly, some people have come up with theoretical reasons why one is 
generally better than the other. I haven't seen a convincing one yet, 
though.

There are some cases where one is clearly better than the other, bindings 
scoping over guards,

foo x y z
  | a == 0 = ...
  | b <= a = ...
  | a <= b+c = ...
  | otherwise = ...
    where
      a = notTooExpensive x y
      b = soSoExpensive z y
      c = reallyExpensive x y z

are much easier to write and read with where. On the other hand,
let binds in expr is an expression, so it's easily usable in contexts 
requiring an expression such as lambda abstractions and do-blocks,

map (\x -> let a = h x in if b then foo a x else bar a x) list

do a <- b
   c <- d
   let e = f a c
   bar e c
   baz
   foo a e

where a where would be awkward at best (though the map example isn't 
particularly good, there

map quux list
  where
    quux x = if b then foo a x else bar a x
      where
        a = h x

isn't bad and becomes easier to understand if the lambda becomes 
complicated enough).

So there are places where one is (clearly) more convenient/better than the 
other, but in other places it's purely up to personal preference.

> > You build the map via fromListWith (+). That's bad if you have input
> > with large counts. fromListWith (+) gives you thunks of the form
> > (...(1+1)+1)...+1) as map-entries. That costs a lot of space and time.
> > Better build the map using insertWith',
> >
> >  mp = foldl' ins empty words
> >    where
> >      ins m w = insertWith' (+) w 1 m
> 
> Please find the "strict" version here:
> https://github.com/lbolla/stanford-cs240h/blob/master/lab1/lab1.hs.

One further time-saver (in printTokens):

    maxCount = maximum $ map count tokens

you need not traverse the entire list of tokens for that,

    maxCount = case sortedTokens of
                 (Token _ c:_) -> c

> 
> Plot of times is now:
> https://github.com/lbolla/stanford-cs240h/blob/master/lab1/times.png
> 
> Python is still slightly faster, but I'm getting there.
> 
> >    3. a Python version using defaultdict.
> >
> > sort is O(n*log n), map and python are O(n*log d), where n is the
> > number of words and d the number of distinct words.
> 
> I believe Python's defaultdict have (optimistically) O(1) lookup and
> insert, because it is implemented as a hashmap.

Ah, I tend to forget about hashmaps. Although the O(1) isn't quite true 
[calculating the hash isn't bounded time, and the lookup in the bucket need 
not be either], for a good hashtable it's true enough that it scales better 
than a tree-based map.




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

Message: 4
Date: Mon, 10 Oct 2011 14:20:17 +0200
From: Christopher Done <chrisd...@googlemail.com>
Subject: Re: [Haskell-beginners] What's the difference between
        "operator"      and "function"?
To: "Costello, Roger L." <coste...@mitre.org>
Cc: "beginners@haskell.org" <beginners@haskell.org>
Message-ID:
        <caajhnpc9kpuf-y_xm2xksjax2p0i3n2zxt400x5h9adn5hc...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

2011/10/10 Costello, Roger L. <coste...@mitre.org>:
> What's the difference between operator and function?

http://www.haskell.org/onlinereport/exps.html#sect3.2

> An operator is either an operator symbol, such as + or $$, or is an ordinary 
> identifier enclosed in grave accents (backquotes), such as `op`. For example, 
> instead of writing the prefix application op x y, one can write the infix 
> application x `op` y. If no fixity declaration is given for `op` then it 
> defaults to highest precedence and left associativity (see Section 4.4.2).
>
> Dually, an operator symbol can be converted to an ordinary identifier by 
> enclosing it in parentheses. For example, (+) x y is equivalent to x + y, and 
> foldr (*) 1 xs is equivalent to foldr (\x y -> x*y) 1 xs.



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

Message: 5
Date: Mon, 10 Oct 2011 20:29:28 +0800
From: yi huang <yi.codepla...@gmail.com>
Subject: Re: [Haskell-beginners] What's the difference between
        "operator"      and "function"?
To: Haskell Beginners <beginners@haskell.org>
Message-ID:
        <cahu7ryanr7f-dsh4c_h_klzs-nx1ezbjzrywickbwcaox_x...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Usually, operator is function that takes two values and return a value, and
used in infix form, since in haskell infix and prefix form is
interchangable, so you can define operator as function taking two arguments.

>>> 1+2
3
>>> (+) 1 2
3
>>> map (+1) [1,2,3]
[2,3,4]
>>> (+1) `map` [1,2,3]
[2,3,4]

Hope you can understand my pool english ;-)
Best regards.

On Mon, Oct 10, 2011 at 8:08 PM, Costello, Roger L. <coste...@mitre.org>wrote:

> Hi Folks,
>
> In a book that I am reading the author distinguishes between "operator" and
> "function."
>
> Example: The "+" is an operator. The "map" is a function.
>
> What's the difference between operator and function?
>
> /Roger
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



-- 
http://www.yi-programmer.com/blog/
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111010/3910f1c9/attachment-0001.htm>

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

Message: 6
Date: Mon, 10 Oct 2011 14:50:52 +0200
From: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Subject: Re: [Haskell-beginners] Recursive update of Records with IO
To: beginners@haskell.org, Alia <alia_kho...@yahoo.com>
Message-ID: <201110101450.52192.daniel.is.fisc...@googlemail.com>
Content-Type: Text/Plain;  charset="utf-8"

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




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

Message: 7
Date: Mon, 10 Oct 2011 15:26:26 +0200
From: Christian Maeder <christian.mae...@dfki.de>
Subject: Re: [Haskell-beginners] quickCheck generation question
To: Joe Van Dyk <j...@fixieconsulting.com>
Cc: beginners <beginners@haskell.org>
Message-ID: <4e92f282.4030...@dfki.de>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Am 08.10.2011 01:40, schrieb Joe Van Dyk:
> I'm going through the 99 Haskell problems and am trying to write
> quickCheck properties for each one.
>
> -- 3 (find k"th element of a list)
> element_at xs x = xs !! x
> prop_3a xs x = (x<  length xs&&  x>= 0) ==>  element_at xs (x::Int) ==
> (xs !! x::Int)

The definition and test look very similar (basically "=" is replaced by 
"=="). So this seems to test reliability of definitions and Eq 
instances. Such tests should not be necessary. (Testing different 
implementations for equality makes more sense.)

Cheers Christian



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

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


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

Reply via email to