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

53 views
Skip to first unread message

silvio

unread,
Feb 28, 2015, 2:11:14 PM2/28/15
to haskell-cafe
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
Haskel...@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

David Feuer

unread,
Feb 28, 2015, 2:41:28 PM2/28/15
to silvio, haskell-cafe
This is impossible. The type of fmap is

fmap :: Functor f => (a->b) -> f a -> f b

You can use a GADT to effectively restrict what a is, because the
caller won't be able to provide a non-bottom f a if a has the wrong
type. But the caller can choose absolutely any type for b, and there's
nothing you can do about that.

David

Christopher Done

unread,
Feb 28, 2015, 2:57:27 PM2/28/15
to David Feuer, haskell-cafe
You could have
class IsWord8 a
instance IsWord8 Word8
instance (IsWord8 a) => Functor (ByteString a) where ...

It would be a legitimate instance.

Christopher Done

unread,
Feb 28, 2015, 2:58:32 PM2/28/15
to Chris Done, haskell-cafe
Ah, I'm talking nonsense. Ignore me.

Chris Wong

unread,
Feb 28, 2015, 7:01:13 PM2/28/15
to silvio, haskell-cafe
On Sun, Mar 1, 2015 at 8:11 AM, silvio <silvio....@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

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

silvio

unread,
Feb 28, 2015, 8:08:49 PM2/28/15
to Chris Wong, haskell-cafe
Wow ConstraintKinds. There's always a new extension to be learned :)
Anyway, if changing the Functor declaration were allowed, it would
probably make more sense to use something like MonoFunctor.
Unfortunately, MPTC or type family stuff is never going to make it into
Prelude.

Silvio

Niklas Haas

unread,
Feb 28, 2015, 9:58:05 PM2/28/15
to silvio, haskell-cafe
I think it's more realistic to use lens style Setters where possible.
Essentially:

type Setter s t a b = (a -> b) -> s -> t
type Setter' s a = Setter s s a a

bytes :: Setter ByteString Word8
bytes = BS.map

fmapped :: Functor f => Setter (f a) (f b) a b
fmapped = fmap

In this framework, you could write a function that can abstract over any
setter, eg.

changeSomething :: Setter s t Foo Bar -> s -> t
changeSomething s = s fooBar
where fooBar :: Foo -> Bar

It's not quite the same thing as making ByteString or Text an instance
of Functor, but for some tasks, it can be a good replacement.

Zemyla

unread,
Mar 2, 2015, 1:06:38 AM3/2/15
to Haskel...@haskell.org

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.

silvio

unread,
Mar 3, 2015, 11:47:03 AM3/3/15
to haskel...@haskell.org
cool trick. This is by far the best solution yet. Of course it's a bit
deceptive in what you are working with. E.g.

bs1 <- pack [1..10]
print bs1
let bs2 = map (+1) bs1
print bs2
let bs3 = map (+1) bs2
print bs3
...
let bsn = map (+1) bsn_1
print bsn

will have quadratic complexity. On the other, hand you will get fusion
for free.

silvio

Ben Franksen

unread,
Mar 5, 2015, 11:46:39 PM3/5/15
to haskel...@haskell.org
silvio wrote:
> cool trick. This is by far the best solution yet. Of course it's a bit
> deceptive in what you are working with. E.g.
>
> bs1 <- pack [1..10]
> print bs1
> let bs2 = map (+1) bs1
> print bs2
> let bs3 = map (+1) bs2
> print bs3
> ...
> let bsn = map (+1) bsn_1
> print bsn
>
> will have quadratic complexity.

One could perhaps replace id with unsafeCoerce in wrap?

Cheers
Ben
Reply all
Reply to author
Forward
0 new messages