
On Sun, Mar 1, 2015 at 8:11 AM, silvio
I have recently heard that some people want to burn bridges (introducing Foldable and Traversable to Prelude) and I've been wondering if it was possible somehow allow Text and Bytestring like containers to make use of those functions. Something along the lines of
import qualified Data.ByteString as BS
newtype ByteString' a = ByteString' BS.ByteString
type ByteString = ByteString' Word8
instance (ByteString' a ~ ByteString' Word8) => Functor (ByteString') where fmap f (ByteString' bs) = ByteString' $ BS.map f bs
If tweak the definition of Functor a bit, we can get that to work: {-# LANGUAGE ConstraintKinds, TypeFamilies #-} import qualified Data.ByteString as B import Data.Word (Word8) import GHC.Prim (Constraint) newtype ByteString' a = ByteString' B.ByteString deriving (Eq, Ord, Show) class Functor' f where type FunctorConstraint f a :: Constraint fmap' :: (FunctorConstraint f a, FunctorConstraint f b) => (a -> b) -> f a -> f b instance Functor' ByteString' where type FunctorConstraint ByteString' a = a ~ Word8 fmap' f (ByteString' x) = ByteString' $ B.map f x But I don't think it's possible with the original type class. -- https://lambda.xyz