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.  gcd (Steve)
   2. Re:  parallel program in haskell in 5 steps (Sean Bartell)
   3.  How to wait till a process is finished before    invoking the
      next one? (Thomas Friedrich)
   4. Re:  How to wait till a process is finished before        invoking
      the next one? (Daniel Fischer)
   5. Re:  How to wait till a process is finished before        invoking
      the next one? (Thomas Friedrich)
   6.  Real World Haskell Chapter 5 (PJ Fitzpatrick)
   7. Re:  How to wait till a process is finished before        invoking
      the next one? (Daniel Fischer)
   8. Re:  Real World Haskell Chapter 5 (Daniel Fischer)
   9. Re:  How to wait till a process is finished before        invoking
      the next one? (Brandon S. Allbery KF8NH)


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

Message: 1
Date: Fri, 01 May 2009 21:30:35 +0800
From: Steve <stevech1...@yahoo.com.au>
Subject: [Haskell-beginners] gcd
To: beginners@haskell.org
Message-ID: <1241184635.4876.18.ca...@host.localdomain>
Content-Type: text/plain

I had a look at the gcd definition in GHC 6.10.1
ghc-6.10.1/libraries/base/GHC/Real.lhs

-- | @'gcd' x y@ is the greatest (positive) integer that divides both
@x@
-- and @y@; for example @'gcd' (-3) 6@ = @3@, @'gcd' (-3) (-6)@ = @3@,
-- @'gcd' 0 4@ = @4...@.  @'gcd' 0 0@ raises a runtime error.
gcd             :: (Integral a) => a -> a -> a
gcd 0 0         =  error "Prelude.gcd: gcd 0 0 is undefined"
gcd x y         =  gcd' (abs x) (abs y)
                   where gcd' a 0  =  a
                         gcd' a b  =  gcd' b (a `rem` b)

Why is gcd 0 0 undefined?

http://en.wikipedia.org/wiki/Greatest_common_divisor says:
"It is useful to define gcd(0, 0) = 0 and lcm(0, 0) = 0 because then the
natural numbers become a complete distributive lattice with gcd as meet
and lcm as join operation. This extension of the definition is also
compatible with the generalization for commutative rings given below."

An added advantage, for haskell, of defining gcd 0 0 = 0 is that gcd
would change from being a partial function to a total function.

Regards,
Steve




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

Message: 2
Date: Wed, 6 May 2009 23:25:43 -0400
From: Sean Bartell <wingedtachik...@gmail.com>
Subject: Re: [Haskell-beginners] parallel program in haskell in 5
        steps
To: Jack Kennedy <j...@realmode.com>
Cc: beginners@haskell.org
Message-ID:
        <dd3762960905062025j33c302q7eeb9107ffc52...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

>
> Does this happen for everyone, or just me?

I get the same result here. Changing a to fib 100 lets me get 65-75%. The
compiler's probably just being smarter than you expect and combining both
instances of ack 4 10.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090506/7b6f0769/attachment-0001.htm

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

Message: 3
Date: Thu, 07 May 2009 12:36:08 -0400
From: Thomas Friedrich <i...@suud.de>
Subject: [Haskell-beginners] How to wait till a process is finished
        before  invoking the next one?
To: beginners@haskell.org
Message-ID: <4a030df8.3040...@suud.de>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hi everyone,

I have the following problem, and I hope that someone of yours might be 
able to help me.

The Haskell program I am writing has the following setup:

writeData :: [String] -> IO ()
writeData cs = ...

runProgram:: [String] -> IO ()
runProgram cs = ...

writeFeatures :: [String] -> IO ()
writeFeatures cs = ...

runTestOnFeatures :: IO ()
runTestOnFeatures = ...

main :: IO ()
main = do
  cs <- getArgs
  writeData cs
  runProgram cs
  writeFeatures cs
  runTestOnFeatures

