[Haskell-cafe] Code review: initial factoring for sequences andother structures

Brian Hulley brianh at metamilk.com
Fri Aug 4 01:07:26 EDT 2006


Brian Hulley wrote:
> Hi -
> I've started work on an initial factoring of sequence ops into
[snip]
>
>    class Foldable c a | c -> a where
>        foldR :: (a -> b -> b) -> b -> c -> b
[snip]
> There is a general problem that when the element type needs to be
> specified along with the type of the overall collection, there is no
> way to talk about the functor type at the same time

After writing this I realised it was a bit silly of me to have used a fundep 
when I could have just specified the functor types directly (instead of the 
resulting collection) thus:

    class Foldable f a where
        foldR :: (a -> b -> b) -> b -> f a -> b

so I applied this change to everything then wrote:

    module Duma.Data.Class.Functor
        ( Functor(..)
        ) where

    import Prelude hiding (map, Functor)
    import Duma.Data.Class.BasicSeq

    class Functor f a b where
        fmap :: (a -> b) -> f a -> f b

    instance (BasicSeq f a, BasicSeq f b) => Functor f a b where
        fmap = map

Now surely such an absolutely clear and straightforward instance decl would 
cause no problems at all, but guess what? Yes, even without fundeps and 
attempts to pattern match against the components of a type, GHC can't handle 
it because it needs at least one non-type variable in the instance head or 
else the dreaded -f-allow-undecidable-instances.

I wonder why there needs to be a distinction between type variables and 
non-type-variables because I'd have thought that the whole point of 
restricted polymorphism is that there's supposed to be a continuum between a 
fully unrestricted polymorphic type and a fully concrete type, with 
constraints like (BasicSeq f a) "partially solidifying" (f) and (a).

The good news is that even though the Functor class can't be implemented, 
(fmap) can at least now be implemented within BasicSeq:

    class Foldable s a => BasicSeq s a where

        map :: BasicSeq t b => (a -> b) -> s a -> t b
        map f xs =
            case viewL xs of
                Just (x, xs') -> pushL (f x) (map f xs')
                Nothing -> empty

        fmap :: BasicSeq s b => (a -> b) -> s a -> s b
        fmap = map

Anyway it's interesting that there does not yet appear to be a proper 
solution (ie to give us Foldable, BasicSeq, and Functor all with restricted 
polymorphism) with the type system as it stands at present unless 
"dangerous" flags are used.

Regards, Brian.
-- 
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 



More information about the Haskell-Cafe mailing list