Introduce a more flexible error handling

This commit is contained in:
mrkkrp 2016-12-21 15:54:27 +03:00
parent 48e14a31ff
commit 2a2d02847e
3 changed files with 40 additions and 34 deletions

View File

@ -14,7 +14,9 @@
* Switched test suite to Hspec. * Switched test suite to Hspec.
* The `toUnderscore`, `toDashed`, and `toCamelCased` are not partial * The `toUnderscore`, `toDashed`, and `toCamelCased` are not partial
anymore, now they operate in `MonadThrow`. anymore. They return parse error in `Left` just like parsing functions,
but this result can be lifted into any instance of `MonadThrow` with
`betterThrow` helper.
* Improved documentation. * Improved documentation.

View File

@ -48,10 +48,9 @@
-- Right [Word "foo",Word "bar"] -- Right [Word "foo",Word "bar"]
-- --
-- We can chain together the tokenization of the input String and the -- We can chain together the tokenization of the input String and the
-- transformation to CamelCase by using 'Control.Monad.LiftM': -- transformation to CamelCase by using 'fmap':
-- --
-- >>> import Control.Monad (liftM) -- >>> camelize <$> parseSnakeCase [] "foo_bar"
-- >>> liftM camelize $ parseSnakeCase "foo_bar"
-- Right "FooBar" -- Right "FooBar"
-- --
-- By separating out the tokenization from the application of inflections, -- By separating out the tokenization from the application of inflections,
@ -110,10 +109,10 @@ module Text.Inflections
-- * Often used combinators -- * Often used combinators
, toUnderscore , toUnderscore
, toDashed , toDashed
, toCamelCased ) , toCamelCased
, betterThrow )
where where
import Control.Monad (liftM)
import Control.Monad.Catch (MonadThrow (..)) import Control.Monad.Catch (MonadThrow (..))
import Data.Text (Text) import Data.Text (Text)
import Text.Inflections.Camelize (camelize, camelizeCustom) import Text.Inflections.Camelize (camelize, camelizeCustom)
@ -134,43 +133,48 @@ import Text.Megaparsec
import Prelude hiding (Word) import Prelude hiding (Word)
#endif #endif
-- | Transforms CamelCasedString to snake_cased_string_with_underscores. In -- | Transforms CamelCasedString to snake_cased_string_with_underscores.
-- case of failed parsing 'InflectionException' is thrown. --
-- > toUnderscore = fmap underscore . parseCamelCase []
-- --
-- >>> toUnderscore "FooBarBazz" -- >>> toUnderscore "FooBarBazz"
-- "foo_bar_bazz" -- "foo_bar_bazz"
toUnderscore :: MonadThrow m => Text -> m Text toUnderscore :: Text -> Either (ParseError Char Dec) Text
toUnderscore = liftM underscore . handleEither . parseCamelCase [] toUnderscore = fmap underscore . parseCamelCase []
{-# INLINE toUnderscore #-}
-- | Transforms CamelCasedString to snake-cased-string-with-dashes. In case -- | Transforms CamelCasedString to snake-cased-string-with-dashes.
-- of failed parsing 'InflectionException' is thrown. --
-- > toDashed = fmap dasherize . parseCamelCase []
-- --
-- >>> toDashed "FooBarBazz" -- >>> toDashed "FooBarBazz"
-- "foo-bar-bazz" -- "foo-bar-bazz"
toDashed :: MonadThrow m => Text -> m Text toDashed :: Text -> Either (ParseError Char Dec) Text
toDashed = liftM dasherize . handleEither . parseCamelCase [] toDashed = fmap dasherize . parseCamelCase []
{-# INLINE toDashed #-}
-- | Transforms underscored_text to CamelCasedText. If first argument is -- | Transforms underscored_text to CamelCasedText. If first argument is
-- 'True' then FirstCharacter in result string will be in upper case. If -- 'True' then FirstCharacter in result string will be in upper case. If
-- 'False' then firstCharacter will be in lower case. In case of failed -- 'False' then firstCharacter will be in lower case.
-- parsing 'InflectionException' is thrown. --
-- > toCamelCased t = fmap (camelizeCustom t) . parseSnakeCase []
-- --
-- >>> toCamelCased True "foo_bar_bazz" -- >>> toCamelCased True "foo_bar_bazz"
-- "FooBarBazz" -- "FooBarBazz"
-- >>> toCamelCased False "foo_bar_bazz" -- >>> toCamelCased False "foo_bar_bazz"
-- "fooBarBazz" -- "fooBarBazz"
toCamelCased :: MonadThrow m toCamelCased
=> Bool -- ^ Capitalize the first character :: Bool -- ^ Capitalize the first character
-> Text -- ^ Input -> Text -- ^ Input
-> m Text -- ^ Ouput -> Either (ParseError Char Dec) Text -- ^ Ouput
toCamelCased t = liftM (camelizeCustom t) . handleEither . parseSnakeCase [] toCamelCased t = fmap (camelizeCustom t) . parseSnakeCase []
{-# INLINE toCamelCased #-}
-- | Take an 'Either' that can contain a parser error and throw it if -- | Lift something of type @'Either' ('ParseError' 'Char' 'Dec') a@ to
-- necessary. If everything is OK, just return 'Right' value. -- an instance of 'MonadThrow'. Useful when you want to shortcut on parsing
handleEither :: MonadThrow m => Either (ParseError Char Dec) a -> m a -- failures and you're in an instance of 'MonadThrow'.
handleEither (Left err) = throwM (InflectionParsingFailed err) --
handleEither (Right x) = return x -- This throws 'InflectionParsingFailed' if given value is inside 'Left'.
{-# INLINE handleEither #-} --
-- /since 0.3.0.0/
betterThrow :: MonadThrow m => Either (ParseError Char Dec) a -> m a
betterThrow (Left err) = throwM (InflectionParsingFailed err)
betterThrow (Right x) = return x

View File

@ -9,16 +9,16 @@ spec :: Spec
spec = do spec = do
describe "toUnderscore" $ do describe "toUnderscore" $ do
it "converts camel case to snake case" $ it "converts camel case to snake case" $
toUnderscore "camelCasedText" `shouldReturn` "camel_cased_text" toUnderscore "camelCasedText" `shouldBe` Right "camel_cased_text"
it "converts camel case to snake case with numbers" $ it "converts camel case to snake case with numbers" $
toUnderscore "ipv4Address" `shouldReturn` "ipv4_address" toUnderscore "ipv4Address" `shouldBe` Right "ipv4_address"
describe "toDashed" $ describe "toDashed" $
it "converts camel case to dashed" $ it "converts camel case to dashed" $
toDashed "camelCasedText" `shouldReturn` "camel-cased-text" toDashed "camelCasedText" `shouldBe` Right "camel-cased-text"
describe "toCamelCased" $ do describe "toCamelCased" $ do
context "when the first argument is False" $ context "when the first argument is False" $
it "converts snake case to camel case" $ it "converts snake case to camel case" $
toCamelCased False "underscored_text" `shouldReturn` "underscoredText" toCamelCased False "underscored_text" `shouldBe` Right "underscoredText"
context "when the first argument is True" $ context "when the first argument is True" $
it "converts snake case to camel case" $ it "converts snake case to camel case" $
toCamelCased True "underscored_text" `shouldReturn` "UnderscoredText" toCamelCased True "underscored_text" `shouldBe` Right "UnderscoredText"