DData in hierarchical libraries

John Meacham john at repetae.net
Fri Feb 20 14:13:47 EST 2004


may I recommend the following instances as well.

I would like to see Seq stay in the library. using 'Seq String' to build
up complicated structures can be much much more efficient than
otherwise and it is a handy idiom to not have to constantly reimplement.


import Data.Monoid
import qualified IntSet as IS
import qualified IntMap as IM
import qualified Set 
import qualified Map 
import qualified Seq 
import Monad


instance Monoid IS.IntSet where
    mempty = IS.empty
    mappend = IS.union
    mconcat = IS.unions

instance Monoid (IM.IntMap a) where
    mempty = IM.empty
    mappend = IM.union
    mconcat = IM.unions
    
instance Ord a => Monoid (Set.Set a) where
    mempty = Set.empty
    mappend = Set.union
    mconcat = Set.unions

instance Ord k => Monoid (Map.Map k v ) where
    mempty = Map.empty
    mappend = Map.union
    mconcat = Map.unions

instance Monoid (Seq.Seq a) where
    mempty = Seq.empty
    mappend = (Seq.<>)


instance Functor Seq.Seq where
    fmap f xs = Seq.fromList (map f (Seq.toList xs))


instance Functor IM.IntMap where
    fmap = IM.map

--instance Ord k => Functor (Map.Map k) where
--    fmap = Map.map
    
instance Monad Seq.Seq where
    a >>= b  = mconcat ( map b (Seq.toList a))
    return x = Seq.single x
    fail _ = Seq.empty

instance MonadPlus Seq.Seq where  -- should this match the Monoid instance?
    mplus = mappend
    mzero = Seq.empty


-- 
---------------------------------------------------------------------------
John Meacham - California Institute of Technology, Alum. - john at foo.net
---------------------------------------------------------------------------


More information about the Libraries mailing list