+reduceStep :: Term -> Term
+reduceStep (RedEx x s t) = substitute x t s
+reduceStep t = t
+
+data Z = R Term Z | L Z Term | ZL VarName Z | E
+data D = Up | Down
+type TermZipper = (Term, Z, D)
+
+move :: TermZipper -> TermZipper
+move (App l r, c, Down) = (l, L c r, Down)
+move (Lambda x t, c, Down) = (t, ZL x c, Down)
+move (Var x, c, Down) = (Var x, c, Up)
+move (t, L c r, Up) = (r, R t c, Down)
+move (t, R l c, Up) = (App l t, c, Up)
+move (t, ZL x c, Up) = (Lambda x t, c, Up)
+move (t, E, Up) = (t, E, Up)
+
+unmove :: TermZipper -> TermZipper
+unmove (t, L c r, Down) = (App t r, c, Down)
+unmove x = x
+
+-- getTerm :: TermZipper -> Term
+
+travPost :: (Monad m) => (Term -> m Term) -> Term -> m Term
+travPost fnc term = tr fnc (term, E, Down)
+ where
+ tr f (t@RedEx{}, c, Up) = do
+ nt <- f t
+ tr f (nt, c, Down)
+ tr _ (t, E, Up) = return t
+ tr f (t, c, Up) = tr f $ move (t, c, Up)
+ tr f (t, c, Down) = tr f $ move (t, c, Down)
+
+travPre :: (Monad m) => (Term -> m Term) -> Term -> m Term
+travPre fnc term = tr fnc (term, E, Down)
+ where
+ tr f (t@RedEx{}, c, Down) = do
+ nt <- f t
+ tr f $ unmove (nt, c, Down)
+ tr _ (t, E, Up) = return t
+ tr f (t, c, Up) = tr f $ move (t, c, Up)
+ tr f (t, c, Down) = tr f $ move (t, c, Down)
+
+-- |
+--
+-- >>> toNormalForm Eager 100 cI
+-- Just (λx.x)
+--
+-- >>> toNormalForm Eager 100 $ App cI cI
+-- Just (λx.x)
+--
+-- >>> toNormalForm Eager 100 $ (App (App cK cI) cY)
+-- Nothing
+--
+-- >>> toNormalForm Lazy 100 $ (App (App cK cI) cY)
+-- Just (λx.x)
+--
+-- prop> within 10000000 $ (\ t u -> t == u || t == Nothing || u == Nothing) (alphaNorm <$> toNormalForm Lazy 100 x) (alphaNorm <$> toNormalForm Eager 100 x)
+
+-- inf = tRead "(\\d.a ((\\d c.c d c) (\\x y z.x z (y z)) (\\f.(\\x.f (x x)) (\\x.f (x x))) e))"
+
+
+toNormalFormDebug :: Strategy -> Int -> Term -> Maybe Term
+toNormalFormDebug Eager n = flip evalStateT 0 . travPost (prnt >=> cnt >=> short n >=> return . reduceStep)
+toNormalFormDebug Lazy n = flip evalStateT 0 . travPre (prnt >=> cnt >=> short n >=> return . reduceStep)