Scrap your boilerplate

From HaskellWiki
Revision as of 23:15, 13 April 2010 by Avo (talk | contribs) (Modify parameterized fields with care.)
Jump to navigation Jump to search


Scrap Your Boilerplate (syb) is an infrastructure for generic programming in Haskell. (This should not be confused with the concept of "generic types" in Java, which in the Java context means parameterized types which allow you to specify the type of list elements and such things - a feature Haskell has had since its inception.)

In the current GHC implementation, it consists of a set of modules (Data.Generics and its submodules) and deriving support for the Data and Typeable classes from those modules.

Code snippets

ListifyWholeLists

This code snippet implements a variation on the listify function. listify recurses into every "node" in a datastructure, which is not so good if what you're searching for is lists (e.g. strings) and you don't want to pick up sublists (substrings, in the case of strings). This function does not recurse into lists of the type being searched for, avoiding that problem.

It illustrates the use of ShowS-style function composition as an alternative to recursive list concatenation - the latter is inefficient. It also illustrates how laziness automatically means that sublists of type [b] won't be examined, without any special effort required. Isn't laziness wonderful?

import Data.Generics

-- A version of Data.Generics.listify which doesn't recurse into sublists of type [b]
listifyWholeLists :: Typeable b => ([b] -> Bool) -> GenericQ [[b]]
listifyWholeLists blp = flip (synthesize id (.) (mkQ id (\bl _ -> if blp bl then (bl:) else id))) []

fmap

This is most likely traverses more than a purpose-written Functor instance.

It is possible to recover modify parameterized types:

{-# LANGUAGE DeriveDataTypeable, ScopedTypeVariables, FlexibleContexts #-}
import Data.Generics
import Unsafe.Coerce

{- | C tags the type that is actually parameterized, so to avoid touching the
Int when a ~ Int:

> data T a = T Int a

by changing the type (not representation) to:

> x :: T Int (C Int)
-}
newtype C a = C a deriving (Data,Typeable)

fmapData :: forall t a b. (Typeable a, Data (t (C a)), Data (t a)) =>
    (a -> b) -> t a -> t b
fmapData f input = uc . everywhere (mkT $ \(x::C a) -> uc (f (uc x)))
                    $ (uc input :: t (C a))
    where uc = unsafeCoerce