1

What I roughly want is this:

data A = ...
data B = ...
data C = ...

class HasA t where
  getA :: t -> A

class HasB t where
  getB :: t -> B

class HasC t where
  getC :: t -> C

So I can do something like this (pseudocode follows):

a :: A
b :: B

x = mkRecord { elemA a, elemB b }
y = mkRecord { elemB b, elemA a }

-- type of `x` == type of `y`

Naturally, only the appropriate get functions work, in the above case getA and getB.

I'd also like the following functions

slice :: Subset a b => a -> b
slice x = -- just remove the bits of x that aren't in type b.

add :: e -> a -> a ++ e
add e x = -- add an element to the "record" (compile error if it's already there)

I feel like this is not a new problem so perhaps a resolution for this already exists. Note that I don't require the solution to be extensible, the amount of types I need to deal with is finite and known, but of course and extensible one wouldn't hurt.

I've found a couple of packages that seem to be in the field of what I'm looking for, namely HList and extensible (perhaps extensible is better because I want my records unordered). I got a bit lost in the Hackage docs so I'd like just some sample code (or a link to some sample code) that roughly achieves what I'm looking for.

Clinton
  • 22,361
  • 15
  • 67
  • 163

1 Answers1

1

This is exactly what HList is good for. However, since I don't have the right setup to test something with the HList package right now (and besides, it has more confusing data definitions), here is a minimal example of HList that uses singletons for the type-level list stuff.

{-# LANGUAGE DataKinds, TypeOperators, GADTs,TypeFamilies, UndecidableInstances,
    PolyKinds,  FlexibleInstances, MultiParamTypeClasses
  #-}

import Data.Singletons
import Data.Promotion.Prelude.List

data HList (l :: [*]) where
  HNil :: HList '[]
  HCons :: x -> HList xs -> HList (x ': xs)

The add function is the simplest: it is just HCons:

add :: x -> HList xs -> HList (x ': xs)
add = HCons 

Something more interesting is combining two records:

-- Notice we are using `:++` from singletons
combine :: HList xs -> HList ys -> HList (xs :++ ys)
combine HNil xs = xs
combine (x `HCons` xs) ys = x `HCons` (xs `combine` ys)

Now, for your get function, you need to dispatch based on the type-level list. To do this, you need an overlapping type class.

class Has x xs where
  get :: xs -> x

instance {-# OVERLAPS #-} Has x (HList (x ': xs)) where
  get (x `HCons` _) = x

instance Has x (HList xs) => Has x (HList (y ': xs)) where
  get (_ `HCons` xs) = get xs

Finally, we can use Has to define a similar Subset class. Same idea as before.

class Subset ys xs where
  slice :: xs -> ys

instance Subset (HList '[]) (HList xs) where
  slice _ = HNil

instance (Get y (HList xs), Subset (HList ys) (HList xs)) =>
           Subset (HList (y ': ys)) (HList xs) where
  slice xs = get xs `HCons` slice xs

As you mention in parens, the simple HList form does not ensure you have only one of any type of field (so get just returns the first field, ignoring the rest). If you want uniqueness, you can just add a constraint to the HList constructor.

data Record (l :: [*]) where
  Nil :: Record '[]
  Cons :: (NotElem x xs ~ 'True) => x -> Record xs -> Record (x ': xs)

However, defining Subset using Record looks like it involves some proofs. :)

Alec
  • 31,829
  • 7
  • 67
  • 114