Skip to content

Instantly share code, notes, and snippets.

@mrkgnao
Created March 13, 2018 08:36
Show Gist options
  • Save mrkgnao/9c6c321ec8659c7cb9be8ba066cd677c to your computer and use it in GitHub Desktop.
Save mrkgnao/9c6c321ec8659c7cb9be8ba066cd677c to your computer and use it in GitHub Desktop.
@ekmett's iterated fmap
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Fmap where
import Control.Category ((<<<), (>>>))
import Prelude hiding (map)
type Reader = (->)
type F f a b = (a -> b) -> f a -> f b
-- (.) . (.)
comp :: forall a b x y . (a -> b) -> (x -> y -> a) -> x -> y -> b
comp ab xya x y = ab (xya x y)
c7 :: (x -> a -> b) -> x -> (y -> z -> a) -> y -> z -> b
c7 = (.) (.) (.) (.) (.) (.) (.)
c7' :: (x -> a -> b) -> x -> (y -> z -> a) -> y -> z -> b
c7' xab x yza y z = xab x (yza y z)
f1 :: forall f a b . Functor f => (a -> b) -> (f a -> f b)
f1 = fmap @f
f2 :: forall f g a b . (Functor f, Functor g) => f (a -> b) -> f (g a -> g b)
f2 = fmap @f (fmap @g)
f3 :: forall f g a b . (Functor f, Functor g) => (a -> b) -> f (g a) -> f (g b)
f3 = fmap @(Reader (a -> b)) (fmap @f) (fmap @g)
f3' :: forall f g a b . (Functor f, Functor g) => (a -> b) -> f (g a) -> f (g b)
f3' = (.) (fmap @f) (fmap @g)
f4
:: forall f g h a b
. (Functor f, Functor g, Functor h)
=> f (g (a -> b))
-> f (g (h a -> h b))
f4 = fmap @(Reader ((a -> b) -> h a -> h b)) (fmap @f) (fmap @g) (fmap @h)
f4'
:: forall f g h a b
. (Functor f, Functor g, Functor h)
=> f (g (a -> b))
-> f (g (h a -> h b))
f4' = (.) (fmap @f) (fmap @g) (fmap @h)
f4''
:: forall f g h a b
. (Functor f, Functor g, Functor h)
=> f (g (a -> b))
-> f (g (h a -> h b))
f4'' = fmap (fmap fmap)
f5 :: forall f a b c . Functor f => (a -> b) -> (c -> a) -> f c -> f b
f5 = fmap @(Reader ((c -> b) -> f c -> f b)) (fmap @(Reader (a -> b)))
(fmap @(Reader (c -> a)))
(fmap @f)
(fmap @(Reader c))
f5' :: forall f a b c . Functor f => (a -> b) -> (c -> a) -> f c -> f b
f5' = comp (fmap @f) ((.) :: (a -> b) -> (c -> a) -> c -> b)
f6
:: forall f g x a b
. (Functor f, Functor g)
=> (x -> a -> b)
-> f x
-> f (g a -> g b)
f6 = fmap @(Reader ((x -> g a -> g b) -> f x -> f (g a -> g b)))
(fmap @(Reader ((a -> b) -> g a -> g b)))
(fmap @(Reader (x -> a -> b)))
(fmap @f)
(fmap @(Reader x))
(fmap @g)
f6'
:: forall f g x a b
. (Functor f, Functor g)
=> (x -> a -> b)
-> f x
-> f (g a -> g b)
f6' = (.) (.) (.) (fmap @f) (.) (fmap @g)
f6''
:: forall f g x a b
. (Functor f, Functor g)
=> (x -> a -> b)
-> f x
-> f (g a -> g b)
f6'' = comp (fmap @f) ((.) @(a -> b) @(g a -> g b) @x) (fmap @g)
f6_
:: forall f g x a b
. (Functor f, Functor g)
=> (x -> a -> b)
-> f x
-> f (g a -> g b)
f6_ xab = mapf (xab >>> mapg)
where
mapf = fmap @f
mapg = fmap @g
f7
:: forall h g f a b
. (Functor f, Functor g, Functor h)
=> f (a -> b)
-> f (g (h a) -> g (h b))
f7 = fmap fmap fmap fmap fmap fmap fmap
f8
:: forall h g f a b
. (Functor f, Functor g, Functor h)
=> (a -> b)
-> f (g (h a))
-> f (g (h b))
f8 = fmap fmap fmap fmap fmap fmap fmap fmap
f9
:: forall f g h i a b.
(Functor f, Functor g, Functor h, Functor i) =>
f (g (h (a -> b))) -> f (g (h (i a -> i b)))
f9 = fmap fmap fmap fmap fmap fmap fmap fmap fmap
f10
:: forall f g a b x
. (Functor f, Functor g)
=> (x -> a -> b) -> f x -> f (g a -> g b)
f10 = fmap fmap fmap fmap fmap fmap fmap fmap fmap fmap
f10'
:: forall f g a b x
. (Functor f, Functor g)
=> (x -> a -> b) -> f x -> f (g a -> g b)
f10' = (.) (.) (.) (.) (.) (.) (.) (fmap @f) (fmap @g) (fmap @f)
f10''
:: forall f g a b x
. (Functor f, Functor g)
=> (x -> a -> b) -> f x -> f (g a -> g b)
f10'' = c7' (fmap @f) (fmap @g) (fmap @f)
f11 ::
forall f g h a b.
(Functor f, Functor g, Functor h) =>
f (a -> b) -> f (g (h a) -> g (h b))
f11 = (.) (.) (.) (.) (.) (.) (.) (fmap @f) (fmap @g) (fmap @f) (fmap @h)
f12
:: forall h g f a b
. (Functor f, Functor g, Functor h)
=> (a -> b)
-> f (g (h a))
-> f (g (h b))
f12 = fmap fmap fmap fmap fmap fmap fmap fmap fmap fmap fmap fmap
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment