...
P.S.:

sth like nested instances (FFunctor) should be possible, too.
and a way to select the defaults in external inteface definitions: "instance 
Monad M . Functor M where".
maybe additional syntactic sugar (instances)?

[code]

class FFunctor m where
  ffmap :: ...
class FFunctor m => Functor m where
  fmap :: ...
  instance FFunctor m where
    ffmap = fmap
class Gunctor m where
  gmap :: ...
class Hunctor m where
  hmap :: ...
  hmap = unsafePerformIO $ putStrLn "class Hunctor" >> undefined
class FFunctor m => Junctor m where
  jmap :: ...
  jmap = unsafePerformIO $ putStrLn "class Junctor" >> undefined
  instance FFunctor m where
    ffmap = jmap

class FFunctor m, Functor m, Gunctor m, Hunctor m, Junctor m => Monad m where
  return :: a -> m a
  (>>=) :: m a -> (a -> m b) -> m b
  instance Functor m where
    fmap f = unsafePerformIO $ putStrLn "class Monad" >> undefined
    --instance FFunctor m where
  instance Hunctor m where
    hmap f = unsafePerformIO $ putStrLn "class Monad" >> undefined
  instance Junctor m . FFunctor m where

-- to define the functions in the *unctor, using the defaults defined in the 
class _*unctor_ (assumed there would be any default):
instance Monad M where
  return = ...
  (>>=) = ...
instance Functor M where
  gmap = unsafePerformIO $ putStrLn "instance Functor" >> undefined
  instance FFunctor M where
instance Gunctor M where
  gmap = unsafePerformIO $ putStrLn "instance Gunctor" >> undefined
instance Hunctor M where
instance Junctor M where

-- to define the functions in the *unctor, using the defaults defined in the 
class _Monad_:
instance Monad M where
  return = ...
  (>>=) = ...
  instance Functor M where
    instance FFunctor M where
  instance Gunctor M where
    gmap = unsafePerformIO $ putStrLn "instance Monad" >> undefined
  instance Hunctor M where
  instance Junctor M where
--or
instance Monad M where
  return = ...
  (>>=) = ...
instance Monad M . Functor M where
instance Functor M . FFunctor M where
--instance Monad M . FFunctor M where
instance Monad M . Gunctor M where
    gmap = unsafePerformIO $ putStrLn "instance Monad" >> undefined
instance Monad M . Hunctor M where
instance Monad M . Junctor M where


--syntactic sugar:
instance Monad M where
  return = ...
  (>>=) = ...
  instances Functor M, Gunctor M, Junctor M where
    gmap = unsafePerformIO $ putStrLn "instance Monad" >> undefined
instances Hunctor M, Junctor M . FFunctor M where

[/code]

- marc
_______________________________________________
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime

Reply via email to