(λblog. blog blog) (λblog. blog blog)

diverging since 2008

Stack-oriented argument shuffling

2009-08-04 10:00

Preliminaries:

> module Data.Function.Stack where
> import Data.Function
> import Control.Monad
> import Control.Monad.Instances

Let's pretend that Haskell functions receive their arguments neatly on a stack. Now suppose our arguments were given in the wrong order and we needed to shuffle them around a bit before actually making the function call. In the Haskell world this is equivalent to applying some sort of permuting combinator to the function. Here are some basic stack operations implemented as combinators:

Swap the first two arguments:

> swap :: (a -> b -> rest) -> (b -> a -> rest)
> swap = flip

Duplicate the first argument:

> dup :: (a -> a -> rest) -> (a -> rest)
> dup = join  -- in the (r->) monad, sorry

Apply a literal argument:

> push :: a -> (a -> rest) -> rest
> push = flip id

Discard an argument:

> pop :: rest -> (a -> rest)
> pop = const

The type signatures can be interpreted as stack effects (which are used in stack-based languages to describe the stack effects of functions, or words as they are called) simply by reading them backwards. The top of a stack is to the left (a -> b -> rest is a stack with a on top) and the signature x -> y means that the stack state y is turned into state x.

First example:

(\a -> f 3 a a) = dup . push 3 $ f

As you can see, the stack combinators are written left-to-right in execution order. Nice.

Some additional combinators:

> dup2 :: (a -> b -> a -> rest) -> (a -> b -> rest)
> dup2 f a b = f a b a
> dup3 :: (a -> b -> c -> a -> rest) -> (a -> b -> c -> rest)
> dup3 f a b c = f a b c a
> rot :: (b -> c -> a -> rest) -> (a -> b -> c -> rest)
> rot = dup3 . pop
> rot' :: (c -> a -> b -> rest) -> (a -> b -> c -> rest)
> rot' = rot . rot

And a second example:

(\a b c -> f b c a 3) = (push 3) . dup3 . pop . rot $ f

Shuffling arguments with just these combinators can be very laboursome. To facilitate deep transformations we introduce the meta-combinator deep:

> deep :: (x -> y) -> ((c -> x) -> (c -> y))
> deep = (.)

Which takes a stack combinator and applies it one level down:

deep (push True) :: (c -> Bool -> rest) -> c -> rest

Now we can rewrite example 2 as:

(\a b c -> f b c a 3) = rot . (deep . deep . deep $ push 3) $ f

We can also describe complicated function compositions in this language of ours by mapping Haskell functions into "words" that manipulate our ephemeral stack:

> apply :: (a -> b) -> (b -> rest) -> (a -> rest)
> apply = flip (.)
> apply2 :: (a -> b -> c) -> (c -> rest) -> (a -> b -> rest)
> apply2 f g = (g .) . f

Example:

(\a b c -> f a (a+b) (g c)) = dup . deep (apply2 (+) . deep (apply g)) $ f

Oh the pointfree fun!

Thanks to ski on #haskell who gave a link to his earlier work in the same vein.

Tags: haskell.