I'm using the genifunctors
package to generate a functor instance for a type whose definition involves type families.
The first module defines the data type itself:
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE DataKinds #-}
module Temp where
data Record (p :: (*,*))
type family Fst p where Fst (Record '(a,b)) = a
type family Snd p where Snd (Record '(a,b)) = b
data Bar s = Bar {
field_a :: Fst s,
field_b :: Snd s
}
newtype Baz a = Baz { getBaz :: Bar (Record '(Maybe a, [a])) }
This works just as expected:
λ> import Temp
λ> :t Baz $ Bar (Just "a") ["b"]
Baz $ Bar (Just "a") ["b"] :: Baz [Char]
The Functor
instance is defined in a separate module:
{-# LANGUAGE TemplateHaskell #-}
module Temp2 where
import Temp
import Data.Generics.Genifunctors
instance Functor (Baz a) where
fmap = $(genFmap ''Baz)
And gives this error:
λ> import Temp1
src/Temp2.hs:9:12-24: Exception when trying to run compile-time code: …
unexpected TyCon: FamilyI (ClosedTypeFamilyD Temp.Fst [PlainTV p_1627394000] (Just StarT) [TySynEqn [AppT (ConT Temp.Record) (AppT (AppT (ConT GHC.Tuple.(,)) (VarT a_1627394001)) (VarT b_1627394002))] (VarT a_1627394001)]) []
Code: genFmap ''Baz
In the splice: $(genFmap ''Baz)
This happens because genifunctors
, just like geniplate
, can only handle
type constructors from newtype
or data
declarations.
This could be fixed by normalizing the type before recursively inspecting it.
So, is there a way to do so within a Template Haskell splice? (i.e.
within the Q
monad?)