cpuinfo-0.1.0.2: Haskell Library for Checking CPU Information
CopyrightTravis Whitaker 2016
LicenseMIT
Maintainerpi.boy.travis@gmail.com
StabilityProvisional
PortabilityLinux >=2.6
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.CPU

Description

This module provides information about the processors available on a system. Modern hardware provides not only multiple physical processors and physical cores, but logical cores which may not have dedicated execution resources. Intel's Hyper-Threading is an example of such a technology, capable of providing two logical cores for every physical core present on a supported physical processor.

These additional logical cores increase the performance of some, but not all workloads. Indeed, some parallel workloads may suffer a performance decrease if all logical cores presented by the operating system do not have dedicated physical resources. This is because technologies providing supernumerary logical cores typically work by scheduling multiple threads in a shared pool of execution resources, e.g. ALUs and FPUs. If threads sharing a pool of execution resources are doing the same sort of work there will be scheduling contention for a single type of execution resource on the physical core.

It is common for threaded Haskell programs to be run with +RTS -N, causing the RTS to simply multiplex Haskell threads or sparks over the number of logical cores available. However, if each logical core does not have dedicated physical resources and the thread/spark workloads are similar, then this might be slower than multiplexing over fewer cores.

This package allows a program to use information about the physical and logical features of the available processors as a heuristic for selecting the number of worker OS threads to use (e.g. via setNumCapabilities). Some workloads may benefit from, for example, using half the number of logical cores available if there are in fact two logical cores for each physical core. This is typically true of numerical workloads, but as always benchmarking should be employed to evaluate the impact of different heuristics.

In its current state this module can only collect information from Linux systems with a kernel from the 2.6 branch or later by reading /proc/cpuinfo. If this module is unable to provide information on your system please file a bug including your /proc/cpuinfo. Help providing Windows support would be greatly appreciated!

Synopsis

Documentation

data CPU Source #

Representation of a logical processor and its features.

Constructors

CPU 

Fields

Instances

Instances details
Eq CPU Source # 
Instance details

Defined in System.CPU

Methods

(==) :: CPU -> CPU -> Bool #

(/=) :: CPU -> CPU -> Bool #

Data CPU Source # 
Instance details

Defined in System.CPU

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CPU -> c CPU #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CPU #

toConstr :: CPU -> Constr #

dataTypeOf :: CPU -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CPU) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CPU) #

gmapT :: (forall b. Data b => b -> b) -> CPU -> CPU #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CPU -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CPU -> r #

gmapQ :: (forall d. Data d => d -> u) -> CPU -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CPU -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CPU -> m CPU #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CPU -> m CPU #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CPU -> m CPU #

Ord CPU Source # 
Instance details

Defined in System.CPU

Methods

compare :: CPU -> CPU -> Ordering #

(<) :: CPU -> CPU -> Bool #

(<=) :: CPU -> CPU -> Bool #

(>) :: CPU -> CPU -> Bool #

(>=) :: CPU -> CPU -> Bool #

max :: CPU -> CPU -> CPU #

min :: CPU -> CPU -> CPU #

Read CPU Source # 
Instance details

Defined in System.CPU

Show CPU Source # 
Instance details

Defined in System.CPU

Methods

showsPrec :: Int -> CPU -> ShowS #

show :: CPU -> String #

showList :: [CPU] -> ShowS #

Generic CPU Source # 
Instance details

Defined in System.CPU

Associated Types

type Rep CPU :: Type -> Type #

Methods

from :: CPU -> Rep CPU x #

to :: Rep CPU x -> CPU #

NFData CPU Source # 
Instance details

Defined in System.CPU

Methods

rnf :: CPU -> () #

type Rep CPU Source # 
Instance details

Defined in System.CPU

type Rep CPU = D1 ('MetaData "CPU" "System.CPU" "cpuinfo-0.1.0.2-2ZFjMHzBfckLt1Q3i7V61h" 'False) (C1 ('MetaCons "CPU" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "processorID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "vendor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ByteString))) :*: (S1 ('MetaSel ('Just "model") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Word32)) :*: S1 ('MetaSel ('Just "modelName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ByteString)))) :*: ((S1 ('MetaSel ('Just "revision") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Word32)) :*: S1 ('MetaSel ('Just "microcode") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Word32))) :*: (S1 ('MetaSel ('Just "freq") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double) :*: (S1 ('MetaSel ('Just "cache") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Word32)) :*: S1 ('MetaSel ('Just "physicalID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32))))) :*: (((S1 ('MetaSel ('Just "siblings") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "coreID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "apicID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Word32)) :*: (S1 ('MetaSel ('Just "fpu") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "fpuExcept") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool))))) :*: ((S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe [ByteString])) :*: S1 ('MetaSel ('Just "bogoMIPS") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double)) :*: (S1 ('MetaSel ('Just "cacheAlignment") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Word32)) :*: (S1 ('MetaSel ('Just "physicalAddress") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Word32)) :*: S1 ('MetaSel ('Just "virtualAddress") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Word32))))))))

Retrieving CPU Information

getCPUs :: IO [CPU] Source #

Read /proc/cpuinfo and try to parse the output. If this function throws an error on your system, please file a bug report with your /proc/cpuinfo contents and CPU specifications.

tryGetCPUs :: IO (Maybe [CPU]) Source #

Read /proc/cpuinfo and try to parse the output. If this function returns Nothing on your system, please file a bug report with your /proc/cpuinfo contents and CPU specifications.

Physical Features

physicalProcessors :: [CPU] -> Int Source #

Counts the number of physical processors in the system. A physical processor corresponds to a single CPU unit in a single socket, i.e. unless you have a multi-socket motherboard, this number will be one.

physicalCores :: [CPU] -> Int Source #

Counts the number of physical cores in the system. A physical core is an independent processing unit that reads and executes instructions on its own, but potentially shares its die (and other resources) with other cores.

logicalCores :: [CPU] -> Int Source #

Counts the number of logical cores in the system. A logical core is a virtual processing unit exposed to the operating system, that may or may not directly correspond with an independent physical processing unit, e.g. a hyperthread appears as an independent processing unit to the operating system, but has no physically dedicated execution resources.

hyperthreadingFactor :: [CPU] -> Rational Source #

The hyperthreading factor is the number of logical cores divided by the number of physical cores. This quantity indicates the degree to which physical execution resources are shared among logical processors, and may be used to tune parallel applications.

hyperthreadingInUse :: [CPU] -> Bool Source #

If hyperthreading is in use, the hyperthreadingFactor will be greater than 1.