Rename TryCastException to TryFromException

This commit is contained in:
Taylor Fausak 2021-05-10 19:36:22 -04:00
parent 57d0695778
commit 1b55654c86
7 changed files with 45 additions and 45 deletions

View File

@ -51,7 +51,7 @@ module Witch
, Witch.Lift.liftedInto
-- * Data types
, Witch.TryCastException.TryCastException(..)
, Witch.TryFromException.TryFromException(..)
-- * Notes
@ -163,5 +163,5 @@ import qualified Witch.From
import Witch.Instances ()
import qualified Witch.Lift
import qualified Witch.TryFrom
import qualified Witch.TryCastException
import qualified Witch.TryFromException
import qualified Witch.Utility

View File

@ -31,7 +31,7 @@ import qualified GHC.Float as Float
import qualified Numeric.Natural as Natural
import qualified Witch.From as From
import qualified Witch.TryFrom as TryFrom
import qualified Witch.TryCastException as TryCastException
import qualified Witch.TryFromException as TryFromException
import qualified Witch.Utility as Utility
-- Int8
@ -1073,19 +1073,19 @@ instance From.From LazyText.Text Text.Text where
instance From.From LazyText.Text LazyByteString.ByteString where
from = LazyText.encodeUtf8
-- TryCastException
-- TryFromException
-- | Uses @coerce@.
instance From.From
(TryCastException.TryCastException s u)
(TryCastException.TryCastException s t)
(TryFromException.TryFromException s u)
(TryFromException.TryFromException s t)
-- | Uses 'show'.
instance
( Show s
, Typeable.Typeable s
, Typeable.Typeable t
) => From.From (TryCastException.TryCastException s t) String where
) => From.From (TryFromException.TryFromException s t) String where
from = show
-- | Converts via 'String'.
@ -1093,7 +1093,7 @@ instance
( Show s
, Typeable.Typeable s
, Typeable.Typeable t
) => From.From (TryCastException.TryCastException s t) Text.Text where
) => From.From (TryFromException.TryFromException s t) Text.Text where
from = Utility.via @String
-- | Converts via 'String'.
@ -1101,7 +1101,7 @@ instance
( Show s
, Typeable.Typeable s
, Typeable.Typeable t
) => From.From (TryCastException.TryCastException s t) LazyText.Text where
) => From.From (TryFromException.TryFromException s t) LazyText.Text where
from = Utility.via @String
fromNonNegativeIntegral

View File

@ -2,7 +2,7 @@
module Witch.TryFrom where
import qualified Witch.TryCastException as TryCastException
import qualified Witch.TryFromException as TryFromException
-- | This type class is for converting values from some @source@ type into
-- some other @target@ type. The constraint @TryFrom source target@ means that
@ -18,4 +18,4 @@ class TryFrom source target where
--
-- Consider using @maybeTryCast@ or @eitherTryCast@ to implement this
-- method.
tryFrom :: source -> Either (TryCastException.TryCastException source target) target
tryFrom :: source -> Either (TryFromException.TryFromException source target) target

View File

@ -1,6 +1,6 @@
{-# LANGUAGE ScopedTypeVariables #-}
module Witch.TryCastException where
module Witch.TryFromException where
import qualified Control.Exception as Exception
import qualified Data.Proxy as Proxy
@ -11,7 +11,7 @@ import qualified Data.Typeable as Typeable
-- type it was trying to convert into. It also has an optional
-- 'Exception.SomeException' for communicating what went wrong while
-- converting.
data TryCastException source target = TryCastException
data TryFromException source target = TryFromException
source
(Maybe Exception.SomeException)
@ -19,10 +19,10 @@ instance
( Show source
, Typeable.Typeable source
, Typeable.Typeable target
) => Show (TryCastException source target) where
showsPrec d (TryCastException x e) =
) => Show (TryFromException source target) where
showsPrec d (TryFromException x e) =
showParen (d > 10)
$ showString "TryCastException @"
$ showString "TryFromException @"
. showsPrec 11 (Typeable.typeRep (Proxy.Proxy :: Proxy.Proxy source))
. showString " @"
. showsPrec 11 (Typeable.typeRep (Proxy.Proxy :: Proxy.Proxy target))
@ -35,4 +35,4 @@ instance
( Show source
, Typeable.Typeable source
, Typeable.Typeable target
) => Exception.Exception (TryCastException source target)
) => Exception.Exception (TryFromException source target)

View File

