{-# LINE 1 "src/System/LibCPUID.hsc" #-}
module System.LibCPUID
(
cpuid
, isCPUIDPresent
, getTotalLogicalCores
, CPUID(..)
) where
import Foreign.C.Types (CInt(..))
import Foreign.Marshal (allocaBytes)
import Foreign.Ptr (Ptr)
import Foreign.Storable (Storable(peek))
import System.LibCPUID.CPUID (CPUID(..))
cpuid :: IO (Either String CPUID)
cpuid = do
allocaBytes (1344) \cpu_raw_data_t_ptr -> do
{-# LINE 52 "src/System/LibCPUID.hsc" #-}
res <- c_cpuid_get_raw_data cpu_raw_data_t_ptr
case toMaybeError res of
Just err -> pure $ Left err
Nothing ->
allocaBytes (432) \cpu_id_t_ptr -> do
{-# LINE 57 "src/System/LibCPUID.hsc" #-}
res' <- c_cpu_identify cpu_raw_data_t_ptr cpu_id_t_ptr
case toMaybeError res' of
Just err -> pure $ Left err
Nothing -> Right <$> peek cpu_id_t_ptr
foreign import ccall "cpuid_get_raw_data"
c_cpuid_get_raw_data :: Ptr cpu_raw_data_t -> IO CInt
foreign import ccall "cpu_identify"
c_cpu_identify :: Ptr cpu_raw_data_r -> Ptr cpu_id_t -> IO CInt
toMaybeError :: CInt -> Maybe String
toMaybeError = \case
0 -> Nothing
{-# LINE 71 "src/System/LibCPUID.hsc" #-}
err -> Just
case err of
-1 -> "CPUID instruction is not supported"
{-# LINE 74 "src/System/LibCPUID.hsc" #-}
-2 -> "RDTSC instruction is not supported"
{-# LINE 75 "src/System/LibCPUID.hsc" #-}
-3 -> "Memory allocation failed"
{-# LINE 76 "src/System/LibCPUID.hsc" #-}
-4 -> "File open operation failed"
{-# LINE 77 "src/System/LibCPUID.hsc" #-}
-5 -> "Bad file format"
{-# LINE 78 "src/System/LibCPUID.hsc" #-}
-6 -> "Not implemented"
{-# LINE 79 "src/System/LibCPUID.hsc" #-}
-7 -> "Unsupported processor"
{-# LINE 80 "src/System/LibCPUID.hsc" #-}
-8 -> "RDMSR instruction is not supported"
{-# LINE 81 "src/System/LibCPUID.hsc" #-}
-9 -> "RDMSR driver error (generic)"
{-# LINE 82 "src/System/LibCPUID.hsc" #-}
-10 -> "No permissions to install RDMSR driver"
{-# LINE 83 "src/System/LibCPUID.hsc" #-}
-11 -> "Cannot extract RDMSR driver (read only media?)"
{-# LINE 84 "src/System/LibCPUID.hsc" #-}
-12 -> "Bad handle"
{-# LINE 85 "src/System/LibCPUID.hsc" #-}
-13 -> "Invalid MSR"
{-# LINE 86 "src/System/LibCPUID.hsc" #-}
-14 -> "Invalid core number"
{-# LINE 87 "src/System/LibCPUID.hsc" #-}
-15 -> "Error on handle read"
{-# LINE 88 "src/System/LibCPUID.hsc" #-}
-16 -> "Invalid given range"
{-# LINE 89 "src/System/LibCPUID.hsc" #-}
_ -> "Unknown error"
getTotalLogicalCores :: IO Int
getTotalLogicalCores = fromIntegral <$> c_cpuid_get_total_cpus
foreign import ccall "cpuid_get_total_cpus"
c_cpuid_get_total_cpus :: IO CInt
isCPUIDPresent :: IO Bool
isCPUIDPresent = (== 1) <$> c_cpuid_present
foreign import ccall "cpuid_present"
c_cpuid_present :: IO CInt