{-# LANGUAGE PolyKinds #-} -- | -- Some functions for using lenses with 'DMap'. module Data.Dependent.Map.Lens ( -- * At dmat -- * Ix , dmix ) where import Prelude hiding (lookup) import Data.Dependent.Map (DMap, alterF, insert, lookup) import Data.GADT.Compare (GCompare) -- | -- These functions have been specialised for use with 'DMap' but without any of the -- specific 'lens' types used so that we have compatibility without needing the -- dependency just for these functions. -- -- | -- This is equivalent to the <https://hackage.haskell.org/package/lens-4.16.1/docs/Control-Lens-At.html#v:at at> <https://hackage.haskell.org/package/lens-4.16.1/docs/Control-Lens-Type.html#t:Lens-39- Lens'> from <https://hackage.haskell.org/package/lens-4.16.1/docs/Control-Lens-At.html Control.Lens.At>: -- -- @ -- type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t -- -- at :: Index m -> Lens' m (Maybe (IxValue m)) -- @ -- -- So the type of 'dmat' is equivalent to: -- -- @ -- dmat :: GCompare k => Lens' (DMap k f) (Maybe (f v)) -- @ -- -- >>> DMap.fromList [AInt :=> Identity 33, AFloat :=> Identity 3.5] & dmat AString ?~ "Hat" -- DMap.fromList [AString :=> Identity "Hat", AInt :=> Identity 33, AFloat :=> Identity 3.5] -- -- >>> DMap.fromList [AString :=> Identity "Shoe", AInt :=> Identity 33, AFloat :=> Identity 3.5] ^? dmat AFloat -- Just (AFloat :=> 3.5) -- dmat :: (GCompare k, Functor f) => k v -> (Maybe (g v) -> f (Maybe (g v))) -> DMap k g -> f (DMap k g) dmat :: k v -> (Maybe (g v) -> f (Maybe (g v))) -> DMap k g -> f (DMap k g) dmat k v k Maybe (g v) -> f (Maybe (g v)) f = k v -> (Maybe (g v) -> f (Maybe (g v))) -> DMap k g -> f (DMap k g) forall k1 (k2 :: k1 -> *) (f :: * -> *) (v :: k1) (g :: k1 -> *). (GCompare k2, Functor f) => k2 v -> (Maybe (g v) -> f (Maybe (g v))) -> DMap k2 g -> f (DMap k2 g) alterF k v k Maybe (g v) -> f (Maybe (g v)) f {-# INLINE dmat #-} -- | -- This is equivalent to the <https://hackage.haskell.org/package/lens-4.16.1/docs/Control-Lens-At.html#v:ix ix> <https://hackage.haskell.org/package/lens-4.16.1/docs/Control-Lens-Type.html#t:Traversal-39- Traversal'> from <https://hackage.haskell.org/package/lens-4.16.1/docs/Control-Lens-At.html Control.Lens.At>: -- -- @ -- type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t -- -- ix :: Index m -> Traversal' m (IxValue m) -- @ -- -- So the type of 'dmix' is equivalent to: -- -- @ -- dmix :: GCompare k => k v -> Traversal' (DMap k f) (f v) -- @ -- -- /NB:/ Setting the value of this -- <https://hackage.haskell.org/package/lens-4.16.1/docs/Control-Lens-Type.html#t:Traversal Traversal> -- will only set the value in 'dmix' if it is already present. -- -- If you want to be able to insert /missing/ values, you want 'dmat'. -- -- >>> DMap.fromList [AString :=> Identity "Shoe", AInt :=> Identity 33, AFloat :=> Identity 3.5] & dmix AInt %~ f -- DMap.fromList [AString :=> Identity "Shoe", AInt :=> Identity (f 33), AFloat :=> Identity 3.5] -- -- >>> DMap.fromList [AString :=> Identity "Shoe", AInt :=> Identity 33, AFloat :=> Identity 3.5] & dmix AString .~ "Hat" -- DMap.fromList [AString :=> Identity "Hat", AInt :=> Identity 33, AFloat :=> Identity 3.5] -- -- >>> DMap.fromList [AString :=> Identity "Shoe", AInt :=> Identity 33, AFloat :=> Identity 3.5] ^? dmix AFloat -- Just (AFloat :=> 3.5) -- -- >>> DMap.fromList [AString :=> Identity "Shoe", AFloat :=> Identity 3.5] ^? dmix AInt -- Nothing dmix :: (GCompare k, Applicative f) => k v -> (g v -> f (g v)) -> DMap k g -> f (DMap k g) dmix :: k v -> (g v -> f (g v)) -> DMap k g -> f (DMap k g) dmix k v k g v -> f (g v) f DMap k g dmap = f (DMap k g) -> (g v -> f (DMap k g)) -> Maybe (g v) -> f (DMap k g) forall b a. b -> (a -> b) -> Maybe a -> b maybe (DMap k g -> f (DMap k g) forall (f :: * -> *) a. Applicative f => a -> f a pure DMap k g dmap) ((g v -> DMap k g) -> f (g v) -> f (DMap k g) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((g v -> DMap k g -> DMap k g) -> DMap k g -> g v -> DMap k g forall a b c. (a -> b -> c) -> b -> a -> c flip (k v -> g v -> DMap k g -> DMap k g forall k1 (k2 :: k1 -> *) (f :: k1 -> *) (v :: k1). GCompare k2 => k2 v -> f v -> DMap k2 f -> DMap k2 f insert k v k) DMap k g dmap) (f (g v) -> f (DMap k g)) -> (g v -> f (g v)) -> g v -> f (DMap k g) forall b c a. (b -> c) -> (a -> b) -> a -> c . g v -> f (g v) f) (Maybe (g v) -> f (DMap k g)) -> Maybe (g v) -> f (DMap k g) forall a b. (a -> b) -> a -> b $ k v -> DMap k g -> Maybe (g v) forall k1 (k2 :: k1 -> *) (f :: k1 -> *) (v :: k1). GCompare k2 => k2 v -> DMap k2 f -> Maybe (f v) lookup k v k DMap k g dmap {-# INLINE dmix #-}