spiros-0.4.2: Spiros Boosalis's Custom Prelude

Safe HaskellNone
LanguageHaskell2010

Prelude.Spiros.System

Description

Information about the current system:

/TODO: respect cross-compilation, i.e. the targetruntime system.//

And information about the current compiler:

(This module is similar to the Foundation.System module in the foundation package.)

Synopsis

Documentation

data IsHyperthreading Source #

Whether the system is currently using any Hyperthreading.

Instances
Bounded IsHyperthreading Source # 
Instance details

Defined in Prelude.Spiros.System

Enum IsHyperthreading Source # 
Instance details

Defined in Prelude.Spiros.System

Eq IsHyperthreading Source # 
Instance details

Defined in Prelude.Spiros.System

Ord IsHyperthreading Source # 
Instance details

Defined in Prelude.Spiros.System

Read IsHyperthreading Source # 
Instance details

Defined in Prelude.Spiros.System

Show IsHyperthreading Source # 
Instance details

Defined in Prelude.Spiros.System

Ix IsHyperthreading Source # 
Instance details

Defined in Prelude.Spiros.System

Generic IsHyperthreading Source # 
Instance details

Defined in Prelude.Spiros.System

Associated Types

type Rep IsHyperthreading :: Type -> Type #

Lift IsHyperthreading Source # 
Instance details

Defined in Prelude.Spiros.System

Methods

lift :: IsHyperthreading -> Q Exp #

Default IsHyperthreading Source #
HyperthreadingIsDisabled
Instance details

Defined in Prelude.Spiros.System

NFData IsHyperthreading Source # 
Instance details

Defined in Prelude.Spiros.System

Methods

rnf :: IsHyperthreading -> () #

Hashable IsHyperthreading Source # 
Instance details

Defined in Prelude.Spiros.System

type Rep IsHyperthreading Source # 
Instance details

Defined in Prelude.Spiros.System

