{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Generics.Sum.Typed
(
AsType (..)
) where
import Data.Kind
import GHC.Generics
import GHC.TypeLits (TypeError, ErrorMessage (..), Symbol)
import Data.Generics.Sum.Internal.Typed
import Data.Generics.Internal.Families
import Data.Generics.Internal.Void
import Data.Generics.Product.Internal.HList
import Data.Generics.Internal.VL.Prism
import Data.Generics.Internal.Profunctor.Iso
import Data.Generics.Internal.Profunctor.Prism (prismPRavel)
class AsType a s where
_Typed :: Prism' s a
_Typed = prism injectTyped (\i -> maybe (Left i) Right (projectTyped i))
{-# INLINE[2] _Typed #-}
injectTyped :: a -> s
injectTyped
= build _Typed
projectTyped :: s -> Maybe a
projectTyped
= either (const Nothing) Just . match _Typed
{-# MINIMAL (injectTyped, projectTyped) | _Typed #-}
instance
( Generic s
, ErrorUnlessOne a s (CollectPartialType as (Rep s))
, as ~ TupleToList a
, ListTuple a as
, GAsType (Rep s) as
) => AsType a s where
_Typed eta = prismRavel (prismPRavel (repIso . _GTyped @_ @as . tupled)) eta
{-# INLINE[2] _Typed #-}
instance {-# OVERLAPPING #-} AsType a Void where
_Typed = undefined
injectTyped = undefined
projectTyped = undefined
instance {-# OVERLAPPING #-} AsType Void a where
_Typed = undefined
injectTyped = undefined
projectTyped = undefined
type family ErrorUnlessOne (a :: Type) (s :: Type) (ctors :: [Symbol]) :: Constraint where
ErrorUnlessOne _ _ '[_]
= ()
ErrorUnlessOne a s '[]
= TypeError
( 'Text "The type "
':<>: 'ShowType s
':<>: 'Text " does not contain a constructor whose field is of type "
':<>: 'ShowType a
)
ErrorUnlessOne a s cs
= TypeError
( 'Text "The type "
':<>: 'ShowType s
':<>: 'Text " contains multiple constructors whose fields are of type "
':<>: 'ShowType a ':<>: 'Text "."
':$$: 'Text "The choice of constructor is thus ambiguous, could be any of:"
':$$: ShowSymbols cs
)