Copyright | Copyright (C) 2006-2018 Bjorn Buckwalter |
---|---|
License | BSD3 |
Maintainer | bjorn@buckwalter.se |
Stability | Stable |
Portability | GHC only |
Safe Haskell | None |
Language | Haskell2010 |
Numeric.Units.Dimensional.Prelude
Description
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
- class HasDynamicDimension a => HasDimension a where
- dimension :: a -> Dimension'
- data Dimension' = Dim' !Int !Int !Int !Int !Int !Int !Int
- type KnownDimension (d :: Dimension) = HasDimension (Proxy d)
- type Cbrt d = NRoot d Pos3
- type Sqrt d = NRoot d Pos2
- type family NRoot (d :: Dimension) (x :: TypeInt) where ...
- type family (d :: Dimension) ^ (x :: TypeInt) where ...
- type Recip (d :: Dimension) = DOne / d
- type family (a :: Dimension) / (d :: Dimension) where ...
- type family (a :: Dimension) * (b :: Dimension) where ...
- type DLuminousIntensity = Dim Zero Zero Zero Zero Zero Zero Pos1
- type DAmountOfSubstance = Dim Zero Zero Zero Zero Zero Pos1 Zero
- type DThermodynamicTemperature = Dim Zero Zero Zero Zero Pos1 Zero Zero
- type DElectricCurrent = Dim Zero Zero Zero Pos1 Zero Zero Zero
- type DTime = Dim Zero Zero Pos1 Zero Zero Zero Zero
- type DMass = Dim Zero Pos1 Zero Zero Zero Zero Zero
- type DLength = Dim Pos1 Zero Zero Zero Zero Zero Zero
- type DOne = Dim Zero Zero Zero Zero Zero Zero Zero
- data Dimension = Dim TypeInt TypeInt TypeInt TypeInt TypeInt TypeInt TypeInt
- data Metricality
- class KnownVariant (v :: Variant) where
- data Dimensional v :: Dimension -> Type -> Type
- type Quantity = SQuantity One
- type Unit (m :: Metricality) = Dimensional (DUnit m)
- siUnit :: forall d a. (KnownDimension d, Num a) => Unit NonMetric d a
- showIn :: (Show a, Fractional a) => Unit m d a -> Quantity d a -> String
- type LuminousIntensity = Quantity DLuminousIntensity
- type AmountOfSubstance = Quantity DAmountOfSubstance
- type ThermodynamicTemperature = Quantity DThermodynamicTemperature
- type ElectricCurrent = Quantity DElectricCurrent
- type Time = Quantity DTime
- type Mass = Quantity DMass
- type Length = Quantity DLength
- type Dimensionless = Quantity DOne
- 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
- (*~) :: Num a => a -> Unit m d a -> Quantity d a
- (/~) :: Fractional a => Quantity d a -> Unit m d a -> a
- (*) :: (KnownVariant v1, KnownVariant v2, KnownVariant (v1 * v2), Num a) => Dimensional v1 d1 a -> Dimensional v2 d2 a -> Dimensional (v1 * v2) (d1 * d2) 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
- (^) :: (Fractional a, KnownTypeInt i, KnownVariant v, KnownVariant (Weaken v)) => Dimensional v d1 a -> Proxy i -> Dimensional (Weaken v) (d1 ^ i) a
- negate :: Num a => Quantity d a -> Quantity d a
- (+) :: Num a => Quantity d a -> Quantity d a -> Quantity d a
- (-) :: Num a => Quantity d a -> Quantity d a -> Quantity d a
- abs :: Num a => Quantity d a -> Quantity d a
- signum :: Num a => Quantity d a -> Dimensionless a
- nroot :: (KnownTypeInt n, Floating a) => Proxy n -> Quantity d a -> Quantity (NRoot d n) a
- sqrt :: Floating a => Quantity d a -> Quantity (Sqrt d) a
- cbrt :: Floating a => Quantity d a -> Quantity (Cbrt d) a
- (^/) :: (KnownTypeInt n, Floating a) => Quantity d a -> Proxy n -> Quantity (NRoot d n) 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
- sum :: (Num a, Foldable f) => f (Quantity d a) -> Quantity d a
- product :: (Num a, Foldable f) => f (Dimensionless a) -> Dimensionless 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]
- exp :: Floating a => Dimensionless a -> Dimensionless a
- log :: Floating 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
- (**) :: Floating a => Dimensionless a -> Dimensionless a -> Dimensionless a
- logBase :: Floating a => Dimensionless a -> Dimensionless a -> Dimensionless a
- atan2 :: RealFloat a => Quantity d a -> Quantity d a -> Dimensionless a
- one :: Num a => Unit NonMetric DOne 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
- pi :: Floating a => Dimensionless a
- tau :: Floating a => Dimensionless a
- 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)
- 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
- module Numeric.Units.Dimensional.Quantities
- module Numeric.Units.Dimensional.SIUnits
- pos5 :: Proxy Pos5
- pos4 :: Proxy Pos4
- pos3 :: Proxy Pos3
- pos2 :: Proxy Pos2
- pos1 :: Proxy Pos1
- zero :: Proxy Zero
- neg1 :: Proxy Neg1
- neg2 :: Proxy Neg2
- neg3 :: Proxy Neg3
- neg4 :: Proxy Neg4
- neg5 :: Proxy Neg5
- class Category (cat :: k -> k -> Type) where
- maximum :: (Foldable t, Ord a) => t a -> a
- minimum :: (Foldable t, Ord a) => t a -> a
- (++) :: [a] -> [a] -> [a]
- seq :: a -> b -> b
- filter :: (a -> Bool) -> [a] -> [a]
- zip :: [a] -> [b] -> [(a, b)]
- print :: Show a => a -> IO ()
- fst :: (a, b) -> a
- snd :: (a, b) -> b
- otherwise :: Bool
- map :: (a -> b) -> [a] -> [b]
- ($) :: (a -> b) -> a -> b
- fromIntegral :: (Integral a, Num b) => a -> b
- realToFrac :: (Real a, Fractional b) => a -> b
- 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 (Real a, Enum a) => Integral a where
- 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 Read 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 Show a 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
- data Bool
- data Char
- data Double
- data Float
- data Int
- data Integer
- data Maybe a
- data Ordering
- type Rational = Ratio Integer
- data IO a
- data Word
- data Either a b
- readIO :: Read a => String -> IO a
- readLn :: Read a => IO a
- appendFile :: FilePath -> String -> IO ()
- writeFile :: FilePath -> String -> IO ()
- readFile :: FilePath -> IO String
- interact :: (String -> String) -> IO ()
- getContents :: IO String
- getLine :: IO String
- getChar :: IO Char
- putStrLn :: String -> IO ()
- putStr :: String -> IO ()
- putChar :: Char -> IO ()
- ioError :: IOError -> IO a
- type FilePath = String
- userError :: String -> IOError
- type IOError = IOException
- notElem :: (Foldable t, Eq a) => a -> t a -> Bool
- all :: Foldable t => (a -> Bool) -> t a -> Bool
- any :: Foldable t => (a -> Bool) -> t a -> Bool
- or :: Foldable t => t Bool -> Bool
- and :: Foldable t => t Bool -> Bool
- concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
- concat :: Foldable t => t [a] -> [a]
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- unwords :: [String] -> String
- words :: String -> [String]
- unlines :: [String] -> String
- lines :: String -> [String]
- read :: Read a => String -> a
- reads :: Read a => ReadS a
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- lex :: ReadS String
- readParen :: Bool -> ReadS a -> ReadS a
- type ReadS a = String -> [(a, String)]
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- lcm :: Integral a => a -> a -> a
- gcd :: Integral a => a -> a -> a
- (^^) :: (Fractional a, Integral b) => a -> b -> a
- odd :: Integral a => a -> Bool
- even :: Integral a => a -> Bool
- showParen :: Bool -> ShowS -> ShowS
- showString :: String -> ShowS
- showChar :: Char -> ShowS
- shows :: Show a => a -> ShowS
- type ShowS = String -> String
- unzip3 :: [(a, b, c)] -> ([a], [b], [c])
- unzip :: [(a, b)] -> ([a], [b])
- zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
- zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
- (!!) :: [a] -> Int -> a
- lookup :: Eq a => a -> [(a, b)] -> Maybe b
- reverse :: [a] -> [a]
- break :: (a -> Bool) -> [a] -> ([a], [a])
- span :: (a -> Bool) -> [a] -> ([a], [a])
- splitAt :: Int -> [a] -> ([a], [a])
- drop :: Int -> [a] -> [a]
- take :: Int -> [a] -> [a]
- dropWhile :: (a -> Bool) -> [a] -> [a]
- takeWhile :: (a -> Bool) -> [a] -> [a]
- cycle :: [a] -> [a]
- replicate :: Int -> a -> [a]
- repeat :: a -> [a]
- iterate :: (a -> a) -> a -> [a]
- scanr1 :: (a -> a -> a) -> [a] -> [a]
- scanr :: (a -> b -> b) -> b -> [a] -> [b]
- scanl1 :: (a -> a -> a) -> [a] -> [a]
- scanl :: (b -> a -> b) -> b -> [a] -> [b]
- init :: [a] -> [a]
- last :: [a] -> a
- tail :: [a] -> [a]
- head :: [a] -> a
- maybe :: b -> (a -> b) -> Maybe a -> b
- uncurry :: (a -> b -> c) -> (a, b) -> c
- curry :: ((a, b) -> c) -> a -> b -> c
- subtract :: Num a => a -> a -> a
- asTypeOf :: a -> a -> a
- until :: (a -> Bool) -> (a -> a) -> a -> a
- ($!) :: (a -> b) -> a -> b
- flip :: (a -> b -> c) -> b -> a -> c
- const :: a -> b -> a
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- type String = [Char]
- undefined :: HasCallStack => a
- errorWithoutStackTrace :: [Char] -> a
- error :: HasCallStack => [Char] -> a
- (&&) :: Bool -> Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- not :: Bool -> Bool
Documentation
class HasDynamicDimension a => HasDimension a where Source #
Dimensional values inhabit this class, which allows access to a term-level representation of their dimension.
Methods
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 Methods dimension :: Dimension' -> Dimension' Source # | |
HasDimension AnyUnit Source # | |
Defined in Numeric.Units.Dimensional.Dynamic Methods dimension :: AnyUnit -> Dimension' Source # | |
HasDimension (AnyQuantity a) Source # | |
Defined in Numeric.Units.Dimensional.Dynamic Methods 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 Methods dimension :: Dimensional v d a -> Dimension' Source # |
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
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 family NRoot (d :: Dimension) (x :: TypeInt) where ... Source #
Roots of dimensions corresponds to division of the base dimensions' exponents by the order of the root.
type family (d :: Dimension) ^ (x :: TypeInt) where ... infixr 8 Source #
Powers of dimensions corresponds 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 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.
type family (a :: Dimension) / (d :: Dimension) where ... infixl 7 Source #
Division of dimensions corresponds to subtraction of the base dimensions' exponents.
type family (a :: Dimension) * (b :: Dimension) where ... infixl 7 Source #
Multiplication of dimensions corresponds to adding of the base dimensions' exponents.
type DOne = Dim Zero Zero Zero Zero Zero Zero Zero Source #
The type-level dimension of dimensionless values.
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 Methods dynamicDimension :: Proxy (Dim l m t i th n j) -> DynamicDimension Source # |
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.
Constructors
Metric | Capable of receiving a metric prefix. |
NonMetric | Incapable of receiving a metric prefix. |
Instances
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.
Minimal complete definition
extractValue, extractName, injectValue, dmap
Associated Types
Instances
KnownVariant (DQuantity s) Source # | |
Defined in Numeric.Units.Dimensional.Internal Associated Types data Dimensional (DQuantity s) a b :: Type Source # Methods extractValue :: Dimensional (DQuantity s) d a -> (a, Maybe ExactPi) extractName :: Dimensional (DQuantity s) d a -> Maybe (UnitName NonMetric) injectValue :: Maybe (UnitName NonMetric) -> (a, Maybe ExactPi) -> Dimensional (DQuantity s) d a dmap :: (a1 -> a2) -> Dimensional (DQuantity s) d a1 -> Dimensional (DQuantity s) d a2 Source # | |
Typeable m => KnownVariant (DUnit m) Source # | |
Defined in Numeric.Units.Dimensional.Internal Associated Types data Dimensional (DUnit m) a b :: Type Source # Methods extractValue :: Dimensional (DUnit m) d a -> (a, Maybe ExactPi) extractName :: Dimensional (DUnit m) d a -> Maybe (UnitName NonMetric) injectValue :: Maybe (UnitName NonMetric) -> (a, Maybe ExactPi) -> Dimensional (DUnit m) d a dmap :: (a1 -> a2) -> Dimensional (DUnit m) d a1 -> Dimensional (DUnit m) d a2 Source # |
type Unit (m :: Metricality) = Dimensional (DUnit m) Source #
A unit of measurement.
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.
type Dimensionless = Quantity DOne Source #
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
.
(*~) :: Num a => a -> Unit m d a -> Quantity d a infixl 7 Source #
Forms a Quantity
by multipliying a number and a unit.
(*) :: (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 #
(/) :: (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
(^) :: (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 NotPrefixable
.
(-) :: Num a => Quantity d a -> Quantity d a -> Quantity d a infixl 6 Source #
Subtracts one Quantity
from another.
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 ^/
.
(^/) :: (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
.
(*~~) :: (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.
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
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
Arguments
:: (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]
exp :: Floating a => Dimensionless a -> Dimensionless a Source #
log :: Floating a => Dimensionless a -> Dimensionless a Source #
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 #
(**) :: 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
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
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 "boxing" of dimensionless values.
_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 #
pi :: Floating a => Dimensionless a Source #
tau :: Floating a => Dimensionless a Source #
Twice pi
.
For background on tau
see http://tauday.com/tau-manifesto (but also
feel free to review http://www.thepimanifesto.com).
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 #
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.
class Category (cat :: k -> k -> Type) where #
A class for categories. Instances should satisfy the laws
f.
id
= f -- (right identity)id
.
f = f -- (left identity) f.
(g.
h) = (f.
g).
h -- (associativity)
(++) :: [a] -> [a] -> [a] infixr 5 #
Append two lists, i.e.,
[x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn] [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...]
If the first list is not finite, the result is the first list.
The value of seq a b
is bottom if a
is bottom, and
otherwise equal to b
. In other words, it evaluates the first
argument a
to weak head normal form (WHNF). seq
is usually
introduced to improve performance by avoiding unneeded laziness.
A note on evaluation order: the expression seq a b
does
not guarantee that a
will be evaluated before b
.
The only guarantee given by seq
is that the both a
and b
will be evaluated before seq
returns a value.
In particular, this means that b
may be evaluated before
a
. If you need to guarantee a specific order of evaluation,
you must use the function pseq
from the "parallel" package.
filter :: (a -> Bool) -> [a] -> [a] #
filter
, applied to a predicate and a list, returns the list of
those elements that satisfy the predicate; i.e.,
filter p xs = [ x | x <- xs, p x]
print :: Show a => a -> IO () #
The print
function outputs a value of any printable type to the
standard output device.
Printable types are those that are instances of class Show
; print
converts values to strings for output using the show
operation and
adds a newline.
For example, a program to print the first 20 integers and their powers of 2 could be written as:
main = print ([(n, 2^n) | n <- [0..19]])
map :: (a -> b) -> [a] -> [b] #
map
f xs
is the list obtained by applying f
to each element
of xs
, i.e.,
map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn] map f [x1, x2, ...] == [f x1, f x2, ...]
($) :: (a -> b) -> a -> b infixr 0 #
Application operator. This operator is redundant, since ordinary
application (f x)
means the same as (f
. However, $
x)$
has
low, right-associative binding precedence, so it sometimes allows
parentheses to be omitted; for example:
f $ g $ h x = f (g (h x))
It is also useful in higher-order situations, such as
,
or map
($
0) xs
.zipWith
($
) fs xs
Note that ($)
is levity-polymorphic in its result type, so that
foo $ True where foo :: Bool -> Int#
is well-typed
fromIntegral :: (Integral a, Num b) => a -> b #
general coercion from integral types
realToFrac :: (Real a, Fractional b) => a -> b #
general coercion to fractional types
The Bounded
class is used to name the upper and lower limits of a
type. Ord
is not a superclass of Bounded
since types that are not
totally ordered may also have upper and lower bounds.
The Bounded
class may be derived for any enumeration type;
minBound
is the first constructor listed in the data
declaration
and maxBound
is the last.
Bounded
may also be derived for single-constructor datatypes whose
constituent types are in Bounded
.
Instances
Bounded Bool | Since: base-2.1 |
Bounded Char | Since: base-2.1 |
Bounded Int | Since: base-2.1 |
Bounded Int8 | Since: base-2.1 |
Bounded Int16 | Since: base-2.1 |
Bounded Int32 | Since: base-2.1 |
Bounded Int64 | Since: base-2.1 |
Bounded Ordering | Since: base-2.1 |
Bounded Word | Since: base-2.1 |
Bounded Word8 | Since: base-2.1 |
Bounded Word16 | Since: base-2.1 |
Bounded Word32 | Since: base-2.1 |
Bounded Word64 | Since: base-2.1 |
Bounded VecCount | Since: base-4.10.0.0 |
Bounded VecElem | Since: base-4.10.0.0 |
Bounded () | Since: base-2.1 |
Bounded All | Since: base-2.1 |
Bounded Any | Since: base-2.1 |
Bounded Associativity | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Bounded SourceUnpackedness | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Bounded SourceStrictness | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Bounded DecidedStrictness | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Bounded CChar | |
Bounded CSChar | |
Bounded CUChar | |
Bounded CShort | |
Bounded CUShort | |
Bounded CInt | |
Bounded CUInt | |
Bounded CLong | |
Bounded CULong | |
Bounded CLLong | |
Bounded CULLong | |
Bounded CBool | |
Bounded CPtrdiff | |
Bounded CSize | |
Bounded CWchar | |
Bounded CSigAtomic | |
Defined in Foreign.C.Types | |
Bounded CIntPtr | |
Bounded CUIntPtr | |
Bounded CIntMax | |
Bounded CUIntMax | |
Bounded WordPtr | |
Bounded IntPtr | |
Bounded a => Bounded (Min a) | Since: base-4.9.0.0 |
Bounded a => Bounded (Max a) | Since: base-4.9.0.0 |
Bounded a => Bounded (First a) | Since: base-4.9.0.0 |
Bounded a => Bounded (Last a) | Since: base-4.9.0.0 |
Bounded m => Bounded (WrappedMonoid m) | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
Bounded a => Bounded (Identity a) | Since: base-4.9.0.0 |
Bounded a => Bounded (Dual a) | Since: base-2.1 |
Bounded a => Bounded (Sum a) | Since: base-2.1 |
Bounded a => Bounded (Product a) | Since: base-2.1 |
(Bounded a, Bounded b) => Bounded (a, b) | Since: base-2.1 |
Bounded (Proxy t) | Since: base-4.7.0.0 |
(Bounded a, Bounded b, Bounded c) => Bounded (a, b, c) | Since: base-2.1 |
Bounded a => Bounded (Const a b) | Since: base-4.9.0.0 |
(Applicative f, Bounded a) => Bounded (Ap f a) | Since: base-4.12.0.0 |
Coercible a b => Bounded (Coercion a b) | Since: base-4.7.0.0 |
a ~ b => Bounded (a :~: b) | Since: base-4.7.0.0 |
Bounded a => Bounded (SQuantity s d a) Source # | |
(Bounded a, Bounded b, Bounded c, Bounded d) => Bounded (a, b, c, d) | Since: base-2.1 |
a ~~ b => Bounded (a :~~: b) | Since: base-4.10.0.0 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e) => Bounded (a, b, c, d, e) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f) => Bounded (a, b, c, d, e, f) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g) => Bounded (a, b, c, d, e, f, g) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h) => Bounded (a, b, c, d, e, f, g, h) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i) => Bounded (a, b, c, d, e, f, g, h, i) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j) => Bounded (a, b, c, d, e, f, g, h, i, j) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k) => Bounded (a, b, c, d, e, f, g, h, i, j, k) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m, Bounded n) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m, Bounded n, Bounded o) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | Since: base-2.1 |
Class Enum
defines operations on sequentially ordered types.
The enumFrom
... methods are used in Haskell's translation of
arithmetic sequences.
Instances of Enum
may be derived for any enumeration type (types
whose constructors have no fields). The nullary constructors are
assumed to be numbered left-to-right by fromEnum
from 0
through n-1
.
See Chapter 10 of the Haskell Report for more details.
For any type that is an instance of class Bounded
as well as Enum
,
the following should hold:
- The calls
andsucc
maxBound
should result in a runtime error.pred
minBound
fromEnum
andtoEnum
should give a runtime error if the result value is not representable in the result type. For example,
is an error.toEnum
7 ::Bool
enumFrom
andenumFromThen
should be defined with an implicit bound, thus:
enumFrom x = enumFromTo x maxBound enumFromThen x y = enumFromThenTo x y bound where bound | fromEnum y >= fromEnum x = maxBound | otherwise = minBound
Methods
the successor of a value. For numeric types, succ
adds 1.
the predecessor of a value. For numeric types, pred
subtracts 1.
Convert from an Int
.
Convert to an Int
.
It is implementation-dependent what fromEnum
returns when
applied to a value that is too large to fit in an Int
.
Used in Haskell's translation of [n..]
with [n..] = enumFrom n
,
a possible implementation being enumFrom n = n : enumFrom (succ n)
.
For example:
enumFrom 4 :: [Integer] = [4,5,6,7,...]
enumFrom 6 :: [Int] = [6,7,8,9,...,maxBound :: Int]
enumFromThen :: a -> a -> [a] #
Used in Haskell's translation of [n,n'..]
with [n,n'..] = enumFromThen n n'
, a possible implementation being
enumFromThen n n' = n : n' : worker (f x) (f x n')
,
worker s v = v : worker s (s v)
, x = fromEnum n' - fromEnum n
and
f n y
| n > 0 = f (n - 1) (succ y)
| n < 0 = f (n + 1) (pred y)
| otherwise = y
For example:
enumFromThen 4 6 :: [Integer] = [4,6,8,10...]
enumFromThen 6 2 :: [Int] = [6,2,-2,-6,...,minBound :: Int]
enumFromTo :: a -> a -> [a] #
Used in Haskell's translation of [n..m]
with
[n..m] = enumFromTo n m
, a possible implementation being
enumFromTo n m
| n <= m = n : enumFromTo (succ n) m
| otherwise = []
.
For example:
enumFromTo 6 10 :: [Int] = [6,7,8,9,10]
enumFromTo 42 1 :: [Integer] = []
enumFromThenTo :: a -> a -> a -> [a] #
Used in Haskell's translation of [n,n'..m]
with
[n,n'..m] = enumFromThenTo n n' m
, a possible implementation
being enumFromThenTo n n' m = worker (f x) (c x) n m
,
x = fromEnum n' - fromEnum n
, c x = bool (>=) ((x 0)
f n y
| n > 0 = f (n - 1) (succ y)
| n < 0 = f (n + 1) (pred y)
| otherwise = y
and
worker s c v m
| c v m = v : worker s c (s v) m
| otherwise = []
For example:
enumFromThenTo 4 2 -6 :: [Integer] = [4,2,0,-2,-4,-6]
enumFromThenTo 6 8 2 :: [Int] = []
Instances
The Eq
class defines equality (==
) and inequality (/=
).
All the basic datatypes exported by the Prelude are instances of Eq
,
and Eq
may be derived for any datatype whose constituents are also
instances of Eq
.
The Haskell Report defines no laws for Eq
. However, ==
is customarily
expected to implement an equivalence relationship where two values comparing
equal are indistinguishable by "public" functions, with a "public" function
being one not allowing to see implementation details. For example, for a
type representing non-normalised natural numbers modulo 100, a "public"
function doesn't make the difference between 1 and 201. It is expected to
have the following properties:
Instances
Eq Bool | |
Eq Char | |
Eq Double | Note that due to the presence of
Also note that
|
Eq Float | Note that due to the presence of
Also note that
|
Eq Int | |
Eq Int8 | Since: base-2.1 |
Eq Int16 | Since: base-2.1 |
Eq Int32 | Since: base-2.1 |
Eq Int64 | Since: base-2.1 |
Eq Integer | |
Eq Natural | Since: base-4.8.0.0 |
Eq Ordering | |
Eq Word | |
Eq Word8 | Since: base-2.1 |
Eq Word16 | Since: base-2.1 |
Eq Word32 | Since: base-2.1 |
Eq Word64 | Since: base-2.1 |
Eq SomeTypeRep | |
Defined in Data.Typeable.Internal | |
Eq () | |
Eq TyCon | |
Eq Module | |
Eq TrName | |
Eq BigNat | |
Eq Void | Since: base-4.8.0.0 |
Eq SpecConstrAnnotation | Since: base-4.3.0.0 |
Defined in GHC.Exts Methods (==) :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool # (/=) :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool # | |
Eq Constr | Equality of constructors Since: base-4.0.0.0 |
Eq DataRep | Since: base-4.0.0.0 |
Eq ConstrRep | Since: base-4.0.0.0 |
Eq Fixity | Since: base-4.0.0.0 |
Eq Unique | |
Eq Version | Since: base-2.1 |
Eq ThreadId | Since: base-4.2.0.0 |
Eq BlockReason | Since: base-4.3.0.0 |
Defined in GHC.Conc.Sync | |
Eq ThreadStatus | Since: base-4.3.0.0 |
Defined in GHC.Conc.Sync | |
Eq AsyncException | Since: base-4.2.0.0 |
Defined in GHC.IO.Exception Methods (==) :: AsyncException -> AsyncException -> Bool # (/=) :: AsyncException -> AsyncException -> Bool # | |
Eq ArrayException | Since: base-4.2.0.0 |
Defined in GHC.IO.Exception Methods (==) :: ArrayException -> ArrayException -> Bool # (/=) :: ArrayException -> ArrayException -> Bool # | |
Eq ExitCode | |
Eq IOErrorType | Since: base-4.1.0.0 |
Defined in GHC.IO.Exception | |
Eq MaskingState | Since: base-4.3.0.0 |
Defined in GHC.IO | |
Eq IOException | Since: base-4.1.0.0 |
Defined in GHC.IO.Exception | |
Eq All | Since: base-2.1 |
Eq Any | Since: base-2.1 |
Eq Fixity | Since: base-4.6.0.0 |
Eq Associativity | Since: base-4.6.0.0 |
Defined in GHC.Generics Methods (==) :: Associativity -> Associativity -> Bool # (/=) :: Associativity -> Associativity -> Bool # | |
Eq SourceUnpackedness | Since: base-4.9.0.0 |
Defined in GHC.Generics Methods (==) :: SourceUnpackedness -> SourceUnpackedness -> Bool # (/=) :: SourceUnpackedness -> SourceUnpackedness -> Bool # | |
Eq SourceStrictness | Since: base-4.9.0.0 |
Defined in GHC.Generics Methods (==) :: SourceStrictness -> SourceStrictness -> Bool # (/=) :: SourceStrictness -> SourceStrictness -> Bool # | |
Eq DecidedStrictness | Since: base-4.9.0.0 |
Defined in GHC.Generics Methods (==) :: DecidedStrictness -> DecidedStrictness -> Bool # (/=) :: DecidedStrictness -> DecidedStrictness -> Bool # | |
Eq SomeSymbol | Since: base-4.7.0.0 |
Defined in GHC.TypeLits | |
Eq SomeNat | Since: base-4.7.0.0 |
Eq CChar | |
Eq CSChar | |
Eq CUChar | |
Eq CShort | |
Eq CUShort | |
Eq CInt | |
Eq CUInt | |
Eq CLong | |
Eq CULong | |
Eq CLLong | |
Eq CULLong | |
Eq CBool | |
Eq CFloat | |
Eq CDouble | |
Eq CPtrdiff | |
Eq CSize | |
Eq CWchar | |
Eq CSigAtomic | |
Defined in Foreign.C.Types | |
Eq CClock | |
Eq CTime | |
Eq CUSeconds | |
Eq CSUSeconds | |
Defined in Foreign.C.Types | |
Eq CIntPtr | |
Eq CUIntPtr | |
Eq CIntMax | |
Eq CUIntMax | |
Eq WordPtr | |
Eq IntPtr | |
Eq Fingerprint | Since: base-4.4.0.0 |
Defined in GHC.Fingerprint.Type | |
Eq SrcLoc | Since: base-4.9.0.0 |
Eq ByteArray | Since: primitive-0.6.3.0 |
Eq Addr | |
Eq DynamicDimension Source # | |
Defined in Numeric.Units.Dimensional.Dimensions.TermLevel Methods (==) :: DynamicDimension -> DynamicDimension -> Bool # (/=) :: DynamicDimension -> DynamicDimension -> Bool # | |
Eq Dimension' Source # | |
Eq InterchangeName Source # | |
Defined in Numeric.Units.Dimensional.UnitNames.InterchangeNames Methods (==) :: InterchangeName -> InterchangeName -> Bool # (/=) :: InterchangeName -> InterchangeName -> Bool # | |
Eq InterchangeNameAuthority Source # | |
Defined in Numeric.Units.Dimensional.UnitNames.InterchangeNames Methods (==) :: InterchangeNameAuthority -> InterchangeNameAuthority -> Bool # (/=) :: InterchangeNameAuthority -> InterchangeNameAuthority -> Bool # | |
Eq Metricality Source # | |
Defined in Numeric.Units.Dimensional.Variants | |
Eq Prefix Source # | |
Eq a => Eq [a] | |
Eq a => Eq (Maybe a) | Since: base-2.1 |
Eq a => Eq (Ratio a) | Since: base-2.1 |
Eq (StablePtr a) | Since: base-2.1 |
Eq (Ptr a) | Since: base-2.1 |
Eq (FunPtr a) | |
Eq p => Eq (Par1 p) | Since: base-4.7.0.0 |
Eq (ForeignPtr a) | Since: base-2.1 |
Defined in GHC.ForeignPtr | |
Eq a => Eq (Complex a) | Since: base-2.1 |
Eq (Fixed a) | Since: base-2.1 |
Eq a => Eq (Min a) | Since: base-4.9.0.0 |
Eq a => Eq (Max a) | Since: base-4.9.0.0 |
Eq a => Eq (First a) | Since: base-4.9.0.0 |
Eq a => Eq (Last a) | Since: base-4.9.0.0 |
Eq m => Eq (WrappedMonoid m) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods (==) :: WrappedMonoid m -> WrappedMonoid m -> Bool # (/=) :: WrappedMonoid m -> WrappedMonoid m -> Bool # | |
Eq a => Eq (Option a) | Since: base-4.9.0.0 |
Eq (StableName a) | Since: base-2.1 |
Defined in GHC.StableName | |
Eq a => Eq (ZipList a) | Since: base-4.7.0.0 |
Eq a => Eq (Identity a) | Since: base-4.8.0.0 |
Eq (TVar a) | Since: base-4.8.0.0 |
Eq (IORef a) | ^ Pointer equality. Since: base-4.1.0.0 |
Eq a => Eq (First a) | Since: base-2.1 |
Eq a => Eq (Last a) | Since: base-2.1 |
Eq a => Eq (Dual a) | Since: base-2.1 |
Eq a => Eq (Sum a) | Since: base-2.1 |
Eq a => Eq (Product a) | Since: base-2.1 |
Eq a => Eq (Down a) | Since: base-4.6.0.0 |
Eq (MVar a) | Since: base-4.1.0.0 |
Eq a => Eq (NonEmpty a) | Since: base-4.9.0.0 |
(Eq a, PrimUnlifted a) => Eq (UnliftedArray a) | |
Defined in Data.Primitive.UnliftedArray Methods (==) :: UnliftedArray a -> UnliftedArray a -> Bool # (/=) :: UnliftedArray a -> UnliftedArray a -> Bool # | |
(Eq a, Prim a) => Eq (PrimArray a) | Since: primitive-0.6.4.0 |
Eq a => Eq (SmallArray a) | |
Defined in Data.Primitive.SmallArray | |
Eq a => Eq (Array a) | |
(Prim a, Eq a) => Eq (Vector a) | |
Eq (NameAtom m) Source # | |
Eq (UnitName m) Source # | |
Eq a => Eq (DynQuantity a) Source # | |
Defined in Numeric.Units.Dimensional.Dynamic Methods (==) :: DynQuantity a -> DynQuantity a -> Bool # (/=) :: DynQuantity a -> DynQuantity a -> Bool # | |
Eq a => Eq (AnyQuantity a) Source # | |
Defined in Numeric.Units.Dimensional.Dynamic Methods (==) :: AnyQuantity a -> AnyQuantity a -> Bool # (/=) :: AnyQuantity a -> AnyQuantity a -> Bool # | |
(Eq a, Eq b) => Eq (Either a b) | Since: base-2.1 |
Eq (V1 p) | Since: base-4.9.0.0 |
Eq (U1 p) | Since: base-4.9.0.0 |
Eq (TypeRep a) | Since: base-2.1 |
(Eq a, Eq b) => Eq (a, b) | |
(Ix i, Eq e) => Eq (Array i e) | Since: base-2.1 |
Eq a => Eq (Arg a b) | Since: base-4.9.0.0 |
Eq (Proxy s) | Since: base-4.7.0.0 |
Eq (STRef s a) | Pointer equality. Since: base-2.1 |
Eq (MutableUnliftedArray s a) | |
Defined in Data.Primitive.UnliftedArray Methods (==) :: MutableUnliftedArray s a -> MutableUnliftedArray s a -> Bool # (/=) :: MutableUnliftedArray s a -> MutableUnliftedArray s a -> Bool # | |
Eq (SmallMutableArray s a) | |
Defined in Data.Primitive.SmallArray Methods (==) :: SmallMutableArray s a -> SmallMutableArray s a -> Bool # (/=) :: SmallMutableArray s a -> SmallMutableArray s a -> Bool # | |
Eq (MutableArray s a) | |
Defined in Data.Primitive.Array Methods (==) :: MutableArray s a -> MutableArray s a -> Bool # (/=) :: MutableArray s a -> MutableArray s a -> Bool # | |
(Eq1 m, Eq a) => Eq (MaybeT m a) | |
(Eq1 m, Eq a) => Eq (ListT m a) | |
Eq (f p) => Eq (Rec1 f p) | Since: base-4.7.0.0 |
Eq (URec (Ptr ()) p) | Since: base-4.9.0.0 |
Eq (URec Char p) | Since: base-4.9.0.0 |
Eq (URec Double p) | Since: base-4.9.0.0 |
Eq (URec Float p) | |
Eq (URec Int p) | Since: base-4.9.0.0 |
Eq (URec Word p) | Since: base-4.9.0.0 |
(Eq a, Eq b, Eq c) => Eq (a, b, c) | |
Eq (STArray s i e) | Since: base-2.1 |
Eq a => Eq (Const a b) | Since: base-4.9.0.0 |
Eq (f a) => Eq (Ap f a) | Since: base-4.12.0.0 |
Eq (f a) => Eq (Alt f a) | Since: base-4.8.0.0 |
Eq (Coercion a b) | Since: base-4.7.0.0 |
Eq (a :~: b) | Since: base-4.7.0.0 |
(Eq w, Eq1 m, Eq a) => Eq (WriterT w m a) | |
(Eq w, Eq1 m, Eq a) => Eq (WriterT w m a) | |
(Eq1 f, Eq a) => Eq (IdentityT f a) | |
(Eq e, Eq1 m, Eq a) => Eq (ExceptT e m a) | |
(Eq e, Eq1 m, Eq a) => Eq (ErrorT e m a) | |
Eq a => Eq (Dimensional (DQuantity s) d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal Methods (==) :: Dimensional (DQuantity s) d a -> Dimensional (DQuantity s) d a -> Bool # (/=) :: Dimensional (DQuantity s) d a -> Dimensional (DQuantity s) d a -> Bool # | |
Eq c => Eq (K1 i c p) | Since: base-4.7.0.0 |
(Eq (f p), Eq (g p)) => Eq ((f :+: g) p) | Since: base-4.7.0.0 |
(Eq (f p), Eq (g p)) => Eq ((f :*: g) p) | Since: base-4.7.0.0 |
(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) | |
(Eq1 f, Eq1 g, Eq a) => Eq (Product f g a) | Since: base-4.9.0.0 |
(Eq1 f, Eq1 g, Eq a) => Eq (Sum f g a) | Since: base-4.9.0.0 |
Eq (a :~~: b) | Since: base-4.10.0.0 |
Eq (f p) => Eq (M1 i c f p) | Since: base-4.7.0.0 |
Eq (f (g p)) => Eq ((f :.: g) p) | Since: base-4.7.0.0 |
(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) | |
(Eq1 f, Eq1 g, Eq a) => Eq (Compose f g a) | Since: base-4.9.0.0 |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (a, b, c, d, e, f, g, h) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (a, b, c, d, e, f, g, h, i) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (a, b, c, d, e, f, g, h, i, j) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k) => Eq (a, b, c, d, e, f, g, h, i, j, k) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l) => Eq (a, b, c, d, e, f, g, h, i, j, k, l) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |
class Fractional a => Floating a #
Trigonometric and hyperbolic functions and related functions.
The Haskell Report defines no laws for Floating
. However, '(+)', '(*)'
and exp
are customarily expected to define an exponential field and have
the following properties:
exp (a + b)
= @exp a * exp bexp (fromInteger 0)
=fromInteger 1
Minimal complete definition
pi, exp, log, sin, cos, asin, acos, atan, sinh, cosh, asinh, acosh, atanh
Instances
class Num a => Fractional a where #
Fractional numbers, supporting real division.
The Haskell Report defines no laws for Fractional
. However, '(+)' and
'(*)' are customarily expected to define a division ring and have the
following properties:
recip
gives the multiplicative inversex * recip x
=recip x * x
=fromInteger 1
Note that it isn't customarily expected that a type instance of
Fractional
implement a field. However, all instances in base
do.
Methods
fromRational :: Rational -> a #
Conversion from a Rational
(that is
).
A floating literal stands for an application of Ratio
Integer
fromRational
to a value of type Rational
, so such literals have type
(
.Fractional
a) => a
Instances
Fractional CFloat | |
Fractional CDouble | |
Fractional ExactPi | |
Defined in Data.ExactPi |