{-# LANGUAGE PackageImports #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Generics.Product.Positions
(
HasPosition (..)
, HasPosition' (..)
, HasPosition_ (..)
, HasPosition0 (..)
, getPosition
, setPosition
) where
import "this" Data.Generics.Internal.VL.Lens as VL
import "generic-lens-core" Data.Generics.Internal.Void
import qualified "generic-lens-core" Data.Generics.Product.Internal.Positions as Core
import GHC.TypeLits (Nat)
class HasPosition (i :: Nat) s t a b | s i -> a, t i -> b, s i b -> t, t i a -> s where
position :: VL.Lens s t a b
class HasPosition_ (i :: Nat) s t a b where
position_ :: VL.Lens s t a b
class HasPosition' (i :: Nat) s a | s i -> a where
position' :: VL.Lens s s a a
class HasPosition0 (i :: Nat) s t a b where
position0 :: VL.Lens s t a b
getPosition :: forall i s a. HasPosition' i s a => s -> a
getPosition :: forall (i :: Nat) s a. HasPosition' i s a => s -> a
getPosition s
s = s
s forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. forall (i :: Nat) s a. HasPosition' i s a => Lens s s a a
position' @i
setPosition :: forall i s a. HasPosition' i s a => a -> s -> s
setPosition :: forall (i :: Nat) s a. HasPosition' i s a => a -> s -> s
setPosition = forall s t a b. Lens s t a b -> b -> s -> t
VL.set (forall (i :: Nat) s a. HasPosition' i s a => Lens s s a a
position' @i)
instance Core.Context' i s a => HasPosition' i s a where
position' :: Lens s s a a
position' a -> f a
f s
s = forall a b i s t.
(ALens a b i a b -> ALens a b i s t) -> Lens s t a b
VL.ravel (forall (i :: Nat) s a. Context' i s a => Lens s s a a
Core.derived' @i) a -> f a
f s
s
{-# INLINE position' #-}
instance (Core.Context i s t a b , HasPosition0 i s t a b) => HasPosition i s t a b where
position :: Lens s t a b
position = forall (i :: Nat) s t a b. HasPosition0 i s t a b => Lens s t a b
position0 @i
{-# INLINE position #-}
instance {-# OVERLAPPING #-} HasPosition f (Void1 a) (Void1 b) a b where
position :: Lens (Void1 a) (Void1 b) a b
position = forall a. HasCallStack => a
undefined
instance (Core.Context_ i s t a b, HasPosition0 i s t a b) => HasPosition_ i s t a b where
position_ :: Lens s t a b
position_ = forall (i :: Nat) s t a b. HasPosition0 i s t a b => Lens s t a b
position0 @i
{-# INLINE position_ #-}
instance {-# OVERLAPPING #-} HasPosition_ f (Void1 a) (Void1 b) a b where
position_ :: Lens (Void1 a) (Void1 b) a b
position_ = forall a. HasCallStack => a
undefined
instance Core.Context0 i s t a b => HasPosition0 i s t a b where
position0 :: Lens s t a b
position0 a -> f b
f s
s = forall a b i s t.
(ALens a b i a b -> ALens a b i s t) -> Lens s t a b
VL.ravel (forall (i :: Nat) s t a b. Context0 i s t a b => Lens s t a b
Core.derived0 @i) a -> f b
f s
s
{-# INLINE position0 #-}