Retrieving record function in generic SOP
Asked Answered
L

1

4

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] 
Lotz answered 28/3, 2016 at 0:42 Comment(0)
E
5

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 
Evolute answered 28/3, 2016 at 2:24 Comment(8)
Won't getting the projection itself and ignoring the fieldInfo be sufficient to retrieve record function? As you said, type of projections here is NP '[Code Rec -> Int, Code Rec -> Maybe String]. Also, Rep a = SOP I (Code a)). Pairing that with to should give us a which is Rec -> Int, a function, no? That is why I am confused about need for :*:. Will appreciate further insights here.Lotz
Also, how did you calculate the type of projections, especially in ghci? That step will be very helpful in experimenting.Lotz
Oh sorry - I thought you wanted the functions and their names. Indeed, you could just have NP ((->) t) r - that's just the functions. Also, I didn't calculate the type in GHCi - just in my head, based on my understanding of the general type. But you could ask ghci, of course, with e.g. :t projections :: (Code Rec ~ '[ xs ]) => NP (Projection f xs) xs - the type is the general type of projections, and the constraint is the same one used in the question - which says :: NP (Projection f '[Int, Maybe String]) '[Int, Maybe String].Evolute
Will appreciate also adding how to get the functions out of it. Type after fromJust is NP ((->) Rec) '[Int, Maybe String]. However, Rep a requires SOP I (Code a). So, NP ((-> Rec)) '[Int, Maybe String] needs to be converted to NP I '[ (Rec -> Int), (Rec -> Maybe String)]. I haven't been able to figure out the type knots here yet.Lotz
The types NP ((->) Rec) '[Int, Maybe String] and NP I '[ (Rec -> Int), (Rec -> Maybe String)] are isomorphic. However, the latter cannot be easily expressed in a general way. It could be NP I (Map ((->) Rec) '[ Int, Maybe String]) for example - but Map here is a type function, meaning it is non-injective. To "map" over a list with generics-sop, you are supposed to use the f parameter of NS and NP. You should simply work with the former type - the latter type will not really allow you to use the combinators provided by the library.Evolute
oh, ok, so how would you work with NP ((->) Rec) then to get the functions out? FYI, I have added an addendum to my question above, in case you haven't noticed that. I looked in generics-sop documentation for combinator functions for NP f but couldn't figure out yet how to do what I asked in the addendum. Learning process :) Appreciate your patient explanations.Lotz
Depends on exactly what you want to do with your functions! If you want to do something with each function, use hmap, hap or the like, which returns another NP. If you need to pass each record projection to some higher-order function q, for example, you can write hmap q (recordSelectors ..). If you need a single one of those functions, you have to decide a way to pick one. For example to arbitrarily select the first one you can use hd (which is a type error if called on an empty product).Evolute
Let us continue this discussion in chat.Lotz

© 2022 - 2024 — McMap. All rights reserved.