hen-0.1.1: Haskell bindings to Xen hypervisor interface

Safe HaskellNone

System.Xen

Contents

Description

Haskell bidings to Xen hypervisor interface. There are three interface levels in this library:

  • Low-level interface. System.Xen.Low. It just provides bindings to c-calls.
  • Mid-level interface. System.Xen.Mid. Contains helper functions and allow to use your favorite Monad.
  • High-level interface. System.Xen.High. Contains Xen monad and provides a safe way to run any Xen computation.

Last one is also re-exported by current module and intend for common usage. Usage example:

 module Main (main) where

 import System.Xen (runXenT, domainGetInfo)

 main :: IO ()
 main = print =<< runXenT domainGetInfo

Synopsis

Errors

data XcHandleOpenError Source

This error can be raised if handle can not be opened, insufficient rights for example.

Constructors

XcHandleOpenError Errno 

data DomainGetInfoError Source

This error can be raised if any error occured during receiving the list, for example: try to to fetch a list in domU.

Domain info

newtype DomId Source

Domain id, wrapper around Word32.

Constructors

DomId 

Fields

unDomId :: Word32
 

data DomainFlag Source

Domain flags. It's translated from xc_dominfo structure, so it's possible to be mutual exclusion flags in one domain, e.g. DomainFlagShutdown and DomainFlagRunning.

High-level API

Monad stuff

data XenT m a Source

A Xen transformer. This transformers keeps connection to the Xen hypervisor interface.

Instances

MonadTrans XenT 
MonadRWS r w s m => MonadRWS r w s (XenT m) 
MonadReader r m => MonadReader r (XenT m) 
MonadState s m => MonadState s (XenT m) 
MonadWriter w m => MonadWriter w (XenT m) 
Monad m => Monad (XenT m) 
Functor m => Functor (XenT m) 
Applicative m => Applicative (XenT m) 
MonadCatch m => MonadCatch (XenT m) 
MonadIO m => MonadIO (XenT m) 
(Functor m, MonadIO m, MonadCatch m) => MonadXen (XenT m) 

type Xen = XenT IOSource

Most simple XenT implementation.

runXenT :: (Functor m, MonadIO m, MonadCatch m) => XenT m a -> m (Either SomeException a)Source

Open new connection to the hypervisor, run any Xen action and close connection if nessesary. This function can fail with Either SomeException with XcHandleOpenError and any error of providing Xen action.

Domain

domainGetInfo :: MonadXen m => m [DomainInfo]Source

Returns a lift of domains, this function can fail with InvalidDomainShutdownReason and DomainGetInfoError.

Domain pause

domainPause :: MonadXen m => DomId -> m BoolSource

Pause domain. A paused domain still exists in memory however it does not receive any timeslices from the hypervisor.

domainUnpause :: MonadXen m => DomId -> m BoolSource

Unpause a domain. The domain should have been previously paused.

Domain powerstate

domainShutdown :: MonadXen m => DomId -> DomainShutdownReason -> m BoolSource

Shutdown domain. This is intended for use in fully-virtualized domains where this operation is analogous to the sched_op operations in a paravirtualized domain.

domainDestroy :: MonadXen m => DomId -> m BoolSource

Destroy a domain. Destroying a domain removes the domain completely from memory. This function should be called after domainShutdown to free up the domain resources.