Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Kvmd.hs @ dde8b625

History | View | Annotate | Download (3.6 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2
{-| Unittests for the KVM daemon.
3

    
4
-}
5

    
6
{-
7

    
8
Copyright (C) 2013 Google Inc.
9

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

    
15
This program is distributed in the hope that it will be useful, but
16
WITHOUT ANY WARRANTY; without even the implied warranty of
17
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
18
General Public License for more details.
19

    
20
You should have received a copy of the GNU General Public License
21
along with this program; if not, write to the Free Software
22
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
23
02110-1301, USA.
24

    
25
-}
26

    
27
module Test.Ganeti.Kvmd (testKvmd) where
28

    
29
import Control.Concurrent
30
import Control.Exception (try)
31
import qualified Network.Socket as Socket
32
import System.Directory
33
import System.FilePath
34
import System.IO
35

    
36
import qualified Ganeti.Kvmd as Kvmd
37
import qualified Ganeti.UDSServer as UDSServer
38
import Test.HUnit as HUnit
39

    
40
import qualified Test.Ganeti.TestHelper as TestHelper (testSuite)
41
import qualified Test.Ganeti.TestCommon as TestCommon (getTempFileName)
42

    
43
import qualified Ganeti.Logging as Logging
44

    
45
{-# ANN module "HLint: ignore Use camelCase" #-}
46

    
47
startKvmd :: FilePath -> IO ThreadId
48
startKvmd dir =
49
  forkIO (do Logging.setupLogging Nothing "ganeti-kvmd" False False
50
               False Logging.SyslogNo
51
             Kvmd.startWith dir)
52

    
53
stopKvmd :: ThreadId -> IO ()
54
stopKvmd = killThread
55

    
56
delayKvmd :: IO ()
57
delayKvmd = threadDelay 1000000
58

    
59
detectShutdown :: (Handle -> IO ()) -> IO Bool
60
detectShutdown putFn =
61
  do monitorDir <- TestCommon.getTempFileName "ganeti"
62
     let monitor = "instance.qmp"
63
         monitorFile = monitorDir </> monitor
64
         shutdownFile = Kvmd.shutdownPath monitorFile
65
     -- ensure the KVM directory exists
66
     createDirectoryIfMissing True monitorDir
67
     -- ensure the shutdown file does not exist
68
     (try (removeFile shutdownFile) :: IO (Either IOError ())) >> return ()
69
     -- start KVM daemon
70
     threadId <- startKvmd monitorDir
71
     threadDelay 1000
72
     -- create a Unix socket
73
     sock <- UDSServer.openServerSocket monitorFile
74
     Socket.listen sock 1
75
     handle <- UDSServer.acceptSocket sock
76
     -- read 'qmp_capabilities' message
77
     res <- try . hGetLine $ handle :: IO (Either IOError String)
78
     case res of
79
       Left err ->
80
         assertFailure $ "Expecting " ++ show Kvmd.monitorGreeting ++
81
                         ", received " ++ show err
82
       Right str -> Kvmd.monitorGreeting @=? str
83
     -- send Qmp messages
84
     putFn handle
85
     hFlush handle
86
     -- close the Unix socket
87
     UDSServer.closeClientSocket handle
88
     UDSServer.closeServerSocket sock monitorFile
89
     -- KVM needs time to create the shutdown file
90
     delayKvmd
91
     -- stop the KVM daemon
92
     stopKvmd threadId
93
     -- check for shutdown file
94
     doesFileExist shutdownFile
95

    
96
case_DetectAdminShutdown :: Assertion
97
case_DetectAdminShutdown =
98
  do res <- detectShutdown putMessage
99
     assertBool "Detected user shutdown instead of administrator shutdown" $
100
       not res
101
  where putMessage handle =
102
          do hPrint handle "POWERDOWN"
103
             hPrint handle "SHUTDOWN"
104

    
105
case_DetectUserShutdown :: Assertion
106
case_DetectUserShutdown =
107
  do res <- detectShutdown putMessage
108
     assertBool "Detected administrator shutdown instead of user shutdown" res
109
  where putMessage handle =
110
          hPrint handle "SHUTDOWN"
111

    
112
TestHelper.testSuite "Kvmd"
113
  [ 'case_DetectAdminShutdown
114
  , 'case_DetectUserShutdown
115
  ]