0

I am trying to make a function that take a index into a forest, and a list of integers to choose a way down a tree, and turns that into a lens that focuses that same element.

Effectively, it is the opposite of what (t :: Data.Tree.Forest) ^@.. itraversed <.> itraversed does.

Here is my attempt:

pathToLens :: (Applicative f) => (Int, [Int]) -> LensLike' f (Data.Tree.Forest a) (Data.Tree.Tree a)
pathToLens (rootIdx, branchIndices) =
    ix rootIdx . helper branchIndices
  where
    helper :: (Applicative f) => [Word64] -> LensLike' f (Data.Tree.Tree a) (Data.Tree.Tree a)
    helper (idx : rest) = branches . ix idx . helper rest
    helper [] = id

The function compiles fine. But then I try to use it:

test = [Data.Tree.Node () []] ^. (pathToLens (0,[]))

And I get:

• No instance for (Monoid (Data.Tree.Tree ()))
    arising from a use of ‘pathToLens’
• In the second argument of ‘(^.)’, namely ‘(pathToLens (0, []))’

Why is there no Monoid for my Tree? From looking at the Tree docs, it seems there is Monad Tree. Does that not include Monoid Tree?

Janus Troelsen
  • 20,267
  • 14
  • 135
  • 196

2 Answers2

1
Why is there no Monoid for my Tree ?

It seems that there is no general way to “add” two Rose trees, because you would have trouble deciding what the root label of the sum tree is supposed to be. Hence you cannot have a general Monoid instance for all possible sorts of Tree objects.

However, what's required here is simply an instance of Monoid for type Tree (). There is only one possible value for the sum root label, so the problem disappears. The relevant code is easy to write:

