{-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} module Tree where import Generics.MultiRec import Generics.MultiRec.TH.Alt import Data.Tree data TheFam :: (* -> *) where Tree_Int :: TheFam (Tree Int) Forest_Int :: TheFam (Forest Int) Pair :: TheFam (Tree Int, Tree Int) $(deriveEverything (DerivOptions [ ( [t| Tree Int |] , "Tree_Int" ) , ( [t| Forest Int |] , "Forest_Int" ) , ( [t| (Tree Int, Tree Int) |], "Pair" ) ] "TheFam" (\t c -> "CONSTRUCTOR_" ++ t ++ "_" ++ c) "ThePF" True ) ) type instance PF TheFam = ThePF