[Haskell-beginners] very impure [global] counter

Thomas haskell at phirho.com
Fri Jul 22 12:08:17 CEST 2011


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.abc at 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 at haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>
>>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners




More information about the Beginners mailing list