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.  Thompson Exercise 9.13 (dan portin)
   2.  Re: why is something different within a function when it
      comes out? (prad)
   3. Re:  Thompson Exercise 9.13 (Daniel Fischer)
   4. Re:  Re: why is something different within a      function when it
      comes out? (Daniel Fischer)
   5.  My first functioning haskell project - a steganography
      utility (Tim Cowlishaw)
   6.  Re: [Haskell-cafe] lists of arbitrary depth (Richard O'Keefe)
   7.  A difficult package (Ben Wise)


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

Message: 1
Date: Wed, 14 Jul 2010 11:55:17 -0700
From: dan portin <danpor...@gmail.com>
Subject: [Haskell-beginners] Thompson Exercise 9.13
To: beginners@haskell.org
Message-ID:
        <aanlktinua9-k2k-n5do64rdusary3kqedhuw8s-md...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi,

I am new to Haskell (and programming). Thompson's exercise 9.13  in *Craft
of Functional Programming *gave me trouble. Searching the list archives, I
saw people define init (xs), last (xs), and so on, in a variety of complex
ways (using the Maybe monad, using fairly complex post-processing). This
seems to be a hard problem for beginners; at least, it was rather hard for
me.

The problem is to define the Prelude functions *init* and *last* using *
foldr*. After a while, I came up with:

-- *Exercise 9.13*: Use foldr (f, s, xs) to give definitions of the prelude
functions
-- unzip, last, and init.

-- Clearly,
--     [(x, y), (x1, y1)] = (x, y) : (x1, y1) : ([], [])
--     foldr f ([], []) ((x, y):(x1, y1):[]) = f (x, y) (f (x1, y1) ([],
[]))
-- Hence, f (x, y) (xs, ys) must equal (x:xs, y:ys) for any xs, ys.

unzip :: [(a, b)] -> ([a], [b])
unzip xys = foldr f ([], []) xys
 where f :: (a, b) -> ([a], [b]) -> ([a], [b])
       f (x, y) (xs, ys) = (x:xs, y:ys)

*last* :: [a] -> a
last xs = head $ foldr f [] xs
 where f :: a -> [a] -> [a]
       f x [] = [x]
       f x ys = ys ++ [x]

*init* :: [a] -> [a]
init xs = tail $ foldr f [] xs
 where f :: a -> [a] -> [a]
       f x [] = [x]
       f x (y:xs) = y : x : xs

Now, these seemed to be hard questions. So, I have three questions: (1) are
these correct? They work on test cases, and I *did* do some quick proofs.
They seem okay. (2) Is there a way to eliminate the post-processing of the
lists (i.e., *head* in *last* and *tail* in *init*)? (3) Why the complex
answers in the list archives? Am I missing something?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100714/b70db061/attachment-0001.html

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

Message: 2
Date: Wed, 14 Jul 2010 13:41:00 -0700
From: prad <p...@towardsfreedom.com>
Subject: [Haskell-beginners] Re: why is something different within a
        function when it comes out?
To: beginners@haskell.org
Message-ID: <20100714134100.7fe3f...@gom>
Content-Type: text/plain; charset=ISO-8859-1

On Wed, 14 Jul 2010 10:54:22 +0200
Chaddaï Fouché <chaddai.fou...@gmail.com> wrote:

> In fact xtract could be written :
> > xtract p c = (c =~ p :: [[String]]) !! 0 !! 1 
this is exactly what i was trying to do but couldn't figure out how to
write it because i couldn't get my head around the return. it seems so
simple when someone else does it. :D

thx for your explanations chaddai and you too michael.

this (as well as some crude attempts i've used earlier) work nicely on
text enclosed in single lines, but find nothing for multiple lines. in
python, there is a dotall or re.S flag so that things can be searched
for over \n in the text. i can't figure out how to do this here.

i looked at
http://hackage.haskell.org/packages/archive/regex-tdfa/1.1.3/doc/html/Text-Regex-TDFA.html
but am having difficulty figuring things out from the documentation -
and there doesn't seem to be any multiline feature.
surely there is some way to do this!

also, python had a re.sub so you can replace things using regex
searchs. how would you go about doing that in haskell?

-- 
In friendship,
prad

                                      ... with you on your journey
Towards Freedom
http://www.towardsfreedom.com (website)
Information, Inspiration, Imagination - truly a site for soaring I's


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

Message: 3
Date: Wed, 14 Jul 2010 23:02:28 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Thompson Exercise 9.13
To: beginners@haskell.org
Message-ID: <201007142302.29268.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="utf-8"

On Wednesday 14 July 2010 20:55:17, dan portin wrote:
> Hi,
>
> I am new to Haskell (and programming). Thompson's exercise 9.13  in
> *Craft of Functional Programming *gave me trouble. Searching the list
> archives, I saw people define init (xs), last (xs), and so on, in a
> variety of complex ways (using the Maybe monad,

Using Maybe isn't really complex, and for the implementations I sort of 
remember, the fact that Maybe is a Monad didn't play a role.

> using fairly complex
> post-processing). This seems to be a hard problem for beginners; at
> least, it was rather hard for me.

Yes, it's not easy before you're familiar with foldr.
If you don't try too hard to avoid any post-processing, it's not incredibly 
hard, though.

>
> The problem is to define the Prelude functions *init* and *last* using *
> foldr*. After a while, I came up with:
>
> -- *Exercise 9.13*: Use foldr (f, s, xs) to give definitions of the
> prelude functions
> -- unzip, last, and init.
>
> -- Clearly,
> --     [(x, y), (x1, y1)] = (x, y) : (x1, y1) : ([], [])

That last one is a typo,

[(x,y),(x1,y1)] = (x,y) : (x1,y1) : []

> --     foldr f ([], []) ((x, y):(x1, y1):[]) = f (x, y) (f (x1, y1) ([],
> []))
> -- Hence, f (x, y) (xs, ys) must equal (x:xs, y:ys) for any xs, ys.

Yup.

>
> unzip :: [(a, b)] -> ([a], [b])
> unzip xys = foldr f ([], []) xys
>  where f :: (a, b) -> ([a], [b]) -> ([a], [b])
>        f (x, y) (xs, ys) = (x:xs, y:ys)

However, this has a small problem,

take 3 . fst $ unzip [(i,i+1) | i <- [0 .. ]]

won't return with that definition of unzip.

The reason is subtle,

f (x,y) (xs,ys) = (x:xs,y:ys)

must inspect its second argument to match it with the pattern (xs,ys).
To do that, it must evaluate the nested call to f first.

f (x,y) (f (x1,y1) ([],[]))
~> match (xs,ys) with f (x1,y1) ([],[])
  ~> evaluate f (x1,y1) ([],[])
    ~> match (xs,ys) with ([],[])
    ~> matches
  ~> (x1:[], y1:[])
  ~> matches
~> (x:x1:[], y:y1:[])

Thus it needs to traverse the entire list before it can start assembling 
the result.
To avoid that, so the result can be assembled from the start of the list, 
you need to make the pattern match on the second argument lazy,

f (x,y) ~(xs,ys) = (x:xs,y:ys)

or

f (x,y) p = (x : fst p, y : snd p)

Now

f (x,y) (f (x1,y1) ([],[]))
~> let (xs,ys) = f (x1,y1) ([],[]) in (x:xs, y:ys)

and assembling the result starts immediately.

The tilde on a pattern makes that pattern irrefutable, the passed argument 
is bound to the pattern immediately and it will only be 
deconstructed/evaluated when needed.
It's sort of a "trust me, the argument will have that form, don't check it" 
message to the compiler/interpreter. Of course it will usually crash hard 
if the passed argument doesn't have the promised form.

In this case, it can't crash very hard, because the type checker doesn't 
allow anything but a pair to be passed as an argument, and a pair can only 
be (blah, blub) or _|_ (bottom). But if you use a tilde-pattern for a 
multi-constructor type, you better get it right.

>
> *last* :: [a] -> a
> last xs = head $ foldr f [] xs
>  where f :: a -> [a] -> [a]
>        f x [] = [x]
>        f x ys = ys ++ [x]

last xs = head (reverse xs), yes, it's correct, but not very pretty.
And not very efficient since it builds a left-associated nest of (++) 
applications and needs to pattern match to decide which branch to take.

last (1:2:3:4:[])
~> head $ foldr f [] (1:2:3:4:[])
~> head $ f 1 (f 2 (f 3 (f 4 [])))
~> head $ f 1 (f 2 (f 3 [4]))
~> head $ f 1 (f 2 ([4] ++ [3]))
~> head $ f 1 (([4] ++ [3]) ++ [2])
~> head $ ((([4] ++ [3]) ++ [2]) ++ [1]

a) in the second branch of f, you don't actually need to concatenate,

f x [] = [x]
f _ ys = ys

works too, but is faster.

b) you can get much faster by delaying the pattern match,

f x ys = (case ys of { [] -> x; y:_ -> y }) : []

>
> *init* :: [a] -> [a]
> init xs = tail $ foldr f [] xs
>  where f :: a -> [a] -> [a]
>        f x [] = [x]
>        f x (y:xs) = y : x : xs

Correct too, but again not very efficient since it has to find the last 
element and bubble it to the front.

Much faster:

import Data.Maybe (fromMaybe)

init' :: [a] -> [a]
init' = fromMaybe (error "init': empty list") . foldr f Nothing
    where
        f x mb = Just $ case mb of
                          Just xs -> x:xs
                          Nothing -> []

By delaying the pattern match on the Maybe until after the constructor is 
applied, we can start building the output with minimal delay (we only need 
to look whether there's a next list element to decide whether to cons it to 
the front or not).

>
> Now, these seemed to be hard questions. So, I have three questions: (1)
> are these correct? They work on test cases, and I *did* do some quick
> proofs. They seem okay. 

They are correct for finite lists, unzip and init above won't return on 
infinite lists (last shouldn't, so that's correct for infinite lists too).
They are not, strictly speaking, correct for infinite lists. But that is 
way beyond beginner territory :)

