Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

About mapping through several nested functorial levels

A random example: given the following [Maybe [a]],

x = [Just [1..3], Nothing, Just [9]]

I want to map f = (^2) through the 3 layers, thus obtaining

[Just [1,4,9],Nothing,Just [81]]

The easiest way to do it seems to be

(fmap . fmap . fmap) (^2) x

where fmap . fmap . fmap is like fmap, but it goes 3 levels deep.

I suspect that the need for something like this, in the general case of composing fmap with itself a given number of times, is not uncommon, so I wonder if there's already something in the standard to compose fmap with itself a certain number of times. Or maybe something which "knows" how many times it should compose fmap with itself based on the input.

like image 495
Enlico Avatar asked Mar 31 '21 08:03

Enlico


3 Answers

You can work with a Compose type to go two (or more if you cascade) levels of functors deep.

So we can implement this as:

import Data.Functor.Compose(Compose(Compose, getCompose))

fmap (^2) (Compose (Compose [Just [1,4,9],Nothing,Just [81]]))

This then yields:

Prelude Data.Functor.Compose> fmap (^2) (Compose (Compose [Just [1,4,9],Nothing,Just [81]]))
Compose (Compose [Just [1,16,81],Nothing,Just [6561]])

we thus can unwrap it with:

Prelude Data.Functor.Compose> (getCompose . getCompose . fmap (^2)) (Compose (Compose [Just [1,4,9],Nothing,Just [81]]))
[Just [1,16,81],Nothing,Just [6561]]

By constructing a Compose that is a structure that is two Functors deep, we thus make it an instance of Functor that combines the two.

like image 191
Willem Van Onsem Avatar answered Nov 20 '22 17:11

Willem Van Onsem


If you want to super over-engineer this, you can use data kinds and type families. It's a bit crazy, but consider the following type family:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

