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:  What is the best practice for code] (Brent Yorgey)
   2. Re:  turning a value into an expression (Brent Yorgey)
   3. Re:  Re: Either Monadic Trouble (Michael Snoyman)
   4. Re:  What is the best practice for code] (Chadda? Fouch?)
   5.  Double Trouble (Philip Scott)
   6. Re:  Double Trouble (Krzysztof Skrz?tnicki)
   7. Re:  Double Trouble (Philip Scott)
   8. Re:  Either Monadic Trouble (Daniel Fischer)
   9.  Complex list manipulation (legajid)


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

Message: 1
Date: Mon, 9 Nov 2009 20:18:34 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] What is the best practice for code]
To: beginners@haskell.org
Message-ID: <20091110011834.ga3...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Mon, Nov 09, 2009 at 10:46:19PM +0100, legajid wrote:
>
> {-    Second solution   -}
> futiles2 xx = [(x, y, z) | x <- xx, y <- xx, z <- xx, y < x, z < y]
> f2 = filter (\(x,y,z) -> (x+y+z)==19) (futiles2 nombres )
>
> {-    Third solution  -}
> f3 = filter (\(x,y,z) -> (x+y+z)==19) ((\ xx -> [(x, y, z) | x <- xx, y <- 
> xx, z <- xx, y < x, z < y]) nombres )

I think the second solution is best (the third solution seems hard to
read).  Shorter code is usually better, but avoid long lines that are
hard to scan.

Here's another possibility:

  f4 = filter (\(x,y,z) -> x+y+z == 19)
              [(x,y,z) | x <- [9,8..1], y <- reverse [1..x-1], z <- reverse 
[1..y-1]]

This way you only generate (x,y,z) where x > y > z, and avoid all the
wasted work of generating triples and then throwing them away.

-Brent


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

Message: 2
Date: Mon, 9 Nov 2009 20:21:12 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] turning a value into an expression
To: beginners@haskell.org
Message-ID: <20091110012112.gb3...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Mon, Nov 09, 2009 at 10:05:43PM +0000, John Moore wrote:
> Hi,
>    How do I turn a value into an expression
> I want to do for e.g. 8 - 1 turn it into (subtract (Val8) (Val1)
> 
> Any ideas

Is this a homework problem?

One good approach would be to make a data type Expr which represents
expressions.  It will have a constructor Val, a constructor Subtract,
etc., one constructor for each operation you want to have in your
expressions.  Then make Expr an instance of the Num type class.

-Brent


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

Message: 3
Date: Tue, 10 Nov 2009 07:04:12 +0200
From: Michael Snoyman <mich...@snoyman.com>
Subject: Re: [Haskell-beginners] Re: Either Monadic Trouble
To: Nicolas Pouillard <nicolas.pouill...@gmail.com>
Cc: Beginners <beginners@haskell.org>
Message-ID:
        <29bf512f0911092104s3c58fe77qec186e50b1165...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Tue, Nov 10, 2009 at 1:12 AM, Nicolas Pouillard <
nicolas.pouill...@gmail.com> wrote:

> Excerpts from iæfai's message of Tue Nov 10 00:05:04 +0100 2009:
> > This is all very confusing. You say that it is defined in the
> > transformers. Does this mean it is possible to use the code I am
> > trying to get to work to do what I want?
>
> Yes by importing Control.Monad.Error
>
> > You also mention the attempt package, I must admit that I am not
> > entirely sure how to use it either. Note that I haven't done a lot of
> > error handling in haskell (the extent usually involved Maybe)
>
> A new version should be released (on Haskell Cafe) pretty soon,
> some documentation links will be provided as well. If you find
> the documentation not clear enough then let me know.
>
> Update: attempt-0.0.1 *has* been released.

Michael
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20091109/365c7696/attachment-0001.html

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

Message: 4
Date: Tue, 10 Nov 2009 10:16:48 +0100
From: Chadda? Fouch? <chaddai.fou...@gmail.com>
Subject: Re: [Haskell-beginners] What is the best practice for code]
To: legajid <lega...@free.fr>
Cc: beginners@haskell.org
Message-ID:
        <e9350eaf0911100116y7ed6a8f3oa360b62d6b1b7...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Mon, Nov 9, 2009 at 10:46 PM, legajid <lega...@free.fr> wrote:
> {-    Third solution  -}
> f3 = filter (\(x,y,z) -> (x+y+z)==19) ((\ xx -> [(x, y, z) | x <- xx, y <-
> xx, z <- xx, y < x, z < y]) nombres )

If you want to use list comprehension just use it for all filtering necessary :
(Si tu veux utiliser les list comprehension utilises les donc pour
tout filtrage nécessaire :)

> f3 = [(x, y, z) | x <- nombres, y <- nombres, z <- nombres, y < x, z < y, 
> x+y+z == 19]

