Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Types.hs @ 6a28e02c

History | View | Annotate | Download (8.4 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Some common Ganeti types.
4

    
5
This holds types common to both core work, and to htools. Types that
6
are very core specific (e.g. configuration objects) should go in
7
'Ganeti.Objects', while types that are specific to htools in-memory
8
representation should go into 'Ganeti.HTools.Types'.
9

    
10
-}
11

    
12
{-
13

    
14
Copyright (C) 2012 Google Inc.
15

    
16
This program is free software; you can redistribute it and/or modify
17
it under the terms of the GNU General Public License as published by
18
the Free Software Foundation; either version 2 of the License, or
19
(at your option) any later version.
20

    
21
This program is distributed in the hope that it will be useful, but
22
WITHOUT ANY WARRANTY; without even the implied warranty of
23
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
24
General Public License for more details.
25

    
26
You should have received a copy of the GNU General Public License
27
along with this program; if not, write to the Free Software
28
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
29
02110-1301, USA.
30

    
31
-}
32

    
33
module Ganeti.Types
34
  ( AllocPolicy(..)
35
  , allocPolicyFromRaw
36
  , allocPolicyToRaw
37
  , InstanceStatus(..)
38
  , instanceStatusFromRaw
39
  , instanceStatusToRaw
40
  , DiskTemplate(..)
41
  , diskTemplateToRaw
42
  , diskTemplateFromRaw
43
  , NonNegative
44
  , fromNonNegative
45
  , mkNonNegative
46
  , Positive
47
  , fromPositive
48
  , mkPositive
49
  , NonEmpty
50
  , fromNonEmpty
51
  , mkNonEmpty
52
  , NonEmptyString
53
  , MigrationMode(..)
54
  , VerifyOptionalChecks(..)
55
  , DdmSimple(..)
56
  , CVErrorCode(..)
57
  , cVErrorCodeToRaw
58
  , Hypervisor(..)
59
  , OobCommand(..)
60
  , StorageType(..)
61
  , NodeEvacMode(..)
62
  ) where
63

    
64
import qualified Text.JSON as JSON
65

    
66
import qualified Ganeti.Constants as C
67
import qualified Ganeti.THH as THH
68
import Ganeti.JSON
69

    
70
-- * Generic types
71

    
72
-- | Type that holds a non-negative value.
73
newtype NonNegative a = NonNegative { fromNonNegative :: a }
74
  deriving (Show, Read, Eq)
75

    
76
-- | Smart constructor for 'NonNegative'.
77
mkNonNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (NonNegative a)
78
mkNonNegative i | i >= 0 = return (NonNegative i)
79
                | otherwise = fail $ "Invalid value for non-negative type '" ++
80
                              show i ++ "'"
81

    
82
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (NonNegative a) where
83
  showJSON = JSON.showJSON . fromNonNegative
84
  readJSON v = JSON.readJSON v >>= mkNonNegative
85

    
86
-- | Type that holds a positive value.
87
newtype Positive a = Positive { fromPositive :: a }
88
  deriving (Show, Read, Eq)
89

    
90
-- | Smart constructor for 'Positive'.
91
mkPositive :: (Monad m, Num a, Ord a, Show a) => a -> m (Positive a)
92
mkPositive i | i > 0 = return (Positive i)
93
             | otherwise = fail $ "Invalid value for positive type '" ++
94
                           show i ++ "'"
95

    
96
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Positive a) where
97
  showJSON = JSON.showJSON . fromPositive
98
  readJSON v = JSON.readJSON v >>= mkPositive
99

    
100
-- | Type that holds a non-null list.
101
newtype NonEmpty a = NonEmpty { fromNonEmpty :: [a] }
102
  deriving (Show, Read, Eq)
103

    
104
-- | Smart constructor for 'NonEmpty'.
105
mkNonEmpty :: (Monad m) => [a] -> m (NonEmpty a)
106
mkNonEmpty [] = fail "Received empty value for non-empty list"
107
mkNonEmpty xs = return (NonEmpty xs)
108

    
109
instance (JSON.JSON a) => JSON.JSON (NonEmpty a) where
110
  showJSON = JSON.showJSON . fromNonEmpty
