{-# LANGUAGE ScopedTypeVariables, Rank2Types #-} {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-} -- .$Header: c:/Source/Haskell/Wrapper/Data/Flex/RCS/Monad.hs,v 1.3 2011/09/20 23:37:34 dosuser Exp dosuser $ module Data.Flex.Monad ( -- * Common flexible Monad instance selection types and classes -- ** Analysis class for @'Monad'@ instance selection FWMonad, -- ** Instance selectors FWDefaultMonad(..), -- ** Function identifier types for @'Apply'@ FWReturn(..), FWBind(..), -- ** Polymorphic function wrappers WrapReturn(..), WrapBind(..), -- ** Constructor aliases wrapReturn, wrapBind ) where -- import Data.Flex.Applicative (WrapPure(..)) -- | Analysis class for @'Monad'@ instance selection -- You need a specific instance of this for any instance selectors -- you may define. class FWMonad (m :: * -> *) r | m -> r -- | Instance selector type for the default @'Monad'@ -- instances data FWDefaultMonad = FWDefaultMonad -- | Function identifier type for @'Apply'@. -- You need a corresponding instance of @'Apply'@ for any -- instance selectors you may define. data FWReturn t (m :: * -> *) = FWReturn -- | Polymorphic function wrapper for @'return'@ newtype WrapReturn m = WrapReturn {unwrapReturn :: forall a. a -> m a} wrapReturn :: (forall a. a -> m a) -> WrapReturn m wrapReturn = WrapReturn {- GHC 6.6.1 can't cope with this version of unwrapReturn type WrapReturn = WrapPure wrapReturn :: (forall a. a -> m a) -> WrapReturn m wrapReturn = WrapPure unwrapReturn :: WrapReturn m -> (forall a. a -> m a) unwrapReturn = unwrapPure -} -- | Function identifier type for @'Apply'@. -- You need a corresponding instance of @'Apply'@ for any -- instance selectors you may define. data FWBind t (m :: * -> *) = FWBind -- | Polymorphic function wrapper for @'>>='@ newtype WrapBind m = WrapBind {unwrapBind :: forall a b. m a -> (a -> m b) -> m b} wrapBind :: (forall a b. m a -> (a -> m b) -> m b) -> WrapBind m wrapBind = WrapBind -- vim: expandtab:tabstop=4:shiftwidth=4