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

module Witch.Utility where

import qualified Control.Exception as Exception
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 :: source -> source
as = source -> source
forall a. a -> a
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 :: source -> target
into = source -> target
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 :: (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

-- | 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 :: 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

-- | 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 :: 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

-- | 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 :: 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.TryFromException source
_ Maybe SomeException
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 -> Maybe SomeException -> TryFromException source target
forall source target.
source -> Maybe SomeException -> TryFromException source target
TryFromException.TryFromException source
s Maybe SomeException
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.TryFromException through
_ Maybe SomeException
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 -> Maybe SomeException -> TryFromException source target
forall source target.
source -> Maybe SomeException -> TryFromException source target
TryFromException.TryFromException source
s Maybe SomeException
e
    Right target
t -> target -> Either (TryFromException source target) target
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 :: (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

-- | 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 :: (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

-- | 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 :: 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 a. a -> a
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

-- | 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 :: source -> target
unsafeInto = source -> target
forall source target.
(HasCallStack, TryFrom source target, Show source, Typeable source,
 Typeable target) =>
source -> target
unsafeFrom