Portability | non-portable (requires IA-32 processor) |
---|---|
Stability | provisional |
Maintainer | martin@grabmueller.de |
Safe Haskell | Safe-Infered |
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 ()
- cpuid :: Word32 -> IO (Word32, Word32, Word32, Word32)
- processorInfo :: IO ProcessorInfo
- vendorString :: IO String
- brandString :: IO String
- cacheInfo :: IO [CacheInfo]
- data Associativity
- data PageSize
- newtype Ways = Ways Int
- newtype Entries = Entries Int
- data CacheSize
- data CacheInfo
- = InstructionTLB (Maybe CacheSize) PageSize Associativity Entries
- | DataTLB (Maybe CacheSize) PageSize Associativity Entries
- | FirstLevelICache CacheSize Associativity LineSize
- | FirstLevelDCache CacheSize Associativity LineSize
- | NoSecondLevelCache
- | SecondLevelCache CacheSize Associativity LineSize (Maybe BytesPerSector)
- | NoThirdLevelCache
- | NoSecondOrThirdLevelCache
- | ThirdLevelCache CacheSize Associativity LineSize (Maybe BytesPerSector)
- | TraceCache MuOps Associativity
- | Prefetching Int
- newtype LineSize = LineSize Int
- newtype MuOps = MuOps Int
- newtype BytesPerSector = BytesPerSector Int
- data ProcessorInfo = ProcessorInfo {}
- features :: IO (FlagSet Feature1C, FlagSet Feature1D)
- type FlagSet = T Word32
- testFlag :: Enum a => a -> FlagSet a -> Bool
- data Feature1C
- sse3 :: Feature1C
- pclmulqdq :: Feature1C
- dtes64 :: Feature1C
- monitor :: Feature1C
- dscpl :: Feature1C
- vmx :: Feature1C
- smx :: Feature1C
- est :: Feature1C
- tm2 :: Feature1C
- ssse3 :: Feature1C
- cnxtid :: Feature1C
- fma :: Feature1C
- cmpxchg16b :: Feature1C
- xtpr :: Feature1C
- pdcm :: Feature1C
- dca :: Feature1C
- sse4_1 :: Feature1C
- sse4_2 :: Feature1C
- x2apic :: Feature1C
- movbe :: Feature1C
- popcnt :: Feature1C
- aes :: Feature1C
- xsave :: Feature1C
- osxsave :: Feature1C
- avx :: Feature1C
- data Feature1D
- fpu :: Feature1D
- vme :: Feature1D
- de :: Feature1D
- pse :: Feature1D
- tsc :: Feature1D
- msr :: Feature1D
- pae :: Feature1D
- mce :: Feature1D
- cx8 :: Feature1D
- apic :: Feature1D
- sep :: Feature1D
- mtrr :: Feature1D
- pge :: Feature1D
- mca :: Feature1D
- cmov :: Feature1D
- pat :: Feature1D
- pse36 :: Feature1D
- psn :: Feature1D
- clfsh :: Feature1D
- ds :: Feature1D
- acpi :: Feature1D
- mmx :: Feature1D
- fxsr :: Feature1D
- sse :: Feature1D
- sse2 :: Feature1D
- ss :: Feature1D
- htt :: Feature1D
- tm :: Feature1D
- pbe :: Feature1D
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 ProcessorInfoSource
Retrieve basic processor information from the processor using the
cpuid
instruction.
vendorString :: IO StringSource
Execute the cpuid
instruction and return the vendor
string reported by that instruction.
brandString :: IO StringSource
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
.
Page size. Some entries can have alternative page sizes, therefore the complicated type.
Cache size. Some entries can have alternative cache sizes, therefore the complicated type.
Information for caches and TLBs.
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. |
Features
features as found in page 1, register C
features as found in page 1, register D