Each of the above function take a list of filenames, run certain 
command-line programs on them, which I invoke by runCommand, and each of 
them produce multiple output-files.  Each function in main needs a 
couple of those output-files that are produced by the function directly 
above it.  How do I get Haskell to wait, till all the data is written to 
the disk, before invoking the next command.  The way the program is 
currently written, Haskell doesn't see that the input of one function 
depends on the output of another, and tries to run them all at the same 
time.

Any ideas?

Thanks everyone for your help.

Cheers,
Thomas



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

Message: 4
Date: Thu, 7 May 2009 19:10:49 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] How to wait till a process is
        finished before invoking the next one?
To: beginners@haskell.org
Message-ID: <200905071910.50054.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Donnerstag 07 Mai 2009 18:36:08 schrieb Thomas Friedrich:
> Hi everyone,
>
> Each of the above function take a list of filenames, run certain
> command-line programs on them, which I invoke by runCommand, and each of
> them produce multiple output-files.  Each function in main needs a
> couple of those output-files that are produced by the function directly
> above it.  How do I get Haskell to wait, till all the data is written to
> the disk, before invoking the next command.

System.Process.waitForProcess

should do it, conveniently runCommand returns a ProcessHandle.

> The way the program is
> currently written, Haskell doesn't see that the input of one function
> depends on the output of another, and tries to run them all at the same
> time.
>
> Any ideas?
>
> Thanks everyone for your help.
>
> Cheers,
> Thomas




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

Message: 5
Date: Thu, 07 May 2009 14:53:11 -0400
From: Thomas Friedrich <i...@suud.de>
Subject: Re: [Haskell-beginners] How to wait till a process is
        finished before invoking the next one?
To: Daniel Fischer <daniel.is.fisc...@web.de>
Cc: beginners@haskell.org
Message-ID: <4a032e17.4030...@suud.de>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hi Daniel and everyone,

Thanks for the reply!

I thought of using waitForProcess, and in fact an earlier version of the 
program did. However, as the program got more complex, I don't really 
see how this is still possible.

For example the runProgram function looks like this:

runProgram :: [String] -> IO ()
runProgram [] = return ()
runProgram (c:cs) = do
  runCommand ("lalala " ++ c)
  runProgram cs

It might be possible to write the function runProgram in a way, so that 
it returns an expression of type [IO ProcessHandle] and then try to work 
from there.  But I have the feeling, that this will become messy very 
quickly, and there must be some more elegant way of doing this.  The 
other thing is that actually not all functions are able to return 
ProcessHandles, e.g.

writeFeatures :: [String] -> IO ()
writeFeatures cs = Exc.bracket (openFile training AppendMode) hClose (\h 
-> goo h)
  where
    goo h = go 1 cs
      where
        go :: Int -> [String] -> IO ()
        go n [] = putStrLn "Features written."
        go n (c:cs) = do
          features <- makeFeatures n c    -- makeFeatures :: Int -> 
String -> IO String
          hPutStr h features
          go (n+1) cs

And the file that is produced here is needed in the next function.