{-#  LANGUAGE  FlexibleInstances  #-}
import  Data.Tree

instance  Semigroup (Tree ())  where  tr1 <> tr2 = Node () [tr1,tr2]
instance  Monoid  (Tree ())    where  mempty = Node () []

And if that can help, you can have a Monoid structure for any Tree m type, assuming that the base type m is itself a Monoid. Like this:

{-#  LANGUAGE  ScopedTypeVariables  #-}
{-#  LANGUAGE  ExplicitForAll       #-}

import Data.Tree

instance  Monoid m => Semigroup (Tree m)  where
    tr1@(Node r1 f1) <> tr2@(Node r2 f2) = Node (r1<>r2) [tr1,tr2]

instance  Monoid m => Monoid (Tree m)  where
    mempty = Node { rootLabel = (mempty::m), subForest = [] }

This code compiles flawlessly with GHC 8.6.5:

{-#  LANGUAGE  ScopedTypeVariables  #-}
{-#  LANGUAGE  ExplicitForAll       #-}

import  Data.Tree
import  Control.Lens
import  Control.Lens.Combinators
import  Data.Tree.Lens

pathToLens :: (Applicative f) => (Int, [Int]) -> LensLike' f (Data.Tree.Forest a) (Data.Tree.Tree a)
pathToLens (rootIdx, branchIndices) =
    ix rootIdx . helper branchIndices
  where
    helper :: (Applicative f) => [Int] -> LensLike' f (Data.Tree.Tree a) (Data.Tree.Tree a)
    helper (idx : rest) = branches . ix idx . helper rest
    helper [] = id

And the instance code above makes the error message about a missing Monoid instance go away:

Testing under ghci:

$ ghci
GHCi, version 8.6.5: http://www.haskell.org/ghc/  :? for help
Loaded GHCi configuration from /home/jeanpaul/.ghci
 λ> 
 λ> :set -XScopedTypeVariables 
 λ> :set -XExplicitForAll
 λ> 
 λ> :!cat pathToLens.hs

import  Data.Tree
import  Control.Lens
import  Control.Lens.Combinators
import  Data.Tree.Lens

pathToLens :: (Applicative f) => (Int, [Int]) -> LensLike' f (Data.Tree.Forest a) (Data.Tree.Tree a)
pathToLens (rootIdx, branchIndices) =
    ix rootIdx . helper branchIndices
  where
    helper :: (Applicative f) => [Int] -> LensLike' f (Data.Tree.Tree a) (Data.Tree.Tree a)
    helper (idx : rest) = branches . ix idx . helper rest
    helper [] = id

 λ> 
 λ> :load pathToLens.hs
[1 of 1] Compiling Main             ( pathToLens.hs, interpreted )
Ok, one module loaded.
 λ> 
 λ> ls = (pathToLens (0,[]))
 λ> test = [Data.Tree.Node () []]  ^.  ls

<interactive>:10:36: error:
    • No instance for (Monoid (Tree ())) arising from a use of ‘ls’
    • In the second argument of ‘(^.)’, namely ‘ls’
      In the expression: [Node () []] ^. ls
      In an equation for ‘test’: test = [Node () []] ^. ls
 λ> 

So, at that stage, the initial problem is reproduced.

Now let's add our little monoid instance for (some) trees, and retry:

 λ> 
 λ> instance  Semigroup γ => Semigroup (Tree γ)  where  t1@(Node r1 f1) <> t2@(Node r2 f2)  =  Node  (r1<>r2)  [t1,t2]
 λ> 
 λ> instance  Monoid µ => Monoid (Tree µ)  where  mempty  =  Node { rootLabel = (mempty::µ), subForest = [] }
 λ> 
 λ> test = [Data.Tree.Node () []]  ^.  ls
 λ> 
 λ> :t test
test :: Tree ()
 λ> 

The Haskell Prelude provides a (trivial) Monoid instance for (), and then the compiler infers from that the existence of another Monoid instance for Tree ().

jpmarinier
  • 4,427
  • 1
  • 10
  • 23
  • Like I said in the question, the function itself compiles fine, it only breaks when I try to use it. Actually, I don't even understand why the Monoid is needed, but it is probably because I put that Applicative constraint in there. But is that really necessary? Surely it should be possible to get and set elements by index even without it. If I remove Applicative, I get an error. Is `LensLike'` even the right choice? – Janus Troelsen Nov 20 '20 at 18:23
  • @JanusTroelsen - well, sorry I have been unclear. If I do NOT include my above definition of a monoid for (some) trees, I do see the error message about a missing monoid instance at execution time. But if I do include it, the error message disappears. I will update the answer for clarity. – jpmarinier Nov 20 '20 at 18:55
1

Given that a tree at the given path might not exist, pathToLens can't be a proper lens. Lenses always hit their targets.

It can be made a Traversal':

import Data.List.NonEmpty

pathToTraversal :: NonEmpty Int -> Traversal' (Data.Tree.Forest a) (Data.Tree.Tree a)
pathToTraversal (rootIdx :| branchIndices) =
    ix rootIdx . helper branchIndices
  where
    helper (idx : rest) = branches . ix idx . helper rest
    helper [] = id

And, if one is feeling adventurous and believes the Traversal' will always hit a target, it can be turned into a Lens' using unsafeSingular:

unsafePathToLens :: NonEmpty Int -> Lens' (Data.Tree.Forest a) (Data.Tree.Tree a)
unsafePathToLens is = unsafeSingular (pathToTraversal is)
danidiaz
  • 26,936
  • 4
  • 45
  • 95
  • Oh my, you only changed the type! I had no idea it would be so simple. Upvoted and accepted. – Janus Troelsen Nov 20 '20 at 20:21
  • 1
    @JanusTroelsen `^.` has type `(^.) :: s -> Getting a s a -> a`, while `Getting` is `type Getting r s a = (a -> Const r a) -> s -> Const r s`. The `Monoid` constraint seems to come from trying to satisfy `Applicative (Const (Tree _)`. The `Const` type needs an accumulator with a `Monoid` instance to be `Applicative`. – danidiaz Nov 20 '20 at 20:26