root / src / Ganeti / BasicTypes.hs @ 53822ec4
History | View | Annotate | Download (6.8 kB)
1 | 93be1ced | Iustin Pop | {-# LANGUAGE FlexibleInstances #-} |
---|---|---|---|
2 | 93be1ced | Iustin Pop | |
3 | 0c37d1e4 | Iustin Pop | {- |
4 | 0c37d1e4 | Iustin Pop | |
5 | 1091021c | Iustin Pop | Copyright (C) 2009, 2010, 2011, 2012 Google Inc. |
6 | 0c37d1e4 | Iustin Pop | |
7 | 0c37d1e4 | Iustin Pop | This program is free software; you can redistribute it and/or modify |
8 | 0c37d1e4 | Iustin Pop | it under the terms of the GNU General Public License as published by |
9 | 0c37d1e4 | Iustin Pop | the Free Software Foundation; either version 2 of the License, or |
10 | 0c37d1e4 | Iustin Pop | (at your option) any later version. |
11 | 0c37d1e4 | Iustin Pop | |
12 | 0c37d1e4 | Iustin Pop | This program is distributed in the hope that it will be useful, but |
13 | 0c37d1e4 | Iustin Pop | WITHOUT ANY WARRANTY; without even the implied warranty of |
14 | 0c37d1e4 | Iustin Pop | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU |
15 | 0c37d1e4 | Iustin Pop | General Public License for more details. |
16 | 0c37d1e4 | Iustin Pop | |
17 | 0c37d1e4 | Iustin Pop | You should have received a copy of the GNU General Public License |
18 | 0c37d1e4 | Iustin Pop | along with this program; if not, write to the Free Software |
19 | 0c37d1e4 | Iustin Pop | Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA |
20 | 0c37d1e4 | Iustin Pop | 02110-1301, USA. |
21 | 0c37d1e4 | Iustin Pop | |
22 | 0c37d1e4 | Iustin Pop | -} |
23 | 0c37d1e4 | Iustin Pop | |
24 | 0c37d1e4 | Iustin Pop | module Ganeti.BasicTypes |
25 | 93be1ced | Iustin Pop | ( GenericResult(..) |
26 | 93be1ced | Iustin Pop | , Result |
27 | d71fbcc5 | Agata Murawska | , ResultT(..) |
28 | d71fbcc5 | Agata Murawska | , resultT |
29 | 93be1ced | Iustin Pop | , FromString(..) |
30 | 0c37d1e4 | Iustin Pop | , isOk |
31 | 0c37d1e4 | Iustin Pop | , isBad |
32 | 0c37d1e4 | Iustin Pop | , eitherToResult |
33 | f3f76ccc | Iustin Pop | , annotateResult |
34 | 2fc5653f | Iustin Pop | , select |
35 | 2fc5653f | Iustin Pop | , LookupResult(..) |
36 | 2fc5653f | Iustin Pop | , MatchPriority(..) |
37 | 2fc5653f | Iustin Pop | , lookupName |
38 | 2fc5653f | Iustin Pop | , goodLookupResult |
39 | 2fc5653f | Iustin Pop | , goodMatchPriority |
40 | 2fc5653f | Iustin Pop | , prefixMatch |
41 | 2fc5653f | Iustin Pop | , compareNameComponent |
42 | 0c37d1e4 | Iustin Pop | ) where |
43 | 0c37d1e4 | Iustin Pop | |
44 | 25779212 | Iustin Pop | import Control.Applicative |
45 | 0c37d1e4 | Iustin Pop | import Control.Monad |
46 | d71fbcc5 | Agata Murawska | import Control.Monad.Trans |
47 | 2fc5653f | Iustin Pop | import Data.Function |
48 | 2fc5653f | Iustin Pop | import Data.List |
49 | 0c37d1e4 | Iustin Pop | |
50 | 93be1ced | Iustin Pop | -- | Generic monad for our error handling mechanisms. |
51 | 93be1ced | Iustin Pop | data GenericResult a b |
52 | 93be1ced | Iustin Pop | = Bad a |
53 | 93be1ced | Iustin Pop | | Ok b |
54 | 139c0683 | Iustin Pop | deriving (Show, Eq) |
55 | 0c37d1e4 | Iustin Pop | |
56 | 93be1ced | Iustin Pop | -- | Type alias for a string Result. |
57 | 93be1ced | Iustin Pop | type Result = GenericResult String |
58 | 93be1ced | Iustin Pop | |
59 | 93be1ced | Iustin Pop | -- | Type class for things that can be built from strings. |
60 | 93be1ced | Iustin Pop | class FromString a where |
61 | 93be1ced | Iustin Pop | mkFromString :: String -> a |
62 | 93be1ced | Iustin Pop | |
63 | 93be1ced | Iustin Pop | -- | Trivial 'String' instance; requires FlexibleInstances extension |
64 | 93be1ced | Iustin Pop | -- though. |
65 | 93be1ced | Iustin Pop | instance FromString [Char] where |
66 | 93be1ced | Iustin Pop | mkFromString = id |
67 | 93be1ced | Iustin Pop | |
68 | 93be1ced | Iustin Pop | -- | 'Monad' instance for 'GenericResult'. |
69 | 93be1ced | Iustin Pop | instance (FromString a) => Monad (GenericResult a) where |
70 | 0c37d1e4 | Iustin Pop | (>>=) (Bad x) _ = Bad x |
71 | 0c37d1e4 | Iustin Pop | (>>=) (Ok x) fn = fn x |
72 | 0c37d1e4 | Iustin Pop | return = Ok |
73 | 93be1ced | Iustin Pop | fail = Bad . mkFromString |
74 | 0c37d1e4 | Iustin Pop | |
75 | 93be1ced | Iustin Pop | instance Functor (GenericResult a) where |
76 | a9ccc950 | Iustin Pop | fmap _ (Bad msg) = Bad msg |
77 | a9ccc950 | Iustin Pop | fmap fn (Ok val) = Ok (fn val) |
78 | a9ccc950 | Iustin Pop | |
79 | 93be1ced | Iustin Pop | instance MonadPlus (GenericResult String) where |
80 | 0c37d1e4 | Iustin Pop | mzero = Bad "zero Result when used as MonadPlus" |
81 | 0c37d1e4 | Iustin Pop | -- for mplus, when we 'add' two Bad values, we concatenate their |
82 | 0c37d1e4 | Iustin Pop | -- error descriptions |
83 | 0c37d1e4 | Iustin Pop | (Bad x) `mplus` (Bad y) = Bad (x ++ "; " ++ y) |
84 | 0c37d1e4 | Iustin Pop | (Bad _) `mplus` x = x |
85 | 0c37d1e4 | Iustin Pop | x@(Ok _) `mplus` _ = x |
86 | 0c37d1e4 | Iustin Pop | |
87 | 93be1ced | Iustin Pop | instance Applicative (GenericResult a) where |
88 | 25779212 | Iustin Pop | pure = Ok |
89 | 25779212 | Iustin Pop | (Bad f) <*> _ = Bad f |
90 | 25779212 | Iustin Pop | _ <*> (Bad x) = Bad x |
91 | 25779212 | Iustin Pop | (Ok f) <*> (Ok x) = Ok $ f x |
92 | 25779212 | Iustin Pop | |
93 | d71fbcc5 | Agata Murawska | -- | This is a monad transformation for Result. It's implementation is |
94 | d71fbcc5 | Agata Murawska | -- based on the implementations of MaybeT and ErrorT. |
95 | 93be1ced | Iustin Pop | newtype ResultT a m b = ResultT {runResultT :: m (GenericResult a b)} |
96 | d71fbcc5 | Agata Murawska | |
97 | 93be1ced | Iustin Pop | instance (Monad m, FromString a) => Monad (ResultT a m) where |
98 | 93be1ced | Iustin Pop | fail err = ResultT (return . Bad $ mkFromString err) |
99 | 274366e5 | Agata Murawska | return = lift . return |
100 | 274366e5 | Agata Murawska | x >>= f = ResultT $ do |
101 | 274366e5 | Agata Murawska | a <- runResultT x |
102 | 274366e5 | Agata Murawska | case a of |
103 | 274366e5 | Agata Murawska | Ok val -> runResultT $ f val |
104 | 274366e5 | Agata Murawska | Bad err -> return $ Bad err |
105 | d71fbcc5 | Agata Murawska | |
106 | 93be1ced | Iustin Pop | instance MonadTrans (ResultT a) where |
107 | d71fbcc5 | Agata Murawska | lift x = ResultT (liftM Ok x) |
108 | d71fbcc5 | Agata Murawska | |
109 | 93be1ced | Iustin Pop | instance (MonadIO m, FromString a) => MonadIO (ResultT a m) where |
110 | d71fbcc5 | Agata Murawska | liftIO = lift . liftIO |
111 | d71fbcc5 | Agata Murawska | |
112 | d71fbcc5 | Agata Murawska | -- | Lift a `Result` value to a `ResultT`. |
113 | 93be1ced | Iustin Pop | resultT :: Monad m => GenericResult a b -> ResultT a m b |
114 | d71fbcc5 | Agata Murawska | resultT = ResultT . return |
115 | d71fbcc5 | Agata Murawska | |
116 | 93be1ced | Iustin Pop | -- | Simple checker for whether a 'GenericResult' is OK. |
117 | 93be1ced | Iustin Pop | isOk :: GenericResult a b -> Bool |
118 | 0c37d1e4 | Iustin Pop | isOk (Ok _) = True |
119 | 93be1ced | Iustin Pop | isOk _ = False |
120 | 0c37d1e4 | Iustin Pop | |
121 | 93be1ced | Iustin Pop | -- | Simple checker for whether a 'GenericResult' is a failure. |
122 | 93be1ced | Iustin Pop | isBad :: GenericResult a b -> Bool |
123 | 0c37d1e4 | Iustin Pop | isBad = not . isOk |
124 | 0c37d1e4 | Iustin Pop | |
125 | 98508e7f | Dato Simó | -- | Converter from Either to 'GenericResult'. |
126 | 93be1ced | Iustin Pop | eitherToResult :: Either a b -> GenericResult a b |
127 | 93be1ced | Iustin Pop | eitherToResult (Left s) = Bad s |
128 | 93be1ced | Iustin Pop | eitherToResult (Right v) = Ok v |
129 | f3f76ccc | Iustin Pop | |
130 | f3f76ccc | Iustin Pop | -- | Annotate a Result with an ownership information. |
131 | f3f76ccc | Iustin Pop | annotateResult :: String -> Result a -> Result a |
132 | f3f76ccc | Iustin Pop | annotateResult owner (Bad s) = Bad $ owner ++ ": " ++ s |
133 | f3f76ccc | Iustin Pop | annotateResult _ v = v |
134 | 1091021c | Iustin Pop | |
135 | 2fc5653f | Iustin Pop | -- * Misc functionality |
136 | 2fc5653f | Iustin Pop | |
137 | 2fc5653f | Iustin Pop | -- | Return the first result with a True condition, or the default otherwise. |
138 | 2fc5653f | Iustin Pop | select :: a -- ^ default result |
139 | 2fc5653f | Iustin Pop | -> [(Bool, a)] -- ^ list of \"condition, result\" |
140 | 2fc5653f | Iustin Pop | -> a -- ^ first result which has a True condition, or default |
141 | 2fc5653f | Iustin Pop | select def = maybe def snd . find fst |
142 | 2fc5653f | Iustin Pop | |
143 | 2fc5653f | Iustin Pop | -- * Lookup of partial names functionality |
144 | 2fc5653f | Iustin Pop | |
145 | 2fc5653f | Iustin Pop | -- | The priority of a match in a lookup result. |
146 | 2fc5653f | Iustin Pop | data MatchPriority = ExactMatch |
147 | 2fc5653f | Iustin Pop | | MultipleMatch |
148 | 2fc5653f | Iustin Pop | | PartialMatch |
149 | 2fc5653f | Iustin Pop | | FailMatch |
150 | 139c0683 | Iustin Pop | deriving (Show, Enum, Eq, Ord) |
151 | 2fc5653f | Iustin Pop | |
152 | 2fc5653f | Iustin Pop | -- | The result of a name lookup in a list. |
153 | 2fc5653f | Iustin Pop | data LookupResult = LookupResult |
154 | 2fc5653f | Iustin Pop | { lrMatchPriority :: MatchPriority -- ^ The result type |
155 | 2fc5653f | Iustin Pop | -- | Matching value (for ExactMatch, PartialMatch), Lookup string otherwise |
156 | 2fc5653f | Iustin Pop | , lrContent :: String |
157 | 139c0683 | Iustin Pop | } deriving (Show) |
158 | 2fc5653f | Iustin Pop | |
159 | 2fc5653f | Iustin Pop | -- | Lookup results have an absolute preference ordering. |
160 | 2fc5653f | Iustin Pop | instance Eq LookupResult where |
161 | 2fc5653f | Iustin Pop | (==) = (==) `on` lrMatchPriority |
162 | 2fc5653f | Iustin Pop | |
163 | 2fc5653f | Iustin Pop | instance Ord LookupResult where |
164 | 2fc5653f | Iustin Pop | compare = compare `on` lrMatchPriority |
165 | 2fc5653f | Iustin Pop | |
166 | 2fc5653f | Iustin Pop | -- | Check for prefix matches in names. |
167 | 2fc5653f | Iustin Pop | -- Implemented in Ganeti core utils.text.MatchNameComponent |
168 | 2fc5653f | Iustin Pop | -- as the regexp r"^%s(\..*)?$" % re.escape(key) |
169 | 2fc5653f | Iustin Pop | prefixMatch :: String -- ^ Lookup |
170 | 2fc5653f | Iustin Pop | -> String -- ^ Full name |
171 | 2fc5653f | Iustin Pop | -> Bool -- ^ Whether there is a prefix match |
172 | 2fc5653f | Iustin Pop | prefixMatch = isPrefixOf . (++ ".") |
173 | 2fc5653f | Iustin Pop | |
174 | 2fc5653f | Iustin Pop | -- | Is the lookup priority a "good" one? |
175 | 2fc5653f | Iustin Pop | goodMatchPriority :: MatchPriority -> Bool |
176 | 2fc5653f | Iustin Pop | goodMatchPriority ExactMatch = True |
177 | 2fc5653f | Iustin Pop | goodMatchPriority PartialMatch = True |
178 | 2fc5653f | Iustin Pop | goodMatchPriority _ = False |
179 | 2fc5653f | Iustin Pop | |
180 | 2fc5653f | Iustin Pop | -- | Is the lookup result an actual match? |
181 | 2fc5653f | Iustin Pop | goodLookupResult :: LookupResult -> Bool |
182 | 2fc5653f | Iustin Pop | goodLookupResult = goodMatchPriority . lrMatchPriority |
183 | 2fc5653f | Iustin Pop | |
184 | 2fc5653f | Iustin Pop | -- | Compares a canonical name and a lookup string. |
185 | 2fc5653f | Iustin Pop | compareNameComponent :: String -- ^ Canonical (target) name |
186 | 2fc5653f | Iustin Pop | -> String -- ^ Partial (lookup) name |
187 | 2fc5653f | Iustin Pop | -> LookupResult -- ^ Result of the lookup |
188 | 2fc5653f | Iustin Pop | compareNameComponent cnl lkp = |
189 | 2fc5653f | Iustin Pop | select (LookupResult FailMatch lkp) |
190 | 2fc5653f | Iustin Pop | [ (cnl == lkp , LookupResult ExactMatch cnl) |
191 | 2fc5653f | Iustin Pop | , (prefixMatch lkp cnl , LookupResult PartialMatch cnl) |
192 | 2fc5653f | Iustin Pop | ] |
193 | 2fc5653f | Iustin Pop | |
194 | 2fc5653f | Iustin Pop | -- | Lookup a string and choose the best result. |
195 | 2fc5653f | Iustin Pop | chooseLookupResult :: String -- ^ Lookup key |
196 | 2fc5653f | Iustin Pop | -> String -- ^ String to compare to the lookup key |
197 | 2fc5653f | Iustin Pop | -> LookupResult -- ^ Previous result |
198 | 2fc5653f | Iustin Pop | -> LookupResult -- ^ New result |
199 | 2fc5653f | Iustin Pop | chooseLookupResult lkp cstr old = |
200 | 2fc5653f | Iustin Pop | -- default: use class order to pick the minimum result |
201 | 2fc5653f | Iustin Pop | select (min new old) |
202 | 2fc5653f | Iustin Pop | -- special cases: |
203 | 2fc5653f | Iustin Pop | -- short circuit if the new result is an exact match |
204 | 2fc5653f | Iustin Pop | [ (lrMatchPriority new == ExactMatch, new) |
205 | 2fc5653f | Iustin Pop | -- if both are partial matches generate a multiple match |
206 | 2fc5653f | Iustin Pop | , (partial2, LookupResult MultipleMatch lkp) |
207 | 2fc5653f | Iustin Pop | ] where new = compareNameComponent cstr lkp |
208 | 2fc5653f | Iustin Pop | partial2 = all ((PartialMatch==) . lrMatchPriority) [old, new] |
209 | 2fc5653f | Iustin Pop | |
210 | 2fc5653f | Iustin Pop | -- | Find the canonical name for a lookup string in a list of names. |
211 | 2fc5653f | Iustin Pop | lookupName :: [String] -- ^ List of keys |
212 | 2fc5653f | Iustin Pop | -> String -- ^ Lookup string |
213 | 2fc5653f | Iustin Pop | -> LookupResult -- ^ Result of the lookup |
214 | 2fc5653f | Iustin Pop | lookupName l s = foldr (chooseLookupResult s) |
215 | 2fc5653f | Iustin Pop | (LookupResult FailMatch s) l |