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:  very impure [global] counter (Thomas)
   2. Re:  another list comprehesion error (Roelof Wobben)
   3. Re:  another list comprehesion error (David Place)
   4. Re:  another list comprehesion error (David Place)
   5.  Haskell state monad example - type mismatch      error (Rohit Garg)
   6. Re:  Haskell state monad example - type mismatch  error
      (Antoine Latter)
   7. Re:  Haskell state monad example - type mismatch  error
      (aditya siram)
   8. Re:  Haskell state monad example - type mismatch  error
      (Rohit Garg)
   9. Re:  another list comprehesion error (Roelof Wobben)


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

Message: 1
Date: Fri, 22 Jul 2011 12:08:17 +0200
From: Thomas <hask...@phirho.com>
Subject: Re: [Haskell-beginners] very impure [global] counter
To: beginners@haskell.org
Message-ID: <4e294c11.6070...@phirho.com>
Content-Type: text/plain; charset=UTF-8; format=flowed

I may misunderstand the issue, but why not using:

System.IO.Temp.openTempFile

and then use the returned FilePath?

This should give unique names even for multiple runs of the controlling 
program.



On 22.07.2011 11:46, David McBride wrote:
> This is what I'd do:
>
> {-# LANGUAGE NoMonomorphismRestriction #-}
> module Counter where
>
> import Control.Monad.State
>
> main = runStateT procedure (0 :: Integer)>>  return ()
>
> incCounter = do
>    n<- get
>    modify (+1)
>    return n
>
> execFile = do
>    n<- incCounter
>    liftIO $ putStrLn $ ("command --createfile=tempfile" ++ show n ++ ".tmp")
>
> procedure = do
>    execFile
>    execFile
>    liftIO $ putStrLn "do something"
>    execFile
>
> On Fri, Jul 22, 2011 at 3:10 AM, Davi Santos<dps....@gmail.com>  wrote:
>> Hello all,
>> I have massive (parallel if possible) system calls to an external
>> non-deterministic program.
>> Each time it is executed, it creates a file depending on a command line
>> option 'opt' (input files path, for example).
>> How can I ensure the file name will be unique? maybe with a global counter?
>> My temporary solution have been to use a large random number:
>> -----------
>> mysteriousExecution :: String ->  IO ()
>> mysteriousExecution opt = do
>>     number<- rand
>>     run $ "mysterious-command " ? opt ? " --create-file=" ? number
>> rand = do
>>     a ?  getStdRandom (randomR (1,999999999999999999999999999999999)) ?  IO
>> Int
>>     let r = take 20 $ randomRs ('a','z') (mkStdGen a) ?  String
>>     return r
>> ========
>> I'm trying to avoid additional parameters to 'mysteriousExecution'.
>> I tried a counter also (to replace rand), but I don't know how could I start
>> it inside  'mysteriousExecution'.
>> c ?  IO Counter
>> c = do
>>      r ?  newIORef 0            -- start
>>      return (do
>>          modifyIORef r (+1)
>>          readIORef r)
>> If somebody says everything is wrong, ok.
>> I understand. 18 years of imperative programming world can damage the brain.
>> Thanks
>> _______________________________________________
>> 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




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

Message: 2
Date: Fri, 22 Jul 2011 10:37:30 +0000
From: Roelof Wobben <rwob...@hotmail.com>
Subject: Re: [Haskell-beginners] another list comprehesion error
To: <beginners@haskell.org>
Message-ID: <snt118-w38eaea9f1b024809ad02fae...@phx.gbl>
Content-Type: text/plain; charset="iso-8859-1"


Oke, 

 

Thanks. 

 

I was wondering one thing and I think at this moment too difficult for me,

But can you with a list comprehession read one list and alter another list.

 

For example:

 

You have a list of numbers

Now you would calculate the average value and put the outcome in another list.

 

Just wondering so you have to say it can or cannot be done.

 

Roelof



----------------------------------------
> Date: Fri, 22 Jul 2011 11:31:07 +0200
> From: hask...@phirho.com
> To: beginners@haskell.org
> Subject: Re: [Haskell-beginners] another list comprehesion error
>
> On 22.07.2011 08:46, Roelof Wobben wrote:
>
> >> Now try this instead:
> >> roelof' n = [x | x<- [1..n]]
> >> What do you get for "roelof' 4" ?
> > A error message that a instance of print is missing.
>
> Then you have a typo somewhere...
>
> >> Now you can try the last two with guards.
>
> > 2) cannot be done without guards and list comprehession generator [ 2,4 
> > ..10] does not work
>
> Sure it can:
> [ 2*x-1 | x <- [1..5]]
> and even easier:
> [1,3..10]
> or, better still (but not only a list comprehension any more):
> take 5 [1, 3..]
>
> > 3) cannot be done withut guards and list comprehession because of the a<=b
>
> This, too, can be done:
> [ (b, a) | a <- [1..5], b <- [1..a]]
>
> Regards,
> Thomas
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners                             
>           


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

