{-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} ----------------------------------------------------------------------------- -- | -- Module : Data.Generics.Product.Internal.Positions -- Copyright : (C) 2017 Csongor Kiss -- License : BSD3 -- Maintainer : Csongor Kiss -- Stability : experimental -- Portability : non-portable -- -- Derive positional product type getters and setters generically. -- ----------------------------------------------------------------------------- module Data.Generics.Product.Internal.Positions ( GHasPosition (..) , 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 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