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:  Empty or Tree? (Adrien Haxaire)
   2. Re:  Empty or Tree? (Michael Schober)
   3.  Processing a list of files the Haskell way (Michael Schober)
   4. Re:  Processing a list of files the Haskell way (edgar klerks)
   5. Re:  Problem with developing NCurses program (Alessandro Pezzoni)
   6. Re:  Processing a list of files the Haskell way (Chadda? Fouch?)
   7. Re:  constant set (Ovidiu Deac)
   8. Re:  constant set (Lyndon Maydwell)


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

Message: 1
Date: Sat, 10 Mar 2012 12:06:03 +0100
From: Adrien Haxaire <adr...@haxaire.org>
Subject: Re: [Haskell-beginners] Empty or Tree?
To: beginners@haskell.org
Message-ID: <20120310110603.GA2188@arch>
Content-Type: text/plain; charset=iso-8859-1

On Sat, Mar 10, 2012 at 10:28:43AM +0000, bahad?r altan wrote:
> Hello everyone. I'm trying to write a code which works on binary trees. When 
> I write code like this ?with a tree with empty nodes :
> 
> data Tree ?= ?Empty | Node ?Integer Tree Tree
> 
> function Node a (Node b Empty Empty)??(Node c Empty Empty)
> 
> it works fine.?
> But when I try to create a more generic code like this ?which could ?work 
> with trees who don't have empty nodes in grandchild level :?
> 
> function Node a (Node b Tree Tree)??(Node c Tree Tree )?
> 
> 
> I get this error :?Undefined data constructor "Tree"
> 
> Can you help me with creating more generic code please?
> Thanks

Hello,

You defined a Tree as an Empty or a Node. So to build it, you can use only 
Empty or Node, which is what you do in your first function. In the second one 
however, you use Tree, which is the type, not the constructor.

If you use them it will look like : 

function Node a (Node b t1 t2) (Node c t3 t4)
  where
    t1 = Empty
    t2 = Node d Empty Empty
    ...

Adding the function signature before your function implementatio help sort 
things out for the parameters you need: t1, to t4, to a to c, etc

Hope that helps.
Adrien

-- 
Adrien Haxaire 
www.adrienhaxaire.org | @adrienhaxaire



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

Message: 2
Date: Sat, 10 Mar 2012 12:45:07 +0100
From: Michael Schober <micha-scho...@web.de>
Subject: Re: [Haskell-beginners] Empty or Tree?
To: beginners@haskell.org
Message-ID: <4f5b3ec3.50...@web.de>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

> But when I try to create a more generic code like this which could work
> with trees who don't have empty nodes in grandchild level :
>
> function Node a (Node b Tree Tree) (Node c Tree Tree )

The problem is that 'Tree' is a type, not a constructor. Someone correct 
me, if I'm mistaken (this is my first post to the mailing-list, yieah 
:-)), but what seems to cause the problem is that the pattern matcher 
needs constructors, so it can determine, whether a pattern can produce 
an input data.

There are several solutions. If you don't need the further subtrees, 
leave them fully unspecified via the underscore:

function (Node a (Node b _ _) (Node c _ _)) = ...

or you could give them variable names like this:

function (Node a (Node b bl br) (Node c cl cr)) = ...

where bl, br, cl, and cr are variables of the type Tree. However, what 
you might want to accomplish is a recursive function over the recursive 
type to get a fully generic code. This usually looks something like this:

-- a generic recursive function
cFunction :: Tree -> a
cFunction Empty = ...
cFunction (Node i l r) = f i (cFunction l) (cFunction r)
   where
     f :: Integer -> a -> a -> a
     f int recLeft recRight = ...

Hope that helped.



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

Message: 3
Date: Sat, 10 Mar 2012 12:55:06 +0100
From: Michael Schober <micha-scho...@web.de>
Subject: [Haskell-beginners] Processing a list of files the Haskell
        way
To: beginners@haskell.org
Message-ID: <4f5b411a.1060...@web.de>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hi everyone,

