Flipping a functor

I’m trying to understand this example a little better

data Tuple a b = Tuple a b deriving (Eq, Show)

newtype Flip f a b = Flip (f b a) deriving (Eq, Show)
-- `f` is a type that has an instance `Functor` and two arguments: `a` and `b`
-- `Flip` returns the same type `f` with `a` and `b` reversed

instance Functor (Flip Tuple a) where
    fmap f (Flip (Tuple x y)) = Flip $ Tuple (f x) y

aa :: Flip Tuple String Integer
aa = fmap (+1) (Flip (Tuple 1 "blah"))
-- Flip (Tuple 2 "blah")

What I get is:

  • In fmap on the left side of =, (Tuple x y) get’s its x and y reversed.
  • On the right side of = f is applied to x and then the Tuple with the new value for x is flipped again.

What I don’t get is:

  • I expected Tuple x y to become Tuple y x
  • And I’m guessing it is, except that x is now y and y is now x
  • But since the order x y hasn’t change I’m left wondering what has changed?

Here is my best/current guess on that is:

  • Before the flip x on the LHS has the value of a in the declaration line. (I’m doubting a actually has a value?)
  • After the flip y has the value of a
  • Therefore x is no longer part of the structure and can now be changed by applying f
  • Then the type is flipped again to the original order.
1 Like

It’s not so much that values are getting reversed here on the fly, but more the type parameter order that Flip is specifying. If x is of type a and y is of type b, then a Tuple x y value will have type Tuple a b, while a Flip (Tuple x y) value will have type Flip Tuple b a.

Using an instance signature (enabled via the InstanceSigs extension) and some type annotations (enabled via ScopedTypeVariables) can help make the Functor instances a little clearer, especially if we line up the Functor (Flip Tuple a) instance with the Functor (Tuple a) instance and keep consistent with naming:

