module Data.Generics.Product.Positions
(
HasPosition (..)
, GHasPosition (..)
) where
import Data.Generics.Internal.Lens
import Data.Kind (Constraint, Type)
import Data.Type.Bool (If, type (&&), Not)
import GHC.Generics
import GHC.TypeLits (type (<=?), type (+), Nat, TypeError, ErrorMessage(..))
class HasPosition (i :: Nat) a s | s i -> a where
position :: Lens' s a
position f s
= fmap (flip (setPosition @i) s) (f (getPosition @i s))
getPosition :: s -> a
getPosition s = s ^. position @i
setPosition :: a -> s -> s
setPosition = set (position @i)
instance
( Generic s
, ErrorUnless i s (0 <? i && i <=? Size (Rep s))
, GHasPosition 1 i (Rep s) a
) => HasPosition i a s where
position = repIso . gposition @1 @i
type family ErrorUnless (i :: Nat) (s :: Type) (hasP :: Bool) :: Constraint where
ErrorUnless i s 'False
= TypeError
( 'Text "The type "
':<>: 'ShowType s
':<>: 'Text " does not contain a field at position "
':<>: 'ShowType i
)
ErrorUnless _ _ 'True
= ()
class GHasPosition (offset :: Nat) (i :: Nat) (f :: Type -> Type) a | offset i f -> a where
gposition :: Lens' (f x) a
instance GHasPosition i i (S1 meta (Rec0 a)) a where
gposition = mIso . kIso
instance GHasPosition offset i f a => GHasPosition offset i (M1 D meta f) a where
gposition = mIso . gposition @offset @i
instance GHasPosition offset i f a => GHasPosition offset i (M1 C meta f) a where
gposition = mIso . gposition @offset @i
instance
( goLeft ~ (i <? (offset + Size l))
, offset' ~ (If goLeft offset (offset + Size l))
, GProductHasPosition offset' i l r a goLeft
) => GHasPosition offset i (l :*: r) a where
gposition = gproductPosition @offset' @i @_ @_ @_ @goLeft
class GProductHasPosition (offset :: Nat) (i :: Nat) l r a (left :: Bool) | offset i l r left -> a where
gproductPosition :: Lens' ((l :*: r) x) a
instance GHasPosition offset i l a => GProductHasPosition offset i l r a 'True where
gproductPosition = first . gposition @offset @i
instance GHasPosition offset i r a => GProductHasPosition offset i l r a 'False where
gproductPosition = second . gposition @offset @i
type family Size f :: Nat where
Size (l :*: r)
= Size l + Size r
Size (l :+: r)
= Min (Size l) (Size r)
Size (D1 meta f)
= Size f
Size (C1 meta f)
= Size f
Size f
= 1
type x <? y = Not (y <=? x)
infixl 4 <?
type Min a b = If (a <? b) a b