> (2) Is there a way to eliminate the
> post-processing of the lists (i.e., *head* in *last* and *tail* in
> *init*)? 

Not in a clean way.

Let us consider last first.

Suppose we had

last xs = foldr f z xs

without post-processing.
Since foldr f z [] = z and last [] = error "Prelude.last: empty list",
we must have z = error "...".
Now last (... x:[]) = x and
foldr f z (... x:[]) = ... (f x z)

So f x y = y if y is not error "..." and f x (error "...") = x, that means 
f would have to find out whether its second argument is a specific error 
and return its first argument in that case, otherwise its second argument.
It's possible to do that, but very unclean.

For init, the situation is similar, the value for the empty list case 
supplied to foldr must be an error and the combining function needs to know 
whether its second argument is an error and do things accordingly.

> (3) Why the complex answers in the list archives? Am I missing
> something?

Don't know. In part, because beginners didn't find the easiest ways, I 
suppose, in part because it's not too easy to give efficient 
implementations with foldr.



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

Message: 4
Date: Wed, 14 Jul 2010 23:12:47 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Re: why is something different within
        a       function when it comes out?
To: beginners@haskell.org
Cc: prad <p...@towardsfreedom.com>
Message-ID: <201007142312.47417.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

On Wednesday 14 July 2010 22:41:00, prad wrote:
> also, python had a re.sub so you can replace things using regex
> searchs. how would you go about doing that in haskell?

