Free Sections

Haskell Syntax Extension

by Andrew Seniuk
The reader is strongly encouraged to navigate to fremissant.net/freesect as these documents are currently experiencing rapid growth and refinement. The local files represent the best documentation available at packaging of this v.0.0.5 source distribution (March 11, 2012).
Free sections are syntactic sugar to extend the usual notion of "section" in functional programming. Recall that a section is just a function which has been applied to some but not all of its arguments. Unless the function is modified, arguments must be supplied in the lexical order determined by the function binding's parameters. For instance, sect is partially applied, but is still a function type and can absorb two more arguments of types Char and Float, in that order.
  f :: Int -> Bool -> Char -> Float -> String
  sect = f 4 True  -- Char -> Float -> String
By using wildcard symbols (__, a double-underscore), any subset of values occurring in a RHS context can be deferred, in the same spirit as partial function application. Special brackets (_[…]_) are used to delimit the lexical extent (or context) of the section, although these could sometimes be omitted (details below). The free section is then a function with arity at least equal to the number of wildcards, and behaves as if a helper function had been defined which shuffled the argument order of the functional expression, turning it into a normal section.

Some examples, including illustrations of context inferencing.

An more complex example...

Here I depict a situation where some API provides you with the dreaded dreadme function, which you have need of using. The example is designed to show that you can really put the __'s anywhere on a RHS that an expression can go.

  {-# LANGUAGE FreeSections #-}  -- use "{- #" if compiling with ghc -F

  tableA = [ [1,2,3], [4,5], [6,7,8,9] ]
  tableB = [ [9,8,7], [6,5], [4,3,2,1] ]

  data D a = D Int [a]

  v = map3  _[ dreadme tableA __ (repeat True,__) (D __ [(+),(*)]) ]_
            [tableA,tableB]
            [0..]
            [-1,1]
FreeSect rewrites the RHS of rslt (where fs0…fs2 must be fresh identifiers) to:
  v = map3  (\ fs0 fs1 fs2 -> dreadme tableA fs0 (repeat True,fs1) (D fs2 [(+),(*)]) )
            [tableA,tableB]
            [0..]
            [-1,1]
(Here is the rest of the code to make a closed module.)

Some virtues of the new syntax

Although the rewrite provided by the extension is simple, there are advantages of free sections relative to explicitly written lambdas: On the other hand, the lambda is more powerful and can achieve arbitrary permutations without further ado.

Implementation

The implementation seems to be working. The freesect package can also be installed from hackage.haskell.org, for instance using cabal-install. I offer fair warning that I'm not a good Haskell coder, but this does demonstrate how a person of modest abilities can use SYB with HSE to create a robust Haskell syntax extension.

Background

There was discussion about this on the #haskell IRC channel. Strangely, eyebloom suggested the same thing about an hour after I had started making inquiries about how to go about writing an extension, and this is the one I had in mind. It's an extraordinary coincidence, as I first sketched the idea in 2003, and had never seen it mentioned per se, beyond discussions of point-free and the like. (Despite eyebloom asking to be contacted if I wanted to work on this, my email was never answered.) Some of the examples mentioned in the chat have been presented above, to show how FreeSect deals with them.

Other details

Nested free sections work correctly, thanks to bottom-up traversal. Note that, as wildcards are syntactically indistinguishable, it is impossible for an outermore freesect to place a wildcard inside an innermore freesect.

Temporary names created by FreeSect are guaranteed to be unique among names referenced within a module. Imported names which are in scope but never used will not incur conflicts. Also, there is no danger of exporting the temporary names inadvertently, as they never have top-level scope.

A default context is automatically applied when the _[…]_ grouping syntax is omitted. Defining this default can be tricky, and a bit arbitrary, so for robust code it's best to use explicit bracketing. As of v.0.0.5, when the _[…]_ are omitted, the defaulting rules are as follows: The semilattice join of all unbacketed wildcards in a RHS are given context of the innermost enclosing parentheses or infix $ operation. If no such parentheses or infix $ are present, the whole RHS becomes the default context. Some of the examples at the top of the page demonstrate these rules. One hopes that the default will result in a type error, should the inferred context differ from the intended. I haven't thought of any situation where more than one bracketing of freesect wildcards yield typeable expressions, but neither have I ruled it out.

Philosophically, use of this sort of syntax promotes "higher-order programming", since any expression can so easily be made into a function, in numerous ways, simply by replacing parts of it with freesect wildcards. That this is worthwhile is demonstrated frequently by usefulness of sections.

Work in progress

A few things don't work quite right yet. Free sections in let expressions are one. Also, guarded RHS's are not yet handled. Work continues...

How to run it

The extension runs as a preprocessor. This can be done with or without the knowledge of GHC. If you use ghc -F (see scripts in the download), then unfortunately GHC checks language pragmas before preprocessing, which means you cannot declare {-# LANGUAGE FreeSections #-} at the top. Although the patched HSE is capable of rejecting source which uses free sections without the pragma, this feature is disabled for interoperability with GHC. All compilers are supported by running freesect as an independent preprocessor, but there are some inconveniences involving temporary files.

Feedback

Please provide feedback on the FreeSect haskell-cafe mailing list thread.

Kind Reg'ds,
Andrew Seniuk
(rasfar on #haskell)
  Feb. 29, 2012