[Haskell-cafe] about Haskell code written to be "too smart"

Claus Reinke claus.reinke at talk21.com
Wed Mar 25 09:37:07 EDT 2009


The beauty of functional programming is that there doesn't have
to be a conflict between those who prefer explicit and those
who prefer implicit recursion. Think of them as different views
on the same functions - just as with graphical visualizations,
pick the view best suited to your purpose and use equational
reasoning to transform one view into another, as needed.

Improving your experience in reasoning about code is going to
help at every level of abstraction, and since you've already
paid the price (using a pure language, to make reasoning easier)
you might as well avail yourself of the facilities;-)

While developing, I might prefer abstraction, as fewer details
mean that I can hold more of the problem in my head at any
point, increasing my chances of seeing all the way to a
solution; if optimizing, or when I haven't found the right
abstractions yet, I might have to resort to less abstract code
until I've sorted out those details or until GHC deals with
the more abstract forms as well as with the less abstract ones.

Fine, you say, but I'd never would have thought of abstract
views like splitAt as a state transformer. Okay, before this
thread, I might not have thought of using that, either. But
after this thread, I'd hope for it to become part of my
thinking about Haskell code. And the way I do that is by
taking the abstract code and unfold it (replacing instances
of left-hand sides with instances of right-hand sides of
definitions - the source links in the Haddock documentation
are very useful for that) until I get to some less abstract
code that I might have come up with.

That doesn't mean that I'd have had the insights to play the
derivation backwards, but by breaking the transformation from
less abstract to more abstract view into smaller steps, starting
from the abstract form that incorporates the additional insights
I was missing, I can increase my understanding of what is going
on, and my chances of noticing the opportunities next time. It
also confirms whether or not the two solutions really are the
same (as has been pointed out, that wasn't the case here).

Paraphrasing and tweaking Sjur Gjøstein Karevoll's remark
a little: clever Perl code is what you hope you understood in
the past, when you wrote it; clever Haskell code is what you
hope you'll understand in the future, when you'll write it yourself!-)

The derivation below is best followed by replaying it yourself
in your editor, but I hope you'll find it helpful anyway.

Claus

-- view transformation: reducing the level of abstraction
-- by turning implicit to explict recursion

takeList = evalState . mapM (State . splitAt)

-- unfold 'mapM'

takeList = evalState . sequence . map (State . splitAt)

-- unfold 'sequence'

takeList = evalState . foldr k (return []) . map (State . splitAt)
  where k m m' = do x<-m; xs<-m'; return (x:xs)
        foldr op n []    = n
        foldr op n (h:t) = h `op` foldr op n t

-- specialize 'foldr' for the call paramenters 'k' and 'return []'

takeList = evalState . foldrkn . map (State . splitAt)
  where k m m' = do x<-m; xs<-m'; return (x:xs)
        foldrkn []    = return []
        foldrkn (h:t) = h `k` foldrkn t

-- unfold 'k'

takeList = evalState . foldrkn . map (State . splitAt)
  where foldrkn []    = return []
        foldrkn (h:t) = do x<-h; xs<-foldrkn t; return (x:xs)

-- foldr op n . map f = foldr (op.f) n

takeList = evalState . foldrkn
  where foldrkn []    = return []
        foldrkn (h:t) = do x<-State (splitAt h); xs<-foldrkn t; return (x:xs)

-- unfold 'return' for 'State', eta-expand 'splitAt h'

takeList = evalState . foldrkn
  where foldrkn []    = State (\s->([],s))
        foldrkn (h:t) = do x<-State (\s->splitAt h s); xs<-foldrkn t; State (\s->(x:xs,s))

-- eta-expand body of 'takeList'

takeList ns xs = evalState (foldrkn ns) xs
  where foldrkn []    = State (\s->([],s))
        foldrkn (h:t) = do x<-State (\s->splitAt h s); xs<-foldrkn t; State (\s->(x:xs,s))

-- unfold the second '>>=' for 'State'

takeList ns xs = evalState (foldrkn ns) xs
  where foldrkn []    = State (\s->([],s))
        foldrkn (h:t) = do x<-State (\s->splitAt h s)
                           State (\s->let (xs,s') = runState (foldrkn t) s
                                      in runState (State (\s->(x:xs,s))) s')

-- runState . State = id

takeList ns xs = evalState (foldrkn ns) xs
  where foldrkn []    = State (\s->([],s))
        foldrkn (h:t) = do x<-State (\s->splitAt h s)
                           State (\s->let (xs,s') = runState (foldrkn t) s
                                      in (\s->(x:xs,s)) s')

-- beta-reduce

takeList ns xs = evalState (foldrkn ns) xs
  where foldrkn []    = State (\s->([],s))
        foldrkn (h:t) = do x<-State (\s->splitAt h s)
                           State (\s->let (xs,s') = runState (foldrkn t) s
                                      in (x:xs,s'))

-- unfold the remainign '>>=' for 'State'

takeList ns xs = evalState (foldrkn ns) xs
  where foldrkn []    = State (\s->([],s))
        foldrkn (h:t) = State (\s->let (x,s') = runState (State (\s->splitAt h s)) s
                                   in runState (State (\s->let (xs,s') = runState (foldrkn t) s
                                                           in (x:xs,s'))) s')

-- runState . State = id (2x)

takeList ns xs = evalState (foldrkn ns) xs
  where foldrkn []    = State (\s->([],s))
        foldrkn (h:t) = State (\s->let (x,s') = (\s->splitAt h s) s
                                   in (\s->let (xs,s') = runState (foldrkn t) s
                                           in (x:xs,s')) s')

-- beta-reduce (2x)

takeList ns xs = evalState (foldrkn ns) xs
  where foldrkn []    = State (\s->([],s))
        foldrkn (h:t) = State (\s->let (x,s') = splitAt h s
                                   in let (xs,s'') = runState (foldrkn t) s'
                                      in (x:xs,s''))

-- unfold 'evalState'

takeList ns xs = fst $ runState (foldrkn ns) xs
  where foldrkn []    = State (\s->([],s))
        foldrkn (h:t) = State (\s->let (x,s') = splitAt h s
                                   in let (xs,s'') = runState (foldrkn t) s'
                                      in (x:xs,s''))

-- all calls to 'foldrkn' are wrapped in 'runState', bring it into the definition

takeList ns xs = fst $ (foldrkn ns) xs
  where foldrkn []    = runState $ State (\s->([],s))
        foldrkn (h:t) = runState $ State (\s->let (x,s') = splitAt h s
                                              in let (xs,s'') = (foldrkn t) s'
                                                 in (x:xs,s''))

-- runState . State = id (2x)

takeList ns xs = fst $ (foldrkn ns) xs
  where foldrkn []    = \s->([],s)
        foldrkn (h:t) = \s->let (x,s') = splitAt h s
                            in let (xs,s'') = (foldrkn t) s'
                               in (x:xs,s'')

-- clean up

takeList ns xs = fst (foldrkn ns xs)
  where foldrkn []    s = ([],s)
        foldrkn (h:t) s = let (x,s') = splitAt h s
                              (xs,s'') = foldrkn t s'
                          in (x:xs,s'')

-- 'snd (foldrkn _ _)' is never used, remove it

takeList ns xs = foldrkn ns xs
  where foldrkn []    s = []
        foldrkn (h:t) s = let (x,s') = splitAt h s
                              xs = foldrkn t s'
                          in x:xs

-- remove indirection

takeList []    s = []
takeList (h:t) s = x : takeList t s'
  where (x,s') = splitAt h s




More information about the Haskell-Cafe mailing list