Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/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.  Hutton 2nd ed, ex 7.6 (trent shipley)
   2. Re:  Hutton 2nd ed, ex 7.6 (David McBride)


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

Message: 1
Date: Wed, 22 Aug 2018 04:00:29 -0700
From: trent shipley <trent.ship...@gmail.com>
To: Haskell Beginners <beginners@haskell.org>
Subject: [Haskell-beginners] Hutton 2nd ed, ex 7.6
Message-ID:
        <caeflybjwta5y06hlqsdr13ak8tdlpqwvuy7d4ti_thszhut...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

1. I got through the problem without getting so stuck I had to ask this
list.  But, I am disappointed in how much I had to cheat by looking up
solutions on Google after making my best attempt.  This higher order
functions chapter is giving more trouble than any chapter so far.

2. Since getting tutoring on how to read function declarations, I'm doing
better at deciphering simple declarations, but writing them myself is
beyond me more often than not.

3. I feel like Hutton introduces concepts well, but with more brevity and
fewer examples than would be best for me.  Unfortunately, he leaves out
almost all the ancillary pragmatics as exemplified by the need for "null"
and "const" below.  My bet is that when Hutton 2nd ed is used as a textbook
in college those practical lacks get covered in lecture, problem sessions,
and in mutual aid between students.

Does anyone have any idea on how I might improve my performance.  I am not
used to having difficulty learning a computer language.  (Prolog and Java
Swing being exceptions.)


{--

6. A higher-order function unfold that encapsulates a simple pattern of
recursion for producing a list can be defined as follows:

unfold p h t x | p x = []
               | otherwise = h x : unfold p h t (t x)

That is, the function unfold p h t produces the empty list if the predicate
p is true of the argument value, and otherwise produces a non-empty list by
applying the function h to this value to give the head, and the function t
to generate another argument that is recursively processed in the same way
to produce the tail of the list. For example, the function int2bin can be
rewritten more compactly using unfold as follows:

int2bin = unfold (==0) (‘mod‘ 2) (‘div‘ 2)

Redefine the functions chop8, map f and iterate f using unfold.

Hutton, Graham. Programming in Haskell (Kindle Locations 2830-2842).
Cambridge University Press. Kindle Edition.

Basically, what you do to develop and test this question is to copy and
paste extended example 7.6 Binary String Transmittter from the chapter into
your text editor.  Then you alter large chunks of it to use the unfold
function.

--}

import Data.Char
import Prelude hiding (iterate, map)

type Bit = Int


-- I had to crib the type signature

unfold :: (b -> Bool) -> (b -> a) -> (b -> b) -> b -> [a]
unfold p h t x | p x = []
               | otherwise = h x : unfold p h t (t x)


-- Hutton, Graham. Programming in Haskell (Kindle Location 2329). Cambridge
University Press. Kindle Edition.

-- cribbed type signature
-- Had to copy (f . head), my attempt was (f head).
-- I had no idea the function "null" existed before Googling the solution.
-- Is Googling to learn the existence of "null" accepted pedagological
practice?
-- Is it a lacuna on Hutton's part?

map :: (a -> b) -> [a] -> [b]
map f = unfold null (f . head) tail

-- had to copy the signature, although I didn't try hard to come up with it
on my own.
-- I had tried to use (==[]).  I got the solution "False" by copying from
the internet.
-- I would not have gotten the word "const" without cheating from the
internet.  It is nowhere in Hutton's book up to this point.

iterate :: (a -> a) -> a -> [a]
iterate f = unfold (const False) id f

-- chop8 :: [Bit] -> [[Bit]]
-- chop8 [] = []
-- chop8 bits = take 8 bits : chop8 (drop 8 bits)

-- Hutton, Graham. Programming in Haskell (Kindle Locations 2681-2683).
Cambridge University Press. Kindle Edition.

-- I attempted this first, and i pretty much got it on my own.

chop8 :: [Bit] -> [[Bit]]
chop8 bits = unfold (==[]) (take 8) (drop 8) bits
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20180822/12047a8d/attachment-0001.html>

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

Message: 2
Date: Wed, 22 Aug 2018 08:35:37 -0400
From: David McBride <toa...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Hutton 2nd ed, ex 7.6
Message-ID:
        <CAN+Tr42TAakr-EnJ1p3oD1GbSnJOBximYFS=saqkylumrua...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

