{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE PolymorphicComponents #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} -- .$Header: c:/Source/Haskell/Wrapper/Data/Flex/RCS/Applicative.hs,v 1.3 2011/09/20 23:35:55 dosuser Exp dosuser $ module Data.Flex.Applicative ( -- * Common flexible Applicative instance selection types and classes -- ** Analysis class for @'Applicative'@ instance selection FWApplicative, -- ** Instance selectors FWDefaultApplicative(..), -- ** Function identifier types for @'Apply'@ FWPure(..), FWCombine(..), -- ** Polymorphic function wrappers WrapPure(..), WrapCombine(..) ) where -- | Analysis class for @'Applicative'@ instance selection -- You need a specific instance of this for any instance selectors -- you may define. class FWApplicative (f :: * -> *) r | f -> r -- | Instance selector type for the default @'Applicative'@ -- instances data FWDefaultApplicative = FWDefaultApplicative -- | Function identifier type for @'Apply'@. -- You need a corresponding instance of @'Apply'@ for any -- instance selectors you may define. data FWPure t (f :: * -> *) = FWPure -- | Polymorphic function wrapper for @'pure'@ newtype WrapPure f = WrapPure {unwrapPure :: forall a. a -> f a} -- | Function identifier type for @'Apply'@. -- You need a corresponding instance of @'Apply'@ for any -- instance selectors you may define. data FWCombine t (f :: * -> *) = FWCombine -- | Polymorphic function wrapper for @'<*>'@ newtype WrapCombine f = WrapCombine {unwrapCombine :: forall a b. f (a -> b) -> (f a -> f b)} -- vim: expandtab:tabstop=4:shiftwidth=4