-- ------------------------------------------------------------

{- |
   Module     : Data.Tree.Class
   Copyright  : Copyright (C) 2005 Uwe Schmidt
   License    : MIT

   Maintainer : Uwe Schmidt (uwe\@fh-wedel.de)
   Stability  : experimental
   Portability: portable

   Interface definition for trees
-}

-- ------------------------------------------------------------

module Data.Tree.Class
    ( module Data.Tree.Class )
where

-- | The interface for trees

class Tree t where
    -- | tree construction: a new tree is constructed by a node attribute and a list of children
    mkTree              ::              a -> [t a] -> t a

    -- | leaf construction: leafs don't have any children
    --
    -- definition: @ mkLeaf n = mkTree n [] @

    mkLeaf              ::                       a -> t a
    mkLeaf a
n            = a -> [t a] -> t a
forall (t :: * -> *) a. Tree t => a -> [t a] -> t a
mkTree a
n []
    {-# INLINE mkLeaf #-}

    -- | leaf test: list of children empty?

    isLeaf              ::                     t a -> Bool
    isLeaf              = [t a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([t a] -> Bool) -> (t a -> [t a]) -> t a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t a -> [t a]
forall (t :: * -> *) a. Tree t => t a -> [t a]
getChildren
    {-# INLINE isLeaf #-}

    -- | innner node test: @ not . isLeaf @

    isInner             ::                     t a -> Bool
    isInner             = Bool -> Bool
not (Bool -> Bool) -> (t a -> Bool) -> t a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t a -> Bool
forall (t :: * -> *) a. Tree t => t a -> Bool
isLeaf
    {-# INLINE isInner #-}

    -- | select node attribute

    getNode             ::                     t a -> a

    -- | select children

    getChildren         ::                     t a -> [t a]

    -- | edit node attribute

    changeNode          ::         (a -> a) -> t a -> t a

    -- | edit children

    changeChildren      :: ([t a] -> [t a]) -> t a -> t a

    -- | substitute node: @ setNode n = changeNode (const n) @

    setNode             ::                a -> t a -> t a
    setNode a
n           = (a -> a) -> t a -> t a
forall (t :: * -> *) a. Tree t => (a -> a) -> t a -> t a
changeNode (a -> a -> a
forall a b. a -> b -> a
const a
n)
    {-# INLINE setNode #-}

    -- | substitute children: @ setChildren cl = changeChildren (const cl) @

    setChildren         ::            [t a] -> t a -> t a
    setChildren [t a]
cl      = ([t a] -> [t a]) -> t a -> t a
forall (t :: * -> *) a. Tree t => ([t a] -> [t a]) -> t a -> t a
changeChildren ([t a] -> [t a] -> [t a]
forall a b. a -> b -> a
const [t a]
cl)
    {-# INLINE setChildren #-}

    -- | fold for trees

    foldTree            ::  (a -> [b] -> b) -> t a -> b

    -- | all nodes of a tree

    nodesTree           ::                     t a -> [a]
    nodesTree           = (a -> [[a]] -> [a]) -> t a -> [a]
forall (t :: * -> *) a b. Tree t => (a -> [b] -> b) -> t a -> b
foldTree (\ a
n [[a]]
rs -> a
n a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [[a]] -> [a]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[a]]
rs)
    {-# INLINE nodesTree #-}

    -- | depth of a tree

    depthTree           ::                     t a -> Int
    depthTree           = (a -> [Int] -> Int) -> t a -> Int
forall (t :: * -> *) a b. Tree t => (a -> [b] -> b) -> t a -> b
foldTree (\ a
_ [Int]
rs -> Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum (Int
0 Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: [Int]
rs))

    -- | number of nodes in a tree

    cardTree            ::                     t a -> Int
    cardTree            = (a -> [Int] -> Int) -> t a -> Int
forall (t :: * -> *) a b. Tree t => (a -> [b] -> b) -> t a -> b
foldTree (\ a
_ [Int]
rs -> Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Int]
rs)

    -- | format tree for readable trace output
    --
    -- a /graphical/ representation of the tree in text format

    formatTree          ::    (a -> String) -> t a -> String
    formatTree a -> String
nf t a
n     = (a -> String)
-> (String -> String)
-> (String -> String)
-> t a
-> String
-> String
forall (t :: * -> *) a.
Tree t =>
(a -> String)
-> (String -> String)
-> (String -> String)
-> t a
-> String
-> String
formatNTree' a -> String
nf (String -> String -> String
showString String
"---") (String -> String -> String
showString String
"   ") t a
n String
""

-- ------------------------------------------------------------
-- |
-- convert a tree into a pseudo graphical string representation

formatNTree'    :: Tree t => (a -> String) -> (String -> String) -> (String -> String) -> t a -> String -> String

formatNTree' :: (a -> String)
-> (String -> String)
-> (String -> String)
-> t a
-> String
-> String
formatNTree' a -> String
node2String String -> String
pf1 String -> String
pf2 t a
tree
    = String -> String
formatNode
      (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> String) -> [t a] -> String -> String
forall (t :: * -> *).
Tree t =>
(String -> String) -> [t a] -> String -> String
formatChildren String -> String
pf2 [t a]
l
    where
    n :: a
n           = t a -> a
forall (t :: * -> *) a. Tree t => t a -> a
getNode     t a
tree
    l :: [t a]
l           = t a -> [t a]
forall (t :: * -> *) a. Tree t => t a -> [t a]
getChildren t a
tree
    formatNode :: String -> String
formatNode  = String -> String
pf1 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((String -> String) -> (String -> String) -> String -> String)
-> (String -> String) -> [String -> String] -> String -> String
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) String -> String
forall a. a -> a
id ((Char -> String -> String) -> String -> [String -> String]
forall a b. (a -> b) -> [a] -> [b]
map Char -> String -> String
trNL (a -> String
node2String a
n)) (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
showNL
    trNL :: Char -> String -> String
trNL Char
'\n'   = String -> String
showNL (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
pf2
    trNL Char
c      = Char -> String -> String
showChar Char
c
    showNL :: String -> String
showNL      = Char -> String -> String
showChar Char
'\n'
    formatChildren :: (String -> String) -> [t a] -> String -> String
formatChildren String -> String
_ []
        = String -> String
forall a. a -> a
id
    formatChildren String -> String
pf (t a
t:[t a]
ts)
        | [t a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [t a]
ts
            = String -> String
pfl'
              (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> String) -> t a -> String -> String
formatTr String -> String
pf2' t a
t
        | Bool
otherwise
            = String -> String
pfl'
              (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> String) -> t a -> String -> String
formatTr String -> String
pf1' t a
t
              (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> String) -> [t a] -> String -> String
formatChildren String -> String
pf [t a]
ts
        where
        pf0' :: String -> String
pf0'    = String -> String
pf (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> String
showString String
indent1
        pf1' :: String -> String
pf1'    = String -> String
pf (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> String
showString String
indent2
        pf2' :: String -> String
pf2'    = String -> String
pf (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> String
showString String
indent3
        pfl' :: String -> String
pfl'    = String -> String
pf (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> String
showString String
indent4
        formatTr :: (String -> String) -> t a -> String -> String
formatTr        = (a -> String)
-> (String -> String)
-> (String -> String)
-> t a
-> String
-> String
forall (t :: * -> *) a.
Tree t =>
(a -> String)
-> (String -> String)
-> (String -> String)
-> t a
-> String
-> String
formatNTree' a -> String
node2String String -> String
pf0'
        indent1 :: String
indent1 = String
"+---"
        indent2 :: String
indent2 = String
"|   "
        indent3 :: String
indent3 = String
"    "
        indent4 :: String
indent4 = String
"|\n"

-- eof ------------------------------------------------------------