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.  Either Monadic Trouble (i?fai)
   2. Re:  Either Monadic Trouble (Henk-Jan van Tuyl)
   3. Re:  Either Monadic Trouble (Nicolas Pouillard)
   4.  Re: Either Monadic Trouble (Ertugrul Soeylemez)
   5. Re:  Re: Either Monadic Trouble (Nicolas Pouillard)
   6.  What is the best practice for code] (legajid)
   7.  turning a value into an expression (John Moore)
   8. Re:  turning a value into an expression (Deniz Dogan)
   9. Re:  Re: Either Monadic Trouble (i?fai)
  10. Re:  Re: Either Monadic Trouble (Nicolas Pouillard)


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

Message: 1
Date: Mon, 09 Nov 2009 04:01:43 -0500
From: i?fai <iae...@me.com>
Subject: [Haskell-beginners] Either Monadic Trouble
To: Beginners@haskell.org
Message-ID: <49f7c1fc-4b1f-4e7e-9585-fcaf5983e...@me.com>
Content-Type: text/plain; charset=windows-1252; format=flowed;
        delsp=yes

With the below code, I am getting an error that I cannot resolve…


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)
         return Config { documentRoot = Map.findWithDefault "web"  
"Document-Root" c }


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-haskell/
 
  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.


-- 
import Network.Shed.Httpd
import Network.URI

import Data.List.Split

import Data.Either
import Data.Map as Map

import Text.ParserCombinators.Parsec

import Control.Monad.Error
import Control.Applicative

import System.Directory

import ChessBoard
import SimpleConfig

data Config = Config { documentRoot :: String } deriving (Read, Show)



main :: IO ()
main
     = do
         let docPath = ""
         let config = Config { documentRoot = "" }
         putStrLn $ "Using document root: " ++ docPath
         putStrLn "Starting up httpd on port 6666"
         server <- initServer 6666 (request config)
         return ()

request :: Config -> Request -> IO Response
request config req
     = do
         putStrLn $ "Recieved " ++ (show $ uriPath $ reqURI req)
         case url of
             "ajax" : _ -> return $ Response 404 [] "Not found."
             _   -> do str <- readFile ((documentRoot config) ++ uri)
                       return $ Response 200 [] str
         where url = drop 1 $ splitOn "/" uri
               uri = uriPath $ reqURI req



getConf :: FilePath -> IO (Either ParseError Config)
getConf filePath
     = return $ do
         c <- readConfig filePath  -- (Either ParseError ConfigMap)
         return Config { documentRoot = Map.findWithDefault "web"  
"Document-Root" c }  -- **** ERROR

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

Message: 2
Date: Mon, 09 Nov 2009 11:10:07 +0100
From: "Henk-Jan van Tuyl" <hjgt...@chello.nl>
Subject: Re: [Haskell-beginners] Either Monadic Trouble
To: i?fai <iae...@me.com>, Beginners@haskell.org
Message-ID: <op.u24g65khpz0...@zen5.router.home>
Content-Type: text/plain; charset=utf-8; format=flowed; delsp=yes


Either is not a monad, you can check this by typing
   :i Either
in GHCi; you will not see a line like
   instance Monad Either
in the result. Compare this to
   :i Maybe

getConf could be something like:
   getConf :: FilePath -> IO (Either ParseError Config)
   getConf filePath =
     do
       c <- readConfig filePath  -- (Either ParseError ConfigMap)
       return $
         case c of
           Right c' -> Right $ Config $ Map.findWithDefault "web"  
"Document-Root" c'
           Left  _  -> c


Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
--


On Mon, 09 Nov 2009 10:01:43 +0100, iæfai <iae...@me.com> wrote:

> With the below code, I am getting an error that I cannot resolve…
>
>
> 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)
>          return Config { documentRoot = Map.findWithDefault "web"  
> "Document-Root" c }
>
>
> 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-haskell/
>    
> 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: 3
Date: Mon, 09 Nov 2009 12:40:38 +0100
From: Nicolas Pouillard <nicolas.pouill...@gmail.com>
Subject: Re: [Haskell-beginners] Either Monadic Trouble
To: Henk-Jan van Tuyl <hjgt...@chello.nl>
Cc: Beginners <beginners@haskell.org>
Message-ID: <1257766690-sup-7...@peray>
Content-Type: text/plain; charset=UTF-8

Excerpts from Henk-Jan van Tuyl's message of Mon Nov 09 11:10:07 +0100 2009:
> 
> Either is not a monad, you can check this by typing
>    :i Either
> in GHCi; you will not see a line like
>    instance Monad Either
> in the result. Compare this to
>    :i Maybe

In fact the Either Monad instance is defined in the 'transformers' (or 'mtl')
packages.

However for this reason among others you may want to use the 'attempt'[1]
package instead of Either.

[1]: http://hackage.haskell.org/package/attempt-0.0.0

-- 
Nicolas Pouillard
http://nicolaspouillard.fr


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

Message: 4
Date: Mon, 9 Nov 2009 21:44:44 +0100
From: Ertugrul Soeylemez <e...@ertes.de>
Subject: [Haskell-beginners] Re: Either Monadic Trouble
To: beginners@haskell.org
Message-ID: <20091109214444.42847...@tritium.xx>
Content-Type: text/plain; charset=US-ASCII

Nicolas Pouillard <nicolas.pouill...@gmail.com> wrote:

> > Either is not a monad, you can check this by typing
> >    :i Either
> > in GHCi; you will not see a line like
> >    instance Monad Either
> > in the result. Compare this to
> >    :i Maybe
>
> In fact the Either Monad instance is defined in the 'transformers' (or
> 'mtl') packages.