Alternatively, you may try to express the same thing without the list
comprehension :
(Tu peux aussi essayer d'exprimer la même chose avec des fonctions seulement :)

> f4 = filter (\[x,y,z] -> z < y && y < x && x+y+z == 19) . replicateM 3 $ 
> nombres

It is almost always better (performance-wise) to only generate the
correct solutions rather than generate all then filter (though if you
can improve the modularity and/or clarity of your code by separating
the two steps it's worth considering), so in your case :
(Il est presque toujours préférable (du point de vue des performances)
de générer uniquement les solutions correctes plutôt que de générer
toutes les possibilités puis de les filtrer (encore que si ça te
permet d'améliorer la modularité ou la clarté de ton code ça vaut le
coup de se poser la question), donc dans ton cas ça donnerait :)

> f5 = reverse [(x, y, z) | x <- [3..9], y <- [2 .. x-1], let z = 19 - x - y, y 
> > z, z > 0]

-- 
Jedaï


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

Message: 5
Date: Tue, 10 Nov 2009 09:28:23 +0000
From: Philip Scott <haskell-beginn...@foo.me.uk>
Subject: [Haskell-beginners] Double Trouble
To: beginners@haskell.org
Message-ID: <4af93237.6060...@foo.me.uk>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hi Folks,

I'd just like to say thank you very much for your patient answers to my 
questions so far; it has been a real help on my Haskell adventure. Once 
I am become a Haskell god like y'all I will endeavour to repay the debt.

My current puzzle is doubles. I've extensively scoured the net and found 
various mentions of the same problem, but as far as I can see no 
answers; which I can't quite believe as it must be something people do 
all the time.

I need to interface my Haskell program with an existing C++ one over a 
TCP socket. I need to feed the C++ program doubles in standard 64-bit 
network order IEEE 765-1985 format, but if I serialize a double using 
Data.Binary I get something which
has altogeather too many bytes (I read somewhere it is an int and a long 
for the exponent and mantissa).

Any advice (or pointers to old threads, it isn't very easy to search the 
list archives) will be compensated for by a credit note for milk and 
cookies next time you are in the Cambridge, UK area :)

- Philip



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

Message: 6
Date: Tue, 10 Nov 2009 10:43:55 +0100
From: Krzysztof Skrz?tnicki <gte...@gmail.com>
Subject: Re: [Haskell-beginners] Double Trouble
To: haskell-beginn...@foo.me.uk
Cc: beginners@haskell.org
Message-ID:
        <220e47b40911100143q37c3629dy2493fb6fe18f7...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

Perhaps this module will help:

http://hackage.haskell.org/package/data-binary-ieee754

Regards

Krzysztof Skrzętnicki

On Tue, Nov 10, 2009 at 10:28, Philip Scott <haskell-beginn...@foo.me.uk> wrote:
> Hi Folks,
>
> I'd just like to say thank you very much for your patient answers to my
> questions so far; it has been a real help on my Haskell adventure. Once I am
> become a Haskell god like y'all I will endeavour to repay the debt.
>
> My current puzzle is doubles. I've extensively scoured the net and found
> various mentions of the same problem, but as far as I can see no answers;
> which I can't quite believe as it must be something people do all the time.
>
> I need to interface my Haskell program with an existing C++ one over a TCP
> socket. I need to feed the C++ program doubles in standard 64-bit network
> order IEEE 765-1985 format, but if I serialize a double using Data.Binary I
> get something which
> has altogeather too many bytes (I read somewhere it is an int and a long for
> the exponent and mantissa).
>
> Any advice (or pointers to old threads, it isn't very easy to search the
> list archives) will be compensated for by a credit note for milk and cookies
> next time you are in the Cambridge, UK area :)
>
> - Philip
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>


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

Message: 7
Date: Tue, 10 Nov 2009 10:02:03 +0000
From: Philip Scott <haskell-beginn...@foo.me.uk>
Subject: Re: [Haskell-beginners] Double Trouble
To: Krzysztof Skrz?tnicki <gte...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <4af93a1b.6000...@foo.me.uk>
Content-Type: text/plain; charset=UTF-8; format=flowed

Hi ho,
> Perhaps this module will help:
>
> http://hackage.haskell.org/package/data-binary-ieee754
>
>   
>> I need to interface my Haskell program with an existing C++ one over a TCP
>> socket. I need to feed the C++ program doubles in standard 64-bit network
>> order IEEE 765-1985 format, but if I serialize a double using Data.Binary I
>> get something which
>> has altogeather too many bytes (I read somewhere it is an int and a long for
>> the exponent and mantissa).
>>     

Thank you very much; I will take a look at that! I have no idea how I 
missed it, I went through every package on hackage that had 'binary' in 
the name, I must have sailed right past :)

- Philip


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

Message: 8
Date: Tue, 10 Nov 2009 16:13:52 +0100
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Either Monadic Trouble
To: beginners@haskell.org
Message-ID: <200911101613.52219.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="windows-1252"

Am Montag 09 November 2009 10:01:43 schrieb iæfai:
> With the below code, I am getting an error that I cannot resolve…

Everybody was so busy discussing whether Either (or rather (Either e)) is a 
monad that 
nobody looked at the code, so:

