I'm trying to implement conversion to YAML for Generic types.
The simple conversion I implemented works well, but I would like to use their Show
instance for the types like data Foo = Bar | Biz
.
I was thinking of something like bellow. It correctly catches the types mentioned above, but fails on invoking the show
as I'm not able to properly constraint it.
instance {-# OVERLAPPING #-} (GToYaml x, GToYaml y) => GToYaml (D1 d (x : : y)) where
gToYaml x = string $ pack $ show $ to x
Is it possible to somehow constraint for original type to have Generic and Show instances? Or it should be handled somehow differently?
CodePudding user response:
Presumably, the original typeclass is something like
class ToYaml x where
toYaml :: x -> Yaml
Suppose we define this auxiliary datatype and typeclass:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
import Data.Proxy
import GHC.Generics
data HowToConvertToYaml = NormalCase | SpecialCase
class ToYaml' (how :: HowToConvertToYaml) x where
toYaml' :: Proxy how -> x -> Yaml
HowToConvertToYaml
is being used as a DataKind
, to provide one piece of extra information to ToYaml'
: whether we are in the special case or not. This allows us to define different instances for each case:
instance Show x => ToYaml' SpecialCase x where
toYaml' _ = undefined
instance (Generic x, GToYaml (Rep x)) => ToYaml' NormalCase x where
toYaml' _ = undefined
The problem is that we want to use ToYaml
, not ToYaml'
. We need a way to automatically compute the HowToConvertToYaml
for each type, and then make the ToYaml
instance delegate on the ToYaml'
one.
We can use a type family:
type family FindHowToConvertToYaml rep :: HowToConvertToYaml where
FindHowToConvertToYaml (D1 _ (_ : : _)) = SpecialCase
FindHowToConvertToYaml _ = NormalCase
And ToYaml
in terms of ToYaml'
would be:
instance (Generic x, ToYaml' (FindHowToConvertToYaml (Rep x)) x) => ToYaml x where
toYaml = toYaml' (Proxy @(FindHowToConvertToYaml (Rep x)))