dimensional-1.1: Statically checked physical dimensions, using Type Families and Data Kinds.

CopyrightCopyright (C) 2006-2018 Bjorn Buckwalter
LicenseBSD3
Maintainerbjorn@buckwalter.se
StabilityStable
PortabilityGHC only
Safe HaskellSafe
LanguageHaskell2010
Extensions
  • BangPatterns
  • DeriveDataTypeable
  • DeriveGeneric
  • DefaultSignatures

Numeric.Units.Dimensional.Dimensions.TermLevel

Contents

Description

This module defines physical dimensions expressed in terms of the SI base dimensions, including arithmetic.

Synopsis

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.

Constructors

Dim' !Int !Int !Int !Int !Int !Int !Int 

Instances

Eq Dimension' Source # 
Data Dimension' Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dimension' -> c Dimension' #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dimension' #

toConstr :: Dimension' -> Constr #

dataTypeOf :: Dimension' -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Dimension') #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dimension') #

gmapT :: (forall b. Data b => b -> b) -> Dimension' -> Dimension' #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dimension' -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dimension' -> r #

gmapQ :: (forall d. Data d => d -> u) -> Dimension' -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dimension' -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dimension' -> m Dimension' #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dimension' -> m Dimension' #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dimension' -> m Dimension' #

Ord Dimension' Source # 
Show Dimension' Source # 
Generic Dimension' Source # 

Associated Types

type Rep Dimension' :: * -> * #

Semigroup Dimension' Source # 
Monoid Dimension' Source #

The monoid of dimensions under multiplication.

NFData Dimension' Source # 

Methods

rnf :: Dimension' -> () #

HasDimension Dimension' Source # 
HasDynamicDimension Dimension' Source # 
type Rep Dimension' Source # 

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.

Minimal complete definition

dimension

Methods

dimension :: a -> Dimension' Source #

Obtains a term-level representation of a value's dimension.

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.

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.

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

Eq DynamicDimension Source # 
Data DynamicDimension Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DynamicDimension -> c DynamicDimension #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DynamicDimension #

toConstr :: DynamicDimension -> Constr #

dataTypeOf :: DynamicDimension -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DynamicDimension) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DynamicDimension) #

gmapT :: (forall b. Data b => b -> b) -> DynamicDimension -> DynamicDimension #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DynamicDimension -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DynamicDimension -> r #

gmapQ :: (forall d. Data d => d -> u) -> DynamicDimension -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DynamicDimension -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DynamicDimension -> m DynamicDimension #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DynamicDimension -> m DynamicDimension #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DynamicDimension -> m DynamicDimension #

Ord DynamicDimension Source # 
Show DynamicDimension Source # 
Generic DynamicDimension Source # 
NFData DynamicDimension Source # 

Methods

rnf :: DynamicDimension -> () #

HasDynamicDimension DynamicDimension Source # 
type Rep DynamicDimension Source # 
type Rep DynamicDimension = D1 * (MetaData "DynamicDimension" "Numeric.Units.Dimensional.Dimensions.TermLevel" "dimensional-1.1-FrwO52z7cgM7jRCbk3nsMF" False) ((:+:) * (C1 * (MetaCons "NoDimension" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SomeDimension" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Dimension'))) (C1 * (MetaCons "AnyDimension" PrefixI False) (U1 *))))

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.

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.