{-# LANGUAGE UndecidableInstances #-}
module Wakame.Keys where
import Prelude
import Data.Proxy
import Data.String (IsString (..))
import GHC.Generics
import GHC.TypeLits
import Wakame.Row (V (..))
keys :: (IsString s, Generic a, Keys' s (Rep a)) => a -> [s]
keys = keys' . from
class IsString s => Keys' s f where
keys' :: f a -> [s]
instance Keys' s a => Keys' s (D1 f a) where
keys' (M1 x) = keys' x
instance Keys' s a => Keys' s (C1 f a) where
keys' (M1 x) = keys' x
instance (Keys' s a, Keys' s b) => Keys' s (a :*: b) where
keys' (x :*: y) = keys' x <> keys' y
instance (IsString s, KnownSymbol key) => Keys' s (S1 ('MetaSel ('Just key) su ss ds) a) where
keys' _ = [fromString $ symbolVal (Proxy @key)]
instance (IsString s, KnownSymbol key) => Keys' s (S1 ('MetaSel 'Nothing su ss ds) (Rec0 (V '(key, a)))) where
keys' _ = [fromString $ symbolVal (Proxy @key)]