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.  Help me make sense of this error (Michael Litchard)
   2. Re:  Help me make sense of this error (aditya siram)
   3. Re:  Help me make sense of this error (Daniel Fischer)
   4.  Ffi, memory allocation and failure ( [email protected] )


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

Message: 1
Date: Tue, 8 Feb 2011 15:48:52 -0800
From: Michael Litchard <[email protected]>
Subject: [Haskell-beginners] Help me make sense of this error
To: [email protected]
Message-ID:
        <[email protected]>
Content-Type: text/plain; charset="iso-8859-1"

Here's the three main functions involved. Let me know if I am missing
pertinent information.

I'm having difficulty unraveling this error message. Help?

> obtainCookies :: Curl -> String -> IO ()
> obtainCookies curl responseBody = do
>                 return $ last $ liftM $
>                    mapM (flip (curlResp2 curl) resourceOpts)
>                     screenScraping responseBody

> screenScraping :: String -> [URLString]
> screenScraping responseBody =
>                let collectedStrings = processHTML responseBody
>                    collectedIDLists = createIDList collectedStrings
>                    in constructedResourceURIs urlBase collectedIDLists

> constructedResourceURIs :: String -> [String] -> [URLString]
> constructedResourceURIs url resourceIDs =
>                         let frontURI = url ++ "/launchWebForward.do?"
>                             midURI = map (frontURI ++) resourceIDs
>                         in map (++ 
> "&policy=0&returnTo=%2FshowWebForwards.do") midURI



HtmlParsing.lhs:81:22:
    Couldn't match expected type `[URLString]'
           against inferred type `String -> [URLString]'
    In the second argument of `mapM', namely `screenScraping'
    In the second argument of `($)', namely
        `mapM
           (flip (curlResp2 curl) resourceOpts) screenScraping responseBody'
    In the second argument of `($)', namely
        `liftM
       $ mapM
           (flip (curlResp2 curl) resourceOpts) screenScraping responseBody'
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20110208/a53c08ae/attachment-0001.htm>

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

Message: 2
Date: Tue, 8 Feb 2011 18:06:59 -0600
From: aditya siram <[email protected]>
Subject: Re: [Haskell-beginners] Help me make sense of this error
To: Michael Litchard <[email protected]>
Cc: [email protected]
Message-ID:
        <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1

It seems like you're being bitten by precedence rules. Your expression
mapM (...) screenScraping responseBody evaluates like this: (mapM
(...) screenScraping) responseBody. You probably want parentheses
aroung screenScraping responseBody. So something like:
mapM (flip ....) (screenScraping responseBody)
or
mapM (flip ...) $ screenScraping responseBody

On Tue, Feb 8, 2011 at 5:48 PM, Michael Litchard <[email protected]> wrote:
> Here's the three main functions involved. Let me know if I am missing
> pertinent information.
>
>
> I'm having difficulty unraveling this error message. Help?
>
>> obtainCookies :: Curl -> String -> IO ()
>
>> obtainCookies curl responseBody = do
>>                 return $ last $ liftM $
>
>>                    mapM (flip (curlResp2 curl) resourceOpts)
>>                     screenScraping responseBody
>
>
>> screenScraping :: String -> [URLString]
>> screenScraping responseBody =
>>                let collectedStrings = processHTML responseBody
>
>>                    collectedIDLists = createIDList collectedStrings
>>                    in constructedResourceURIs urlBase collectedIDLists
>
>
>> constructedResourceURIs :: String -> [String] -> [URLString]
>> constructedResourceURIs url resourceIDs =
>
>>                         let frontURI = url ++ "/launchWebForward.do?"
>>                             midURI = map (frontURI ++) resourceIDs
>
>>                         in map (++
>> "&policy=0&returnTo=%2FshowWebForwards.do") midURI
>
>
>
>
> HtmlParsing.lhs:81:22:
>     Couldn't match expected type `[URLString]'
>
>            against inferred type `String -> [URLString]'
>     In the second argument of `mapM', namely `screenScraping'
>
>     In the second argument of `($)', namely
>         `mapM
>            (flip (curlResp2 curl) resourceOpts) screenScraping responseBody'
>
>     In the second argument of `($)', namely
>         `liftM
>        $ mapM
>
>            (flip (curlResp2 curl) resourceOpts) screenScraping responseBody'
>
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
>
>



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

Message: 3
Date: Wed, 9 Feb 2011 01:45:02 +0100
From: Daniel Fischer <[email protected]>
Subject: Re: [Haskell-beginners] Help me make sense of this error
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain;  charset="utf-8"

On Wednesday 09 February 2011 00:48:52, Michael Litchard wrote:
> Here's the three main functions involved. Let me know if I am missing
> pertinent information.
>
> I'm having difficulty unraveling this error message. Help?
>
> > obtainCookies :: Curl -> String -> IO ()
> > obtainCookies curl responseBody = do
> >                 return $ last $ liftM $

> >                    mapM (flip (curlResp2 curl) resourceOpts)
> >                     screenScraping responseBody

