Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Hypervisor / Xen / Types.hs @ 11e90588

History | View | Annotate | Download (3.9 kB)

1 b8585908 Michele Tartara
{-# LANGUAGE FlexibleInstances, TypeSynonymInstances #-}
2 b8585908 Michele Tartara
{-| Data types for Xen-specific hypervisor functionalities.
3 b8585908 Michele Tartara
4 b8585908 Michele Tartara
-}
5 b8585908 Michele Tartara
{-
6 b8585908 Michele Tartara
7 b8585908 Michele Tartara
Copyright (C) 2013 Google Inc.
8 b8585908 Michele Tartara
9 b8585908 Michele Tartara
This program is free software; you can redistribute it and/or modify
10 b8585908 Michele Tartara
it under the terms of the GNU General Public License as published by
11 b8585908 Michele Tartara
the Free Software Foundation; either version 2 of the License, or
12 b8585908 Michele Tartara
(at your option) any later version.
13 b8585908 Michele Tartara
14 b8585908 Michele Tartara
This program is distributed in the hope that it will be useful, but
15 b8585908 Michele Tartara
WITHOUT ANY WARRANTY; without even the implied warranty of
16 b8585908 Michele Tartara
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 b8585908 Michele Tartara
General Public License for more details.
18 b8585908 Michele Tartara
19 b8585908 Michele Tartara
You should have received a copy of the GNU General Public License
20 b8585908 Michele Tartara
along with this program; if not, write to the Free Software
21 b8585908 Michele Tartara
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 b8585908 Michele Tartara
02110-1301, USA.
23 b8585908 Michele Tartara
24 b8585908 Michele Tartara
-}
25 b8585908 Michele Tartara
module Ganeti.Hypervisor.Xen.Types
26 b8585908 Michele Tartara
  ( LispConfig(..)
27 b8585908 Michele Tartara
  , Domain(..)
28 b8585908 Michele Tartara
  , FromLispConfig(..)
29 c5a957c3 Michele Tartara
  , UptimeInfo(..)
30 b8585908 Michele Tartara
  , ActualState(..)
31 b8585908 Michele Tartara
  ) where
32 b8585908 Michele Tartara
33 b8585908 Michele Tartara
import qualified Text.JSON as J
34 b8585908 Michele Tartara
35 b8585908 Michele Tartara
import Ganeti.BasicTypes
36 b8585908 Michele Tartara
37 b8585908 Michele Tartara
-- | Data type representing configuration data as produced by the
38 b8585908 Michele Tartara
-- @xm list --long@ command.
39 b8585908 Michele Tartara
data LispConfig = LCList [LispConfig]
40 b8585908 Michele Tartara
                | LCString String
41 b8585908 Michele Tartara
                | LCDouble Double
42 b8585908 Michele Tartara
                deriving (Eq, Show)
43 b8585908 Michele Tartara
44 b8585908 Michele Tartara
-- | Data type representing a Xen Domain.
45 b8585908 Michele Tartara
data Domain = Domain
46 b8585908 Michele Tartara
  { domId      :: Int
47 b8585908 Michele Tartara
  , domName    :: String
48 b8585908 Michele Tartara
  , domCpuTime :: Double
49 b8585908 Michele Tartara
  , domState   :: ActualState
50 b8585908 Michele Tartara
  , domIsHung  :: Maybe Bool
51 b8585908 Michele Tartara
  } deriving (Show, Eq)
52 b8585908 Michele Tartara
53 b8585908 Michele Tartara
-- | Class representing all the types that can be extracted from LispConfig.
54 b8585908 Michele Tartara
class FromLispConfig a where
55 b8585908 Michele Tartara
  fromLispConfig :: LispConfig -> Result a
56 b8585908 Michele Tartara
57 b8585908 Michele Tartara
-- | Instance of FromLispConfig for Int.
58 b8585908 Michele Tartara
instance FromLispConfig Int where
59 b8585908 Michele Tartara
  fromLispConfig (LCDouble d) = Ok $ floor d
60 b8585908 Michele Tartara
  fromLispConfig (LCList (LCString _:LCDouble d:[])) = Ok $ floor d
61 b8585908 Michele Tartara
  fromLispConfig c =
62 b8585908 Michele Tartara
    Bad $ "Unable to extract a Int from this configuration: "
63 b8585908 Michele Tartara
      ++ show c
64 b8585908 Michele Tartara
65 b8585908 Michele Tartara
-- | Instance of FromLispConfig for Double.
66 b8585908 Michele Tartara
instance FromLispConfig Double where
67 b8585908 Michele Tartara
  fromLispConfig (LCDouble d) = Ok d
68 b8585908 Michele Tartara
  fromLispConfig (LCList (LCString _:LCDouble d:[])) = Ok d
69 b8585908 Michele Tartara
  fromLispConfig c =
70 b8585908 Michele Tartara
    Bad $ "Unable to extract a Double from this configuration: "
71 b8585908 Michele Tartara
      ++ show c
72 b8585908 Michele Tartara
73 b8585908 Michele Tartara
-- | Instance of FromLispConfig for String
74 b8585908 Michele Tartara
instance FromLispConfig String where
75 b8585908 Michele Tartara
  fromLispConfig (LCString s) = Ok s
76 b8585908 Michele Tartara
  fromLispConfig (LCList (LCString _:LCString s:[])) = Ok s
77 b8585908 Michele Tartara
  fromLispConfig c =
78 b8585908 Michele Tartara
    Bad $ "Unable to extract a String from this configuration: "
79 b8585908 Michele Tartara
      ++ show c
80 b8585908 Michele Tartara
81 b8585908 Michele Tartara
-- | Instance of FromLispConfig for [LispConfig]
82 b8585908 Michele Tartara
instance FromLispConfig [LispConfig] where
83 b8585908 Michele Tartara
  fromLispConfig (LCList l) = Ok l
84 b8585908 Michele Tartara
  fromLispConfig c =
85 b8585908 Michele Tartara
    Bad $ "Unable to extract a List from this configuration: "
86 b8585908 Michele Tartara
      ++ show c
87 b8585908 Michele Tartara
88 c5a957c3 Michele Tartara
-- Data type representing the information that can be obtained from @xm uptime@
89 c5a957c3 Michele Tartara
data UptimeInfo = UptimeInfo
90 c5a957c3 Michele Tartara
  { uInfoName   :: String
91 c5a957c3 Michele Tartara
  , uInfoID     :: Int
92 c5a957c3 Michele Tartara
  , uInfoUptime :: String
93 c5a957c3 Michele Tartara
  } deriving (Eq, Show)
94 c5a957c3 Michele Tartara
95 b8585908 Michele Tartara
data ActualState = ActualRunning  -- ^ The instance is running
96 b8585908 Michele Tartara
                 | ActualBlocked  -- ^ The instance is not running or runnable
97 b8585908 Michele Tartara
                 | ActualPaused   -- ^ The instance has been paused
98 b8585908 Michele Tartara
                 | ActualShutdown -- ^ The instance is shut down
99 b8585908 Michele Tartara
                 | ActualCrashed  -- ^ The instance has crashed
100 b8585908 Michele Tartara
                 | ActualDying    -- ^ The instance is in process of dying
101 b8585908 Michele Tartara
                 | ActualHung     -- ^ The instance is hung
102 b8585908 Michele Tartara
                 | ActualUnknown  -- ^ Unknown state. Parsing error.
103 b8585908 Michele Tartara
                 deriving (Show, Eq)
104 b8585908 Michele Tartara
105 b8585908 Michele Tartara
instance J.JSON ActualState where
106 b8585908 Michele Tartara
  showJSON ActualRunning = J.showJSON "running"
107 b8585908 Michele Tartara
  showJSON ActualBlocked = J.showJSON "blocked"
108 b8585908 Michele Tartara
  showJSON ActualPaused = J.showJSON "paused"
109 b8585908 Michele Tartara
  showJSON ActualShutdown = J.showJSON "shutdown"
110 b8585908 Michele Tartara
  showJSON ActualCrashed = J.showJSON "crashed"
111 b8585908 Michele Tartara
  showJSON ActualDying = J.showJSON "dying"
112 b8585908 Michele Tartara
  showJSON ActualHung = J.showJSON "hung"
113 b8585908 Michele Tartara
  showJSON ActualUnknown = J.showJSON "unknown"
114 b8585908 Michele Tartara
115 b8585908 Michele Tartara
  readJSON = error "JSON read instance not implemented for type ActualState"