There's subRegex in Text.Regex in the regex-compat package (don't know if 
it's also provided in other packages).


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

Message: 5
Date: Tue, 13 Jul 2010 14:35:45 +0100
From: Tim Cowlishaw <t...@harmonypark.net>
Subject: [Haskell-beginners] My first functioning haskell project - a
        steganography utility
To: beginners@haskell.org
Message-ID: <749803fa-3b47-43b4-8f83-2e229c4d7...@harmonypark.net>
Content-Type: text/plain; charset=us-ascii

Hey there all,

I've just completed my first functional haskell project - a simple utility for 
steganography - hiding messages within the least significant bit of another 
sort of data file.

Therefore, I was wondering if any of you had any pointers about how I could 
refactor or otherwise improve my code? Any input would be greatly appreciated - 
whether howling great errors or smaller points of "good haskell style". In 
particular, I'd be really interested in whether my type declarations are 
correct - for instance, whether I have been to specific or not specific enough 
in specifying the types of my functions (Integral vs Int, etc).

In addition, I keep feeling that my Steganograph 'smells like' a monad and/or 
functor , as it 'wraps around' a message - however, I'm having trouble defining 
quite how I could achieve construct a monadic type representing a steganograph. 
Is my hunch incorrect, or is there a way of doing this that I haven't yet 
discovered?