type family DT fs x where
  DT '[] x = x
  DT (f ': fs) x = f (DT fs x)

Given a type-level list of functors (well, more generally, type function of kind * -> *), this wraps up a type in each value of the list. With this, we can write a crazy type class:

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE AllowAmbiguousTypes #-}

class DMap (fs :: [* -> *]) where
  dmap' :: (a -> b) -> DT fs a -> DT fs b

The function dmap' takes a function to apply (much like fmap) and then transforms this wrapped up a into a wrapped up b. The instances for this follow (somewhat) naturally, applying the idea of composing fmap with itself as many times as there are functors in the list:

instance DMap '[] where
  dmap' = id

instance (DMap fs, Functor f) => DMap (f ': fs) where
  dmap' = fmap . dmap' @fs

With this, we can write the following:

{-# LANGUAGE TypeApplications #-}

x = [Just [1..3], Nothing, Just [9]]
x' = dmap' @'[[], Maybe, []] (^2) x

Woohoo! Well, it's good, but writing out the list of functors is a pain, and shouldn't GHC be able to do that for us? We can add that by introducing another type family:

{-# LANGUAGE TypeOperators #-}

import GHC.TypeLits (Nat, type (-))

type family FType n a where
  FType 0 a = '[]
  FType n (f a) = f ': FType (n-1) a

This type family produces a type-level list of functors from a type that already is wrapped up (using the Nat to limit us from going deeper than we may want). We can then write a proper dmap that uses FType to solve what the list of functors are:

dmap :: forall n (fs :: [* -> *]) a b c d. (fs ~ FType n c, fs ~ FType n d, DMap fs, DT fs a ~ c, DT fs b ~ d) => (a -> b) -> c -> d
dmap = dmap' @fs

The type signature is a little hairy, but basically it's telling GHC to use the c value to determine what the functors are. In practice, this means we can write:

x' = dmap @3 (^2) x

(Note, I may have left out a language extension or two here or there .)


For the record, I don't know if I'd ever use something like this. The error messages are not great, to say the least, and to advanced Haskellers, seeing fmap . fmap (or even fmap . fmap . fmap) is not very scary.

like image 38
DDub Avatar answered Nov 20 '22 15:11

DDub


This answer is inspired by DDub's, but I think it's rather simpler, and it should offer slightly better type inference and probably better type errors. Let's first clear our throats:

{-# language FlexibleContexts #-}
{-# language FlexibleInstances #-}
{-# language MultiParamTypeClasses #-}
{-# language DataKinds #-}
{-# language AllowAmbiguousTypes #-}
{-# language UndecidableInstances #-}
{-# language ScopedTypeVariables #-}
module DMap where
import Data.Kind (Type)
import GHC.TypeNats

GHC's built-in Nats are pretty awkward to work with, because we can't pattern match on "not 0". So let's make them just part of the interface, and avoid them in the implementation.

-- Real unary naturals
data UNat = Z | S UNat

-- Convert 'Nat' to 'UNat' in the obvious way.
type family ToUnary (n :: Nat) where
  ToUnary 0 = 'Z
  ToUnary n = 'S (ToUnary (n - 1))

-- This is just a little wrapper function to deal with the
-- 'Nat'-to-'UNat' business.
dmap :: forall n s t a b. DMap (ToUnary n) s t a b
     => (a -> b) -> s -> t
dmap = dmap' @(ToUnary n)

Now that we've gotten the utterly boring part out of the way, the rest turns out to be pretty simple.

-- @n@ indicates how many 'Functor' layers to peel off @s@
-- and @t@ to reach @a@ and @b@, respectively.
class DMap (n :: UNat) s t a b where
  dmap' :: (a -> b) -> s -> t

How do we write the instances? Let's start with the obvious way, and then transform it into a way that will give better inference. The obvious way:

instance DMap 'Z a b a b where
  dmap' = id

instance (Functor f, DMap n x y a b)
  => DMap ('S n) (f x) (f y) a b where
  dmap' = fmap . dmap' @n

The trouble with writing it this way is the usual problem with multi-parameter instance resolution. GHC will only choose the first instance if it sees that the first argument is 'Z and the second and fourth arguments are the same and the third and fifth arguments are the same. Similarly, it will only choose the second instance if it sees that the first argument is 'S and the second argument is an application and the third argument is an application and the constructors applied in the second and third arguments are the same.

We want to choose the right instance as soon as we know the first argument. We can do that by simply shifting everything else to the left of the double arrow:

-- This stays the same.
class DMap (n :: UNat) s t a b where
  dmap' :: (a -> b) -> s -> t

instance (s ~ a, t ~ b) => DMap 'Z s t a b where
  dmap' = id

-- Notice how we're allowed to pull @f@, @x@,
-- and @y@ out of thin air here.
instance (Functor f, fx ~ (f x), fy ~ (f y), DMap n x y a b) 
  => DMap ('S n) fx fy a b where
  dmap' = fmap . dmap' @ n

Now, I claimed above that this gives better type inference than DDub's, so I'd better back that up. Let me just pull up GHCi:

*DMap> :t dmap @3
dmap @3
  :: (Functor f1, Functor f2, Functor f3) =>
     (a -> b) -> f1 (f2 (f3 a)) -> f1 (f2 (f3 b))

That's precisely the type of fmap.fmap.fmap. Perfect! With DDub's code, I instead get

dmap @3
  :: (DMap (FType 3 c), DT (FType 3 c) a ~ c,
      FType 3 (DT (FType 3 c) b) ~ FType 3 c) =>
     (a -> b) -> c -> DT (FType 3 c) b

which is ... not so clear. As I mentioned in a comment, this could be fixed, but it adds a bit more complexity to code that is already somewhat complicated.


Just for fun, we can pull the same trick with traverse and foldMap.

dtraverse :: forall n f s t a b. (DTraverse (ToUnary n) s t a b, Applicative f) => (a -> f b) -> s -> f t
dtraverse = dtraverse' @(ToUnary n)

class DTraverse (n :: UNat) s t a b where
  dtraverse' :: Applicative f => (a -> f b) -> s -> f t

instance (s ~ a, t ~ b) => DTraverse 'Z s t a b where
  dtraverse' = id

instance (Traversable t, tx ~ (t x), ty ~ (t y), DTraverse n x y a b) => DTraverse ('S n) tx ty a b where
  dtraverse' = traverse . dtraverse' @ n

dfoldMap :: forall n m s a. (DFold (ToUnary n) s a, Monoid m) => (a -> m) -> s -> m
dfoldMap = dfoldMap' @(ToUnary n)

class DFold (n :: UNat) s a where
  dfoldMap' :: Monoid m => (a -> m) -> s -> m

instance s ~ a => DFold 'Z s a where
  dfoldMap' = id

instance (Foldable t, tx ~ (t x), DFold n x a) => DFold ('S n) tx a where
  dfoldMap' = foldMap . dfoldMap' @ n
like image 3
dfeuer Avatar answered Nov 20 '22 17:11

dfeuer