I'm currently trying to solve a problem in which I have to process a 
long list of files, more specifically I want to compute MD5 checksums 
for all files.

I have code which lists me all the files and holds it in the following 
data structure:

data DirTree = FileNode FilePath | DirNode FilePath [DirTree]

I tried the following:

-- calculates MD5 sums for all files in a dirtree
addChecksums :: DirTree -> IO [(DirTree,MD5Digest)]
addChecksums dir = addChecksums' [dir]
   where
     addChecksums' :: [DirTree] -> IO [(DirTree,MD5Digest)]
     addChecksums' [] = return []
     addChecksums' (f@(FileNode fp):re) = do
       bytes <- BL.readFile fp
       rest <- addChecksums' re
       return ((f,md5 bytes):rest)
     addChecksums' ((DirNode fp filelist):re) = do
       efiles <- addChecksums' filelist
       rest <- addChecksums' re
       return $ efiles ++ rest


This works fine, but only for a small number of files. If I try it on a 
big directory tree, the memory gets junked up and it aborts with an 
error message telling me that there are too many open files.

So I guess, I have to sequentialize the code a little bit more. But at 
the same time, I want to keep it as functional as possible and I don't 
want to write C-like code.

What would be the Haskell way to do something like this?

Thanks for all the input,
Michael






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

Message: 4
Date: Sat, 10 Mar 2012 13:32:25 +0100
From: edgar klerks <edgar.kle...@gmail.com>
Subject: Re: [Haskell-beginners] Processing a list of files the
        Haskell way
To: Michael Schober <micha-scho...@web.de>
Cc: beginners@haskell.org
Message-ID:
        <cagauytmi-n79uym+pbqv5tceh_sk74cryos5qxl_b-rrx1r...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi Michael,

Your code has a very C-like feel to it. I would first separate the
reading of the directory structure and the files and the walk over the
tree. Something like this:

data DirTree = FileNode FilePath | DirNode FilePath [DirTree]

walkDirTree :: (FilePath -> a) -> DirTree -> [a]
walkDirTree f (FileNode fp)  = [f fp]
walkDirTree f (DirNode fp fs)  = f fp : (fs >>= (walkDirTree f))


I know this isn't what you need, I didn't read your solution properly
when I wrote it, but it is a useful hint. The separation of the pure
part and the IO part of your program is important.

The problem of the open files is another beast. You are using lazy
bytestrings. Lazy bytestrings can keep the file descriptor open as
long as you haven't read all the bytes. I suspect you need to add some
strictness to your program. You can try to use strict bytestrings. Or
use seq to evaluate the md5 thunks earlier in the program execution.

Greets,

Edgar

On 3/10/12, Michael Schober <micha-scho...@web.de> wrote:
> Hi everyone,
>
> I'm currently trying to solve a problem in which I have to process a
> long list of files, more specifically I want to compute MD5 checksums
> for all files.
>
> I have code which lists me all the files and holds it in the following
> data structure:
>
> data DirTree = FileNode FilePath | DirNode FilePath [DirTree]
>
> I tried the following:
>
> -- calculates MD5 sums for all files in a dirtree
> addChecksums :: DirTree -> IO [(DirTree,MD5Digest)]
> addChecksums dir = addChecksums' [dir]
>    where
>      addChecksums' :: [DirTree] -> IO [(DirTree,MD5Digest)]
>      addChecksums' [] = return []
>      addChecksums' (f@(FileNode fp):re) = do
>        bytes <- BL.readFile fp
>        rest <- addChecksums' re
>        return ((f,md5 bytes):rest)
>      addChecksums' ((DirNode fp filelist):re) = do
>        efiles <- addChecksums' filelist
>        rest <- addChecksums' re
>        return $ efiles ++ rest
>
>
> This works fine, but only for a small number of files. If I try it on a
> big directory tree, the memory gets junked up and it aborts with an
> error message telling me that there are too many open files.
>
> So I guess, I have to sequentialize the code a little bit more. But at
> the same time, I want to keep it as functional as possible and I don't
> want to write C-like code.
>
> What would be the Haskell way to do something like this?
>
> Thanks for all the input,
> Michael
>
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



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

