module Ganeti.Objects.Disk where
import Prelude ()
import Ganeti.Prelude
import qualified Data.ByteString.UTF8 as UTF8
import Data.Char (isAsciiLower, isAsciiUpper, isDigit)
import Data.List (isPrefixOf, isInfixOf)
import Language.Haskell.TH.Syntax
import Text.JSON (showJSON, readJSON, JSValue(..))
import qualified Text.JSON as J
import Ganeti.JSON (Container, fromObj)
import Ganeti.THH
import Ganeti.THH.Field
import Ganeti.Types
import Ganeti.Utils.Validate
devType :: String
devType = "dev_type"
type DiskParams = Container JSValue
type DRBDSecret = String
data LogicalVolume = LogicalVolume { lvGroup :: String
, lvVolume :: String
}
deriving (Eq, Ord)
instance Show LogicalVolume where
showsPrec _ (LogicalVolume g v) =
showString g . showString "/" . showString v
instance Validatable LogicalVolume where
validate (LogicalVolume g v) = do
let vgn = "Volume group name"
nonEmpty vgn g
validChars vgn g
notStartsDash vgn g
notIn vgn g [".", ".."]
let lvn = "Volume name"
nonEmpty lvn v
validChars lvn v
notStartsDash lvn v
notIn lvn v [".", "..", "snapshot", "pvmove"]
reportIf ("_mlog" `isInfixOf` v) $ lvn ++ " must not contain '_mlog'."
reportIf ("_mimage" `isInfixOf` v) $ lvn ++ "must not contain '_mimage'."
where
nonEmpty prefix x = reportIf (null x) $ prefix ++ " must be non-empty"
notIn prefix x =
mapM_ (\y -> reportIf (x == y)
$ prefix ++ " must not be '" ++ y ++ "'")
notStartsDash prefix x = reportIf ("-" `isPrefixOf` x)
$ prefix ++ " must not start with '-'"
validChars prefix x =
reportIf (not . all validChar $ x)
$ prefix ++ " must consist only of [a-z][A-Z][0-9][+_.-]"
validChar c = isAsciiLower c || isAsciiUpper c || isDigit c
|| (c `elem` "+_.-")
instance J.JSON LogicalVolume where
showJSON = J.showJSON . show
readJSON (J.JSString s) | (g, _ : l) <- break (== '/') (J.fromJSString s) =
either fail return . evalValidate . validate' $ LogicalVolume g l
readJSON v = fail $ "Invalid JSON value " ++ show v
++ " for a logical volume"
data DiskLogicalId
= LIDPlain LogicalVolume
| LIDDrbd8 String String Int Int Int (Private DRBDSecret)
| LIDFile FileDriver String
| LIDSharedFile FileDriver String
| LIDGluster FileDriver String
| LIDBlockDev BlockDriver String
| LIDRados String String
| LIDExt String String
deriving (Show, Eq)
lidDiskType :: DiskLogicalId -> DiskTemplate
lidDiskType (LIDPlain {}) = DTPlain
lidDiskType (LIDDrbd8 {}) = DTDrbd8
lidDiskType (LIDFile {}) = DTFile
lidDiskType (LIDSharedFile {}) = DTSharedFile
lidDiskType (LIDGluster {}) = DTGluster
lidDiskType (LIDBlockDev {}) = DTBlock
lidDiskType (LIDRados {}) = DTRbd
lidDiskType (LIDExt {}) = DTExt
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
getStorageId :: DiskLogicalId -> Maybe String
getStorageId dlid =
case dlid of
LIDPlain lv -> Just $ lvGroup lv ++ "/" ++ lvVolume lv
LIDDrbd8 {} -> Nothing
LIDFile _ path -> Just path
LIDSharedFile _ path -> Just path
LIDGluster _ path -> Just path
LIDBlockDev _ path -> Just path
LIDRados _ path -> Just path
LIDExt _ uniqueName -> Just uniqueName
getExtProvider :: DiskLogicalId -> Maybe String
getExtProvider (LIDExt provider _) = Just provider
getExtProvider _ = Nothing
encodeDLId :: DiskLogicalId -> JSValue
encodeDLId (LIDPlain (LogicalVolume vg lv)) =
JSArray [showJSON vg, showJSON lv]
encodeDLId (LIDDrbd8 nodeA nodeB port minorA minorB key) =
JSArray [ showJSON nodeA, showJSON nodeB, showJSON port
, showJSON minorA, showJSON minorB, showJSON key ]
encodeDLId (LIDRados pool name) = JSArray [showJSON pool, showJSON name]
encodeDLId (LIDFile driver name) = JSArray [showJSON driver, showJSON name]
encodeDLId (LIDSharedFile driver name) =
JSArray [showJSON driver, showJSON name]
encodeDLId (LIDGluster driver name) = JSArray [showJSON driver, showJSON name]
encodeDLId (LIDBlockDev driver name) = JSArray [showJSON driver, showJSON name]
encodeDLId (LIDExt extprovider name) =
JSArray [showJSON extprovider, showJSON name]
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
decodeDLId :: [(String, JSValue)] -> JSValue -> J.Result DiskLogicalId
decodeDLId obj lid = do
dtype <- fromObj obj devType
case dtype of
DTDrbd8 ->
case lid of
JSArray [nA, nB, p, mA, mB, k] ->
LIDDrbd8
<$> readJSON nA
<*> readJSON nB
<*> readJSON p
<*> readJSON mA
<*> readJSON mB
<*> readJSON k
_ -> fail "Can't read logical_id for DRBD8 type"
DTPlain ->
case lid of
JSArray [vg, lv] -> LIDPlain <$>
(LogicalVolume <$> readJSON vg <*> readJSON lv)
_ -> fail "Can't read logical_id for plain type"
DTFile ->
case lid of
JSArray [driver, path] ->
LIDFile
<$> readJSON driver
<*> readJSON path
_ -> fail "Can't read logical_id for file type"
DTSharedFile ->
case lid of
JSArray [driver, path] ->
LIDSharedFile
<$> readJSON driver
<*> readJSON path
_ -> fail "Can't read logical_id for shared file type"
DTGluster ->
case lid of
JSArray [driver, path] ->
LIDGluster
<$> readJSON driver
<*> readJSON path
_ -> fail "Can't read logical_id for shared file type"
DTBlock ->
case lid of
JSArray [driver, path] ->
LIDBlockDev
<$> readJSON driver
<*> readJSON path
_ -> fail "Can't read logical_id for blockdev type"
DTRbd ->
case lid of
JSArray [driver, path] ->
LIDRados
<$> readJSON driver
<*> readJSON path
_ -> fail "Can't read logical_id for rdb type"
DTExt ->
case lid of
JSArray [extprovider, name] ->
LIDExt
<$> readJSON extprovider
<*> readJSON name
_ -> fail "Can't read logical_id for extstorage type"
DTDiskless ->
fail "Retrieved 'diskless' disk."
$(buildObjectWithForthcoming "Disk" "disk" $
[ customField 'decodeDLId 'encodeFullDLId ["dev_type"] $
simpleField "logical_id" [t| DiskLogicalId |]
, defaultField [| [] |]
$ simpleField "children" (return . AppT ListT . ConT $ mkName "Disk")
, defaultField [| [] |] $ simpleField "nodes" [t| [String] |]
, defaultField [| "" |] $ simpleField "iv_name" [t| String |]
, simpleField "size" [t| Int |]
, defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
, optionalField $ simpleField "name" [t| String |]
, optionalField $ simpleField "spindles" [t| Int |]
, optionalField $ simpleField "params" [t| DiskParams |]
]
++ uuidFields
++ serialFields
++ timeStampFields)
instance TimeStampObject Disk where
cTimeOf = diskCtime
mTimeOf = diskMtime
instance UuidObject Disk where
uuidOf = UTF8.toString . diskUuid
instance SerialNoObject Disk where
serialOf = diskSerial
instance ForthcomingObject Disk where
isForthcoming = diskForthcoming
includesLogicalId :: LogicalVolume -> Disk -> Bool
includesLogicalId lv disk =
case diskLogicalId disk of
Just (LIDPlain lv') -> lv' == lv
Just (LIDDrbd8 {}) ->
any (includesLogicalId lv) $ diskChildren disk
_ -> False