{-# LANGUAGE DeriveDataTypeable    #-}
{-# LANGUAGE DeriveGeneric         #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE StandaloneDeriving    #-}
{-# LANGUAGE TypeFamilies          #-}
{-# LANGUAGE UndecidableInstances  #-}
module Data.Strict.Lens (
    -- * Tuple
    -- | See instances, in particular for 'Field1' and 'Field2' type classes.
    -- * Either
    _Left, _Right,
    -- * Maybe
    _Just, _Nothing,
    -- * These
    here, there,
    _This, _That, _These,
    ) where


import           Control.Applicative (pure, (<$>))
import           Prelude             (Int, flip, ($), (.))

-- Lazy variants
import qualified Prelude             as L

import           Control.Lens        (Index, Prism, Prism', Traversal, prism,
                                      prism')

import           Data.Strict         (Either (..), Maybe (..), Pair (..),
                                      These (..), either, maybe, these)

-------------------------------------------------------------------------------
-- Tuple
-------------------------------------------------------------------------------

-- TODO: this should be removed. Probably.
type instance Index (Pair a b) = Int

-------------------------------------------------------------------------------
-- Either
-------------------------------------------------------------------------------

-- | Analogous to 'Control.Lens.Prism._Left' in "Control.Lens.Prism".
_Left :: Prism (Either a c) (Either b c) a b
_Left :: forall a c b. Prism (Either a c) (Either b c) a b
_Left = forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall a b. b -> Either a b
L.Right (forall a b. a -> Either a b
L.Left forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right)

-- | Analogous to 'Control.Lens.Prism._Right' in "Control.Lens.Prism".
_Right :: Prism (Either c a) (Either c b) a b
_Right :: forall c a b. Prism (Either c a) (Either c b) a b
_Right = forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> Either a b
L.Left forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left) forall a b. b -> Either a b
L.Right

-------------------------------------------------------------------------------
-- Maybe
-------------------------------------------------------------------------------

-- | Analogous to 'Control.Lens.Prism._Just' in "Control.Lens.Prism"
_Just :: Prism (Maybe a) (Maybe b) a b
_Just :: forall a b. Prism (Maybe a) (Maybe b) a b
_Just = forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a b. a -> Either a b
L.Left forall a. Maybe a
Nothing) forall a b. b -> Either a b
L.Right

-- | Analogous to 'Control.Lens.Prism._Nothing' in "Control.Lens.Prism"
_Nothing :: Prism' (Maybe a) ()
_Nothing :: forall a. Prism' (Maybe a) ()
_Nothing = forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' (forall a b. a -> b -> a
L.const forall a. Maybe a
Nothing) forall a b. (a -> b) -> a -> b
$ forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a. a -> Maybe a
L.Just ()) (forall a b. a -> b -> a
L.const forall a. Maybe a
L.Nothing)

-------------------------------------------------------------------------------
-- These
-------------------------------------------------------------------------------

-- | A 'Control.Lens.Traversal' of the first half of a 'These', suitable for use with "Control.Lens".
--
-- >>> over here show (That 1)
-- That 1
--
-- >>> over here show (These 'a' 2)
-- These "'a'" 2
--
here :: Traversal (These a c) (These b c) a b
here :: forall a c b. Traversal (These a c) (These b c) a b
here a -> f b
f (This a
x)    = forall a b. a -> These a b
This forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
x
here a -> f b
f (These a
x c
y) = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. a -> b -> These a b
These c
y forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
x
here a -> f b
_ (That c
x)    = forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a b. b -> These a b
That c
x)

-- | A 'Control.Lens.Traversal' of the second half of a 'These', suitable for use with "Control.Lens".
--
-- @
-- 'there' :: 'Control.Lens.Traversal' ('These' t b) ('These' t b) a b
-- @
--
-- >>> over there show (That 1)
-- That "1"
--
-- >>> over there show (These 'a' 2)
-- These 'a' "2"
--
there :: Traversal (These c a) (These c b) a b
there :: forall c a b. Traversal (These c a) (These c b) a b
there a -> f b
_ (This c
x)    = forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a b. a -> These a b
This c
x)
there a -> f b
f (These c
x a
y) = forall a b. a -> b -> These a b
These c
x forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
y
there a -> f b
f (That a
x)    = forall a b. b -> These a b
That forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
x

-- | A 'Control.Lens.Prism'' selecting the 'This' constructor.
--
-- /Note:/ cannot change type.
_This :: Prism' (These a b) a
_This :: forall a b. Prism' (These a b) a
_This = forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism forall a b. a -> These a b
This (forall a c b.
(a -> c) -> (b -> c) -> (a -> b -> c) -> These a b -> c
these forall a b. b -> Either a b
L.Right (forall a b. a -> Either a b
L.Left forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> These a b
That) (\a
x b
y -> forall a b. a -> Either a b
L.Left forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> These a b
These a
x b
y))

-- | A 'Control.Lens.Prism'' selecting the 'That' constructor.
--
-- /Note:/ cannot change type.
_That :: Prism' (These a b) b
_That :: forall a b. Prism' (These a b) b
_That = forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism forall a b. b -> These a b
That (forall a c b.
(a -> c) -> (b -> c) -> (a -> b -> c) -> These a b -> c
these (forall a b. a -> Either a b
L.Left forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> These a b
This) forall a b. b -> Either a b
L.Right (\a
x b
y -> forall a b. a -> Either a b
L.Left forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> These a b
These a
x b
y))

-- | A 'Control.Lens.Prism'' selecting the 'These' constructor. 'These' names are ridiculous!
--
-- /Note:/ cannot change type.
_These :: Prism' (These a b) (a, b)
_These :: forall a b. Prism' (These a b) (a, b)
_These = forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism (\(a
a,b
b) -> forall a b. a -> b -> These a b
These a
a b
b) (forall a c b.
(a -> c) -> (b -> c) -> (a -> b -> c) -> These a b -> c
these (forall a b. a -> Either a b
L.Left forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> These a b
This) (forall a b. a -> Either a b
L.Left forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> These a b
That) (\a
x b
y -> forall a b. b -> Either a b
L.Right (a
x, b
y)))