| Copyright | Copyright (C) 2006-2018 Bjorn Buckwalter | 
|---|---|
| License | BSD3 | 
| Maintainer | bjorn@buckwalter.se | 
| Stability | Stable | 
| Portability | GHC only | 
| Safe Haskell | Safe | 
| Language | Haskell2010 | 
| Extensions | 
  | 
Numeric.Units.Dimensional.Dimensions.TermLevel
Contents
Description
This module defines physical dimensions expressed in terms of the SI base dimensions, including arithmetic.
Synopsis
- data Dimension' = Dim' !Int !Int !Int !Int !Int !Int !Int
 - class HasDynamicDimension a => HasDimension a where
- dimension :: a -> Dimension'
 
 - class HasDynamicDimension a where
- dynamicDimension :: a -> DynamicDimension
 
 - data DynamicDimension
 - (*) :: Dimension' -> Dimension' -> Dimension'
 - (/) :: Dimension' -> Dimension' -> Dimension'
 - (^) :: Dimension' -> Int -> Dimension'
 - recip :: Dimension' -> Dimension'
 - nroot :: Int -> Dimension' -> Maybe Dimension'
 - sqrt :: Dimension' -> Maybe Dimension'
 - cbrt :: Dimension' -> Maybe Dimension'
 - dOne :: Dimension'
 - dLength :: Dimension'
 - dMass :: Dimension'
 - dTime :: Dimension'
 - dElectricCurrent :: Dimension'
 - dThermodynamicTemperature :: Dimension'
 - dAmountOfSubstance :: Dimension'
 - dLuminousIntensity :: Dimension'
 - asList :: Dimension' -> [Int]
 - matchDimensions :: DynamicDimension -> DynamicDimension -> DynamicDimension
 - isCompatibleWith :: HasDynamicDimension a => a -> Dimension' -> Bool
 - hasSomeDimension :: HasDynamicDimension a => a -> Bool
 
Type
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
Access to Dimension of Dimensional Values
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 #  | |
class HasDynamicDimension a where Source #
Dimensional values, or those that are only possibly dimensional, inhabit this class, which allows access to a term-level representation of their dimension.
Minimal complete definition
Nothing
Methods
dynamicDimension :: a -> DynamicDimension Source #
Gets the 'DynamicDimension of a dynamic dimensional value, which may be NoDimension if it does not represent
 a dimensional value of any Dimension.
A default implementation is available for types that are also in the HasDimension typeclass.
dynamicDimension :: HasDimension a => a -> DynamicDimension Source #
Gets the 'DynamicDimension of a dynamic dimensional value, which may be NoDimension if it does not represent
 a dimensional value of any Dimension.
A default implementation is available for types that are also in the HasDimension typeclass.
Instances
data DynamicDimension Source #
The dimension of a dynamic value, which may not have any dimension at all.
Constructors
| NoDimension | The value has no valid dimension.  | 
| SomeDimension Dimension' | The value has the given dimension.  | 
| AnyDimension | The value may be interpreted as having any dimension.  | 
Instances
Dimension Arithmetic
(*) :: Dimension' -> Dimension' -> Dimension' infixl 7 Source #
Forms the product of two dimensions.
(/) :: Dimension' -> Dimension' -> Dimension' infixl 7 Source #
Forms the quotient of two dimensions.
(^) :: Dimension' -> Int -> Dimension' infixr 8 Source #
Raises a dimension to an integer power.
recip :: Dimension' -> Dimension' Source #
Forms the reciprocal of a dimension.
nroot :: Int -> Dimension' -> Maybe Dimension' Source #
Takes the nth root of a dimension, if it exists.
n must not be zero.
nroot (negate n) d == nroot n (recip d)
sqrt :: Dimension' -> Maybe Dimension' Source #
Takes the square root of a dimension, if it exists.
sqrt d == nroot 2 d
cbrt :: Dimension' -> Maybe Dimension' Source #
Takes the cube root of a dimension, if it exists.
cbrt d == nroot 3 d
Synonyms for Base Dimensions
dOne :: Dimension' Source #
The dimension of dimensionless values.
dLength :: Dimension' Source #
dMass :: Dimension' Source #
dTime :: Dimension' Source #
Deconstruction
asList :: Dimension' -> [Int] Source #
Converts a dimension to a list of 7 integers, representing the exponent associated with each of the 7 SI base dimensions in the standard order.
Examining Dynamic Dimensions
matchDimensions :: DynamicDimension -> DynamicDimension -> DynamicDimension Source #
Combines two DynamicDimensions, determining the DynamicDimension of a quantity that must
 match both inputs.
This is the lattice meet operation for DynamicDimension.
isCompatibleWith :: HasDynamicDimension a => a -> Dimension' -> Bool Source #
Determines if a value that has a DynamicDimension is compatible with a specified Dimension'.
hasSomeDimension :: HasDynamicDimension a => a -> Bool Source #
Determines if a value that has a DynamicDimension in fact has any valid dimension at all.