Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Types.hs @ c65621d7

History | View | Annotate | Download (8.6 kB)

1 5e9deac0 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 5e9deac0 Iustin Pop
3 5e9deac0 Iustin Pop
{-| Some common Ganeti types.
4 5e9deac0 Iustin Pop
5 5e9deac0 Iustin Pop
This holds types common to both core work, and to htools. Types that
6 5e9deac0 Iustin Pop
are very core specific (e.g. configuration objects) should go in
7 5e9deac0 Iustin Pop
'Ganeti.Objects', while types that are specific to htools in-memory
8 5e9deac0 Iustin Pop
representation should go into 'Ganeti.HTools.Types'.
9 5e9deac0 Iustin Pop
10 5e9deac0 Iustin Pop
-}
11 5e9deac0 Iustin Pop
12 5e9deac0 Iustin Pop
{-
13 5e9deac0 Iustin Pop
14 5e9deac0 Iustin Pop
Copyright (C) 2012 Google Inc.
15 5e9deac0 Iustin Pop
16 5e9deac0 Iustin Pop
This program is free software; you can redistribute it and/or modify
17 5e9deac0 Iustin Pop
it under the terms of the GNU General Public License as published by
18 5e9deac0 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
19 5e9deac0 Iustin Pop
(at your option) any later version.
20 5e9deac0 Iustin Pop
21 5e9deac0 Iustin Pop
This program is distributed in the hope that it will be useful, but
22 5e9deac0 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
23 5e9deac0 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
24 5e9deac0 Iustin Pop
General Public License for more details.
25 5e9deac0 Iustin Pop
26 5e9deac0 Iustin Pop
You should have received a copy of the GNU General Public License
27 5e9deac0 Iustin Pop
along with this program; if not, write to the Free Software
28 5e9deac0 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
29 5e9deac0 Iustin Pop
02110-1301, USA.
30 5e9deac0 Iustin Pop
31 5e9deac0 Iustin Pop
-}
32 5e9deac0 Iustin Pop
33 5e9deac0 Iustin Pop
module Ganeti.Types
34 5e9deac0 Iustin Pop
  ( AllocPolicy(..)
35 5e9deac0 Iustin Pop
  , allocPolicyFromRaw
36 5e9deac0 Iustin Pop
  , allocPolicyToRaw
37 5e9deac0 Iustin Pop
  , InstanceStatus(..)
38 5e9deac0 Iustin Pop
  , instanceStatusFromRaw
39 5e9deac0 Iustin Pop
  , instanceStatusToRaw
40 5e9deac0 Iustin Pop
  , DiskTemplate(..)
41 5e9deac0 Iustin Pop
  , diskTemplateToRaw
42 5e9deac0 Iustin Pop
  , diskTemplateFromRaw
43 edb5a1c8 Iustin Pop
  , NonNegative
44 edb5a1c8 Iustin Pop
  , fromNonNegative
45 edb5a1c8 Iustin Pop
  , mkNonNegative
46 edb5a1c8 Iustin Pop
  , Positive
47 edb5a1c8 Iustin Pop
  , fromPositive
48 edb5a1c8 Iustin Pop
  , mkPositive
49 edb5a1c8 Iustin Pop
  , NonEmpty
50 edb5a1c8 Iustin Pop
  , fromNonEmpty
51 edb5a1c8 Iustin Pop
  , mkNonEmpty
52 6a28e02c Iustin Pop
  , NonEmptyString
53 d696bbef Iustin Pop
  , MigrationMode(..)
54 d696bbef Iustin Pop
  , VerifyOptionalChecks(..)
55 d696bbef Iustin Pop
  , DdmSimple(..)
56 d696bbef Iustin Pop
  , CVErrorCode(..)
57 d696bbef Iustin Pop
  , cVErrorCodeToRaw
58 22381768 Iustin Pop
  , Hypervisor(..)
59 6a28e02c Iustin Pop
  , OobCommand(..)
60 48755fac Iustin Pop
  , StorageType(..)
61 6a28e02c Iustin Pop
  , NodeEvacMode(..)
62 c65621d7 Iustin Pop
  , FileDriver(..)
63 5e9deac0 Iustin Pop
  ) where
