{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE PolymorphicComponents #-} -- .$Header: c:/Source/Haskell/Wrapper/smallcheck/Data/Flex/RCS/Serial.hs,v 1.1 2011/09/21 00:11:45 dosuser Exp dosuser $ -- | Utilies for implementing @'Serial'@ for flexible wrappers module Data.Flex.Serial ( -- * Polymorphic function wrapper WrapCoseries(..), -- * Functor-like map function for (type alias) @'Series'@ seriesMap ) where import Test.SmallCheck (Series) import Data.Flex.Utils (result) -- | Polymorphic function wrapper for @'coseries'@ newtype WrapCoseries a = WrapCoseries { unwrapCoseries :: forall b. Series b -> Series (a -> b) } seriesMap :: (a -> b) -> Series a -> Series b seriesMap = result . map -- vim: expandtab:tabstop=4:shiftwidth=4