module Codec.Xlsx.Parser.Internal.Util ( boolean , eitherBoolean , decimal , eitherDecimal , rational , eitherRational ) where import Data.Text (Text) import Control.Monad.Fail (MonadFail) import qualified Data.Text as T import qualified Data.Text.Read as T import qualified Control.Monad.Fail as F decimal :: (MonadFail m, Integral a) => Text -> m a decimal :: forall (m :: * -> *) a. (MonadFail m, Integral a) => Text -> m a decimal = forall (m :: * -> *) b. MonadFail m => Either String b -> m b fromEither forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. Integral a => Text -> Either String a eitherDecimal eitherDecimal :: (Integral a) => Text -> Either String a eitherDecimal :: forall a. Integral a => Text -> Either String a eitherDecimal Text t = case forall a. Num a => Reader a -> Reader a T.signed forall a. Integral a => Reader a T.decimal Text t of Right (a d, Text leftover) | Text -> Bool T.null Text leftover -> forall a b. b -> Either a b Right a d Either String (a, Text) _ -> forall a b. a -> Either a b Left forall a b. (a -> b) -> a -> b $ String "invalid decimal: " forall a. [a] -> [a] -> [a] ++ forall a. Show a => a -> String show Text t rational :: (MonadFail m) => Text -> m Double rational :: forall (m :: * -> *). MonadFail m => Text -> m Double rational = forall (m :: * -> *) b. MonadFail m => Either String b -> m b fromEither forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> Either String Double eitherRational eitherRational :: Text -> Either String Double eitherRational :: Text -> Either String Double eitherRational Text t = case forall a. Num a => Reader a -> Reader a T.signed forall a. Fractional a => Reader a T.rational Text t of Right (Double r, Text leftover) | Text -> Bool T.null Text leftover -> forall a b. b -> Either a b Right Double r Either String (Double, Text) _ -> forall a b. a -> Either a b Left forall a b. (a -> b) -> a -> b $ String "invalid rational: " forall a. [a] -> [a] -> [a] ++ forall a. Show a => a -> String show Text t boolean :: (MonadFail m) => Text -> m Bool boolean :: forall (m :: * -> *). MonadFail m => Text -> m Bool boolean = forall (m :: * -> *) b. MonadFail m => Either String b -> m b fromEither forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> Either String Bool eitherBoolean eitherBoolean :: Text -> Either String Bool eitherBoolean :: Text -> Either String Bool eitherBoolean Text t = case Text -> String T.unpack forall a b. (a -> b) -> a -> b $ Text -> Text T.strip Text t of String "true" -> forall a b. b -> Either a b Right Bool True String "false" -> forall a b. b -> Either a b Right Bool False String _ -> forall a b. a -> Either a b Left forall a b. (a -> b) -> a -> b $ String "invalid boolean: " forall a. [a] -> [a] -> [a] ++ forall a. Show a => a -> String show Text t fromEither :: (MonadFail m) => Either String b -> m b fromEither :: forall (m :: * -> *) b. MonadFail m => Either String b -> m b fromEither (Left String a) = forall (m :: * -> *) a. MonadFail m => String -> m a F.fail String a fromEither (Right b b) = forall (m :: * -> *) a. Monad m => a -> m a return b b