For the purpose of generically deriving instances for FromRow
-kind-of-class on simple products I would like to statically analyze a type without actually providing any concrete terms.
Example:
class FromRow a where
rowrep :: Proxy a -> [Maybe NativeType]
fromRow :: Statement -> IO a
data User = User
{ name :: String
, uid :: Int
, active :: Bool
} deriving (Show, Generic)
The "trick" is I need the rowrep before I fetch any data - to possibly override the defaults for some or even all columns. At the point in time where I want to use rowrep I don't yet have a term, thus the Proxy
. Writing instances of FromRow
could get extremely tedious and error prone so I thought I'd add a default
implementation for Generic
types. However, it seems to get the generic representation I need to provide a term of a given type (from :: a -> Rep a
), knowledge of type itself is not enough.
Indeed we can see this isn't just a gimmick of the API and that Generic representations do hold values:
> from (User "foo" 1 True)
M1 {unM1 = M1 {unM1 = M1 {unM1 = K1 {unK1 = "foo"}} :*: (M1 {unM1 = K1 {unK1 = 1}} :*: M1 {unM1 = K1 {unK1 = True}})}}
Is there a way to use Generic
just to analyze the structure and type of things i.e. where we don't care about actual values? Failing that, is TH going to cover this use case?
CodePudding user response:
You don't need to provide a term. You don't need a value of Rep a
, you just need to inspect this as a type, and that can be done without ever using from
.
For that matter, you also don't need Proxy
, that was always just an ugly hack to make up for a deficiency of Haskell before TypeApplications
came along.
{-# LANGUAGE TypeFamilies, TypeApplications, AllowAmbiguousTypes
, ScopedTypeVariables, UnicodeSyntax, DefaultSignatures #-}
import Data.Kind (Type)
data NativeType = Intish | Floatish
class FromRow a where
rowrep :: [Maybe NativeType]
instance FromRow Int where
rowrep = [Just Intish]
Now, for writing generic instances we first need a helper class that does the type-level inspection of the Rep
:
class GFromRow (g :: k -> Type) where
gRowrep :: [Maybe NativeType]
instance ∀ i c f . GFromRow f => GFromRow (M1 i c f) where
gRowRep = gRowRep @f
instance ∀ i c . FromRow c => GFromRow (K1 i c) where
gRowRep = rowRep @c
... -- instances for U1 and f:*:g
Then the default implementation will be
class FromRow a where
rowrep :: [Maybe NativeType]
default rowrep :: GFromRow (Rep a) => [Maybe NativeType]
rowrep = gRowrep @(Rep a)