Skip to content

Instantly share code, notes, and snippets.

@kana-sama
Created February 13, 2021 14:01
Show Gist options
  • Save kana-sama/4e62aa148e57d450830de49fdb513a99 to your computer and use it in GitHub Desktop.
Save kana-sama/4e62aa148e57d450830de49fdb513a99 to your computer and use it in GitHub Desktop.
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Aeson.GenericFields (type (<?>)) where
import Data.Proxy
import GHC.Generics
import GHC.TypeLits
type a <?> name = a
class GLabelModifier a where
glabelModifier :: [(String, String)]
instance GLabelModifier constructors => GLabelModifier (D1 meta constructors) where
glabelModifier = glabelModifier @constructors
instance (GLabelModifier l, GLabelModifier r) => GLabelModifier (l :+: r) where
glabelModifier = glabelModifier @l <> glabelModifier @r
instance GLabelModifier selectors => GLabelModifier (C1 meta selectors) where
glabelModifier = glabelModifier @selectors
instance (GLabelModifier l, GLabelModifier r) => GLabelModifier (l :*: r) where
glabelModifier = glabelModifier @l <> glabelModifier @r
instance GLabelModifier (S1 meta sel) where
glabelModifier = []
instance {-# OVERLAPS #-} (KnownSymbol old, KnownSymbol new) => GLabelModifier (S1 (MetaSel (Just old) _m1 _m2 _m3) (Rec0 (a <?> new))) where
glabelModifier = [(symbolVal @old Proxy, symbolVal @new Proxy)]
labelModifier :: forall a. GLabelModifier (Rep a) => [(String, String)]
labelModifier = glabelModifier @(Rep a)
data X = X {a :: Int <?> "aasd", b :: String} deriving (Generic)
x = labelModifier @X
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment