Skip to content
Snippets Groups Projects
Commit 19f38ee8 authored by Iustin Pop's avatar Iustin Pop
Browse files

Move the RqType and Request types to Loader.hs

These two will be more generic than now, and belong somewhere else -
Loader.hs is a generic module for data loading, thus we move them there.
parent d85a0a0f
No related branches found
No related tags found
No related merge requests found
......@@ -3,11 +3,8 @@
-}
module Ganeti.HTools.IAlloc
(
parseData
( parseData
, formatResponse
, RqType(..)
, Request(..)
) where
import Data.Either ()
......@@ -22,17 +19,6 @@ import Ganeti.HTools.Loader
import Ganeti.HTools.Utils
import Ganeti.HTools.Types
-- | The request type.
data RqType
= Allocate Instance.Instance Int -- ^ A new instance allocation
| Relocate Idx Int [Ndx] -- ^ Move an instance to a new
-- secondary node
deriving (Show)
-- | A complete request, as received from Ganeti.
data Request = Request RqType Node.List Instance.List String
deriving (Show)
-- | Parse the basic specifications of an instance.
--
-- Instances in the cluster instance list and the instance in an
......
......@@ -11,6 +11,8 @@ module Ganeti.HTools.Loader
, lookupNode
, lookupInstance
, stripSuffix
, RqType(..)
, Request(..)
) where
import Data.List
......@@ -23,6 +25,26 @@ import qualified Ganeti.HTools.Node as Node
import Ganeti.HTools.Types
-- * Types
{-| The request type.
This type denotes what request we got from Ganeti and also holds
request-specific fields.
-}
data RqType
= Allocate Instance.Instance Int -- ^ A new instance allocation
| Relocate Idx Int [Ndx] -- ^ Move an instance to a new
-- secondary node
deriving (Show)
-- | A complete request, as received from Ganeti.
data Request = Request RqType Node.List Instance.List String
deriving (Show)
-- * Functions
-- | Lookups a node into an assoc list.
lookupNode :: (Monad m) => [(String, Ndx)] -> String -> String -> m Ndx
lookupNode ktn inst node =
......
......@@ -3,7 +3,12 @@
-}
module Ganeti.HTools.Types
where
( Idx
, Ndx
, NameAssoc
, Result(..)
, Element(..)
) where
-- | The instance index type.
type Idx = Int
......
......@@ -22,6 +22,7 @@ import qualified Ganeti.HTools.Instance as Instance
import qualified Ganeti.HTools.CLI as CLI
import Ganeti.HTools.IAlloc
import Ganeti.HTools.Types
import Ganeti.HTools.Loader (RqType(..), Request(..))
-- | Command line options structure.
data Options = Options
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment