[Haskell-cafe] is it possible to implement Functor for ByteString and Text

Zemyla zemyla at gmail.com
Mon Mar 2 06:06:31 UTC 2015


What I would do is hold the function to apply in the wrapper type.

import qualified Data.ByteString as BS

data ByteString' a = ByteString' (Word8 -> a) BS.ByteString

wrap :: BS.ByteString -> ByteString' Word8
wrap bs = ByteString' id bs

-- The type ensures you can only unwrap with a function Word8 -> Word8.
unwrap :: ByteString' Word8 -> ByteString
unwrap (ByteString' f bs) = BS.map f bs

-- Functor instance just concatenates the fmapped function.
instance Functor ByteString' where
    fmap f (ByteString' g bs) = ByteString' (f . g) bs

-- Foldable instance just uses the fmapped function.
instance Foldable ByteString' where
    foldr f z (ByteString' g bs) = BS.foldr (f . g) z bs
-- You could define foldr', foldl, etc. based on the ones in
Data.ByteString.
-- Not strictly necessary, but nice to have.

As an added benefit, this doesn't require GADTs. It probably would if you
wanted to implement Monad as well, though.
On Feb 28, 2015 1:11 PM, "silvio" <silvio.frischi at gmail.com> wrote:

> 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
>
>
> Or if DataContexts worked as you would expect.
>
> newtype (Word8 ~ a) => ByteString' a = ByteString' BS.ByteString
>
> However I couldn't find a solution and I was just wondering if it is
> possible.
>
> P.S. Using GADTS it does actually work for Foldable, but only because it
> doesn't have to output any ByteStrings. It doesn't work for Functor for
> instance.
>
> data ByteString' a where
>         ByteString' :: BS.ByteString -> ByteString' Word8
>
> type ByteString = ByteString' Word8
>
> instance Foldable ByteString' where
>         foldr f ini (ByteString' bs) = BS.foldr f ini bs
>
>
> Silvio
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150302/82ebc147/attachment.html>


More information about the Haskell-Cafe mailing list