I hoped to do something with forkIO, as I would like to parallelize the 
whole program at the end.  Especially the function runProgram would 
benefit hugely from this (I so don't have a clue how to do this yet;). I 
tried for example the following:

main :: IO ()
main = do
 cs <- getArgs
 p1 <- forkIO $ writeData cs
 p2 <- forkIO $ runProgram cs
 p3 <- forkIO $ writeFeatures cs
 p4 <- forkIO $ runTestOnFeatures
 seq p1 (seq p2 (seq p3 (seq p4 (putStrLn "Done"))))

But that of course doesn't work, because now I am not actually 
requesting anything.  The program does in fact nothing, apart from 
printing out "Done".

Any ideas?

Cheers,
Thomas


Daniel Fischer wrote:
> Am Donnerstag 07 Mai 2009 18:36:08 schrieb Thomas Friedrich:
>   
>> Hi everyone,
>>
>> Each of the above function take a list of filenames, run certain
>> command-line programs on them, which I invoke by runCommand, and each of
>> them produce multiple output-files.  Each function in main needs a
>> couple of those output-files that are produced by the function directly
>> above it.  How do I get Haskell to wait, till all the data is written to
>> the disk, before invoking the next command.
>>     
>
> System.Process.waitForProcess
>
> should do it, conveniently runCommand returns a ProcessHandle.
>
>   
>> The way the program is
>> currently written, Haskell doesn't see that the input of one function
>> depends on the output of another, and tries to run them all at the same
>> time.
>>
>> Any ideas?
>>
>> Thanks everyone for your help.
>>
>> Cheers,
>> Thomas
>>     
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>   



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

Message: 6
Date: Thu, 7 May 2009 20:18:46 +0100
From: PJ Fitzpatrick <fitzpatrick...@googlemail.com>
Subject: [Haskell-beginners] Real World Haskell Chapter 5
To: Beginners@haskell.org
Message-ID:
        <32531bb40905071218k287b23b9xb1331d5af7fb0...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi,
I have compiled the SimpleJSON.hs file from chapter 5 and from another file
attempted to import it. I am getting a could not find module error and the
prelude tells me that the locations searched were SimpleJSON.hs and
SimpleJSON.lhs.
I am running Vista, GHC 6.10.2
Any ideas?
tks,
PJ
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090507/6c391add/attachment-0001.htm

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

Message: 7
Date: Thu, 7 May 2009 22:04:51 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] How to wait till a process is
        finished before invoking the next one?
To: beginners@haskell.org
Message-ID: <200905072204.51750.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Donnerstag 07 Mai 2009 20:53:11 schrieb Thomas Friedrich:
> Hi Daniel and everyone,
>
> Thanks for the reply!
>
> I thought of using waitForProcess, and in fact an earlier version of the
> program did. However, as the program got more complex, I don't really
> see how this is still possible.
>
> For example the runProgram function looks like this:
>
> runProgram :: [String] -> IO ()
> runProgram [] = return ()
> runProgram (c:cs) = do
>   runCommand ("lalala " ++ c)
>   runProgram cs

You could have

   runCommand ("lalala " ++ c) >>= waitForProcess

