{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Generics.Product.Types
(
HasTypes
, types
, Children
, ChGeneric
, HasTypesUsing
, typesUsing
, HasTypesCustom (typesCustom)
) where
import Data.Kind
import Data.Int (Int8, Int16, Int32, Int64)
import Data.Word (Word, Word8, Word16, Word32, Word64)
import qualified Data.Text as T
import GHC.Generics
import GHC.TypeLits
import Data.Generics.Internal.VL.Traversal
import Data.Generics.Internal.Errors
types :: forall a s. HasTypes s a => Traversal' s a
types = types_ @s @a
{-# INLINE types #-}
class HasTypes s a where
types_ :: Traversal' s a
default types_ :: Traversal' s a
types_ _ = pure
{-# INLINE types_ #-}
instance
( HasTypesUsing ChGeneric s a
) => HasTypes s a where
types_ = typesUsing_ @ChGeneric
{-# INLINE types_ #-}
data Void
instance {-# OVERLAPPING #-} HasTypes Void a where
types_ _ = pure
instance {-# OVERLAPPING #-} HasTypes s Void where
types_ _ = pure
instance {-# OVERLAPPING #-} HasTypesUsing ch Void a where
typesUsing_ _ = pure
instance {-# OVERLAPPING #-} HasTypesUsing ch s Void where
typesUsing_ _ = pure
type family Children (ch :: Type) (a :: Type) :: [Type]
typesUsing :: forall ch a s. HasTypesUsing ch s a => Traversal' s a
typesUsing = typesUsing_ @ch @s @a
{-# INLINE typesUsing #-}
class HasTypesUsing (ch :: Type) s a where
typesUsing_ :: Traversal' s a
instance {-# OVERLAPPABLE #-}
( HasTypesOpt ch (Interesting ch a s) s a
) => HasTypesUsing ch s a where
typesUsing_ = typesOpt @ch @(Interesting ch a s)
{-# INLINE typesUsing_ #-}
instance {-# OVERLAPPABLE #-} HasTypesUsing ch a a where
typesUsing_ = id
class HasTypesCustom (ch :: Type) s a where
typesCustom :: Traversal' s a
instance {-# OVERLAPPABLE #-}
( GHasTypes ch (Rep s) a
, Generic s
, Defined (Rep s)
(PrettyError '[ 'Text "No instance " ':<>: QuoteType (HasTypesCustom ch s a)])
(() :: Constraint)
) => HasTypesCustom ch s a where
typesCustom f s = to <$> gtypes_ @ch f (from s)
data ChGeneric
type instance Children ChGeneric a = ChildrenDefault a
type family ChildrenDefault (a :: Type) :: [Type] where
ChildrenDefault Char = '[]
ChildrenDefault Double = '[]
ChildrenDefault Float = '[]
ChildrenDefault Integer = '[]
ChildrenDefault Int = '[]
ChildrenDefault Int8 = '[]
ChildrenDefault Int16 = '[]
ChildrenDefault Int32 = '[]
ChildrenDefault Int64 = '[]
ChildrenDefault Word = '[]
ChildrenDefault Word8 = '[]
ChildrenDefault Word16 = '[]
ChildrenDefault Word32 = '[]
ChildrenDefault Word64 = '[]
ChildrenDefault T.Text = '[]
ChildrenDefault a
= Defined (Rep a)
(NoGeneric a
'[ 'Text "arising from a generic traversal."
, 'Text "Either derive the instance, or define a custom traversal using " ':<>: QuoteType HasTypesCustom
])
(ChildrenGeneric (Rep a) '[])
type family ChildrenGeneric (f :: k -> Type) (cs :: [Type]) :: [Type] where
ChildrenGeneric (M1 _ _ f) cs = ChildrenGeneric f cs
ChildrenGeneric (l :*: r) cs = ChildrenGeneric l (ChildrenGeneric r cs)
ChildrenGeneric (l :+: r) cs = ChildrenGeneric l (ChildrenGeneric r cs)
ChildrenGeneric (Rec0 a) cs = a ': cs
ChildrenGeneric _ cs = cs
class HasTypesOpt (ch :: Type) (t :: Bool) s a where
typesOpt :: Traversal' s a
instance HasTypesCustom ch s a => HasTypesOpt ch 'True s a where
typesOpt = typesCustom @ch
instance HasTypesOpt ch 'False s a where
typesOpt _ = pure
class GHasTypes ch s a where
gtypes_ :: Traversal' (s x) a
instance
( GHasTypes ch l a
, GHasTypes ch r a
) => GHasTypes ch (l :*: r) a where
gtypes_ f (l :*: r) = (:*:) <$> gtypes_ @ch f l <*> gtypes_ @ch f r
{-# INLINE gtypes_ #-}
instance
( GHasTypes ch l a
, GHasTypes ch r a
) => GHasTypes ch (l :+: r) a where
gtypes_ f (L1 l) = L1 <$> gtypes_ @ch f l
gtypes_ f (R1 r) = R1 <$> gtypes_ @ch f r
{-# INLINE gtypes_ #-}
instance (GHasTypes ch s a) => GHasTypes ch (M1 m meta s) a where
gtypes_ f (M1 s) = M1 <$> gtypes_ @ch f s
{-# INLINE gtypes_ #-}
instance HasTypesUsing ch b a => GHasTypes ch (Rec0 b) a where
gtypes_ f (K1 x) = K1 <$> typesUsing_ @ch @b @a f x
{-# INLINE gtypes_ #-}
instance {-# OVERLAPPING #-} HasTypes b a => GHasTypes ChGeneric (Rec0 b) a where
gtypes_ f (K1 x) = K1 <$> types_ @b @a f x
{-# INLINE gtypes_ #-}
instance GHasTypes ch U1 a where
gtypes_ _ _ = pure U1
{-# INLINE gtypes_ #-}
instance GHasTypes ch V1 a where
gtypes_ _ = pure
{-# INLINE gtypes_ #-}
type Interesting (ch :: Type) (a :: Type) (t :: Type)
= Defined_list (Children ch t) (NoChildren ch t)
(IsNothing (Interesting' ch a '[t] (Children ch t)))
type family NoChildren (ch :: Type) (a :: Type) :: Constraint where
NoChildren ch a = PrettyError
'[ 'Text "No type family instance for " ':<>: QuoteType (Children ch a)
, 'Text "arising from a traversal over " ':<>: QuoteType a
, 'Text "with custom strategy " ':<>: QuoteType ch
]
type family Interesting' (ch :: Type) (a :: Type) (seen :: [Type]) (ts :: [Type]) :: Maybe [Type] where
Interesting' ch _ seen '[] = 'Just seen
Interesting' ch a seen (t ': ts) =
InterestingOr ch a (InterestingUnless ch a seen t (Elem t seen)) ts
type family InterestingUnless
(ch :: Type) (a :: Type) (seen :: [Type]) (t :: Type) (alreadySeen :: Bool) ::
Maybe [Type] where
InterestingUnless ch a seen a _ = 'Nothing
InterestingUnless ch a seen t 'True = 'Just seen
InterestingUnless ch a seen t 'False
= Defined_list (Children ch t) (NoChildren ch t)
(Interesting' ch a (t ': seen) (Children ch t))
type family InterestingOr
(ch :: Type) (a :: Type) (seen' :: Maybe [Type]) (ts :: [Type]) ::
Maybe [Type] where
InterestingOr ch a 'Nothing _ = 'Nothing
InterestingOr ch a ('Just seen) ts = Interesting' ch a seen ts
type family Elem a as where
Elem a (a ': _) = 'True
Elem a (_ ': as) = Elem a as
Elem a '[] = 'False
type family IsNothing a where
IsNothing ('Just _) = 'False
IsNothing 'Nothing = 'True