gdiff-th-0.1.0.1: Generate gdiff GADTs and Instances.

Safe HaskellNone

Data.Generic.Diff.TH

Contents

Description

This module exports the Template Haskell functions necessary deriving gdiff GADTs and associated instances. Usage is pretty straightforward.

module Example where
import Data.Generic.Diff  
import Data.Generic.Diff.TH  
import System.Console.Terminfo.Color
import Text.PrettyPrint.Free hiding (parens)
import System.Console.Terminfo.PrettyPrint

data Exp = Exp :+: Exp
         | Exp :*: Exp
         | B Integer
         deriving(Show, Eq, Typeable)

{- Make the GDiff apparatus -}
makeGDiff ''Exp

testA :: Exp
testA = foldl1 (:+:) . map B $ [0..20]

testB :: Exp
testB = foldl1 (:+:) . map B $ [0..8] ++ [42] ++ [10..20]

{- Make a type signature to help inference -}
diffExp :: Type ExpFamily Exp => Exp -> Exp -> EditScript ExpFamily Exp Exp
diffExp = diff

diffAandB = showCompressed $ diffExp testA testB  

main = diffAandB

{- Utility functions to show colored diffs -}
showEdits :: forall (f :: * -> * -> *) txs tys.
                   EditScriptL f txs tys -> IO ()
showEdits      = display . pprEdits 

showCompressed :: Family f => EditScriptL f txs tys -> IO ()
showCompressed = display . pprEdits . compress

pprEdits :: EditScriptL f txs tys -> TermDoc
pprEdits x = case x of 
    Cpy c d   -> (text $ string c) + pprEdits d
    CpyTree d -> text " ... "      + pprEdits d
    Del c d   -> (with (Foreground Red)   . text $ "- " ++ string c) + pprEdits d
    Ins c d   -> (with (Foreground Green) . text $ "+ " ++ string c) + pprEdits d
    End       -> line

Running the main function above would result in the following output

>>> main
:+: :+: :+: :+: :+: :+: :+: :+: :+: :+: :+: :+:  ...  B + 42 - 9  ...   ...   ...   ...   ...   ...   ...   ...   ...   ...   ... 

Except with pretty colors :).

Synopsis

Main Creation Function

makeGDiff :: Name -> Q [Dec]Source

Create the GADT and instances for GDiff with the defaults

Customizable Creation

makeGDiffWith :: String -> ConstructorRenamer -> [(Name, Exp)] -> Name -> Q [Dec]Source

Customizable creation.

Arg0 : The suffix added to the Family

Arg1 : Function used for naming constructors of the GADT after specialization

Arg2 : A list of primitives and an expression for showing them

Arg3 : The root type

defaultFamSuffix :: StringSource

Default suffix for the family Family

defaultConstructorRenamer :: String -> Name -> Type -> Q NameSource

Default constructor renamer. Using the family suffix, the name of the constructor and the specialized type of constructor

defaultPrimitives :: [(Name, Exp)]Source

Default primitives and expressions for showing them

type ConstructorRenamer = String -> Name -> Type -> Q NameSource

The type of function used for naming the GADTs constructors

Arg0 : The family suffix

Arg1 : The name of the constructor

Arg2 : The specialized type the constructor is from