In Sum of Products
approach, how would one retrieve the record function? An example code below with record datatype (ghc 7.10.3
):
{-# LANGUAGE DeriveGeneric #-}
import qualified GHC.Generics as GHC
import Generics.SOP
data Rec = Rec { frec :: Int, srec :: Maybe String}
deriving (Show, GHC.Generic)
instance Generic Rec -- empty
instance HasDatatypeInfo Rec
Let us see DataTypeInfo
at ghci prompt:
*Main> datatypeInfo (Proxy :: Proxy Rec)
ADT "Main" "Rec" (Record "Rec" (FieldInfo "frec" :* (FieldInfo "srec" :* Nil)) :* Nil)
We see that frec
and srec
are both of type FieldInfo
which has a constructor FieldInfo
which takes the fieldName
as string. So, I don't see any way to get the actual functions frec :: Rec -> Int
and srec :: Rec -> Maybe String
. I also looked at show example but it doesn't use record functions.
Will appreciate pointers on how to get the record functions (could be HList of type HList '[(Rec -> Int), (Rec -> Maybe String)]
)).
Addendum to the question
I am tied up in the type knots about how to get the functions out of the projections using the approach user2407038 has laid out. So, I will like to add to the question further: how do we build a function like below using SOP
approach on Rec
constructor - we use both record field name as well as the function here:
[ ("frec" ++) . show . frec, ("srec" ++) . show . srec]
The generics-sop
library implements general combinators for working with sums of products, so you should write such a function using those combinators.
There is one issue - generics-sop
does not have any information about records vs. constructors on the type level, so your function will be still be partial (unless you go digging in the GHC generics Rep
).
For this example I'll just go with the partial function route.
First, you need this datatype:
data (:*:) f g x = f x :*: g x deriving (Show, Eq, Ord, Functor)
It seems like it should be included in the library, but it isn't (or I can't find it).
The type of the function will be
recordSelectors :: forall t r . (Code t ~ '[ r ], Generic t, HasDatatypeInfo t)
=> Proxy t -> Maybe (NP (FieldInfo :*: (->) t) r)
The constraint Code t ~ '[ r ]
simply says that the sum of productions representation of t
is a singleton list (one constructor). The return type is (maybe) a product over the list r
(the list of record field types) where there is a FieldInfo x
and a t -> x
for each type x
in r
.
One implementation is
case datatypeInfo (Proxy :: Proxy t) of
ADT _ _ (Record _ fields :* Nil) -> Just $
hzipWith (\nm (Fn prj) -> nm :*: (unI . prj . K . (\(Z x) -> x) . unSOP . from))
fields
projections
_ -> Nothing
Here the function determines in the given datatype is really a record, and otherwise returns Nothing
. If it is a record, zip togther the record fields and the projections
(defined by the library), which defines projections for an arbitrary generic product, which is essentially just NP '[ Code Rec -> Int, Code Rec -> Maybe String ]
for your type. All that is left is to compose the from
function with each projection to get the "real" projections. The rest (Fn
, unSOP
, etc.) are just identities.
Since it turns out you just want the record projection functions, sans function names, this is even simpler. And now the function isn't partial - any one constructor type has "record projections".
recordSelectors' :: forall t r . (Code t ~ '[ r ], Generic t)
=> Proxy t -> NP ((->) t) r
recordSelectors' _ = hmap (\(Fn prj) -> unI . prj . K . (\(Z x) -> x) . unSOP . from)
projections