Copyright | Copyright (C) 2006-2018 Bjorn Buckwalter |
---|---|
License | BSD3 |
Maintainer | bjorn@buckwalter.se |
Stability | Stable |
Portability | GHC only |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Summary
This module supplies a convenient set of imports for working with the dimensional package, including aliases for common Quantity
s and Dimension
s,
and a comprehensive set of SI units and units accepted for use with the SI.
It re-exports the Prelude, hiding arithmetic functions whose names collide with the dimensionally-typed versions supplied by this package.
Synopsis
- type family (a :: Dimension) * (b :: Dimension) where ...
- type family (d :: Dimension) ^ (x :: TypeInt) where ...
- type family (a :: Dimension) / (d :: Dimension) where ...
- type Recip (d :: Dimension) = DOne / d
- class KnownVariant (v :: Variant) where
- data Dimensional v :: Dimension -> Type -> Type
- type Unit (m :: Metricality) = Dimensional ('DUnit m)
- type Quantity = SQuantity One
- data Metricality
- data Dimension = Dim TypeInt TypeInt TypeInt TypeInt TypeInt TypeInt TypeInt
- type family NRoot (d :: Dimension) (x :: TypeInt) where ...
- type Sqrt d = NRoot d 'Pos2
- type Cbrt d = NRoot d 'Pos3
- data Dimension' = Dim' !Int !Int !Int !Int !Int !Int !Int
- class HasDynamicDimension a => HasDimension a where
- dimension :: a -> Dimension'
- type KnownDimension (d :: Dimension) = HasDimension (Proxy d)
- type DOne = 'Dim 'Zero 'Zero 'Zero 'Zero 'Zero 'Zero 'Zero
- type DLength = 'Dim 'Pos1 'Zero 'Zero 'Zero 'Zero 'Zero 'Zero
- type DMass = 'Dim 'Zero 'Pos1 'Zero 'Zero 'Zero 'Zero 'Zero
- type DTime = 'Dim 'Zero 'Zero 'Pos1 'Zero 'Zero 'Zero 'Zero
- type DElectricCurrent = 'Dim 'Zero 'Zero 'Zero 'Pos1 'Zero 'Zero 'Zero
- type DThermodynamicTemperature = 'Dim 'Zero 'Zero 'Zero 'Zero 'Pos1 'Zero 'Zero
- type DAmountOfSubstance = 'Dim 'Zero 'Zero 'Zero 'Zero 'Zero 'Pos1 'Zero
- type DLuminousIntensity = 'Dim 'Zero 'Zero 'Zero 'Zero 'Zero 'Zero 'Pos1
- type Dimensionless = Quantity DOne
- type Length = Quantity DLength
- type Mass = Quantity DMass
- type Time = Quantity DTime
- type ElectricCurrent = Quantity DElectricCurrent
- type ThermodynamicTemperature = Quantity DThermodynamicTemperature
- type AmountOfSubstance = Quantity DAmountOfSubstance
- type LuminousIntensity = Quantity DLuminousIntensity
- (-) :: Num a => Quantity d a -> Quantity d a -> Quantity d a
- negate :: Num a => Quantity d a -> Quantity d a
- (+) :: Num a => Quantity d a -> Quantity d a -> Quantity d a
- (*) :: (KnownVariant v1, KnownVariant v2, KnownVariant (v1 * v2), Num a) => Dimensional v1 d1 a -> Dimensional v2 d2 a -> Dimensional (v1 * v2) (d1 * d2) a
- (^) :: (Fractional a, KnownTypeInt i, KnownVariant v, KnownVariant (Weaken v)) => Dimensional v d1 a -> Proxy i -> Dimensional (Weaken v) (d1 ^ i) a
- abs :: Num a => Quantity d a -> Quantity d a
- signum :: Num a => Quantity d a -> Dimensionless a
- sum :: (Num a, Foldable f) => f (Quantity d a) -> Quantity d a
- product :: (Num a, Foldable f) => f (Dimensionless a) -> Dimensionless a
- (/) :: (KnownVariant v1, KnownVariant v2, KnownVariant (v1 / v2), Fractional a) => Dimensional v1 d1 a -> Dimensional v2 d2 a -> Dimensional (v1 / v2) (d1 / d2) a
- recip :: Fractional a => Quantity d a -> Quantity (Recip d) a
- atan2 :: RealFloat a => Quantity d a -> Quantity d a -> Dimensionless a
- pi :: Floating a => Dimensionless a
- exp :: Floating a => Dimensionless a -> Dimensionless a
- log :: Floating a => Dimensionless a -> Dimensionless a
- sqrt :: Floating a => Quantity d a -> Quantity (Sqrt d) a
- (**) :: Floating a => Dimensionless a -> Dimensionless a -> Dimensionless a
- logBase :: Floating a => Dimensionless a -> Dimensionless a -> Dimensionless a
- sin :: Floating a => Dimensionless a -> Dimensionless a
- cos :: Floating a => Dimensionless a -> Dimensionless a
- tan :: Floating a => Dimensionless a -> Dimensionless a
- asin :: Floating a => Dimensionless a -> Dimensionless a
- acos :: Floating a => Dimensionless a -> Dimensionless a
- atan :: Floating a => Dimensionless a -> Dimensionless a
- sinh :: Floating a => Dimensionless a -> Dimensionless a
- cosh :: Floating a => Dimensionless a -> Dimensionless a
- tanh :: Floating a => Dimensionless a -> Dimensionless a
- asinh :: Floating a => Dimensionless a -> Dimensionless a
- acosh :: Floating a => Dimensionless a -> Dimensionless a
- atanh :: Floating a => Dimensionless a -> Dimensionless a
- log1p :: Floating a => Dimensionless a -> Dimensionless a
- expm1 :: Floating a => Dimensionless a -> Dimensionless a
- log1pexp :: Floating a => Dimensionless a -> Dimensionless a
- log1mexp :: Floating a => Dimensionless a -> Dimensionless a
- (*~) :: Num a => a -> Unit m d a -> Quantity d a
- (/~) :: Fractional a => Quantity d a -> Unit m d a -> a
- (^/) :: (KnownTypeInt n, Floating a) => Quantity d a -> Proxy n -> Quantity (NRoot d n) a
- nroot :: (KnownTypeInt n, Floating a) => Proxy n -> Quantity d a -> Quantity (NRoot d n) a
- cbrt :: Floating a => Quantity d a -> Quantity (Cbrt d) a
- (*~~) :: (Functor f, Num a) => f a -> Unit m d a -> f (Quantity d a)
- (/~~) :: forall f m d a. (Functor f, Fractional a) => f (Quantity d a) -> Unit m d a -> f a
- mean :: (Fractional a, Foldable f) => f (Quantity d a) -> Quantity d a
- dimensionlessLength :: (Num a, Foldable f) => f b -> Dimensionless a
- nFromTo :: (Fractional a, Integral b) => Quantity d a -> Quantity d a -> b -> [Quantity d a]
- _0 :: Num a => Quantity d a
- _1 :: Num a => Dimensionless a
- _2 :: Num a => Dimensionless a
- _3 :: Num a => Dimensionless a
- _4 :: Num a => Dimensionless a
- _5 :: Num a => Dimensionless a
- _6 :: Num a => Dimensionless a
- _7 :: Num a => Dimensionless a
- _8 :: Num a => Dimensionless a
- _9 :: Num a => Dimensionless a
- tau :: Floating a => Dimensionless a
- siUnit :: forall d a. (KnownDimension d, Num a) => Unit 'NonMetric d a
- one :: Num a => Unit 'NonMetric DOne a
- mkUnitR :: Floating a => UnitName m -> ExactPi -> Unit m1 d a -> Unit m d a
- mkUnitQ :: Fractional a => UnitName m -> Rational -> Unit m1 d a -> Unit m d a
- mkUnitZ :: Num a => UnitName m -> Integer -> Unit m1 d a -> Unit m d a
- name :: Unit m d a -> UnitName m
- exactValue :: Unit m d a -> ExactPi
- weaken :: Unit m d a -> Unit 'NonMetric d a
- strengthen :: Unit m d a -> Maybe (Unit 'Metric d a)
- exactify :: Unit m d a -> Unit m d ExactPi
- showIn :: (Show a, Fractional a) => Unit m d a -> Quantity d a -> String
- changeRep :: (KnownVariant v, Real a, Fractional b) => Dimensional v d a -> Dimensional v d b
- changeRepApproximate :: (KnownVariant v, Floating b) => Dimensional v d ExactPi -> Dimensional v d b
- asLens :: Fractional a => Unit m d a -> forall f. Functor f => (a -> f a) -> Quantity d a -> f (Quantity d a)
- module Numeric.Units.Dimensional.Quantities
- module Numeric.Units.Dimensional.SIUnits
- neg5 :: Proxy 'Neg5
- neg4 :: Proxy 'Neg4
- neg3 :: Proxy 'Neg3
- neg2 :: Proxy 'Neg2
- neg1 :: Proxy 'Neg1
- zero :: Proxy 'Zero
- pos1 :: Proxy 'Pos1
- pos2 :: Proxy 'Pos2
- pos3 :: Proxy 'Pos3
- pos4 :: Proxy 'Pos4
- pos5 :: Proxy 'Pos5
- class Category (cat :: k -> k -> Type) where
- maximum :: (Foldable t, Ord a) => t a -> a
- minimum :: (Foldable t, Ord a) => t a -> a
- data Int
- data Float
- data Char
- data IO a
- data Bool
- data Double
- data Word
- data Ordering
- data Maybe a
- class a ~# b => (a :: k) ~ (b :: k)
- data Integer
- data Either a b
- class (Real a, Enum a) => Integral a where
- type Rational = Ratio Integer
- type String = [Char]
- class Read a where
- class Show a where
- type IOError = IOException
- class Bounded a where
- class Enum a where
- succ :: a -> a
- pred :: a -> a
- toEnum :: Int -> a
- fromEnum :: a -> Int
- enumFrom :: a -> [a]
- enumFromThen :: a -> a -> [a]
- enumFromTo :: a -> a -> [a]
- enumFromThenTo :: a -> a -> a -> [a]
- class Eq a where
- class Fractional a => Floating a
- class Num a => Fractional a where
- fromRational :: Rational -> a
- class Applicative m => Monad (m :: Type -> Type) where
- class Functor (f :: Type -> Type) where
- class Num a where
- fromInteger :: Integer -> a
- class Eq a => Ord a where
- class (Num a, Ord a) => Real a where
- toRational :: a -> Rational
- class (RealFrac a, Floating a) => RealFloat a where
- floatRadix :: a -> Integer
- floatDigits :: a -> Int
- floatRange :: a -> (Int, Int)
- decodeFloat :: a -> (Integer, Int)
- encodeFloat :: Integer -> Int -> a
- exponent :: a -> Int
- significand :: a -> a
- scaleFloat :: Int -> a -> a
- isNaN :: a -> Bool
- isInfinite :: a -> Bool
- isDenormalized :: a -> Bool
- isNegativeZero :: a -> Bool
- isIEEE :: a -> Bool
- class (Real a, Fractional a) => RealFrac a where
- class Monad m => MonadFail (m :: Type -> Type) where
- class Functor f => Applicative (f :: Type -> Type) where
- class Foldable (t :: Type -> Type) where
- class (Functor t, Foldable t) => Traversable (t :: Type -> Type) where
- traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
- sequenceA :: Applicative f => t (f a) -> f (t a)
- mapM :: Monad m => (a -> m b) -> t a -> m (t b)
- sequence :: Monad m => t (m a) -> m (t a)
- class Semigroup a where
- (<>) :: a -> a -> a
- class Semigroup a => Monoid a where
- type ShowS = String -> String
- type ReadS a = String -> [(a, String)]
- type FilePath = String
- error :: forall (r :: RuntimeRep) (a :: TYPE r). HasCallStack => [Char] -> a
- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
- even :: Integral a => a -> Bool
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- ($) :: forall (r :: RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b
- fst :: (a, b) -> a
- uncurry :: (a -> b -> c) -> (a, b) -> c
- head :: HasCallStack => [a] -> a
- writeFile :: FilePath -> String -> IO ()
- getLine :: IO String
- putStrLn :: String -> IO ()
- filter :: (a -> Bool) -> [a] -> [a]
- cycle :: HasCallStack => [a] -> [a]
- (++) :: [a] -> [a] -> [a]
- seq :: forall {r :: RuntimeRep} a (b :: TYPE r). a -> b -> b
- concat :: Foldable t => t [a] -> [a]
- zip :: [a] -> [b] -> [(a, b)]
- print :: Show a => a -> IO ()
- otherwise :: Bool
- map :: (a -> b) -> [a] -> [b]
- fromIntegral :: (Integral a, Num b) => a -> b
- realToFrac :: (Real a, Fractional b) => a -> b
- (&&) :: Bool -> Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- not :: Bool -> Bool
- errorWithoutStackTrace :: forall (r :: RuntimeRep) (a :: TYPE r). [Char] -> a
- undefined :: forall (r :: RuntimeRep) (a :: TYPE r). HasCallStack => a
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- const :: a -> b -> a
- flip :: (a -> b -> c) -> b -> a -> c
- ($!) :: forall (r :: RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b
- until :: (a -> Bool) -> (a -> a) -> a -> a
- asTypeOf :: a -> a -> a
- subtract :: Num a => a -> a -> a
- maybe :: b -> (a -> b) -> Maybe a -> b
- tail :: HasCallStack => [a] -> [a]
- last :: HasCallStack => [a] -> a
- init :: HasCallStack => [a] -> [a]
- scanl :: (b -> a -> b) -> b -> [a] -> [b]
- scanl1 :: (a -> a -> a) -> [a] -> [a]
- scanr :: (a -> b -> b) -> b -> [a] -> [b]
- scanr1 :: (a -> a -> a) -> [a] -> [a]
- iterate :: (a -> a) -> a -> [a]
- repeat :: a -> [a]
- replicate :: Int -> a -> [a]
- takeWhile :: (a -> Bool) -> [a] -> [a]
- dropWhile :: (a -> Bool) -> [a] -> [a]
- take :: Int -> [a] -> [a]
- drop :: Int -> [a] -> [a]
- splitAt :: Int -> [a] -> ([a], [a])
- span :: (a -> Bool) -> [a] -> ([a], [a])
- break :: (a -> Bool) -> [a] -> ([a], [a])
- reverse :: [a] -> [a]
- and :: Foldable t => t Bool -> Bool
- or :: Foldable t => t Bool -> Bool
- any :: Foldable t => (a -> Bool) -> t a -> Bool
- all :: Foldable t => (a -> Bool) -> t a -> Bool
- notElem :: (Foldable t, Eq a) => a -> t a -> Bool
- lookup :: Eq a => a -> [(a, b)] -> Maybe b
- concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
- (!!) :: HasCallStack => [a] -> Int -> a
- zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
- zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
- unzip :: [(a, b)] -> ([a], [b])
- unzip3 :: [(a, b, c)] -> ([a], [b], [c])
- shows :: Show a => a -> ShowS
- showChar :: Char -> ShowS
- showString :: String -> ShowS
- showParen :: Bool -> ShowS -> ShowS
- odd :: Integral a => a -> Bool
- (^^) :: (Fractional a, Integral b) => a -> b -> a
- gcd :: Integral a => a -> a -> a
- lcm :: Integral a => a -> a -> a
- snd :: (a, b) -> b
- curry :: ((a, b) -> c) -> a -> b -> c
- lex :: ReadS String
- readParen :: Bool -> ReadS a -> ReadS a
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- reads :: Read a => ReadS a
- read :: Read a => String -> a
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- lines :: String -> [String]
- unlines :: [String] -> String
- words :: String -> [String]
- unwords :: [String] -> String
- userError :: String -> IOError
- ioError :: IOError -> IO a
- putChar :: Char -> IO ()
- putStr :: String -> IO ()
- getChar :: IO Char
- getContents :: IO String
- interact :: (String -> String) -> IO ()
- readFile :: FilePath -> IO String
- appendFile :: FilePath -> String -> IO ()
- readLn :: Read a => IO a
- readIO :: Read a => String -> IO a
Documentation
type family (a :: Dimension) * (b :: Dimension) where ... infixl 7 Source #
Multiplication of dimensions corresponds to addition of the base dimensions' exponents.
type family (d :: Dimension) ^ (x :: TypeInt) where ... infixr 8 Source #
Powers of dimensions correspond to multiplication of the base dimensions' exponents by the exponent.
We limit ourselves to integer powers of Dimensionals as fractional powers make little physical sense.
type family (a :: Dimension) / (d :: Dimension) where ... infixl 7 Source #
Division of dimensions corresponds to subtraction of the base dimensions' exponents.
type Recip (d :: Dimension) = DOne / d Source #
The reciprocal of a dimension is defined as the result of dividing DOne
by it,
or of negating each of the base dimensions' exponents.
class KnownVariant (v :: Variant) Source #
A KnownVariant is one whose term-level Dimensional
values we can represent with an associated data family instance
and manipulate with certain functions, not all of which are exported from the package.
Each validly constructed type of kind Variant
has a KnownVariant
instance.
extractValue, extractName, injectValue, dmap
Instances
type Unit (m :: Metricality) = Dimensional ('DUnit m) Source #
A unit of measurement.
data Metricality Source #
Encodes whether a unit is a metric unit, that is, whether it can be combined with a metric prefix to form a related unit.
Instances
Represents a physical dimension in the basis of the 7 SI base dimensions, where the respective dimensions are represented by type variables using the following convention:
- l: Length
- m: Mass
- t: Time
- i: Electric current
- th: Thermodynamic temperature
- n: Amount of substance
- j: Luminous intensity
For the equivalent term-level representation, see Dimension'
Instances
(KnownTypeInt l, KnownTypeInt m, KnownTypeInt t, KnownTypeInt i, KnownTypeInt th, KnownTypeInt n, KnownTypeInt j) => HasDimension (Proxy ('Dim l m t i th n j)) Source # | |
(KnownTypeInt l, KnownTypeInt m, KnownTypeInt t, KnownTypeInt i, KnownTypeInt th, KnownTypeInt n, KnownTypeInt j) => HasDynamicDimension (Proxy ('Dim l m t i th n j)) Source # | |
Defined in Numeric.Units.Dimensional.Dimensions.TypeLevel dynamicDimension :: Proxy ('Dim l m t i th n j) -> DynamicDimension Source # |
type family NRoot (d :: Dimension) (x :: TypeInt) where ... Source #
Roots of dimensions correspond to division of the base dimensions' exponents by the order of the root.
data Dimension' Source #
A physical dimension, encoded as 7 integers, representing a factorization of the dimension into the
7 SI base dimensions. By convention they are stored in the same order as
in the Dimension
data kind.
Instances
class HasDynamicDimension a => HasDimension a where Source #
Dimensional values inhabit this class, which allows access to a term-level representation of their dimension.
dimension :: a -> Dimension' Source #
Obtains a term-level representation of a value's dimension.
Instances
HasDimension Dimension' Source # | |
Defined in Numeric.Units.Dimensional.Dimensions.TermLevel dimension :: Dimension' -> Dimension' Source # | |
HasDimension AnyUnit Source # | |
Defined in Numeric.Units.Dimensional.Dynamic dimension :: AnyUnit -> Dimension' Source # | |
HasDimension (AnyQuantity a) Source # | |
Defined in Numeric.Units.Dimensional.Dynamic dimension :: AnyQuantity a -> Dimension' Source # | |
(KnownTypeInt l, KnownTypeInt m, KnownTypeInt t, KnownTypeInt i, KnownTypeInt th, KnownTypeInt n, KnownTypeInt j) => HasDimension (Proxy ('Dim l m t i th n j)) Source # | |
KnownDimension d => HasDimension (Dimensional v d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal dimension :: Dimensional v d a -> Dimension' Source # |
type KnownDimension (d :: Dimension) = HasDimension (Proxy d) Source #
A KnownDimension is one for which we can construct a term-level representation.
Each validly constructed type of kind Dimension
has a KnownDimension
instance.
While KnownDimension
is a constraint synonym, the presence of
in
a context allows use of KnownDimension
d
.dimension
:: Proxy
d -> Dimension'
type DOne = 'Dim 'Zero 'Zero 'Zero 'Zero 'Zero 'Zero 'Zero Source #
The type-level dimension of dimensionless values.
type Dimensionless = Quantity DOne Source #
(-) :: Num a => Quantity d a -> Quantity d a -> Quantity d a infixl 6 Source #
Subtracts one Quantity
from another.
(*) :: (KnownVariant v1, KnownVariant v2, KnownVariant (v1 * v2), Num a) => Dimensional v1 d1 a -> Dimensional v2 d2 a -> Dimensional (v1 * v2) (d1 * d2) a infixl 7 Source #
(^) :: (Fractional a, KnownTypeInt i, KnownVariant v, KnownVariant (Weaken v)) => Dimensional v d1 a -> Proxy i -> Dimensional (Weaken v) (d1 ^ i) a infixr 8 Source #
Raises a Quantity
or Unit
to an integer power.
Because the power chosen impacts the Dimension
of the result, it is necessary to supply a type-level representation
of the exponent in the form of a Proxy
to some TypeInt
. Convenience values pos1
, pos2
, neg1
, ...
are supplied by the Numeric.NumType.DK.Integers module. The most commonly used ones are
also reexported by Numeric.Units.Dimensional.Prelude.
The intimidating type signature captures the similarity between these operations
and ensures that composite Unit
s are NonMetric
.
sum :: (Num a, Foldable f) => f (Quantity d a) -> Quantity d a Source #
The sum of all elements in a foldable structure.
>>>
sum ([] :: [Mass Double])
0.0 kg
>>>
sum [12.4 *~ meter, 1 *~ foot]
12.7048 m
product :: (Num a, Foldable f) => f (Dimensionless a) -> Dimensionless a Source #
The product of all elements in a foldable structure.
>>>
product ([] :: [Dimensionless Double])
1.0
>>>
product [pi, _4, 0.36 *~ one]
4.523893421169302
(/) :: (KnownVariant v1, KnownVariant v2, KnownVariant (v1 / v2), Fractional a) => Dimensional v1 d1 a -> Dimensional v2 d2 a -> Dimensional (v1 / v2) (d1 / d2) a infixl 7 Source #
recip :: Fractional a => Quantity d a -> Quantity (Recip d) a Source #
Forms the reciprocal of a Quantity
, which has the reciprocal dimension.
>>>
recip $ 47 *~ hertz
2.127659574468085e-2 s
atan2 :: RealFloat a => Quantity d a -> Quantity d a -> Dimensionless a Source #
The standard two argument arctangent function. Since it interprets its two arguments in comparison with one another, the input may have any dimension.
>>>
atan2 _0 _1
0.0
>>>
atan2 _1 _0
1.5707963267948966
>>>
atan2 _0 (negate _1)
3.141592653589793
>>>
atan2 (negate _1) _0
-1.5707963267948966
pi :: Floating a => Dimensionless a Source #
exp :: Floating a => Dimensionless a -> Dimensionless a Source #
log :: Floating a => Dimensionless a -> Dimensionless a Source #
(**) :: Floating a => Dimensionless a -> Dimensionless a -> Dimensionless a infixr 8 Source #
Raises a dimensionless quantity to a dimensionless power.
logBase :: Floating a => Dimensionless a -> Dimensionless a -> Dimensionless a Source #
Takes the logarithm of the second argument in the base of the first.
>>>
logBase _2 _8
3.0
sin :: Floating a => Dimensionless a -> Dimensionless a Source #
cos :: Floating a => Dimensionless a -> Dimensionless a Source #
tan :: Floating a => Dimensionless a -> Dimensionless a Source #
asin :: Floating a => Dimensionless a -> Dimensionless a Source #
acos :: Floating a => Dimensionless a -> Dimensionless a Source #
atan :: Floating a => Dimensionless a -> Dimensionless a Source #
sinh :: Floating a => Dimensionless a -> Dimensionless a Source #
cosh :: Floating a => Dimensionless a -> Dimensionless a Source #
tanh :: Floating a => Dimensionless a -> Dimensionless a Source #
asinh :: Floating a => Dimensionless a -> Dimensionless a Source #
acosh :: Floating a => Dimensionless a -> Dimensionless a Source #
atanh :: Floating a => Dimensionless a -> Dimensionless a Source #
log1p :: Floating a => Dimensionless a -> Dimensionless a Source #
expm1 :: Floating a => Dimensionless a -> Dimensionless a Source #
log1pexp :: Floating a => Dimensionless a -> Dimensionless a Source #
log1mexp :: Floating a => Dimensionless a -> Dimensionless a Source #
(*~) :: Num a => a -> Unit m d a -> Quantity d a infixl 7 Source #
Forms a Quantity
by multipliying a number and a unit.
(^/) :: (KnownTypeInt n, Floating a) => Quantity d a -> Proxy n -> Quantity (NRoot d n) a infixr 8 Source #
Computes the nth root of a Quantity
using **
.
The NRoot
type family will prevent application of this operator where the result would have a fractional dimension or where n is zero.
Because the root chosen impacts the Dimension
of the result, it is necessary to supply a type-level representation
of the root in the form of a Proxy
to some TypeInt
. Convenience values pos1
, pos2
, neg1
, ...
are supplied by the Numeric.NumType.DK.Integers module. The most commonly used ones are
also reexported by Numeric.Units.Dimensional.Prelude.
Also available in prefix form, see nroot
.
nroot :: (KnownTypeInt n, Floating a) => Proxy n -> Quantity d a -> Quantity (NRoot d n) a Source #
Computes the nth root of a Quantity
using **
.
The NRoot
type family will prevent application of this operator where the result would have a fractional dimension or where n is zero.
Because the root chosen impacts the Dimension
of the result, it is necessary to supply a type-level representation
of the root in the form of a Proxy
to some TypeInt
. Convenience values pos1
, pos2
, neg1
, ...
are supplied by the Numeric.NumType.DK.Integers module. The most commonly used ones are
also reexported by Numeric.Units.Dimensional.Prelude.
n must not be zero. Negative roots are defined such that nroot (Proxy :: Proxy (Negate n)) x == nroot (Proxy :: Proxy n) (recip x)
.
Also available in operator form, see ^/
.
(*~~) :: (Functor f, Num a) => f a -> Unit m d a -> f (Quantity d a) infixl 7 Source #
Applies *~
to all values in a functor.
(/~~) :: forall f m d a. (Functor f, Fractional a) => f (Quantity d a) -> Unit m d a -> f a infixl 7 Source #
Applies /~
to all values in a functor.
mean :: (Fractional a, Foldable f) => f (Quantity d a) -> Quantity d a Source #
The arithmetic mean of all elements in a foldable structure.
>>>
mean [pi, _7]
5.070796326794897
dimensionlessLength :: (Num a, Foldable f) => f b -> Dimensionless a Source #
The length of the foldable data structure as a Dimensionless
.
This can be useful for purposes of e.g. calculating averages.
>>>
dimensionlessLength ["foo", "bar"]
2
:: (Fractional a, Integral b) | |
=> Quantity d a | The initial value. |
-> Quantity d a | The final value. |
-> b | The number of intermediate values. If less than one, no intermediate values will result. |
-> [Quantity d a] |
Returns a list of quantities between given bounds.
n <= 0 ==> nFromTo (x :: Mass Double) (y :: Mass Double) n == [x, y]
(x :: Length Double) <= (y :: Length Double) ==> all (\z -> x <= z && z <= y) (nFromTo x y n)
>>>
nFromTo _0 _3 2
[0.0,1.0,2.0,3.0]
>>>
nFromTo _1 _0 7
[1.0,0.875,0.75,0.625,0.5,0.375,0.25,0.125,0.0]
>>>
nFromTo _0 _1 (-5)
[0.0,1.0]
_0 :: Num a => Quantity d a Source #
The constant for zero is polymorphic, allowing it to express zero Length
or
Capacitance
or Velocity
etc,
in addition to the Dimensionless
value zero.
_1 :: Num a => Dimensionless a Source #
_2 :: Num a => Dimensionless a Source #
_3 :: Num a => Dimensionless a Source #
_4 :: Num a => Dimensionless a Source #
_5 :: Num a => Dimensionless a Source #
_6 :: Num a => Dimensionless a Source #
_7 :: Num a => Dimensionless a Source #
_8 :: Num a => Dimensionless a Source #
_9 :: Num a => Dimensionless a Source #
tau :: Floating a => Dimensionless a Source #
Twice pi
.
For background on tau
see https://tauday.com/tau-manifesto (but also
feel free to review https://web.archive.org/web/20200926221249/http://www.thepimanifesto.com/).
siUnit :: forall d a. (KnownDimension d, Num a) => Unit 'NonMetric d a Source #
A polymorphic Unit
which can be used in place of the coherent
SI base unit of any dimension. This allows polymorphic quantity
creation and destruction without exposing the Dimensional
constructor.
one :: Num a => Unit 'NonMetric DOne a Source #
The unit one
has dimension DOne
and is the base unit of dimensionless values.
As detailed in 7.10 "Values of quantities expressed simply as numbers:
the unit one, symbol 1" of [1], the unit one generally does not
appear in expressions. However, for us it is necessary to use one
as we would any other unit to perform the "wrapping" of dimensionless values.
mkUnitR :: Floating a => UnitName m -> ExactPi -> Unit m1 d a -> Unit m d a Source #
Forms a new atomic Unit
by specifying its UnitName
and its definition as a multiple of another Unit
.
Use this variant when the scale factor of the resulting unit is irrational or Approximate
. See mkUnitQ
for when it is rational
and mkUnitZ
for when it is an integer.
Note that supplying zero as a definining quantity is invalid, as the library relies upon units forming a group under multiplication.
Supplying negative defining quantities is allowed and handled gracefully, but is discouraged on the grounds that it may be unexpected by other readers.
exactValue :: Unit m d a -> ExactPi Source #
weaken :: Unit m d a -> Unit 'NonMetric d a Source #
Discards potentially unwanted type level information about a Unit
.
changeRep :: (KnownVariant v, Real a, Fractional b) => Dimensional v d a -> Dimensional v d b Source #
Convenient conversion between numerical types while retaining dimensional information.
>>>
let x = (37 :: Rational) *~ poundMass
>>>
changeRep x :: Mass Double
16.78291769 kg
changeRepApproximate :: (KnownVariant v, Floating b) => Dimensional v d ExactPi -> Dimensional v d b Source #
Convenient conversion from exactly represented values while retaining dimensional information.
asLens :: Fractional a => Unit m d a -> forall f. Functor f => (a -> f a) -> Quantity d a -> f (Quantity d a) Source #
class Category (cat :: k -> k -> Type) where #
A class for categories. Instances should satisfy the laws
id :: forall (a :: k). cat a a #
the identity morphism
(.) :: forall (b :: k) (c :: k) (a :: k). cat b c -> cat a b -> cat a c infixr 9 #
morphism composition
Instances
maximum :: (Foldable t, Ord a) => t a -> a #
The largest element of a non-empty structure.
This function is non-total and will raise a runtime exception if the structure happens to be empty. A structure that supports random access and maintains its elements in order should provide a specialised implementation to return the maximum in faster than linear time.
Examples
Basic usage:
>>>
maximum [1..10]
10
>>>
maximum []
*** Exception: Prelude.maximum: empty list
>>>
maximum Nothing
*** Exception: maximum: empty structure
WARNING: This function is partial for possibly-empty structures like lists.
Since: base-4.8.0.0
minimum :: (Foldable t, Ord a) => t a -> a #
The least element of a non-empty structure.
This function is non-total and will raise a runtime exception if the structure happens to be empty. A structure that supports random access and maintains its elements in order should provide a specialised implementation to return the minimum in faster than linear time.
Examples
Basic usage:
>>>
minimum [1..10]
1
>>>
minimum []
*** Exception: Prelude.minimum: empty list
>>>
minimum Nothing
*** Exception: minimum: empty structure
WARNING: This function is partial for possibly-empty structures like lists.
Since: base-4.8.0.0
A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]
.
The exact range for a given implementation can be determined by using
minBound
and maxBound
from the Bounded
class.
Instances
Data Int | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int -> c Int # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int # dataTypeOf :: Int -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int) # gmapT :: (forall b. Data b => b -> b) -> Int -> Int # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r # gmapQ :: (forall d. Data d => d -> u) -> Int -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Int -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int -> m Int # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int # | |
Storable Int | Since: base-2.1 |
Defined in Foreign.Storable | |
Bits Int | Since: base-2.1 |
Defined in GHC.Bits | |
FiniteBits Int | Since: base-4.6.0.0 |
Defined in GHC.Bits | |
Bounded Int | Since: base-2.1 |
Enum Int | Since: base-2.1 |
Num Int | Since: base-2.1 |
Read Int | Since: base-2.1 |
Integral Int | Since: base-2.0.1 |
Real Int | Since: base-2.0.1 |
Defined in GHC.Real toRational :: Int -> Rational # | |
Show Int | Since: base-2.1 |
NFData Int | |
Defined in Control.DeepSeq | |
Eq Int | |
Ord Int | |
AEq Int | |
Unbox Int | |
Defined in Data.Vector.Unboxed.Base | |
Lift Int | |
Vector Vector Int | |
Defined in Data.Vector.Unboxed.Base basicUnsafeFreeze :: Mutable Vector s Int -> ST s (Vector Int) # basicUnsafeThaw :: Vector Int -> ST s (Mutable Vector s Int) # basicLength :: Vector Int -> Int # basicUnsafeSlice :: Int -> Int -> Vector Int -> Vector Int # basicUnsafeIndexM :: Vector Int -> Int -> Box Int # basicUnsafeCopy :: Mutable Vector s Int -> Vector Int -> ST s () # | |
MVector MVector Int | |
Defined in Data.Vector.Unboxed.Base basicLength :: MVector s Int -> Int # basicUnsafeSlice :: Int -> Int -> MVector s Int -> MVector s Int # basicOverlaps :: MVector s Int -> MVector s Int -> Bool # basicUnsafeNew :: Int -> ST s (MVector s Int) # basicInitialize :: MVector s Int -> ST s () # basicUnsafeReplicate :: Int -> Int -> ST s (MVector s Int) # basicUnsafeRead :: MVector s Int -> Int -> ST s Int # basicUnsafeWrite :: MVector s Int -> Int -> Int -> ST s () # basicClear :: MVector s Int -> ST s () # basicSet :: MVector s Int -> Int -> ST s () # basicUnsafeCopy :: MVector s Int -> MVector s Int -> ST s () # basicUnsafeMove :: MVector s Int -> MVector s Int -> ST s () # basicUnsafeGrow :: MVector s Int -> Int -> ST s (MVector s Int) # | |
Generic1 (URec Int :: k -> Type) | |
Foldable (UInt :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UInt m -> m # foldMap :: Monoid m => (a -> m) -> UInt a -> m # foldMap' :: Monoid m => (a -> m) -> UInt a -> m # foldr :: (a -> b -> b) -> b -> UInt a -> b # foldr' :: (a -> b -> b) -> b -> UInt a -> b # foldl :: (b -> a -> b) -> b -> UInt a -> b # foldl' :: (b -> a -> b) -> b -> UInt a -> b # foldr1 :: (a -> a -> a) -> UInt a -> a # foldl1 :: (a -> a -> a) -> UInt a -> a # elem :: Eq a => a -> UInt a -> Bool # maximum :: Ord a => UInt a -> a # | |
Traversable (UInt :: Type -> Type) | Since: base-4.9.0.0 |
Functor (URec Int :: Type -> Type) | Since: base-4.9.0.0 |
Generic (URec Int p) | |
Show (URec Int p) | Since: base-4.9.0.0 |
Eq (URec Int p) | Since: base-4.9.0.0 |
Ord (URec Int p) | Since: base-4.9.0.0 |
newtype Vector Int | |
data URec Int (p :: k) | Used for marking occurrences of Since: base-4.9.0.0 |
newtype MVector s Int | |
type Rep1 (URec Int :: k -> Type) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Int p) | Since: base-4.9.0.0 |
Defined in GHC.Generics |
Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.
Instances
Data Float | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Float -> c Float # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Float # dataTypeOf :: Float -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Float) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Float) # gmapT :: (forall b. Data b => b -> b) -> Float -> Float # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r # gmapQ :: (forall d. Data d => d -> u) -> Float -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Float -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Float -> m Float # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float # | |
Storable Float | Since: base-2.1 |
Floating Float | Since: base-2.1 |
RealFloat Float | Since: base-2.1 |
Defined in GHC.Float floatRadix :: Float -> Integer # floatDigits :: Float -> Int # floatRange :: Float -> (Int, Int) # decodeFloat :: Float -> (Integer, Int) # encodeFloat :: Integer -> Int -> Float # significand :: Float -> Float # scaleFloat :: Int -> Float -> Float # isInfinite :: Float -> Bool # isDenormalized :: Float -> Bool # isNegativeZero :: Float -> Bool # | |
Read Float | Since: base-2.1 |
NFData Float | |
Defined in Control.DeepSeq | |
Eq Float | Note that due to the presence of
Also note that
|
Ord Float | Note that due to the presence of
Also note that, due to the same,
|
AEq Float | |
IEEE Float | |
Defined in Numeric.IEEE minDenormal :: Float # copySign :: Float -> Float -> Float # identicalIEEE :: Float -> Float -> Bool # bisectIEEE :: Float -> Float -> Float # sameSignificandBits :: Float -> Float -> Int # nanWithPayload :: Word64 -> Float # maxNaNPayload :: Float -> Word64 # nanPayload :: Float -> Word64 # | |
Unbox Float | |
Defined in Data.Vector.Unboxed.Base | |
Lift Float | |
Vector Vector Float | |
Defined in Data.Vector.Unboxed.Base basicUnsafeFreeze :: Mutable Vector s Float -> ST s (Vector Float) # basicUnsafeThaw :: Vector Float -> ST s (Mutable Vector s Float) # basicLength :: Vector Float -> Int # basicUnsafeSlice :: Int -> Int -> Vector Float -> Vector Float # basicUnsafeIndexM :: Vector Float -> Int -> Box Float # basicUnsafeCopy :: Mutable Vector s Float -> Vector Float -> ST s () # | |
MVector MVector Float | |
Defined in Data.Vector.Unboxed.Base basicLength :: MVector s Float -> Int # basicUnsafeSlice :: Int -> Int -> MVector s Float -> MVector s Float # basicOverlaps :: MVector s Float -> MVector s Float -> Bool # basicUnsafeNew :: Int -> ST s (MVector s Float) # basicInitialize :: MVector s Float -> ST s () # basicUnsafeReplicate :: Int -> Float -> ST s (MVector s Float) # basicUnsafeRead :: MVector s Float -> Int -> ST s Float # basicUnsafeWrite :: MVector s Float -> Int -> Float -> ST s () # basicClear :: MVector s Float -> ST s () # basicSet :: MVector s Float -> Float -> ST s () # basicUnsafeCopy :: MVector s Float -> MVector s Float -> ST s () # basicUnsafeMove :: MVector s Float -> MVector s Float -> ST s () # basicUnsafeGrow :: MVector s Float -> Int -> ST s (MVector s Float) # | |
Generic1 (URec Float :: k -> Type) | |
Foldable (UFloat :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UFloat m -> m # foldMap :: Monoid m => (a -> m) -> UFloat a -> m # foldMap' :: Monoid m => (a -> m) -> UFloat a -> m # foldr :: (a -> b -> b) -> b -> UFloat a -> b # foldr' :: (a -> b -> b) -> b -> UFloat a -> b # foldl :: (b -> a -> b) -> b -> UFloat a -> b # foldl' :: (b -> a -> b) -> b -> UFloat a -> b # foldr1 :: (a -> a -> a) -> UFloat a -> a # foldl1 :: (a -> a -> a) -> UFloat a -> a # elem :: Eq a => a -> UFloat a -> Bool # maximum :: Ord a => UFloat a -> a # minimum :: Ord a => UFloat a -> a # | |
Traversable (UFloat :: Type -> Type) | Since: base-4.9.0.0 |
AEq (Complex Float) | |
Functor (URec Float :: Type -> Type) | Since: base-4.9.0.0 |
Generic (URec Float p) | |
Show (URec Float p) | |
Eq (URec Float p) | |
Ord (URec Float p) | |
Defined in GHC.Generics | |
newtype Vector Float | |
data URec Float (p :: k) | Used for marking occurrences of Since: base-4.9.0.0 |
newtype MVector s Float | |
type Rep1 (URec Float :: k -> Type) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Float p) | |
Defined in GHC.Generics |
The character type Char
is an enumeration whose values represent
Unicode (or equivalently ISO/IEC 10646) code points (i.e. characters, see
http://www.unicode.org/ for details). This set extends the ISO 8859-1
(Latin-1) character set (the first 256 characters), which is itself an extension
of the ASCII character set (the first 128 characters). A character literal in
Haskell has type Char
.
To convert a Char
to or from the corresponding Int
value defined
by Unicode, use toEnum
and fromEnum
from the
Enum
class respectively (or equivalently ord
and
chr
).
Instances
Data Char | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Char -> c Char # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Char # dataTypeOf :: Char -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Char) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Char) # gmapT :: (forall b. Data b => b -> b) -> Char -> Char # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r # gmapQ :: (forall d. Data d => d -> u) -> Char -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Char -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Char -> m Char # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char # | |
Storable Char | Since: base-2.1 |
Defined in Foreign.Storable | |
Bounded Char | Since: base-2.1 |
Enum Char | Since: base-2.1 |
Read Char | Since: base-2.1 |
Show Char | Since: base-2.1 |
NFData Char | |
Defined in Control.DeepSeq | |
Eq Char | |
Ord Char | |
AEq Char | |
Unbox Char | |
Defined in Data.Vector.Unboxed.Base | |
TestCoercion SChar | Since: base-4.18.0.0 |
Defined in GHC.TypeLits | |
TestEquality SChar | Since: base-4.18.0.0 |
Defined in GHC.TypeLits | |
Lift Char | |
Vector Vector Char | |
Defined in Data.Vector.Unboxed.Base basicUnsafeFreeze :: Mutable Vector s Char -> ST s (Vector Char) # basicUnsafeThaw :: Vector Char -> ST s (Mutable Vector s Char) # basicLength :: Vector Char -> Int # basicUnsafeSlice :: Int -> Int -> Vector Char -> Vector Char # basicUnsafeIndexM :: Vector Char -> Int -> Box Char # basicUnsafeCopy :: Mutable Vector s Char -> Vector Char -> ST s () # | |
MVector MVector Char | |
Defined in Data.Vector.Unboxed.Base basicLength :: MVector s Char -> Int # basicUnsafeSlice :: Int -> Int -> MVector s Char -> MVector s Char # basicOverlaps :: MVector s Char -> MVector s Char -> Bool # basicUnsafeNew :: Int -> ST s (MVector s Char) # basicInitialize :: MVector s Char -> ST s () # basicUnsafeReplicate :: Int -> Char -> ST s (MVector s Char) # basicUnsafeRead :: MVector s Char -> Int -> ST s Char # basicUnsafeWrite :: MVector s Char -> Int -> Char -> ST s () # basicClear :: MVector s Char -> ST s () # basicSet :: MVector s Char -> Char -> ST s () # basicUnsafeCopy :: MVector s Char -> MVector s Char -> ST s () # basicUnsafeMove :: MVector s Char -> MVector s Char -> ST s () # basicUnsafeGrow :: MVector s Char -> Int -> ST s (MVector s Char) # | |
Generic1 (URec Char :: k -> Type) | |
Foldable (UChar :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UChar m -> m # foldMap :: Monoid m => (a -> m) -> UChar a -> m # foldMap' :: Monoid m => (a -> m) -> UChar a -> m # foldr :: (a -> b -> b) -> b -> UChar a -> b # foldr' :: (a -> b -> b) -> b -> UChar a -> b # foldl :: (b -> a -> b) -> b -> UChar a -> b # foldl' :: (b -> a -> b) -> b -> UChar a -> b # foldr1 :: (a -> a -> a) -> UChar a -> a # foldl1 :: (a -> a -> a) -> UChar a -> a # elem :: Eq a => a -> UChar a -> Bool # maximum :: Ord a => UChar a -> a # minimum :: Ord a => UChar a -> a # | |
Traversable (UChar :: Type -> Type) | Since: base-4.9.0.0 |
Functor (URec Char :: Type -> Type) | Since: base-4.9.0.0 |
Generic (URec Char p) | |
Show (URec Char p) | Since: base-4.9.0.0 |
Eq (URec Char p) | Since: base-4.9.0.0 |
Ord (URec Char p) | Since: base-4.9.0.0 |
newtype Vector Char | |
data URec Char (p :: k) | Used for marking occurrences of Since: base-4.9.0.0 |
newtype MVector s Char | |
type Compare (a :: Char) (b :: Char) | |
Defined in Data.Type.Ord | |
type Rep1 (URec Char :: k -> Type) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Char p) | Since: base-4.9.0.0 |
Defined in GHC.Generics |
A value of type
is a computation which, when performed,
does some I/O before returning a value of type IO
aa
.
There is really only one way to "perform" an I/O action: bind it to
Main.main
in your program. When your program is run, the I/O will
be performed. It isn't possible to perform I/O from an arbitrary
function, unless that function is itself in the IO
monad and called
at some point, directly or indirectly, from Main.main
.
IO
is a monad, so IO
actions can be combined using either the do-notation
or the >>
and >>=
operations from the Monad
class.
Instances
Instances
Data Bool | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bool -> c Bool # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bool # dataTypeOf :: Bool -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bool) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bool) # gmapT :: (forall b. Data b => b -> b) -> Bool -> Bool # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r # gmapQ :: (forall d. Data d => d -> u) -> Bool -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bool -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bool -> m Bool # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool # | |
Storable Bool | Since: base-2.1 |
Defined in Foreign.Storable | |
Bits Bool | Interpret Since: base-4.7.0.0 |
Defined in GHC.Bits (.&.) :: Bool -> Bool -> Bool # (.|.) :: Bool -> Bool -> Bool # complement :: Bool -> Bool # shift :: Bool -> Int -> Bool # rotate :: Bool -> Int -> Bool # setBit :: Bool -> Int -> Bool # clearBit :: Bool -> Int -> Bool # complementBit :: Bool -> Int -> Bool # testBit :: Bool -> Int -> Bool # bitSizeMaybe :: Bool -> Maybe Int # shiftL :: Bool -> Int -> Bool # unsafeShiftL :: Bool -> Int -> Bool # shiftR :: Bool -> Int -> Bool # unsafeShiftR :: Bool -> Int -> Bool # rotateL :: Bool -> Int -> Bool # | |
FiniteBits Bool | Since: base-4.7.0.0 |
Defined in GHC.Bits | |
Bounded Bool | Since: base-2.1 |
Enum Bool | Since: base-2.1 |
Generic Bool | |
SingKind Bool | Since: base-4.9.0.0 |
Defined in GHC.Generics type DemoteRep Bool | |
Read Bool | Since: base-2.1 |
Show Bool | Since: base-2.1 |
NFData Bool | |
Defined in Control.DeepSeq | |
Eq Bool | |
Ord Bool | |
AEq Bool | |
Unbox Bool | |
Defined in Data.Vector.Unboxed.Base | |
SingI 'False | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
SingI 'True | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Lift Bool | |
Vector Vector Bool | |
Defined in Data.Vector.Unboxed.Base basicUnsafeFreeze :: Mutable Vector s Bool -> ST s (Vector Bool) # basicUnsafeThaw :: Vector Bool -> ST s (Mutable Vector s Bool) # basicLength :: Vector Bool -> Int # basicUnsafeSlice :: Int -> Int -> Vector Bool -> Vector Bool # basicUnsafeIndexM :: Vector Bool -> Int -> Box Bool # basicUnsafeCopy :: Mutable Vector s Bool -> Vector Bool -> ST s () # | |
MVector MVector Bool | |
Defined in Data.Vector.Unboxed.Base basicLength :: MVector s Bool -> Int # basicUnsafeSlice :: Int -> Int -> MVector s Bool -> MVector s Bool # basicOverlaps :: MVector s Bool -> MVector s Bool -> Bool # basicUnsafeNew :: Int -> ST s (MVector s Bool) # basicInitialize :: MVector s Bool -> ST s () # basicUnsafeReplicate :: Int -> Bool -> ST s (MVector s Bool) # basicUnsafeRead :: MVector s Bool -> Int -> ST s Bool # basicUnsafeWrite :: MVector s Bool -> Int -> Bool -> ST s () # basicClear :: MVector s Bool -> ST s () # basicSet :: MVector s Bool -> Bool -> ST s () # basicUnsafeCopy :: MVector s Bool -> MVector s Bool -> ST s () # basicUnsafeMove :: MVector s Bool -> MVector s Bool -> ST s () # basicUnsafeGrow :: MVector s Bool -> Int -> ST s (MVector s Bool) # | |
type DemoteRep Bool | |
Defined in GHC.Generics | |
type Rep Bool | Since: base-4.6.0.0 |
data Sing (a :: Bool) | |
newtype Vector Bool | |
newtype MVector s Bool | |
Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.
Instances
Data Double | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Double -> c Double # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Double # toConstr :: Double -> Constr # dataTypeOf :: Double -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Double) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Double) # gmapT :: (forall b. Data b => b -> b) -> Double -> Double # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r # gmapQ :: (forall d. Data d => d -> u) -> Double -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Double -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Double -> m Double # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double # | |
Storable Double | Since: base-2.1 |
Floating Double | Since: base-2.1 |
RealFloat Double | Since: base-2.1 |
Defined in GHC.Float floatRadix :: Double -> Integer # floatDigits :: Double -> Int # floatRange :: Double -> (Int, Int) # decodeFloat :: Double -> (Integer, Int) # encodeFloat :: Integer -> Int -> Double # significand :: Double -> Double # scaleFloat :: Int -> Double -> Double # isInfinite :: Double -> Bool # isDenormalized :: Double -> Bool # isNegativeZero :: Double -> Bool # | |
Read Double | Since: base-2.1 |
NFData Double | |
Defined in Control.DeepSeq | |
Eq Double | Note that due to the presence of
Also note that
|
Ord Double | Note that due to the presence of
Also note that, due to the same,
|
AEq Double | |
IEEE Double | |
Defined in Numeric.IEEE minDenormal :: Double # copySign :: Double -> Double -> Double # identicalIEEE :: Double -> Double -> Bool # succIEEE :: Double -> Double # predIEEE :: Double -> Double # bisectIEEE :: Double -> Double -> Double # sameSignificandBits :: Double -> Double -> Int # nanWithPayload :: Word64 -> Double # maxNaNPayload :: Double -> Word64 # nanPayload :: Double -> Word64 # | |
Unbox Double | |
Defined in Data.Vector.Unboxed.Base | |
Lift Double | |
Vector Vector Double | |
Defined in Data.Vector.Unboxed.Base basicUnsafeFreeze :: Mutable Vector s Double -> ST s (Vector Double) # basicUnsafeThaw :: Vector Double -> ST s (Mutable Vector s Double) # basicLength :: Vector Double -> Int # basicUnsafeSlice :: Int -> Int -> Vector Double -> Vector Double # basicUnsafeIndexM :: Vector Double -> Int -> Box Double # basicUnsafeCopy :: Mutable Vector s Double -> Vector Double -> ST s () # | |
MVector MVector Double | |
Defined in Data.Vector.Unboxed.Base basicLength :: MVector s Double -> Int # basicUnsafeSlice :: Int -> Int -> MVector s Double -> MVector s Double # basicOverlaps :: MVector s Double -> MVector s Double -> Bool # basicUnsafeNew :: Int -> ST s (MVector s Double) # basicInitialize :: MVector s Double -> ST s () # basicUnsafeReplicate :: Int -> Double -> ST s (MVector s Double) # basicUnsafeRead :: MVector s Double -> Int -> ST s Double # basicUnsafeWrite :: MVector s Double -> Int -> Double -> ST s () # basicClear :: MVector s Double -> ST s () # basicSet :: MVector s Double -> Double -> ST s () # basicUnsafeCopy :: MVector s Double -> MVector s Double -> ST s () # basicUnsafeMove :: MVector s Double -> MVector s Double -> ST s () # basicUnsafeGrow :: MVector s Double -> Int -> ST s (MVector s Double) # | |
Generic1 (URec Double :: k -> Type) | |
Foldable (UDouble :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UDouble m -> m # foldMap :: Monoid m => (a -> m) -> UDouble a -> m # foldMap' :: Monoid m => (a -> m) -> UDouble a -> m # foldr :: (a -> b -> b) -> b -> UDouble a -> b # foldr' :: (a -> b -> b) -> b -> UDouble a -> b # foldl :: (b -> a -> b) -> b -> UDouble a -> b # foldl' :: (b -> a -> b) -> b -> UDouble a -> b # foldr1 :: (a -> a -> a) -> UDouble a -> a # foldl1 :: (a -> a -> a) -> UDouble a -> a # elem :: Eq a => a -> UDouble a -> Bool # maximum :: Ord a => UDouble a -> a # minimum :: Ord a => UDouble a -> a # | |
Traversable (UDouble :: Type -> Type) | Since: base-4.9.0.0 |
AEq (Complex Double) | |
Functor (URec Double :: Type -> Type) | Since: base-4.9.0.0 |
Generic (URec Double p) | |
Show (URec Double p) | Since: base-4.9.0.0 |
Eq (URec Double p) | Since: base-4.9.0.0 |
Ord (URec Double p) | Since: base-4.9.0.0 |
Defined in GHC.Generics compare :: URec Double p -> URec Double p -> Ordering # (<) :: URec Double p -> URec Double p -> Bool # (<=) :: URec Double p -> URec Double p -> Bool # (>) :: URec Double p -> URec Double p -> Bool # (>=) :: URec Double p -> URec Double p -> Bool # | |
newtype Vector Double | |
data URec Double (p :: k) | Used for marking occurrences of Since: base-4.9.0.0 |
newtype MVector s Double | |
type Rep1 (URec Double :: k -> Type) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Double p) | Since: base-4.9.0.0 |
Defined in GHC.Generics |
Instances
Data Word | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word -> c Word # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word # dataTypeOf :: Word -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word) # gmapT :: (forall b. Data b => b -> b) -> Word -> Word # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r # gmapQ :: (forall d. Data d => d -> u) -> Word -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Word -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word -> m Word # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word # | |
Storable Word | Since: base-2.1 |
Defined in Foreign.Storable | |
Bits Word | Since: base-2.1 |
Defined in GHC.Bits (.&.) :: Word -> Word -> Word # (.|.) :: Word -> Word -> Word # complement :: Word -> Word # shift :: Word -> Int -> Word # rotate :: Word -> Int -> Word # setBit :: Word -> Int -> Word # clearBit :: Word -> Int -> Word # complementBit :: Word -> Int -> Word # testBit :: Word -> Int -> Bool # bitSizeMaybe :: Word -> Maybe Int # shiftL :: Word -> Int -> Word # unsafeShiftL :: Word -> Int -> Word # shiftR :: Word -> Int -> Word # unsafeShiftR :: Word -> Int -> Word # rotateL :: Word -> Int -> Word # | |
FiniteBits Word | Since: base-4.6.0.0 |
Defined in GHC.Bits | |
Bounded Word | Since: base-2.1 |
Enum Word | Since: base-2.1 |
Num Word | Since: base-2.1 |
Read Word | Since: base-4.5.0.0 |
Integral Word | Since: base-2.1 |
Real Word | Since: base-2.1 |
Defined in GHC.Real toRational :: Word -> Rational # | |
Show Word | Since: base-2.1 |
NFData Word | |
Defined in Control.DeepSeq | |
Eq Word | |
Ord Word | |
AEq Word | |
Unbox Word | |
Defined in Data.Vector.Unboxed.Base | |
Lift Word | |
Vector Vector Word | |
Defined in Data.Vector.Unboxed.Base basicUnsafeFreeze :: Mutable Vector s Word -> ST s (Vector Word) # basicUnsafeThaw :: Vector Word -> ST s (Mutable Vector s Word) # basicLength :: Vector Word -> Int # basicUnsafeSlice :: Int -> Int -> Vector Word -> Vector Word # basicUnsafeIndexM :: Vector Word -> Int -> Box Word # basicUnsafeCopy :: Mutable Vector s Word -> Vector Word -> ST s () # | |
MVector MVector Word | |
Defined in Data.Vector.Unboxed.Base basicLength :: MVector s Word -> Int # basicUnsafeSlice :: Int -> Int -> MVector s Word -> MVector s Word # basicOverlaps :: MVector s Word -> MVector s Word -> Bool # basicUnsafeNew :: Int -> ST s (MVector s Word) # basicInitialize :: MVector s Word -> ST s () # basicUnsafeReplicate :: Int -> Word -> ST s (MVector s Word) # basicUnsafeRead :: MVector s Word -> Int -> ST s Word # basicUnsafeWrite :: MVector s Word -> Int -> Word -> ST s () # basicClear :: MVector s Word -> ST s () # basicSet :: MVector s Word -> Word -> ST s () # basicUnsafeCopy :: MVector s Word -> MVector s Word -> ST s () # basicUnsafeMove :: MVector s Word -> MVector s Word -> ST s () # basicUnsafeGrow :: MVector s Word -> Int -> ST s (MVector s Word) # | |
Generic1 (URec Word :: k -> Type) | |
Foldable (UWord :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UWord m -> m # foldMap :: Monoid m => (a -> m) -> UWord a -> m # foldMap' :: Monoid m => (a -> m) -> UWord a -> m # foldr :: (a -> b -> b) -> b -> UWord a -> b # foldr' :: (a -> b -> b) -> b -> UWord a -> b # foldl :: (b -> a -> b) -> b -> UWord a -> b # foldl' :: (b -> a -> b) -> b -> UWord a -> b # foldr1 :: (a -> a -> a) -> UWord a -> a # foldl1 :: (a -> a -> a) -> UWord a -> a # elem :: Eq a => a -> UWord a -> Bool # maximum :: Ord a => UWord a -> a # minimum :: Ord a => UWord a -> a # | |
Traversable (UWord :: Type -> Type) | Since: base-4.9.0.0 |
Functor (URec Word :: Type -> Type) | Since: base-4.9.0.0 |
Generic (URec Word p) | |
Show (URec Word p) | Since: base-4.9.0.0 |
Eq (URec Word p) | Since: base-4.9.0.0 |
Ord (URec Word p) | Since: base-4.9.0.0 |
newtype Vector Word | |
data URec Word (p :: k) | Used for marking occurrences of Since: base-4.9.0.0 |
newtype MVector s Word | |
type Rep1 (URec Word :: k -> Type) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Word p) | Since: base-4.9.0.0 |
Defined in GHC.Generics |
Instances
Data Ordering | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ordering -> c Ordering # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ordering # toConstr :: Ordering -> Constr # dataTypeOf :: Ordering -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ordering) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ordering) # gmapT :: (forall b. Data b => b -> b) -> Ordering -> Ordering # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r # gmapQ :: (forall d. Data d => d -> u) -> Ordering -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ordering -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering # | |
Monoid Ordering | Since: base-2.1 |
Semigroup Ordering | Since: base-4.9.0.0 |
Bounded Ordering | Since: base-2.1 |
Enum Ordering | Since: base-2.1 |
Generic Ordering | |
Read Ordering | Since: base-2.1 |
Show Ordering | Since: base-2.1 |
NFData Ordering | |
Defined in Control.DeepSeq | |
Eq Ordering | |
Ord Ordering | |
Defined in GHC.Classes | |
AEq Ordering | |
type Rep Ordering | Since: base-4.6.0.0 |
The Maybe
type encapsulates an optional value. A value of type
either contains a value of type Maybe
aa
(represented as
),
or it is empty (represented as Just
aNothing
). Using Maybe
is a good way to
deal with errors or exceptional cases without resorting to drastic
measures such as error
.
The Maybe
type is also a monad. It is a simple kind of error
monad, where all errors are represented by Nothing
. A richer
error monad can be built using the Either
type.
Instances
MonadFail Maybe | Since: base-4.9.0.0 |
Defined in Control.Monad.Fail | |
Foldable Maybe | Since: base-2.1 |
Defined in Data.Foldable fold :: Monoid m => Maybe m -> m # foldMap :: Monoid m => (a -> m) -> Maybe a -> m # foldMap' :: Monoid m => (a -> m) -> Maybe a -> m # foldr :: (a -> b -> b) -> b -> Maybe a -> b # foldr' :: (a -> b -> b) -> b -> Maybe a -> b # foldl :: (b -> a -> b) -> b -> Maybe a -> b # foldl' :: (b -> a -> b) -> b -> Maybe a -> b # foldr1 :: (a -> a -> a) -> Maybe a -> a # foldl1 :: (a -> a -> a) -> Maybe a -> a # elem :: Eq a => a -> Maybe a -> Bool # maximum :: Ord a => Maybe a -> a # minimum :: Ord a => Maybe a -> a # | |
Eq1 Maybe | Since: base-4.9.0.0 |
Ord1 Maybe | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 Maybe | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 Maybe | Since: base-4.9.0.0 |
Traversable Maybe | Since: base-2.1 |
Alternative Maybe | Picks the leftmost Since: base-2.1 |
Applicative Maybe | Since: base-2.1 |
Functor Maybe | Since: base-2.1 |
Monad Maybe | Since: base-2.1 |
MonadPlus Maybe | Picks the leftmost Since: base-2.1 |
NFData1 Maybe | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Generic1 Maybe | |
Lift a => Lift (Maybe a :: Type) | |
Data a => Data (Maybe a) | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Maybe a -> c (Maybe a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Maybe a) # toConstr :: Maybe a -> Constr # dataTypeOf :: Maybe a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Maybe a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Maybe a)) # gmapT :: (forall b. Data b => b -> b) -> Maybe a -> Maybe a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r # gmapQ :: (forall d. Data d => d -> u) -> Maybe a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Maybe a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) # | |
Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
Semigroup a => Semigroup (Maybe a) | Since: base-4.9.0.0 |
Generic (Maybe a) | |
SingKind a => SingKind (Maybe a) | Since: base-4.9.0.0 |
Defined in GHC.Generics type DemoteRep (Maybe a) | |
Read a => Read (Maybe a) | Since: base-2.1 |
Show a => Show (Maybe a) | Since: base-2.1 |
NFData a => NFData (Maybe a) | |
Defined in Control.DeepSeq | |
Eq a => Eq (Maybe a) | Since: base-2.1 |
Ord a => Ord (Maybe a) | Since: base-2.1 |
AEq a => AEq (Maybe a) | |
SingI ('Nothing :: Maybe a) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
SingI a2 => SingI ('Just a2 :: Maybe a1) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep1 Maybe | Since: base-4.6.0.0 |
type DemoteRep (Maybe a) | |
Defined in GHC.Generics | |
type Rep (Maybe a) | Since: base-4.6.0.0 |
Defined in GHC.Generics | |
data Sing (b :: Maybe a) | |
class a ~# b => (a :: k) ~ (b :: k) infix 4 #
Lifted, homogeneous equality. By lifted, we mean that it
can be bogus (deferred type error). By homogeneous, the two
types a
and b
must have the same kinds.
Arbitrary precision integers. In contrast with fixed-size integral types
such as Int
, the Integer
type represents the entire infinite range of
integers.
Integers are stored in a kind of sign-magnitude form, hence do not expect two's complement form when using bit operations.
If the value is small (fit into an Int
), IS
constructor is used.
Otherwise Integer
and IN
constructors are used to store a BigNat
representing respectively the positive or the negative value magnitude.
Invariant: Integer
and IN
are used iff value doesn't fit in IS
Instances
Data Integer | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Integer -> c Integer # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Integer # toConstr :: Integer -> Constr # dataTypeOf :: Integer -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Integer) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Integer) # gmapT :: (forall b. Data b => b -> b) -> Integer -> Integer # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r # gmapQ :: (forall d. Data d => d -> u) -> Integer -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Integer -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Integer -> m Integer # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer # | |
Bits Integer | Since: base-2.1 |
Defined in GHC.Bits (.&.) :: Integer -> Integer -> Integer # (.|.) :: Integer -> Integer -> Integer # xor :: Integer -> Integer -> Integer # complement :: Integer -> Integer # shift :: Integer -> Int -> Integer # rotate :: Integer -> Int -> Integer # setBit :: Integer -> Int -> Integer # clearBit :: Integer -> Int -> Integer # complementBit :: Integer -> Int -> Integer # testBit :: Integer -> Int -> Bool # bitSizeMaybe :: Integer -> Maybe Int # shiftL :: Integer -> Int -> Integer # unsafeShiftL :: Integer -> Int -> Integer # shiftR :: Integer -> Int -> Integer # unsafeShiftR :: Integer -> Int -> Integer # rotateL :: Integer -> Int -> Integer # | |
Enum Integer | Since: base-2.1 |
Num Integer | Since: base-2.1 |
Read Integer | Since: base-2.1 |