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 (David McBride)
   2. Re:  very impure [global] counter (Patrick LeBoutillier)


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

Message: 1
Date: Fri, 22 Jul 2011 05:46:43 -0400
From: David McBride <dmcbr...@neondsl.com>
Subject: Re: [Haskell-beginners] very impure [global] counter
To: Davi Santos <dps....@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <CAN+Tr43gyOTB+eR6zDAiUu9ST7U7Pfq77TbCaHaORUBgqoga=q...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

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



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

Message: 2
Date: Fri, 22 Jul 2011 05:55:16 -0400
From: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Subject: Re: [Haskell-beginners] very impure [global] counter
To: Davi Santos <dps....@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <CAJcQsbjTCKag8zajva2VTHVTi=gcvv+zoqjhhxoydzzbgf1...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

Davi,

Perhaps you could use openTempFile
(http://haskell.org/ghc/docs/6.12.2/html/libraries/base-4.2.0.1/System-IO.html#22)?

It will create a file with a unique name and open it for you, you can
then just close it and pass the filename to your program.

Patrick


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



-- 
=====================
Patrick LeBoutillier
Rosem?re, Qu?bec, Canada



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

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


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

Reply via email to