in the penultimate line. That would ensure that the command has finished before 
its 
results are requested, but of course destroy all possibilities of parallelism 
:-(

Another option would be

runProgram [] = return []
runProgram (c:cs) = unsafeInterleaveIO $ do
    ph <- runCommand ("lalala " ++ c)
    phs <- runProgram cs
    return (ph:phs)

and then,
    processHandles <- runProgram blah
    mapM_ waitForProcess (processHandles)
    next step

that should work (I hope) and would allow the commands to be run in parallel 
while making 
sure all have finished before the next step is started.

>
> It might be possible to write the function runProgram in a way, so that
> it returns an expression of type [IO ProcessHandle] and then try to work
> from there.  But I have the feeling, that this will become messy very
> quickly, and there must be some more elegant way of doing this.  The
> other thing is that actually not all functions are able to return
> ProcessHandles, e.g.
>
> writeFeatures :: [String] -> IO ()
> writeFeatures cs = Exc.bracket (openFile training AppendMode) hClose (\h
> -> goo h)
>   where
>     goo h = go 1 cs
>       where
>         go :: Int -> [String] -> IO ()
>         go n [] = putStrLn "Features written."
>         go n (c:cs) = do
>           features <- makeFeatures n c    -- makeFeatures :: Int ->
> String -> IO String
>           hPutStr h features
>           go (n+1) cs
>
> And the file that is produced here is needed in the next function.

That can't appear in runProgram, though.

I'm not sure it would work, but you coud give

{-# LANGUAGE BangPatterns #-}

...
    !a <- writeFeatures blah
    more

or 
    go n (c:cs) = do
        features <- makeFeatures n c
        !a <- hPutStr h features
        go (n+1) cs

a try.

>
> I hoped to do something with forkIO, as I would like to parallelize the
> whole program at the end.  Especially the function runProgram would
> benefit hugely from this (I so don't have a clue how to do this yet;). I
> tried for example the following:
>
> main :: IO ()
> main = do
>  cs <- getArgs
>  p1 <- forkIO $ writeData cs
>  p2 <- forkIO $ runProgram cs
>  p3 <- forkIO $ writeFeatures cs
>  p4 <- forkIO $ runTestOnFeatures
>  seq p1 (seq p2 (seq p3 (seq p4 (putStrLn "Done"))))
>
> But that of course doesn't work, because now I am not actually
> requesting anything.  The program does in fact nothing, apart from
> printing out "Done".

Huh. There doesn't seem to be a wait function for ThreadIds, so I guess you 
would have to 
communicate via MVars, QSemNs or some such means to signal that one task has 
been 
completed and the next can be started.

>
> Any ideas?
>
> Cheers,
> Thomas




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

Message: 8
Date: Thu, 7 May 2009 22:10:53 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Real World Haskell Chapter 5
To: beginners@haskell.org
Message-ID: <200905072210.53557.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-15"

Am Donnerstag 07 Mai 2009 21:18:46 schrieb PJ Fitzpatrick:
> Hi,
> I have compiled the SimpleJSON.hs file from chapter 5 and from another file
> attempted to import it. I am getting a could not find module error and the
> prelude tells me that the locations searched were SimpleJSON.hs and
> SimpleJSON.lhs.
> I am running Vista, GHC 6.10.2
> Any ideas?
> tks,
> PJ

If the other file is not in the same directory, you have to tell GHC where to 
look for it,

ghc -ipath/to/SimpleJSONDir:path/to/OtherImport --make UseSimpleJSON

or build a package with SimpleJSON in it (using Cabal) and register that, then 
ghc --make 
will know where to find it.

If the file is in the same directory, it may be an encoding error (or some 
case-muck-up), 
but definitely something bad.


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

Message: 9
Date: Thu, 7 May 2009 17:25:40 -0400
From: "Brandon S. Allbery KF8NH" <allb...@ece.cmu.edu>
Subject: Re: [Haskell-beginners] How to wait till a process is
        finished before invoking the next one?
To: Thomas Friedrich <i...@suud.de>
Cc: beginners@haskell.org
Message-ID: <3895bfdd-3c6c-46cb-adbd-6712d7d97...@ece.cmu.edu>
Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes

-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA1

On May 7, 2009, at 14:53 , Thomas Friedrich wrote:
> writeFeatures :: [String] -> IO ()
> writeFeatures cs = Exc.bracket (openFile training AppendMode) hClose  
> (\h -> goo h)
> where
>   goo h = go 1 cs
>     where
>       go :: Int -> [String] -> IO ()
>       go n [] = putStrLn "Features written."
>       go n (c:cs) = do
>         features <- makeFeatures n c    -- makeFeatures :: Int ->  
> String -> IO String
>         hPutStr h features
>         go (n+1) cs
>
> And the file that is produced here is needed in the next function.

You probably want to rethink how you're doing this.  My own thought is  
that you have something like:

 > runThis :: FilePath -> [String] -> String -> IO (MVar String)
 > runThis cmd args inp = do
 >   mvar <- newEmptyMVar
 >   forkIO (readProcess cmd args inp >>= writeMVar mvar)
 >   return mvar

runOne launches in the background, you synchronize by doing takeMVar  
on the returned MVar (which will give you the output, if any).  Even  
if there is no useful output you can still create data dependencies to  
insure things wait for what they need --- and that is exactly what you  
want to do:  insure that there are data dependencies to constrain when  
programs are run.

Otherwise, you'll have to settle for linear execution.

- --
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university    KF8NH


-----BEGIN PGP SIGNATURE-----
Version: GnuPG v2.0.10 (Darwin)

iEYEARECAAYFAkoDUeAACgkQIn7hlCsL25VH/gCghNldOSJnChoHrJwjeaboseU4
Z28An39bR2DAAlP6K9g00eb+NnHhKZSU
=NHpz
-----END PGP SIGNATURE-----


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

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


End of Beginners Digest, Vol 11, Issue 7
****************************************

Reply via email to