cpuid-0.2.3.1: Binding for the cpuid machine instruction on x86 compatible processors
Copyright(c) 20082010 Martin Grabmueller
(c) 2011 Henning Thielemann
LicenseGPL
Maintainermartin@grabmueller.de
Stabilityprovisional
Portabilitynon-portable (requires IA-32 processor)
Safe HaskellSafe-Inferred
LanguageHaskell98

System.Cpuid

Description

This module provides the function cpuid for accessing the cpuid instruction on modern IA-32 processors. Additionally, some convenience functions are provided, which perform some of the (really complicated and obstruse) decoding.

As an example, you may use the following program to determine some characteristics of your machine:

module Main(main) where

import Text.Printf (printf, )
import System.Cpuid

main :: IO ()
main = do
   (a, b, c, d) <- cpuid 0
   _ <- printf "Basic CPUID usage: EAX=0: %8x %8x %8x %8x\n\n" a b c d
   _ <- printf "Vendor string: %s\n\n" =<< vendorString
   _ <- printf "Brand string: %s\n\n" =<< brandString
   putStrLn "Cache information:"
   putStrLn . unlines .
      map (\ v -> "  " ++ show v) =<< cacheInfo
   p <- processorInfo
   _ <- printf "Processor info: family: %d, model: %d, stepping: %d, processor type: %d\n"
      (piFamily p) (piModel p) (piStepping p) (piType p)
   return ()
Synopsis

Functions

cpuid :: Word32 -> IO (Word32, Word32, Word32, Word32) Source #

Execute the cpuid instructions with the given argument in the EAX register. Return the values of the registers EAX, EBX, ECX and EDX in that order.

processorInfo :: IO ProcessorInfo Source #

Retrieve basic processor information from the processor using the cpuid instruction.

vendorString :: IO String Source #

Execute the cpuid instruction and return the vendor string reported by that instruction.

brandString :: IO String Source #

Execute the cpuid instruction and return the brand string (processor name and maximum frequency) reported by that instruction.

cacheInfo :: IO [CacheInfo] Source #

Fetch all available cache information from the processor, using the cpuid instruction. The list is not ordered.

Data types

data Associativity Source #

Cache associativity. For some entries, this is not specified in the manual. We report these as DirectMapped.

Instances

Instances details
Show Associativity Source # 
Instance details

Defined in System.Cpuid

data PageSize Source #

Page size. Some entries can have alternative page sizes, therefore the complicated type.

Instances

Instances details
Show PageSize Source # 
Instance details

Defined in System.Cpuid

newtype Ways Source #

Associativity in a set-associative cache.

Constructors

Ways Int 

Instances

Instances details
Show Ways Source # 
Instance details

Defined in System.Cpuid

Methods

showsPrec :: Int -> Ways -> ShowS #

show :: Ways -> String #

showList :: [Ways] -> ShowS #

newtype Entries Source #

Number of entries in a TLB.

Constructors

Entries Int 

Instances

Instances details
Show Entries Source # 
Instance details

Defined in System.Cpuid

data CacheSize Source #

Cache size. Some entries can have alternative cache sizes, therefore the complicated type.

Instances

Instances details
Show CacheSize Source # 
Instance details

Defined in System.Cpuid

data CacheInfo Source #

Information for caches and TLBs.

Constructors

InstructionTLB (Maybe CacheSize) PageSize Associativity Entries

Configuration of code TLB.

DataTLB (Maybe CacheSize) PageSize Associativity Entries

Configuration of data TLB.

FirstLevelICache CacheSize Associativity LineSize

First-level code cache configuration.

FirstLevelDCache CacheSize Associativity LineSize

First-level code cache configuration.

NoSecondLevelCache

No second level support.

SecondLevelCache CacheSize Associativity LineSize (Maybe BytesPerSector)

Second-level cache configuration.

NoThirdLevelCache

No third level support.

NoSecondOrThirdLevelCache

Internal use only.

ThirdLevelCache CacheSize Associativity LineSize (Maybe BytesPerSector)

Second-level cache configuration.

TraceCache MuOps Associativity

Trace cache (1st-level code cache) configuration.

Prefetching Int

Prefetching information.

Instances

Instances details
Show CacheInfo Source # 
Instance details

Defined in System.Cpuid

newtype LineSize Source #

Line size in a cache.

Constructors

LineSize Int 

Instances

Instances details
Show LineSize Source # 
Instance details

Defined in System.Cpuid

newtype MuOps Source #

MuOps in a processors trace cache.

Constructors

MuOps Int 

Instances

Instances details
Show MuOps Source # 
Instance details

Defined in System.Cpuid

Methods

showsPrec :: Int -> MuOps -> ShowS #

show :: MuOps -> String #

showList :: [MuOps] -> ShowS #

newtype BytesPerSector Source #

Bytes per sector in a cache.

Constructors

BytesPerSector Int 

Instances

Instances details
Show BytesPerSector Source # 
Instance details

Defined in System.Cpuid

data ProcessorInfo Source #

Processor information.

Constructors

ProcessorInfo 

Fields

Features

testFlag :: Enum a => a -> FlagSet a -> Bool Source #

data Feature1C Source #

features as found in page 1, register C

data Feature1D Source #

features as found in page 1, register D