]> Git — Sourcephile - majurity.git/blob - hjugement-protocol/src/Voting/Protocol/Utils.hs
protocol: add Version and abstract over FFC
[majurity.git] / hjugement-protocol / src / Voting / Protocol / Utils.hs
1 module Voting.Protocol.Utils where
2
3 import Control.Applicative (Applicative(..))
4 import Data.Bool
5 import Data.Either (Either(..), either)
6 import Data.Eq (Eq(..))
7 import Data.Foldable (sequenceA_)
8 import Data.Function (($), (.))
9 import Data.Functor ((<$))
10 import Data.Maybe (Maybe(..), maybe)
11 import Data.String (String)
12 import Data.Traversable (Traversable(..))
13 import Data.Tuple (uncurry)
14 import qualified Data.Aeson.Internal as JSON
15 import qualified Data.List as List
16
17 -- | Like ('.') but with two arguments.
18 o2 :: (c -> d) -> (a -> b -> c) -> a -> b -> d
19 o2 f g = \x y -> f (g x y)
20 infixr 9 `o2`
21 {-# INLINE o2 #-}
22
23 -- | NOTE: check the lengths before applying @f@.
24 isoZipWith :: (a->b->c) -> [a]->[b]->Maybe [c]
25 isoZipWith f as bs
26 | List.length as /= List.length bs = Nothing
27 | otherwise = Just (List.zipWith f as bs)
28
29 -- | NOTE: check the lengths before applying @f@.
30 isoZipWith3 :: (a->b->c->d) -> [a]->[b]->[c]->Maybe [d]
31 isoZipWith3 f as bs cs
32 | al /= List.length bs = Nothing
33 | al /= List.length cs = Nothing
34 | otherwise = Just (List.zipWith3 f as bs cs)
35 where al = List.length as
36
37 isoZipWithM ::
38 Applicative f =>
39 f () -> (a->b->f c) -> [a]->[b]->f [c]
40 isoZipWithM err f as bs =
41 maybe ([] <$ err) sequenceA $
42 isoZipWith f as bs
43
44 isoZipWithM_ ::
45 Applicative f =>
46 f () -> (a->b->f c) -> [a]->[b]->f ()
47 isoZipWithM_ err f as bs =
48 maybe err sequenceA_ $
49 isoZipWith f as bs
50
51 isoZipWith3M ::
52 Applicative f =>
53 f () -> (a->b->c->f d) -> [a]->[b]->[c]->f [d]
54 isoZipWith3M err f as bs cs =
55 maybe ([] <$ err) sequenceA $
56 isoZipWith3 f as bs cs
57
58 isoZipWith3M_ ::
59 Applicative f =>
60 f () -> (a->b->c->f d) -> [a]->[b]->[c]->f ()
61 isoZipWith3M_ err f as bs cs =
62 maybe err sequenceA_ $
63 isoZipWith3 f as bs cs
64
65 -- | Copied from 'Data.Aeson''s 'eitherFormatError'
66 -- which is not exported.
67 jsonEitherFormatError :: Either (JSON.JSONPath, String) a -> Either String a
68 jsonEitherFormatError = either (Left . uncurry JSON.formatError) Right
69 {-# INLINE jsonEitherFormatError #-}