Message: 3
Date: Fri, 22 Jul 2011 10:27:29 -0400
From: David Place <d...@vidplace.com>
Subject: Re: [Haskell-beginners] another list comprehesion error
To: Roelof Wobben <rwob...@hotmail.com>
Cc: "<beginners@haskell.org>" <beginners@haskell.org>
Message-ID: <5a81d8ae-8662-4a98-acaf-bfb630f41...@vidplace.com>
Content-Type: text/plain;       charset=us-ascii

Hi, Roelof. 

When you are working to unders

_____________________
David F. Place
Owner,  Panpipes Ho!, LLC
http://panpipesho.com

On Jul 22, 2011, at 6:37 AM, Roelof Wobben <rwob...@hotmail.com> wrote:

> 



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

Message: 4
Date: Fri, 22 Jul 2011 10:32:03 -0400
From: David Place <d...@vidplace.com>
Subject: Re: [Haskell-beginners] another list comprehesion error
To: David Place <d...@vidplace.com>
Cc: "<beginners@haskell.org>" <beginners@haskell.org>
Message-ID: <25b7793e-6b14-49d1-ae44-f50b47b90...@vidplace.com>
Content-Type: text/plain; charset=us-ascii

Whoops, sorry.  I swiped the tiny send button on my iPhone.  

Hi, Roelof.

When you are working to understand examples from "Programming in Haskell" 
perhaps you can give page numbers so we can follow along.

Cheers,
David

____________________
David Place   
Owner, Panpipes Ho! LLC
http://panpipesho.com
d...@vidplace.com



On Jul 22, 2011, at 10:27 AM, David Place wrote:

> Hi, Roelof. 
> 
> When you are working to unders
> 
> _____________________
> David F. Place
> Owner,  Panpipes Ho!, LLC
> http://panpipesho.com
> 
> On Jul 22, 2011, at 6:37 AM, Roelof Wobben <rwob...@hotmail.com> wrote:
> 
>> 
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners




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

Message: 5
Date: Fri, 22 Jul 2011 20:20:23 +0530
From: Rohit Garg <rpg....@gmail.com>
Subject: [Haskell-beginners] Haskell state monad example - type
        mismatch        error
To: beginners@haskell.org
Message-ID:
        <cac1t7giu+t351fejy8v60udj2lok5sgvunujjbkewgzk2dy...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi,

I am trying out a simple haskell state monad example. I think I have
understood the concept of monads, but I am getting stuck at using
State monad. As far as I understand, the code below should compile,
but it is throwing a type mismatch error in the argument to show. The
rest of the code, however, type checks all right.

If any one can point out what I am doing wrong, it would be really helpful.

Thanks and regards,
Rohit

===============================
import Control.Monad.State
import Data.Word

type LCGState = Word32

lcg :: LCGState -> (Integer, LCGState)
lcg s0 = (output, s1)
    where s1 = 1103515245 * s0 + 12345
          output = fromIntegral s1 * 2^16 `div` 2^32

seed :: LCGState
seed = 5

getRandom :: State LCGState Integer
getRandom = do
    s0 <- get
    let (x,s1) = lcg s0
    put s1
    return x

addThreeRandoms :: State LCGState Integer
addThreeRandoms = do
    a <- getRandom
    b <- getRandom
    c <- getRandom
    return (a+b+c)

main :: IO ()
main = putStrLn show(addThreeRandoms seed)

-- 
Rohit Garg

http://rpg-314.blogspot.com/



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

Message: 6
Date: Fri, 22 Jul 2011 09:59:29 -0500
From: Antoine Latter <aslat...@gmail.com>
Subject: Re: [Haskell-beginners] Haskell state monad example - type
        mismatch        error
To: Rohit Garg <rpg....@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <cakjsnqhowov4rnaou_c8qo-ueykz7dxqsw7anfrxqokojcv...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Fri, Jul 22, 2011 at 9:50 AM, Rohit Garg <rpg....@gmail.com> wrote:
> Hi,
>
> I am trying out a simple haskell state monad example. I think I have
> understood the concept of monads, but I am getting stuck at using
> State monad. As far as I understand, the code below should compile,
> but it is throwing a type mismatch error in the argument to show. The
> rest of the code, however, type checks all right.
>