type Rep IsHyperthreading = D1 (MetaData "IsHyperthreading" "Prelude.Spiros.System" "spiros-0.4.2-AXTfsSIxN6qJkldZU4Dlmr" False) (C1 (MetaCons "HyperthreadingIsDisabled" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HyperthreadingIsEnabled" PrefixI False) (U1 :: Type -> Type))

data CPUsSummary Source #

Instances
Eq CPUsSummary Source # 
Instance details

Defined in Prelude.Spiros.System

Ord CPUsSummary Source # 
Instance details

Defined in Prelude.Spiros.System

Read CPUsSummary Source # 
Instance details

Defined in Prelude.Spiros.System

Show CPUsSummary Source # 
Instance details

Defined in Prelude.Spiros.System

Generic CPUsSummary Source # 
Instance details

Defined in Prelude.Spiros.System

Associated Types

type Rep CPUsSummary :: Type -> Type #

Lift CPUsSummary Source # 
Instance details

Defined in Prelude.Spiros.System

Methods

lift :: CPUsSummary -> Q Exp #

Default CPUsSummary Source # 
Instance details

Defined in Prelude.Spiros.System

Methods

def :: CPUsSummary #

NFData CPUsSummary Source # 
Instance details

Defined in Prelude.Spiros.System

Methods

rnf :: CPUsSummary -> () #

Hashable CPUsSummary Source # 
Instance details

Defined in Prelude.Spiros.System

type Rep CPUsSummary Source # 
Instance details

Defined in Prelude.Spiros.System

type Rep CPUsSummary = D1 (MetaData "CPUsSummary" "Prelude.Spiros.System" "spiros-0.4.2-AXTfsSIxN6qJkldZU4Dlmr" False) (C1 (MetaCons "CPUsSummary" PrefixI True) (S1 (MetaSel (Just "isHyperthreading") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IsHyperthreading) :*: (S1 (MetaSel (Just "physicalCores") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural) :*: S1 (MetaSel (Just "logicalCores") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural))))

data KnownHaskellCompiler Source #

Enumeration of the known GHC-based compilers.

Constructors

GHC

C FFI.

GHCJS

Javascript FFI.

GHCETA

Java FFI.

Instances
Bounded KnownHaskellCompiler Source # 
Instance details

Defined in Prelude.Spiros.System

Enum KnownHaskellCompiler Source # 
Instance details

Defined in Prelude.Spiros.System

Eq KnownHaskellCompiler Source # 
Instance details

Defined in Prelude.Spiros.System

Ord KnownHaskellCompiler Source # 
Instance details

Defined in Prelude.Spiros.System

Read KnownHaskellCompiler Source # 
Instance details

Defined in Prelude.Spiros.System

Show KnownHaskellCompiler Source # 
Instance details

Defined in Prelude.Spiros.System

Ix KnownHaskellCompiler Source # 
Instance details

Defined in Prelude.Spiros.System

Generic KnownHaskellCompiler Source # 
Instance details

Defined in Prelude.Spiros.System

Associated Types

type Rep KnownHaskellCompiler :: Type -> Type #

Lift KnownHaskellCompiler Source # 
Instance details

Defined in Prelude.Spiros.System

Default KnownHaskellCompiler Source #
GHC
Instance details

Defined in Prelude.Spiros.System

NFData KnownHaskellCompiler Source # 
Instance details

Defined in Prelude.Spiros.System

Methods

rnf :: KnownHaskellCompiler -> () #

Hashable KnownHaskellCompiler Source # 
Instance details

Defined in Prelude.Spiros.System

type Rep KnownHaskellCompiler Source # 
Instance details

Defined in Prelude.Spiros.System

type Rep KnownHaskellCompiler = D1 (MetaData "KnownHaskellCompiler" "Prelude.Spiros.System" "spiros-0.4.2-AXTfsSIxN6qJkldZU4Dlmr" False) (C1 (MetaCons "GHC" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "GHCJS" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GHCETA" PrefixI False) (U1 :: Type -> Type)))

data ProcessorBits Source #

Whether the processor is 64-bit or 32-bit.

https://en.wikipedia.org/wiki/64-bit_computing: "In computer architecture, 64-bit computing is the use of processors that have datapath widths, integer size, and memory address widths of 64 bits (eight octets)."

Instances
Bounded ProcessorBits Source # 
Instance details

Defined in Prelude.Spiros.System

Enum ProcessorBits Source # 
Instance details

Defined in Prelude.Spiros.System

Eq ProcessorBits Source # 
Instance details

Defined in Prelude.Spiros.System

Ord ProcessorBits Source # 
Instance details

Defined in Prelude.Spiros.System

Read ProcessorBits Source # 
Instance details

Defined in Prelude.Spiros.System

Show ProcessorBits Source # 
Instance details

Defined in Prelude.Spiros.System

Ix ProcessorBits Source # 
Instance details

Defined in Prelude.Spiros.System

Generic ProcessorBits Source # 
Instance details

Defined in Prelude.Spiros.System

Associated Types

type Rep ProcessorBits :: Type -> Type #

Lift ProcessorBits Source # 
Instance details

Defined in Prelude.Spiros.System

Methods

lift :: ProcessorBits -> Q Exp #

Default ProcessorBits Source #
Processor64Bit
Instance details

Defined in Prelude.Spiros.System

Methods

def :: ProcessorBits #

NFData ProcessorBits Source # 
Instance details

Defined in Prelude.Spiros.System

Methods

rnf :: ProcessorBits -> () #

Hashable ProcessorBits Source # 
Instance details

Defined in Prelude.Spiros.System

type Rep ProcessorBits Source # 
Instance details

Defined in Prelude.Spiros.System

type Rep ProcessorBits = D1 (MetaData "ProcessorBits" "Prelude.Spiros.System" "spiros-0.4.2-AXTfsSIxN6qJkldZU4Dlmr" False) (C1 (MetaCons "Processor32Bit" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Processor64Bit" PrefixI False) (U1 :: Type -> Type))

data Endianness Source #

Whether the processor is little-endian or big-endian.

https://en.wikipedia.org/wiki/Endianness: "Endianness is the sequential order in which bytes are arranged into larger numerical values when stored in memory or when transmitted over digital links."

Constructors

LittleEndian 
BigEndian 
Instances
Bounded Endianness Source # 
Instance details

Defined in Prelude.Spiros.System

Enum Endianness Source # 
Instance details

Defined in Prelude.Spiros.System

Eq Endianness Source # 
Instance details

Defined in Prelude.Spiros.System

Ord Endianness Source # 
Instance details

Defined in Prelude.Spiros.System

Read Endianness Source # 
Instance details

Defined in Prelude.Spiros.System

Show Endianness Source # 
Instance details

Defined in Prelude.Spiros.System

Ix Endianness Source # 
Instance details

Defined in Prelude.Spiros.System

Generic Endianness Source # 
Instance details

Defined in Prelude.Spiros.System

Associated Types

type Rep Endianness :: Type -> Type #

Lift Endianness Source # 
Instance details

Defined in Prelude.Spiros.System

Methods

lift :: Endianness -> Q Exp #

Default Endianness Source #
LittleEndian
Instance details

Defined in Prelude.Spiros.System

Methods

def :: Endianness #

NFData Endianness Source # 
Instance details

Defined in Prelude.Spiros.System

Methods

rnf :: Endianness -> () #

Hashable Endianness Source # 
Instance details

Defined in Prelude.Spiros.System

type Rep Endianness Source # 
Instance details

Defined in Prelude.Spiros.System

type Rep Endianness = D1 (MetaData "Endianness" "Prelude.Spiros.System" "spiros-0.4.2-AXTfsSIxN6qJkldZU4Dlmr" False) (C1 (MetaCons "LittleEndian" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BigEndian" PrefixI False) (U1 :: Type -> Type))

data KnownManufacturer Source #

Instances
Bounded KnownManufacturer Source # 
Instance details

Defined in Prelude.Spiros.System

Enum KnownManufacturer Source # 
Instance details

Defined in Prelude.Spiros.System

Eq KnownManufacturer Source # 
Instance details

Defined in Prelude.Spiros.System

Ord KnownManufacturer Source # 
Instance details

Defined in Prelude.Spiros.System

Read KnownManufacturer Source # 
Instance details

Defined in Prelude.Spiros.System

Show KnownManufacturer Source # 
Instance details

Defined in Prelude.Spiros.System

Ix KnownManufacturer Source # 
Instance details

Defined in Prelude.Spiros.System

Generic KnownManufacturer Source # 
Instance details

Defined in Prelude.Spiros.System

Associated Types

type Rep KnownManufacturer :: Type -> Type #

Lift KnownManufacturer Source # 
Instance details

Defined in Prelude.Spiros.System

Default KnownManufacturer Source #
Intel_Manufacturer
Instance details

Defined in Prelude.Spiros.System

NFData KnownManufacturer Source # 
Instance details

Defined in Prelude.Spiros.System

Methods

rnf :: KnownManufacturer -> () #

Hashable KnownManufacturer Source # 
Instance details

Defined in Prelude.Spiros.System

type Rep KnownManufacturer Source # 
Instance details

Defined in Prelude.Spiros.System

type Rep KnownManufacturer = D1 (MetaData "KnownManufacturer" "Prelude.Spiros.System" "spiros-0.4.2-AXTfsSIxN6qJkldZU4Dlmr" False) ((C1 (MetaCons "Intel_Manufacturer" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PowerPC_Manufacturer" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Sparc_Manufacturer" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ARM_Manufacturer" PrefixI False) (U1 :: Type -> Type)))

data KnownArchitecture Source #

Enumeration of the known GHC supported architecture.

Instances
Eq KnownArchitecture Source # 
Instance details

Defined in Prelude.Spiros.System

Ord KnownArchitecture Source # 
Instance details

Defined in Prelude.Spiros.System

Read KnownArchitecture Source # 
Instance details

Defined in Prelude.Spiros.System

Show KnownArchitecture Source # 
Instance details

Defined in Prelude.Spiros.System

Generic KnownArchitecture Source # 
Instance details

Defined in Prelude.Spiros.System

Associated Types

type Rep KnownArchitecture :: Type -> Type #

Lift KnownArchitecture Source # 
Instance details

Defined in Prelude.Spiros.System

Default KnownArchitecture Source #

IntelManufacturer and Processor64Bit.

Instance details

Defined in Prelude.Spiros.System

NFData KnownArchitecture Source # 
Instance details

Defined in Prelude.Spiros.System

Methods

rnf :: KnownArchitecture -> () #

Hashable KnownArchitecture Source # 
Instance details

Defined in Prelude.Spiros.System

type Rep KnownArchitecture Source # 
Instance details

Defined in Prelude.Spiros.System

type Rep KnownArchitecture = D1 (MetaData "KnownArchitecture" "Prelude.Spiros.System" "spiros-0.4.2-AXTfsSIxN6qJkldZU4Dlmr" False) (C1 (MetaCons "KnownArchitecture" PrefixI True) (S1 (MetaSel (Just "architectureManufacturer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 KnownManufacturer) :*: S1 (MetaSel (Just "architectureProcessorBits") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProcessorBits)))

data KnownOperatingSystem Source #

Enumeration of the known GHC supported operating systems.

Constructors

Linux 
Windows 
OSX 
Android 
BSD 
Instances
Bounded KnownOperatingSystem Source # 
Instance details

Defined in Prelude.Spiros.System

Enum KnownOperatingSystem Source # 
Instance details

Defined in Prelude.Spiros.System

Eq KnownOperatingSystem Source # 
Instance details

Defined in Prelude.Spiros.System

Ord KnownOperatingSystem Source # 
Instance details

Defined in Prelude.Spiros.System

Read KnownOperatingSystem Source # 
Instance details

Defined in Prelude.Spiros.System

Show KnownOperatingSystem Source # 
Instance details

Defined in Prelude.Spiros.System

Ix KnownOperatingSystem Source # 
Instance details

Defined in Prelude.Spiros.System

Generic KnownOperatingSystem Source # 
Instance details

Defined in Prelude.Spiros.System

Associated Types

type Rep KnownOperatingSystem :: Type -> Type #

Lift KnownOperatingSystem Source # 
Instance details

Defined in Prelude.Spiros.System

NFData KnownOperatingSystem Source # 
Instance details

Defined in Prelude.Spiros.System

Methods

rnf :: KnownOperatingSystem -> () #

Hashable KnownOperatingSystem Source # 
Instance details

Defined in Prelude.Spiros.System

type Rep KnownOperatingSystem Source # 
Instance details

Defined in Prelude.Spiros.System

type Rep KnownOperatingSystem = D1 (MetaData "KnownOperatingSystem" "Prelude.Spiros.System" "spiros-0.4.2-AXTfsSIxN6qJkldZU4Dlmr" False) ((C1 (MetaCons "Linux" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Windows" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "OSX" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Android" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BSD" PrefixI False) (U1 :: Type -> Type))))

currentOperatingSystem :: Either String KnownOperatingSystem Source #

get the operating system on which the program is running.

Either return the known OS or a strict String of the OS name.

This function uses the base's os function.

currentArchitecture :: Either String KnownArchitecture Source #

Get the machine architecture on which the program is running.

Either return the known architecture or a Strict String of the architecture name.

This function uses the base's arch function.

currentManufacturer :: Maybe KnownManufacturer Source #

Get the manufacturer (if known) of the architecture on which the program is running.

Uses base's arch function.

currentEndianness :: Maybe Endianness Source #

The endianness of the current machine's architecture.

Nothing represents:

  • unknown endianness.

These endiannesses aren't represented:

  • Bi-endianness. (the endianness, if swapped before the haskell program starts up, may differ).

For example, PowerPC processors start in big-endian, but PowerPC itself is bi-endian.

currentProcessorBits :: Maybe ProcessorBits Source #

Get the number of bits (if known) of the processor on which the program is running.

Uses base's arch function.

currentCompiler :: Either String KnownHaskellCompiler Source #

get the compiler name

This function uses the base's compilerName function.

currentNumberOfCPUs :: IO Natural Source #

returns the number of CPUs the machine has