Skip to content

Instantly share code, notes, and snippets.

@jszmajda
Created June 9, 2017 03:27
Show Gist options
  • Star 1 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save jszmajda/b333784274010e631120b50f276b6a43 to your computer and use it in GitHub Desktop.
Save jszmajda/b333784274010e631120b50f276b6a43 to your computer and use it in GitHub Desktop.
module Y2017.M06.D07.Exercise where
import qualified Data.List as L
{--
So, here's one of the questions Amazon asks developers to test their under-
standing of data structures.
You have a binary tree of the following structure:
A
/ \
/ \
B C
/ \ / \
D E F G
1. create the BinaryTree type and materialize the above value.
--}
data Sym = A | B | C | D | E | F | G | H | I | J | K | L | M | N | O
deriving (Eq, Ord, Enum, Bounded, Show)
data Node a = Bin a (Node a) (Node a) | Leaf a
deriving (Eq, Show)
abcdefg :: Node Sym
abcdefg = Bin A ( Bin B (Leaf D) (Leaf E) ) ( Bin C (Leaf F) (Leaf G) )
{--
Now, you want to traverse the external nodes in a clockwise direction. For the
above binary tree, a clockwise Edge Node traversal will return:
--}
clockwiseSmallTree :: [Sym]
clockwiseSmallTree = [A, C, G, F, E, D, B]
-- define
data Dir = Lef | Rig deriving (Show, Eq)
descend :: [Dir] -> Node a -> [a]
descend _ (Leaf v) = [v]
descend hist (Bin v l r) =
case lastDir of
Rig -> meIfAllSameDescent ++ lrd
Lef -> lrd ++ meIfAllSameDescent
where
lastDir = head hist
meIfAllSameDescent = if (L.all (== lastDir) hist) then [v] else []
lrd = (descend (Rig : hist) r) ++ (descend (Lef : hist) l)
clockwiseEdgeTraversal :: Node a -> [a]
clockwiseEdgeTraversal (Leaf v) = [v]
clockwiseEdgeTraversal (Bin v l r) = [v] ++ (descend [Rig] r) ++ (descend [Lef] l)
{--
such that:
>>> clockwiseEdgeTraversal abcdefg == clockwiseSmallTree
True
--}
{-- BONUS -----------------------------------------------------------------
Simple enough, eh?
Now, does it work for the larger tree?
A
/ \
/ \
/ \
B C
/ \ / \
D E F G
/ \ / \ / \ / \
H I J K L M N O
--}
largerTree :: Node Sym
largerTree = Bin A
(Bin B
(Bin D (Leaf H) (Leaf I))
(Bin E (Leaf J) (Leaf K)))
(Bin C
(Bin F (Leaf L) (Leaf M))
(Bin G (Leaf N) (Leaf O)))
-- the EDGE clockwise traversal is thus:
largerClockwiseTraversal :: [Sym]
largerClockwiseTraversal = [A, C, G, O, N, M, L, K, J, I, H, D, B]
{--
n.b.: as E and F are internal nodes, not edge nodes, they are NOT part of
the traversal.
so:
>>> clockwiseEdgeTraversal largerTree == largerClockwiseTraversal
True
Got it?
--}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment