{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Functora.Witch.Utility where
import qualified Control.Exception as Exception
import qualified Data.Coerce as Coerce
import qualified Data.Typeable as Typeable
import qualified Functora.Witch.From as From
import qualified Functora.Witch.TryFrom as TryFrom
import qualified Functora.Witch.TryFromException as TryFromException
import qualified GHC.Stack as Stack
as :: forall source. source -> source
as :: forall source. source -> source
as = source -> source
forall source. source -> source
id
into :: forall target source. (From.From source target) => source -> target
into :: forall target source. From source target => source -> target
into = source -> target
forall source target. From source target => source -> target
From.from
over ::
forall target source.
(From.From source target, From.From target source) =>
(target -> target) ->
source ->
source
over :: forall target source.
(From source target, From target source) =>
(target -> target) -> source -> source
over target -> target
f = target -> source
forall source target. From source target => source -> target
From.from (target -> source) -> (source -> target) -> source -> source
forall b c a. (b -> c) -> (a -> b) -> a -> c
. target -> target
f (target -> target) -> (source -> target) -> source -> target
forall b c a. (b -> c) -> (a -> b) -> a -> c
. source -> target
forall source target. From source target => source -> target
From.from
via ::
forall through source target.
(From.From source through, From.From through target) =>
source ->
target
via :: forall through source target.
(From source through, From through target) =>
source -> target
via = through -> target
forall source target. From source target => source -> target
From.from (through -> target) -> (source -> through) -> source -> target
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\through
x -> through
x :: through) (through -> through) -> (source -> through) -> source -> through
forall b c a. (b -> c) -> (a -> b) -> a -> c
. source -> through
forall source target. From source target => source -> target
From.from
tryInto ::
forall target source.
(TryFrom.TryFrom source target) =>
source ->
Either (TryFromException.TryFromException source target) target
tryInto :: forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
tryInto = source -> Either (TryFromException source target) target
forall source target.
TryFrom source target =>
source -> Either (TryFromException source target) target
TryFrom.tryFrom
tryVia ::
forall through source target.
(TryFrom.TryFrom source through, TryFrom.TryFrom through target) =>
source ->
Either (TryFromException.TryFromException source target) target
tryVia :: forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
tryVia source
s = case source -> Either (TryFromException source through) through
forall source target.
TryFrom source target =>
source -> Either (TryFromException source target) target
TryFrom.tryFrom source
s of
Left TryFromException source through
e -> TryFromException source target
-> Either (TryFromException source target) target
forall a b. a -> Either a b
Left (TryFromException source target
-> Either (TryFromException source target) target)
-> TryFromException source target
-> Either (TryFromException source target) target
forall a b. (a -> b) -> a -> b
$ TryFromException source through -> TryFromException source target
forall newTarget source oldTarget.
TryFromException source oldTarget
-> TryFromException source newTarget
withTarget TryFromException source through
e
Right through
u -> case through -> Either (TryFromException through target) target
forall source target.
TryFrom source target =>
source -> Either (TryFromException source target) target
TryFrom.tryFrom (through
u :: through) of
Left TryFromException through target
e -> TryFromException source target
-> Either (TryFromException source target) target
forall a b. a -> Either a b
Left (TryFromException source target
-> Either (TryFromException source target) target)
-> TryFromException source target
-> Either (TryFromException source target) target
forall a b. (a -> b) -> a -> b
$ source
-> TryFromException through target
-> TryFromException source target
forall newSource oldSource target.
newSource
-> TryFromException oldSource target
-> TryFromException newSource target
withSource source
s TryFromException through target
e
Right target
t -> target -> Either (TryFromException source target) target
forall a b. b -> Either a b
Right target
t
maybeTryFrom ::
(source -> Maybe target) ->
source ->
Either (TryFromException.TryFromException source target) target
maybeTryFrom :: forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
maybeTryFrom source -> Maybe target
f source
s = case source -> Maybe target
f source
s of
Maybe target
Nothing -> TryFromException source target
-> Either (TryFromException source target) target
forall a b. a -> Either a b
Left (TryFromException source target
-> Either (TryFromException source target) target)
-> TryFromException source target
-> Either (TryFromException source target) target
forall a b. (a -> b) -> a -> b
$ source -> Maybe SomeException -> TryFromException source target
forall source target.
source -> Maybe SomeException -> TryFromException source target
TryFromException.TryFromException source
s Maybe SomeException
forall a. Maybe a
Nothing
Just target
t -> target -> Either (TryFromException source target) target
forall a b. b -> Either a b
Right target
t
eitherTryFrom ::
(Exception.Exception exception) =>
(source -> Either exception target) ->
source ->
Either (TryFromException.TryFromException source target) target
eitherTryFrom :: forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
eitherTryFrom source -> Either exception target
f source
s = case source -> Either exception target
f source
s of
Left exception
e ->
TryFromException source target
-> Either (TryFromException source target) target
forall a b. a -> Either a b
Left (TryFromException source target
-> Either (TryFromException source target) target)
-> (SomeException -> TryFromException source target)
-> SomeException
-> Either (TryFromException source target) target
forall b c a. (b -> c) -> (a -> b) -> a -> c
. source -> Maybe SomeException -> TryFromException source target
forall source target.
source -> Maybe SomeException -> TryFromException source target
TryFromException.TryFromException source
s (Maybe SomeException -> TryFromException source target)
-> (SomeException -> Maybe SomeException)
-> SomeException
-> TryFromException source target
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> Maybe SomeException
forall a. a -> Maybe a
Just (SomeException -> Either (TryFromException source target) target)
-> SomeException -> Either (TryFromException source target) target
forall a b. (a -> b) -> a -> b
$ exception -> SomeException
forall e. Exception e => e -> SomeException
Exception.toException exception
e
Right target
t -> target -> Either (TryFromException source target) target
forall a b. b -> Either a b
Right target
t
unsafeFrom ::
forall source target.
( Stack.HasCallStack,
TryFrom.TryFrom source target,
Show source,
Typeable.Typeable source,
Typeable.Typeable target
) =>
source ->
target
unsafeFrom :: forall source target.
(HasCallStack, TryFrom source target, Show source, Typeable source,
Typeable target) =>
source -> target
unsafeFrom = (TryFromException source target -> target)
-> (target -> target)
-> Either (TryFromException source target) target
-> target
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either TryFromException source target -> target
forall a e. Exception e => e -> a
Exception.throw target -> target
forall source. source -> source
id (Either (TryFromException source target) target -> target)
-> (source -> Either (TryFromException source target) target)
-> source
-> target
forall b c a. (b -> c) -> (a -> b) -> a -> c
. source -> Either (TryFromException source target) target
forall source target.
TryFrom source target =>
source -> Either (TryFromException source target) target
TryFrom.tryFrom
unsafeInto ::
forall target source.
( Stack.HasCallStack,
TryFrom.TryFrom source target,
Show source,
Typeable.Typeable source,
Typeable.Typeable target
) =>
source ->
target
unsafeInto :: forall target source.
(HasCallStack, TryFrom source target, Show source, Typeable source,
Typeable target) =>
source -> target
unsafeInto = source -> target
forall source target.
(HasCallStack, TryFrom source target, Show source, Typeable source,
Typeable target) =>
source -> target
unsafeFrom
withSource ::
newSource ->
TryFromException.TryFromException oldSource target ->
TryFromException.TryFromException newSource target
withSource :: forall newSource oldSource target.
newSource
-> TryFromException oldSource target
-> TryFromException newSource target
withSource newSource
x (TryFromException.TryFromException oldSource
_ Maybe SomeException
e) =
newSource
-> Maybe SomeException -> TryFromException newSource target
forall source target.
source -> Maybe SomeException -> TryFromException source target
TryFromException.TryFromException newSource
x Maybe SomeException
e
withTarget ::
forall newTarget source oldTarget.
TryFromException.TryFromException source oldTarget ->
TryFromException.TryFromException source newTarget
withTarget :: forall newTarget source oldTarget.
TryFromException source oldTarget
-> TryFromException source newTarget
withTarget = TryFromException source oldTarget
-> TryFromException source newTarget
forall a b. Coercible a b => a -> b
Coerce.coerce