| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
System.Statgrab
Description
Monadic context and data types for managing the underlying libstatgrab FFI calls with transparent resource allocation and deallocation.
- data Stats a
- runStats :: MonadIO m => Stats a -> m a
- async :: Stats a -> Stats (Async a)
- snapshot :: (Stat (Struct a), Copy a) => Stats a
- snapshots :: (Stat (Struct a), Copy a) => Stats [a]
- class Stat a
- data family Struct a
- data Host = Host {- hostOsName :: !ByteString
- hostOsRelease :: !ByteString
- hostOsVersion :: !ByteString
- hostPlatform :: !ByteString
- hostName :: !ByteString
- hostBitWidth :: !Integer
- hostState :: !HostState
- hostNCPU :: !Integer
- hostMaxCPU :: !Integer
- hostUptime :: !POSIXTime
- hostSystime :: !POSIXTime
 
- data CPU = CPU {- cpuUser :: !Integer
- cpuKernel :: !Integer
- cpuIdle :: !Integer
- cpuIOWait :: !Integer
- cpuSwap :: !Integer
- cpuNice :: !Integer
- cpuTotal :: !Integer
- cpuCtxSwitches :: !Integer
- cpuVoluntaryCtxSwitches :: !Integer
- cpuInvoluntaryCtxSwitches :: !Integer
- cpuSyscalls :: !Integer
- cpuInterrupts :: !Integer
- cpuSoftInterrupts :: !Integer
- cpuSystime :: !POSIXTime
 
- data CPUPercent = CPUPercent {- cpuPctUser :: !Double
- cpuPctKernel :: !Double
- cpuPctIdle :: !Double
- cpuPctIOWait :: !Double
- cpuPctSwap :: !Double
- cpuPctNice :: !Double
- cpuPctTimeTaken :: !POSIXTime
 
- data Memory = Memory {}
- data Load = Load {}
- data User = User {}
- data Swap = Swap {}
- data FileSystem = FileSystem {- fsDeviceName :: !ByteString
- fsType :: !ByteString
- fsMountPoint :: !ByteString
- fsDeviceType :: !DeviceType
- fsSize :: !Integer
- fsUsed :: !Integer
- fsFree :: !Integer
- fsAvail :: !Integer
- fsTotalInodes :: !Integer
- fsUsedInodes :: !Integer
- fsFreeInodes :: !Integer
- fsAvailInodes :: !Integer
- fsIOSize :: !Integer
- fsBlockSize :: !Integer
- fsTotalBlocks :: !Integer
- fsFreeBlocks :: !Integer
- fsUsedBlocks :: !Integer
- fsAvailBlocks :: !Integer
- fsSystime :: !POSIXTime
 
- data DiskIO = DiskIO {- diskName :: !ByteString
- diskRead :: !Integer
- diskWrite :: !Integer
- diskSystime :: !POSIXTime
 
- data NetworkIO = NetworkIO {- ifaceIOName :: !ByteString
- ifaceTX :: !Integer
- ifaceRX :: !Integer
- ifaceIPackets :: !Integer
- ifaceOPackets :: !Integer
- ifaceIErrors :: !Integer
- ifaceOErrors :: !Integer
- ifaceCollisions :: !Integer
- ifaceSystem :: !POSIXTime
 
- data NetworkInterface = NetworkInterface {}
- data Page = Page {}
- data Process = Process {- procName :: !ByteString
- procTitle :: !ByteString
- procPid :: !Integer
- procParent :: !Integer
- procPGid :: !Integer
- procSessId :: !Integer
- procUid :: !Integer
- procEUid :: !Integer
- procGid :: !Integer
- procEGid :: !Integer
- procSwitches :: !Integer
- procVoluntary :: !Integer
- procInvoluntary :: !Integer
- procSize :: !Integer
- procResident :: !Integer
- procStart :: !POSIXTime
- procSpent :: !POSIXTime
- procCPUPercent :: !Double
- procNice :: !Integer
- procState :: !ProcessState
- procSystime :: !POSIXTime
 
- data ProcessCount = ProcessCount {- countTotal :: !Integer
- countRunning :: !Integer
- countSleeping :: !Integer
- countStopped :: !Integer
- countZombie :: !Integer
- countUnknown :: !Integer
- countSystime :: !POSIXTime
 
- newtype HostState = HostState CInt
- newtype CPUPercentSource = CPUPercentSource CInt
- newtype DeviceType = DeviceType CInt
- newtype InterfaceMode = InterfaceMode CInt
- newtype InterfaceStatus = InterfaceStatus CInt
- newtype ProcessState = ProcessState CInt
- newtype ProcessSource = ProcessSource CInt
- data Async a :: * -> *
- wait :: Async a -> IO a
Running the Stats Monad
runStats :: MonadIO m => Stats a -> m a Source
Run the Stats Monad, bracketing libstatgrab's sg_init and sg_shutdown
 calls via reference counting to ensure reentrancy.
Retrieving Statistics
snapshot :: (Stat (Struct a), Copy a) => Stats a Source
Retrieve statistics from the underlying operating system, copying them to
 the Haskell heap and freeing the related Ptr a.
The *_r variants of the libstatgrab functions are used and the deallocation strategy is bracketed.
snapshots :: (Stat (Struct a), Copy a) => Stats [a] Source
Retrieve a list of statistics from the underlying operating system.
See: snapshot.
Bracket routines for acquiring and releasing Ptr as.
Minimal complete definition
acquire, release
Instances
Statistic Types
Constructors
| Host | |
| Fields 
 | |
Instances
| Eq Host | |
| Ord Host | |
| Show Host | |
| Generic Host | |
| Storable (Struct Host) | |
| Stat (Struct Host) | |
| type Rep Host | |
| data Struct Host = CHost { 
 | 
Constructors
| CPU | |
| Fields 
 | |
Instances
| Eq CPU | |
| Ord CPU | |
| Show CPU | |
| Generic CPU | |
| Storable (Struct CPU) | |
| Stat (Struct CPU) | |
| type Rep CPU | |
| data Struct CPU = CCPU { 
 | 
data CPUPercent Source
Constructors
| CPUPercent | |
| Fields 
 | |
Instances
| Eq CPUPercent | |
| Ord CPUPercent | |
| Show CPUPercent | |
| Generic CPUPercent | |
| Storable (Struct CPUPercent) | |
| type Rep CPUPercent | |
| data Struct CPUPercent = CCPUPercent { 
 | 
Constructors
| Memory | |
Constructors
| Load | |
Constructors
| User | |
| Fields 
 | |
Instances
| Eq User | |
| Ord User | |
| Show User | |
| Generic User | |
| Storable (Struct User) | |
| Stat (Struct User) | |
| type Rep User | |
| data Struct User = CUser { 
 | 
Constructors
| Swap | |
data FileSystem Source
Constructors
| FileSystem | |
| Fields 
 | |
Instances
| Eq FileSystem | |
| Ord FileSystem | |
| Show FileSystem | |
| Generic FileSystem | |
| Storable (Struct FileSystem) | |
| Stat (Struct FileSystem) | |
| type Rep FileSystem | |
| data Struct FileSystem = CFileSystem { 
 | 
Constructors
| DiskIO | |
| Fields 
 | |
Constructors
| NetworkIO | |
| Fields 
 | |
Instances
| Eq NetworkIO | |
| Ord NetworkIO | |
| Show NetworkIO | |
| Generic NetworkIO | |
| Storable (Struct NetworkIO) | |
| Stat (Struct NetworkIO) | |
| type Rep NetworkIO | |
| data Struct NetworkIO = CNetworkIO { 
 | 
data NetworkInterface Source
Constructors
| NetworkInterface | |
| Fields 
 | |
Instances
Constructors
| Process | |
| Fields 
 | |
Instances
| Eq Process | |
| Ord Process | |
| Show Process | |
| Generic Process | |
| Storable (Struct Process) | |
| Stat (Struct Process) | |
| type Rep Process | |
| data Struct Process = CProcess { 
 | 
data ProcessCount Source
Constructors
| ProcessCount | |
| Fields 
 | |
Instances
| Eq ProcessCount | |
| Ord ProcessCount | |
| Show ProcessCount | |
| Generic ProcessCount | |
| Storable (Struct ProcessCount) | |
| type Rep ProcessCount | |
| data Struct ProcessCount = CProcessCount { 
 | 
Enums
newtype CPUPercentSource Source
Constructors
| CPUPercentSource CInt | 
newtype DeviceType Source
Constructors
| DeviceType CInt | 
newtype InterfaceMode Source
Constructors
| InterfaceMode CInt | 
newtype InterfaceStatus Source
Constructors
| InterfaceStatus CInt | 
newtype ProcessState Source
Constructors
| ProcessState CInt | 
newtype ProcessSource Source
Constructors
| ProcessSource CInt |