{-# LANGUAGE PackageImports #-}
{-# 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 "this" Data.Generics.Internal.VL.Prism
import qualified "generic-lens-core" Data.Generics.Sum.Internal.Typed as Core
import "generic-lens-core" Data.Generics.Internal.Void
class AsType a s where
_Typed :: Prism' s a
_Typed = forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism forall a s. AsType a s => a -> s
injectTyped (\s
i -> forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a b. a -> Either a b
Left s
i) forall a b. b -> Either a b
Right (forall a s. AsType a s => s -> Maybe a
projectTyped s
i))
{-# INLINE _Typed #-}
injectTyped :: a -> s
injectTyped
= forall s t a b. Prism s t a b -> b -> t
build forall a s. AsType a s => Prism' s a
_Typed
projectTyped :: s -> Maybe a
projectTyped
= forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> b -> a
const forall a. Maybe a
Nothing) forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s t a b. Prism s t a b -> s -> Either t a
match forall a s. AsType a s => Prism' s a
_Typed
{-# MINIMAL (injectTyped, projectTyped) | _Typed #-}
instance Core.Context a s => AsType a s where
_Typed :: Prism' s a
_Typed p a (f a)
eta = forall i s t a b. APrism i s t a b -> Prism s t a b
prism2prismvl forall a s. Context a s => Prism' s a
Core.derived p a (f a)
eta
{-# INLINE _Typed #-}
instance {-# OVERLAPPING #-} AsType a Void where
_Typed :: Prism' Void a
_Typed = forall a. HasCallStack => a
undefined
injectTyped :: a -> Void
injectTyped = forall a. HasCallStack => a
undefined
projectTyped :: Void -> Maybe a
projectTyped = forall a. HasCallStack => a
undefined
instance {-# OVERLAPPING #-} AsType Void a where
_Typed :: Prism' a Void
_Typed = forall a. HasCallStack => a
undefined
injectTyped :: Void -> a
injectTyped = forall a. HasCallStack => a
undefined
projectTyped :: a -> Maybe Void
projectTyped = forall a. HasCallStack => a
undefined