Reputation: 19664
Looking at an answer to this question:
https://stackoverflow.com/a/34164251/1052117
I see that it defines a data type that is used to parse a JSON object.
data Address = Address
{ house :: Integer
, street :: String
, city :: String
, state :: Maybe String
, zip :: String -- here I change the original, zip codes are strings, they have leading zeros.
} deriving (Show, Eq)
$(deriveJSON defaultOptions ''Address)
This is helpful, but I wonder: How could I change the Address data type to have all json fields be nullable? Specifically I see a Maybe before the state field, but I'm imagining a larger data structure where it would be tedious to modify all of the fields to Maybe fields. For example, while I /could/ re-write above as:
data Address = Address
{ house :: Maybe Integer
, street :: Maybe String
, city :: Maybe String
, state :: Maybe String
, zip :: Maybe String
} deriving (Show, Eq)
What function could I apply to the Address data type /in code/ to achieve this same result without rewriting all the code and manually inserting the Maybes?
Upvotes: 5
Views: 572
Reputation: 27756
achieve this same result without rewriting all the code and manually inserting the Maybes
To avoid intrusive changes to the record type, we can work with another type that is derived from the record one by analyzing its structure, something which requires relatively advanced generic and type-level programming. This answer uses the generics-sop package.
Some required pragmas and imports:
{-# LANGUAGE DataKinds, TypeFamilies, FlexibleInstances, UndecidableInstances,
ScopedTypeVariables, TypeApplications, TypeOperators,
DeriveGeneric, StandaloneDeriving, MultiParamTypeClasses,
FunctionalDependencies, AllowAmbiguousTypes, FlexibleContexts #-}
import Data.Kind (Type)
import Data.Type.Equality (type (==))
import GHC.TypeLits
import qualified GHC.Generics as GHC
import Generics.SOP -- from package "generics-sop"
import qualified Generics.SOP.Type.Metadata as M
This newtype represents an n-ary product of field values derived from a record, each wrapped in a functor f
. The type-level list ns
of field names is kept as a phantom type variable:
newtype Wrapped f (ns :: [Symbol]) (xs :: [Type]) = Wrapped { unwrap :: NP f xs }
deriving instance All (Generics.SOP.Compose Show f) xs => Show (Wrapped f ns xs)
type family FieldNamesOf (a :: M.DatatypeInfo) :: [Symbol] where
FieldNamesOf ('M.ADT moduleName datatypeName '[ 'M.Record constructorName fields ]) =
ExtractFieldNames fields
type family ExtractFieldNames (a :: [M.FieldInfo]) :: [Symbol] where
ExtractFieldNames '[] = '[]
ExtractFieldNames (('M.FieldInfo n) ': xs) = n ': ExtractFieldNames xs
fromRecord :: forall r ns xs. (IsProductType r xs,
HasDatatypeInfo r,
FieldNamesOf (DatatypeInfoOf r) ~ ns)
=> r
-> Wrapped I ns xs
fromRecord r = let (SOP (Z np)) = from r in Wrapped np
toRecord :: forall r ns xs. (IsProductType r xs,
HasDatatypeInfo r,
FieldNamesOf (DatatypeInfoOf r) ~ ns)
=> Wrapped I ns xs
-> r
toRecord (Wrapped np) = to (SOP (Z np))
If we don't need to keep the field names around, the newtype becomes superfluous, and it's better to work directly with the n-ary product NP, manipulating it with the rich set of functions provided by generics-sop.
But if we do want to maintain the ability to select fields by name, then we need to define a function on the newtype, supported by a pair typeclasses:
getWrappedField :: forall n f ns xs x. HasField ns n xs x => Wrapped f ns xs -> f x
getWrappedField (Wrapped np) = getHasField @ns @n np
class HasField (ns :: [Symbol]) (n :: Symbol)
(xs :: [Type]) (x :: Type) | ns n xs -> x where
getHasField :: NP f xs -> f x
instance ((e == n) ~ flag, HasField' flag (e : ns) n xs x) => HasField (e : ns) n xs x where
getHasField = getHasField' @flag @(e : ns) @n
class HasField' (flag :: Bool)
(ns :: [Symbol]) (n :: Symbol)
(xs :: [Type]) (x :: Type) | ns n xs -> x where
getHasField' :: NP f xs -> f x
instance HasField' True (n : ns) n (x : xs) x where
getHasField' (v :* _) = v
instance HasField ns n xs x => HasField' False (nz : ns) n (xz : xs) x where
getHasField' (_ :* rest) = getHasField @ns @n rest
Given this example record which derives the necessary supporting typeclasses:
data Person = Person { name :: String, age :: Int } deriving (Show, GHC.Generic)
instance Generic Person
instance HasDatatypeInfo Person
We can construct its generalized representation (where all the fields are initially wrapped in the identity functor I) and then get one of the fields, like this:
ghci> getWrappedField @"age" (fromRecord (Person "Jimmy" 25))
I 25
The name of the field is passed as a type-level Symbol
, using type application.
Upvotes: 2
Reputation: 348
As is discussed in the comments, using a functor-functor would work for this with just very small changes to the original data type.
If you start out with
data Address = Address
{ house :: Integer
, street :: String
, city :: String
, state :: Maybe String
, zip :: String
} deriving (Show, Eq)
then it is equivalent to
import Data.Functor.Identity
data AddressF f = Address
{ house :: f Integer
, street :: f String
, city :: f String
, state :: Maybe String
, zip :: f String
} deriving (Show, Eq)
type Address = AddressF Identity
and then you can get the second one by writing
type Address' = AddressF Maybe
To get back to the original definition, you can write
toOriginal (AddressF (Identity house) (Identity street) (Identity city) mbState (Identity zip)) = Address house street city mbState zip
Upvotes: 5