{-# LANGUAGE BangPatterns      #-}
{-# LANGUAGE CPP               #-}
{-# LANGUAGE DeriveFoldable    #-}
{-# LANGUAGE DeriveFunctor     #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE Safe              #-}
{-# LANGUAGE TypeFamilies      #-}
module Data.RAList.Tree.Internal (
    Leaf (..),
    Node (..),
    Dir (..),
    -- * Tree class
    -- | TODO move to private module so new instances cannot be defined
    IsTree (..),
    Size,
    Offset,
    ) where

import Prelude
       (Bool (..), Eq (..), Functor (..), Int, Maybe (..), Num (..), Ord (..),
       Show, div, otherwise, seq, (&&), (.))

import Control.Applicative (Applicative (..), (<$>))
import Control.DeepSeq     (NFData (..))
import Data.Hashable       (Hashable (..))
import Data.Monoid         (Monoid (..))
import Data.Semigroup      (Semigroup (..))

import qualified Data.Foldable    as I (Foldable (..))
import qualified Data.Traversable as I (Traversable (..))

#ifdef MIN_VERSION_distributive
import qualified Data.Distributive as I (Distributive (..))

#ifdef MIN_VERSION_adjunctions
import qualified Data.Functor.Rep as I (Representable (..))
#endif
#endif

#ifdef MIN_VERSION_semigroupoids
import Data.Functor.Apply (Apply (..))

import qualified Data.Semigroup.Foldable    as I (Foldable1 (..))
import qualified Data.Semigroup.Traversable as I (Traversable1 (..))
#endif

-------------------------------------------------------------------------------
-- Types
-------------------------------------------------------------------------------

-- | A 'Leaf' is isomorphic to 'Identity', but we reimplement it here
-- to have domain specific type. The short constructor name is a bonus.
newtype Leaf a = Lf a
  deriving (Leaf a -> Leaf a -> Bool
(Leaf a -> Leaf a -> Bool)
-> (Leaf a -> Leaf a -> Bool) -> Eq (Leaf a)
forall a. Eq a => Leaf a -> Leaf a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Leaf a -> Leaf a -> Bool
$c/= :: forall a. Eq a => Leaf a -> Leaf a -> Bool
== :: Leaf a -> Leaf a -> Bool
$c== :: forall a. Eq a => Leaf a -> Leaf a -> Bool
Eq, Eq (Leaf a)
Eq (Leaf a)
-> (Leaf a -> Leaf a -> Ordering)
-> (Leaf a -> Leaf a -> Bool)
-> (Leaf a -> Leaf a -> Bool)
-> (Leaf a -> Leaf a -> Bool)
-> (Leaf a -> Leaf a -> Bool)
-> (Leaf a -> Leaf a -> Leaf a)
-> (Leaf a -> Leaf a -> Leaf a)
-> Ord (Leaf a)
Leaf a -> Leaf a -> Bool
Leaf a -> Leaf a -> Ordering
Leaf a -> Leaf a -> Leaf a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (Leaf a)
forall a. Ord a => Leaf a -> Leaf a -> Bool
forall a. Ord a => Leaf a -> Leaf a -> Ordering
forall a. Ord a => Leaf a -> Leaf a -> Leaf a
min :: Leaf a -> Leaf a -> Leaf a
$cmin :: forall a. Ord a => Leaf a -> Leaf a -> Leaf a
max :: Leaf a -> Leaf a -> Leaf a
$cmax :: forall a. Ord a => Leaf a -> Leaf a -> Leaf a
>= :: Leaf a -> Leaf a -> Bool
$c>= :: forall a. Ord a => Leaf a -> Leaf a -> Bool
> :: Leaf a -> Leaf a -> Bool
$c> :: forall a. Ord a => Leaf a -> Leaf a -> Bool
<= :: Leaf a -> Leaf a -> Bool
$c<= :: forall a. Ord a => Leaf a -> Leaf a -> Bool
< :: Leaf a -> Leaf a -> Bool
$c< :: forall a. Ord a => Leaf a -> Leaf a -> Bool
compare :: Leaf a -> Leaf a -> Ordering
$ccompare :: forall a. Ord a => Leaf a -> Leaf a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (Leaf a)
Ord, Int -> Leaf a -> ShowS
[Leaf a] -> ShowS
Leaf a -> String
(Int -> Leaf a -> ShowS)
-> (Leaf a -> String) -> ([Leaf a] -> ShowS) -> Show (Leaf a)
forall a. Show a => Int -> Leaf a -> ShowS
forall a. Show a => [Leaf a] -> ShowS
forall a. Show a => Leaf a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Leaf a] -> ShowS
$cshowList :: forall a. Show a => [Leaf a] -> ShowS
show :: Leaf a -> String
$cshow :: forall a. Show a => Leaf a -> String
showsPrec :: Int -> Leaf a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Leaf a -> ShowS
Show, a -> Leaf b -> Leaf a
(a -> b) -> Leaf a -> Leaf b
(forall a b. (a -> b) -> Leaf a -> Leaf b)
-> (forall a b. a -> Leaf b -> Leaf a) -> Functor Leaf
forall a b. a -> Leaf b -> Leaf a
forall a b. (a -> b) -> Leaf a -> Leaf b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Leaf b -> Leaf a
$c<$ :: forall a b. a -> Leaf b -> Leaf a
fmap :: (a -> b) -> Leaf a -> Leaf b
$cfmap :: forall a b. (a -> b) -> Leaf a -> Leaf b
Functor, Functor Leaf
Foldable Leaf
Functor Leaf
-> Foldable Leaf
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> Leaf a -> f (Leaf b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Leaf (f a) -> f (Leaf a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Leaf a -> m (Leaf b))
-> (forall (m :: * -> *) a. Monad m => Leaf (m a) -> m (Leaf a))
-> Traversable Leaf
(a -> f b) -> Leaf a -> f (Leaf b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Leaf (m a) -> m (Leaf a)
forall (f :: * -> *) a. Applicative f => Leaf (f a) -> f (Leaf a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Leaf a -> m (Leaf b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Leaf a -> f (Leaf b)
sequence :: Leaf (m a) -> m (Leaf a)
$csequence :: forall (m :: * -> *) a. Monad m => Leaf (m a) -> m (Leaf a)
mapM :: (a -> m b) -> Leaf a -> m (Leaf b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Leaf a -> m (Leaf b)
sequenceA :: Leaf (f a) -> f (Leaf a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Leaf (f a) -> f (Leaf a)
traverse :: (a -> f b) -> Leaf a -> f (Leaf b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Leaf a -> f (Leaf b)
$cp2Traversable :: Foldable Leaf
$cp1Traversable :: Functor Leaf
I.Traversable)

-- | 'Node' is a product of two @f@. This way we can form a perfect binary tree.
data Node f a = Nd (f a) (f a)
  deriving (Node f a -> Node f a -> Bool
(Node f a -> Node f a -> Bool)
-> (Node f a -> Node f a -> Bool) -> Eq (Node f a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (f :: * -> *) a. Eq (f a) => Node f a -> Node f a -> Bool
/= :: Node f a -> Node f a -> Bool
$c/= :: forall (f :: * -> *) a. Eq (f a) => Node f a -> Node f a -> Bool
== :: Node f a -> Node f a -> Bool
$c== :: forall (f :: * -> *) a. Eq (f a) => Node f a -> Node f a -> Bool
Eq, Eq (Node f a)
Eq (Node f a)
-> (Node f a -> Node f a -> Ordering)
-> (Node f a -> Node f a -> Bool)
-> (Node f a -> Node f a -> Bool)
-> (Node f a -> Node f a -> Bool)
-> (Node f a -> Node f a -> Bool)
-> (Node f a -> Node f a -> Node f a)
-> (Node f a -> Node f a -> Node f a)
-> Ord (Node f a)
Node f a -> Node f a -> Bool
Node f a -> Node f a -> Ordering
Node f a -> Node f a -> Node f a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall (f :: * -> *) a. Ord (f a) => Eq (Node f a)
forall (f :: * -> *) a. Ord (f a) => Node f a -> Node f a -> Bool
forall (f :: * -> *) a.
Ord (f a) =>
Node f a -> Node f a -> Ordering
forall (f :: * -> *) a.
Ord (f a) =>
Node f a -> Node f a -> Node f a
min :: Node f a -> Node f a -> Node f a
$cmin :: forall (f :: * -> *) a.
Ord (f a) =>
Node f a -> Node f a -> Node f a
max :: Node f a -> Node f a -> Node f a
$cmax :: forall (f :: * -> *) a.
Ord (f a) =>
Node f a -> Node f a -> Node f a
>= :: Node f a -> Node f a -> Bool
$c>= :: forall (f :: * -> *) a. Ord (f a) => Node f a -> Node f a -> Bool
> :: Node f a -> Node f a -> Bool
$c> :: forall (f :: * -> *) a. Ord (f a) => Node f a -> Node f a -> Bool
<= :: Node f a -> Node f a -> Bool
$c<= :: forall (f :: * -> *) a. Ord (f a) => Node f a -> Node f a -> Bool
< :: Node f a -> Node f a -> Bool
$c< :: forall (f :: * -> *) a. Ord (f a) => Node f a -> Node f a -> Bool
compare :: Node f a -> Node f a -> Ordering
$ccompare :: forall (f :: * -> *) a.
Ord (f a) =>
Node f a -> Node f a -> Ordering
$cp1Ord :: forall (f :: * -> *) a. Ord (f a) => Eq (Node f a)
Ord, Int -> Node f a -> ShowS
[Node f a] -> ShowS
Node f a -> String
(Int -> Node f a -> ShowS)
-> (Node f a -> String) -> ([Node f a] -> ShowS) -> Show (Node f a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (f :: * -> *) a. Show (f a) => Int -> Node f a -> ShowS
forall (f :: * -> *) a. Show (f a) => [Node f a] -> ShowS
forall (f :: * -> *) a. Show (f a) => Node f a -> String
showList :: [Node f a] -> ShowS
$cshowList :: forall (f :: * -> *) a. Show (f a) => [Node f a] -> ShowS
show :: Node f a -> String
$cshow :: forall (f :: * -> *) a. Show (f a) => Node f a -> String
showsPrec :: Int -> Node f a -> ShowS
$cshowsPrec :: forall (f :: * -> *) a. Show (f a) => Int -> Node f a -> ShowS
Show, a -> Node f b -> Node f a
(a -> b) -> Node f a -> Node f b
(forall a b. (a -> b) -> Node f a -> Node f b)
-> (forall a b. a -> Node f b -> Node f a) -> Functor (Node f)
forall a b. a -> Node f b -> Node f a
forall a b. (a -> b) -> Node f a -> Node f b
forall (f :: * -> *) a b. Functor f => a -> Node f b -> Node f a
forall (f :: * -> *) a b.
Functor f =>
(a -> b) -> Node f a -> Node f b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Node f b -> Node f a
$c<$ :: forall (f :: * -> *) a b. Functor f => a -> Node f b -> Node f a
fmap :: (a -> b) -> Node f a -> Node f b
$cfmap :: forall (f :: * -> *) a b.
Functor f =>
(a -> b) -> Node f a -> Node f b
Functor, Functor (Node f)
Foldable (Node f)
Functor (Node f)
-> Foldable (Node f)
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> Node f a -> f (Node f b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Node f (f a) -> f (Node f a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Node f a -> m (Node f b))
-> (forall (m :: * -> *) a.
    Monad m =>
    Node f (m a) -> m (Node f a))
-> Traversable (Node f)
(a -> f b) -> Node f a -> f (Node f b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (f :: * -> *). Traversable f => Functor (Node f)
forall (f :: * -> *). Traversable f => Foldable (Node f)
forall (f :: * -> *) (m :: * -> *) a.
(Traversable f, Monad m) =>
Node f (m a) -> m (Node f a)
forall (f :: * -> *) (f :: * -> *) a.
(Traversable f, Applicative f) =>
Node f (f a) -> f (Node f a)
forall (f :: * -> *) (m :: * -> *) a b.
(Traversable f, Monad m) =>
(a -> m b) -> Node f a -> m (Node f b)
forall (f :: * -> *) (f :: * -> *) a b.
(Traversable f, Applicative f) =>
(a -> f b) -> Node f a -> f (Node f b)
forall (m :: * -> *) a. Monad m => Node f (m a) -> m (Node f a)
forall (f :: * -> *) a.
Applicative f =>
Node f (f a) -> f (Node f a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Node f a -> m (Node f b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Node f a -> f (Node f b)
sequence :: Node f (m a) -> m (Node f a)
$csequence :: forall (f :: * -> *) (m :: * -> *) a.
(Traversable f, Monad m) =>
Node f (m a) -> m (Node f a)
mapM :: (a -> m b) -> Node f a -> m (Node f b)
$cmapM :: forall (f :: * -> *) (m :: * -> *) a b.
(Traversable f, Monad m) =>
(a -> m b) -> Node f a -> m (Node f b)
sequenceA :: Node f (f a) -> f (Node f a)
$csequenceA :: forall (f :: * -> *) (f :: * -> *) a.
(Traversable f, Applicative f) =>
Node f (f a) -> f (Node f a)
traverse :: (a -> f b) -> Node f a -> f (Node f b)
$ctraverse :: forall (f :: * -> *) (f :: * -> *) a b.
(Traversable f, Applicative f) =>
(a -> f b) -> Node f a -> f (Node f b)
$cp2Traversable :: forall (f :: * -> *). Traversable f => Foldable (Node f)
$cp1Traversable :: forall (f :: * -> *). Traversable f => Functor (Node f)
I.Traversable)

-- | Direction in 'Node'.
data Dir a = L a | R a
  deriving (Dir a -> Dir a -> Bool
(Dir a -> Dir a -> Bool) -> (Dir a -> Dir a -> Bool) -> Eq (Dir a)
forall a. Eq a => Dir a -> Dir a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Dir a -> Dir a -> Bool
$c/= :: forall a. Eq a => Dir a -> Dir a -> Bool
== :: Dir a -> Dir a -> Bool
$c== :: forall a. Eq a => Dir a -> Dir a -> Bool
Eq, Eq (Dir a)
Eq (Dir a)
-> (Dir a -> Dir a -> Ordering)
-> (Dir a -> Dir a -> Bool)
-> (Dir a -> Dir a -> Bool)
-> (Dir a -> Dir a -> Bool)
-> (Dir a -> Dir a -> Bool)
-> (Dir a -> Dir a -> Dir a)
-> (Dir a -> Dir a -> Dir a)
-> Ord (Dir a)
Dir a -> Dir a -> Bool
Dir a -> Dir a -> Ordering
Dir a -> Dir a -> Dir a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (Dir a)
forall a. Ord a => Dir a -> Dir a -> Bool
forall a. Ord a => Dir a -> Dir a -> Ordering
forall a. Ord a => Dir a -> Dir a -> Dir a
min :: Dir a -> Dir a -> Dir a
$cmin :: forall a. Ord a => Dir a -> Dir a -> Dir a
max :: Dir a -> Dir a -> Dir a
$cmax :: forall a. Ord a => Dir a -> Dir a -> Dir a
>= :: Dir a -> Dir a -> Bool
$c>= :: forall a. Ord a => Dir a -> Dir a -> Bool
> :: Dir a -> Dir a -> Bool
$c> :: forall a. Ord a => Dir a -> Dir a -> Bool
<= :: Dir a -> Dir a -> Bool
$c<= :: forall a. Ord a => Dir a -> Dir a -> Bool
< :: Dir a -> Dir a -> Bool
$c< :: forall a. Ord a => Dir a -> Dir a -> Bool
compare :: Dir a -> Dir a -> Ordering
$ccompare :: forall a. Ord a => Dir a -> Dir a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (Dir a)
Ord, Int -> Dir a -> ShowS
[Dir a] -> ShowS
Dir a -> String
(Int -> Dir a -> ShowS)
-> (Dir a -> String) -> ([Dir a] -> ShowS) -> Show (Dir a)
forall a. Show a => Int -> Dir a -> ShowS
forall a. Show a => [Dir a] -> ShowS
forall a. Show a => Dir a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Dir a] -> ShowS
$cshowList :: forall a. Show a => [Dir a] -> ShowS
show :: Dir a -> String
$cshow :: forall a. Show a => Dir a -> String
showsPrec :: Int -> Dir a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Dir a -> ShowS
Show, a -> Dir b -> Dir a
(a -> b) -> Dir a -> Dir b
(forall a b. (a -> b) -> Dir a -> Dir b)
-> (forall a b. a -> Dir b -> Dir a) -> Functor Dir
forall a b. a -> Dir b -> Dir a
forall a b. (a -> b) -> Dir a -> Dir b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Dir b -> Dir a
$c<$ :: forall a b. a -> Dir b -> Dir a
fmap :: (a -> b) -> Dir a -> Dir b
$cfmap :: forall a b. (a -> b) -> Dir a -> Dir b
Functor, Dir a -> Bool
(a -> m) -> Dir a -> m
(a -> b -> b) -> b -> Dir a -> b
(forall m. Monoid m => Dir m -> m)
-> (forall m a. Monoid m => (a -> m) -> Dir a -> m)
-> (forall m a. Monoid m => (a -> m) -> Dir a -> m)
-> (forall a b. (a -> b -> b) -> b -> Dir a -> b)
-> (forall a b. (a -> b -> b) -> b -> Dir a -> b)
-> (forall b a. (b -> a -> b) -> b -> Dir a -> b)
-> (forall b a. (b -> a -> b) -> b -> Dir a -> b)
-> (forall a. (a -> a -> a) -> Dir a -> a)
-> (forall a. (a -> a -> a) -> Dir a -> a)
-> (forall a. Dir a -> [a])
-> (forall a. Dir a -> Bool)
-> (forall a. Dir a -> Int)
-> (forall a. Eq a => a -> Dir a -> Bool)
-> (forall a. Ord a => Dir a -> a)
-> (forall a. Ord a => Dir a -> a)
-> (forall a. Num a => Dir a -> a)
-> (forall a. Num a => Dir a -> a)
-> Foldable Dir
forall a. Eq a => a -> Dir a -> Bool
forall a. Num a => Dir a -> a
forall a. Ord a => Dir a -> a
forall m. Monoid m => Dir m -> m
forall a. Dir a -> Bool
forall a. Dir a -> Int
forall a. Dir a -> [a]
forall a. (a -> a -> a) -> Dir a -> a
forall m a. Monoid m => (a -> m) -> Dir a -> m
forall b a. (b -> a -> b) -> b -> Dir a -> b
forall a b. (a -> b -> b) -> b -> Dir a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Dir a -> a
$cproduct :: forall a. Num a => Dir a -> a
sum :: Dir a -> a
$csum :: forall a. Num a => Dir a -> a
minimum :: Dir a -> a
$cminimum :: forall a. Ord a => Dir a -> a
maximum :: Dir a -> a
$cmaximum :: forall a. Ord a => Dir a -> a
elem :: a -> Dir a -> Bool
$celem :: forall a. Eq a => a -> Dir a -> Bool
length :: Dir a -> Int
$clength :: forall a. Dir a -> Int
null :: Dir a -> Bool
$cnull :: forall a. Dir a -> Bool
toList :: Dir a -> [a]
$ctoList :: forall a. Dir a -> [a]
foldl1 :: (a -> a -> a) -> Dir a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Dir a -> a
foldr1 :: (a -> a -> a) -> Dir a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Dir a -> a
foldl' :: (b -> a -> b) -> b -> Dir a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Dir a -> b
foldl :: (b -> a -> b) -> b -> Dir a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Dir a -> b
foldr' :: (a -> b -> b) -> b -> Dir a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Dir a -> b
foldr :: (a -> b -> b) -> b -> Dir a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Dir a -> b
foldMap' :: (a -> m) -> Dir a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Dir a -> m
foldMap :: (a -> m) -> Dir a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Dir a -> m
fold :: Dir m -> m
$cfold :: forall m. Monoid m => Dir m -> m
I.Foldable, Functor Dir
Foldable Dir
Functor Dir
-> Foldable Dir
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> Dir a -> f (Dir b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Dir (f a) -> f (Dir a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Dir a -> m (Dir b))
-> (forall (m :: * -> *) a. Monad m => Dir (m a) -> m (Dir a))
-> Traversable Dir
(a -> f b) -> Dir a -> f (Dir b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Dir (m a) -> m (Dir a)
forall (f :: * -> *) a. Applicative f => Dir (f a) -> f (Dir a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Dir a -> m (Dir b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Dir a -> f (Dir b)
sequence :: Dir (m a) -> m (Dir a)
$csequence :: forall (m :: * -> *) a. Monad m => Dir (m a) -> m (Dir a)
mapM :: (a -> m b) -> Dir a -> m (Dir b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Dir a -> m (Dir b)
sequenceA :: Dir (f a) -> f (Dir a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Dir (f a) -> f (Dir a)
traverse :: (a -> f b) -> Dir a -> f (Dir b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Dir a -> f (Dir b)
$cp2Traversable :: Foldable Dir
$cp1Traversable :: Functor Dir
I.Traversable)

-------------------------------------------------------------------------------
-- Instances
-------------------------------------------------------------------------------

-- These instances are manually implemented, because we can have efficient
-- foldr and foldl
instance I.Foldable Leaf where
    foldMap :: (a -> m) -> Leaf a -> m
foldMap a -> m
f (Lf a
x) = a -> m
f a
x
    foldr :: (a -> b -> b) -> b -> Leaf a -> b
foldr a -> b -> b
f b
z (Lf a
x) = a -> b -> b
f a
x b
z
    foldl :: (b -> a -> b) -> b -> Leaf a -> b
foldl b -> a -> b
f b
z (Lf a
x) = b -> a -> b
f b
z a
x
    foldr' :: (a -> b -> b) -> b -> Leaf a -> b
foldr' a -> b -> b
f b
z (Lf a
x) = a -> b -> b
f a
x b
z
    foldl' :: (b -> a -> b) -> b -> Leaf a -> b
foldl' b -> a -> b
f b
z (Lf a
x) = b -> a -> b
f b
z a
x

#if MIN_VERSION_base(4,8,0)
    length :: Leaf a -> Int
length Leaf a
_ = Int
1
    null :: Leaf a -> Bool
null Leaf a
_ = Bool
False
#endif

instance I.Foldable f => I.Foldable (Node f) where
    foldMap :: (a -> m) -> Node f a -> m
foldMap a -> m
f (Nd f a
x f a
y) = m -> m -> m
forall a. Monoid a => a -> a -> a
mappend ((a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
I.foldMap a -> m
f f a
x) ((a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
I.foldMap a -> m
f f a
y)

    foldr :: (a -> b -> b) -> b -> Node f a -> b
foldr a -> b -> b
f b
z (Nd f a
x f a
y) = (a -> b -> b) -> b -> f a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
I.foldr a -> b -> b
f ((a -> b -> b) -> b -> f a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
I.foldr a -> b -> b
f b
z f a
y) f a
x
    foldl :: (b -> a -> b) -> b -> Node f a -> b
foldl b -> a -> b
f b
z (Nd f a
x f a
y) = (b -> a -> b) -> b -> f a -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
I.foldl b -> a -> b
f ((b -> a -> b) -> b -> f a -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
I.foldl b -> a -> b
f b
z f a
x) f a
y

    foldr' :: (a -> b -> b) -> b -> Node f a -> b
foldr' a -> b -> b
f b
z (Nd f a
x f a
y) = let !acc :: b
acc = (a -> b -> b) -> b -> f a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
I.foldr' a -> b -> b
f b
z f a
y in (a -> b -> b) -> b -> f a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
I.foldr' a -> b -> b
f b
acc f a
x
    foldl' :: (b -> a -> b) -> b -> Node f a -> b
foldl' b -> a -> b
f b
z (Nd f a
x f a
y) = let !acc :: b
acc = (b -> a -> b) -> b -> f a -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
I.foldl' b -> a -> b
f b
z f a
x in (b -> a -> b) -> b -> f a -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
I.foldl' b -> a -> b
f b
acc f a
y

#if MIN_VERSION_base(4,8,0)
    length :: Node f a -> Int
length (Nd f a
x f a
y) = f a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
I.length f a
x Int -> Int -> Int
forall a. Num a => a -> a -> a
+ f a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
I.length f a
y
    null :: Node f a -> Bool
null (Nd f a
x f a
y)   = f a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
I.null f a
x Bool -> Bool -> Bool
&& f a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
I.null f a
y
#endif

#ifdef MIN_VERSION_semigroupoids
instance I.Foldable1 Leaf where
    foldMap1 :: (a -> m) -> Leaf a -> m
foldMap1 a -> m
f (Lf a
x) = a -> m
f a
x

instance I.Traversable1 Leaf where
    traverse1 :: (a -> f b) -> Leaf a -> f (Leaf b)
traverse1 a -> f b
f (Lf a
x) = b -> Leaf b
forall a. a -> Leaf a
Lf (b -> Leaf b) -> f b -> f (Leaf b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
x

instance I.Foldable1 f => I.Foldable1 (Node f) where
    foldMap1 :: (a -> m) -> Node f a -> m
foldMap1 a -> m
f (Nd f a
x f a
y) = (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable1 t, Semigroup m) =>
(a -> m) -> t a -> m
I.foldMap1 a -> m
f f a
x m -> m -> m
forall a. Semigroup a => a -> a -> a
<> (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable1 t, Semigroup m) =>
(a -> m) -> t a -> m
I.foldMap1 a -> m
f f a
y

instance I.Traversable1 f => I.Traversable1 (Node f) where
    traverse1 :: (a -> f b) -> Node f a -> f (Node f b)
traverse1 a -> f b
f (Nd f a
x f a
y) = f b -> f b -> Node f b
forall (f :: * -> *) a. f a -> f a -> Node f a
Nd (f b -> f b -> Node f b) -> f (f b) -> f (f b -> Node f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable1 t, Apply f) =>
(a -> f b) -> t a -> f (t b)
I.traverse1 a -> f b
f f a
x f (f b -> Node f b) -> f (f b) -> f (Node f b)
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> (a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable1 t, Apply f) =>
(a -> f b) -> t a -> f (t b)
I.traverse1 a -> f b
f f a
y
#endif

instance NFData a => NFData (Leaf a) where
    rnf :: Leaf a -> ()
rnf (Lf a
a) = a -> ()
forall a. NFData a => a -> ()
rnf a
a

instance NFData (f a) => NFData (Node f a) where
    rnf :: Node f a -> ()
rnf (Nd f a
x f a
y) = f a -> ()
forall a. NFData a => a -> ()
rnf f a
x () -> () -> ()
`seq` f a -> ()
forall a. NFData a => a -> ()
rnf f a
y

instance Hashable a => Hashable (Leaf a) where
    hashWithSalt :: Int -> Leaf a -> Int
hashWithSalt Int
salt (Lf a
x) = Int -> a -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt a
x

instance Hashable (f a) => Hashable (Node f a)  where
    hashWithSalt :: Int -> Node f a -> Int
hashWithSalt Int
salt (Nd f a
x f a
y) = Int
salt
        Int -> f a -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` f a
x
        Int -> f a -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` f a
y

#ifdef MIN_VERSION_distributive
instance I.Distributive Leaf where
    distribute :: f (Leaf a) -> Leaf (f a)
distribute f (Leaf a)
xs = f a -> Leaf (f a)
forall a. a -> Leaf a
Lf ((Leaf a -> a) -> f (Leaf a) -> f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Lf a
x) -> a
x) f (Leaf a)
xs)

instance I.Distributive f => I.Distributive (Node f) where
    distribute :: f (Node f a) -> Node f (f a)
distribute f (Node f a)
xs = f (f a) -> f (f a) -> Node f (f a)
forall (f :: * -> *) a. f a -> f a -> Node f a
Nd
        (f (f a) -> f (f a)
forall (g :: * -> *) (f :: * -> *) a.
(Distributive g, Functor f) =>
f (g a) -> g (f a)
I.distribute ((Node f a -> f a) -> f (Node f a) -> f (f a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Nd f a
x f a
_) -> f a
x) f (Node f a)
xs))
        (f (f a) -> f (f a)
forall (g :: * -> *) (f :: * -> *) a.
(Distributive g, Functor f) =>
f (g a) -> g (f a)
I.distribute ((Node f a -> f a) -> f (Node f a) -> f (f a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Nd f a
_ f a
y) -> f a
y) f (Node f a)
xs))

#ifdef MIN_VERSION_adjunctions
instance I.Representable Leaf where
    type Rep Leaf = ()
    index :: Leaf a -> Rep Leaf -> a
index (Lf a
x) Rep Leaf
_ = a
x
    tabulate :: (Rep Leaf -> a) -> Leaf a
tabulate Rep Leaf -> a
f     = a -> Leaf a
forall a. a -> Leaf a
Lf (Rep Leaf -> a
f ())

instance I.Representable f => I.Representable (Node f) where
    type Rep (Node f) = Dir (I.Rep f)

    index :: Node f a -> Rep (Node f) -> a
index (Nd f a
x f a
_) (L i) = f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
I.index f a
x Rep f
i
    index (Nd f a
_ f a
y) (R j) = f a -> Rep f -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
I.index f a
y Rep f
j

    tabulate :: (Rep (Node f) -> a) -> Node f a
tabulate Rep (Node f) -> a
f = f a -> f a -> Node f a
forall (f :: * -> *) a. f a -> f a -> Node f a
Nd ((Rep f -> a) -> f a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
I.tabulate (Rep (Node f) -> a
Dir (Rep f) -> a
f (Dir (Rep f) -> a) -> (Rep f -> Dir (Rep f)) -> Rep f -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rep f -> Dir (Rep f)
forall a. a -> Dir a
L)) ((Rep f -> a) -> f a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
I.tabulate (Rep (Node f) -> a
Dir (Rep f) -> a
f (Dir (Rep f) -> a) -> (Rep f -> Dir (Rep f)) -> Rep f -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rep f -> Dir (Rep f)
forall a. a -> Dir a
R))
#endif
#endif

-------------------------------------------------------------------------------
-- IsLeaf
-------------------------------------------------------------------------------

-- | Size of a tree.
type Size = Int
type Offset = Int

class (
#ifdef MIN_VERSION_semigroupoids
    I.Traversable1 t
#else
    I.Traversable t
#endif
    ) => IsTree t where
    -- indexing
    safeIndex :: Size -> t a -> Int -> Maybe a

    head :: t a -> a
    last :: t a -> a

    -- folding

    ifoldr :: Offset -> Size
           -> (Int -> a -> b -> b) -> b -> t a -> b

    ifoldMap1 :: Semigroup s => Offset -> Size
              -> (Int -> a -> s) -> t a -> s

    foldr1Map  :: (        a -> b -> b) -> (a -> b) -> t a -> b
    ifoldr1Map :: Offset -> Size
               -> (Int ->  a -> b -> b) -> (Int -> a -> b) -> t a -> b

    -- mapping

    adjust :: Size -> Int -> (a -> a) -> t a -> t a

    itraverse
        :: Applicative f
        => Offset
        -> Size
        -> (Int -> a -> f b) -> t a -> f (t b)

#ifdef MIN_VERSION_semigroupoids
    traverse1  :: Apply f => (a -> f b) -> t a -> f (t b)
    itraverse1 :: Apply f => Offset -> Size -> (Int -> a -> f b) -> t a -> f (t b)
#endif

-------------------------------------------------------------------------------
-- IsTree Leaf
-------------------------------------------------------------------------------

instance IsTree Leaf where
    -- indexing
    safeIndex :: Int -> Leaf a -> Int -> Maybe a
safeIndex Int
_ (Lf a
x) Int
0 = a -> Maybe a
forall a. a -> Maybe a
Just a
x
    safeIndex  Int
_ Leaf a
_     Int
_ = Maybe a
forall a. Maybe a
Nothing

    head :: Leaf a -> a
head (Lf a
x) = a
x
    last :: Leaf a -> a
last = Leaf a -> a
forall (t :: * -> *) a. IsTree t => t a -> a
head


    -- folding
    foldr1Map :: (a -> b -> b) -> (a -> b) -> Leaf a -> b
foldr1Map       a -> b -> b
_ a -> b
z (Lf a
x) = a -> b
z a
x

    ifoldr :: Int -> Int -> (Int -> a -> b -> b) -> b -> Leaf a -> b
ifoldr     !Int
o Int
_ Int -> a -> b -> b
f b
z (Lf a
x) = Int -> a -> b -> b
f Int
o a
x b
z
    ifoldMap1 :: Int -> Int -> (Int -> a -> s) -> Leaf a -> s
ifoldMap1  !Int
o Int
_ Int -> a -> s
f   (Lf a
x) = Int -> a -> s
f Int
o a
x
    ifoldr1Map :: Int
-> Int -> (Int -> a -> b -> b) -> (Int -> a -> b) -> Leaf a -> b
ifoldr1Map !Int
o Int
_ Int -> a -> b -> b
_ Int -> a -> b
z (Lf a
x) = Int -> a -> b
z Int
o a
x

    -- mapping
    adjust :: Int -> Int -> (a -> a) -> Leaf a -> Leaf a
adjust Int
_ !Int
i a -> a
f (Lf a
x)
        | Int
0 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
i    = a -> Leaf a
forall a. a -> Leaf a
Lf (a -> a
f a
x)
        | Bool
otherwise = a -> Leaf a
forall a. a -> Leaf a
Lf a
x

    itraverse :: Int -> Int -> (Int -> a -> f b) -> Leaf a -> f (Leaf b)
itraverse !Int
o Int
_ Int -> a -> f b
f (Lf a
x) = (b -> Leaf b) -> f b -> f (Leaf b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap b -> Leaf b
forall a. a -> Leaf a
Lf (Int -> a -> f b
f Int
o a
x)

#ifdef MIN_VERSION_semigroupoids
    traverse1 :: (a -> f b) -> Leaf a -> f (Leaf b)
traverse1       a -> f b
f (Lf a
x) = (b -> Leaf b) -> f b -> f (Leaf b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap b -> Leaf b
forall a. a -> Leaf a
Lf (a -> f b
f a
x)
    itraverse1 :: Int -> Int -> (Int -> a -> f b) -> Leaf a -> f (Leaf b)
itraverse1 !Int
o Int
_ Int -> a -> f b
f (Lf a
x) = (b -> Leaf b) -> f b -> f (Leaf b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap b -> Leaf b
forall a. a -> Leaf a
Lf (Int -> a -> f b
f Int
o a
x)
#endif

-------------------------------------------------------------------------------
-- IsTree Node
-------------------------------------------------------------------------------

instance IsTree f => IsTree (Node f) where
    -- indexing

    safeIndex :: Int -> Node f a -> Int -> Maybe a
safeIndex Int
s (Nd f a
x f a
y) Int
i
        | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
s2    = Int -> f a -> Int -> Maybe a
forall (t :: * -> *) a. IsTree t => Int -> t a -> Int -> Maybe a
safeIndex Int
s2 f a
x Int
i
        | Bool
otherwise = Int -> f a -> Int -> Maybe a
forall (t :: * -> *) a. IsTree t => Int -> t a -> Int -> Maybe a
safeIndex Int
s2 f a
y (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
s2)
      where
        s2 :: Int
s2 = Int
s Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2

    head :: Node f a -> a
head (Nd f a
x f a
_) = f a -> a
forall (t :: * -> *) a. IsTree t => t a -> a
head f a
x
    last :: Node f a -> a
last (Nd f a
_ f a
y) = f a -> a
forall (t :: * -> *) a. IsTree t => t a -> a
last f a
y

    -- folding

    foldr1Map :: (a -> b -> b) -> (a -> b) -> Node f a -> b
foldr1Map a -> b -> b
f a -> b
z (Nd f a
x f a
y) = (a -> b -> b) -> b -> f a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
I.foldr a -> b -> b
f ((a -> b -> b) -> (a -> b) -> f a -> b
forall (t :: * -> *) a b.
IsTree t =>
(a -> b -> b) -> (a -> b) -> t a -> b
foldr1Map a -> b -> b
f a -> b
z f a
y) f a
x

    ifoldr1Map :: Int
-> Int -> (Int -> a -> b -> b) -> (Int -> a -> b) -> Node f a -> b
ifoldr1Map !Int
o !Int
s Int -> a -> b -> b
f Int -> a -> b
z (Nd f a
x f a
y) = Int -> Int -> (Int -> a -> b -> b) -> b -> f a -> b
forall (t :: * -> *) a b.
IsTree t =>
Int -> Int -> (Int -> a -> b -> b) -> b -> t a -> b
ifoldr Int
o Int
s2 Int -> a -> b -> b
f (Int -> Int -> (Int -> a -> b -> b) -> (Int -> a -> b) -> f a -> b
forall (t :: * -> *) a b.
IsTree t =>
Int -> Int -> (Int -> a -> b -> b) -> (Int -> a -> b) -> t a -> b
ifoldr1Map (Int
o Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
s2) Int
s2 Int -> a -> b -> b
f Int -> a -> b
z f a
y) f a
x
      where
        s2 :: Int
s2 = Int
s Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2

    ifoldr :: Int -> Int -> (Int -> a -> b -> b) -> b -> Node f a -> b
ifoldr !Int
o !Int
s Int -> a -> b -> b
f b
z (Nd f a
x f a
y) = Int -> Int -> (Int -> a -> b -> b) -> b -> f a -> b
forall (t :: * -> *) a b.
IsTree t =>
Int -> Int -> (Int -> a -> b -> b) -> b -> t a -> b
ifoldr Int
o Int
s2 Int -> a -> b -> b
f (Int -> Int -> (Int -> a -> b -> b) -> b -> f a -> b
forall (t :: * -> *) a b.
IsTree t =>
Int -> Int -> (Int -> a -> b -> b) -> b -> t a -> b
ifoldr (Int
o Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
s2) Int
s2 Int -> a -> b -> b
f b
z f a
y) f a
x
      where
        s2 :: Int
s2 = Int
s Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2

    ifoldMap1 :: Int -> Int -> (Int -> a -> s) -> Node f a -> s
ifoldMap1 !Int
o !Int
s Int -> a -> s
f (Nd f a
x f a
y) = Int -> Int -> (Int -> a -> s) -> f a -> s
forall (t :: * -> *) s a.
(IsTree t, Semigroup s) =>
Int -> Int -> (Int -> a -> s) -> t a -> s
ifoldMap1 Int
o Int
s2 Int -> a -> s
f f a
x s -> s -> s
forall a. Semigroup a => a -> a -> a
<> Int -> Int -> (Int -> a -> s) -> f a -> s
forall (t :: * -> *) s a.
(IsTree t, Semigroup s) =>
Int -> Int -> (Int -> a -> s) -> t a -> s
ifoldMap1 (Int
o Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
s2) Int
s2 Int -> a -> s
f f a
y
      where
        s2 :: Int
s2 = Int
s Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2

    -- mapping

    adjust :: Int -> Int -> (a -> a) -> Node f a -> Node f a
adjust Int
s Int
i a -> a
f nd :: Node f a
nd@(Nd f a
x f a
y)
        | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
s2    = f a -> f a -> Node f a
forall (f :: * -> *) a. f a -> f a -> Node f a
Nd (Int -> Int -> (a -> a) -> f a -> f a
forall (t :: * -> *) a.
IsTree t =>
Int -> Int -> (a -> a) -> t a -> t a
adjust Int
s2 Int
i a -> a
f f a
x) f a
y
        | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
s     = f a -> f a -> Node f a
forall (f :: * -> *) a. f a -> f a -> Node f a
Nd f a
x (Int -> Int -> (a -> a) -> f a -> f a
forall (t :: * -> *) a.
IsTree t =>
Int -> Int -> (a -> a) -> t a -> t a
adjust Int
s2 (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
s2) a -> a
f f a
y)
        | Bool
otherwise = Node f a
nd
      where
        s2 :: Int
s2 = Int
s Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2

    itraverse :: Int -> Int -> (Int -> a -> f b) -> Node f a -> f (Node f b)
itraverse !Int
o !Int
s Int -> a -> f b
f (Nd f a
x f a
y) = f b -> f b -> Node f b
forall (f :: * -> *) a. f a -> f a -> Node f a
Nd
        (f b -> f b -> Node f b) -> f (f b) -> f (f b -> Node f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Int -> (Int -> a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(IsTree t, Applicative f) =>
Int -> Int -> (Int -> a -> f b) -> t a -> f (t b)
itraverse Int
o        Int
s2 Int -> a -> f b
f f a
x
        f (f b -> Node f b) -> f (f b) -> f (Node f b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Int -> (Int -> a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(IsTree t, Applicative f) =>
Int -> Int -> (Int -> a -> f b) -> t a -> f (t b)
itraverse (Int
o Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
s2) Int
s2 Int -> a -> f b
f f a
y
      where
        s2 :: Int
s2 = Int
s Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2

#ifdef MIN_VERSION_semigroupoids
    traverse1 :: (a -> f b) -> Node f a -> f (Node f b)
traverse1 a -> f b
f (Nd f a
x f a
y) = f b -> f b -> Node f b
forall (f :: * -> *) a. f a -> f a -> Node f a
Nd (f b -> f b -> Node f b) -> f (f b) -> f (f b -> Node f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(IsTree t, Apply f) =>
(a -> f b) -> t a -> f (t b)
traverse1 a -> f b
f f a
x f (f b -> Node f b) -> f (f b) -> f (Node f b)
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> (a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(IsTree t, Apply f) =>
(a -> f b) -> t a -> f (t b)
traverse1 a -> f b
f f a
y

    itraverse1 :: Int -> Int -> (Int -> a -> f b) -> Node f a -> f (Node f b)
itraverse1 !Int
o !Int
s Int -> a -> f b
f (Nd f a
x f a
y) = f b -> f b -> Node f b
forall (f :: * -> *) a. f a -> f a -> Node f a
Nd
        (f b -> f b -> Node f b) -> f (f b) -> f (f b -> Node f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Int -> (Int -> a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(IsTree t, Apply f) =>
Int -> Int -> (Int -> a -> f b) -> t a -> f (t b)
itraverse1 Int
o        Int
s2 Int -> a -> f b
f f a
x
        f (f b -> Node f b) -> f (f b) -> f (Node f b)
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> Int -> Int -> (Int -> a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(IsTree t, Apply f) =>
Int -> Int -> (Int -> a -> f b) -> t a -> f (t b)
itraverse1 (Int
o Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
s2) Int
s2 Int -> a -> f b
f f a
y
      where
        s2 :: Int
s2 = Int
s Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2
#endif