This is parsed as

           (mapM (flip (curlResp2 curl) resourceOpts) screenScraping)
                    responseBody

which of course doesn't make sense, since screenScraping is a function, not 
a list. You forgot a ($) or parentheses,

       mapM (flip (curlResp2 curl) resourceOpts) $
           screenScraping responseBody

But then you get another error,

liftM :: Monad m => (a -> b) -> m a -> m b

so it expects a function as first argument, but it gets an (IO [a]).
You probably meant

      liftM last $ mapM ...

but that already is an IO (), so the return shouldn't be there (it would 
make obtainCookies an IO (IO ()), which isn't what you want.

However,

curlResp2 :: Curl -> String -> [CurlOpts {- or whatever opts they were -}]
                    -> IO ()

so it doesn't return any meaningful value. Then don't use mapM.
mapM should only be used if one really wants to collect the results of the 
mapM'ed action, if the result type of action is IO () [more generally, 
Monad m => m ()] or one isn't interested in the results, only in the 
effects of running the actions, one should use

mapM_ :: Monad m => (a -> m b) -> [a] -> m ()

which discards the results of the actions and is much more efficient (since 
it needn't keep book).

So,

obtainCookies curl responseBody =
   mapM_ (flip (curlResp2 curl) resourceOpts) (screenScraping responseBody)

> >
> > screenScraping :: String -> [URLString]
> > screenScraping responseBody =
> >                let collectedStrings = processHTML responseBody
> >                    collectedIDLists = createIDList collectedStrings
> >                    in constructedResourceURIs urlBase collectedIDLists

What about

screenScraping =
    constructedResourceURIs urlBase
    . createIDList
    . processHTML

?

Or, if you prefer, with (>>>) [from Control.Arrow or defined yourself as 
flip (.)], in left-to-right order:

screenScraping =
    processHTML >>>
    createIDList    >>>
    constructedResourceURIs urlBase

> >
> > constructedResourceURIs :: String -> [String] -> [URLString]
> > constructedResourceURIs url resourceIDs =
> >                         let frontURI = url ++ "/launchWebForward.do?"
> >                             midURI = map (frontURI ++) resourceIDs
> >                         in map (++
> > "&policy=0&returnTo=%2FshowWebForwards.do") midURI

constructedResourceURIs url resourceIDs =
  [frontURI ++ str ++ uriEnd | str <- resourceIDs]
  where
    frontURI = url ++ "/launchWebForward.do?"
    uriEnd = "&policy=0&returnTo=%2FshowWebForwards.do"

or

constructedResourceURIs url = map ((frontURI ++) . (++ uriEnd))
  where
    frontURI = url ++ "/launchWebForward.do?"
    uriEnd = "&policy=0&returnTo=%2FshowWebForwards.do"

if you develop a taste for partial pointfreeness.

>
> HtmlParsing.lhs:81:22:
>     Couldn't match expected type `[URLString]'
>            against inferred type `String -> [URLString]'
>     In the second argument of `mapM', namely `screenScraping'
>     In the second argument of `($)', namely
>         `mapM
>            (flip (curlResp2 curl) resourceOpts) screenScraping
> responseBody' In the second argument of `($)', namely
>         `liftM
>        $ mapM
>            (flip (curlResp2 curl) resourceOpts) screenScraping
> responseBody'




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

Message: 4
Date: Wed, 09 Feb 2011 09:45:09 +0100
From: " [email protected] " <[email protected]>
Subject: [Haskell-beginners] Ffi, memory allocation and failure
To: " [email protected] " <[email protected]>
Message-ID: <[email protected]>
Content-Type: text/plain; charset="utf-8"


Dear Haskellers,
I have a question about the FFI and interfacing to C++ via C.
I want to use funcionality that I have implemented a while ago
using C++ classes, and I also see this as an exercise on how to
create wrappers using the Haskell FFI.

The class I want to wrap first is a matrix class.
Here is the thing: In order to create a matrix object, I create a C function
that calls the C++ new operator, creating a matrix object, and
returning it as a void pointer.
Deletion is handled analogously.
Then in Haskell, I import the two functions, and I have a matrix type
like this:
newtype Matrix = Matrix (Ptr Matrix)

>From this I create a ForeignPtr with newForeignPtr, giving the
deletion function (which calls the C++ destructor for a matrix)
as finalizer.

Testing this showed me that it does work.
/But/: So far everything is happening in the IO monad. However, I want to
be able to work with matrices outside IO. Now, of course memory allocation
can fail, and I don't want to use something like unsafePerformIO when
there can actually be a failure when calling the constructor for a matrix.

Is there a recommended way to do this?
Also, is there a way to get memory from the Haskell runtime system in a safer
way and construct the object in that memory?

I hope I could make myself clear enough, as usual thanks for any hints!!
Christian

-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20110209/727154c9/attachment-0001.htm>

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

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


End of Beginners Digest, Vol 32, Issue 25
*****************************************

Reply via email to