Send Beginners mailing list submissions to
        [email protected]

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
        [email protected]

You can reach the person managing the list at
        [email protected]

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Working out the types (Patrick LeBoutillier)
   2.  I get no speedup with RWH examples of parallel   sorting
      (Kees Bleijenberg)
   3. Re:  I get no speedup with RWH examples of        parallel sorting
      (David Place)
   4.  Does one need a ticket to attend ICFP? (Sebastien Zany)
   5.  Throughly confused by this error message (Michael Litchard)
   6. Re:  Does one need a ticket to attend ICFP? (Erik de Castro Lopo)
   7. Re:  Throughly confused by this error message (Michael Litchard)


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

Message: 1
Date: Wed, 6 Jul 2011 08:19:44 -0400
From: Patrick LeBoutillier <[email protected]>
Subject: Re: [Haskell-beginners] Working out the types
To: Daniel Fischer <[email protected]>
Cc: [email protected]
Message-ID:
        <CAJcQsbiin4WPvaDjvN-Fi1uuAA9pXAyzKpay7_nKR4=0jbc...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Daniel,

The paper you recommend seems like very interesting stuff.  I will
definitely look at it closer.


Thanks a lot,

Patrick


On Tue, Jul 5, 2011 at 3:24 PM, Daniel Fischer
<[email protected]> wrote:
> On Tuesday 05 July 2011, 19:55:43, Patrick LeBoutillier wrote:
>> Hi all,
>
>> Here's my question: Does ghci have a verbose mode or something where
>> is can show you step by step how the types
>> are worked out?
>
> No. You can use it to get the types of subexpressions, though, and work
> towards the complete expression from that:
>
> Prelude> :t (:)
> (:) :: a -> [a] -> [a]
> Prelude> :t (. (:))
> (. (:)) :: (([a] -> [a]) -> c) -> a -> c
> Prelude> :t (map . (:))
> (map . (:)) :: a -> [[a]] -> [[a]]
>
> which gives you smaller gaps to fill in.
>
>> If not is there a hackage (or any other kind of)
>> package that can do that?
>
> I'm not aware of any, but there might be.
>
>>
>> a lot, so I was wondering if such a program existed that could do it
>> automatically.
>
> Automatic type checkers do exist (every compiler/interpreter needs one),
> but I don't think they have been written with the ability to output not
> only the result but also the derivation.
>
> For someone familiar with a particular type checker, it probably wouldn't
> be hard to add that feature, but if it's a complicated beast like GHC's
> type checker, becoming familiar with it would probably be a big
> undertaking.
>
> Writing your own much-reduced (able to parse and typecheck only a very
> restricted subset of the language) might be easier, but probably working
> from Mark P. Jones' "Typing Haskell in Haskell"
> http://web.cecs.pdx.edu/~mpj/thih/
> would be better than starting from scratch (it's somewhat oldish, so it
> certainly doesn't cope with recent GHC extensions, but for everyday run-of-
> the-mill problems, it should be working with only minor modifications).
>
>



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



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

Message: 2
Date: Wed, 6 Jul 2011 17:08:41 +0200
From: "Kees Bleijenberg" <[email protected]>
Subject: [Haskell-beginners] I get no speedup with RWH examples of
        parallel        sorting
To: <[email protected]>
Message-ID: <[email protected]>
Content-Type: text/plain; charset="us-ascii"

I've carefully followed the instructions in Real World Haskell for parallel
sorting:
In SortMain.hs
1. Set testfunction=sort
Then del *.o  (force recompilation)
ghc --make -O2 sortMain.hs
run SortMain and I get 500000 numbers  => 3.9735 sec.
 
2. Set testFunction = parSort2 2
del *.o 
ghc -threaded --make -O2 sortMain.hs
run SortMain +RTS -N2 -RTS,  I get =>  5.3 sec
run SortMain +RTS -N1 -RTS,  I get =>  4.3 sec
With the +RTS -s option I get 3 SPARK3 (3 converted, 0 pruned)
All other testFunctions are worse.
 
I have a dual core computer that runs Windows XP. 
I've experimented a lot with par, pseq ... in other programs. I almost
always get a few hundred sparks. Half of them are converted and the other
half gets pruned. But I never got a faster program (then sequential).
 
What am I doing wrong, any ideas?
 
Kees
 
 
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20110706/145b2d3f/attachment-0001.htm>

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

Message: 3
Date: Wed, 6 Jul 2011 11:43:27 -0400
From: David Place <[email protected]>
Subject: Re: [Haskell-beginners] I get no speedup with RWH examples of
        parallel sorting
To: "Kees Bleijenberg" <[email protected]>
Cc: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset="us-ascii"

My experience with running parallel programs on dual processor machines is 
similar.  With only two processors, one is always busy doing something for the 
OS.  As a result, it rarely gets scheduled.   You need a quad cpu to play with 
parallel programming.


