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:  Missing some functions in Hoogle (Ken Kawamoto)
   2.  Stymied by mutable arrays in the ST monad (Matthew Moppett)
   3. Re:  Stymied by mutable arrays in the ST monad (Tobias Brandt)
   4. Re:  Stymied by mutable arrays in the ST monad (Matthew Moppett)
   5. Re:  Stymied by mutable arrays in the ST monad (Matthew Moppett)


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

Message: 1
Date: Fri, 25 May 2012 23:04:26 +0900
From: Ken Kawamoto <[email protected]>
Subject: Re: [Haskell-beginners] Missing some functions in Hoogle
To: Paulo Pocinho <[email protected]>
Cc: [email protected]
Message-ID:
        <cagbyeko6_eoodc-x2jfxkm0wafwxbhcr5r1fwokdvmtjg+j...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Thanks Paulo for your comment and sorry for late reply.

On Tue, May 22, 2012 at 11:09 PM, Paulo Pocinho <[email protected]> wrote:
> After testing Hoogle cabal package [4], it can either generate
> databases for the current system or fetch the database from the
> internet. However, database search only covered standard libraries.

What does this part mean?
With Hoogle package, you can generate databases for any library, but
the search works only for standard libraries?

Although this is consistent with what I experienced, it's a bit
surprising because this means generating database doesn't make any
sense, does it?

Hayhoo seems to suit what I want.

-- Ken


On Tue, May 22, 2012 at 11:09 PM, Paulo Pocinho <[email protected]> wrote:
> On 21 May 2012 00:55, Ken Kawamoto <[email protected]> wrote:
> (...)
>> Now I'm wondering if I'm missing something, or Hoogle supports only a
>> predefined set of functions.
>> Any advise would be appreciated.
>
> Hi.
>
> Hoogle [1] can search by type as well as by name. This currently only
> works for standard Haskell libraries.
> Hayhoo [2] is a string-based search only but also covers hackage [3].
>
> After testing Hoogle cabal package [4], it can either generate
> databases for the current system or fetch the database from the
> internet. However, database search only covered standard libraries.
> Having search by type in hackage would be great though.
>
> Hope this helps.
>
> --
> 1. http://www.haskell.org/hoogle/
> 2. http://holumbus.fh-wedel.de/hayoo/hayoo.html
> 3. http://hackage.haskell.org/packages/hackage.html
> 4. http://hackage.haskell.org/package/hoogle
>
> Regards,
> Paulo



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

Message: 2
Date: Sat, 26 May 2012 02:50:57 +1000
From: Matthew Moppett <[email protected]>
Subject: [Haskell-beginners] Stymied by mutable arrays in the ST monad
To: [email protected]
Message-ID:
        <CAMLEjZAuA4Fq+a29vL6j=sg9nrfkzwxvyrhvzz3hbdwde9z...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I've been trying to use mutable arrays in the ST monad, and wrote out a
little proof of concept function:

idST :: [Int] -> [Int]
idST xs = runST $ do
    array <- newListArray (1, (length xs)) xs
    return (getElems array)

-- where idSt should be equivalent to id.

And I get the error message:

Couldn't match type `[Int]' with `Int'
    In the return type of a call of `getElems'
    In the first argument of `return', namely `(getElems array)'
    In a stmt of a 'do' block: return (getElems array)

Obviously I'm making a very simple mistake here, but I can't seem to spot
it. Can anyone offer some advice?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120526/e31d586b/attachment-0001.htm>

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

Message: 3
Date: Fri, 25 May 2012 19:05:01 +0200
From: Tobias Brandt <[email protected]>
Subject: Re: [Haskell-beginners] Stymied by mutable arrays in the ST
        monad
To: Matthew Moppett <[email protected]>
Cc: [email protected]
Message-ID:
        <caoowqio6wse+vfumes16sco43+jaujnjeguqtegyjve+-le...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On 25 May 2012 18:50, Matthew Moppett <[email protected]> wrote:
> I've been trying to use mutable arrays in the ST monad, and wrote out a
> little proof of concept function:
>
> idST :: [Int] -> [Int]
> idST xs = runST $ do
> ? ? array <- newListArray (1, (length xs)) xs
> ? ? return (getElems array)
>
> -- where idSt should be equivalent to id.
>
> And I get the error message:
>
> Couldn't match type `[Int]' with `Int'
> ? ? In the return type of a call of `getElems'
> ? ? In the first argument of `return', namely `(getElems array)'
> ? ? In a stmt of a 'do' block: return (getElems array)
>
> Obviously I'm making a very simple mistake here, but I can't seem to spot
> it. Can anyone offer some advice?