@ -8,7 +8,7 @@ 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.TryCastException as TryCastException
import qualified Witch.TryFromException as TryFromException
-- | This is the same as 'id' except that it requires a type application. This
-- can be an ergonomic way to pin down a polymorphic type in a function
@ -80,7 +80,7 @@ via = From.from . (\x -> x :: through) . From.from
-- application for the @target@ type.
--
-- > -- Avoid this:
-- > tryFrom x :: Either (TryCastException s t) t
-- > tryFrom x :: Either (TryFromException s t) t
-- >
-- > -- Prefer this:
-- > tryInto @t x
@ -88,12 +88,12 @@ tryInto
:: forall target source
. TryFrom.TryFrom source target
=> source
-> Either (TryCastException.TryCastException source target) target
-> Either (TryFromException.TryFromException source target) target
tryInto = 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 'TryCastException.TryCastException' can be tedious.
-- the types in the 'TryFromException.TryFromException' can be tedious.
--
-- > -- Avoid this:
-- > case tryInto @u x of
@ -110,13 +110,13 @@ tryVia
, TryFrom.TryFrom through target
)
=> source
-> Either (TryCastException.TryCastException source target) target
-> Either (TryFromException.TryFromException source target) target
tryVia s = case TryFrom.tryFrom s of
Left (TryCastException.TryCastException _ e) ->
Left $ TryCastException.TryCastException s e
Left (TryFromException.TryFromException _ e) ->
Left $ TryFromException.TryFromException s e
Right u -> case TryFrom.tryFrom (u :: through) of
Left (TryCastException.TryCastException _ e) ->
Left $ TryCastException.TryCastException s e
Left (TryFromException.TryFromException _ e) ->
Left $ TryFromException.TryFromException s e
Right t -> Right t
-- | This function can be used to implement 'TryFrom.tryFrom' with a function
@ -124,7 +124,7 @@ tryVia s = case TryFrom.tryFrom s of
--
-- > -- Avoid this:
-- > tryFrom s = case f s of
-- > Nothing -> Left $ TryCastException s Nothing
-- > Nothing -> Left $ TryFromException s Nothing
-- > Just t -> Right t
-- >
-- > -- Prefer this:
@ -132,9 +132,9 @@ tryVia s = case TryFrom.tryFrom s of
maybeTryCast
:: (source -> Maybe target)
-> source
-> Either (TryCastException.TryCastException source target) target
-> Either (TryFromException.TryFromException source target) target
maybeTryCast f s = case f s of
Nothing -> Left $ TryCastException.TryCastException s Nothing
Nothing -> Left $ TryFromException.TryFromException s Nothing
Just t -> Right t
-- | This function can be used to implement 'TryFrom.tryFrom' with a function
@ -142,7 +142,7 @@ maybeTryCast f s = case f s of
--
-- > -- Avoid this:
-- > tryFrom s = case f s of
-- > Left e -> Left . TryCastException s . Just $ toException e
-- > Left e -> Left . TryFromException s . Just $ toException e
-- > Right t -> Right t
-- >
-- > -- Prefer this:
@ -151,10 +151,10 @@ eitherTryCast
:: Exception.Exception exception
=> (source -> Either exception target)
-> source
-> Either (TryCastException.TryCastException source target) target
-> Either (TryFromException.TryFromException source target) target
eitherTryCast f s = case f s of
Left e ->
Left . TryCastException.TryCastException s . Just $ Exception.toException e
Left . TryFromException.TryFromException s . Just $ Exception.toException e
Right t -> Right t
-- | This function is like 'TryFrom.tryFrom' except that it will throw an

View File

@ -1636,23 +1636,23 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f (LazyText.pack "") `Hspec.shouldBe` LazyByteString.pack []
test $ f (LazyText.pack "a") `Hspec.shouldBe` LazyByteString.pack [0x61]
-- TryCastException
-- TryFromException
Hspec.describe "From (TryCastException s t0) (TryCastException s t1)" $ do
Hspec.describe "From (TryFromException s t0) (TryFromException s t1)" $ do
Hspec.it "needs tests" Hspec.pending
Hspec.describe "From (TryCastException s t) String" $ do
test $ Witch.from (Witch.TryCastException Nothing Nothing :: Witch.TryCastException (Maybe Bool) (Maybe Int)) `Hspec.shouldBe` "TryCastException @(Maybe Bool) @(Maybe Int) Nothing Nothing"
let f = Witch.from @(Witch.TryCastException Bool Int) @String
test $ f (Witch.TryCastException False Nothing) `Hspec.shouldBe` "TryCastException @Bool @Int False Nothing"
Hspec.describe "From (TryFromException s t) String" $ do
test $ Witch.from (Witch.TryFromException Nothing Nothing :: Witch.TryFromException (Maybe Bool) (Maybe Int)) `Hspec.shouldBe` "TryFromException @(Maybe Bool) @(Maybe Int) Nothing Nothing"
let f = Witch.from @(Witch.TryFromException Bool Int) @String
test $ f (Witch.TryFromException False Nothing) `Hspec.shouldBe` "TryFromException @Bool @Int False Nothing"
Hspec.describe "From (TryCastException s t) Text" $ do
let f = Witch.from @(Witch.TryCastException Bool Int) @Text.Text
test $ f (Witch.TryCastException False Nothing) `Hspec.shouldBe` Text.pack "TryCastException @Bool @Int False Nothing"
Hspec.describe "From (TryFromException s t) Text" $ do
let f = Witch.from @(Witch.TryFromException Bool Int) @Text.Text
test $ f (Witch.TryFromException False Nothing) `Hspec.shouldBe` Text.pack "TryFromException @Bool @Int False Nothing"
Hspec.describe "From (TryCastException s t) LazyText" $ do
let f = Witch.from @(Witch.TryCastException Bool Int) @LazyText.Text
test $ f (Witch.TryCastException False Nothing) `Hspec.shouldBe` LazyText.pack "TryCastException @Bool @Int False Nothing"
Hspec.describe "From (TryFromException s t) LazyText" $ do
let f = Witch.from @(Witch.TryFromException Bool Int) @LazyText.Text
test $ f (Witch.TryFromException False Nothing) `Hspec.shouldBe` LazyText.pack "TryFromException @Bool @Int False Nothing"
test :: Hspec.Example a => a -> Hspec.SpecWith (Hspec.Arg a)
test = Hspec.it ""

View File

@ -49,8 +49,8 @@ library
Witch.From
Witch.Instances
Witch.Lift
Witch.TryCastException
Witch.TryFrom
Witch.TryFromException
Witch.Utility
hs-source-dirs: src/lib