____________________
David Place   
Owner, Panpipes Ho! LLC
http://panpipesho.com
[email protected]



On Jul 6, 2011, at 11:08 AM, Kees Bleijenberg wrote:

> I've carefully followed the instructions in Real World Haskell for parallel 
> sorting:
> In SortMain.hs
> 1. Set testfunction=sort
> Then del *.o  (force recompilation)
> ghc --make -O2 sortMain.hs
> run SortMain and I get 500000 numbers  => 3.9735 sec.
>  
> 2. Set testFunction = parSort2 2
> del *.o
> ghc -threaded --make -O2 sortMain.hs
> run SortMain +RTS -N2 -RTS,  I get =>  5.3 sec
> run SortMain +RTS -N1 -RTS,  I get =>  4.3 sec
> With the +RTS -s option I get 3 SPARK3 (3 converted, 0 pruned)
> All other testFunctions are worse.
>  
> I have a dual core computer that runs Windows XP.
> I've experimented a lot with par, pseq ... in other programs. I almost always 
> get a few hundred sparks. Half of them are converted and the other half gets 
> pruned. But I never got a faster program (then sequential).
>  
> What am I doing wrong, any ideas?
>  
> Kees
>  
>  
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners

-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20110706/318e2491/attachment-0001.htm>

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

Message: 4
Date: Wed, 6 Jul 2011 13:13:42 -0700
From: Sebastien Zany <[email protected]>
Subject: [Haskell-beginners] Does one need a ticket to attend ICFP?
To: Haskell Beginners <[email protected]>
Message-ID:
        <caa+2x_vakwsf162zfsl1hq4wcbuz4pgqm8mqxoae2dnrf37...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

There's a "Registration" item on the left menu at
http://www.icfpconference.org/icfp2011/ but it doesn't link to anywhere. Can
I just show up?

Sebastien
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20110706/177cef8f/attachment-0001.htm>

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

Message: 5
Date: Wed, 6 Jul 2011 15:42:15 -0700
From: Michael Litchard <[email protected]>
Subject: [Haskell-beginners] Throughly confused by this error message
To: [email protected]
Message-ID:
        <caezekyrn9rpst85sqads5hukgexett9rnavfxr4oacd2vpy...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

I'd like someone to help me learn what questions to ask about this
error. I'm not sure how to contextualize. I will include code segments
that I think are important, and trust your questions will reveal what
I am leaving out.



HtmlParsing.lhs:81:25:
    The first argument of ($) takes one argument,
    but its type `URLString' has none
    In the second argument of `($)', namely `initial $ method_GET'
    In a stmt of a 'do' expression:
          curlResp curl $ initial $ method_GET
    In the expression:
      do { let initial = urlInitial urlSequence
               login = urlLogin urlSequence
               ....;
             curlResp curl $ initial $ method_GET;
             curlResp curl $ urlLogin urlSequence $ loginOpts user pass;
             curlResp curl $ urlFlash1 urlSequence resourceOpts;
           .... }


> generateResourceHtml :: Curl -> String -> String -> FilePath -> IO (Either 
> String String)
> generateResourceHtml curl user pass ipFile = do
>   urlSequence <- popURLrec ipFile
>   let makeIDPage = do
>       let initial = urlInitial urlSequence
>           login = urlLogin urlSequence
>           flash1 = urlFlash1 urlSequence
>           flash2 = urlFlash2 urlSequence
>           showWebForwards = urlShowWebForwards urlSequence
>           quickCreate = urlQuickCreate urlSequence
>           getResource =  urlGetResource urlSequence
>       curlResp curl $ initial $ method_GET
>       curlResp curl $ urlLogin urlSequence $ loginOpts user pass
>       curlResp curl $ urlFlash1 urlSequence resourceOpts
>       curlResp curl $ urlFlash2 urlSequence resourceOpts
>       curlResp curl $ urlShowWebForwards urlSequence resourceOpts
>       curlResp curl $ urlQuickCreate urlSequence resourceOpts
>       curlResp curl $ urlGetResource urlSequence resourceOpts
>   runErrorT makeIDPage

> data URLSequence = URLSequence { urlInitial :: URLString
>                                , urlLogin :: URLString
>                                , urlFlash1 :: URLString
>                                , urlFlash2 :: URLString
>                                , urlShowWebForwards :: URLString
>                                , urlQuickCreate :: URLString
>                                , urlGetResource :: URLString
>                                } deriving Show

> curlResp :: (Error e, MonadError e m, MonadIO m) =>
>       Curl -> URLString -> [CurlOption] -> m String --CurlResponse
> curlResp curl url opts = do
>   resp <- liftIO $ (do_curl_ curl url opts :: IO CurlResponse)
>   let code   = respCurlCode resp
>       status = respStatus resp
>   if code /= CurlOK || status /= 200
>      then throwError $ strMsg $ "Error: " ++ show code ++ " -- " ++ show 
> status
>      else return $ respBody resp



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