It sounds to me like you are just lacking a familiarity with the standard
library.  All of the list functions (such as null) are detailed on hackage (
http://hackage.haskell.org/package/base/docs/Data-List.html) with
reasonable examples.

There is also hoogle https://www.haskell.org/hoogle/, which allows you to
search both for function names as well as types and operators like (.), all
of which link to the documentation.

As for unfold's type signature, the first thing any haskell programmer
would have done is load it into ghci, and type :t unfold.  I could get it
from his description of the function, and perhaps that would have been good
practice, but there's no need to turn to google for that.
:t unfold
unfold :: (t -> Bool) -> (t -> a) -> (t -> t) -> t -> [a]

Haskell's a pretty different language from most of the mainstream
languages.  I wouldn't feel bad because your previous experience barely
applies and also these exercises are not the easiest I've ever seen.
Unfold is not a standard function in haskell and so being able to derive
standard functions from it is more of an algorithmic problem than a
learning haskell problem.  In any case, I think based on what you've
written that you are doing just fine.

On Wed, Aug 22, 2018 at 7:00 AM, trent shipley <trent.ship...@gmail.com>
wrote:

> 1. I got through the problem without getting so stuck I had to ask this
> list.  But, I am disappointed in how much I had to cheat by looking up
> solutions on Google after making my best attempt.  This higher order
> functions chapter is giving more trouble than any chapter so far.
>
> 2. Since getting tutoring on how to read function declarations, I'm doing
> better at deciphering simple declarations, but writing them myself is
> beyond me more often than not.
>
> 3. I feel like Hutton introduces concepts well, but with more brevity and
> fewer examples than would be best for me.  Unfortunately, he leaves out
> almost all the ancillary pragmatics as exemplified by the need for "null"
> and "const" below.  My bet is that when Hutton 2nd ed is used as a textbook
> in college those practical lacks get covered in lecture, problem sessions,
> and in mutual aid between students.
>
> Does anyone have any idea on how I might improve my performance.  I am not
> used to having difficulty learning a computer language.  (Prolog and Java
> Swing being exceptions.)
>
>
> {--
>
> 6. A higher-order function unfold that encapsulates a simple pattern of
> recursion for producing a list can be defined as follows:
>
> unfold p h t x | p x = []
>                | otherwise = h x : unfold p h t (t x)
>
> That is, the function unfold p h t produces the empty list if the
> predicate p is true of the argument value, and otherwise produces a
> non-empty list by applying the function h to this value to give the head,
> and the function t to generate another argument that is recursively
> processed in the same way to produce the tail of the list. For example, the
> function int2bin can be rewritten more compactly using unfold as follows:
>
> int2bin = unfold (==0) (‘mod‘ 2) (‘div‘ 2)
>
> Redefine the functions chop8, map f and iterate f using unfold.
>
> Hutton, Graham. Programming in Haskell (Kindle Locations 2830-2842).
> Cambridge University Press. Kindle Edition.
>
> Basically, what you do to develop and test this question is to copy and
> paste extended example 7.6 Binary String Transmittter from the chapter into
> your text editor.  Then you alter large chunks of it to use the unfold
> function.
>
> --}
>
> import Data.Char
> import Prelude hiding (iterate, map)
>
> type Bit = Int
>
>
> -- I had to crib the type signature
>
> unfold :: (b -> Bool) -> (b -> a) -> (b -> b) -> b -> [a]
> unfold p h t x | p x = []
>                | otherwise = h x : unfold p h t (t x)
>
>
> -- Hutton, Graham. Programming in Haskell (Kindle Location 2329).
> Cambridge University Press. Kindle Edition.
>
> -- cribbed type signature
> -- Had to copy (f . head), my attempt was (f head).
> -- I had no idea the function "null" existed before Googling the solution.
> -- Is Googling to learn the existence of "null" accepted pedagological
> practice?
> -- Is it a lacuna on Hutton's part?
>
> map :: (a -> b) -> [a] -> [b]
> map f = unfold null (f . head) tail
>
> -- had to copy the signature, although I didn't try hard to come up with
> it on my own.
> -- I had tried to use (==[]).  I got the solution "False" by copying from
> the internet.
> -- I would not have gotten the word "const" without cheating from the
> internet.  It is nowhere in Hutton's book up to this point.
>
> iterate :: (a -> a) -> a -> [a]
> iterate f = unfold (const False) id f
>
> -- chop8 :: [Bit] -> [[Bit]]
> -- chop8 [] = []
> -- chop8 bits = take 8 bits : chop8 (drop 8 bits)
>
> -- Hutton, Graham. Programming in Haskell (Kindle Locations 2681-2683).
> Cambridge University Press. Kindle Edition.
>
> -- I attempted this first, and i pretty much got it on my own.
>
> chop8 :: [Bit] -> [[Bit]]
> chop8 bits = unfold (==[]) (take 8) (drop 8) bits
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20180822/725ec01d/attachment-0001.html>

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

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


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

End of Beginners Digest, Vol 122, Issue 12
******************************************

Reply via email to