{-# LANGUAGE FlexibleInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Try
(
Try
, onFail
, nothingFail
, failReport
, failReports
, runTry
, ifFail
, isFail
, concatFails
, ignoreFails
, tryAtLeastOne
, atLeastOne
) where
import Data.Either(fromRight, lefts, rights, isLeft)
type Try a = Either ShowS a
onFail:: String -> Try a -> Try a
onFail :: forall a. String -> Try a -> Try a
onFail String
s = (ShowS -> Try a) -> (a -> Try a) -> Try a -> Try a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (ShowS -> Try a
forall a b. a -> Either a b
Left (ShowS -> Try a) -> (ShowS -> ShowS) -> ShowS -> Try a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> ShowS
forall a. a -> String -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
s <>)) a -> Try a
forall a b. b -> Either a b
Right
failReport :: String -> Try a
failReport :: forall a. String -> Try a
failReport = ShowS -> Either ShowS a
forall a b. a -> Either a b
Left (ShowS -> Either ShowS a)
-> (String -> ShowS) -> String -> Either ShowS a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
forall a. Semigroup a => a -> a -> a
(<>)
failReports :: [String] -> Try a
failReports :: forall a. [String] -> Try a
failReports = ShowS -> Either ShowS a
forall a b. a -> Either a b
Left (ShowS -> Either ShowS a)
-> ([String] -> ShowS) -> [String] -> Either ShowS a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ShowS] -> ShowS
forall a. Monoid a => [a] -> a
mconcat ([ShowS] -> ShowS) -> ([String] -> [ShowS]) -> [String] -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> ShowS) -> [String] -> [ShowS]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> ShowS
forall a. Semigroup a => a -> a -> a
(<>)
nothingFail :: Maybe b -> String -> Try b
nothingFail :: forall b. Maybe b -> String -> Try b
nothingFail Maybe b
a String
s = Try b -> (b -> Try b) -> Maybe b -> Try b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Try b
forall a. String -> Try a
failReport String
s) b -> Try b
forall a b. b -> Either a b
Right Maybe b
a
runTry:: Try a -> a
runTry :: forall a. Try a -> a
runTry = (ShowS -> a) -> (a -> a) -> Either ShowS a -> a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> (ShowS -> String) -> ShowS -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String
"")) a -> a
forall a. a -> a
id
ifFail :: a -> Try a -> a
ifFail :: forall a. a -> Try a -> a
ifFail = a -> Either ShowS a -> a
forall b a. b -> Either a b -> b
fromRight
isFail:: Try a -> Bool
isFail :: forall a. Try a -> Bool
isFail = Either ShowS a -> Bool
forall a b. Either a b -> Bool
isLeft
concatFails:: [Try a] -> Try [a]
concatFails :: forall a. [Try a] -> Try [a]
concatFails [Try a]
ls = case [Try a] -> [ShowS]
forall a b. [Either a b] -> [a]
lefts [Try a]
ls of
[] -> [a] -> Try [a]
forall a b. b -> Either a b
Right ([a] -> Try [a]) -> [a] -> Try [a]
forall a b. (a -> b) -> a -> b
$ [Try a] -> [a]
forall a b. [Either a b] -> [b]
rights [Try a]
ls
[ShowS]
other -> ShowS -> Try [a]
forall a b. a -> Either a b
Left (ShowS -> Try [a]) -> ShowS -> Try [a]
forall a b. (a -> b) -> a -> b
$ [ShowS] -> ShowS
forall a. Monoid a => [a] -> a
mconcat [ShowS]
other
ignoreFails:: [Try a] -> [a]
ignoreFails :: forall a. [Try a] -> [a]
ignoreFails = [Either ShowS a] -> [a]
forall a b. [Either a b] -> [b]
rights
tryAtLeastOne:: [Try a] -> Try [a]
tryAtLeastOne :: forall a. [Try a] -> Try [a]
tryAtLeastOne [] = String -> Try [a]
forall a. String -> Try a
failReport String
"atLeastOne: applied to empty list.\n"
tryAtLeastOne [Try a]
results = case [Try a] -> [a]
forall a. [Try a] -> [a]
ignoreFails [Try a]
results of
[] -> String -> Try [a] -> Try [a]
forall a. String -> Try a -> Try a
onFail String
"atLeastOne: no successful results.\n" (Try [a] -> Try [a]) -> Try [a] -> Try [a]
forall a b. (a -> b) -> a -> b
$ [Try a] -> Try [a]
forall a. [Try a] -> Try [a]
concatFails [Try a]
results
[a]
other -> [a] -> Try [a]
forall a b. b -> Either a b
Right [a]
other
atLeastOne:: [Try a] -> [a]
atLeastOne :: forall a. [Try a] -> [a]
atLeastOne = Try [a] -> [a]
forall a. Try a -> a
runTry (Try [a] -> [a]) -> ([Try a] -> Try [a]) -> [Try a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Try a] -> Try [a]
forall a. [Try a] -> Try [a]
tryAtLeastOne
instance Show ShowS where
show :: ShowS -> String
show ShowS
r = ShowS
forall a. Show a => a -> String
show String
"<function> = (" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
r String
"" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
" ++)"