{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor      #-}
{-# LANGUAGE CPP                #-}
module Database.PostgreSQL.Simple.Ok where
import Control.Applicative
import Control.Exception
import Control.Monad(MonadPlus(..))
import Data.Typeable
import qualified Control.Monad.Fail as Fail
data Ok a = Errors [SomeException] | Ok !a
    deriving(Int -> Ok a -> ShowS
forall a. Show a => Int -> Ok a -> ShowS
forall a. Show a => [Ok a] -> ShowS
forall a. Show a => Ok a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Ok a] -> ShowS
$cshowList :: forall a. Show a => [Ok a] -> ShowS
show :: Ok a -> String
$cshow :: forall a. Show a => Ok a -> String
showsPrec :: Int -> Ok a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Ok a -> ShowS
Show, Typeable, forall a b. a -> Ok b -> Ok a
forall a b. (a -> b) -> Ok a -> Ok b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Ok b -> Ok a
$c<$ :: forall a b. a -> Ok b -> Ok a
fmap :: forall a b. (a -> b) -> Ok a -> Ok b
$cfmap :: forall a b. (a -> b) -> Ok a -> Ok b
Functor)
instance Eq a => Eq (Ok a) where
    Errors [SomeException]
_ == :: Ok a -> Ok a -> Bool
== Errors [SomeException]
_  = Bool
True
    Ok  a
a    == Ok  a
b     = a
a forall a. Eq a => a -> a -> Bool
== a
b
    Ok a
_        == Ok a
_         = Bool
False
instance Applicative Ok where
    pure :: forall a. a -> Ok a
pure = forall a. a -> Ok a
Ok
    Errors [SomeException]
es <*> :: forall a b. Ok (a -> b) -> Ok a -> Ok b
<*> Ok a
_ = forall a. [SomeException] -> Ok a
Errors [SomeException]
es
    Ok (a -> b)
_ <*> Errors [SomeException]
es = forall a. [SomeException] -> Ok a
Errors [SomeException]
es
    Ok a -> b
f <*> Ok a
a   = forall a. a -> Ok a
Ok (a -> b
f a
a)
instance Alternative Ok where
    empty :: forall a. Ok a
empty = forall a. [SomeException] -> Ok a
Errors []
    a :: Ok a
a@(Ok a
_)  <|> :: forall a. Ok a -> Ok a -> Ok a
<|> Ok a
_         = Ok a
a
    Errors [SomeException]
_  <|> b :: Ok a
b@(Ok a
_)  = Ok a
b
    Errors [SomeException]
as <|> Errors [SomeException]
bs = forall a. [SomeException] -> Ok a
Errors ([SomeException]
as forall a. [a] -> [a] -> [a]
++ [SomeException]
bs)
instance MonadPlus Ok where
    mzero :: forall a. Ok a
mzero = forall (f :: * -> *) a. Alternative f => f a
empty
    mplus :: forall a. Ok a -> Ok a -> Ok a
mplus = forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>)
instance Monad Ok where
    Errors [SomeException]
es >>= :: forall a b. Ok a -> (a -> Ok b) -> Ok b
>>= a -> Ok b
_ = forall a. [SomeException] -> Ok a
Errors [SomeException]
es
    Ok a
a      >>= a -> Ok b
f = a -> Ok b
f a
a
#if !(MIN_VERSION_base(4,13,0))
    fail = Fail.fail
#endif
instance Fail.MonadFail Ok where
    fail :: forall a. String -> Ok a
fail String
str = forall a. [SomeException] -> Ok a
Errors [forall e. Exception e => e -> SomeException
SomeException (String -> ErrorCall
ErrorCall String
str)]
newtype ManyErrors = ManyErrors [SomeException]
   deriving (Int -> ManyErrors -> ShowS
[ManyErrors] -> ShowS
ManyErrors -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ManyErrors] -> ShowS
$cshowList :: [ManyErrors] -> ShowS
show :: ManyErrors -> String
$cshow :: ManyErrors -> String
showsPrec :: Int -> ManyErrors -> ShowS
$cshowsPrec :: Int -> ManyErrors -> ShowS
Show, Typeable)
instance Exception ManyErrors