111
  readJSON v = JSON.readJSON v >>= mkNonEmpty
112

    
113
-- | A simple type alias for non-empty strings.
114
type NonEmptyString = NonEmpty Char
115

    
116
-- * Ganeti types
117

    
118
-- | Instance disk template type.
119
$(THH.declareSADT "DiskTemplate"
120
       [ ("DTDiskless",   'C.dtDiskless)
121
       , ("DTFile",       'C.dtFile)
122
       , ("DTSharedFile", 'C.dtSharedFile)
123
       , ("DTPlain",      'C.dtPlain)
124
       , ("DTBlock",      'C.dtBlock)
125
       , ("DTDrbd8",      'C.dtDrbd8)
126
       , ("DTRbd",        'C.dtRbd)
127
       ])
128
$(THH.makeJSONInstance ''DiskTemplate)
129

    
130
instance HasStringRepr DiskTemplate where
131
  fromStringRepr = diskTemplateFromRaw
132
  toStringRepr = diskTemplateToRaw
133

    
134
-- | The Group allocation policy type.
135
--
136
-- Note that the order of constructors is important as the automatic
137
-- Ord instance will order them in the order they are defined, so when
138
-- changing this data type be careful about the interaction with the
139
-- desired sorting order.
140
$(THH.declareSADT "AllocPolicy"
141
       [ ("AllocPreferred",   'C.allocPolicyPreferred)
142
       , ("AllocLastResort",  'C.allocPolicyLastResort)
143
       , ("AllocUnallocable", 'C.allocPolicyUnallocable)
144
       ])
145
$(THH.makeJSONInstance ''AllocPolicy)
146

    
147
-- | The Instance real state type. FIXME: this could be improved to
148
-- just wrap a /NormalState AdminStatus | ErrorState ErrorCondition/.
149
$(THH.declareSADT "InstanceStatus"
150
       [ ("StatusDown",    'C.inststAdmindown)
151
       , ("StatusOffline", 'C.inststAdminoffline)
152
       , ("ErrorDown",     'C.inststErrordown)
153
       , ("ErrorUp",       'C.inststErrorup)
154
       , ("NodeDown",      'C.inststNodedown)
155
       , ("NodeOffline",   'C.inststNodeoffline)
156
       , ("Running",       'C.inststRunning)
157
       , ("WrongNode",     'C.inststWrongnode)
158
       ])
159
$(THH.makeJSONInstance ''InstanceStatus)
160

    
161
-- | Migration mode.
162
$(THH.declareSADT "MigrationMode"
163
     [ ("MigrationLive",    'C.htMigrationLive)
164
     , ("MigrationNonLive", 'C.htMigrationNonlive)
165
     ])
166
$(THH.makeJSONInstance ''MigrationMode)
167

    
168
-- | Verify optional checks.
169
$(THH.declareSADT "VerifyOptionalChecks"
170
     [ ("VerifyNPlusOneMem", 'C.verifyNplusoneMem)
171
     ])
172
$(THH.makeJSONInstance ''VerifyOptionalChecks)
173

    
174
-- | Cluster verify error codes.
175
$(THH.declareSADT "CVErrorCode"
176
  [ ("CvECLUSTERCFG",           'C.cvEclustercfgCode)
177
  , ("CvECLUSTERCERT",          'C.cvEclustercertCode)
178
  , ("CvECLUSTERFILECHECK",     'C.cvEclusterfilecheckCode)
179
  , ("CvECLUSTERDANGLINGNODES", 'C.cvEclusterdanglingnodesCode)
180
  , ("CvECLUSTERDANGLINGINST",  'C.cvEclusterdanglinginstCode)
181
  , ("CvEINSTANCEBADNODE",      'C.cvEinstancebadnodeCode)
182
  , ("CvEINSTANCEDOWN",         'C.cvEinstancedownCode)
183
  , ("CvEINSTANCELAYOUT",       'C.cvEinstancelayoutCode)
184
  , ("CvEINSTANCEMISSINGDISK",  'C.cvEinstancemissingdiskCode)
185
  , ("CvEINSTANCEFAULTYDISK",   'C.cvEinstancefaultydiskCode)
186
  , ("CvEINSTANCEWRONGNODE",    'C.cvEinstancewrongnodeCode)
187
  , ("CvEINSTANCESPLITGROUPS",  'C.cvEinstancesplitgroupsCode)
188
  , ("CvEINSTANCEPOLICY",       'C.cvEinstancepolicyCode)
189
  , ("CvENODEDRBD",             'C.cvEnodedrbdCode)
190
  , ("CvENODEDRBDHELPER",       'C.cvEnodedrbdhelperCode)
191
  , ("CvENODEFILECHECK",        'C.cvEnodefilecheckCode)
192
  , ("CvENODEHOOKS",            'C.cvEnodehooksCode)
193
  , ("CvENODEHV",               'C.cvEnodehvCode)
194
  , ("CvENODELVM",              'C.cvEnodelvmCode)
195
  , ("CvENODEN1",               'C.cvEnoden1Code)
196
  , ("CvENODENET",              'C.cvEnodenetCode)
197
  , ("CvENODEOS",               'C.cvEnodeosCode)
198
  , ("CvENODEORPHANINSTANCE",   'C.cvEnodeorphaninstanceCode)
199
  , ("CvENODEORPHANLV",         'C.cvEnodeorphanlvCode)
200
  , ("CvENODERPC",              'C.cvEnoderpcCode)
201
  , ("CvENODESSH",              'C.cvEnodesshCode)
202
  , ("CvENODEVERSION",          'C.cvEnodeversionCode)
203
  , ("CvENODESETUP",            'C.cvEnodesetupCode)
204
  , ("CvENODETIME",             'C.cvEnodetimeCode)
205
  , ("CvENODEOOBPATH",          'C.cvEnodeoobpathCode)
206
  , ("CvENODEUSERSCRIPTS",      'C.cvEnodeuserscriptsCode)
207
  , ("CvENODEFILESTORAGEPATHS", 'C.cvEnodefilestoragepathsCode)
208
  ])
209
$(THH.makeJSONInstance ''CVErrorCode)
210

    
211
-- | Dynamic device modification, just add\/remove version.
212
$(THH.declareSADT "DdmSimple"
213
     [ ("DdmSimpleAdd",    'C.ddmAdd)
214
     , ("DdmSimpleRemove", 'C.ddmRemove)
215
     ])
216
$(THH.makeJSONInstance ''DdmSimple)
217

    
218
-- | Hypervisor type definitions.
219
$(THH.declareSADT "Hypervisor"
220
  [ ( "Kvm",    'C.htKvm )
221
  , ( "XenPvm", 'C.htXenPvm )
222
  , ( "Chroot", 'C.htChroot )
223
  , ( "XenHvm", 'C.htXenHvm )
224
  , ( "Lxc",    'C.htLxc )
225
  , ( "Fake",   'C.htFake )
226
  ])
227
$(THH.makeJSONInstance ''Hypervisor)
228

    
229
-- | Oob command type.
230
$(THH.declareSADT "OobCommand"
231
  [ ("OobHealth",      'C.oobHealth)
232
  , ("OobPowerCycle",  'C.oobPowerCycle)
233
  , ("OobPowerOff",    'C.oobPowerOff)
234
  , ("OobPowerOn",     'C.oobPowerOn)
235
  , ("OobPowerStatus", 'C.oobPowerStatus)
236
  ])
237
$(THH.makeJSONInstance ''OobCommand)
238

    
239
-- | Storage type.
240
$(THH.declareSADT "StorageType"
241
  [ ("StorageFile", 'C.stFile)
242
  , ("StorageLvmPv", 'C.stLvmPv)
243
  , ("StorageLvmVg", 'C.stLvmVg)
244
  ])
245
$(THH.makeJSONInstance ''StorageType)
246

    
247
-- | Node evac modes.
248
$(THH.declareSADT "NodeEvacMode"
249
  [ ("NEvacPrimary",   'C.iallocatorNevacPri)
250
  , ("NEvacSecondary", 'C.iallocatorNevacSec)
251
  , ("NEvacAll",       'C.iallocatorNevacAll)
252
  ])
253
$(THH.makeJSONInstance ''NodeEvacMode)