>
>
> Chess.hs:52:82:
>      Couldn't match expected type `Map [Char] [Char]'
>             against inferred type `Either ParseError ConfigMap'
>      In the third argument of `findWithDefault', namely `c'
>      In the `documentRoot' field of a record
>      In the first argument of `return', namely
>          `Config {documentRoot = (findWithDefault "web" "Document-
> Root" c)}'
>
>
> The specific code is:
>
> getConf :: FilePath -> IO (Either ParseError Config)
> getConf filePath
>      = return $ do
>          c <- readConfig filePath  -- (Either ParseError ConfigMap)

I believe the type of readConfig is

FilePath -> IO (Either ParseError ConfigMap)

, thus the binding of c, (c <-), still takes place in IO and c is one of (Left 
parseerror) 
or (Right configmap), hence c is not a suitable argument for findWithDefault.

>          return Config { documentRoot = Map.findWithDefault "web"
> "Document-Root" c }

The inner return also lives in IO, so had c a suitable type, your getConf would 
have type

FilePath -> IO (IO something).

I think you want 

getConf filePath = do
    r <- readConfig filePath
    return $ do
        c <- r       -- *now* we're using the monad (Either ParseError)
        return Config{ documentRoot = Map.findWithDefault "web" "Document-Root" 
c }

(if you have instance Monad (Either ParseError) in scope) or the equivalent 
using Pattern 
matching on the result of readConfig filePath.

>
>
> The type of c should be Either ParseError ConfigMap, which by my
> understanding of the Either monad would cause the c to be the Right
> side stripped, or skipped if Left.
>
> Full source for the module is below, and full project is hosted at
> http://patch-tag.com/r/iaefai/chess
>
> For some general information, I am replacing ConfigFile dependancy
> with a Parsec based config parser (I call it SimpleConfig) that suits
> my needs - it came from
>
> http://www.serpentine.com/blog/2007/01/31/parsing-a-simple-config-file-in-h
>askell/ originally and I modified it. On windows ConfigFile's dependancy on
> a posix regex library was causing trouble, so this is the effort to get rid
> of that dependancy.
>
> Any thoughts would be useful.
>
> There is one associated thought…
>
> The original function used to get configuration back to the program is
> -- Mostly from Chris Done's Blog
> getConf :: FilePath -> IO (Either (C.CPErrorData, String) Config)
> getConf filePath = runErrorT $ do
>      let cp = C.emptyCP { optionxform = id }
>      contents <- liftIO $ readFile filePath
>      config <- C.readstring cp contents
>      let get = C.get config "DEFAULT"
>      Config <$> get "Document-Root"
>
> I noted it used <$> and in the code that I retrieved originally from
> Chris Done's blog (no longer able to find it) used <*> for additional
> items. I would like some easy method of constructing the new Config
> structure in my new code, especially if it can be done without the
> record syntax like this thing gets away with. I am not sure how this
> thing associated "Document-Root" with documentRoot mind you.
>
> Thank you again.
> iæfai.



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

Message: 9
Date: Tue, 10 Nov 2009 22:09:36 +0100
From: legajid <lega...@free.fr>
Subject: [Haskell-beginners] Complex list manipulation
To: beginners@haskell.org
Message-ID: <4af9d690.6010...@free.fr>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hello,
i'm trying to manipulate lists with a "complex" (two-level) structure : 
a list containing tuples, containing a list containing tuples.
The object is to find a specific value according to 2 criterias.

Here is my code

tabmul= [ ( a, [ ( n, n*a ) | n <- [1..9] ] ) | a <- [2,3,4] ]

{- gives the following list
[
 (2, [(1,2), (2,4), ....(9,18)]),
 (3, [(1,3), (2,6), ....(9,27)]),
 (4, [(1,4), (2,8), ....(9,36)])
]
-}


{-  Get the result for a=3 and n=5  -}

-- select level 1 tuple for a=3
s1_flt (x,_) = (x==3)
s1=filter (s1_flt) tabmul -- get the list  [(3, [(), () .......])]
s1_liste =head(s1)        -- get the tuple (3, [.....])

-- extract the level 2 list of tuples
s1_tup (x,y)=y

-- then tuple for n=5
s1_flt2 (x, y) = x==5
s1_soltup = filter (s1_flt2) (s1_tup s1_liste)  -- [(3,15)]

--finally result for 3 * 5
s1_sol1 (x, y)= y                               
s1_sol = s1_sol1 (head s1_soltup)


Perhaps the structure is not the most efficient for this example, but it 
may simulate records in a database.
Getting the result seems really hard.
Do you know a shorter way to implement this search?
It probably would be simpler when i had triples (a, n ,a*n) ?

Another question : the values of criterias are hard-coded. What if i 
would like to type in s1_sol 3 5; how to put these parameters in the 
expressions for filters; the filters must get the parameters of the 
function, in other words the function should return or generate filters ?

Thanks for helping
Didier.




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

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


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

Reply via email to