[Haskell-cafe] Code review: initial factoring for sequences and
other structures
Brian Hulley
brianh at metamilk.com
Fri Aug 4 00:07:19 EDT 2006
Hi -
I've started work on an initial factoring of sequence ops into classes, and
already I've run into some major design issues which stand like a mountain
in the way of progress. The classes are below:
-- all code below standard BSD3 licence :-)
module Duma.Data.Class.Foldable
( Foldable(..)
) where
import qualified Data.List as List
class Foldable c a | c -> a where
foldR :: (a -> b -> b) -> b -> c -> b
foldL :: (b -> a -> b) -> b -> c -> b
foldL' :: (b -> a -> b) -> b -> c -> b
-- arg order from FingerTree paper
-- opposite to Edison arg order
reduceR :: (a -> b -> b) -> (c -> b -> b)
reduceR f xs y = foldR f y xs
reduceL :: (b -> a -> b) -> (b -> c -> b)
reduceL = foldL
reduceL' :: (b -> a -> b) -> (b -> c -> b)
reduceL' = foldL'
instance Foldable [a] a where
foldR = List.foldr
foldL = List.foldl
foldL' = List.foldl'
and
module Duma.Data.Class.BasicSeq
( BasicSeq(..)
) where
import Prelude hiding(map)
import Duma.Data.Class.Foldable
import qualified Data.List as List
import Control.Monad
class Foldable c a => BasicSeq c a where
empty :: c
isEmpty :: c -> Bool
atL :: c -> a
atR :: c -> a
pushL :: a -> c -> c
pushR :: c -> a -> c
viewL :: Monad m => c -> m (a, c)
viewR :: Monad m => c -> m (c, a)
-- (1) Should this be in its own class?
convert :: BasicSeq d a => c -> d
convert = foldR pushL empty
-- (2) Is this too general or not general enough?
map :: BasicSeq d b => (a -> b) -> c -> d
map f xs =
case viewL xs of
Just (x, xs') -> pushL (f x) (map f xs')
Nothing -> empty
instance BasicSeq [a] a where
empty = []
isEmpty [] = True
isEmpty _ = False
atL (x:_) = x
atR = List.last
pushL = (:)
pushR xs x = xs ++ [x]
viewL (x:xs) = return (x,xs)
viewL _ = fail "viewL"
viewR xs@(_:_) = return (List.init xs, List.last xs)
viewR _ = fail "viewR"
(Indexing ops like take, drop, length, at, split would be provided by a
third class and measurements (to access the power of finger trees and
similar structures) would be dealt with by a fourth class with analogous ops
ie takeWith, splitWith etc)
However already with just the above I have some questions about the
(convert) and (map) functions:
1) Because (convert) takes BasicSeq d a as a context, it is currently
impossible to provide an optimized version for specific combinations of
source/dest types eg if both types are the same (convert) should just be
(id). Does this mean I should put (convert) into its own class or should I
expect the compiler to be able to rewrite (foldR pushL empty) into (id) in
this situation?
2) Ditto with (map), but here there is another issue: it is at once too
general and too specific compared to the usual definitions of (map):
--Prelude - limited to lists only
map f (x:xs) = f x : map f xs
map _ [] = []
-- Functor - source and dest limited to the same type
fmap :: (a->b) -> f a -> f b
So even though fmap is constrained to only map between the same type, it is
more general than BasicSeq.map because the type doesn't need to be a
BasicSeq. However it is less general in the sense that fmap wouldn't allow
to map between two different instances of BasicSeq.
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 eg I'd like to be able to write something
like this:
class Functor f a b where
fmap :: (a->b) -> f a -> f b
instance (BasicSeq (f a) a, BasicSeq (f b) b) => Functor f a b where
fmap = map
but GHC complains that I'd need to use -fallow-undecidable-instances which
I'm reluctant to do because I don't know what the implications of such a
decision would be. Why are these instances for such a simple thing (ie just
pattern matching against the components of a type) already undecidable?
The issues above are the kind of problems I just don't know how to solve or
even how to approach, since there seem to be too many conflicting dimensions
in the design space. Any ideas?
Thanks, 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