[Haskell-cafe] Haddock documentation of Data.Array.* is confusing

Alfonso Acosta alfonso.acosta at gmail.com
Tue Feb 12 15:32:20 EST 2008


Hi,

Excuse me for the subject, but IMHO is absolutely true. Anyhow, the
purpose of this message is not merely to rant about it (which I know
doesn't help) but to illustrate the possible impression of a Haskell
newcomers.

It's been a long long time since I last used arrays in Haskell (lists
are normally just fine for me) so I checked the docs to refresh my
memory. This is the result of my experience:

The first thing I checked was Data.Array which ... just shows function
names without signatures!

OK, I followed the advice shown in "Data.Array" and tried to
understand the more generic interface of Data.IArray.

Fine, the documentation is much better, however it mentions
Data.Array.Base, whose documentation link is missing :S

I was suprised to see that even if all the functions of Data.IArray
(i.e. array, listArray ... ) are perfectly sensible and generic (which
is nice), they are not part of ot the IArray multiparameter class.

So I wondered .. how can someone add its own implementation of
inmutable arrays to the IArray interface? It was obvious that "bounds"
(the only method of the IArray typeclass) was not going to enough, but
I tried anyway with a naive example.

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
data Ix i => LArray i e = LArray [e] (i,i)

instance IArray LArray e where
-- bounds :: (Ix i, IArray LArray e) => LArray i e -> (i,i)
 bounds (LArray _ b) = b

GHC warned me about missing definitions for some"unsafe" methods of
ArrayI which .... as expected, belong to the "phantom" Data.Array.Base
module.

The sources of Data.Array.Base revealed that the purpose of hiding
them was to protect the user.

Someone who wants add an array implementation to the IArray interface
should use Data.Array.Base but why would it hurt to add a note in
IArray mentioning it? and Why is Data.Array.Base hidden for Haddock
(especially when there are some broken links pointing to it)?

Cheers,

Fons


More information about the Haskell-Cafe mailing list