{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Data.Wedge.Microlens
(
here
, there
, _Nowhere
, _Here
, _There
) where
import Lens.Micro
import Data.Wedge
here :: Traversal' (Wedge a b) a
here :: (a -> f a) -> Wedge a b -> f (Wedge a b)
here a -> f a
f = \case
Wedge a b
Nowhere -> Wedge a b -> f (Wedge a b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Wedge a b
forall a b. Wedge a b
Nowhere
Here a
a -> a -> Wedge a b
forall a b. a -> Wedge a b
Here (a -> Wedge a b) -> f a -> f (Wedge a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a
f a
a
There b
b -> Wedge a b -> f (Wedge a b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (b -> Wedge a b
forall a b. b -> Wedge a b
There b
b)
there :: Traversal' (Wedge a b) b
there :: (b -> f b) -> Wedge a b -> f (Wedge a b)
there b -> f b
f = \case
Wedge a b
Nowhere -> Wedge a b -> f (Wedge a b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Wedge a b
forall a b. Wedge a b
Nowhere
Here a
a -> Wedge a b -> f (Wedge a b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Wedge a b
forall a b. a -> Wedge a b
Here a
a)
There b
b -> b -> Wedge a b
forall a b. b -> Wedge a b
There (b -> Wedge a b) -> f b -> f (Wedge a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> b -> f b
f b
b
_Nowhere :: Traversal' (Wedge a b) ()
_Nowhere :: (() -> f ()) -> Wedge a b -> f (Wedge a b)
_Nowhere () -> f ()
f = \case
Wedge a b
Nowhere -> Wedge a b
forall a b. Wedge a b
Nowhere Wedge a b -> f () -> f (Wedge a b)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ () -> f ()
f ()
Here a
a -> Wedge a b -> f (Wedge a b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Wedge a b
forall a b. a -> Wedge a b
Here a
a)
There b
b -> Wedge a b -> f (Wedge a b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (b -> Wedge a b
forall a b. b -> Wedge a b
There b
b)
_Here :: Traversal (Wedge a b) (Wedge c b) a c
_Here :: (a -> f c) -> Wedge a b -> f (Wedge c b)
_Here a -> f c
f = \case
Here a
a -> c -> Wedge c b
forall a b. a -> Wedge a b
Here (c -> Wedge c b) -> f c -> f (Wedge c b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f c
f a
a
There b
b -> Wedge c b -> f (Wedge c b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (b -> Wedge c b
forall a b. b -> Wedge a b
There b
b)
Wedge a b
Nowhere -> Wedge c b -> f (Wedge c b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Wedge c b
forall a b. Wedge a b
Nowhere
_There :: Traversal (Wedge a b) (Wedge a d) b d
_There :: (b -> f d) -> Wedge a b -> f (Wedge a d)
_There b -> f d
f = \case
There b
b -> d -> Wedge a d
forall a b. b -> Wedge a b
There (d -> Wedge a d) -> f d -> f (Wedge a d)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> b -> f d
f b
b
Here a
a -> Wedge a d -> f (Wedge a d)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Wedge a d
forall a b. a -> Wedge a b
Here a
a)
Wedge a b
Nowhere -> Wedge a d -> f (Wedge a d)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Wedge a d
forall a b. Wedge a b
Nowhere