shapely-data-0.0: Template haskell conversion of types to a "structural form" built from primitive sum, product, and unit types.

Safe HaskellNone

Data.Shapely

Synopsis

Documentation

This is an experimantal module for converting aribtrary algebraic data types into combinations of haskell's primitive product ((,)), sum (Either), and unit (()) types. The idea is to move the structure of a data type into the type system. . The templeate haskell function mkName can be used in a splice to generate Shapely class instances for a list of types. Here is an example of a Shapely instance generated for Maybe, illustrating naming conventions in generated code:

 {-# LANGUAGE TemplateHaskell #-}
 -- This code:
 $(mkShapely [''Maybe])
 -- generates code equivalent to:
 {-
  newtype ShapelyMaybe a = ShapelyMaybe {shapelyMaybe :: Either () a}
  instance Shapely (Maybe a) (ShapelyMaybe a) where
        toShapely a = ShapelyMaybe (toShapely' a)
          where
              toShapely' Nothing = Left GHC.Unit.()
              toShapely' (Just s1) = Right s1
        fromShapely a = fromShapely' (shapelyMaybe a)
          where
              fromShapely' (Left sumVar) = Nothing
              fromShapely' (Right sumVar)
                = \constr a-> constr a Just sumVar 
 -}

Note that the resulting structural form might be ambiguous, for instance both the types data Foo = Foo Int | Empty and data Bar = Bar Int | HoldsUnit () will convert to Either Int (). This poses no problem for conversions however. . This is mostly proof-of-concept, but some potentially-useful applications for this and future versions: . - generic view functions and lenses - conversions between similarly-structured data, or canonical representation - incremental Category-level modification of data structure, e.g. with Arrow - serializing data types . Caveats: In this version only basic (non-record) types are supported, recursive type arguments are not converted, etc. Let me know if you would find this module useful with additional functionality or more robust handling of input types.

mkShapely :: [Name] -> Q [Dec]Source

Generate a Shapely instance and newtype wrapper for the referenced types (see above for naming conventions). Usage:

 $(mkShapely [''Foo])  -- single-quotes reference a TH "Name"

This requires the TemplateHaskell extension to be enabled.

class Shapely a b | a -> b, b -> a whereSource

A class for types to be converted into a sort of normal form by converting its constructors into a combination of Either, (,) and (), and back again.

Methods

toShapely :: a -> bSource

fromShapely :: b -> aSource