The sources is here: http://gist.github.com/473862


Cheers,

Tim



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

Message: 6
Date: Wed, 14 Jul 2010 11:20:07 +1200
From: "Richard O'Keefe" <o...@cs.otago.ac.nz>
Subject: [Haskell-beginners] Re: [Haskell-cafe] lists of arbitrary
        depth
To: <chrisd...@googlemail.com>
Cc: beginners@haskell.org, haskell-c...@haskell.org
Message-ID: <40114aa6-df7f-40d5-84c5-951c59f7f...@cs.otago.ac.nz>
Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes


On Jul 13, 2010, at 9:00 PM, Christopher Done wrote:

> On 13 July 2010 10:58, vadali <shlomivak...@gmail.com> wrote:\
>>
>> i want to define a function which takes as a parameter a list which  
>> can
>> contain other lists, eg. [1,[2,3],[4,[5,6]]]

What would the type of a list like that be?

What you _can_ do is
        data List_Or t = Item t | List [List_Or t]
                         deriving (Eq, Ord, Show)
and have a "list" like
        ell :: List_Or Int
        ell = List [Item 1, List [Item 2, Item 3], List [Item 4,
              List [Item 5, Item 6]]]

>> how would i define a function that can iterate through the items so  
>> (in this
>> example)
>> iter1 = 1
>> iter2 = [2,3]
>> iter3 = [4,[5,6]]
>>

Then you can write functions like
        iter n (List x) = head (drop (n-1) x)
with examples
        *Main> iter 1 ell
        Item 1
        *Main> iter 2 ell
        List [Item 2,Item 3]
        *Main> iter 3 ell
        List [Item 4,List [Item 5,Item 6]]

>> ( can i do that without using the Tree data type? )

This basically _is_ a tree data type, even if not THE Tree
data type.  That's because nested lists are trees.

>


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

Message: 7
Date: Wed, 14 Jul 2010 13:20:09 -0400
From: "Ben Wise" <bw...@oceanofstones.net>
Subject: [Haskell-beginners] A difficult package
To: beginners@haskell.org
Message-ID: <1ad2722de5e7b6b1106b813bc85eda27.squir...@telavant.com>
Content-Type: text/plain;charset=iso-8859-1

Folks,

I'm trying to work through Conrad Barski's Haskell tutorial,
http://www.lisperati.com/haskell/, and I've run into a difficult package
problem. I've googled around for two days, but nothing seems to work.

Basically, I can not get it recognize matchRegex, mkRegex, and similar.
They are all in the Text.Regex.Posix package, and version 0.94.1 is
installed according to 'cabal list regex'. The 'import Text.Regex.Posix'
line compiles just fine, so it is finding the package: it just doesn't
find the symbols in it ?!

But (under all four combinations of command line ghc or Leksah on Windows
7 or Ubuntu), it keeps trying to use the 'base' version, not posix. At
least, that's what 'ghc -v main.hs' seems to be saying. In Leksah, adding
some of the suggested build dependencies fixed earlier problems with
importing the Text and Random things, but adding 'regex-compat' as
suggested did not help.

Has anyone else gotten CB's tutorial to work?

Any suggestions as to how to get Text.Regex.Posix imported?

-- 
Ben Wise, PhD
0xCAF514E1



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

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


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

Reply via email to