Given a widely parameterized type class > class Monad (m g n) => GenericNetworkMonad g m n where > ret :: a -> m g n a > ret = return
the question seems to be about defining a specialized alias of it, instantiating the parameters g m n in some way. The hope is that the alias has fewer parameters and so is more convenient to use. Would not the standard approach of defining aliases work then? For example, > class NetworkMonad mg n where > instance GenericNetworkMonad g m n => NetworkMonad (m g) n where Granted, we would have to write boilerplate as we have to re-direct specialized methods to the general ones. Here is the complete code > {-# LANGUAGE TypeFamilies #-} > {-# LANGUAGE MultiParamTypeClasses #-} > {-# LANGUAGE FlexibleContexts, FlexibleInstances #-} > {-# LANGUAGE UndecidableInstances #-} > > data family GNT g :: * -> * -> * > data family GNQ g :: * -> * -> * > > class Monad (m g n) => GenericNetworkMonad g m n where > ret :: a -> m g n a > ret = return > > -- A few instances > data instance GNT Int n a = GNT_Int a -- n is phantom > data instance GNQ Int n a = GNQ_Int a > > instance Monad (GNT Int n) where > return = GNT_Int > GNT_Int x >>= f = f x > > instance Monad (GNQ Int n) where > return = GNQ_Int > GNQ_Int x >>= f = f x > > type NT n a = GNT Int n a > type NQ n a = GNQ Int n a > > instance GenericNetworkMonad Int GNT n > instance GenericNetworkMonad Int GNQ n > > genericMonadicValue :: GenericNetworkMonad g m n => m g n () > genericMonadicValue = ret () > > monadicValue :: GenericNetworkMonad Int m n => m Int n () > monadicValue = ret () > > class NetworkMonad mg n where > mv'' :: mg n () > > instance GenericNetworkMonad g m n => NetworkMonad (m g) n where > mv'' = genericMonadicValue > > monadicValue'' :: NetworkMonad m n => m n () > monadicValue'' = mv'' In general, the Apply class trick should work for defining arbitrary aliases to class constraints. One Apply constraint is all one ever needs in Haskell: http://okmij.org/ftp/ftp/Haskell/types.html#Haskell1 Here is the instance of this trick, adopted to use type families rather than functional dependencies (no UndecidableInstances is required now): > class Apply label where > type Typ label :: * > apply :: label -> Typ label > > data NM (mg :: * -> * -> *) n = NM > instance GenericNetworkMonad g m n => Apply (NM (m g) n) where > type Typ (NM (m g) n) = m g n () > apply _ = genericMonadicValue > > monadicValue''' :: > forall mg n m. (Apply (NM mg n), > Typ (NM mg n) ~ m n ()) => > m n () > monadicValue''' = apply (NM :: NM mg n) _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe