Revision d286d795

b/src/Ganeti/Query/Common.hs
24 24
-}
25 25

  
26 26
module Ganeti.Query.Common
27
  ( rsNoData
27
  ( NoDataRuntime(..)
28
  , rsNoData
28 29
  , rsUnavail
29 30
  , rsNormal
30 31
  , rsMaybeNoData
......
52 53
import Ganeti.Query.Types
53 54
import Ganeti.Types
54 55

  
56
-- | The runtime used by queries which retrieve no live data.
57
data NoDataRuntime = NoDataRuntime
58

  
55 59
-- * Generic functions
56 60

  
57 61
-- | Conversion from 'VType' to 'FieldType'.
b/src/Ganeti/Query/Group.hs
24 24
-}
25 25

  
26 26
module Ganeti.Query.Group
27
  ( Runtime
28
  , fieldsMap
29
  , collectLiveData
30
  ) where
27
  (fieldsMap) where
31 28

  
32 29
import qualified Data.Map as Map
33 30

  
......
38 35
import Ganeti.Query.Types
39 36
import Ganeti.Utils (niceSort)
40 37

  
41
-- | There is no runtime.
42
data Runtime = Runtime
43

  
44
groupFields :: FieldList NodeGroup Runtime
38
groupFields :: FieldList NodeGroup NoDataRuntime
45 39
groupFields =
46 40
  [ (FieldDefinition "alloc_policy" "AllocPolicy" QFTText
47 41
       "Allocation policy for group",
......
89 83
  tagsFields
90 84

  
91 85
-- | The group fields map.
92
fieldsMap :: FieldMap NodeGroup Runtime
86
fieldsMap :: FieldMap NodeGroup NoDataRuntime
93 87
fieldsMap =
94 88
  Map.fromList $ map (\v@(f, _, _) -> (fdefName f, v)) groupFields
95

  
96
-- | Dummy function for collecting live data (which groups don't have).
97
collectLiveData :: Bool -> ConfigData -> [NodeGroup]
98
                -> IO [(NodeGroup, Runtime)]
99
collectLiveData _ _ = return . map (\n -> (n, Runtime))
b/src/Ganeti/Query/Instance.hs
1
{-# LANGUAGE TupleSections #-}
2

  
3 1
{-| Implementation of the Ganeti Query2 instance queries.
4 2

  
5 3
-}
......
26 24
-}
27 25

  
28 26
module Ganeti.Query.Instance
29
  ( Runtime
30
  , fieldsMap
31
  , collectLiveData
32
  ) where
27
  (fieldsMap) where
33 28

  
34 29
import qualified Data.Map as Map
35 30

  
......
38 33
import Ganeti.Query.Language
39 34
import Ganeti.Query.Types
40 35

  
41
-- | Dummy type for runtime to be implemented later, see the 'genericQuery'
42
-- function in 'Ganeti.Query.Query' for an explanation
43
data Runtime = Runtime
44

  
45
instanceFields :: FieldList Instance Runtime
36
instanceFields :: FieldList Instance NoDataRuntime
46 37
instanceFields =
47 38
  [ (FieldDefinition "disk_template" "Disk_template" QFTText
48 39
     "Disk template",
......
63 54
  serialFields "Instance" ++
64 55
  uuidFields "Instance"
65 56

  
66
fieldsMap :: FieldMap Instance Runtime
57
fieldsMap :: FieldMap Instance NoDataRuntime
67 58
fieldsMap =
68 59
  Map.fromList [(fdefName f, v) | v@(f, _, _) <- instanceFields]
69

  
70
-- | Dummy function for collecting live data - just for interface testing
71
collectLiveData :: Bool -> ConfigData -> [Instance] -> IO [(Instance, Runtime)]
72
collectLiveData _ _ = return . map (, Runtime)
b/src/Ganeti/Query/Network.hs
27 27
  ( getGroupConnection
28 28
  , getNetworkUuid
29 29
  , instIsConnected
30
  , Runtime
31 30
  , fieldsMap
32
  , collectLiveData
33 31
  ) where
34 32

  
35
-- FIXME: everything except Runtime(..) and fieldsMap
33
-- FIXME: everything except fieldsMap
36 34
-- is only exported for testing.
37 35

  
38 36
import qualified Data.Map as Map
......
47 45
import Ganeti.Query.Types
48 46
import Ganeti.Types
49 47

  
50
-- | There is no actual runtime.
51
data Runtime = Runtime
52

  
53
networkFields :: FieldList Network Runtime
48
networkFields :: FieldList Network NoDataRuntime
54 49
networkFields =
55 50
  [ (FieldDefinition "name" "Network" QFTText "Name",
56 51
     FieldSimple (rsNormal . networkName), QffNormal)
......
98 93
  tagsFields
99 94

  
100 95
-- | The group fields map.
101
fieldsMap :: FieldMap Network Runtime
96
fieldsMap :: FieldMap Network NoDataRuntime
102 97
fieldsMap =
103 98
  Map.fromList $ map (\v@(f, _, _) -> (fdefName f, v)) networkFields
104 99

  
......
177 172
  let addrs = getReservations (networkNetwork net)
178 173
              (fromMaybe "" $ networkExtReservations net)
179 174
  in rsNormal . intercalate ", " $ map show addrs
180

  
181
-- | Dummy function for collecting live data (which networks don't have).
182
collectLiveData :: Bool -> ConfigData -> [Network] -> IO [(Network, Runtime)]
183
collectLiveData _ _ = return . map (\n -> (n, Runtime))
b/src/Ganeti/Query/Query.hs
1
{-# LANGUAGE TupleSections #-}
2

  
1 3
{-| Implementation of the Ganeti Query2 functionality.
2 4

  
3 5
 -}
......
50 52
    , queryCompat
51 53
    , getRequestedNames
52 54
    , nameField
55
    , NoDataRuntime
53 56
    ) where
54 57

  
55 58
import Control.DeepSeq
......
209 212
  queryJobs cfg live fields qfilter
210 213
query cfg live qry = queryInner cfg live qry $ getRequestedNames qry
211 214

  
215
-- | Dummy data collection fuction
216
dummyCollectLiveData :: Bool -> ConfigData -> [a] -> IO [(a, NoDataRuntime)]
217
dummyCollectLiveData _ _ = return . map (, NoDataRuntime)
218

  
212 219
-- | Inner query execution function.
213 220
queryInner :: ConfigData   -- ^ The current configuration
214 221
           -> Bool         -- ^ Whether to collect live data
......
221 228
               cfg live fields qfilter wanted
222 229

  
223 230
queryInner cfg live (Query (ItemTypeOpCode QRInstance) fields qfilter) wanted =
224
  genericQuery Instance.fieldsMap Instance.collectLiveData instName
231
  genericQuery Instance.fieldsMap dummyCollectLiveData instName
225 232
               configInstances getInstance cfg live fields qfilter wanted
226 233

  
227 234
queryInner cfg live (Query (ItemTypeOpCode QRGroup) fields qfilter) wanted =
228
  genericQuery Group.fieldsMap Group.collectLiveData groupName configNodegroups
235
  genericQuery Group.fieldsMap dummyCollectLiveData groupName configNodegroups
229 236
               getGroup cfg live fields qfilter wanted
230 237

  
231 238
queryInner cfg live (Query (ItemTypeOpCode QRNetwork) fields qfilter) wanted =
232
  genericQuery Network.fieldsMap Network.collectLiveData
239
  genericQuery Network.fieldsMap dummyCollectLiveData
233 240
               (fromNonEmpty . networkName)
234 241
               configNetworks getNetwork cfg live fields qfilter wanted
235 242

  

Also available in: Unified diff