{-# LANGUAGE DerivingStrategies    #-}
{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude     #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE TypeFamilies          #-}
module Persistent.Lens(entityTupleIso, valueLens, keyLens) where
import Control.Lens
import Database.Persist.Types
import Prelude
entityTupleIso :: Iso' (Entity a) (Key a, a)
entityTupleIso :: p (Key a, a) (f (Key a, a)) -> p (Entity a) (f (Entity a))
entityTupleIso = (Entity a -> (Key a, a))
-> ((Key a, a) -> Entity a)
-> Iso (Entity a) (Entity a) (Key a, a) (Key a, a)
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\(Entity Key a
a a
b) -> (Key a
a, a
b)) (((Key a, a) -> Entity a)
 -> Iso (Entity a) (Entity a) (Key a, a) (Key a, a))
-> ((Key a, a) -> Entity a)
-> Iso (Entity a) (Entity a) (Key a, a) (Key a, a)
forall a b. (a -> b) -> a -> b
$ (Key a -> a -> Entity a) -> (Key a, a) -> Entity a
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Key a -> a -> Entity a
forall record. Key record -> record -> Entity record
Entity
valueLens :: Lens' (Entity a) a
valueLens :: (a -> f a) -> Entity a -> f (Entity a)
valueLens = ((Key a, a) -> f (Key a, a)) -> Entity a -> f (Entity a)
forall a. Iso' (Entity a) (Key a, a)
entityTupleIso (((Key a, a) -> f (Key a, a)) -> Entity a -> f (Entity a))
-> ((a -> f a) -> (Key a, a) -> f (Key a, a))
-> (a -> f a)
-> Entity a
-> f (Entity a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> f a) -> (Key a, a) -> f (Key a, a)
forall s t a b. Field2 s t a b => Lens s t a b
_2
keyLens :: Lens' (Entity a) (Key a)
keyLens :: (Key a -> f (Key a)) -> Entity a -> f (Entity a)
keyLens = ((Key a, a) -> f (Key a, a)) -> Entity a -> f (Entity a)
forall a. Iso' (Entity a) (Key a, a)
entityTupleIso (((Key a, a) -> f (Key a, a)) -> Entity a -> f (Entity a))
-> ((Key a -> f (Key a)) -> (Key a, a) -> f (Key a, a))
-> (Key a -> f (Key a))
-> Entity a
-> f (Entity a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key a -> f (Key a)) -> (Key a, a) -> f (Key a, a)
forall s t a b. Field1 s t a b => Lens s t a b
_1