{-# LANGUAGE ScopedTypeVariables, PolymorphicComponents #-} {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-} -- .$Header: c:/Source/Haskell/Wrapper/Data/Flex/RCS/Functor.hs,v 1.4 2011/09/20 23:36:59 dosuser Exp dosuser $ module Data.Flex.Functor ( -- * Common flexible Functor instance selection types and classes -- ** Analysis class for @'Functor'@ instance selection FWFunctor, -- ** Instance selector FWDefaultFunctor(..), -- ** Function identifier type for @'Apply'@ FWFmap(..), -- ** Polymorphic function wrapper WrapFmap(..) ) where -- | Analysis class for @'Functor'@ instance selection -- You need a specific instance of this for any instance selectors -- you may define. class FWFunctor (f :: * -> *) r | f -> r -- | Instance selector type for the default @'Functor'@ -- instances data FWDefaultFunctor = FWDefaultFunctor -- | Function identifier type for @'Apply'@. -- You need a corresponding instance of @'Apply'@ for any -- instance selectors you may define. data FWFmap t (f :: * -> *) = FWFmap -- | Polymorphic function wrapper for @'fmap'@ newtype WrapFmap f = WrapFmap {unwrapFmap :: forall a b. (a -> b) -> (f a -> f b)} -- vim: expandtab:tabstop=4:shiftwidth=4