64 5e9deac0 Iustin Pop
65 edb5a1c8 Iustin Pop
import qualified Text.JSON as JSON
66 edb5a1c8 Iustin Pop
67 5e9deac0 Iustin Pop
import qualified Ganeti.Constants as C
68 5e9deac0 Iustin Pop
import qualified Ganeti.THH as THH
69 edc1acde Iustin Pop
import Ganeti.JSON
70 5e9deac0 Iustin Pop
71 edb5a1c8 Iustin Pop
-- * Generic types
72 edb5a1c8 Iustin Pop
73 edb5a1c8 Iustin Pop
-- | Type that holds a non-negative value.
74 edb5a1c8 Iustin Pop
newtype NonNegative a = NonNegative { fromNonNegative :: a }
75 edb5a1c8 Iustin Pop
  deriving (Show, Read, Eq)
76 edb5a1c8 Iustin Pop
77 edb5a1c8 Iustin Pop
-- | Smart constructor for 'NonNegative'.
78 edb5a1c8 Iustin Pop
mkNonNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (NonNegative a)
79 edb5a1c8 Iustin Pop
mkNonNegative i | i >= 0 = return (NonNegative i)
80 edb5a1c8 Iustin Pop
                | otherwise = fail $ "Invalid value for non-negative type '" ++
81 edb5a1c8 Iustin Pop
                              show i ++ "'"
82 edb5a1c8 Iustin Pop
83 edb5a1c8 Iustin Pop
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (NonNegative a) where
84 edb5a1c8 Iustin Pop
  showJSON = JSON.showJSON . fromNonNegative
85 edb5a1c8 Iustin Pop
  readJSON v = JSON.readJSON v >>= mkNonNegative
86 edb5a1c8 Iustin Pop
87 edb5a1c8 Iustin Pop
-- | Type that holds a positive value.
88 edb5a1c8 Iustin Pop
newtype Positive a = Positive { fromPositive :: a }
89 edb5a1c8 Iustin Pop
  deriving (Show, Read, Eq)
90 edb5a1c8 Iustin Pop
91 edb5a1c8 Iustin Pop
-- | Smart constructor for 'Positive'.
92 edb5a1c8 Iustin Pop
mkPositive :: (Monad m, Num a, Ord a, Show a) => a -> m (Positive a)
93 edb5a1c8 Iustin Pop
mkPositive i | i > 0 = return (Positive i)
94 edb5a1c8 Iustin Pop
             | otherwise = fail $ "Invalid value for positive type '" ++
95 edb5a1c8 Iustin Pop
                           show i ++ "'"
96 edb5a1c8 Iustin Pop
97 edb5a1c8 Iustin Pop
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Positive a) where
98 edb5a1c8 Iustin Pop
  showJSON = JSON.showJSON . fromPositive
99 edb5a1c8 Iustin Pop
  readJSON v = JSON.readJSON v >>= mkPositive
100 edb5a1c8 Iustin Pop
101 edb5a1c8 Iustin Pop
-- | Type that holds a non-null list.
102 edb5a1c8 Iustin Pop
newtype NonEmpty a = NonEmpty { fromNonEmpty :: [a] }
103 edb5a1c8 Iustin Pop
  deriving (Show, Read, Eq)
104 edb5a1c8 Iustin Pop
105 edb5a1c8 Iustin Pop
-- | Smart constructor for 'NonEmpty'.
106 edb5a1c8 Iustin Pop
mkNonEmpty :: (Monad m) => [a] -> m (NonEmpty a)
107 edb5a1c8 Iustin Pop
mkNonEmpty [] = fail "Received empty value for non-empty list"
108 edb5a1c8 Iustin Pop
mkNonEmpty xs = return (NonEmpty xs)
109 edb5a1c8 Iustin Pop
110 edb5a1c8 Iustin Pop
instance (JSON.JSON a) => JSON.JSON (NonEmpty a) where
111 edb5a1c8 Iustin Pop
  showJSON = JSON.showJSON . fromNonEmpty
112 edb5a1c8 Iustin Pop
  readJSON v = JSON.readJSON v >>= mkNonEmpty