Message: 5
Date: Sat, 10 Mar 2012 13:38:28 +0100
From: Alessandro Pezzoni <alessandro_pezz...@lavabit.com>
Subject: Re: [Haskell-beginners] Problem with developing NCurses
        program
To: Aditya Manthramurthy <aditya....@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <cajbh-xcwzdysebphx+7annerpjy8pj0xsou7f0zccjapvgc...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

> I am using ghc 7.0.3 which comes with the latest Ubuntu (11.10). Would
> installing the latest ghc release help?

As they say it has been fixed in ghc upstream, I suppose that yes,
upgrading ghc should definitely help.

Alessandro

-- 
If God had intended for email to be written in HTML, then the
traditional signoff of prayers would be </amen> -- Tom Liston




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

Message: 6
Date: Sat, 10 Mar 2012 13:48:22 +0100
From: Chadda? Fouch? <chaddai.fou...@gmail.com>
Subject: Re: [Haskell-beginners] Processing a list of files the
        Haskell way
To: Michael Schober <micha-scho...@web.de>
Cc: beginners@haskell.org
Message-ID:
        <CANfjZRapghPC+Pem7vP4zNvuMtLb=pr+idflcppe7grqrgm...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Sat, Mar 10, 2012 at 12:55 PM, Michael Schober <micha-scho...@web.de> wrote:
> Hi everyone,
>
> I'm currently trying to solve a problem in which I have to process a long
> list of files, more specifically I want to compute MD5 checksums for all
> files.
>
> I have code which lists me all the files and holds it in the following data
> structure:
>
> data DirTree = FileNode FilePath | DirNode FilePath [DirTree]
>
> I tried the following:
>
> -- calculates MD5 sums for all files in a dirtree
> addChecksums :: DirTree -> IO [(DirTree,MD5Digest)]
> addChecksums dir = addChecksums' [dir]
> ?where
> ? ?addChecksums' :: [DirTree] -> IO [(DirTree,MD5Digest)]
> ? ?addChecksums' [] = return []
> ? ?addChecksums' (f@(FileNode fp):re) = do
> ? ? ?bytes <- BL.readFile fp
> ? ? ?rest <- addChecksums' re
> ? ? ?return ((f,md5 bytes):rest)

You're not computing the md5 sums before you have done the same for
all other files in the directory... And since you're being lazy you
don't even compute it _at all_ before you ask for it leter in your
program.

If readFile wasn't lazy, you would need to keep all the contents of
those files in memory until after addChecksums is completely finished
(which would be a big problem in itself), but since readFile is lazy,
those file aren't read either until you need their content. But
they're still opened, so you get a lot of opened handle you don't
close, and opened handle are a limited resource in any OS so...

What you need to do is computing the md5 sums as soon as you see the
file and before you do anything else, so :

>    addChecksums' (f@(FileNode fp):re) = do
>      bytes <- BL.readFile fp
>      let !md5sum = md5 bytes
>      rest <- addChecksums' re
>      return ((f,md5sum):rest)

The ! before md5sum indicates that this let-binding should be
immediately computed rather than deferred until needed which is the
norm for let-binding. Don't forget to add {-# LANGUAGE BangPattern #-}
at the beginning of your file. Since the file is read to its end by
md5, the handle is automatically closed, so you shouldn't have the
same problem.

Note that you solution isn't very "functional-like", but rather
imperative. On the other hand, making it more functional in this
particular case come with its own brand of subtle difficulties.

-- 
Jeda?



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