instance Functor (Tuple a) where
    fmap :: (b -> b') -> Tuple a b -> Tuple a b'
    fmap f (Tuple (x :: a) (y :: b)) = Tuple x (f y)

instance Functor (Flip Tuple a) where
    fmap :: (b -> b') -> Flip Tuple a b -> Flip Tuple a b'
    fmap f (Flip (Tuple (y :: b) (x :: a))) = Flip $ Tuple (f y) x

Hope this adds some clarity! If there are spots where a deeper dive would be helpful, we can poke at it more.

2 Likes

Remember that Functor is a ‘Constructor Class’ – there’s an unmentioned type param for its instance heads.

>:info Functor ===> class Functor (f :: * -> *) where ...
instance Functor (Either a)               -- doesn't mention Either's second param

Then the straightforward way to write a Functor instance for Tuple:

instance Functor (Tuple a)  where         -- again don't mention Tuple's second param
    fmap f (Tuple x y) = Tuple x (f y)

The Flip version wants fmap to apply the f to Tuple's first param, leaving the second untouched:

    fmapFlipped f (Tuple x y) = Tuple (f x) y

The Flip newtype and constructor are there to tie the whole business in knots so that Tuple's first param can be presented as if second.

2 Likes

I’m not sure why I’m resistive to the idea of the type parameter order being changed. It just seems like an invalid kind of thing to do.

Your way of laying out the Functor instances for Tuple and Flip Tuple helps with clarity and makes it easy to flip them in my mind - :+1:

So given you can change the order of arguments via the use of Flip does that mean there is no rule against changing their order? Is it a good practice, common, useful?

If I change the order of a type’s arguments is it the same type or a different type?

newtype Flip f a b = Flip (f b a) deriving (Eq, Show) is certainly a new type, parametrized by the old type f, rather than a different way of seeing the old type. It is isomorphic though (i.e. holds the same information).

Tuple always takes its arguments in the order that you’d expect. Flip is just a wrapper on top of Tuple - it doesn’t change anything about Tuple per se. I think that might be a source of confusion, though not sure.

I wouldn’t say this sort of thing is often very useful, it’s more like a curiosity as far as practical code goes.

There isn’t any rule against flipping the order, in the sense that Flip does.

One thing that may be confusing is that in the definition of Tuple below, Tuple on the left and Tuple on the right are actually different things.

data Tuple a b = Tuple a b

The Tuple on the left is a type constructor (like, for example, Maybe), and the Tuple on the right is a data constructor (like Just). They’re only the same because Haskell lets you choose the same name for both. Reusing names like this is called “punning”.

If you avoid punning by changing the names of the data constructors to MkTuple and MkFlip, the difference becomes clearer.

data Tuple a b = MkTuple a b deriving (Eq, Show)

newtype Flip f a b = MkFlip (f b a) deriving (Eq, Show)

instance Functor (Flip Tuple a) where
    fmap f (MkFlip (MkTuple x y)) = MkFlip $ MkTuple (f x) y

aa :: Flip Tuple String Integer
aa = fmap (+1) (MkFlip (MkTuple 1 "blah"))
-- MkFlip (MkTuple 2 "blah")

Now, checking their types and kinds shows the difference:

ghci> :kind Flip 
Flip :: (* -> * -> *) -> * -> * -> *
ghci> :type MkFlip
MkFlip :: f b a -> Flip f a b
ghci> :type Flip

<interactive>:1:1: error:
    • Data constructor not in scope: Flip
    • Perhaps you meant variable ‘flip’ (imported from Prelude)
ghci> :kind MkFlip

<interactive>:1:1: error:
    Not in scope: type constructor or class ‘MkFlip’
    A data constructor of that name is in scope; did you mean DataKinds?
    Perhaps you meant ‘Flip’ (line 5)
1 Like

I was aware of that difference. What does surprise me is how much can happen on the LHS of = in Haskell. In other languages I know it seems that the LHS is just a name for all the dynamic stuff that happens on the RHS.

Tuple & Flip Tuple are different types but is the Tuple inside of Flip Tuple the same Tuple (but with arguments reordered) or a new type?

It’s the same Tuple, with no reordering. Not a new type.

For functions (and values in general), the LHS really is just a name for the righthand side. E.g.:

f x = x + x

This just means: whenever you see f x in code, you can replace it with x + x. That’s all it means.

In types, I personally find the GADT syntax clearer, because it avoids having an =:

newtype Flip f a b where
  MkFlip :: (f b a) -> Flip f a b

This says: values of type Flip f a b exist. Make one by applying the function MkFlip to a value of type f b a.

Flip Tuple Int Double isn’t really flipping anything at all. It’s just a wrapper around Tuple. The only difference is that it has a different Functor instance to Tuple Int Double.

data Tuple a b = Tuple a b deriving (Eq, Show)
newtype Flip f a b     = Flip (f     b a) deriving (Eq, Show)
aa :: Flip Tuple String Integer           -- [A]
aa = fmap (+1) (Flip (Tuple 1 "blah"))    -- [B]
-- Flip (Tuple 2 "blah")

I was looking at fmap in the Functor instance for Flip Tuple and had overlooked [A] and [B] above. This makes a little more sense now.

  • [A] has Flip Tuple String Integer
  • [B] is already flipped Flip Tuple 1 "blah" i.e., Integer String

I’m wondering if asking, “When does it flip?” is a good question to ask. aa's type is one type and the return type is a different type. Is it possible to point to a line of code where it got flipped?

Line 2, newtype Flip f a b = Flip (f b a), does the flipping (“flipping”). If there is any “flipping” to speak of, it’s in type expressions, not term/value expressions.

2 Likes

It may also be helpful to explore using Flip with another type, like Either a b:

data Either a b = Left a | Right b deriving (Eq, Show)

The Functor instance for Either a (I’m using the InstanceSigs and ScopedTypeVariables extensions again to help better document the types):

instance Functor (Either a) where
  fmap :: (b -> b') -> Either a b -> Either a b'
  fmap _ (Left (x :: a)) = Left x
  fmap f (Right (y :: b)) = Right (f y)

Now we’ll write the Functor instance for Flip Either a, and we’ll stay consistent with variable naming for values of types a and b:

instance Functor (Flip Either a) where
  fmap :: (b -> b') -> Flip Either a b -> Flip Either a b'
  fmap f (Flip (Left (y :: b))) = Flip $ Left $ f y
  fmap _ (Flip (Right (x :: a))) = Flip $ Right x

Flip hasn’t flipped values around, but rather it’s flipped the type parameter order for the types that will be passed to the type constructor (i.e. Tuple or Either) it was given. If we start with the definition of Flip:

newtype Flip f a b = Flip (f b a) deriving (Eq, Show)

We see that the first type parameter is a type constructor, and the second and third type parameters are types passed to this type constructor (f b a).

If we do some substituting with specializations for Tuple and Either, this type parameter ordering stuff becomes a little clearer:

newtype FlippedTuple a b = FlippedTuple (Flip Tuple a b)
-- which if we substitute in Flip's definition, is equivalent to:
newtype FlippedTuple' a b = FlippedTuple' (Tuple b a)
newtype FlippedEither a b = FlippedEither (Flip Either a b)
-- similarly, if we substitute in Flip's definition, is equivalent to:
newtype FlippedEither' a b = FlippedEither' (Either b a)
2 Likes

Sorry if my last explanation was too low-level, but I still think it would be useful to focus on the difference between type constructors on the type level and data constructors on the value level. Here is an example I hope will help.

data MessyType a b = MessyType b a Bool a Char b

messyValue :: MessyType String Integer             -- [A]
messyValue = MessyType 1 "blah" True "hello" 'z' 2 -- [B]

Are you surprised that [A] is just MessyType String Integer, while [B] is MessyType followed by a long line of values of different types: Integer String Bool String Char Integer? Probably not.

Notice how [A] corresponds to the left hand side of the data definition, and [B] corresponds to the right hand side. The same thing is happening with the newtype definition for Flip.

I think I threw folks off when I asked if the values were getting switched. I knew that wasn’t right but had tried so long to figure it out that I started to doubt myself. My last post above tries to explain where the confusion came from.

I do get the difference between type constructors and data constructors. I’m a not sure about messyValue. If MessyType takes two arguments, in this case String Integer, how can you pass it 6 1 "blah" True "hello" 'z' 2?

I hadn’t heard the term constructor class before but found an older paper that talks about them and it added to my understanding of types. Someone on the Discord forum said

A constructor class is a type class where the parameter is a type constructor

This is a constructor class

class HasMap g where
  map :: (a -> b) -> g a -> g b

This is not a constructor class

class Semigroup a where
  (<>) :: a -> a -> a

Do you agree with that?

Because there are two different things both called MessyType. One of them takes two arguments (like String Integer), and the other one takes six arguments (like 1 "blah" True "hello" 'z' 2).

data MessyType a b = MessyType b a Bool a Char b

In this definition, the name MessyType occurs twice, once on the left and once on the right.

The MessyType on the left is the type constructor and takes two arguments (like String Integer).

The MessyType on the right is the data constructor, and takes six arguments (like 1 "blah" True "hello" 'z' 2). As I wrote before, it’s allowed to have the same name as the type constructor because of punning, but it’s a completely different thing.

If the MessyType definition seems weird to you, try comparing it to an ordinary product datatype definition like data XYPoint = XYPoint Int Int. It’s not that different, except that it’s polymorphic over types a and b.

I do get the difference between type constructors and data constructors. I’m a not sure about messyValue . If MessyType takes two arguments, in this case String Integer , how can you pass it 6 1 "blah" True "hello" 'z' 2 ?

Here is where you’re confusing types and values, and my sense is that this is the root of what’s confusing about Flip. As per the other reply, MessyType is a type that takes two types, with a constructor also called MessyType that takes 6 values.

My recommendation would be to play around with that example until it’s entirely clear and then return to Flip.

See here for some notes on punning: Punning - The Haskell Guide

# cat VeryPunny.hs
module VeryPunny where
import qualified Prelude

undefined :: undefined
undefined = Prelude.undefined

error :: Prelude.String -> error
error = Prelude.error

id :: id -> id
id = Prelude.id

const :: const -> id -> const
const = Prelude.const

flip :: (error -> id -> flip) -> id -> error -> flip
flip = Prelude.flip

#  ghci VeryPunny.hs
GHCi, version 9.0.2: https://www.haskell.org/ghc/  :? for help
[1 of 1] Compiling VeryPunny        ( VeryPunny.hs, interpreted )
Ok, one module loaded.
ghci> :t undefined
undefined :: undefined
ghci> :t error
error :: Prelude.String -> error
ghci> :t id
id :: id -> id
ghci> :t const
const :: const -> id -> const
ghci> :t flip
flip :: (error -> id -> flip) -> id -> error -> flip
ghci> :q
Leaving GHCi.
#

…so why - on this planet or any other - would punning ever be considered useful to have in a programming language?

#  ghci
GHCi, version 9.0.2: https://www.haskell.org/ghc/  :? for help
ghci> :t ()
() :: ()
ghci> :t []
[] :: [a]
ghci> :t (True, "as")
(True, "as") :: (Bool, String)
ghci> :t ('p', 'u', 'n')
('p', 'u', 'n') :: (Char, Char, Char)
ghci>  :q
Leaving GHCi.
#

Now for a suggestion: in all the examples in this thread, rewrite the data constructors all in uppercase e.g:

data Tuple a b = TUPLE a b deriving (Eq, Show)

newtype Flip f a b = FLIP (f b a) deriving (Eq, Show)
-- `f` is a type that has an instance `Functor` and two arguments: `a` and `b`
-- `Flip` returns the same type `f` with `a` and `b` reversed

instance Functor (Flip Tuple a) where
    fmap f (FLIP (TUPLE x y)) = FLIP $ TUPLE (f x) y

aa :: Flip Tuple String Integer
aa = fmap (+1) (FLIP (TUPLE 1 "blah"))
-- FLIP (TUPLE 2 "blah")

…etc (ghci will let you know which one is which). Doing this temporarily should make the difference between type and data constructors easier to understand.

Honestly, I don’t think I’m confused by type vs data constructor, nor type vs term level. I’m just not seeing what is in front of my face. Looking at MessyType again I see the type def is right there and the data constructor has 6 arguments. I missed that whole line.

Lately I’m working with a lot of interrupts and trying to squeeze Haskell in. I’ll have to work on that.

That said, when I first made the post I did wonder what was getting flipped and didn’t know if it was the data or type constructor. I clearly see now it’s the data constructor. I got that when I saw

aa :: Flip Tuple String Integer          -- String   Integer (type constructor)
aa = fmap (+1) (Flip (Tuple 1 "blah"))   -- Integer  String  (data constructr)

I read the link on punning - got all of that (recursive types are still a challenge). I’m going to play with MessyType some but make sure I have time to settle in and think a bit first :slight_smile:

2 Likes