module Network.IRC.Client.Lens where
import Control.Concurrent.STM (TVar)
import Control.Monad.Catch (SomeException)
import Data.ByteString (ByteString)
import Data.Profunctor (Choice(right'),
Profunctor(dimap))
import Data.Text (Text)
import Data.Time (NominalDiffTime)
import Network.IRC.Client.Internal.Lens
import Network.IRC.Client.Internal.Types
{-# ANN module ("HLint: ignore Redundant lambda") #-}
{-# INLINE connectionConfig #-}
connectionConfig :: Getter (IRCState s) (ConnectionConfig s)
connectionConfig :: (ConnectionConfig s -> f (ConnectionConfig s))
-> IRCState s -> f (IRCState s)
connectionConfig = \ ConnectionConfig s -> f (ConnectionConfig s)
afb IRCState s
s -> (\ ConnectionConfig s
b -> IRCState s
s {_connectionConfig :: ConnectionConfig s
_connectionConfig = ConnectionConfig s
b}) (ConnectionConfig s -> IRCState s)
-> f (ConnectionConfig s) -> f (IRCState s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ConnectionConfig s -> f (ConnectionConfig s)
afb (IRCState s -> ConnectionConfig s
forall s. IRCState s -> ConnectionConfig s
_connectionConfig IRCState s
s)
{-# INLINE userState #-}
userState :: Lens' (IRCState s) (TVar s)
userState :: (TVar s -> f (TVar s)) -> IRCState s -> f (IRCState s)
userState = \ TVar s -> f (TVar s)
afb IRCState s
s -> (\ TVar s
b -> IRCState s
s {_userState :: TVar s
_userState = TVar s
b}) (TVar s -> IRCState s) -> f (TVar s) -> f (IRCState s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TVar s -> f (TVar s)
afb (IRCState s -> TVar s
forall s. IRCState s -> TVar s
_userState IRCState s
s)
{-# INLINE instanceConfig #-}
instanceConfig :: Lens' (IRCState s) (TVar (InstanceConfig s))
instanceConfig :: (TVar (InstanceConfig s) -> f (TVar (InstanceConfig s)))
-> IRCState s -> f (IRCState s)
instanceConfig = \ TVar (InstanceConfig s) -> f (TVar (InstanceConfig s))
afb IRCState s
s -> (\ TVar (InstanceConfig s)
b -> IRCState s
s {_instanceConfig :: TVar (InstanceConfig s)
_instanceConfig = TVar (InstanceConfig s)
b}) (TVar (InstanceConfig s) -> IRCState s)
-> f (TVar (InstanceConfig s)) -> f (IRCState s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TVar (InstanceConfig s) -> f (TVar (InstanceConfig s))
afb (IRCState s -> TVar (InstanceConfig s)
forall s. IRCState s -> TVar (InstanceConfig s)
_instanceConfig IRCState s
s)
{-# INLINE connectionState #-}
connectionState :: Lens' (IRCState s) (TVar ConnectionState)
connectionState :: (TVar ConnectionState -> f (TVar ConnectionState))
-> IRCState s -> f (IRCState s)
connectionState = \ TVar ConnectionState -> f (TVar ConnectionState)
afb IRCState s
s -> (\ TVar ConnectionState
b -> IRCState s
s {_connectionState :: TVar ConnectionState
_connectionState = TVar ConnectionState
b}) (TVar ConnectionState -> IRCState s)
-> f (TVar ConnectionState) -> f (IRCState s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TVar ConnectionState -> f (TVar ConnectionState)
afb (IRCState s -> TVar ConnectionState
forall s. IRCState s -> TVar ConnectionState
_connectionState IRCState s
s)
{-# INLINE server #-}
server :: Getter (ConnectionConfig s) ByteString
server :: (ByteString -> f ByteString)
-> ConnectionConfig s -> f (ConnectionConfig s)
server = \ ByteString -> f ByteString
afb ConnectionConfig s
s -> (\ ByteString
b -> ConnectionConfig s
s {_server :: ByteString
_server = ByteString
b}) (ByteString -> ConnectionConfig s)
-> f ByteString -> f (ConnectionConfig s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> f ByteString
afb (ConnectionConfig s -> ByteString
forall s. ConnectionConfig s -> ByteString
_server ConnectionConfig s
s)
{-# INLINE port #-}
port :: Getter (ConnectionConfig s) Int
port :: (Int -> f Int) -> ConnectionConfig s -> f (ConnectionConfig s)
port = \ Int -> f Int
afb ConnectionConfig s
s -> (\ Int
b -> ConnectionConfig s
s {_port :: Int
_port = Int
b}) (Int -> ConnectionConfig s) -> f Int -> f (ConnectionConfig s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> f Int
afb (ConnectionConfig s -> Int
forall s. ConnectionConfig s -> Int
_port ConnectionConfig s
s)
{-# INLINE username #-}
username :: Lens' (ConnectionConfig s) Text
username :: (Text -> f Text) -> ConnectionConfig s -> f (ConnectionConfig s)
username = \ Text -> f Text
afb ConnectionConfig s
s -> (\ Text
b -> ConnectionConfig s
s {_username :: Text
_username = Text
b}) (Text -> ConnectionConfig s) -> f Text -> f (ConnectionConfig s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> f Text
afb (ConnectionConfig s -> Text
forall s. ConnectionConfig s -> Text
_username ConnectionConfig s
s)
{-# INLINE realname #-}
realname :: Lens' (ConnectionConfig s) Text
realname :: (Text -> f Text) -> ConnectionConfig s -> f (ConnectionConfig s)
realname = \ Text -> f Text
afb ConnectionConfig s
s -> (\ Text
b -> ConnectionConfig s
s {_realname :: Text
_realname = Text
b}) (Text -> ConnectionConfig s) -> f Text -> f (ConnectionConfig s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> f Text
afb (ConnectionConfig s -> Text
forall s. ConnectionConfig s -> Text
_realname ConnectionConfig s
s)
{-# INLINE password #-}
password :: Lens' (ConnectionConfig s) (Maybe Text)
password :: (Maybe Text -> f (Maybe Text))
-> ConnectionConfig s -> f (ConnectionConfig s)
password = \ Maybe Text -> f (Maybe Text)
afb ConnectionConfig s
s -> (\ Maybe Text
b -> ConnectionConfig s
s {_password :: Maybe Text
_password = Maybe Text
b}) (Maybe Text -> ConnectionConfig s)
-> f (Maybe Text) -> f (ConnectionConfig s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text -> f (Maybe Text)
afb (ConnectionConfig s -> Maybe Text
forall s. ConnectionConfig s -> Maybe Text
_password ConnectionConfig s
s)
{-# INLINE flood #-}
flood :: Lens' (ConnectionConfig s) NominalDiffTime
flood :: (NominalDiffTime -> f NominalDiffTime)
-> ConnectionConfig s -> f (ConnectionConfig s)
flood = \ NominalDiffTime -> f NominalDiffTime
afb ConnectionConfig s
s -> (\ NominalDiffTime
b -> ConnectionConfig s
s {_flood :: NominalDiffTime
_flood = NominalDiffTime
b}) (NominalDiffTime -> ConnectionConfig s)
-> f NominalDiffTime -> f (ConnectionConfig s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NominalDiffTime -> f NominalDiffTime
afb (ConnectionConfig s -> NominalDiffTime
forall s. ConnectionConfig s -> NominalDiffTime
_flood ConnectionConfig s
s)
{-# INLINE timeout #-}
timeout :: Lens' (ConnectionConfig s) NominalDiffTime
timeout :: (NominalDiffTime -> f NominalDiffTime)
-> ConnectionConfig s -> f (ConnectionConfig s)
timeout = \ NominalDiffTime -> f NominalDiffTime
afb ConnectionConfig s
s -> (\ NominalDiffTime
b -> ConnectionConfig s
s {_timeout :: NominalDiffTime
_timeout = NominalDiffTime
b}) (NominalDiffTime -> ConnectionConfig s)
-> f NominalDiffTime -> f (ConnectionConfig s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NominalDiffTime -> f NominalDiffTime
afb (ConnectionConfig s -> NominalDiffTime
forall s. ConnectionConfig s -> NominalDiffTime
_timeout ConnectionConfig s
s)
{-# INLINE onconnect #-}
onconnect :: Lens' (ConnectionConfig s) (IRC s ())
onconnect :: (IRC s () -> f (IRC s ()))
-> ConnectionConfig s -> f (ConnectionConfig s)
onconnect = \ IRC s () -> f (IRC s ())
afb ConnectionConfig s
s -> (\ IRC s ()
b -> ConnectionConfig s
s {_onconnect :: IRC s ()
_onconnect = IRC s ()
b}) (IRC s () -> ConnectionConfig s)
-> f (IRC s ()) -> f (ConnectionConfig s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IRC s () -> f (IRC s ())
afb (ConnectionConfig s -> IRC s ()
forall s. ConnectionConfig s -> IRC s ()
_onconnect ConnectionConfig s
s)
{-# INLINE ondisconnect #-}
ondisconnect :: Lens' (ConnectionConfig s) (Maybe SomeException -> IRC s ())
ondisconnect :: ((Maybe SomeException -> IRC s ())
-> f (Maybe SomeException -> IRC s ()))
-> ConnectionConfig s -> f (ConnectionConfig s)
ondisconnect = \ (Maybe SomeException -> IRC s ())
-> f (Maybe SomeException -> IRC s ())
afb ConnectionConfig s
s -> (\ Maybe SomeException -> IRC s ()
b -> ConnectionConfig s
s {_ondisconnect :: Maybe SomeException -> IRC s ()
_ondisconnect = Maybe SomeException -> IRC s ()
b}) ((Maybe SomeException -> IRC s ()) -> ConnectionConfig s)
-> f (Maybe SomeException -> IRC s ()) -> f (ConnectionConfig s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Maybe SomeException -> IRC s ())
-> f (Maybe SomeException -> IRC s ())
afb (ConnectionConfig s -> Maybe SomeException -> IRC s ()
forall s. ConnectionConfig s -> Maybe SomeException -> IRC s ()
_ondisconnect ConnectionConfig s
s)
{-# INLINE logfunc #-}
logfunc :: Lens' (ConnectionConfig s) (Origin -> ByteString -> IO ())
logfunc :: ((Origin -> ByteString -> IO ())
-> f (Origin -> ByteString -> IO ()))
-> ConnectionConfig s -> f (ConnectionConfig s)
logfunc = \ (Origin -> ByteString -> IO ())
-> f (Origin -> ByteString -> IO ())
afb ConnectionConfig s
s -> (\ Origin -> ByteString -> IO ()
b -> ConnectionConfig s
s {_logfunc :: Origin -> ByteString -> IO ()
_logfunc = Origin -> ByteString -> IO ()
b}) ((Origin -> ByteString -> IO ()) -> ConnectionConfig s)
-> f (Origin -> ByteString -> IO ()) -> f (ConnectionConfig s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Origin -> ByteString -> IO ())
-> f (Origin -> ByteString -> IO ())
afb (ConnectionConfig s -> Origin -> ByteString -> IO ()
forall s. ConnectionConfig s -> Origin -> ByteString -> IO ()
_logfunc ConnectionConfig s
s)
{-# INLINE nick #-}
nick :: Lens' (InstanceConfig s) Text
nick :: (Text -> f Text) -> InstanceConfig s -> f (InstanceConfig s)
nick = \ Text -> f Text
afb InstanceConfig s
s -> (\ Text
b -> InstanceConfig s
s {_nick :: Text
_nick = Text
b}) (Text -> InstanceConfig s) -> f Text -> f (InstanceConfig s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> f Text
afb (InstanceConfig s -> Text
forall s. InstanceConfig s -> Text
_nick InstanceConfig s
s)
{-# INLINE channels #-}
channels :: Lens' (InstanceConfig s) [Text]
channels :: ([Text] -> f [Text]) -> InstanceConfig s -> f (InstanceConfig s)
channels = \ [Text] -> f [Text]
afb InstanceConfig s
s -> (\ [Text]
b -> InstanceConfig s
s {_channels :: [Text]
_channels = [Text]
b}) ([Text] -> InstanceConfig s) -> f [Text] -> f (InstanceConfig s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Text] -> f [Text]
afb (InstanceConfig s -> [Text]
forall s. InstanceConfig s -> [Text]
_channels InstanceConfig s
s)
{-# INLINE version #-}
version :: Lens' (InstanceConfig s) Text
version :: (Text -> f Text) -> InstanceConfig s -> f (InstanceConfig s)
version = \ Text -> f Text
afb InstanceConfig s
s -> (\ Text
b -> InstanceConfig s
s {_version :: Text
_version = Text
b}) (Text -> InstanceConfig s) -> f Text -> f (InstanceConfig s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> f Text
afb (InstanceConfig s -> Text
forall s. InstanceConfig s -> Text
_version InstanceConfig s
s)
{-# INLINE handlers #-}
handlers :: Lens' (InstanceConfig s) [EventHandler s]
handlers :: ([EventHandler s] -> f [EventHandler s])
-> InstanceConfig s -> f (InstanceConfig s)
handlers = \ [EventHandler s] -> f [EventHandler s]
afb InstanceConfig s
s -> (\ [EventHandler s]
b -> InstanceConfig s
s {_handlers :: [EventHandler s]
_handlers = [EventHandler s]
b}) ([EventHandler s] -> InstanceConfig s)
-> f [EventHandler s] -> f (InstanceConfig s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [EventHandler s] -> f [EventHandler s]
afb (InstanceConfig s -> [EventHandler s]
forall s. InstanceConfig s -> [EventHandler s]
_handlers InstanceConfig s
s)
{-# INLINE ignore #-}
ignore :: Lens' (InstanceConfig s) [(Text, Maybe Text)]
ignore :: ([(Text, Maybe Text)] -> f [(Text, Maybe Text)])
-> InstanceConfig s -> f (InstanceConfig s)
ignore = \ [(Text, Maybe Text)] -> f [(Text, Maybe Text)]
afb InstanceConfig s
s -> (\ [(Text, Maybe Text)]
b -> InstanceConfig s
s {_ignore :: [(Text, Maybe Text)]
_ignore = [(Text, Maybe Text)]
b}) ([(Text, Maybe Text)] -> InstanceConfig s)
-> f [(Text, Maybe Text)] -> f (InstanceConfig s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Text, Maybe Text)] -> f [(Text, Maybe Text)]
afb (InstanceConfig s -> [(Text, Maybe Text)]
forall s. InstanceConfig s -> [(Text, Maybe Text)]
_ignore InstanceConfig s
s)
{-# INLINE _Connected #-}
_Connected :: Prism' ConnectionState ()
_Connected :: p () (f ()) -> p ConnectionState (f ConnectionState)
_Connected = (ConnectionState -> Either ConnectionState ())
-> (Either ConnectionState (f ()) -> f ConnectionState)
-> p (Either ConnectionState ()) (Either ConnectionState (f ()))
-> p ConnectionState (f ConnectionState)
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap (\ ConnectionState
s -> case ConnectionState
s of ConnectionState
Connected -> () -> Either ConnectionState ()
forall a b. b -> Either a b
Right (); ConnectionState
_ -> ConnectionState -> Either ConnectionState ()
forall a b. a -> Either a b
Left ConnectionState
s)
((ConnectionState -> f ConnectionState)
-> (f () -> f ConnectionState)
-> Either ConnectionState (f ())
-> f ConnectionState
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ConnectionState -> f ConnectionState
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((f () -> f ConnectionState)
-> Either ConnectionState (f ()) -> f ConnectionState)
-> (f () -> f ConnectionState)
-> Either ConnectionState (f ())
-> f ConnectionState
forall a b. (a -> b) -> a -> b
$ (() -> ConnectionState) -> f () -> f ConnectionState
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ () -> ConnectionState
Connected)) (p (Either ConnectionState ()) (Either ConnectionState (f ()))
-> p ConnectionState (f ConnectionState))
-> (p () (f ())
-> p (Either ConnectionState ()) (Either ConnectionState (f ())))
-> p () (f ())
-> p ConnectionState (f ConnectionState)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ())
-> p (Either ConnectionState ()) (Either ConnectionState (f ()))
forall (p :: * -> * -> *) a b c.
Choice p =>
p a b -> p (Either c a) (Either c b)
right'
{-# INLINE _Disconnecting #-}
_Disconnecting :: Prism' ConnectionState ()
_Disconnecting :: p () (f ()) -> p ConnectionState (f ConnectionState)
_Disconnecting = (ConnectionState -> Either ConnectionState ())
-> (Either ConnectionState (f ()) -> f ConnectionState)
-> p (Either ConnectionState ()) (Either ConnectionState (f ()))
-> p ConnectionState (f ConnectionState)
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap (\ ConnectionState
s -> case ConnectionState
s of ConnectionState
Disconnecting -> () -> Either ConnectionState ()
forall a b. b -> Either a b
Right (); ConnectionState
_ -> ConnectionState -> Either ConnectionState ()
forall a b. a -> Either a b
Left ConnectionState
s)
((ConnectionState -> f ConnectionState)
-> (f () -> f ConnectionState)
-> Either ConnectionState (f ())
-> f ConnectionState
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ConnectionState -> f ConnectionState
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((f () -> f ConnectionState)
-> Either ConnectionState (f ()) -> f ConnectionState)
-> (f () -> f ConnectionState)
-> Either ConnectionState (f ())
-> f ConnectionState
forall a b. (a -> b) -> a -> b
$ (() -> ConnectionState) -> f () -> f ConnectionState
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ () -> ConnectionState
Disconnecting)) (p (Either ConnectionState ()) (Either ConnectionState (f ()))
-> p ConnectionState (f ConnectionState))
-> (p () (f ())
-> p (Either ConnectionState ()) (Either ConnectionState (f ())))
-> p () (f ())
-> p ConnectionState (f ConnectionState)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ())
-> p (Either ConnectionState ()) (Either ConnectionState (f ()))
forall (p :: * -> * -> *) a b c.
Choice p =>
p a b -> p (Either c a) (Either c b)
right'
{-# INLINE _Disconnected #-}
_Disconnected :: Prism' ConnectionState ()
_Disconnected :: p () (f ()) -> p ConnectionState (f ConnectionState)
_Disconnected = (ConnectionState -> Either ConnectionState ())
-> (Either ConnectionState (f ()) -> f ConnectionState)
-> p (Either ConnectionState ()) (Either ConnectionState (f ()))
-> p ConnectionState (f ConnectionState)
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap (\ ConnectionState
s -> case ConnectionState
s of ConnectionState
Disconnected -> () -> Either ConnectionState ()
forall a b. b -> Either a b
Right (); ConnectionState
_ -> ConnectionState -> Either ConnectionState ()
forall a b. a -> Either a b
Left ConnectionState
s)
((ConnectionState -> f ConnectionState)
-> (f () -> f ConnectionState)
-> Either ConnectionState (f ())
-> f ConnectionState
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ConnectionState -> f ConnectionState
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((f () -> f ConnectionState)
-> Either ConnectionState (f ()) -> f ConnectionState)
-> (f () -> f ConnectionState)
-> Either ConnectionState (f ())
-> f ConnectionState
forall a b. (a -> b) -> a -> b
$ (() -> ConnectionState) -> f () -> f ConnectionState
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ () -> ConnectionState
Disconnected)) (p (Either ConnectionState ()) (Either ConnectionState (f ()))
-> p ConnectionState (f ConnectionState))
-> (p () (f ())
-> p (Either ConnectionState ()) (Either ConnectionState (f ())))
-> p () (f ())
-> p ConnectionState (f ConnectionState)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ())
-> p (Either ConnectionState ()) (Either ConnectionState (f ()))
forall (p :: * -> * -> *) a b c.
Choice p =>
p a b -> p (Either c a) (Either c b)
right'
{-# INLINE _FromServer #-}
_FromServer :: Prism' Origin ()
_FromServer :: p () (f ()) -> p Origin (f Origin)
_FromServer = (Origin -> Either Origin ())
-> (Either Origin (f ()) -> f Origin)
-> p (Either Origin ()) (Either Origin (f ()))
-> p Origin (f Origin)
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap (\ Origin
s -> case Origin
s of Origin
FromServer -> () -> Either Origin ()
forall a b. b -> Either a b
Right (); Origin
_ -> Origin -> Either Origin ()
forall a b. a -> Either a b
Left Origin
s)
((Origin -> f Origin)
-> (f () -> f Origin) -> Either Origin (f ()) -> f Origin
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either Origin -> f Origin
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((f () -> f Origin) -> Either Origin (f ()) -> f Origin)
-> (f () -> f Origin) -> Either Origin (f ()) -> f Origin
forall a b. (a -> b) -> a -> b
$ (() -> Origin) -> f () -> f Origin
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ () -> Origin
FromServer)) (p (Either Origin ()) (Either Origin (f ()))
-> p Origin (f Origin))
-> (p () (f ()) -> p (Either Origin ()) (Either Origin (f ())))
-> p () (f ())
-> p Origin (f Origin)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p (Either Origin ()) (Either Origin (f ()))
forall (p :: * -> * -> *) a b c.
Choice p =>
p a b -> p (Either c a) (Either c b)
right'
{-# INLINE _FromClient #-}
_FromClient :: Prism' Origin ()
_FromClient :: p () (f ()) -> p Origin (f Origin)
_FromClient = (Origin -> Either Origin ())
-> (Either Origin (f ()) -> f Origin)
-> p (Either Origin ()) (Either Origin (f ()))
-> p Origin (f Origin)
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap (\ Origin
s -> case Origin
s of Origin
FromClient -> () -> Either Origin ()
forall a b. b -> Either a b
Right (); Origin
_ -> Origin -> Either Origin ()
forall a b. a -> Either a b
Left Origin
s)
((Origin -> f Origin)
-> (f () -> f Origin) -> Either Origin (f ()) -> f Origin
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either Origin -> f Origin
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((f () -> f Origin) -> Either Origin (f ()) -> f Origin)
-> (f () -> f Origin) -> Either Origin (f ()) -> f Origin
forall a b. (a -> b) -> a -> b
$ (() -> Origin) -> f () -> f Origin
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ () -> Origin
FromClient)) (p (Either Origin ()) (Either Origin (f ()))
-> p Origin (f Origin))
-> (p () (f ()) -> p (Either Origin ()) (Either Origin (f ())))
-> p () (f ())
-> p Origin (f Origin)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p (Either Origin ()) (Either Origin (f ()))
forall (p :: * -> * -> *) a b c.
Choice p =>
p a b -> p (Either c a) (Either c b)
right'