module Data.Tree.Optics
  ( root
  , branches
  ) where
import Data.Tree (Tree (..))
import Optics.Lens
root :: Lens' (Tree a) a
root :: forall a. Lens' (Tree a) a
root = forall s t a b. LensVL s t a b -> Lens s t a b
lensVL forall a b. (a -> b) -> a -> b
$ \a -> f a
f (Node a
a [Tree a]
as) -> (forall a. a -> [Tree a] -> Tree a
`Node` [Tree a]
as) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a
f a
a
{-# INLINE root #-}
branches :: Lens' (Tree a) [Tree a]
branches :: forall a. Lens' (Tree a) [Tree a]
branches = forall s t a b. LensVL s t a b -> Lens s t a b
lensVL forall a b. (a -> b) -> a -> b
$ \[Tree a] -> f [Tree a]
f (Node a
a [Tree a]
as) -> forall a. a -> [Tree a] -> Tree a
Node a
a forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Tree a] -> f [Tree a]
f [Tree a]
as
{-# INLINE branches #-}