Message: 7
Date: Sat, 10 Mar 2012 16:45:27 +0200
From: Ovidiu Deac <ovidiud...@gmail.com>
Subject: Re: [Haskell-beginners] constant set
To: Ertugrul S?ylemez <e...@ertes.de>, emacs...@gmail.com
Cc: beginners@haskell.org
Message-ID:
        <cakvse7v0x74exlvw9t1fw9buzspujpwfoud-17u6-lp8eux...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Thanks for the answers. I guess my example with the colors was misleading.
In that case it makes sense to use an abstract type.

In my case an abstract type is not ok. What I want is a set of int
constants i.e. some names for some ints that I will use in my code, to
avoid magic numbers in the code.

Of course I could define them like this:
red = 1
blue = 2

...but that would pollute the namespace

Also I don't want to define them in a separate file. I would like to define
them in the same file where I use them.

I already tried this approach:

module Main where

import ....

module Colors where
  red = 1
  blue = 2
.....

but the compiler complains at the line "module Colors where". It says:
parse error on input `module'


In Haskell this would usually be an abstract type:
>
>    data Color = Red | Blue | ...
>
> You could then use functions to convert between integers and colors.
>
>    fromColor :: Color -> Int
>    toColor   :: Int -> Maybe Color
>
> You could also derive an Enum instance and get the conversion functions
> 'fromEnum' and 'toEnum' for free, although in that case the 'toEnum'
> function is less safe (no Maybe):
>
>    data Color = Red | Blue | ...
>                 deriving Enum
>
>    fromEnum :: Color -> Int
>    toEnum   :: Int -> Color
>
>
> Greets,
> Ertugrul
>
> --
> nightmare = unsafePerformIO (getWrongWife >>= sex)
> http://ertes.de/
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120310/eed0fe7e/attachment-0001.htm>

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

Message: 8
Date: Sat, 10 Mar 2012 22:56:03 +0800
From: Lyndon Maydwell <maydw...@gmail.com>
Subject: Re: [Haskell-beginners] constant set
To: Ovidiu Deac <ovidiud...@gmail.com>
Cc: beginners@haskell.org, Ertugrul S?ylemez <e...@ertes.de>
Message-ID:
        <CAM5QZtzhW05O2xPPzWttyneR86z=7AosdaVsjFp7Cz=2vma...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

If you simply want color names to correspond to Ints, you can just
define them at the top level:

> red = 1
> blue = 2
> green = 3

What are you trying to gain here by having the color namespace?

2012/3/10 Ovidiu Deac <ovidiud...@gmail.com>:
> Thanks for the answers. I guess my example with the colors was misleading.
> In that case it makes sense to use an abstract type.
>
> In my case an abstract type is not ok. What I want is a set of int constants
> i.e. some names for some ints that I will use in my code, to avoid magic
> numbers in the code.
>
> Of course I could define them like this:
> red = 1
> blue = 2
>
> ...but that would pollute the namespace
>
> Also I don't want to define them in a separate file. I would like to define
> them in the same file where I use them.
>
> I already tried this approach:
>
> module Main where
>
> import ....
>
> module Colors where
> ? red = 1
> ? blue = 2
> .....
>
> but the compiler complains at the line "module Colors where". It says: parse
> error on input `module'
>
>
>> In Haskell this would usually be an abstract type:
>>
>> ? ?data Color = Red | Blue | ...
>>
>> You could then use functions to convert between integers and colors.
>>
>> ? ?fromColor :: Color -> Int
>> ? ?toColor ? :: Int -> Maybe Color
>>
>> You could also derive an Enum instance and get the conversion functions
>> 'fromEnum' and 'toEnum' for free, although in that case the 'toEnum'
>> function is less safe (no Maybe):
>>
>> ? ?data Color = Red | Blue | ...
>> ? ? ? ? ? ? ? ? deriving Enum
>>
>> ? ?fromEnum :: Color -> Int
>> ? ?toEnum ? :: Int -> Color
>>
>>
>> Greets,
>> Ertugrul
>>
>> --
>> nightmare = unsafePerformIO (getWrongWife >>= sex)
>> http://ertes.de/
>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners@haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



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

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


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

Reply via email to