Message: 6
Date: Thu, 7 Jul 2011 08:46:29 +1000
From: Erik de Castro Lopo <[email protected]>
Subject: Re: [Haskell-beginners] Does one need a ticket to attend
        ICFP?
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=US-ASCII

Sebastien Zany wrote:

> There's a "Registration" item on the left menu at
> http://www.icfpconference.org/icfp2011/ but it doesn't link to anywhere. Can
> I just show up?

I don't thnk registration is open yet.

Erik
-- 
----------------------------------------------------------------------
Erik de Castro Lopo
http://www.mega-nerd.com/



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

Message: 7
Date: Wed, 6 Jul 2011 16:03:08 -0700
From: Michael Litchard <[email protected]>
Subject: Re: [Haskell-beginners] Throughly confused by this error
        message
To: [email protected]
Message-ID:
        <caezekypan2bydsmfh86e8pler69ayu1yw9ijhfi5k921kb7...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

You know, it's happened more than once. I'll send my problem to this
list, and a few minutes later I see someone really obviously wrong.
The problem is partially fixed in the sense that the changes I made
are producing errors that make sense to me.

On Wed, Jul 6, 2011 at 3:42 PM, Michael Litchard <[email protected]> wrote:
> I'd like someone to help me learn what questions to ask about this
> error. I'm not sure how to contextualize. I will include code segment> that I 
> think are important, and trust your questions will reveal what
> I am leaving out.
>
>
>
> HtmlParsing.lhs:81:25:
> ? ?The first argument of ($) takes one argument,
> ? ?but its type `URLString' has none
> ? ?In the second argument of `($)', namely `initial $ method_GET'
> ? ?In a stmt of a 'do' expression:
> ? ? ? ? ?curlResp curl $ initial $ method_GET
> ? ?In the expression:
> ? ? ?do { let initial = urlInitial urlSequence
> ? ? ? ? ? ? ? login = urlLogin urlSequence
> ? ? ? ? ? ? ? ....;
> ? ? ? ? ? ? curlResp curl $ initial $ method_GET;
> ? ? ? ? ? ? curlResp curl $ urlLogin urlSequence $ loginOpts user pass;
> ? ? ? ? ? ? curlResp curl $ urlFlash1 urlSequence resourceOpts;
> ? ? ? ? ? .... }
>
>
>> generateResourceHtml :: Curl -> String -> String -> FilePath -> IO (Either 
>> String String)
>> generateResourceHtml curl user pass ipFile = do
>> ? urlSequence <- popURLrec ipFile
>> ? let makeIDPage = do
>> ? ? ? let initial = urlInitial urlSequence
>> ? ? ? ? ? login = urlLogin urlSequence
>> ? ? ? ? ? flash1 = urlFlash1 urlSequence
>> ? ? ? ? ? flash2 = urlFlash2 urlSequence
>> ? ? ? ? ? showWebForwards = urlShowWebForwards urlSequence
>> ? ? ? ? ? quickCreate = urlQuickCreate urlSequence
>> ? ? ? ? ? getResource = ?urlGetResource urlSequence
>> ? ? ? curlResp curl $ initial $ method_GET
>> ? ? ? curlResp curl $ urlLogin urlSequence $ loginOpts user pass
>> ? ? ? curlResp curl $ urlFlash1 urlSequence resourceOpts
>> ? ? ? curlResp curl $ urlFlash2 urlSequence resourceOpts
>> ? ? ? curlResp curl $ urlShowWebForwards urlSequence resourceOpts
>> ? ? ? curlResp curl $ urlQuickCreate urlSequence resourceOpts
>> ? ? ? curlResp curl $ urlGetResource urlSequence resourceOpts
>> ? runErrorT makeIDPage
>
>> data URLSequence = URLSequence { urlInitial :: URLString
>> ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ?, urlLogin :: URLString
>> ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ?, urlFlash1 :: URLString
>> ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ?, urlFlash2 :: URLString
>> ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ?, urlShowWebForwards :: URLString
>> ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ?, urlQuickCreate :: URLString
>> ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ?, urlGetResource :: URLString
>> ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ?} deriving Show
>
>> curlResp :: (Error e, MonadError e m, MonadIO m) =>
>> ? ? ? Curl -> URLString -> [CurlOption] -> m String --CurlResponse
>> curlResp curl url opts = do
>> ? resp <- liftIO $ (do_curl_ curl url opts :: IO CurlResponse)
>> ? let code ? = respCurlCode resp
>> ? ? ? status = respStatus resp
>> ? if code /= CurlOK || status /= 200
>> ? ? ?then throwError $ strMsg $ "Error: " ++ show code ++ " -- " ++ show 
>> status
>> ? ? ?else return $ respBody resp
>



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

_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners


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

Reply via email to