'getElems array' already has type 'ST s [Int]', you don't need
another 'return'. Furthermore you need to help out with the type
inference a little bit (it's similar to the read-show problem).
This should work:

idST :: [Int] -> [Int]
idST xs = runST $ do
    array <- newListArray (1, (length xs)) xs :: ST s (STArray s Int Int)
    getElems array

(You could also replace STArray by STUArray.)



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

Message: 4
Date: Sat, 26 May 2012 03:43:04 +1000
From: Matthew Moppett <[email protected]>
Subject: Re: [Haskell-beginners] Stymied by mutable arrays in the ST
        monad
To: Tobias Brandt <[email protected]>
Cc: [email protected]
Message-ID:
        <CAMLEjZDJ_-0vyDXTBOpEm9g7BVC8FLvBQkLBfS13H804W=g...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Thanks, Tobias.

I guess my eyes kind of glazed over when I read "getElems :: (MArray a e
m, Ix i) => a i e -> m [e]" in the docs, and didn't relate that to the
meaning of "return"... lesson learnt.

About the extra type info needed -- what part of the type "ST s (STArray s
Int Int)" is the compiler unable to infer?

I've worked out from this that the error message "no instance for"... might
signal a missing type signature, but I'm having trouble working out the
general lesson of when the compiler needs some extra hints.


On 25 May 2012 18:50, Matthew Moppett <[email protected]> wrote:
> I've been trying to use mutable arrays in the ST monad, and wrote out a
> little proof of concept function:
>
> idST :: [Int] -> [Int]
> idST xs = runST $ do
>     array <- newListArray (1, (length xs)) xs
>     return (getElems array)
>
> -- where idSt should be equivalent to id.
>
> And I get the error message:
>
> Couldn't match type `[Int]' with `Int'
>     In the return type of a call of `getElems'
>     In the first argument of `return', namely `(getElems array)'
>     In a stmt of a 'do' block: return (getElems array)
>
> Obviously I'm making a very simple mistake here, but I can't seem to spot
> it. Can anyone offer some advice?

'getElems array' already has type 'ST s [Int]', you don't need
another 'return'. Furthermore you need to help out with the type
inference a little bit (it's similar to the read-show problem).
This should work:

idST :: [Int] -> [Int]
idST xs = runST $ do
   array <- newListArray (1, (length xs)) xs :: ST s (STArray s Int Int)
   getElems array

(You could also replace STArray by STUArray.)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120526/04e7ba17/attachment-0001.htm>

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

Message: 5
Date: Sat, 26 May 2012 04:25:37 +1000
From: Matthew Moppett <[email protected]>
Subject: Re: [Haskell-beginners] Stymied by mutable arrays in the ST
        monad
To: Tobias Brandt <[email protected]>
Cc: [email protected]
Message-ID:
        <camlejzbmaqdsktucckzxxoyxvklqy+eytu4_8uqfrkvnwa5...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Brilliant. I think I've got it now. Thanks heaps, Tobias.

On Sat, May 26, 2012 at 4:01 AM, Tobias Brandt <[email protected]>wrote:

> On 25 May 2012 19:43, Matthew Moppett <[email protected]> wrote:
> > About the extra type info needed -- what part of the type "ST s (STArray
> s
> > Int Int)" is the compiler unable to infer?
>
> It doesn't know which array type to use, because 'newListArray' is
> polymorphic
> in the type of array it returns. This type is not mentioned in
> the signature of idST because the array is immediately consumed again by
> 'getElems'.
>
> You can try it out in ghci (':t expr' gives you the type of an expression):
>
> :m +Data.Array.ST
> let xs = [1,2,3 :: Int]
>
> :t xs
> [Int]
>
> :t newListArray (1, length xs) xs
> MArray a Int m => m (a Int Int)
>
> Applying getElems gets you this:
> :t (newListArray (1, length xs) xs) >>= getElems
> MArray a Int m => m [Int]
>
> From the 'runST' in your program, the compiler knows that m = ST s,
> for some s, but there is nothing constraining 'a' further.
> Any 'a' fulfilling the constraint 'MArray a Int (ST s)' will do.
> Therefore we have to fix 'a' to some type, e.g. 'STArray s', but
> 'STUArray s' would work too, in this case.
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120526/e171d763/attachment-0001.htm>

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

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


End of Beginners Digest, Vol 47, Issue 21
*****************************************

Reply via email to