{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Witch.Utility where

import qualified Control.Exception as Exception
import qualified Data.Coerce as Coerce
import qualified Data.Typeable as Typeable
import qualified GHC.Stack as Stack
import qualified Witch.From as From
import qualified Witch.TryFrom as TryFrom
import qualified Witch.TryFromException as TryFromException

-- | This is the same as 'id'. This can be an ergonomic way to pin down a
-- polymorphic type in a function pipeline. For example:
--
-- > -- Avoid this:
-- > f . (\ x -> x :: Int) . g
-- >
-- > -- Prefer this:
-- > f . as @Int . g
as :: forall source. source -> source
as :: forall source. source -> source
as = forall source. source -> source
id

-- | This is the same as 'From.from' except that the type variables are in the
-- opposite order.
--
-- > -- Avoid this:
-- > from x :: t
-- >
-- > -- Prefer this:
-- > into @t x
into :: forall target source. (From.From source target) => source -> target
into :: forall target source. From source target => source -> target
into = forall source target. From source target => source -> target
From.from

-- | This function converts from some @source@ type into some @target@ type,
-- applies the given function, then converts back into the @source@ type. This
-- is useful when you have two types that are isomorphic but some function
-- that only works with one of them.
--
-- > -- Avoid this:
-- > from @t . f . into @t
-- >
-- > -- Prefer this:
-- > over @t f
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 = forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. target -> target
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target. From source target => source -> target
From.from

-- | This function first converts from some @source@ type into some @through@
-- type, and then converts that into some @target@ type. Usually this is used
-- when writing 'From.From' instances. Sometimes this can be used to work
-- around the lack of an instance that should probably exist.
--
-- > -- Avoid this:
-- > from @u . into @u
-- >
-- > -- Prefer this:
-- > via @u
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 = forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\through
x -> through
x :: through) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target. From source target => source -> target
From.from

-- | This is the same as 'TryFrom.tryFrom' except that the type variables are
-- in the opposite order.
--
-- > -- Avoid this:
-- > tryFrom x :: Either (TryFromException s t) t
-- >
-- > -- Prefer this:
-- > tryInto @t x
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 = forall source target.
TryFrom source target =>
source -> Either (TryFromException source target) target
TryFrom.tryFrom

-- | This is similar to 'via' except that it works with 'TryFrom.TryFrom'
-- instances instead. This function is especially convenient because juggling
-- the types in the 'TryFromException.TryFromException' can be tedious.
--
-- > -- Avoid this:
-- > case tryInto @u x of
-- >   Left (TryFromException _ e) -> Left $ TryFromException x e
-- >   Right y -> case tryFrom @u y of
-- >     Left (TryFromException _ e) -> Left $ TryFromException x e
-- >     Right z -> Right z
-- >
-- > -- Prefer this:
-- > tryVia @u
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 forall source target.
TryFrom source target =>
source -> Either (TryFromException source target) target
TryFrom.tryFrom source
s of
  Left TryFromException source through
e -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ forall newTarget source oldTarget.
TryFromException source oldTarget
-> TryFromException source newTarget
withTarget TryFromException source through
e
  Right through
u -> case forall source target.
TryFrom source target =>
source -> Either (TryFromException source target) target
TryFrom.tryFrom (through
u :: through) of
    Left TryFromException through target
e -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ forall newSource oldSource target.
newSource
-> TryFromException oldSource target
-> TryFromException newSource target
withSource source
s TryFromException through target
e
    Right target
t -> forall a b. b -> Either a b
Right target
t

-- | This function can be used to implement 'TryFrom.tryFrom' with a function
-- that returns 'Maybe'. For example:
--
-- > -- Avoid this:
-- > tryFrom s = case f s of
-- >   Nothing -> Left $ TryFromException s Nothing
-- >   Just t -> Right t
-- >
-- > -- Prefer this:
-- > tryFrom = maybeTryFrom f
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 -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ forall source target.
source -> Maybe SomeException -> TryFromException source target
TryFromException.TryFromException source
s forall a. Maybe a
Nothing
  Just target
t -> forall a b. b -> Either a b
Right target
t

-- | This function can be used to implement 'TryFrom.tryFrom' with a function
-- that returns 'Either'. For example:
--
-- > -- Avoid this:
-- > tryFrom s = case f s of
-- >   Left e -> Left . TryFromException s . Just $ toException e
-- >   Right t -> Right t
-- >
-- > -- Prefer this:
-- > tryFrom = eitherTryFrom f
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 ->
    forall a b. a -> Either a b
Left forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target.
source -> Maybe SomeException -> TryFromException source target
TryFromException.TryFromException source
s forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall e. Exception e => e -> SomeException
Exception.toException exception
e
  Right target
t -> forall a b. b -> Either a b
Right target
t

-- | This function is like 'TryFrom.tryFrom' except that it will throw an
-- impure exception if the conversion fails.
--
-- > -- Avoid this:
-- > either throw id . tryFrom @s
-- >
-- > -- Prefer this:
-- > unsafeFrom @s
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 = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall a e. Exception e => e -> a
Exception.throw forall source. source -> source
id forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target.
TryFrom source target =>
source -> Either (TryFromException source target) target
TryFrom.tryFrom

-- | This function is like 'tryInto' except that it will throw an impure
-- exception if the conversion fails.
--
-- > -- Avoid this:
-- > either throw id . tryInto @t
-- >
-- > -- Prefer this:
-- > unsafeInto @t
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 = 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) =
  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 = coerce :: forall a b. Coercible a b => a -> b
Coerce.coerce