{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Data.Vec.Lazy.Inline.Optics (
ix,
_Cons,
_head,
_tail,
_Pull,
_Vec,
) where
import Control.Applicative ((<$>))
import Data.Fin (Fin (..))
import Data.Nat (Nat (..))
import Data.Vec.Lazy.Optics (_Cons, _head, _tail)
import Prelude (Functor, ($), (.))
import qualified Data.Fin as F
import qualified Data.Type.Nat as N
import qualified Data.Vec.Pull as P
import qualified Optics.Core as L
import Data.Vec.Lazy.Inline
type LensLikeVL f s t a b = (a -> f b) -> s -> f t
type LensLikeVL' f s a = LensLikeVL f s s a a
ix :: forall n a. N.InlineInduction n => Fin n -> L.Lens' (Vec n a) a
ix i = L.lensVL (ixVL i)
{-# INLINE ix #-}
ixVL :: forall n f a. (N.InlineInduction n, Functor f) => Fin n -> LensLikeVL' f (Vec n a) a
ixVL = getIxLens $ N.inlineInduction1 start step where
start :: IxLens f 'Z a
start = IxLens F.absurd
step :: IxLens f m a -> IxLens f ('S m) a
step (IxLens l) = IxLens $ \i -> case i of
FZ -> headVL
FS j -> tailVL . l j
{-# INLINE ixVL #-}
newtype IxLens f n a = IxLens { getIxLens :: Fin n -> LensLikeVL' f (Vec n a) a }
headVL :: Functor f => LensLikeVL' f (Vec ('S n) a) a
headVL f (x ::: xs) = (::: xs) <$> f x
{-# INLINE headVL #-}
tailVL :: Functor f => LensLikeVL' f (Vec ('S n) a) (Vec n a)
tailVL f (x ::: xs) = (x :::) <$> f xs
{-# INLINE tailVL #-}
_Pull :: N.InlineInduction n => L.Iso (Vec n a) (Vec n b) (P.Vec n a) (P.Vec n b)
_Pull = L.iso toPull fromPull
_Vec :: N.InlineInduction n => L.Prism' [a] (Vec n a)
_Vec = L.prism' toList fromList