Home > front end >  How should I use all combinations in applicative
How should I use all combinations in applicative

Time:11-20

I encountered with a haskell problem. Here is the question.

toList $ fromList [( ),(*)] <*> fromList [1..3] <*> fromList [10,100,1000] =
    [11,101,1001,12,102,1002,13,103,1003,10,100,1000,20,200,2000,30,300,3000]

toList is a function that convert the Tree type into list and fromList is to convert a list to Tree Type.

And my job is to implement the pure and the <*> operator of Applicative Class. Here is my implement.

data Tree a = Branch (Tree a) (Tree a) | Leaf a deriving (Eq, Show)

instance Applicative Tree where
  pure = Leaf
  Leaf f       <*> t            = f <$> t
  Branch t1 t2 <*> Leaf a       = t1 <*> Leaf a
  Branch t1 t2 <*> Branch t3 t4 = Branch (t1 <*> t3) (t2 <*> t4)

But I do not know how to firgue out the "all combinations". Please help me.

CodePudding user response:

You were correct with the pure.

As to the <*>, you've also started right with the Leaf f <*> t clause. Just go with it, by small steps. For example:

data Tree a = Branch (Tree a) (Tree a) | Leaf a deriving (Eq, Show)

instance Functor Tree where
  fmap f (Leaf a)     =  Leaf (f a)
  fmap f (Branch l r) =  Branch (fmap f l) (fmap f r)

instance Applicative Tree where
  pure x  =  Leaf x
  --
  Leaf f     <*> t       =  f     <$> t
  t          <*> Leaf a  =  ($ a) <$> …
  Branch l r <*> t       =  Branch (… <*> t) (r <*> …)

You don't have to have a complete solution in your head before you write the code. Just start writing it, clause by clause, enumerating all the possibilities you could think of (meaning, structural possibilities for each of the arguments -- in this case, whether it's a leaf or a branch). You can always remove a redundant clause later.


The above definition of <*> works by recursion. And recursion works by assuming that we already have our definition for the the simpler cases, so we can build the result for a more complex case from solutions for its simpler sub-parts. Making sure that if the solutions for the sub-problems are correct -- and they are, by the assumption -- we combine those partial solutions properly so that the combined solution is correct for the whole problem:

recursion (problem) = solution where
  problem has part1, part2, ...
  sol1 = recursion(part1)
  sol2 = recursion(part2)
  ....
  solution is sol1, sol2, ..., combined properly together

And so in our case, when tree1 is Branch l r,

tree1 <*> tree2 = 
  case tree1 of Branch l r -> 
    let sol1 = l <*> tree2
        sol2 = .....
    in
       combineTogether sol1 sol2
   where
     combineTogether subtree1 subtree2 = .....

Just finish it up and try it at the REPL. See that it works all by itself, through the magic of recursion, since we've also defined how to handle the simplest cases directly:

  ....
  case tree1 of Leaf f -> 
  ....

(treat the above as bits of pseudo-syntax).


Thus the last line of our proposed definition,

  Branch l r <*> t       =  Branch (… <*> t) (r <*> …)

reads: all combinations of a tree which is Branch l r, with another tree t, is a new tree, which is Branch new_l new_r, where new_l holds all combinations of the .... with t, and the other one, new_r, holds the other combinations (just go ahead and make the most obvious substitutions for the dots there).

Just like with lists, all combinations of [(1 ),(2 )] with [30,40] is a list which combines all combinations of [(1 )] with [30,40], and all the combinations of [(2 )] with [30,40]:

      [(1 ),(2 )] <*> [30,40]
=
   ([(1 )]    [(2 )]) <*> [30,40]
=
([(1 )] <*> [30,40])    ([(2 )] <*> [30,40])

CodePudding user response:

One way to do it is to notice that leaf trees are monads.

import Control.Monad (liftM2)
import Control.Applicative (Applicative (..))

instance Monad Tree where
  Leaf a >>= f = f a
  Branch l r >>= f = Branch (l >>= f) (r >>= f)

instance Applicative Tree where
  pure = Leaf
  liftA2 = liftM2

Identity laws:

pure a >>= f = Leaf a >>= f = f a

m >>= pure
-- Leaf case
Leaf a >>= pure
= -- def of >>=
pure a
= -- def of pure
Leaf a

-- Branch case
Branch l r >>= pure
= -- def of >>=
Branch (l >>= pure) (r >>= pure)
= -- structural induction
Branch l r

Associative law:

(m >>= f) >>= g
-- when m = Leaf a
(Leaf a >>= f) >>= g
= --def of >>=
f a >>= g
= -- beta reduction
(\q -> f q >>= g) a
= -- def of >>=
Leaf a >>= \q -> f q >>= g
= -- assumption
m >> \q -> f q >>= g

-- when m = Branch l r
(Branch l r >>= f) >>= g
= -- def of >>=
Branch (l >>= f) (r >>= f) >>= g
= -- def of >>=
Branch ((l >>= f) >>= g) ((r >>= f) >>= g)
= -- Structural induction
Branch (l >>= \q -> f q >>= g) (r >>= \q -> f q >>= g)
= -- def of >>=
Branch l r >>= \q -> f q >>= g

To avoid certain (usually tiny) space leaks, you can change the definition of >>= a bit so it can inline:

instance Monad Tree where
  m >>= f = go m
    where
       go (Leaf a) = f a
       go (Branch l r) = Branch (go l) (go r)
  • Related