113 edb5a1c8 Iustin Pop
114 6a28e02c Iustin Pop
-- | A simple type alias for non-empty strings.
115 6a28e02c Iustin Pop
type NonEmptyString = NonEmpty Char
116 6a28e02c Iustin Pop
117 edb5a1c8 Iustin Pop
-- * Ganeti types
118 edb5a1c8 Iustin Pop
119 5e9deac0 Iustin Pop
-- | Instance disk template type.
120 5e9deac0 Iustin Pop
$(THH.declareSADT "DiskTemplate"
121 5e9deac0 Iustin Pop
       [ ("DTDiskless",   'C.dtDiskless)
122 5e9deac0 Iustin Pop
       , ("DTFile",       'C.dtFile)
123 5e9deac0 Iustin Pop
       , ("DTSharedFile", 'C.dtSharedFile)
124 5e9deac0 Iustin Pop
       , ("DTPlain",      'C.dtPlain)
125 5e9deac0 Iustin Pop
       , ("DTBlock",      'C.dtBlock)
126 5e9deac0 Iustin Pop
       , ("DTDrbd8",      'C.dtDrbd8)
127 5e9deac0 Iustin Pop
       , ("DTRbd",        'C.dtRbd)
128 5e9deac0 Iustin Pop
       ])
129 5e9deac0 Iustin Pop
$(THH.makeJSONInstance ''DiskTemplate)
130 5e9deac0 Iustin Pop
131 edc1acde Iustin Pop
instance HasStringRepr DiskTemplate where
132 edc1acde Iustin Pop
  fromStringRepr = diskTemplateFromRaw
133 edc1acde Iustin Pop
  toStringRepr = diskTemplateToRaw
134 edc1acde Iustin Pop
135 5e9deac0 Iustin Pop
-- | The Group allocation policy type.
136 5e9deac0 Iustin Pop
--
137 5e9deac0 Iustin Pop
-- Note that the order of constructors is important as the automatic
138 5e9deac0 Iustin Pop
-- Ord instance will order them in the order they are defined, so when
139 5e9deac0 Iustin Pop
-- changing this data type be careful about the interaction with the
140 5e9deac0 Iustin Pop
-- desired sorting order.
141 5e9deac0 Iustin Pop
$(THH.declareSADT "AllocPolicy"
142 5e9deac0 Iustin Pop
       [ ("AllocPreferred",   'C.allocPolicyPreferred)
143 5e9deac0 Iustin Pop
       , ("AllocLastResort",  'C.allocPolicyLastResort)
144 5e9deac0 Iustin Pop
       , ("AllocUnallocable", 'C.allocPolicyUnallocable)
145 5e9deac0 Iustin Pop
       ])
146 5e9deac0 Iustin Pop
$(THH.makeJSONInstance ''AllocPolicy)
147 5e9deac0 Iustin Pop
148 5e9deac0 Iustin Pop
-- | The Instance real state type. FIXME: this could be improved to
149 5e9deac0 Iustin Pop
-- just wrap a /NormalState AdminStatus | ErrorState ErrorCondition/.
150 5e9deac0 Iustin Pop
$(THH.declareSADT "InstanceStatus"
151 5e9deac0 Iustin Pop
       [ ("StatusDown",    'C.inststAdmindown)
152 5e9deac0 Iustin Pop
       , ("StatusOffline", 'C.inststAdminoffline)
153 5e9deac0 Iustin Pop
       , ("ErrorDown",     'C.inststErrordown)
154 5e9deac0 Iustin Pop
       , ("ErrorUp",       'C.inststErrorup)
155 5e9deac0 Iustin Pop
       , ("NodeDown",      'C.inststNodedown)
156 5e9deac0 Iustin Pop
       , ("NodeOffline",   'C.inststNodeoffline)
157 5e9deac0 Iustin Pop
       , ("Running",       'C.inststRunning)
158 5e9deac0 Iustin Pop
       , ("WrongNode",     'C.inststWrongnode)
159 5e9deac0 Iustin Pop
       ])
160 5e9deac0 Iustin Pop
$(THH.makeJSONInstance ''InstanceStatus)
161 d696bbef Iustin Pop
162 d696bbef Iustin Pop
-- | Migration mode.
163 d696bbef Iustin Pop
$(THH.declareSADT "MigrationMode"
164 d696bbef Iustin Pop
     [ ("MigrationLive",    'C.htMigrationLive)
165 d696bbef Iustin Pop
     , ("MigrationNonLive", 'C.htMigrationNonlive)
166 d696bbef Iustin Pop
     ])
167 d696bbef Iustin Pop
$(THH.makeJSONInstance ''MigrationMode)
168 d696bbef Iustin Pop
169 d696bbef Iustin Pop
-- | Verify optional checks.
170 d696bbef Iustin Pop
$(THH.declareSADT "VerifyOptionalChecks"
171 d696bbef Iustin Pop
     [ ("VerifyNPlusOneMem", 'C.verifyNplusoneMem)
172 d696bbef Iustin Pop
     ])
173 d696bbef Iustin Pop
$(THH.makeJSONInstance ''VerifyOptionalChecks)
174 d696bbef Iustin Pop
175 d696bbef Iustin Pop
-- | Cluster verify error codes.
176 d696bbef Iustin Pop
$(THH.declareSADT "CVErrorCode"
177 d696bbef Iustin Pop
  [ ("CvECLUSTERCFG",           'C.cvEclustercfgCode)
178 d696bbef Iustin Pop
  , ("CvECLUSTERCERT",          'C.cvEclustercertCode)
179 d696bbef Iustin Pop
  , ("CvECLUSTERFILECHECK",     'C.cvEclusterfilecheckCode)
180 d696bbef Iustin Pop
  , ("CvECLUSTERDANGLINGNODES", 'C.cvEclusterdanglingnodesCode)
181 d696bbef Iustin Pop
  , ("CvECLUSTERDANGLINGINST",  'C.cvEclusterdanglinginstCode)
182 d696bbef Iustin Pop
  , ("CvEINSTANCEBADNODE",      'C.cvEinstancebadnodeCode)
183 d696bbef Iustin Pop
  , ("CvEINSTANCEDOWN",         'C.cvEinstancedownCode)
184 d696bbef Iustin Pop
  , ("CvEINSTANCELAYOUT",       'C.cvEinstancelayoutCode)
185 d696bbef Iustin Pop
  , ("CvEINSTANCEMISSINGDISK",  'C.cvEinstancemissingdiskCode)
186 d696bbef Iustin Pop
  , ("CvEINSTANCEFAULTYDISK",   'C.cvEinstancefaultydiskCode)
187 d696bbef Iustin Pop
  , ("CvEINSTANCEWRONGNODE",    'C.cvEinstancewrongnodeCode)
188 d696bbef Iustin Pop
  , ("CvEINSTANCESPLITGROUPS",  'C.cvEinstancesplitgroupsCode)
189 d696bbef Iustin Pop
  , ("CvEINSTANCEPOLICY",       'C.cvEinstancepolicyCode)
190 d696bbef Iustin Pop
  , ("CvENODEDRBD",             'C.cvEnodedrbdCode)
191 d696bbef Iustin Pop
  , ("CvENODEDRBDHELPER",       'C.cvEnodedrbdhelperCode)
192 d696bbef Iustin Pop
  , ("CvENODEFILECHECK",        'C.cvEnodefilecheckCode)
193 d696bbef Iustin Pop
  , ("CvENODEHOOKS",            'C.cvEnodehooksCode)
194 d696bbef Iustin Pop
  , ("CvENODEHV",               'C.cvEnodehvCode)
195 d696bbef Iustin Pop
  , ("CvENODELVM",              'C.cvEnodelvmCode)
196 d696bbef Iustin Pop
  , ("CvENODEN1",               'C.cvEnoden1Code)
197 d696bbef Iustin Pop
  , ("CvENODENET",              'C.cvEnodenetCode)
198 d696bbef Iustin Pop
  , ("CvENODEOS",               'C.cvEnodeosCode)
199 d696bbef Iustin Pop
  , ("CvENODEORPHANINSTANCE",   'C.cvEnodeorphaninstanceCode)
200 d696bbef Iustin Pop
  , ("CvENODEORPHANLV",         'C.cvEnodeorphanlvCode)
201 d696bbef Iustin Pop
  , ("CvENODERPC",              'C.cvEnoderpcCode)
202 d696bbef Iustin Pop
  , ("CvENODESSH",              'C.cvEnodesshCode)
203 d696bbef Iustin Pop
  , ("CvENODEVERSION",          'C.cvEnodeversionCode)
204 d696bbef Iustin Pop
  , ("CvENODESETUP",            'C.cvEnodesetupCode)
205 d696bbef Iustin Pop
  , ("CvENODETIME",             'C.cvEnodetimeCode)
206 d696bbef Iustin Pop
  , ("CvENODEOOBPATH",          'C.cvEnodeoobpathCode)
207 d696bbef Iustin Pop
  , ("CvENODEUSERSCRIPTS",      'C.cvEnodeuserscriptsCode)
208 d696bbef Iustin Pop
  , ("CvENODEFILESTORAGEPATHS", 'C.cvEnodefilestoragepathsCode)
209 d696bbef Iustin Pop
  ])
210 d696bbef Iustin Pop
$(THH.makeJSONInstance ''CVErrorCode)
211 d696bbef Iustin Pop
212 d696bbef Iustin Pop
-- | Dynamic device modification, just add\/remove version.
213 d696bbef Iustin Pop
$(THH.declareSADT "DdmSimple"
214 d696bbef Iustin Pop
     [ ("DdmSimpleAdd",    'C.ddmAdd)
215 d696bbef Iustin Pop
     , ("DdmSimpleRemove", 'C.ddmRemove)
216 d696bbef Iustin Pop
     ])
217 d696bbef Iustin Pop
$(THH.makeJSONInstance ''DdmSimple)
218 22381768 Iustin Pop
219 22381768 Iustin Pop
-- | Hypervisor type definitions.
220 22381768 Iustin Pop
$(THH.declareSADT "Hypervisor"
221 22381768 Iustin Pop
  [ ( "Kvm",    'C.htKvm )
222 22381768 Iustin Pop
  , ( "XenPvm", 'C.htXenPvm )
223 22381768 Iustin Pop
  , ( "Chroot", 'C.htChroot )
224 22381768 Iustin Pop
  , ( "XenHvm", 'C.htXenHvm )
225 22381768 Iustin Pop
  , ( "Lxc",    'C.htLxc )
226 22381768 Iustin Pop
  , ( "Fake",   'C.htFake )
227 22381768 Iustin Pop
  ])
228 22381768 Iustin Pop
$(THH.makeJSONInstance ''Hypervisor)
229 48755fac Iustin Pop
230 6a28e02c Iustin Pop
-- | Oob command type.
231 6a28e02c Iustin Pop
$(THH.declareSADT "OobCommand"
232 6a28e02c Iustin Pop
  [ ("OobHealth",      'C.oobHealth)
233 6a28e02c Iustin Pop
  , ("OobPowerCycle",  'C.oobPowerCycle)
234 6a28e02c Iustin Pop
  , ("OobPowerOff",    'C.oobPowerOff)
235 6a28e02c Iustin Pop
  , ("OobPowerOn",     'C.oobPowerOn)
236 6a28e02c Iustin Pop
  , ("OobPowerStatus", 'C.oobPowerStatus)
237 6a28e02c Iustin Pop
  ])
238 6a28e02c Iustin Pop
$(THH.makeJSONInstance ''OobCommand)
239 6a28e02c Iustin Pop
240 48755fac Iustin Pop
-- | Storage type.
241 48755fac Iustin Pop
$(THH.declareSADT "StorageType"
242 48755fac Iustin Pop
  [ ("StorageFile", 'C.stFile)
243 48755fac Iustin Pop
  , ("StorageLvmPv", 'C.stLvmPv)
244 48755fac Iustin Pop
  , ("StorageLvmVg", 'C.stLvmVg)
245 48755fac Iustin Pop
  ])
246 48755fac Iustin Pop
$(THH.makeJSONInstance ''StorageType)
247 6a28e02c Iustin Pop
248 6a28e02c Iustin Pop
-- | Node evac modes.
249 6a28e02c Iustin Pop
$(THH.declareSADT "NodeEvacMode"
250 6a28e02c Iustin Pop
  [ ("NEvacPrimary",   'C.iallocatorNevacPri)
251 6a28e02c Iustin Pop
  , ("NEvacSecondary", 'C.iallocatorNevacSec)
252 6a28e02c Iustin Pop
  , ("NEvacAll",       'C.iallocatorNevacAll)
253 6a28e02c Iustin Pop
  ])
254 6a28e02c Iustin Pop
$(THH.makeJSONInstance ''NodeEvacMode)
255 c65621d7 Iustin Pop
256 c65621d7 Iustin Pop
-- | The file driver type.
257 c65621d7 Iustin Pop
$(THH.declareSADT "FileDriver"
258 c65621d7 Iustin Pop
  [ ("FileLoop",   'C.fdLoop)
259 c65621d7 Iustin Pop
  , ("FileBlktap", 'C.fdBlktap)
260 c65621d7 Iustin Pop
  ])
261 c65621d7 Iustin Pop
$(THH.makeJSONInstance ''FileDriver)