You need to include the function 'runState' or 'evalState' somewhere -
a value of type 'State x y' is not a function, so trying to apply it
to values as if it were a function is not going to work.

http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-State-Lazy.html#v:runState
http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-State-Lazy.html#v:evalState

Antoine

> If any one can point out what I am doing wrong, it would be really helpful.
>
> Thanks and regards,
> Rohit
>
> ===============================
> import Control.Monad.State
> import Data.Word
>
> type LCGState = Word32
>
> lcg :: LCGState -> (Integer, LCGState)
> lcg s0 = (output, s1)
> ? ?where s1 = 1103515245 * s0 + 12345
> ? ? ? ? ?output = fromIntegral s1 * 2^16 `div` 2^32
>
> seed :: LCGState
> seed = 5
>
> getRandom :: State LCGState Integer
> getRandom = do
> ? ?s0 <- get
> ? ?let (x,s1) = lcg s0
> ? ?put s1
> ? ?return x
>
> addThreeRandoms :: State LCGState Integer
> addThreeRandoms = do
> ? ?a <- getRandom
> ? ?b <- getRandom
> ? ?c <- getRandom
> ? ?return (a+b+c)
>
> main :: IO ()
> main = putStrLn show(addThreeRandoms seed)
>
> --
> Rohit Garg
>
> http://rpg-314.blogspot.com/
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



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

Message: 7
Date: Fri, 22 Jul 2011 10:05:15 -0500
From: aditya siram <aditya.si...@gmail.com>
Subject: Re: [Haskell-beginners] Haskell state monad example - type
        mismatch        error
To: Antoine Latter <aslat...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <cajrreygjedyuz8xtmmsvgewr_shtay59izhatyns9b6ckfw...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi,
Your main function needs to be:
main :: IO ()
main = putStrLn $ show $ runState addThreeRandoms seed
=>(70496,695785320)
if you want to preserve the final state

or:
main' :: IO ()
main' = putStrLn $ show $ execState addThreeRandoms seed
=>695785320

if you don't.

-deech


On Fri, Jul 22, 2011 at 9:59 AM, Antoine Latter <aslat...@gmail.com> wrote:
> On Fri, Jul 22, 2011 at 9:50 AM, Rohit Garg <rpg....@gmail.com> wrote:
>> Hi,
>>
>> I am trying out a simple haskell state monad example. I think I have
>> understood the concept of monads, but I am getting stuck at using
>> State monad. As far as I understand, the code below should compile,
>> but it is throwing a type mismatch error in the argument to show. The
>> rest of the code, however, type checks all right.
>>
>
> You need to include the function 'runState' or 'evalState' somewhere -
> a value of type 'State x y' is not a function, so trying to apply it
> to values as if it were a function is not going to work.
>
> http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-State-Lazy.html#v:runState
> http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-State-Lazy.html#v:evalState
>
> Antoine
>
>> If any one can point out what I am doing wrong, it would be really helpful.
>>
>> Thanks and regards,
>> Rohit
>>
>> ===============================
>> import Control.Monad.State
>> import Data.Word
>>
>> type LCGState = Word32
>>
>> lcg :: LCGState -> (Integer, LCGState)
>> lcg s0 = (output, s1)
>> ? ?where s1 = 1103515245 * s0 + 12345
>> ? ? ? ? ?output = fromIntegral s1 * 2^16 `div` 2^32
>>
>> seed :: LCGState
>> seed = 5
>>
>> getRandom :: State LCGState Integer
>> getRandom = do
>> ? ?s0 <- get
>> ? ?let (x,s1) = lcg s0
>> ? ?put s1
>> ? ?return x
>>
>> addThreeRandoms :: State LCGState Integer
>> addThreeRandoms = do
>> ? ?a <- getRandom
>> ? ?b <- getRandom
>> ? ?c <- getRandom
>> ? ?return (a+b+c)
>>
>> main :: IO ()
>> main = putStrLn show(addThreeRandoms seed)
>>
>> --
>> Rohit Garg
>>
>> http://rpg-314.blogspot.com/
>>
>> _______________________________________________
>> 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
>



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

Message: 8
Date: Fri, 22 Jul 2011 20:59:07 +0530
From: Rohit Garg <rpg....@gmail.com>
Subject: Re: [Haskell-beginners] Haskell state monad example - type
        mismatch        error
