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:  MD2 Implementation (Rafael Gustavo da Cunha Pereira Pinto)
   2.  Re: Hudak state emulation discussion - can you   give me some
      idea? (Benjamin L.Russell)
   3.  Understanding recursion in Haskell. (Caitlin)
   4. Re:  Understanding recursion in Haskell. (Adrian Neumann)
   5. Re:  Re: Hudak state emulation discussion - can   you give me
      some idea? (Girish Bhat)


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

Message: 1
Date: Tue, 17 Mar 2009 11:15:10 -0300
From: Rafael Gustavo da Cunha Pereira Pinto
        <rafaelgcpp.li...@gmail.com>
Subject: Re: [Haskell-beginners] MD2 Implementation
To: Sean Bartell <wingedtachik...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <351ff25e0903170715s6c11ae98pe7892acae1271...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I am studying your code, and noticed you used a ByteString for your "table"

This is bad, because you are doing a O(n) lookup every time you do a " b
`xor` table `B.index` fromIntegral t "



On Mon, Mar 16, 2009 at 00:33, Sean Bartell <wingedtachik...@gmail.com>wrote:

> I've just recently started learning Haskell, and I wrote an MD2
> implementation. This version is correct, but crashes on large files
> because of the weak evaluation. What I'm wondering is, what's the sort
> of thought-process I would go through to find the problem areas and
> fix it?
>
> Also, please post any suggestions you have for this code, for style or
> whatever :).
>
> {-# LANGUAGE BangPatterns #-}
>
> module MD2 (md2) where
>
> import qualified Data.ByteString as B
> import Data.Bits (xor)
> import Data.List (foldl', mapAccumL)
> import Data.Word (Word8)
>
> table = B.pack [0x29, 0x2E, 0x43, 0xC9, 0xA2, 0xD8, 0x7C, 0x01,
>                0x3D, 0x36, 0x54, 0xA1, 0xEC, 0xF0, 0x06, 0x13,
>                0x62, 0xA7, 0x05, 0xF3, 0xC0, 0xC7, 0x73, 0x8C,
>                0x98, 0x93, 0x2B, 0xD9, 0xBC, 0x4C, 0x82, 0xCA,
>                0x1E, 0x9B, 0x57, 0x3C, 0xFD, 0xD4, 0xE0, 0x16,
>                0x67, 0x42, 0x6F, 0x18, 0x8A, 0x17, 0xE5, 0x12,
>                0xBE, 0x4E, 0xC4, 0xD6, 0xDA, 0x9E, 0xDE, 0x49,
>                0xA0, 0xFB, 0xF5, 0x8E, 0xBB, 0x2F, 0xEE, 0x7A,
>                0xA9, 0x68, 0x79, 0x91, 0x15, 0xB2, 0x07, 0x3F,
>                0x94, 0xC2, 0x10, 0x89, 0x0B, 0x22, 0x5F, 0x21,
>                0x80, 0x7F, 0x5D, 0x9A, 0x5A, 0x90, 0x32, 0x27,
>                0x35, 0x3E, 0xCC, 0xE7, 0xBF, 0xF7, 0x97, 0x03,
>                0xFF, 0x19, 0x30, 0xB3, 0x48, 0xA5, 0xB5, 0xD1,
>                0xD7, 0x5E, 0x92, 0x2A, 0xAC, 0x56, 0xAA, 0xC6,
>                0x4F, 0xB8, 0x38, 0xD2, 0x96, 0xA4, 0x7D, 0xB6,
>                0x76, 0xFC, 0x6B, 0xE2, 0x9C, 0x74, 0x04, 0xF1,
>                0x45, 0x9D, 0x70, 0x59, 0x64, 0x71, 0x87, 0x20,
>                0x86, 0x5B, 0xCF, 0x65, 0xE6, 0x2D, 0xA8, 0x02,
>                0x1B, 0x60, 0x25, 0xAD, 0xAE, 0xB0, 0xB9, 0xF6,
>                0x1C, 0x46, 0x61, 0x69, 0x34, 0x40, 0x7E, 0x0F,
>                0x55, 0x47, 0xA3, 0x23, 0xDD, 0x51, 0xAF, 0x3A,
>                0xC3, 0x5C, 0xF9, 0xCE, 0xBA, 0xC5, 0xEA, 0x26,
>                0x2C, 0x53, 0x0D, 0x6E, 0x85, 0x28, 0x84, 0x09,
>                0xD3, 0xDF, 0xCD, 0xF4, 0x41, 0x81, 0x4D, 0x52,
>                0x6A, 0xDC, 0x37, 0xC8, 0x6C, 0xC1, 0xAB, 0xFA,
>                0x24, 0xE1, 0x7B, 0x08, 0x0C, 0xBD, 0xB1, 0x4A,
>                0x78, 0x88, 0x95, 0x8B, 0xE3, 0x63, 0xE8, 0x6D,
>                0xE9, 0xCB, 0xD5, 0xFE, 0x3B, 0x00, 0x1D, 0x39,
>                0xF2, 0xEF, 0xB7, 0x0E, 0x66, 0x58, 0xD0, 0xE4,
>                0xA6, 0x77, 0x72, 0xF8, 0xEB, 0x75, 0x4B, 0x0A,
>                0x31, 0x44, 0x50, 0xB4, 0x8F, 0xED, 0x1F, 0x1A,
>                0xDB, 0x99, 0x8D, 0x33, 0x9F, 0x11, 0x83, 0x14]
>
> -- NOTE: There's a problematic typo in RFC 1319 in section 3.2. It says
> -- Set C[j] to S[c xor L], but it should be Set C[j] to C[j] xor S[c xor
> L].
>
> type Block = B.ByteString
>
> two x = (x, x)
> applySnd f (x, y) = (x, f y)
>
> zeroBlock = B.replicate 16 0
> checksumInitial = (0, zeroBlock)
>
> foldlBlocks :: (a -> Block -> a) -> a -> B.ByteString -> a
> foldlBlocks f v x | B.null x = v
>                  | otherwise = foldlBlocks f v' rest
>                        where (block, rest) = B.splitAt 16 x
>                              !v' = f v block
>
> checksumBlock :: (Word8, Block) -> Block -> (Word8, Block)
> checksumBlock (l, cs) bs = applySnd B.pack $ mapAccumL updateL l $ B.zip cs
> bs
>    where updateL l (c, b) = two $ c `xor` table `B.index`
> fromIntegral (l `xor` b)
>
> doBlock :: Block -> Block -> Block
> doBlock ds bs = B.take 16 xs'
>    where xs = ds `B.append` bs `B.append` B.pack (B.zipWith xor ds bs)
>          (_, xs') = foldl' doRound (0, xs) [0..17]
>          doRound (t, xs) n = let (t', xs') = B.mapAccumL updateT t xs
>                              in (t' + n, xs')
>          updateT t b = two $ b `xor` table `B.index` fromIntegral t
>
> doBlockAndCS (csState, blockState) block = (checksumBlock csState
> block, doBlock blockState block)
>
> padding n = B.replicate n (fromIntegral n)
>
> md2 :: B.ByteString -> Block
> md2 bs = let padded = bs `B.append` padding (16 - B.length bs `mod` 16)
>             ((_, cksum), state) = foldlBlocks doBlockAndCS
> (checksumInitial, zeroBlock) padded
>         in doBlock state cksum
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



-- 
Rafael Gustavo da Cunha Pereira Pinto
Electronic Engineer, MSc.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090317/8da257d2/attachment-0001.htm

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

Message: 2
Date: Wed, 18 Mar 2009 11:49:35 +0900
From: Benjamin L.Russell <dekudekup...@yahoo.com>
Subject: [Haskell-beginners] Re: Hudak state emulation discussion -
        can you give me some idea?
To: beginners@haskell.org
Message-ID: <ntm0s4hkp9j8difkefvrpgv34uumgeh...@4ax.com>
Content-Type: text/plain; charset=iso-2022-jp

On Tue, 17 Mar 2009 14:32:24 +0530, Girish Bhat
<girishbhat6...@gmail.com> wrote:

>Hi Everyone,
>
>I was going through the classic Hudak paper "Conception, Evolution,
>and Application of Functional Programming".
>Probably the most valuable part is towards the end where he talks
>about how state is represented in Haskell.
>On Page 48 of the PDF (page 406 of the ACM Computing survey volume),
>he gives the following equations
>"For expository purposes we would like to make the state as implicit
>as possible, and thus we express the result as a composition of
>higher-order functions. To facilitate this and to make the result look
>as much like the original program as possible, we define the following
>higher-order infix operators and functions":
>
>
>1 f:=g =\s -> +fs(gs)
>
>2? ?f;g =\s -> g(fs)=\s-+fs(gs)
>
>3? ?f;g =\s -> g(fs)
>
>4 goto f = f
>
>5 f+‘g=\s-+fs+gs
>
>6 f<‘g=\s-+fs<gs
>
>7 if’ p c = \s + (if (p s) then (c s) else s)
>
>
>
>Unfortunately I am unable to parse/understand what he is doing here.
>My closure understanding too seems to be wonky. :)
>Would someone be kind enough to translate each of the above into plain
>english and explain how to read such eqns in the future?

(FYI, there is a copy of the above-mentioned paper that doesn't
require an ACM account available at
http://www.cs.berkeley.edu/~jcondit/pl-prelim/hudak89functional.pdf.)

Hudak is just defining a series of higher-order infix operators and
functions.  (You have made some notational errors in the
above-mentioned notation, so I am revising it to match the paper as
below.)  A backslash denotes a lambda symbol; i.e., whatever
immediately follows the lambda is a parameter in the following
equation.  Specifically:  

>1 f := g =\s -> f s (g s)

In other words, the infix operator ':=' works between functions f and
g such that lambda s -> f s (g s).

>2 f ; g = \s -> g (f s)

In other words, the infix operator ';' works between functions f and g
such that lambda s -> g (f s).

>3? ?f;g =\s -> g(fs)

I couldn't find this equation on p. 406 of the volume; where did you
find it?

>4 goto f = f

In other words, the function "goto" applied to f is defined as simply
f.

>5 f +' g = \s -> f s + g s

In other words, the infix operator '+'' works between functions f and
g such that lambda s -> f s + g s.

>6 f <' g = \s -> f s < g s

In other words, the infix operator '<'' works between functions f and
g such that lambda s -> f s < g s.

>7 if' p c = \s -> (if (p s) then (c s) else s)

In other words, the function "if'" applied to functions p and c is
such that lambda p c -> (if (p s) then (c s) else s).

Hope this helps....

-- Benjamin L. Russell
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
"Furuike ya, kawazu tobikomu mizu no oto." 
-- Matsuo Basho^ 



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

Message: 3
Date: Tue, 17 Mar 2009 22:28:50 -0700 (PDT)
From: Caitlin <the_polymo...@rocketmail.com>
Subject: [Haskell-beginners] Understanding recursion in Haskell.
To: beginners@haskell.org
Message-ID: <440511.56077...@web50808.mail.re2.yahoo.com>
Content-Type: text/plain; charset=us-ascii


Hi.

As a Haskell beginner, I was wondering if someoneone could explain how the 
following programs function (pardon the pun)?

maximum' :: (Ord a) => [a] -> a  
maximum' [] = error "maximum of empty list"  
maximum' [x] = x  
maximum' (x:xs)   
    | x > maxTail = x  
    | otherwise = maxTail  
    where maxTail = maximum' xs


take' :: (Num i, Ord i) => i -> [a] -> [a]  
take' n _  
    | n <= 0   = []  
take' _ []     = []  
take' n (x:xs) = x : take' (n-1) xs 



zip' :: [a] -> [b] -> [(a,b)]  
zip' _ [] = []  
zip' [] _ = []  
zip' (x:xs) (y:ys) = (x,y):zip' xs ys 



quicksort :: (Ord a) => [a] -> [a]  
quicksort [] = []  
quicksort (x:xs) =   
    let smallerSorted = quicksort [a | a <- xs, a <= x]  
        biggerSorted = quicksort [a | a <- xs, a > x]  
    in  smallerSorted ++ [x] ++ biggerSorted


Thanks,

Caitlin 


      


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

Message: 4
Date: Wed, 18 Mar 2009 08:05:09 +0100
From: Adrian Neumann <aneum...@inf.fu-berlin.de>
Subject: Re: [Haskell-beginners] Understanding recursion in Haskell.
To: beginners@haskell.org
Message-ID: <e84c9780-c8c0-4856-8d3c-4ca73e16b...@inf.fu-berlin.de>
Content-Type: text/plain; charset="us-ascii"


Am 18.03.2009 um 06:28 schrieb Caitlin:

>
> Hi.
>
> As a Haskell beginner, I was wondering if someoneone could explain  
> how the following programs function (pardon the pun)?
>


This function takes some type which has an ordering defined, i.e. you  
can compare its elements to one another

> maximum' :: (Ord a) => [a] -> a

it doesn't work for an empty list

> maximum' [] = error "maximum of empty list"

the maximum of a one element list is the lone element. this is the  
base case which will be eventually reached by the recursion

> maximum' [x] = x

should the list have more than one element

> maximum' (x:xs)

compare the first element to the maximum of the other elements. if  
it's greater, it's the maximum

>     | x > maxTail = x

otherwise the maximum of the other elements is the maximum of the  
whole list

>     | otherwise = maxTail

how to compute the maximum of the other elements? just use this  
function again. after a while we will only have one element left and  
reach the base case above.

>     where maxTail = maximum' xs
>
>

This function takes a number and a list of some type a

> take' :: (Num i, Ord i) => i -> [a] -> [a]

first, ignore the list and check whether n is <= 0. in this case  
return an empty list. this is the base case, that's eventually  
reached by the recursion

> take' n _
>     | n <= 0   = []

otherwise, check if the list is empty. this is another base case.

> take' _ []     = []

if neither n<=0 or the list empty, take the first element, x, and put  
it on front of the prefix of length (n-1) of the other elements. use  
take' again, to get that prefix. after a while either n is 0 or there  
are no more elements in the list and we reach the  base case

> take' n (x:xs) = x : take' (n-1) xs
>
>

Take two lists

>
> zip' :: [a] -> [b] -> [(a,b)]

if either one of them is empty, stop

> zip' _ [] = []
> zip' [] _ = []

otherwise prepend a tuple, build from the two first elements to the  
zipped list of the other elements. after a while one of the lists  
should become empty and the base case is reached.

> zip' (x:xs) (y:ys) = (x,y):zip' xs ys
>
>
>
> quicksort :: (Ord a) => [a] -> [a]

empty list -> nothing to do

> quicksort [] = []
> quicksort (x:xs) =

otherwise take the first element of the list and use it to split the  
list in two halves. one with all the elements that are smaller or  
equal than x, the other one with all those that are bigger. now sort  
them and put x in the middle. that should give us a sorted whole. how  
to sort them? just use quicksort again! after some splitting the  
lists will become empty and the recursion stops.

>     let smallerSorted = quicksort [a | a <- xs, a <= x]
>         biggerSorted = quicksort [a | a <- xs, a > x]
>     in  smallerSorted ++ [x] ++ biggerSorted

-------------- next part --------------
A non-text attachment was scrubbed...
Name: PGP.sig
Type: application/pgp-signature
Size: 194 bytes
Desc: Signierter Teil der Nachricht
Url : 
http://www.haskell.org/pipermail/beginners/attachments/20090318/9f494f3f/PGP-0001.bin

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

Message: 5
Date: Wed, 18 Mar 2009 13:02:34 +0530
From: Girish Bhat <girishbhat6...@gmail.com>
Subject: Re: [Haskell-beginners] Re: Hudak state emulation discussion
        - can   you give me some idea?
To: "Benjamin L.Russell" <dekudekup...@yahoo.com>
Cc: beginners@haskell.org
Message-ID:
        <cdef83d60903180032j3b831103lb0310f4cdc842...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

> (FYI, there is a copy of the above-mentioned paper that doesn't
> require an ACM account available at
> http://www.cs.berkeley.edu/~jcondit/pl-prelim/hudak89functional.pdf.)
>
> Hudak is just defining a series of higher-order infix operators and
> functions.  (You have made some notational errors in the
> above-mentioned notation, so I am revising it to match the paper as
> below.)  A backslash denotes a lambda symbol; i.e., whatever

Sorry about that.

> >3? ?f;g =\s -> g(fs)
>
> I couldn't find this equation on p. 406 of the volume; where did you
> find it?
>

Again my transcription error.

> In other words, the function "if'" applied to functions p and c is
> such that lambda p c -> (if (p s) then (c s) else s).
>
> Hope this helps....
>
Thanks! It does. I think what threw me was that while there is enough
redundancy in what he states for someone more clever than me, he would
have explicitly stated before hand  that he was defining the operators
[:=], [+'], ['if] etc.:)

thanks again.


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

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


End of Beginners Digest, Vol 9, Issue 18
****************************************

Reply via email to