{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Data.Generics.Labels
(
Field(..)
, Field'
, Constructor(..)
, Constructor'
) where
import Data.Generics.Product
import Data.Generics.Sum
import Data.Generics.Internal.VL.Lens (Lens)
import Data.Generics.Internal.VL.Prism (Prism)
import Data.Profunctor (Choice)
import Data.Type.Bool (type (&&))
import Data.Type.Equality (type (==))
import GHC.OverloadedLabels
import GHC.TypeLits
class Field name s t a b | s name -> a, t name -> b, s name b -> t, t name a -> s where
fieldLens :: Lens s t a b
type Field' name s a = Field name s s a a
instance {-# INCOHERENT #-} HasField name s t a b => Field name s t a b where
fieldLens = field @name
instance {-# INCOHERENT #-} HasField' name s a => Field name s s a a where
fieldLens = field' @name
class Constructor name s t a b | name s -> a, name t -> b where
constructorPrism :: Prism s t a b
type Constructor' name s a = Constructor name s s a a
instance {-# INCOHERENT #-} AsConstructor name s t a b => Constructor name s t a b where
constructorPrism = _Ctor @name
instance {-# INCOHERENT #-} AsConstructor' name s a => Constructor name s s a a where
constructorPrism = _Ctor' @name
type family BeginsWithCapital (name :: Symbol) :: Bool where
BeginsWithCapital name = CmpSymbol "_@" name == 'LT && CmpSymbol "_[" name == 'GT
instance ( capital ~ BeginsWithCapital name
, IsLabelHelper capital name p f s t a b
, pafb ~ p a (f b), psft ~ p s (f t)) => IsLabel name (pafb -> psft) where
#if __GLASGOW_HASKELL__ >= 802
fromLabel = labelOutput @capital @name @p @f
#else
fromLabel _ = labelOutput @capital @name @p @f
#endif
class IsLabelHelper capital name p f s t a b where
labelOutput :: p a (f b) -> p s (f t)
instance (Functor f, Field name s t a b) => IsLabelHelper 'False name (->) f s t a b where
labelOutput = fieldLens @name
#if __GLASGOW_HASKELL__ >= 802
instance ( Applicative f, Choice p, Constructor name s t a b
, name' ~ AppendSymbol "_" name) => IsLabelHelper 'True name' p f s t a b where
labelOutput = constructorPrism @name
#else
instance (TypeError ('Text "Labels for Prisms require at least GHC 8.2"), Choice p) => IsLabelHelper 'True name' p f s t a b where
labelOutput = undefined
#endif