How to understand the type of (fmap fmap fmap) in Haskell? - haskell

In Haskell, the Functor has a function fmap which the type of it is:
ghci> :t fmap
fmap :: Functor f => (a -> b) -> f a -> f b
This makes sense to me that fmap lifts a function from the type of a -> b to f a -> f b.
Then I am curious about what is the type of fmap fmap, so I tried and got something weird to me:
ghci> :t fmap fmap
fmap fmap
:: (Functor f1, Functor f2) => f1 (a -> b) -> f1 (f2 a -> f2 b)
Hmm, this type is somewhat complicate, but I can explain it by replacing a with a -> b and b with f2 a -> f2 b.
Then, I wanted to one step further:
fmap fmap fmap
:: (Functor f1, Functor f2) => (a -> b) -> f1 (f2 a) -> f1 (f2 b)
Oh, wait! Things go to be fun when putting 3 fmap together. How to explain this?
Could someone help to explain how could I derive the type of fmap fmap fmap?

For clarity, let's introduce
fmapA, fmapB, fmapC :: Functor f => (a -> b) -> f a -> f b
fmapA = fmapB = fmapC = fmap
and consider
fmapA fmapB fmapC :: ?
Forget about fmapB for a bit, start with fmapA _ fmapC. You're treating fmapC on the right as a container here, over which you map something. Does that make sense? Well, look at the type in non-infix form. Recall that x -> y -> z is the same as x -> (y -> z), and p -> q is the same as ((->) p) q, thus
fmapC :: ((->) p) q where {p ~ (a->b), q ~ (f a->f b)}
To use this as a container type, the f in fmapA's signature needs to unify with (->) p. That's the function functor. So, despite having three polymorphic fmaps here, one of the functors is already predetermined by the expression. Therefore, it would be better to immediately resolve the polymorphism that only makes it more difficult to understand, and replace it with the definition of that particular functor instance, which turns out to be rather simple:
instance Functor ((->) a) where
fmap = (.)
So, that reduces our expression to (.) fmapB fmapC – or, as it's preferrably written,
fmapB . fmapC
Which is a far more sensible thing to write in actual code, and has been discussed previously on StackOverflow.

{-# Language BlockArguments #-}
{-# Language ScopedTypeVariables #-}
{-# Language TypeApplications #-}
fffmap
:: forall f g a b. ()
=> Functor f
=> Functor g
=> (a -> b)
-> (f (g a) -> f (g b))
fffmap = fmap fmap fmap
A polymorphic function takes a type as an argument. The forall. quantifiee is invisible and implicitly solved by unification but we can explicitly instantiate it with a type application #...
I use block arguments which allows me to write fmap fmap fmap as
do fmap
do fmap
do fmap
just to make it clearer. This is how they are actually instantiated:
fffmap
:: forall f g a b. ()
=> Functor f
=> Functor g
=> (a -> b)
-> (f (g a) -> f (g b))
fffmap =
do fmap #((->) (a -> b)) #(g a -> g b) #(f (g a) -> f (g b))
do fmap #f #(g a) #(g b)
do fmap #g #a #b
The first fmap = (.) is instantiated to the reader monad (.. ->), no wonder you find it complicated. If you look at the type of f1, it IS complicated.
fffmap
:: forall f g a b.
Functor f
=> Functor g
=> (a -> b)
-> (f (g a) -> f (g b))
fffmap = f1 f2 f3 where
f1 :: ((g a -> g b) -> f (g a) -> f (g b)) -> ((a -> b) -> g a -> g b) -> (a -> b) -> f (g a) -> f (g b)
f1 = fmap
f2 :: (g a -> g b) -> (f (g a) -> f (g b))
f2 = fmap
f3 :: (a -> b) -> (g a -> g b)
f3 = fmap

Related

Is there a name for this higher-level "bi" version of distribute in Haskell?

I have a Bitraversable called t that supports this operation:
someName :: Monad m => (t (m a) (m b) -> c) -> m (t a b) -> c
In other words, it's possible to take a function that accepts two monads packaged into the bitraversable and turn it into a mapping that accepts a single monad containing a bitraversable without the monad layer. This is something like a bitraversable and higher-level version of distribute; the type signature is similar to this:
\f -> \x -> f (distribute x)
:: (Distributive g, Functor f) => (g (f a) -> c) -> f (g a) -> c
My questions:
Is there a standard name for this "higher-level" version of distribute that works on functions that accept distributives rather than distributives themselves?
Is there a name for the bitraversable version?
Does it work with every bitraversable/functor/monad/whatever, or are there restrictions?
As per #Noughtmare, your "higher level" functions someName and distribute are just written in continuation passing style. These generally aren't worth additional names, because they are just right function compositions:
highLevelDistribute = (. distribute)
Practically speaking, anywhere you want to call highLevelDistribute on an argument:
highLevelDistribute f
this expression is equivalent to:
f . distribute
and even if you're using highLevelDistribute as a first-class value, it's just not that hard to write and understand the section (. distribute).
Note that traverse and sequenceA are a little different, since we have:
sequenceA = traverse id
You could make an argument that this difference doesn't really warrant separate names either, but that's an argument for another day.
Getting back to someName, it's a CPS version of:
someOtherName :: m (t a b) -> t (m a) (m b)
which looks like a bifunctor analogue of distribute:
distribute :: (Distributive g, Functor f) => f (g a) -> g (f a)
So, I'd suggest inventing a Bidistributive to reflect this, and someOtherName becomes bidistribute:
class Bifunctor g => Bidistributive g where
{-# MINIMAL bidistribute | bicollect #-}
bidistribute :: Functor f => f (g a b) -> g (f a) (f b)
bidistribute = bicollect id
bicollect :: Functor f => (a -> g b c) -> f a -> g (f b) (f c)
bicollect f = bidistribute . fmap f
Again, your "higher level" someName is just right-composition:
someName = (. bidistribute)
Reasonable laws for a Bidistributive would probably include the following. I'm not sure if these are sufficiently general and/or exhaustive:
-- naturality
bimap (fmap f) (fmap g) . bidistribute = bidistribute . fmap (bimap f g)
-- identity
bidistribute . Identity = bimap Identity Identity
-- composition
bimap Compose Compose . bidistribute . fmap bidistribute = bidistribute . Compose
For your question #3, not all Bitraversables are Bidistributive, for much the same reason that not all Traversables are Distributive. A Distributive allows you to "expose structure" under an arbitrary functor. So, for example, there's no Distributive instance for lists, because if there was, you could call:
distribute :: IO [a] -> [IO a]
which would allow you to determine if a list returned by an IO action was empty or not, without executing the IO action.
Similarly, Either is Bitraversable, but it can't be Bidistributive, because if it was, you'd be able to use:
bidistribute :: IO (Either a b) -> Either (IO a) (IO b)
to determine if the IO action returned a Left or Right without having to execute the IO action.
One interesting thing about bidistribute is that the "other functor" can be any Functor; it doesn't need to be an Applicative. So, just as we have:
sequenceA :: (Traversable t, Applicative f) => t (f a) -> f (t a)
distribute :: (Distributive g, Functor f) => f (g a) -> g (f a)
we have:
bisequence :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b)
bidistribute :: (Bidistributive g, Functor f) => f (g a b) -> g (f a) (f b)
Intuitively, sequencing needs the power of an applicative functor f to be able to "build" the f (t a) from a traversal of its functorial f a "parts", while distribution only needs to take the f (g a) apart. In practical terms, this means that sequencing typically looks like this:
-- specialized to t ~ []
sequenceA :: [f a] -> f [a]
sequenceA (f:fs) = (:) <$> f <*> fs -- need applicative operations
while distribution typically looks like this:
-- specialized to g ~ (->) r
distribute :: f (r -> a) -> (r -> f a)
distribute f r = fmap ($ r) f -- only need fmap
(Technically, according to the documentation for Data.Distributive, the Distributive class only requires a Functor rather than some coapplicative class because of the lack of non-trivial comonoids in Haskell. See this SO answer.)

How can I instantiate Functor for this data type?

How Can I instantiate the following data types to be Functor ?
data LiftItOut f a = LiftItOut (f a)
data Parappa f g a = DaWrappa (f a) (g a)
data IgnoreOne f g a b = IgnoringSomething (f a) (g b)
data Notorious g o a t = Notorious (g o) (g a) (g t)
There are not very clear for the declaration themselves, inside the parantheses in the right member, is that function application (I ve never seen that, only basic type constructors)? I am new to haskell and I am just trying to understand the basics.
Ask the compiler to show you how. Use the command line flag -ddump-deriv, enable the DeriveFunctor language extension, and put deriving Functor at the end of each type definition, and then the compiler will print Functor instances for each of them:
==================== Derived instances ====================
Derived class instances:
instance GHC.Base.Functor g =>
GHC.Base.Functor (Main.Notorious g o a) where
GHC.Base.fmap f_aK1 (Main.Notorious a1_aK2 a2_aK3 a3_aK4)
= Main.Notorious a1_aK2 a2_aK3 (GHC.Base.fmap f_aK1 a3_aK4)
(GHC.Base.<$) z_aK5 (Main.Notorious a1_aK6 a2_aK7 a3_aK8)
= Main.Notorious a1_aK6 a2_aK7 ((GHC.Base.<$) z_aK5 a3_aK8)
instance forall k (f :: k -> *) (g :: * -> *) (a :: k).
GHC.Base.Functor g =>
GHC.Base.Functor (Main.IgnoreOne f g a) where
GHC.Base.fmap f_aK9 (Main.IgnoringSomething a1_aKa a2_aKb)
= Main.IgnoringSomething a1_aKa (GHC.Base.fmap f_aK9 a2_aKb)
(GHC.Base.<$) z_aKc (Main.IgnoringSomething a1_aKd a2_aKe)
= Main.IgnoringSomething a1_aKd ((GHC.Base.<$) z_aKc a2_aKe)
instance (GHC.Base.Functor f, GHC.Base.Functor g) =>
GHC.Base.Functor (Main.Parappa f g) where
GHC.Base.fmap f_aKf (Main.DaWrappa a1_aKg a2_aKh)
= Main.DaWrappa
(GHC.Base.fmap f_aKf a1_aKg) (GHC.Base.fmap f_aKf a2_aKh)
(GHC.Base.<$) z_aKi (Main.DaWrappa a1_aKj a2_aKk)
= Main.DaWrappa
((GHC.Base.<$) z_aKi a1_aKj) ((GHC.Base.<$) z_aKi a2_aKk)
instance GHC.Base.Functor f =>
GHC.Base.Functor (Main.LiftItOut f) where
GHC.Base.fmap f_aKl (Main.LiftItOut a1_aKm)
= Main.LiftItOut (GHC.Base.fmap f_aKl a1_aKm)
(GHC.Base.<$) z_aKn (Main.LiftItOut a1_aKo)
= Main.LiftItOut ((GHC.Base.<$) z_aKn a1_aKo)
That's kind of messy-looking, but it's rather straightforward to clean up:
data LiftItOut f a = LiftItOut (f a)
instance Functor f => Functor (LiftItOut f) where
fmap f (LiftItOut a) = LiftItOut (fmap f a)
data Parappa f g a = DaWrappa (f a) (g a)
instance (Functor f, Functor g) => Functor (Parappa f g) where
fmap f (DaWrappa a1 a2) = DaWrappa (fmap f a1) (fmap f a2)
data IgnoreOne f g a b = IgnoringSomething (f a) (g b)
instance Functor g => Functor (IgnoreOne f g a) where
fmap f (IgnoringSomething a1 a2) = IgnoringSomething a1 (fmap f a2)
data Notorious g o a t = Notorious (g o) (g a) (g t)
instance Functor g => Functor (Notorious g o a) where
fmap f (Notorious a1 a2 a3) = Notorious a1 a2 (fmap f a3)
Also worth noting that your LiftItOut is isomorphic to Ap and IdentityT, and your Parappa is isomorphic to Product.
A functor f is a type constructor with an associated function fmap that from a function of type (a -> b) creates a function of type (f a) -> (f b) which applies it "on the inside": (the parentheses are redundant and are used for clarity/emphasis only)
fmap :: (Functor f) => ( a -> b)
-> (f a) -> (f b)
-- i.e. g :: a -> b -- from this
-- --------------------------
-- fmap g :: (f a) -> (f b) -- we get this
(read it "fmap of g from a to b goes from f a to f b").
Put differently, something being a "Functor" means that it can be substituted for f in
fmap id (x :: f a) = x
(fmap g . fmap h) = fmap (g . h)
so that the expressions involved make sense (i.e. are well formed, i.e. have a type), and, importantly, the above equations hold -- they are in fact the two "Functor laws".
You have
data LiftItOut h a = MkLiftItOut (h a) -- "Mk..." for "Make..."
------------- ----------- ------
new type, data type of the data constructor's
defined here constructor one argument (one field)
This means h a is a type of a thing which can serve as an argument to MkLiftItOut. For example, Maybe Int (i.e. h ~ Maybe and a ~ Int), [(Float,String)] (i.e. h ~ [] and a ~ (Float,String)), etc.
h, a are type variables -- meaning, they can be replaced by any specific type so that the whole syntactic expressions make sense.
These syntactic expressions include MkLiftItOut x which is a thing of type LiftItOut h a provided x is a thing of type h a; LiftItOut h a which is a type; h a which is a type of a thing which can appear as an argument to MkLiftItOut. Thus we can have in our programs
v1 = MkLiftItOut ([1,2,3] :: [] Int ) :: LiftItOut [] Int
v2 = MkLiftItOut ((Just "") :: Maybe String) :: LiftItOut Maybe String
v3 = MkLiftItOut (Nothing :: Maybe () ) :: LiftItOut Maybe ()
.....
etc. Then we have
ghci> :i Functor
class Functor (f :: * -> *) where
fmap :: (a -> b) -> f a -> f b
(<$) :: a -> f b -> f a
..........
This means that Functor f => (f a) is a type of a thing which a variable can reference, e.g.
-- f a
v4 = Just 4 :: Maybe Int
v41 = 4 :: Int
v5 = [4.4, 5.5] :: [] Float
v51 = 4.4 :: Float
v52 = 5.5 :: Float
v6 = (1,"a") :: ((,) Int) String -- or simpler, `(Int, String)`
v61 = "a" :: String
v7 = (\x -> 7) :: ((->) Int) Int -- or simpler, `Int -> Int`
Here a is a type of a thing, f a is a type of a thing, f is a type which, when given a type of a thing, becomes a type of a thing; etc. There's no thing which can be referenced by a variable which would have the type f on its own.
All the above fs are instances of the Functor typeclass. This means that somewhere in the libraries there are definitions of
instance Functor Maybe where ....
instance Functor [] where ....
instance Functor ((,) a) where ....
instance Functor ((->) r) where ....
Notice we always have the f, and the a. f in particular can be made of more than one constituents, but a is always some one type.
Thus in this case we must have
instance Functor (LiftItOut h) where ....
(...why? do convince yourself in this; see how all the above statements apply and are correct)
Then the actual definition must be
-- fmap :: (a -> b) -> f a -> f b
-- fmap :: (a -> b) -> LiftItOut h a -> LiftItOut h b
fmap g (MkLiftItOut x ) = (MkLiftItOut y )
where
y = ....
In particular, we'll have
-- g :: a -> b -- x :: (h a) -- y :: (h b)
and we don't even know what the h is.
How can we solve this? How can we construct an h b-type of thing from an h a-type of thing when we don't even know anything about h, a, nor b?
We can't.
But what if we knew that h is also a Functor?
instance (Functor h) => Functor (LiftItOut h) where
-- fmap :: (a -> b) -> (f a) -> (f b)
-- fmap :: (a -> b) -> (LiftItOut h a) -> (LiftItOut h b)
fmap g (MkLiftItOut x ) = (MkLiftItOut y )
where
-- fmap :: (a -> b) -> (h a) -> (h b)
y = ....
Hopefully you can finish this up. And also do the other types in your question as well. If not, post a new question for the one type with which you might have any further problems.

(fmap.fmap) for Applicative

fmap.fmap allows us to go "two layers deep" into a functor:
fmap.fmap :: (a -> b) -> f (g a) -> f (g b)
Is this also possible for applicative functors? Let's say I wanted to combine Just (+5) and [1,2,3] by using their applicative properties. I can think of an obvious way to do it, but it doesn't seem that trivial to me.
(<*>).(<*>) doesn't a have a conclusive type signature:
((<*>).(<*>)) :: (a1 -> a2 -> b) -> ((a1 -> a2) -> a1) -> (a1 -> a2) -> b
-- where I would expect something like:
-- ((<*>).(<*>)) :: f (g (a -> b)) -> f (g a) -> f (g b)
Is it possible to compose Just (+5) and [1,2,3] in this fashion?
EDIT:
The first step would be to go with either:
pure $ Just (+5) and fmap pure [1,2,3], or
fmap pure (Just (+5) and pure [1,2,3]
But I still don't how to compose these...
EDIT:
It would be nice to have a general way to compose a function f (g (a -> b) and f (g a), I'm not just looking for a solution for the above case, which is just supposed to serve as an example input of such a function. Basically I want a function:
(<***>) :: f (g (a -> b)) -> f (g a) -> f (g b)
liftA2 has a similar compositional property as fmap.
liftA2 f :: f a -> f b -> f c
(liftA2 . liftA2) f :: g (f a) -> g (f b) -> g (f c)
So you can write
(liftA2 . liftA2) ($) (pure (Just (+5))) (fmap pure [1,2,3]) :: [Maybe Integer]
i.e., (<***>) = (liftA2 . liftA2) ($). (much like (<*>) = liftA2 ($))
Another way to look at it is that the composition of applicative functors is an applicative functors, this is made concrete by Data.Functor.Compose:
{-# LANGUAGE ScopedTypeVariables, PartialTypeSignatures #-}
import Data.Functor.Compose
import Data.Coerce
(<***>) :: forall f g a b. (Applicative f, Applicative g)
=> f (g (a -> b)) -> f (g a) -> f (g b)
(<***>) = coerce ((<*>) :: Compose f g (a -> b) -> _)
The point with coerce is to show that (<***>) is the applicative (<*>) for the right type; we can also do the unwrapping manually
f <***> x = getCompose $ Compose f <*> Compose x
We have a f (g (a->b)). To get g a -> g b from g (a->b) we just need <*>, but g (a->b) is wrapped in f. Luckily f is a Functor so we can fmap over it.
Prelude> :t fmap (<*>)
fmap (<*>)
:: (Functor f1, Applicative f) =>
f1 (f (a -> b)) -> f1 (f a -> f b)
Prelude>
That's better, we have a function wrapped in a Functor now. If this Functor happens to be an Applicative, we can apply <*> through it.
Prelude> :t (<*>) . fmap (<*>)
(<*>) . fmap (<*>)
:: (Applicative f, Applicative f1) =>
f1 (f (a -> b)) -> f1 (f a) -> f1 (f b)
Prelude>
Just what the doctor ordered.
Prelude> let (<***>) = (<*>) . fmap (<*>)
Prelude> [Just (+2), Just (*3), Nothing] <***> [Just 7, Just 42, Nothing]
[Just 9,Just 44,Nothing,Just 21,Just 126,Nothing,Nothing,Nothing,Nothing]
Prelude>

Why do the types in `(fmap . fmap) sum Just [1, 2, 3]` work?

I'm having the time of my life reading the wonderful Haskell Programming from first principles and I came by the following example that I'm just not able to take apart (Page 1286 e-reader):
Prelude> (fmap . fmap) sum Just [1, 2, 3]
Just 6
It is obvious to me how the following works:
Prelude> fmap sum $ Just [1,2,3]
Just 6
And I already manually deconstructed (fmap . fmap) to understand how the types work. But when thinking about this as "lifting twice" it doesn't make sense, since I'm lifting over both the Just and List data constructors.
I typed out the following in ghci:
Prelude> :t (fmap . fmap)
(fmap . fmap)
:: (Functor f, Functor f1) => (a -> b) -> f1 (f a) -> f1 (f b)
Prelude> :t (fmap . fmap) sum
(fmap . fmap) sum
:: (Num b, Foldable t, Functor f, Functor f1) =>
f1 (f (t b)) -> f1 (f b)
Prelude> :t (fmap . fmap) sum Just
(fmap . fmap) sum Just :: (Num b, Foldable t) => t b -> Maybe b
I don't understand how to derive the last output. When feeding (fmap . fmap) sum the Just data constructor, How does the compiler know to replace both f1 and f for Maybe? After I'll get a good answer here, how could I have figured it out myself?
That isn't lifting over both Maybe and List (that would be (fmap . fmap) sum (Just [1,2,3]), which has a type problem), but over the function type (->) and Maybe.
Just :: a -> Maybe a
-- ((->) a) (Maybe a)
-- f (g a) for f ~ ((->) a) and g ~ Maybe
(fmap . fmap) :: (a -> b) -> f (g a ) -> f (g b)
-- Num x => ([x] -> x) -> f (g [x]) -> f (g x)
-- Num x => ([x] -> x) -> ([x] -> Maybe [x]) -> [x] -> Maybe x
-- ^ ^ ^
-- sum Just [1,2,3]
If you don't understand how a particular answer works, line up the argument you are supplying with the type from the previous step.
Prelude> :t (fmap . fmap) sum
(fmap . fmap) sum
:: (Functor f, Functor f1, Num b) => f (f1 [b]) -> f (f1 b)
So in order for this work, Just has to have type f (f1 [b]), and then (fmap . fmap) sum Just has to have type f (f1 b).
Just :: (Functor f, Functor f1, Num b) => f (f1 [b])
It's not obvious what f or f1 should be here, so let's try the RHS instead. We can cheat and ask GHCi to check what the actual value of (fmap . fmap) sum Just should be:
Prelude> :t (fmap . fmap) sum Just
(fmap . fmap) sum Just :: Num b => [b] -> Maybe b
But this should match:
(Functor f, Functor f1, Num b) => f (f1 b)
We're trying to figure out what f and f1 are here. So we have to rewrite it a little bit so it has the same structure (remember that -> is syntactic sugar and gets in the way sometimes):
(fmap . fmap) sum Just :: Num b => [b] -> Maybe b
-- Same as...
(fmap . fmap) sum Just :: Num b => (->) [b] (Maybe b)
-- Or...
(fmap . fmap) sum Just :: Num b => ((->) [b]) (Maybe b)
-- Functor f = ((->) [b])
-- Functor f1 = Maybe
So we can figure out that in order for the types to match, the Functor f has to be (->) [b]… remember that functions are functors too! And the Functor f1 is Maybe, which is a bit more obvious.
We can test this out:
Prelude> :t (fmap . fmap) sum :: Num b => ([b] -> Maybe [b]) -> ([b] -> Maybe b)
(fmap . fmap) sum :: Num b => ([b] -> Maybe [b]) -> ([b] -> Maybe b)
:: Num b => ([b] -> Maybe [b]) -> [b] -> Maybe b
And GHCi thinks it type checks just fine.
The only part here that's easy to forget is just that (->) [b] is a valid functor!

How do I give a Functor instance to a datatype built for general recursion schemes?

I have a recursive datatype which has a Functor instance:
data Expr1 a
= Val1 a
| Add1 (Expr1 a) (Expr1 a)
deriving (Eq, Show, Functor)
Now, I'm interested in modifying this datatype to support general recursion schemes, as they are described in this tutorial and this Hackage package. I managed to get the catamorphism to work:
newtype Fix f = Fix {unFix :: f (Fix f)}
data ExprF a r
= Val a
| Add r r
deriving (Eq, Show, Functor)
type Expr2 a = Fix (ExprF a)
cata :: Functor f => (f a -> a) -> Fix f -> a
cata f = f . fmap (cata f) . unFix
eval :: Expr2 Int -> Int
eval = cata $ \case
Val n -> n
Add x y -> x + y
main :: IO ()
main =
print $ eval
(Fix (Add (Fix (Val 1)) (Fix (Val 2))))
But now I can't figure out how to give Expr2 the same functor instance that the original Expr had. It seems there is a kind mismatch when trying to define the functor instance:
instance Functor (Fix (ExprF a)) where
fmap = undefined
Kind mis-match
The first argument of `Functor' should have kind `* -> *',
but `Fix (ExprF a)' has kind `*'
In the instance declaration for `Functor (Fix (ExprF a))'
How do I write a Functor instance for Expr2?
I thought about wrapping Expr2 in a newtype with newtype Expr2 a = Expr2 (Fix (ExprF a)) but then this newtype needs to be unwrapped to be passed to cata, which I don't like very much. I also don't know if it would be possible to automatically derive the Expr2 functor instance like I did with Expr1.
This is an old sore for me. The crucial point is that your ExprF is functorial in both its parameters. So if we had
class Bifunctor b where
bimap :: (x1 -> y1) -> (x2 -> y2) -> b x1 x2 -> b y1 y2
then you could define (or imagine a machine defining for you)
instance Bifunctor ExprF where
bimap k1 k2 (Val a) = Val (k1 a)
bimap k1 k2 (Add x y) = Add (k2 x) (k2 y)
and now you can have
newtype Fix2 b a = MkFix2 (b a (Fix2 b a))
accompanied by
map1cata2 :: Bifunctor b => (a -> a') -> (b a' t -> t) -> Fix2 b a -> t
map1cata2 e f (MkFix2 bar) = f (bimap e (map1cata2 e f) bar)
which in turn gives you that when you take a fixpoint in one of the parameters, what's left is still functorial in the other
instance Bifunctor b => Functor (Fix2 b) where
fmap k = map1cata2 k MkFix2
and you sort of get what you wanted. But your Bifunctor instance isn't going to be built by magic. And it's a bit annoying that you need a different fixpoint operator and a whole new kind of functor. The trouble is that you now have two sorts of substructure: "values" and "subexpressions".
And here's the turn. There is a notion of functor which is closed under fixpoints. Turn on the kitchen sink (especially DataKinds) and
type s :-> t = forall x. s x -> t x
class FunctorIx (f :: (i -> *) -> (o -> *)) where
mapIx :: (s :-> t) -> f s :-> f t
Note that "elements" come in a kind indexed over i and "structures" in a kind indexed over some other o. We take i-preserving functions on elements to o preserving functions on structures. Crucially, i and o can be different.
The magic words are "1, 2, 4, 8, time to exponentiate!". A type of kind * can easily be turned into a trivially indexed GADT of kind () -> *. And two types can be rolled together to make a GADT of kind Either () () -> *. That means we can roll both sorts of substructure together. In general, we have a kind of type level either.
data Case :: (a -> *) -> (b -> *) -> Either a b -> * where
CL :: f a -> Case f g (Left a)
CR :: g b -> Case f g (Right b)
equipped with its notion of "map"
mapCase :: (f :-> f') -> (g :-> g') -> Case f g :-> Case f' g'
mapCase ff gg (CL fx) = CL (ff fx)
mapCase ff gg (CR gx) = CR (gg gx)
So we can refunctor our bifactors as Either-indexed FunctorIx instances.
And now we can take the fixpoint of any node structure f which has places for either elements p or subnodes. It's just the same deal we had above.
newtype FixIx (f :: (Either i o -> *) -> (o -> *))
(p :: i -> *)
(b :: o)
= MkFixIx (f (Case p (FixIx f p)) b)
mapCata :: forall f p q t. FunctorIx f =>
(p :-> q) -> (f (Case q t) :-> t) -> FixIx f p :-> t
mapCata e f (MkFixIx node) = f (mapIx (mapCase e (mapCata e f)) node)
But now, we get the fact that FunctorIx is closed under FixIx.
instance FunctorIx f => FunctorIx (FixIx f) where
mapIx f = mapCata f MkFixIx
Functors on indexed sets (with the extra freedom to vary the index) can be very precise and very powerful. They enjoy many more convenient closure properties than Functors do. I don't suppose they'll catch on.
I wonder if you might be better off using the Free type:
data Free f a
= Pure a
| Wrap (f (Free f a))
deriving Functor
data ExprF r
= Add r r
deriving Functor
This has the added benefit that there are quite a few libraries that work on free monads already, so maybe they'll save you some work.
Nothing wrong with pigworker's answer, but maybe you can use a simpler one as a stepping-stone:
{-# LANGUAGE DeriveFunctor, ScopedTypeVariables #-}
import Prelude hiding (map)
newtype Fix f = Fix { unFix :: f (Fix f) }
-- This is the catamorphism function you hopefully know and love
-- already. Generalizes 'foldr'.
cata :: Functor f => (f r -> r) -> Fix f -> r
cata phi = phi . fmap (cata phi) . unFix
-- The 'Bifunctor' class. You can find this in Hackage, so if you
-- want to use this just use it from there.
--
-- Minimal definition: either 'bimap' or both 'first' and 'second'.
class Bifunctor f where
bimap :: (a -> c) -> (b -> d) -> f a b -> f c d
bimap f g = first f . second g
first :: (a -> c) -> f a b -> f c b
first f = bimap f id
second :: (b -> d) -> f a b -> f a d
second g = bimap id g
-- The generic map function. I wrote this out with
-- ScopedTypeVariables to make it easier to read...
map :: forall f a b. (Functor (f a), Bifunctor f) =>
(a -> b) -> Fix (f a) -> Fix (f b)
map f = cata phi
where phi :: f a (Fix (f b)) -> Fix (f b)
phi = Fix . first f
Now your expression language works like this:
-- This is the base (bi)functor for your expression type.
data ExprF a r = Val a
| Add r r
deriving (Eq, Show, Functor)
instance Bifunctor ExprF where
bimap f g (Val a) = Val (f a)
bimap f g (Add l r) = Add (g l) (g r)
newtype Expr a = Expr (Fix (ExprF a))
instance Functor Expr where
fmap f (Expr exprF) = Expr (map f exprF)
EDIT: Here's a link to the bifunctors package in Hackage.
The keyword type is used only as a synonymous of an existing type, maybe this is what you are looking for
newtype Expr2 a r = In { out :: (ExprF a r)} deriving Functor

Resources