Composing function composition: How does (.).(.) work?

后端 未结 7 1618
温柔的废话
温柔的废话 2020-11-29 06:36

(.) takes two functions that take one value and return a value:

(.) :: (b -> c) -> (a -> b) -> a -> c

相关标签:
7条回答
  • 2020-11-29 06:56

    (Read my answer on function composition, $ operator and point-free style first.)

    Imagine you have a simple function: it adds up 2 numbers and then negates the result. We'll call it foo:

    foo a b = negate (a + b)
    

    Now let's make it point-free step by step and see what we end up with:

    foo a b = negate $ a + b
    foo a b = negate $ (+) a b
    foo a b = negate $ (+) a $ b
    foo a b = negate . (+) a $ b
    foo a   = negate . (+) a -- f x = g x is equivalent to f = g
    foo a   = (.) negate ((+) a) -- any infix operator is just a function
    foo a   = (negate.) ((+) a) -- (2+) is the same as ((+) 2)
    foo a   = (negate.) $ (+) a
    foo a   = (negate.) . (+) $ a
    foo     = (negate.) . (+)
    foo     = ((.) negate) . (+)
    foo     = (.) ((.) negate) (+) -- move dot in the middle in prefix position
    foo     = ((.) ((.) negate)) (+) -- add extra parentheses
    

    Now let's analyze expression (.) ((.) negate) more closely. It's a partial application of (.) function, whose first argument is ((.) negate). Can we transform it even further? Yes we can:

    (.) ((.) negate)
    (.) . (.) $ negate -- because f (f x) is the same as (f . f) x
    (.)(.)(.) $ negate
    ((.)(.)(.)) negate
    

    (.).(.) is equivalent to (.)(.)(.), because in the 1st expression, the dot in the middle can be moved in prefix position and surrounded with parentheses, which gives rise to the 2nd expression.

    Now we can rewrite our foo function:

    foo = ((.).(.)) negate (+)
    foo = ((.)(.)(.)) negate (+) -- same as previous one
    foo = negate .: (+)
      where (.:) = (.).(.)
    

    Now you know that (.).(.) is equivalent to (\f g x y -> f (g x y)):

    (\f g x y -> f (g x y)) negate (+) 2 3 -- returns -5
    ((.).(.)) negate (+) 2 3 -- returns -5
    
    0 讨论(0)
  • 2020-11-29 07:05

    Yes this is due to currying. (.) as all functions in Haskell only takes one argument. What you are composing is the first partial call to each respective composed (.) which takes its first argument (the first function of the composition).

    0 讨论(0)
  • 2020-11-29 07:06

    This is one of those neat cases where I think it's simpler to grasp the more general case first, and then think about the specific case. So let's think about functors. We know that functors provide a way to map functions over a structure --

    class Functor f where
      fmap :: (a -> b) -> f a -> f b
    

    But what if we have two layers of the functor? For example, a list of lists? In that case we can use two layers of fmap

    >>> let xs = [[1,2,3], [4,5,6]]
    >>> fmap (fmap (+10)) xs
    [[11,12,13],[14,15,16]]
    

    But the pattern f (g x) is exactly the same as (f . g) x so we could write

    >>> (fmap . fmap) (+10) xs
    [[11,12,13],[14,15,16]]
    

    What is the type of fmap . fmap?

    >>> :t fmap.fmap
      :: (Functor g, Functor f) => (a -> b) -> f (g a) -> f (g b)
    

    We see that it maps over two layers of functor, as we wanted. But now remember that (->) r is a functor (the type of functions from r, which you might prefer to read as (r ->)) and its functor instance is

    instance Functor ((->) r) where
      fmap f g = f . g
    

    For a function, fmap is just function composition! When we compose two fmaps we map over two levels of the function functor. We initially have something of type (->) s ((->) r a), which is equivalent to s -> r -> a, and we end up with something of type s -> r -> b, so the type of (.).(.) must be

    (.).(.) :: (a -> b) -> (s -> r -> a) -> (s -> r -> b)
    

    which takes its first function, and uses it to transform the output of the second (two-argument) function. So for example, the function ((.).(.)) show (+) is a function of two arguments, that first adds its arguments together and then transforms the result to a String using show:

    >>> ((.).(.)) show (+) 11 22
    "33"
    

    There is then a natural generalization to thinking about longer chains of fmap, for example

    fmap.fmap.fmap ::
      (Functor f, Functor g, Functor h) => (a -> b) -> f (g (h a)) -> f (g (h b))
    

    which maps over three layers of functor, which is equivalent to composing with a function of three arguments:

    (.).(.).(.) :: (a -> b) -> (r -> s -> t -> a) -> (r -> s -> t -> b)
    

    for example

    >>> import Data.Map
    >>> ((.).(.).(.)) show insert 1 True empty
    "fromList [(1,True)]"
    

    which inserts the value True into an empty map with key 1, and then converts the output to a string with show.


    These functions can be generally useful, so you sometimes see them defined as

    (.:) :: (a -> b) -> (r -> s -> a) -> (r -> s -> b)
    (.:) = (.).(.)
    

    so that you can write

    >>> let f = show .: (+)
    >>> f 10 20
    "30"
    

    Of course, a simpler, pointful definition of (.:) can be given

    (.:) :: (a -> b) -> (r -> s -> a) -> (r -> s -> b)
    (f .: g) x y = f (g x y)
    

    which may help to demystify (.).(.) somewhat.

    0 讨论(0)
  • 2020-11-29 07:19

    Let's first play typechecker for the mechanical proof. I'll describe an intuitive way of thinking about it afterward.

    I want to apply (.) to (.) and then I'll apply (.) to the result. The first application helps us to define some equivalences of variables.

    ((.) :: (b -> c) -> (a -> b) -> a -> c) 
          ((.) :: (b' -> c') -> (a' -> b') -> a' -> c') 
          ((.) :: (b'' -> c'') -> (a'' -> b'') -> a'' -> c'')
    
    let b = (b' -> c') 
        c = (a' -> b') -> a' -> c'
    
    ((.) (.) :: (a -> b) -> a -> c) 
          ((.) :: (b'' -> c'') -> (a'' -> b'') -> a'' -> c'')
    

    Then we begin the second, but get stuck quickly...

    let a = (b'' -> c'')
    

    This is key: we want to let b = (a'' -> b'') -> a'' -> c'', but we already defined b, so instead we must try to unify --- to match up our two definitions as best we can. Fortunately, they do match

    UNIFY b = (b' -> c') =:= (a'' -> b'') -> a'' -> c''
    which implies 
          b' = a'' -> b''
          c' = a'' -> c''
    

    and with those definitions/unifications we can continue the application

    ((.) (.) (.) :: (b'' -> c'') -> (a' -> b') -> (a' -> c'))
    

    then expand

    ((.) (.) (.) :: (b'' -> c'') -> (a' -> a'' -> b'') -> (a' -> a'' -> c''))
    

    and clean it up

    substitute b'' -> b
               c'' -> c
               a'  -> a
               a'' -> a1
    
    (.).(.) :: (b -> c) -> (a -> a1 -> b) -> (a -> a1 -> c)
    

    which, to be honest, is a bit of a counterintuitive result.


    Here's the intuition. First take a look at fmap

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

    it "lifts" a function up into a Functor. We can apply it repeatedly

    fmap.fmap.fmap :: (Functor f, Functor g, Functor h) 
                   => (a -> b) -> (f (g (h a)) -> f (g (h b)))
    

    allowing us to lift a function into deeper and deeper layers of Functors.

    It turns out that the data type (r ->) is a Functor.

    instance Functor ((->) r) where
       fmap = (.)
    

    which should look pretty familiar. This means that fmap.fmap translates to (.).(.). Thus, (.).(.) is just letting us transform the parametric type of deeper and deeper layers of the (r ->) Functor. The (r ->) Functor is actually the Reader Monad, so layered Readers is like having multiple independent kinds of global, immutable state.

    Or like having multiple input arguments which aren't being affected by the fmaping. Sort of like composing a new continuation function on "just the result" of a (>1) arity function.


    It's finally worth noting that if you think this stuff is interesting, it forms the core intuition behind deriving the Lenses in Control.Lens.

    0 讨论(0)
  • 2020-11-29 07:20

    Let’s ignore types for a moment and just use lambda calculus.

    • Desugar infix notation:
      (.) (.) (.)

    • Eta-expand:
      (\ a b -> (.) a b) (\ c d -> (.) c d) (\ e f -> (.) e f)

    • Inline the definition of (.):
      (\ a b x -> a (b x)) (\ c d y -> c (d y)) (\ e f z -> e (f z))

    • Substitute a:
      (\ b x -> (\ c d y -> c (d y)) (b x)) (\ e f z -> e (f z))

    • Substitute b:
      (\ x -> (\ c d y -> c (d y)) ((\ e f z -> e (f z)) x))

    • Substitute e:
      (\ x -> (\ c d y -> c (d y)) (\ f z -> x (f z)))

    • Substitute c:
      (\ x -> (\ d y -> (\ f z -> x (f z)) (d y)))

    • Substitute f:
      (\ x -> (\ d y -> (\ z -> x (d y z))))

    • Resugar lambda notation:
      \ x d y z -> x (d y z)

    And if you ask GHCi, you’ll find that this has the expected type. Why? Because the function arrow is right-associative to support currying: the type (b -> c) -> (a -> b) -> a -> c really means (b -> c) -> ((a -> b) -> (a -> c)). At the same time, the type variable b can stand for any type, including a function type. See the connection?

    0 讨论(0)
  • 2020-11-29 07:21

    You're right, (.) only takes two arguments. You just seem to be confused with the syntax of haskell. In the expression (.).(.), it's in fact the dot in the middle that takes the other two dots as argument, just like in the expression 100 + 200, which can be written as (+) 100 200.

    (.).(.) === (number the dots)
    (1.)2.(3.) === (rewrite using just syntax rules)
    (2.)(1.)(3.) === (unnumber and put spaces)
    (.) (.) (.) ===
    

    And it should be even more clear from (.) (.) (.) that the first (.) is taking the second (.) and third (.) as it's arguments.

    0 讨论(0)
提交回复
热议问题