Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

infer a type for common fields in two records

Bear with me if this is a foolish question. How can I type a generic function that takes two records and returns an array of their common fields?

Let's say I have:

type A = { name :: String, color :: String }
type B = { name :: String, address :: Address, color :: String }

myImaginaryFunction :: ???
-- should return ["name", "color"] :: Array of [name color]

I want to write a function that takes ANY two types of records and return an array of common fields. A haskell solution would work as well.

like image 912
Sam R. Avatar asked Oct 18 '25 23:10

Sam R.


2 Answers

To express two record types with common fields in Haskell, you'll need a GHC extension:

{-# LANGUAGE DuplicateRecordFields #-}

and to introspect the names of the fields, you'll need generics based on the Data class:

{-# LANGUAGE DeriveDataTypeable #-}
import Data.Data ( Data, Typeable, DataRep(AlgRep), dataTypeRep
                 , dataTypeOf, constrFields)
import Data.List (intersect)
import Data.Proxy (Proxy(..), asProxyTypeOf)

This will allow you to define two data types using the same field names:

data Address = Address String deriving (Typeable, Data)
data A = A { name :: String, color :: String }
    deriving (Typeable, Data)
data B = B { name :: String, address :: Address, color :: String}
    deriving (Typeable, Data)

and then you can retrieve the field names using:

fieldNames :: (Data t) => Proxy t -> [String]
fieldNames t = case dataTypeRep $ dataTypeOf $ asProxyTypeOf undefined t of
  AlgRep [con] -> constrFields con

and get the common fields with:

commonFields :: (Data t1, Data t2) => Proxy t1 -> Proxy t2 -> [String]
commonFields t1 t2 = intersect (fieldNames t1) (fieldNames t2)

After which the following will work:

ghci> commonFields (Proxy :: Proxy A) (Proxy :: Proxy B)
["name", "color"]
ghci>

Note that the implementation of fieldNames above assumes that only record types with a single constructor will be introspected. See the documentation for Data.Data if you want to generalize it.

Now, because you're a help vampire, I know that you will demand a type level function, even though you said nothing in your question about requiring a type-level function! In fact, I can see you've already added a comment about how you're interested in somehow returning an array of name | color though no such thing exists in Haskell and even though you explicitly said in your question that you expected the term-level answer ["name", "color"].

Still, there may be non-vampires with a similar question, and perhaps this answer will help them instead.

like image 79
K. A. Buhr Avatar answered Oct 20 '25 18:10

K. A. Buhr


For Haskell, I like K.A. Buhr's answer, but personally I would not use Typeable and instead reach for GHC Generics. I think that might be preference at this point though.

For PureScript, I wrote about this kind of problem in my blog post Making Diffs of differently-typed Records in PureScript earlier this month. The approach is completely different from what you have with languages that don't have row types (No, Elm does not have these. You really don't get a solution there other than to use a homogeneous String Map).

First off, if you're at all familiar with PureScript, you might want to use Union, but this won't work either, as you'd want to do something like:

Union r1' r r1

Where r1' would be the complement of the shared subtype r between your first record r1 and r2. The reason being that you have two unsolved variables here, and the functional dependencies of Union require that any two of three parameters of Union be solved for.

So since we can't use Union directly, we'll have to craft some kind of solution. Since I can get a RowList structure that is sorted by keys, I opted to use this to walk through the two different records' RowLists and get out the intersection:

class RowListIntersection
  (xs :: RowList)
  (ys :: RowList)
  (res :: RowList)
  | xs ys -> res

instance rliNilXS :: RowListIntersection Nil (Cons name ty tail) Nil
instance rliNilYS :: RowListIntersection (Cons name ty tail) Nil Nil
instance rliNilNil :: RowListIntersection Nil Nil Nil
instance rliConsCons ::
  ( CompareSymbol xname yname ord
  , Equals ord EQ isEq
  , Equals ord LT isLt
  , Or isEq isLt isEqOrLt
  , If isEq xty trashty yty
  , If isEq xty trashty2 zty
  , If isEq (SProxy xname) trashname (SProxy zname)
  , If isEq
      (RLProxy (Cons zname zty res'))
      (RLProxy res')
      (RLProxy res)
  , If isEqOrLt
      (RLProxy xs)
      (RLProxy (Cons xname xty xs))
      (RLProxy xs')
  , If isLt
      (RLProxy (Cons xname yty ys))
      (RLProxy ys)
      (RLProxy ys')
  , RowListIntersection xs' ys' res'
  ) => RowListIntersection (Cons xname xty xs) (Cons yname yty ys) res

Then I used a short definition for getting the keys of the resulting RowList out:

class Keys (xs :: RowList) where
  keysImpl :: RLProxy xs -> List String

instance nilKeys :: Keys Nil where
  keysImpl _ = mempty

instance consKeys ::
  ( IsSymbol name
  , Keys tail
  ) => Keys (Cons name ty tail) where
  keysImpl _ = first : rest
    where
      first = reflectSymbol (SProxy :: SProxy name)
      rest = keysImpl (RLProxy :: RLProxy tail)

So together, I can define a function like so to get the shared labels:

getSharedLabels
  :: forall r1 rl1 r2 rl2 rl
  . RowToList r1 rl1
  => RowToList r2 rl2
  => RowListIntersection rl1 rl2 rl
  => Keys rl
  => Record r1
  -> Record r2
  -> List String
getSharedLabels _ _ = keysImpl (RLProxy :: RLProxy rl)

Then we can see results we expect:

main = do
  logShow <<< Array.fromFoldable $
    getSharedLabels
      { a: 123, b: "abc" }
      { a: 123, b: "abc", c: true }
  -- logs out ["a","b"] as expected

If you're new to RowList/RowToList, you might consider reading through my RowList Fun With PureScript 2nd Edition slides.

I put the code for this answer here.

If all this seems too involved, your other solution may be to coerce the records into a String Map and get the set union of the keys. I don't know if this is an answer in Elm though, since the runtime representation of a String Map probably does not match Record's. But for PureScript, this is one option as StrMap's runtime representation is the same as a Record.

like image 28
kakigoori Avatar answered Oct 20 '25 19:10

kakigoori