Either is still not a monad.  Have a look at its kind.


Greets,
Ertugrul.


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://blog.ertes.de/




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

Message: 5
Date: Mon, 09 Nov 2009 22:00:02 +0100
From: Nicolas Pouillard <nicolas.pouill...@gmail.com>
Subject: Re: [Haskell-beginners] Re: Either Monadic Trouble
To: Ertugrul Soeylemez <e...@ertes.de>
Cc: beginners <beginners@haskell.org>
Message-ID: <1257800088-sup-1...@peray>
Content-Type: text/plain; charset=UTF-8

Excerpts from Ertugrul Soeylemez's message of Mon Nov 09 21:44:44 +0100 2009:
> Nicolas Pouillard <nicolas.pouill...@gmail.com> wrote:
> 
> > > Either is not a monad, you can check this by typing
> > >    :i Either
> > > in GHCi; you will not see a line like
> > >    instance Monad Either
> > > in the result. Compare this to
> > >    :i Maybe
> >
> > In fact the Either Monad instance is defined in the 'transformers' (or
> > 'mtl') packages.
> 
> Either is still not a monad.  Have a look at its kind.

OK, right Either is not but (Either e), where e must be in
the Error type class.

-- 
Nicolas Pouillard
http://nicolaspouillard.fr


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

Message: 6
Date: Mon, 09 Nov 2009 22:46:19 +0100
From: legajid <lega...@free.fr>
Subject: [Haskell-beginners] What is the best practice for code]
To: beginners@haskell.org
Message-ID: <4af88dab.7000...@free.fr>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hello,

i wanted to write a program that searches for all combinations of some 
numbers, the sum of which is a given value.
So, i started writing my program, creating a function for each separate 
phase : creating list of triples, selecting valuable ones, filtering the 
result.

Looking at my code, i've reduced it several ways; the last version holds 
on one single line of code.

Please, from the 3 versions i established, which one is " better"? What 
are the criterias of a "good" code ?
What about using many anonymous functions?
I think there are other solutions than those i propose.

Following is my code

{-    First solution     -}
nombres=[9,8..1]
-- all combinations
ftoutes xx = [(x, y, z) | x <- xx, y <- xx, z <- xx]
-- keep valuable ones
futiles xyz = [(x, y, z) | (x,y,z) <- xyz, y < x, z < y ]
-- filter
f_flt (x,y, z) = (x+y+z) == 19
-- final result
f = filter (f_flt) (futiles (ftoutes nombres ))

{-    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 )

Thanks for your advice

Didier.





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

Message: 7
Date: Mon, 9 Nov 2009 22:05:43 +0000
From: John Moore <john.moor...@gmail.com>
Subject: [Haskell-beginners] turning a value into an expression
To: beginners@haskell.org
Message-ID:
        <4f7ad1ad0911091405i58bfc339g1776768243fa7...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

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

J
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20091109/973318cf/attachment-0001.html

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

Message: 8
Date: Mon, 9 Nov 2009 23:48:38 +0100
From: Deniz Dogan <deniz.a.m.do...@gmail.com>
Subject: Re: [Haskell-beginners] turning a value into an expression
To: John Moore <john.moor...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <7b501d5c0911091448mff920c2m1048d25968960...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

2009/11/9 John Moore <john.moor...@gmail.com>:
> 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
>
> J
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>

import Prelude hiding ((-))

data Val a = Val a
  deriving Show

data Expr a b = Subtract a b
  deriving Show

(-) :: Num a => a -> a -> Expr (Val a) (Val a)
x - y = Subtract (Val x) (Val y)



> 4 - 3
Subtract (Val 4) (Val 3)

-- 
Deniz Dogan


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

Message: 9
Date: Mon, 09 Nov 2009 18:05:04 -0500
From: i?fai <iae...@me.com>
Subject: Re: [Haskell-beginners] Re: Either Monadic Trouble
To: Nicolas Pouillard <nicolas.pouill...@gmail.com>
Cc: Beginners@haskell.org
Message-ID: <97c85097-db8e-4ef2-aafd-7edda7618...@me.com>
Content-Type: text/plain; charset=iso-8859-1; format=flowed; delsp=yes

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?

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)

- iæfai.


On 2009-11-09, at 4:00 PM, Nicolas Pouillard wrote:

> Excerpts from Ertugrul Soeylemez's message of Mon Nov 09 21:44:44  
> +0100 2009:
>> Nicolas Pouillard <nicolas.pouill...@gmail.com> wrote:
>>
>>>> Either is not a monad, you can check this by typing
>>>>   :i Either
>>>> in GHCi; you will not see a line like
>>>>   instance Monad Either
>>>> in the result. Compare this to
>>>>   :i Maybe
>>>
>>> In fact the Either Monad instance is defined in the  
>>> 'transformers' (or
>>> 'mtl') packages.
>>
>> Either is still not a monad.  Have a look at its kind.
>
> OK, right Either is not but (Either e), where e must be in
> the Error type class.
>
> -- 
> Nicolas Pouillard
> http://nicolaspouillard.fr
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners



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

Message: 10
Date: Tue, 10 Nov 2009 00:12:56 +0100
From: Nicolas Pouillard <nicolas.pouill...@gmail.com>
Subject: Re: [Haskell-beginners] Re: Either Monadic Trouble
To: i?fai <iae...@me.com>
Cc: Beginners <beginners@haskell.org>
Message-ID: <1257808266-sup-4...@peray>
Content-Type: text/plain; charset=UTF-8

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.

-- 
Nicolas Pouillard
http://nicolaspouillard.fr


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

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


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

Reply via email to