To: aditya siram <aditya.si...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <cac1t7gjuokesbpu9o274ga4bthzupke1aq7f5nxr+4t5qje...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On Fri, Jul 22, 2011 at 8:35 PM, aditya siram <aditya.si...@gmail.com> wrote:
> Hi,
> Your main function needs to be:
> main :: IO ()
> main = putStrLn $ show $ runState addThreeRandoms seed
> =>(70496,695785320)
> if you want to preserve the final state
>
> or:
> main' :: IO ()
> main' = putStrLn $ show $ execState addThreeRandoms seed
> =>695785320
>
> if you don't.

Thanks. This cleared up the matter.

>
> -deech
>
>
> On Fri, Jul 22, 2011 at 9:59 AM, Antoine Latter <aslat...@gmail.com> wrote:
>> On Fri, Jul 22, 2011 at 9:50 AM, Rohit Garg <rpg....@gmail.com> wrote:
>>> Hi,
>>>
>>> I am trying out a simple haskell state monad example. I think I have
>>> understood the concept of monads, but I am getting stuck at using
>>> State monad. As far as I understand, the code below should compile,
>>> but it is throwing a type mismatch error in the argument to show. The
>>> rest of the code, however, type checks all right.
>>>
>>
>> You need to include the function 'runState' or 'evalState' somewhere -
>> a value of type 'State x y' is not a function, so trying to apply it
>> to values as if it were a function is not going to work.
>>
>> http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-State-Lazy.html#v:runState
>> http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-State-Lazy.html#v:evalState
>>
>> Antoine
>>
>>> If any one can point out what I am doing wrong, it would be really helpful.
>>>
>>> Thanks and regards,
>>> Rohit
>>>
>>> ===============================
>>> import Control.Monad.State
>>> import Data.Word
>>>
>>> type LCGState = Word32
>>>
>>> lcg :: LCGState -> (Integer, LCGState)
>>> lcg s0 = (output, s1)
>>> ? ?where s1 = 1103515245 * s0 + 12345
>>> ? ? ? ? ?output = fromIntegral s1 * 2^16 `div` 2^32
>>>
>>> seed :: LCGState
>>> seed = 5
>>>
>>> getRandom :: State LCGState Integer
>>> getRandom = do
>>> ? ?s0 <- get
>>> ? ?let (x,s1) = lcg s0
>>> ? ?put s1
>>> ? ?return x
>>>
>>> addThreeRandoms :: State LCGState Integer
>>> addThreeRandoms = do
>>> ? ?a <- getRandom
>>> ? ?b <- getRandom
>>> ? ?c <- getRandom
>>> ? ?return (a+b+c)
>>>
>>> main :: IO ()
>>> main = putStrLn show(addThreeRandoms seed)
>>>
>>> --
>>> Rohit Garg
>>>
>>> http://rpg-314.blogspot.com/
>>>
>>> _______________________________________________
>>> 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
>>
>



-- 
Rohit Garg

http://rpg-314.blogspot.com/



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

Message: 9
Date: Fri, 22 Jul 2011 15:33:57 +0000
From: Roelof Wobben <rwob...@hotmail.com>
Subject: Re: [Haskell-beginners] another list comprehesion error
To: <beginners@haskell.org>
Message-ID: <snt118-w523db45fbe670f5a115324ae...@phx.gbl>
Content-Type: text/plain; charset="iso-8859-1"


Oke', 

But they are not examples but exercises.

 

Roelof



----------------------------------------
> Subject: Re: [Haskell-beginners] another list comprehesion error
> From: d...@vidplace.com
> Date: Fri, 22 Jul 2011 10:32:03 -0400
> CC: rwob...@hotmail.com; beginners@haskell.org
> To: d...@vidplace.com
>
> Whoops, sorry. I swiped the tiny send button on my iPhone.
>
> Hi, Roelof.
>
> When you are working to understand examples from "Programming in Haskell" 
> perhaps you can give page numbers so we can follow along.
>
> Cheers,
> David
>
> ____________________
> David Place
> Owner, Panpipes Ho! LLC
> http://panpipesho.com
> d...@vidplace.com
>
>
>
> On Jul 22, 2011, at 10:27 AM, David Place wrote:
>
> > Hi, Roelof.
> >
> > When you are working to unders
> >
> > _____________________
> > David F. Place
> > Owner, Panpipes Ho!, LLC
> > http://panpipesho.com
> >
> > On Jul 22, 2011, at 6:37 AM, Roelof Wobben <rwob...@hotmail.com> wrote:
> >
> >>
> >
> > _______________________________________________
> > 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 37, Issue 46
*****************************************

Reply via email to