I'll try to present here an "idiomatic" singletons
solution (if such a thing even exists). Preliminaries:
{-# LANGUAGE
RankNTypes, DataKinds, PolyKinds, ConstraintKinds, GADTs,
TypeOperators, MultiParamTypeClasses, TypeFamilies, ScopedTypeVariables #-}
import Data.Singletons.Prelude
import Data.Proxy
import GHC.Exts (Constraint)
-- SingI constraint here for simplicity's sake
class SingI name => Analyze (name :: Symbol) ty where
analyze :: Proxy name -> ty -> Int
data Rec rs where
Nil :: Rec '[]
Cons :: ty -> Rec rs -> Rec ( '(name, ty) ': rs )
recName :: Rec ('(name, t) ': rs) -> Proxy name
recName _ = Proxy
We need an All c rs
constraint, but we give it a spin and make c
a TyFun
instead a plain a -> Constraint
constructor:
type family AllC (c :: TyFun a Constraint -> *) (rs :: [a]) :: Constraint where
AllC c '[] = ()
AllC c (x ': xs) = (c @@ x, AllC c xs)
TyFun
lets us abstract over type constructors and type families and gives us partial application. It gives us almost first-class type-level functions with a somewhat ugly syntax. Note though that we necessarily lose constructor injectivity. @@
is the operator for applying TyFun
-s. TyFun a b -> *
means that a
is the input and b
is the output, and the trailing -> *
is just an artifact of the encoding. With GHC 8.0 we'll be able to just do
type a ~> b = TyFun a b -> *
And use a ~> b
thereafter.
We can implement now a general "classy" mapping over Rec
:
cMapRec ::
forall c rs r.
AllC c rs => Proxy c -> (forall name t. (c @@ '(name, t)) => Proxy name -> t -> r) -> Rec rs -> [r]
cMapRec p f Nil = []
cMapRec p f r@(Cons x xs) = f (recName r) x : cMapRec p f xs
Note that above c
has kind TyFun (a, *) Constraint -> *
.
And then implement analyzeRec
:
analyzeRec ::
forall c rs. (c ~ UncurrySym1 (TyCon2 Analyze))
=> AllC c rs => Rec rs -> [(String, Int)]
analyzeRec = cMapRec (Proxy :: Proxy c) (\p t -> (fromSing $ singByProxy p, analyze p t))
First, c ~ UncurrySym1 (TyCon2 Analyze)
is just a type-level let
binding that lets me use c
in Proxy c
as a shorthand. (If I really wanted to use all the dirty tricks, I would add {-# LANGUAGE PartialTypeSignatures #-}
and write Proxy :: _ c
).
UncurrySym1 (TyCon2 Analyze)
does the same thing that uncurry Analyze
would do if Haskell had full support for type level functions. The obvious advantage here is that we can write out the type of analyzeRec
on the fly without extra top-level type families or classes, and also use AllC
far more generally.
As a bonus, let's remove the SingI
constraint from Analyze
, and try to implement analyzeRec
.
class Analyze (name :: Symbol) ty where
analyze :: Proxy name -> ty -> Int
Now we have to require an additional constraint that expresses that all the name
-s in our Rec
are SingI
. We can use two cMapRec
-s, and zip the results:
analyzeRec ::
forall analyze names rs.
(analyze ~ UncurrySym1 (TyCon2 Analyze),
names ~ (TyCon1 SingI :.$$$ FstSym0),
AllC analyze rs,
AllC names rs)
=> Rec rs -> [(String, Int)]
analyzeRec rc = zip
(cMapRec (Proxy :: Proxy names) (\p _ -> fromSing $ singByProxy p) rc)
(cMapRec (Proxy :: Proxy analyze) (\p t -> analyze p t) rc)
Here TyCon1 SingI :.$$$ FstSym0
can be translated as SingI . fst
.
This is still roughly within the level of abstraction that can be readily expressed with TyFun
-s. The main limitation, of course, is the lack of lambdas. Ideally we wouldn't have to use zip
, instead we would use AllC (\(name, t) -> (SingI name, Analyze name t))
, and use a single cMapRec
. With singletons
, if we can't wing it anymore with point-free type-level programming, we have to introduce a new pointful type family.
Amusingly, GHC 8.0 will be strong enough so that we can implement type-level lambdas from scratch, although it will be probably ugly as hell. For example, \p -> (SingI (fst p), uncurry Analyze p)
could look something like this:
Eval (
Lam "p" $
PairL :@@
(LCon1 SingI :@@ (FstL :@@ Var "p")) :@@
(UncurryL :@@ LCon2 Analyze :@@ Var "p"))
where all the L
postfixes denote the lambda term embeddings of ordinary TyFun
-s (yet another collection of shorthands to be generated by TH...).
I have a prototype, although it only works with the even uglier de Bruijn variables yet, because of a GHC bug. It also features Fix
and explicit laziness on the type level.
AllC
and had been stuck on understanding the function symbols. I think I can make this work. I feel like going the full cMap route is too far at the moment, but it's close to feasible! – Johnnyjumpup