aboutsummaryrefslogtreecommitdiffstats
path: root/src/VeriFuzz/Result.hs
blob: 04aa899020a136ec61db41eab830acf91a3b2c04 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
{-|
Module      : VeriFuzz.Result
Description : Result monadic type.
Copyright   : (c) 2019, Yann Herklotz Grave
License     : GPL-3
Maintainer  : ymherklotz [at] gmail [dot] com
Stability   : experimental
Portability : POSIX

Result monadic type. This is nearly equivalent to the transformers 'Error' type,
but to have more control this is reimplemented with the instances that are
needed in "VeriFuzz".
-}

{-# LANGUAGE ScopedTypeVariables #-}

module VeriFuzz.Result
    ( Result(..)
    , ResultT(..)
    , (<?>)
    , annotate
    )
where

import           Control.Monad.IO.Class
import           Shelly                 (RunFailed (..), Sh, catch_sh)
import           Shelly.Lifted          (MonadSh, liftSh)

-- | Result type which is equivalent to 'Either' or 'Error'. This is
-- reimplemented so that there is full control over the 'Monad' definition and
-- definition of a 'Monad' transformer 'ResultT'.
data Result a b = Fail a
                | Pass b
                deriving (Eq, Show)

instance Semigroup (Result a b) where
    Fail _ <> b = b
    a <> _ = a

instance (Monoid b) => Monoid (Result a b) where
    mempty = Pass mempty

instance Functor (Result a) where
    fmap f (Pass a) = Pass $ f a
    fmap _ (Fail b) = Fail b

instance Applicative (Result a) where
    pure = Pass
    Fail e <*> _ = Fail e
    Pass f <*> r = fmap f r

instance Monad (Result a) where
    Pass a >>= f = f a
    Fail b >>= _ = Fail b

-- | The transformer for the 'Result' type. This
newtype ResultT a m b = ResultT { runResultT :: m (Result a b) }

instance Functor f => Functor (ResultT a f) where
    fmap f = ResultT . fmap (fmap f) . runResultT

instance Monad m => Applicative (ResultT a m) where
    pure = ResultT . pure . pure
    f <*> a = ResultT $ do
        f' <- runResultT f
        case f' of
            Fail e -> return (Fail e)
            Pass k -> do
                a' <- runResultT a
                case a' of
                    Fail e -> return (Fail e)
                    Pass v -> return (Pass $ k v)

instance Monad m => Monad (ResultT a m) where
    a >>= b = ResultT $ do
        m <- runResultT a
        case m of
            Fail e -> return (Fail e)
            Pass p -> runResultT (b p)

instance (MonadSh m, Monoid a) => MonadSh (ResultT a m) where
    liftSh s =
        ResultT
        . liftSh
        . catch_sh (Pass <$> s)
        $ (const (Fail <$> return mempty) :: RunFailed -> Sh (Result a b))

instance (MonadIO m) => MonadIO (ResultT a m) where
    liftIO s = ResultT $ Pass <$> liftIO s

infix 0 <?>

(<?>) :: (Monad m, Monoid a) => ResultT a m b -> a -> ResultT a m b
m <?> b = ResultT $ do
    a <- runResultT m
    case a of
        Pass a' -> return $ Pass a'
        Fail a' -> return . Fail $ a' <> b

annotate :: (Monad m, Monoid a) => a -> ResultT a m b -> ResultT a m b
annotate = flip (<?>)