[Haskell-cafe] Re: how to user mergeIO
OK, I think I figured it out. If I understand correctly, I was just computing the input lists in parallel. The actual values were computed in the main thread lazily, later. This seems unintuitive to me. Shouldn't the merge functions force the evaluation of their arguments? Surely one wouldn't be calling them if they wanted to compute the results lazily. On Sun, Mar 14, 2010 at 6:25 PM, Brock Peabody wrote: > Hi, > I've been trying to use Control.Concurrent.mergeIO to parallelize > computation, and can't make it work. In the sample program below, I expect > the function 'parallelTest' to be almost twice as fast as 'sequentialTest', > and to compute its results in two threads, as implied by the documentation > for mergeIO. This is not what happens. If I link my program with the > option '-threaded', the running process does have three threads. If I run > with the option "+RTS -N2", the process will have 5 threads. In no case > does the process appear to be using more than one CPU, and in fact it is > slower with the threading options turned on. > > I'm sure I am doing something obviously (to someone else) wrong. Any ideas? > > I am running the latest version of Mac OSX on a core2 duo machine with 2 > cores, using ghc version 6.10.4. > > Cheers, Brock > > My test program follows: > > {-# OPTIONS_GHC -fglasgow-exts #-} > module Main where > > import Control.Concurrent > import Random > > doSum :: RandomGen g => g -> Int -> Integer > doSum g count > = let runner curG sum numDone > | numDone == count = sum > | otherwise > = let (newNum :: Integer, newG) = random curG > newSum = sum + newNum > newNumDone = numDone + 1 > in ((runner $! newG) $! newSum) $! newNumDone > in runner g 0 0 > > sequentialTest > = do let gen = mkStdGen 0 >(g0,g1) = split gen >count = 1000 >sum0 = doSum g0 count >sum1 = doSum g1 count >total = sum0 + sum1 >putStrLn $ "total: " ++ show total > > parallelTest > = do let gen = mkStdGen 0 >(g0,g1) = split gen >count = 1000 >sum0 = doSum g0 count >sum1 = doSum g1 count >[res0, res1] <- mergeIO [sum0] [sum1] >let total = res0 + res1 >putStrLn $ "total: " ++ show total > main > = parallelTest > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] how to user mergeIO
Hi, I've been trying to use Control.Concurrent.mergeIO to parallelize computation, and can't make it work. In the sample program below, I expect the function 'parallelTest' to be almost twice as fast as 'sequentialTest', and to compute its results in two threads, as implied by the documentation for mergeIO. This is not what happens. If I link my program with the option '-threaded', the running process does have three threads. If I run with the option "+RTS -N2", the process will have 5 threads. In no case does the process appear to be using more than one CPU, and in fact it is slower with the threading options turned on. I'm sure I am doing something obviously (to someone else) wrong. Any ideas? I am running the latest version of Mac OSX on a core2 duo machine with 2 cores, using ghc version 6.10.4. Cheers, Brock My test program follows: {-# OPTIONS_GHC -fglasgow-exts #-} module Main where import Control.Concurrent import Random doSum :: RandomGen g => g -> Int -> Integer doSum g count = let runner curG sum numDone | numDone == count = sum | otherwise = let (newNum :: Integer, newG) = random curG newSum = sum + newNum newNumDone = numDone + 1 in ((runner $! newG) $! newSum) $! newNumDone in runner g 0 0 sequentialTest = do let gen = mkStdGen 0 (g0,g1) = split gen count = 1000 sum0 = doSum g0 count sum1 = doSum g1 count total = sum0 + sum1 putStrLn $ "total: " ++ show total parallelTest = do let gen = mkStdGen 0 (g0,g1) = split gen count = 1000 sum0 = doSum g0 count sum1 = doSum g1 count [res0, res1] <- mergeIO [sum0] [sum1] let total = res0 + res1 putStrLn $ "total: " ++ show total main = parallelTest ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] newbie - how to call a Haskell interpreter from C
On 8/25/07, Henk-Jan van Tuyl <[EMAIL PROTECTED]> wrote: > > > The easiest way to run Haskell software from a C program is to give the > shell command: >runhaskell Foo.hs I'm a newbie but not that new :) I really have to be able to interpret the Haskell from within the same process. A more advanced way is, to link Haskell libraries by means of the foreign > function interface (FFI) [1]. > There are several tools to support FFI development [2]. I am sure my list > of URL's is not complete. > > [1] http://www.cse.unsw.edu.au/~chak/haskell/ffi/ > <http://www.cse.unsw.edu.au/%7Echak/haskell/ffi/> > http://www.haskell.org/haskellwiki/FFI_Introduction > http://www.haskell.org/haskellwiki/FFI_cook_book > > [2] http://www.haskell.org/haskellwiki/FFI_imports_packaging_utility > http://www.haskell.org/haskellwiki/HSFFIG My understanding is that FFI helps you to call into other languages from Haskell and vice-versa. I will definitely need this, but what I can't figure out how to do is to invoke the ghci or hugs interpreter programmatically, in-process. I didn't see a way to do that in the links you listed, am I missing something? Much thanks, Brock Peabody ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] newbie - how to call a Haskell interpreter from C
Hi, I've been trying to find place to use Haskell at work, and I think a good opportunity will be to use it for our scripting language. To do that, I need to be able to invoke an interpreter directly from another language. I've investigated using HaskellScript (too web/ActiveX centric), but really I just want to compile ghci or hugs into my executable/library. It seems like this is something I should be able to figure out easily, but so far I've failed and have not found any reference to others succeeding. any advice? thanks in advance, Brock ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: Re[2]: [Haskell-cafe] newbie type signature question
> From: Bulat Ziganshin [mailto:[EMAIL PROTECTED] > when you work with C++ or some other OOP language, you can define that > some field in structure should some some specific interface and this > allows to use functions of this interface on this field. i required > the same feature in Haskell, for example: I come from a C++ background, and there is no formal way in the language to specify constraints for type (template) parameters; a major weakness for generic programming. Some interesting work is being done to add this ability though, ex: http://www.boost.org/libs/concept_check/concept_check.htm. Regards, Brock ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] newbie type signature question
> Brian Hulley wrote: > "Don't put class constraints on a data type, >constraints belong only to the functions >that manipulate the data." > > So according to this guideline you're not supposed to think of associating > contraints with data: constraints are only relevant for functions which > manipulate the data, therefore (if you agree with this view) the very idea > of associating constraints with data is wrong. I wonder what the reasoning for this guideline is. It seems that it would require one to repeat the constraint over and over. For the Prelude Data.Map type, for instance, wouldn't almost every function have to have the constraint that the key type is ordered? Also, I think it would push detection of the error further from the place where it could have been detected. Doesn't it make more sense to detect that there is an error when a user tries to instantiate a map with an unordered type rather than later when an attempt is made to use it? Regards, Brock ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] newbie type signature question
> From: Brandon Moore > Getting them both is tricky, but you can do it if you use a GADT to > write a type that means "exists a such that a = m and a is a Monad": Is GADT a way to assemble types at compile-time? It looks really cool. > {-# OPTIONS -fglasgow-exts #-} > data TyEq (a :: * -> *) (b :: * -> *) where ^ ^ Compiling this fails here (the first '*') for me with "parse error on input '*'" (ghc 6.4.1), but I'll keep playing with it. Thanks, Brock ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] newbie type signature question
> Brian Hulley wrote: > There was a post a while back (unfortunately I can't seem to locate it) > where someone posted a link to some guidelines on haskell coding style > where > one guideline was never to use contexts in data declarations. I would love to see that guideline. What is the correct way to express a constraint for a data declaration if this way is wrong? Thanks, Brock ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] newbie type signature question
Please excuse my newbiness, but in this snippet: data (Monad m) => DataType m = DataType { f :: Char -> m () } test_function :: (Monad m) => DataType m -> m () test_function d = f d 'C' Why is "(Monad m) =>" required, when the definition of DataType already implies it? Is there an easier way to do this or will I have to have it in all signatures containing DataType? Thanks, Brock ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] database access recommendation
Hi Bulat, Thanks for all the information. I'm giving HDBC a try as it seems to be the most actively maintained and because I was able to install it. Regards, Brock ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] database access recommendation
> From: Duncan Coutts [mailto:[EMAIL PROTECTED] > It's that too! And SQLite and you can write other backends > independently. Sounds cool! Unfortunately I'm having problems installing it but I think it's probably something simple this time. I can configure, build, and install hdbc. When I try to build hdbc-postgresql it fails because it can't include libpq-fe.h or pg_config.h, both of which are present in /usr/local/include. I noticed when I ran configure that it mentioned the absence of haddock, happy, and alex, so I am installing them just in case that had anything to do with it. Thanks, Brock ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] database access recommendation
> From: Duncan Coutts [mailto:[EMAIL PROTECTED] > There is also HDBC which is nearing a 1.0 release and in my experience > is easier to install. (I package both HSQL & HDBC for Gentoo) Thanks, I'll check that out. For some reason I saw HDBC and just assumed it was an interface for ODBC. Brock ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] database access recommendation
I'm teaching myself Haskell, and was wondering if anyone could recommend a library for accessing databases, PostgreSQL in particular. I looked at http://www.haskell.org/haskellwiki/Libraries_and_tools, and HSQL looked promising, but I can't get it to install on Windows or FreeBSD, with Hugs or GHC. According to the FreeBSD ports system, it is marked as broken. It fails with Hugs on both platforms on the "runhugs Setup.lhs configure" step in the base HSQL library with: FreeBSD: ERROR "/usr/local/lib/hugs/libraries/Text/ParserCombinators/ReadP.hs":133 - Syntax error in type expression (unexpected `.') Windows: ERROR "C:\Program Files\WinHugs\libraries\Text\ParserCombinators\ReadP.hs":156 - Syntax error in type expression (unexpected `.') GHC crashes with no error on the "runghc Setup.lhs build" step in the base HSQL library in Windows. In FreeBSD I can completely build and install the base library, but in any of the database specific directories, "runghc Setup.lhs configure" yields: "Setup.lhs:17:71: Couldn't match `PackageDescription' against `LocalBuildInfo' Expected type: Args -> ConfigFlags -> LocalBuildInfo -> IO ExitCode Inferred type: [String] -> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO ExitCode In the `postConf' field of a record In the record update: defaultUserHooks {preConf = preConf, postConf = postConf} :1:87: Failed to load interface for `Main': Bad interface file: Setup.hi Setup.hi: openBinaryFile: does not exist (No such file or directory)" Thanks, Brock ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe