cifl-math-library-1.1.1.0: Math libraries
Safe HaskellTrustworthy
LanguageHaskell2010

Math.Number.Units

Description

This module contains auxiliary definitions related to dimensional analysis. This is based on the SI system of units. This module supports compile-time checking for dimensional units. This is accomplished by a set of newtype wrappers of Double.

It is not necessarily a good idea to make the checking in compile-time. In particular, this can prevent operations to be available, e.g. Num class is not supported for compile-time checked quantities. Num because it has wrong type for the multiplication and division. Instead of Num, VectorSpace operations and operations defined in this module should be used.

However, these types can distinguish quantities even in cases where the dimensions match, e.g. radians and steradians. Explicit conversions are nonetheless available when dimensions match.

Read operations are pretty strict in that they require exactly the syntax "double unit", where unit is the result of unitOf (fromAmount 0 :: T). Example: (read "3 m^2" :: SquareLength) This can sometimes be unintuitive and is sensitive to the algorithm used to print units. For example: unitOf (fromAmount 0 :: Mass :/ Length) == "m^-1 kg". If in doubt, it's possible to use the read algorithm handling all units from DimensionalAnalysis module.

However, it's very much likely that compile-time checked newtypes are faster at run-time than using the run-time checked quantities. This is probably the primary reason for wanting this module instead of run-time checked version.

Also it's not possible to cast input data directly without run-time check to a compile-time checked quantity.

See "Barton&Nackman: Scientific and Engineering C++" for C++ approach to dimensional analysis.

https://en.wikipedia.org/wiki/International_System_of_Units

Synopsis

Documentation

type UnitName u = Scalar u -> u Source #

Notice that fromAmount from Unit class has type (Unit u) => UnitName u. However usually a concrete constructor of one of the newtypes is used as value.

(*%%) :: Scalar u ~ Scalar u' => UnitName u -> UnitName u' -> UnitName (u :* u') Source #

(/%%) :: Scalar u ~ Scalar u' => UnitName u -> UnitName u' -> UnitName (u :/ u') Source #

(*%) :: (LiteralUnit u, LiteralUnit w, Num (Scalar u), Scalar u ~ Scalar w) => u -> w -> u :* w Source #

heterogeneous product respecting units It may be necessary to use quantity operation to convert to run-time representation after using this, because the result type accumulates new parts with each use without considering what the total dimension of the result is. This can produce excessively complicated types, because the type represents the structure of the expression rather than structure of the result.

(/%) :: (Fractional (Scalar u), LiteralUnit u, LiteralUnit w, Scalar u ~ Scalar w) => u -> w -> u :/ w Source #

heterogeneous division respecting units. These simply accumulate type information about the units. It may be necessary to use quantity operation to convert to run-time representation after using this, because the result type accumulates new parts with each use without considering what the total dimension of the result is. This can produce excessively complicated types, because the type represents the structure of the expression rather than the structure of the result.

mapAmount :: LiteralUnit a => (Scalar a -> Scalar a) -> a -> a Source #

mapAmount2 :: LiteralUnit a => (Scalar a -> Scalar a -> Scalar a) -> a -> a -> a Source #

asUnit :: (MonadFail m, Show (Scalar u), Show u, LiteralUnit u, Fractional (Scalar u)) => Quantity (Scalar u) -> UnitName u -> m u Source #

Conversion from "Quantity a" to a unit-specific type. The second argument is the constructor for the newtype specific to the unit.

Example: (3 %* meter) asUnit Meters == return (Meters 3) 0.3 asUnit Radians == return (Radians 0.3)

If the dimensions don't match, this raises an exception.

quantity :: LiteralUnit u => u -> Quantity (Scalar u) Source #

Converts a compile-time checked dimensional unit to run-time checked version This often has the effect of reducing the complexity in types.

data a :/ b Source #

Instances

Instances details
Generic (a :/ b) Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep (a :/ b) :: Type -> Type #

Methods

from :: (a :/ b) -> Rep (a :/ b) x #

to :: Rep (a :/ b) x -> a :/ b #

(LiteralUnit a, LiteralUnit b, Read (Scalar a), Show (Scalar a), Scalar a ~ Scalar b) => Read (a :/ b) Source # 
Instance details

Defined in Math.Number.Units

Methods

readsPrec :: Int -> ReadS (a :/ b) #

readList :: ReadS [a :/ b] #

readPrec :: ReadPrec (a :/ b) #

readListPrec :: ReadPrec [a :/ b] #

(Scalar a ~ Scalar b, LiteralUnit a, LiteralUnit b, Show (Scalar a)) => Show (a :/ b) Source # 
Instance details

Defined in Math.Number.Units

Methods

showsPrec :: Int -> (a :/ b) -> ShowS #

show :: (a :/ b) -> String #

showList :: [a :/ b] -> ShowS #

(LiteralUnit a, LiteralUnit b, Scalar a ~ Scalar b) => VectorSpace (a :/ b) Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar (a :/ b) Source #

Methods

vzero :: a :/ b Source #

vnegate :: (a :/ b) -> a :/ b Source #

(%+) :: (a :/ b) -> (a :/ b) -> a :/ b Source #

(%*) :: Scalar (a :/ b) -> (a :/ b) -> a :/ b Source #

(Scalar a ~ Scalar b, Show (Scalar a), LiteralUnit a, LiteralUnit b) => LiteralUnit (a :/ b) Source # 
Instance details

Defined in Math.Number.Units

Methods

fromAmount :: Scalar (a :/ b) -> a :/ b Source #

zeroAmount :: (Scalar (a :/ b) -> a :/ b) -> Scalar (a :/ b) Source #

conversionFactor :: (Scalar (a :/ b) -> a :/ b) -> Scalar (a :/ b) Source #

(LiteralUnit a, LiteralUnit b, Show (Scalar a), Scalar a ~ Scalar b) => Unit (a :/ b) Source # 
Instance details

Defined in Math.Number.Units

Methods

amount :: (a :/ b) -> Scalar (a :/ b) Source #

fromQuantity :: (Alternative m, MonadFail m) => Quantity (Scalar (a :/ b)) -> m (a :/ b) Source #

unitOf :: (a :/ b) -> String Source #

dimension :: (a :/ b) -> Dimension Source #

type Rep (a :/ b) Source # 
Instance details

Defined in Math.Number.Units

type Rep (a :/ b) = D1 ('MetaData ":/" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'False) (C1 ('MetaCons "QDivide" 'PrefixI 'True) (S1 ('MetaSel ('Just "qdivide_amount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Scalar a)) :*: (S1 ('MetaSel ('Just "qdivide_dividend_unit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UnitName a)) :*: S1 ('MetaSel ('Just "qdivide_divisor_unit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UnitName b)))))
type Scalar (a :/ b) Source # 
Instance details

Defined in Math.Number.Units

type Scalar (a :/ b) = Scalar a

data a :* b Source #

Instances

Instances details
Generic (a :* b) Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep (a :* b) :: Type -> Type #

Methods

from :: (a :* b) -> Rep (a :* b) x #

to :: Rep (a :* b) x -> a :* b #

(LiteralUnit a, LiteralUnit b, Read (Scalar a), Show (Scalar a), Scalar a ~ Scalar b) => Read (a :* b) Source # 
Instance details

Defined in Math.Number.Units

Methods

readsPrec :: Int -> ReadS (a :* b) #

readList :: ReadS [a :* b] #

readPrec :: ReadPrec (a :* b) #

readListPrec :: ReadPrec [a :* b] #

(Scalar a ~ Scalar b, LiteralUnit a, LiteralUnit b, Show (Scalar a)) => Show (a :* b) Source # 
Instance details

Defined in Math.Number.Units

Methods

showsPrec :: Int -> (a :* b) -> ShowS #

show :: (a :* b) -> String #

showList :: [a :* b] -> ShowS #

(LiteralUnit a, LiteralUnit b, Scalar a ~ Scalar b) => VectorSpace (a :* b) Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar (a :* b) Source #

Methods

vzero :: a :* b Source #

vnegate :: (a :* b) -> a :* b Source #

(%+) :: (a :* b) -> (a :* b) -> a :* b Source #

(%*) :: Scalar (a :* b) -> (a :* b) -> a :* b Source #

(Scalar a ~ Scalar b, Show (Scalar a), LiteralUnit a, LiteralUnit b) => LiteralUnit (a :* b) Source # 
Instance details

Defined in Math.Number.Units

Methods

fromAmount :: Scalar (a :* b) -> a :* b Source #

zeroAmount :: (Scalar (a :* b) -> a :* b) -> Scalar (a :* b) Source #

conversionFactor :: (Scalar (a :* b) -> a :* b) -> Scalar (a :* b) Source #

(LiteralUnit a, LiteralUnit b, Show (Scalar a), Scalar a ~ Scalar b) => Unit (a :* b) Source # 
Instance details

Defined in Math.Number.Units

Methods

amount :: (a :* b) -> Scalar (a :* b) Source #

fromQuantity :: (Alternative m, MonadFail m) => Quantity (Scalar (a :* b)) -> m (a :* b) Source #

unitOf :: (a :* b) -> String Source #

dimension :: (a :* b) -> Dimension Source #

type Rep (a :* b) Source # 
Instance details

Defined in Math.Number.Units

type Rep (a :* b) = D1 ('MetaData ":*" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'False) (C1 ('MetaCons "QProduct" 'PrefixI 'True) (S1 ('MetaSel ('Just "qproduct_amount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Scalar a)) :*: (S1 ('MetaSel ('Just "qproduct_first_unit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UnitName a)) :*: S1 ('MetaSel ('Just "qproduct_second_unit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UnitName b)))))
type Scalar (a :* b) Source # 
Instance details

Defined in Math.Number.Units

type Scalar (a :* b) = Scalar a

newtype Dimensionless Source #

Constructors

Dimensionless 

Instances

Instances details
Data Dimensionless Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Dimensionless -> Constr #

dataTypeOf :: Dimensionless -> DataType #

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

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

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

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

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

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

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

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

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

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

Floating Dimensionless Source # 
Instance details

Defined in Math.Number.Units

RealFloat Dimensionless Source # 
Instance details

Defined in Math.Number.Units

Generic Dimensionless Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Dimensionless :: Type -> Type #

Num Dimensionless Source # 
Instance details

Defined in Math.Number.Units

Read Dimensionless Source # 
Instance details

Defined in Math.Number.Units

Fractional Dimensionless Source # 
Instance details

Defined in Math.Number.Units

Real Dimensionless Source # 
Instance details

Defined in Math.Number.Units

RealFrac Dimensionless Source # 
Instance details

Defined in Math.Number.Units

Show Dimensionless Source # 
Instance details

Defined in Math.Number.Units

Binary Dimensionless Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Dimensionless Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Dimensionless Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Dimensionless Source #

LiteralUnit Dimensionless Source # 
Instance details

Defined in Math.Number.Units

Unit Dimensionless Source # 
Instance details

Defined in Math.Number.Units

Eq Dimensionless Source # 
Instance details

Defined in Math.Number.Units

Ord Dimensionless Source # 
Instance details

Defined in Math.Number.Units

type Rep Dimensionless Source # 
Instance details

Defined in Math.Number.Units

type Rep Dimensionless = D1 ('MetaData "Dimensionless" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Dimensionless" 'PrefixI 'True) (S1 ('MetaSel ('Just "dimensionless_value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Dimensionless Source # 
Instance details

Defined in Math.Number.Units

newtype Information Source #

Constructors

Bits 

Instances

Instances details
Data Information Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Information -> Constr #

dataTypeOf :: Information -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Information Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Information :: Type -> Type #

Read Information Source # 
Instance details

Defined in Math.Number.Units

Show Information Source # 
Instance details

Defined in Math.Number.Units

Binary Information Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Information Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Information Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Information Source #

LiteralUnit Information Source # 
Instance details

Defined in Math.Number.Units

Unit Information Source # 
Instance details

Defined in Math.Number.Units

Eq Information Source # 
Instance details

Defined in Math.Number.Units

Ord Information Source # 
Instance details

Defined in Math.Number.Units

type Rep Information Source # 
Instance details

Defined in Math.Number.Units

type Rep Information = D1 ('MetaData "Information" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Bits" 'PrefixI 'True) (S1 ('MetaSel ('Just "number_of_bits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Information Source # 
Instance details

Defined in Math.Number.Units

newtype SoundLevel Source #

Constructors

SoundAmplitude 

Instances

Instances details
Data SoundLevel Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: SoundLevel -> Constr #

dataTypeOf :: SoundLevel -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic SoundLevel Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep SoundLevel :: Type -> Type #

Read SoundLevel Source # 
Instance details

Defined in Math.Number.Units

Show SoundLevel Source # 
Instance details

Defined in Math.Number.Units

Binary SoundLevel Source # 
Instance details

Defined in Math.Number.Units

VectorSpace SoundLevel Source #

NOTE: additive operations mapped to multiplicative. Notice this reduces the possible range of SoundLevel values to around -300..300 dB based on possible exponents in Double.

Instance details

Defined in Math.Number.Units

Associated Types

type Scalar SoundLevel Source #

LiteralUnit SoundLevel Source # 
Instance details

Defined in Math.Number.Units

Unit SoundLevel Source # 
Instance details

Defined in Math.Number.Units

Eq SoundLevel Source # 
Instance details

Defined in Math.Number.Units

Ord SoundLevel Source # 
Instance details

Defined in Math.Number.Units

type Rep SoundLevel Source # 
Instance details

Defined in Math.Number.Units

type Rep SoundLevel = D1 ('MetaData "SoundLevel" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "SoundAmplitude" 'PrefixI 'True) (S1 ('MetaSel ('Just "sound_amplitude") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar SoundLevel Source # 
Instance details

Defined in Math.Number.Units

newtype Angle Source #

Constructors

Radians 

Fields

Instances

Instances details
Data Angle Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Angle -> Constr #

dataTypeOf :: Angle -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Angle Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Angle :: Type -> Type #

Methods

from :: Angle -> Rep Angle x #

to :: Rep Angle x -> Angle #

Num Angle Source # 
Instance details

Defined in Math.Number.Units

Read Angle Source # 
Instance details

Defined in Math.Number.Units

Fractional Angle Source # 
Instance details

Defined in Math.Number.Units

Show Angle Source # 
Instance details

Defined in Math.Number.Units

Methods

showsPrec :: Int -> Angle -> ShowS #

show :: Angle -> String #

showList :: [Angle] -> ShowS #

Binary Angle Source # 
Instance details

Defined in Math.Number.Units

Methods

put :: Angle -> Put #

get :: Get Angle #

putList :: [Angle] -> Put #

NormedSpace Angle Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Angle Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Angle Source #

LiteralUnit Angle Source # 
Instance details

Defined in Math.Number.Units

Unit Angle Source # 
Instance details

Defined in Math.Number.Units

Eq Angle Source # 
Instance details

Defined in Math.Number.Units

Methods

(==) :: Angle -> Angle -> Bool #

(/=) :: Angle -> Angle -> Bool #

Ord Angle Source # 
Instance details

Defined in Math.Number.Units

Methods

compare :: Angle -> Angle -> Ordering #

(<) :: Angle -> Angle -> Bool #

(<=) :: Angle -> Angle -> Bool #

(>) :: Angle -> Angle -> Bool #

(>=) :: Angle -> Angle -> Bool #

max :: Angle -> Angle -> Angle #

min :: Angle -> Angle -> Angle #

type Rep Angle Source # 
Instance details

Defined in Math.Number.Units

type Rep Angle = D1 ('MetaData "Angle" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Radians" 'PrefixI 'True) (S1 ('MetaSel ('Just "radians") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Angle Source # 
Instance details

Defined in Math.Number.Units

fromPolar :: (Unit u, Scalar u ~ Double) => u -> Angle -> Complex u Source #

newtype DegreesAngle Source #

Constructors

Degrees 

Fields

Instances

Instances details
Data DegreesAngle Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: DegreesAngle -> Constr #

dataTypeOf :: DegreesAngle -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic DegreesAngle Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep DegreesAngle :: Type -> Type #

Read DegreesAngle Source # 
Instance details

Defined in Math.Number.Units

Show DegreesAngle Source # 
Instance details

Defined in Math.Number.Units

Binary DegreesAngle Source # 
Instance details

Defined in Math.Number.Units

NormedSpace DegreesAngle Source # 
Instance details

Defined in Math.Number.Units

VectorSpace DegreesAngle Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar DegreesAngle Source #

LiteralUnit DegreesAngle Source # 
Instance details

Defined in Math.Number.Units

Unit DegreesAngle Source # 
Instance details

Defined in Math.Number.Units

Eq DegreesAngle Source # 
Instance details

Defined in Math.Number.Units

Ord DegreesAngle Source # 
Instance details

Defined in Math.Number.Units

type Rep DegreesAngle Source # 
Instance details

Defined in Math.Number.Units

type Rep DegreesAngle = D1 ('MetaData "DegreesAngle" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Degrees" 'PrefixI 'True) (S1 ('MetaSel ('Just "degrees") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar DegreesAngle Source # 
Instance details

Defined in Math.Number.Units

newtype SolidAngle Source #

Constructors

Steradians 

Fields

Instances

Instances details
Data SolidAngle Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: SolidAngle -> Constr #

dataTypeOf :: SolidAngle -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic SolidAngle Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep SolidAngle :: Type -> Type #

Read SolidAngle Source # 
Instance details

Defined in Math.Number.Units

Show SolidAngle Source # 
Instance details

Defined in Math.Number.Units

Binary SolidAngle Source # 
Instance details

Defined in Math.Number.Units

NormedSpace SolidAngle Source # 
Instance details

Defined in Math.Number.Units

VectorSpace SolidAngle Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar SolidAngle Source #

LiteralUnit SolidAngle Source # 
Instance details

Defined in Math.Number.Units

Unit SolidAngle Source # 
Instance details

Defined in Math.Number.Units

Eq SolidAngle Source # 
Instance details

Defined in Math.Number.Units

Ord SolidAngle Source # 
Instance details

Defined in Math.Number.Units

type Rep SolidAngle Source # 
Instance details

Defined in Math.Number.Units

type Rep SolidAngle = D1 ('MetaData "SolidAngle" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Steradians" 'PrefixI 'True) (S1 ('MetaSel ('Just "steradians") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar SolidAngle Source # 
Instance details

Defined in Math.Number.Units

show_unit :: (Unit u, Show (Scalar u)) => u -> String Source #

newtype Percentage Source #

Constructors

Percentages 

Fields

Instances

Instances details
Data Percentage Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Percentage -> Constr #

dataTypeOf :: Percentage -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Percentage Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Percentage :: Type -> Type #

Read Percentage Source # 
Instance details

Defined in Math.Number.Units

Show Percentage Source # 
Instance details

Defined in Math.Number.Units

Binary Percentage Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Percentage Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Percentage Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Percentage Source #

LiteralUnit Percentage Source # 
Instance details

Defined in Math.Number.Units

Unit Percentage Source # 
Instance details

Defined in Math.Number.Units

Eq Percentage Source # 
Instance details

Defined in Math.Number.Units

Ord Percentage Source # 
Instance details

Defined in Math.Number.Units

type Rep Percentage Source # 
Instance details

Defined in Math.Number.Units

type Rep Percentage = D1 ('MetaData "Percentage" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Percentages" 'PrefixI 'True) (S1 ('MetaSel ('Just "percentages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Percentage Source # 
Instance details

Defined in Math.Number.Units

newtype Acceleration Source #

Instances

Instances details
Data Acceleration Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Acceleration -> Constr #

dataTypeOf :: Acceleration -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Acceleration Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Acceleration :: Type -> Type #

Read Acceleration Source # 
Instance details

Defined in Math.Number.Units

Show Acceleration Source # 
Instance details

Defined in Math.Number.Units

Binary Acceleration Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Acceleration Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Acceleration Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Acceleration Source #

LiteralUnit Acceleration Source # 
Instance details

Defined in Math.Number.Units

Unit Acceleration Source # 
Instance details

Defined in Math.Number.Units

Eq Acceleration Source # 
Instance details

Defined in Math.Number.Units

Ord Acceleration Source # 
Instance details

Defined in Math.Number.Units

type Rep Acceleration Source # 
Instance details

Defined in Math.Number.Units

type Rep Acceleration = D1 ('MetaData "Acceleration" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "MetersPerSquareSecond" 'PrefixI 'True) (S1 ('MetaSel ('Just "metersPerSquareSecond") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Acceleration Source # 
Instance details

Defined in Math.Number.Units

newtype Velocity Source #

Constructors

MetersPerSecond 

Instances

Instances details
Data Velocity Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Velocity -> Constr #

dataTypeOf :: Velocity -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Velocity Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Velocity :: Type -> Type #

Methods

from :: Velocity -> Rep Velocity x #

to :: Rep Velocity x -> Velocity #

Read Velocity Source # 
Instance details

Defined in Math.Number.Units

Show Velocity Source # 
Instance details

Defined in Math.Number.Units

Binary Velocity Source # 
Instance details

Defined in Math.Number.Units

Methods

put :: Velocity -> Put #

get :: Get Velocity #

putList :: [Velocity] -> Put #

NormedSpace Velocity Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Velocity Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Velocity Source #

LiteralUnit Velocity Source # 
Instance details

Defined in Math.Number.Units

Unit Velocity Source # 
Instance details

Defined in Math.Number.Units

Eq Velocity Source # 
Instance details

Defined in Math.Number.Units

Ord Velocity Source # 
Instance details

Defined in Math.Number.Units

type Rep Velocity Source # 
Instance details

Defined in Math.Number.Units

type Rep Velocity = D1 ('MetaData "Velocity" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "MetersPerSecond" 'PrefixI 'True) (S1 ('MetaSel ('Just "metersPerSecond") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Velocity Source # 
Instance details

Defined in Math.Number.Units

newtype SquareLength Source #

Constructors

SquareMeters 

Fields

Instances

Instances details
Data SquareLength Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: SquareLength -> Constr #

dataTypeOf :: SquareLength -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic SquareLength Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep SquareLength :: Type -> Type #

Read SquareLength Source # 
Instance details

Defined in Math.Number.Units

Show SquareLength Source # 
Instance details

Defined in Math.Number.Units

Binary SquareLength Source # 
Instance details

Defined in Math.Number.Units

NormedSpace SquareLength Source # 
Instance details

Defined in Math.Number.Units

VectorSpace SquareLength Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar SquareLength Source #

LiteralUnit SquareLength Source # 
Instance details

Defined in Math.Number.Units

Unit SquareLength Source # 
Instance details

Defined in Math.Number.Units

Eq SquareLength Source # 
Instance details

Defined in Math.Number.Units

Ord SquareLength Source # 
Instance details

Defined in Math.Number.Units

type Rep SquareLength Source # 
Instance details

Defined in Math.Number.Units

type Rep SquareLength = D1 ('MetaData "SquareLength" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "SquareMeters" 'PrefixI 'True) (S1 ('MetaSel ('Just "squaremeters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar SquareLength Source # 
Instance details

Defined in Math.Number.Units

newtype CubicLength Source #

Constructors

CubicMeters 

Fields

Instances

Instances details
Data CubicLength Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: CubicLength -> Constr #

dataTypeOf :: CubicLength -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic CubicLength Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep CubicLength :: Type -> Type #

Read CubicLength Source # 
Instance details

Defined in Math.Number.Units

Show CubicLength Source # 
Instance details

Defined in Math.Number.Units

Binary CubicLength Source # 
Instance details

Defined in Math.Number.Units

VectorSpace CubicLength Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar CubicLength Source #

LiteralUnit CubicLength Source # 
Instance details

Defined in Math.Number.Units

Unit CubicLength Source # 
Instance details

Defined in Math.Number.Units

Eq CubicLength Source # 
Instance details

Defined in Math.Number.Units

Ord CubicLength Source # 
Instance details

Defined in Math.Number.Units

type Rep CubicLength Source # 
Instance details

Defined in Math.Number.Units

type Rep CubicLength = D1 ('MetaData "CubicLength" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "CubicMeters" 'PrefixI 'True) (S1 ('MetaSel ('Just "cubicmeters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar CubicLength Source # 
Instance details

Defined in Math.Number.Units

newtype Length Source #

Constructors

Meters 

Fields

Instances

Instances details
Data Length Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Length -> Constr #

dataTypeOf :: Length -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Length Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Length :: Type -> Type #

Methods

from :: Length -> Rep Length x #

to :: Rep Length x -> Length #

Read Length Source # 
Instance details

Defined in Math.Number.Units

Show Length Source # 
Instance details

Defined in Math.Number.Units

Binary Length Source # 
Instance details

Defined in Math.Number.Units

Methods

put :: Length -> Put #

get :: Get Length #

putList :: [Length] -> Put #

NormedSpace Length Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Length Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Length Source #

LiteralUnit Length Source # 
Instance details

Defined in Math.Number.Units

Unit Length Source # 
Instance details

Defined in Math.Number.Units

Eq Length Source # 
Instance details

Defined in Math.Number.Units

Methods

(==) :: Length -> Length -> Bool #

(/=) :: Length -> Length -> Bool #

Ord Length Source # 
Instance details

Defined in Math.Number.Units

type Rep Length Source # 
Instance details

Defined in Math.Number.Units

type Rep Length = D1 ('MetaData "Length" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Meters" 'PrefixI 'True) (S1 ('MetaSel ('Just "meters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Length Source # 
Instance details

Defined in Math.Number.Units

newtype Mass Source #

Constructors

Kilograms 

Fields

Instances

Instances details
Data Mass Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Mass -> Constr #

dataTypeOf :: Mass -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Mass Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Mass :: Type -> Type #

Methods

from :: Mass -> Rep Mass x #

to :: Rep Mass x -> Mass #

Read Mass Source # 
Instance details

Defined in Math.Number.Units

Show Mass Source # 
Instance details

Defined in Math.Number.Units

Methods

showsPrec :: Int -> Mass -> ShowS #

show :: Mass -> String #

showList :: [Mass] -> ShowS #

Binary Mass Source # 
Instance details

Defined in Math.Number.Units

Methods

put :: Mass -> Put #

get :: Get Mass #

putList :: [Mass] -> Put #

NormedSpace Mass Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Mass Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Mass Source #

LiteralUnit Mass Source # 
Instance details

Defined in Math.Number.Units

Unit Mass Source # 
Instance details

Defined in Math.Number.Units

Eq Mass Source # 
Instance details

Defined in Math.Number.Units

Methods

(==) :: Mass -> Mass -> Bool #

(/=) :: Mass -> Mass -> Bool #

Ord Mass Source # 
Instance details

Defined in Math.Number.Units

Methods

compare :: Mass -> Mass -> Ordering #

(<) :: Mass -> Mass -> Bool #

(<=) :: Mass -> Mass -> Bool #

(>) :: Mass -> Mass -> Bool #

(>=) :: Mass -> Mass -> Bool #

max :: Mass -> Mass -> Mass #

min :: Mass -> Mass -> Mass #

type Rep Mass Source # 
Instance details

Defined in Math.Number.Units

type Rep Mass = D1 ('MetaData "Mass" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Kilograms" 'PrefixI 'True) (S1 ('MetaSel ('Just "kilograms") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Mass Source # 
Instance details

Defined in Math.Number.Units

newtype Time Source #

Constructors

Seconds 

Fields

Instances

Instances details
Data Time Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Time -> Constr #

dataTypeOf :: Time -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Time Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Time :: Type -> Type #

Methods

from :: Time -> Rep Time x #

to :: Rep Time x -> Time #

Read Time Source # 
Instance details

Defined in Math.Number.Units

Show Time Source # 
Instance details

Defined in Math.Number.Units

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

Binary Time Source # 
Instance details

Defined in Math.Number.Units

Methods

put :: Time -> Put #

get :: Get Time #

putList :: [Time] -> Put #

NormedSpace Time Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Time Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Time Source #

LiteralUnit Time Source # 
Instance details

Defined in Math.Number.Units

Unit Time Source # 
Instance details

Defined in Math.Number.Units

Eq Time Source # 
Instance details

Defined in Math.Number.Units

Methods

(==) :: Time -> Time -> Bool #

(/=) :: Time -> Time -> Bool #

Ord Time Source # 
Instance details

Defined in Math.Number.Units

Methods

compare :: Time -> Time -> Ordering #

(<) :: Time -> Time -> Bool #

(<=) :: Time -> Time -> Bool #

(>) :: Time -> Time -> Bool #

(>=) :: Time -> Time -> Bool #

max :: Time -> Time -> Time #

min :: Time -> Time -> Time #

type Rep Time Source # 
Instance details

Defined in Math.Number.Units

type Rep Time = D1 ('MetaData "Time" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Seconds" 'PrefixI 'True) (S1 ('MetaSel ('Just "seconds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Time Source # 
Instance details

Defined in Math.Number.Units

newtype Current Source #

Constructors

Amperes 

Fields

Instances

Instances details
Data Current Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Current -> Constr #

dataTypeOf :: Current -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Current Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Current :: Type -> Type #

Methods

from :: Current -> Rep Current x #

to :: Rep Current x -> Current #

Read Current Source # 
Instance details

Defined in Math.Number.Units

Show Current Source # 
Instance details

Defined in Math.Number.Units

Binary Current Source # 
Instance details

Defined in Math.Number.Units

Methods

put :: Current -> Put #

get :: Get Current #

putList :: [Current] -> Put #

NormedSpace Current Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Current Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Current Source #

LiteralUnit Current Source # 
Instance details

Defined in Math.Number.Units

Unit Current Source # 
Instance details

Defined in Math.Number.Units

Eq Current Source # 
Instance details

Defined in Math.Number.Units

Methods

(==) :: Current -> Current -> Bool #

(/=) :: Current -> Current -> Bool #

Ord Current Source # 
Instance details

Defined in Math.Number.Units

type Rep Current Source # 
Instance details

Defined in Math.Number.Units

type Rep Current = D1 ('MetaData "Current" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Amperes" 'PrefixI 'True) (S1 ('MetaSel ('Just "amperes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Current Source # 
Instance details

Defined in Math.Number.Units

newtype DegreesFahrenheit Source #

Constructors

DegreesFahrenheit 

Fields

Instances

Instances details
Data DegreesFahrenheit Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: DegreesFahrenheit -> Constr #

dataTypeOf :: DegreesFahrenheit -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic DegreesFahrenheit Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep DegreesFahrenheit :: Type -> Type #

Read DegreesFahrenheit Source # 
Instance details

Defined in Math.Number.Units

Show DegreesFahrenheit Source # 
Instance details

Defined in Math.Number.Units

Binary DegreesFahrenheit Source # 
Instance details

Defined in Math.Number.Units

NormedSpace DegreesFahrenheit Source # 
Instance details

Defined in Math.Number.Units

VectorSpace DegreesFahrenheit Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar DegreesFahrenheit Source #

LiteralUnit DegreesFahrenheit Source # 
Instance details

Defined in Math.Number.Units

Unit DegreesFahrenheit Source # 
Instance details

Defined in Math.Number.Units

Eq DegreesFahrenheit Source # 
Instance details

Defined in Math.Number.Units

Ord DegreesFahrenheit Source # 
Instance details

Defined in Math.Number.Units

type Rep DegreesFahrenheit Source # 
Instance details

Defined in Math.Number.Units

type Rep DegreesFahrenheit = D1 ('MetaData "DegreesFahrenheit" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "DegreesFahrenheit" 'PrefixI 'True) (S1 ('MetaSel ('Just "fahrenheits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar DegreesFahrenheit Source # 
Instance details

Defined in Math.Number.Units

newtype DegreesTemperature Source #

Constructors

DegreesCelcius 

Fields

Instances

Instances details
Data DegreesTemperature Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: DegreesTemperature -> Constr #

dataTypeOf :: DegreesTemperature -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic DegreesTemperature Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep DegreesTemperature :: Type -> Type #

Read DegreesTemperature Source # 
Instance details

Defined in Math.Number.Units

Show DegreesTemperature Source # 
Instance details

Defined in Math.Number.Units

Binary DegreesTemperature Source # 
Instance details

Defined in Math.Number.Units

NormedSpace DegreesTemperature Source # 
Instance details

Defined in Math.Number.Units

VectorSpace DegreesTemperature Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar DegreesTemperature Source #

LiteralUnit DegreesTemperature Source # 
Instance details

Defined in Math.Number.Units

Unit DegreesTemperature Source # 
Instance details

Defined in Math.Number.Units

Eq DegreesTemperature Source # 
Instance details

Defined in Math.Number.Units

Ord DegreesTemperature Source # 
Instance details

Defined in Math.Number.Units

type Rep DegreesTemperature Source # 
Instance details

Defined in Math.Number.Units

type Rep DegreesTemperature = D1 ('MetaData "DegreesTemperature" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "DegreesCelcius" 'PrefixI 'True) (S1 ('MetaSel ('Just "celciuses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar DegreesTemperature Source # 
Instance details

Defined in Math.Number.Units

newtype Temperature Source #

Constructors

DegreesKelvin 

Fields

Instances

Instances details
Data Temperature Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Temperature -> Constr #

dataTypeOf :: Temperature -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Temperature Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Temperature :: Type -> Type #

Read Temperature Source # 
Instance details

Defined in Math.Number.Units

Show Temperature Source # 
Instance details

Defined in Math.Number.Units

Binary Temperature Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Temperature Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Temperature Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Temperature Source #

LiteralUnit Temperature Source # 
Instance details

Defined in Math.Number.Units

Unit Temperature Source # 
Instance details

Defined in Math.Number.Units

Eq Temperature Source # 
Instance details

Defined in Math.Number.Units

Ord Temperature Source # 
Instance details

Defined in Math.Number.Units

type Rep Temperature Source # 
Instance details

Defined in Math.Number.Units

type Rep Temperature = D1 ('MetaData "Temperature" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "DegreesKelvin" 'PrefixI 'True) (S1 ('MetaSel ('Just "kelvins") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Temperature Source # 
Instance details

Defined in Math.Number.Units

newtype Substance Source #

Constructors

Moles 

Fields

Instances

Instances details
Data Substance Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Substance -> Constr #

dataTypeOf :: Substance -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Substance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Substance :: Type -> Type #

Read Substance Source # 
Instance details

Defined in Math.Number.Units

Show Substance Source # 
Instance details

Defined in Math.Number.Units

Binary Substance Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Substance Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Substance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Substance Source #

LiteralUnit Substance Source # 
Instance details

Defined in Math.Number.Units

Unit Substance Source # 
Instance details

Defined in Math.Number.Units

Eq Substance Source # 
Instance details

Defined in Math.Number.Units

Ord Substance Source # 
Instance details

Defined in Math.Number.Units

type Rep Substance Source # 
Instance details

Defined in Math.Number.Units

type Rep Substance = D1 ('MetaData "Substance" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Moles" 'PrefixI 'True) (S1 ('MetaSel ('Just "moles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Substance Source # 
Instance details

Defined in Math.Number.Units

newtype Intensity Source #

Constructors

Candelas 

Fields

Instances

Instances details
Data Intensity Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Intensity -> Constr #

dataTypeOf :: Intensity -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Intensity Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Intensity :: Type -> Type #

Read Intensity Source # 
Instance details

Defined in Math.Number.Units

Show Intensity Source # 
Instance details

Defined in Math.Number.Units

Binary Intensity Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Intensity Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Intensity Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Intensity Source #

LiteralUnit Intensity Source # 
Instance details

Defined in Math.Number.Units

Unit Intensity Source # 
Instance details

Defined in Math.Number.Units

Eq Intensity Source # 
Instance details

Defined in Math.Number.Units

Ord Intensity Source # 
Instance details

Defined in Math.Number.Units

type Rep Intensity Source # 
Instance details

Defined in Math.Number.Units

type Rep Intensity = D1 ('MetaData "Intensity" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Candelas" 'PrefixI 'True) (S1 ('MetaSel ('Just "candelas") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Intensity Source # 
Instance details

Defined in Math.Number.Units

newtype Frequency Source #

Constructors

Hertzes 

Fields

Instances

Instances details
Data Frequency Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Frequency -> Constr #

dataTypeOf :: Frequency -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Frequency Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Frequency :: Type -> Type #

Read Frequency Source # 
Instance details

Defined in Math.Number.Units

Show Frequency Source # 
Instance details

Defined in Math.Number.Units

Binary Frequency Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Frequency Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Frequency Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Frequency Source #

LiteralUnit Frequency Source # 
Instance details

Defined in Math.Number.Units

Unit Frequency Source # 
Instance details

Defined in Math.Number.Units

Eq Frequency Source # 
Instance details

Defined in Math.Number.Units

Ord Frequency Source # 
Instance details

Defined in Math.Number.Units

type Rep Frequency Source # 
Instance details

Defined in Math.Number.Units

type Rep Frequency = D1 ('MetaData "Frequency" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Hertzes" 'PrefixI 'True) (S1 ('MetaSel ('Just "hertzes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Frequency Source # 
Instance details

Defined in Math.Number.Units

newtype Force Source #

Constructors

Newtons 

Fields

Instances

Instances details
Data Force Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Force -> Constr #

dataTypeOf :: Force -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Force Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Force :: Type -> Type #

Methods

from :: Force -> Rep Force x #

to :: Rep Force x -> Force #

Read Force Source # 
Instance details

Defined in Math.Number.Units

Show Force Source # 
Instance details

Defined in Math.Number.Units

Methods

showsPrec :: Int -> Force -> ShowS #

show :: Force -> String #

showList :: [Force] -> ShowS #

Binary Force Source # 
Instance details

Defined in Math.Number.Units

Methods

put :: Force -> Put #

get :: Get Force #

putList :: [Force] -> Put #

NormedSpace Force Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Force Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Force Source #

LiteralUnit Force Source # 
Instance details

Defined in Math.Number.Units

Unit Force Source # 
Instance details

Defined in Math.Number.Units

Eq Force Source # 
Instance details

Defined in Math.Number.Units

Methods

(==) :: Force -> Force -> Bool #

(/=) :: Force -> Force -> Bool #

Ord Force Source # 
Instance details

Defined in Math.Number.Units

Methods

compare :: Force -> Force -> Ordering #

(<) :: Force -> Force -> Bool #

(<=) :: Force -> Force -> Bool #

(>) :: Force -> Force -> Bool #

(>=) :: Force -> Force -> Bool #

max :: Force -> Force -> Force #

min :: Force -> Force -> Force #

type Rep Force Source # 
Instance details

Defined in Math.Number.Units

type Rep Force = D1 ('MetaData "Force" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Newtons" 'PrefixI 'True) (S1 ('MetaSel ('Just "newtons") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Force Source # 
Instance details

Defined in Math.Number.Units

newtype Torque Source #

Constructors

NewtonMeters 

Fields

Instances

Instances details
Data Torque Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Torque -> Constr #

dataTypeOf :: Torque -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Torque Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Torque :: Type -> Type #

Methods

from :: Torque -> Rep Torque x #

to :: Rep Torque x -> Torque #

Read Torque Source # 
Instance details

Defined in Math.Number.Units

Show Torque Source # 
Instance details

Defined in Math.Number.Units

Binary Torque Source # 
Instance details

Defined in Math.Number.Units

Methods

put :: Torque -> Put #

get :: Get Torque #

putList :: [Torque] -> Put #

NormedSpace Torque Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Torque Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Torque Source #

LiteralUnit Torque Source # 
Instance details

Defined in Math.Number.Units

Unit Torque Source # 
Instance details

Defined in Math.Number.Units

Eq Torque Source # 
Instance details

Defined in Math.Number.Units

Methods

(==) :: Torque -> Torque -> Bool #

(/=) :: Torque -> Torque -> Bool #

Ord Torque Source # 
Instance details

Defined in Math.Number.Units

type Rep Torque Source # 
Instance details

Defined in Math.Number.Units

type Rep Torque = D1 ('MetaData "Torque" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "NewtonMeters" 'PrefixI 'True) (S1 ('MetaSel ('Just "newtonmeters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Torque Source # 
Instance details

Defined in Math.Number.Units

newtype Pressure Source #

Constructors

Pascals 

Fields

Instances

Instances details
Data Pressure Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Pressure -> Constr #

dataTypeOf :: Pressure -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Pressure Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Pressure :: Type -> Type #

Methods

from :: Pressure -> Rep Pressure x #

to :: Rep Pressure x -> Pressure #

Read Pressure Source # 
Instance details

Defined in Math.Number.Units

Show Pressure Source # 
Instance details

Defined in Math.Number.Units

Binary Pressure Source # 
Instance details

Defined in Math.Number.Units

Methods

put :: Pressure -> Put #

get :: Get Pressure #

putList :: [Pressure] -> Put #

NormedSpace Pressure Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Pressure Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Pressure Source #

LiteralUnit Pressure Source # 
Instance details

Defined in Math.Number.Units

Unit Pressure Source # 
Instance details

Defined in Math.Number.Units

Eq Pressure Source # 
Instance details

Defined in Math.Number.Units

Ord Pressure Source # 
Instance details

Defined in Math.Number.Units

type Rep Pressure Source # 
Instance details

Defined in Math.Number.Units

type Rep Pressure = D1 ('MetaData "Pressure" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Pascals" 'PrefixI 'True) (S1 ('MetaSel ('Just "pascals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Pressure Source # 
Instance details

Defined in Math.Number.Units

newtype Energy Source #

Constructors

Joules 

Fields

Instances

Instances details
Data Energy Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Energy -> Constr #

dataTypeOf :: Energy -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Energy Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Energy :: Type -> Type #

Methods

from :: Energy -> Rep Energy x #

to :: Rep Energy x -> Energy #

Read Energy Source # 
Instance details

Defined in Math.Number.Units

Show Energy Source # 
Instance details

Defined in Math.Number.Units

Binary Energy Source # 
Instance details

Defined in Math.Number.Units

Methods

put :: Energy -> Put #

get :: Get Energy #

putList :: [Energy] -> Put #

NormedSpace Energy Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Energy Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Energy Source #

LiteralUnit Energy Source # 
Instance details

Defined in Math.Number.Units

Unit Energy Source # 
Instance details

Defined in Math.Number.Units

Eq Energy Source # 
Instance details

Defined in Math.Number.Units

Methods

(==) :: Energy -> Energy -> Bool #

(/=) :: Energy -> Energy -> Bool #

Ord Energy Source # 
Instance details

Defined in Math.Number.Units

type Rep Energy Source # 
Instance details

Defined in Math.Number.Units

type Rep Energy = D1 ('MetaData "Energy" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Joules" 'PrefixI 'True) (S1 ('MetaSel ('Just "joules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Energy Source # 
Instance details

Defined in Math.Number.Units

newtype Power Source #

Constructors

Watts 

Fields

Instances

Instances details
Data Power Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Power -> Constr #

dataTypeOf :: Power -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Power Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Power :: Type -> Type #

Methods

from :: Power -> Rep Power x #

to :: Rep Power x -> Power #

Read Power Source # 
Instance details

Defined in Math.Number.Units

Show Power Source # 
Instance details

Defined in Math.Number.Units

Methods

showsPrec :: Int -> Power -> ShowS #

show :: Power -> String #

showList :: [Power] -> ShowS #

Binary Power Source # 
Instance details

Defined in Math.Number.Units

Methods

put :: Power -> Put #

get :: Get Power #

putList :: [Power] -> Put #

NormedSpace Power Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Power Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Power Source #

LiteralUnit Power Source # 
Instance details

Defined in Math.Number.Units

Unit Power Source # 
Instance details

Defined in Math.Number.Units

Eq Power Source # 
Instance details

Defined in Math.Number.Units

Methods

(==) :: Power -> Power -> Bool #

(/=) :: Power -> Power -> Bool #

Ord Power Source # 
Instance details

Defined in Math.Number.Units

Methods

compare :: Power -> Power -> Ordering #

(<) :: Power -> Power -> Bool #

(<=) :: Power -> Power -> Bool #

(>) :: Power -> Power -> Bool #

(>=) :: Power -> Power -> Bool #

max :: Power -> Power -> Power #

min :: Power -> Power -> Power #

type Rep Power Source # 
Instance details

Defined in Math.Number.Units

type Rep Power = D1 ('MetaData "Power" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Watts" 'PrefixI 'True) (S1 ('MetaSel ('Just "watts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Power Source # 
Instance details

Defined in Math.Number.Units

newtype Charge Source #

Constructors

Coulombs 

Fields

Instances

Instances details
Data Charge Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Charge -> Constr #

dataTypeOf :: Charge -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Charge Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Charge :: Type -> Type #

Methods

from :: Charge -> Rep Charge x #

to :: Rep Charge x -> Charge #

Read Charge Source # 
Instance details

Defined in Math.Number.Units

Show Charge Source # 
Instance details

Defined in Math.Number.Units

Binary Charge Source # 
Instance details

Defined in Math.Number.Units

Methods

put :: Charge -> Put #

get :: Get Charge #

putList :: [Charge] -> Put #

NormedSpace Charge Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Charge Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Charge Source #

LiteralUnit Charge Source # 
Instance details

Defined in Math.Number.Units

Unit Charge Source # 
Instance details

Defined in Math.Number.Units

Eq Charge Source # 
Instance details

Defined in Math.Number.Units

Methods

(==) :: Charge -> Charge -> Bool #

(/=) :: Charge -> Charge -> Bool #

Ord Charge Source # 
Instance details

Defined in Math.Number.Units

type Rep Charge Source # 
Instance details

Defined in Math.Number.Units

type Rep Charge = D1 ('MetaData "Charge" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Coulombs" 'PrefixI 'True) (S1 ('MetaSel ('Just "coulombs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Charge Source # 
Instance details

Defined in Math.Number.Units

newtype Voltage Source #

Constructors

Volts 

Fields

Instances

Instances details
Data Voltage Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Voltage -> Constr #

dataTypeOf :: Voltage -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Voltage Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Voltage :: Type -> Type #

Methods

from :: Voltage -> Rep Voltage x #

to :: Rep Voltage x -> Voltage #

Read Voltage Source # 
Instance details

Defined in Math.Number.Units

Show Voltage Source # 
Instance details

Defined in Math.Number.Units

Binary Voltage Source # 
Instance details

Defined in Math.Number.Units

Methods

put :: Voltage -> Put #

get :: Get Voltage #

putList :: [Voltage] -> Put #

NormedSpace Voltage Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Voltage Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Voltage Source #

LiteralUnit Voltage Source # 
Instance details

Defined in Math.Number.Units

Unit Voltage Source # 
Instance details

Defined in Math.Number.Units

Eq Voltage Source # 
Instance details

Defined in Math.Number.Units

Methods

(==) :: Voltage -> Voltage -> Bool #

(/=) :: Voltage -> Voltage -> Bool #

Ord Voltage Source # 
Instance details

Defined in Math.Number.Units

type Rep Voltage Source # 
Instance details

Defined in Math.Number.Units

type Rep Voltage = D1 ('MetaData "Voltage" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Volts" 'PrefixI 'True) (S1 ('MetaSel ('Just "volts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Voltage Source # 
Instance details

Defined in Math.Number.Units

newtype Capacitance Source #

Constructors

Farads 

Fields

Instances

Instances details
Data Capacitance Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Capacitance -> Constr #

dataTypeOf :: Capacitance -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Capacitance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Capacitance :: Type -> Type #

Read Capacitance Source # 
Instance details

Defined in Math.Number.Units

Show Capacitance Source # 
Instance details

Defined in Math.Number.Units

Binary Capacitance Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Capacitance Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Capacitance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Capacitance Source #

LiteralUnit Capacitance Source # 
Instance details

Defined in Math.Number.Units

Unit Capacitance Source # 
Instance details

Defined in Math.Number.Units

Eq Capacitance Source # 
Instance details

Defined in Math.Number.Units

Ord Capacitance Source # 
Instance details

Defined in Math.Number.Units

type Rep Capacitance Source # 
Instance details

Defined in Math.Number.Units

type Rep Capacitance = D1 ('MetaData "Capacitance" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Farads" 'PrefixI 'True) (S1 ('MetaSel ('Just "farads") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Capacitance Source # 
Instance details

Defined in Math.Number.Units

newtype Resistance Source #

Constructors

Ohms 

Fields

Instances

Instances details
Data Resistance Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Resistance -> Constr #

dataTypeOf :: Resistance -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Resistance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Resistance :: Type -> Type #

Read Resistance Source # 
Instance details

Defined in Math.Number.Units

Show Resistance Source # 
Instance details

Defined in Math.Number.Units

Binary Resistance Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Resistance Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Resistance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Resistance Source #

LiteralUnit Resistance Source # 
Instance details

Defined in Math.Number.Units

Unit Resistance Source # 
Instance details

Defined in Math.Number.Units

Eq Resistance Source # 
Instance details

Defined in Math.Number.Units

Ord Resistance Source # 
Instance details

Defined in Math.Number.Units

type Rep Resistance Source # 
Instance details

Defined in Math.Number.Units

type Rep Resistance = D1 ('MetaData "Resistance" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Ohms" 'PrefixI 'True) (S1 ('MetaSel ('Just "ohms") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Resistance Source # 
Instance details

Defined in Math.Number.Units

newtype Conductance Source #

Constructors

Siemenses 

Fields

Instances

Instances details
Data Conductance Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Conductance -> Constr #

dataTypeOf :: Conductance -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Conductance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Conductance :: Type -> Type #

Read Conductance Source # 
Instance details

Defined in Math.Number.Units

Show Conductance Source # 
Instance details

Defined in Math.Number.Units

Binary Conductance Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Conductance Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Conductance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Conductance Source #

LiteralUnit Conductance Source # 
Instance details

Defined in Math.Number.Units

Unit Conductance Source # 
Instance details

Defined in Math.Number.Units

Eq Conductance Source # 
Instance details

Defined in Math.Number.Units

Ord Conductance Source # 
Instance details

Defined in Math.Number.Units

type Rep Conductance Source # 
Instance details

Defined in Math.Number.Units

type Rep Conductance = D1 ('MetaData "Conductance" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Siemenses" 'PrefixI 'True) (S1 ('MetaSel ('Just "siemenses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Conductance Source # 
Instance details

Defined in Math.Number.Units

newtype Flux Source #

Constructors

Webers 

Fields

Instances

Instances details
Data Flux Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Flux -> Constr #

dataTypeOf :: Flux -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Flux Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Flux :: Type -> Type #

Methods

from :: Flux -> Rep Flux x #

to :: Rep Flux x -> Flux #

Read Flux Source # 
Instance details

Defined in Math.Number.Units

Show Flux Source # 
Instance details

Defined in Math.Number.Units

Methods

showsPrec :: Int -> Flux -> ShowS #

show :: Flux -> String #

showList :: [Flux] -> ShowS #

Binary Flux Source # 
Instance details

Defined in Math.Number.Units

Methods

put :: Flux -> Put #

get :: Get Flux #

putList :: [Flux] -> Put #

NormedSpace Flux Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Flux Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Flux Source #

LiteralUnit Flux Source # 
Instance details

Defined in Math.Number.Units

Unit Flux Source # 
Instance details

Defined in Math.Number.Units

Eq Flux Source # 
Instance details

Defined in Math.Number.Units

Methods

(==) :: Flux -> Flux -> Bool #

(/=) :: Flux -> Flux -> Bool #

Ord Flux Source # 
Instance details

Defined in Math.Number.Units

Methods

compare :: Flux -> Flux -> Ordering #

(<) :: Flux -> Flux -> Bool #

(<=) :: Flux -> Flux -> Bool #

(>) :: Flux -> Flux -> Bool #

(>=) :: Flux -> Flux -> Bool #

max :: Flux -> Flux -> Flux #

min :: Flux -> Flux -> Flux #

type Rep Flux Source # 
Instance details

Defined in Math.Number.Units

type Rep Flux = D1 ('MetaData "Flux" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Webers" 'PrefixI 'True) (S1 ('MetaSel ('Just "webers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Flux Source # 
Instance details

Defined in Math.Number.Units

newtype FluxDensity Source #

Constructors

Teslas 

Fields

Instances

Instances details
Data FluxDensity Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: FluxDensity -> Constr #

dataTypeOf :: FluxDensity -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic FluxDensity Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep FluxDensity :: Type -> Type #

Read FluxDensity Source # 
Instance details

Defined in Math.Number.Units

Show FluxDensity Source # 
Instance details

Defined in Math.Number.Units

Binary FluxDensity Source # 
Instance details

Defined in Math.Number.Units

NormedSpace FluxDensity Source # 
Instance details

Defined in Math.Number.Units

VectorSpace FluxDensity Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar FluxDensity Source #

LiteralUnit FluxDensity Source # 
Instance details

Defined in Math.Number.Units

Unit FluxDensity Source # 
Instance details

Defined in Math.Number.Units

Eq FluxDensity Source # 
Instance details

Defined in Math.Number.Units

Ord FluxDensity Source # 
Instance details

Defined in Math.Number.Units

type Rep FluxDensity Source # 
Instance details

Defined in Math.Number.Units

type Rep FluxDensity = D1 ('MetaData "FluxDensity" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Teslas" 'PrefixI 'True) (S1 ('MetaSel ('Just "teslas") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar FluxDensity Source # 
Instance details

Defined in Math.Number.Units

newtype Inductance Source #

Constructors

Henrys 

Fields

Instances

Instances details
Data Inductance Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Inductance -> Constr #

dataTypeOf :: Inductance -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Inductance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Inductance :: Type -> Type #

Read Inductance Source # 
Instance details

Defined in Math.Number.Units

Show Inductance Source # 
Instance details

Defined in Math.Number.Units

Binary Inductance Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Inductance Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Inductance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Inductance Source #

LiteralUnit Inductance Source # 
Instance details

Defined in Math.Number.Units

Unit Inductance Source # 
Instance details

Defined in Math.Number.Units

Eq Inductance Source # 
Instance details

Defined in Math.Number.Units

Ord Inductance Source # 
Instance details

Defined in Math.Number.Units

type Rep Inductance Source # 
Instance details

Defined in Math.Number.Units

type Rep Inductance = D1 ('MetaData "Inductance" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Henrys" 'PrefixI 'True) (S1 ('MetaSel ('Just "henrys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Inductance Source # 
Instance details

Defined in Math.Number.Units

newtype LuminousFlux Source #

Constructors

Lumens 

Fields

Instances

Instances details
Data LuminousFlux Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: LuminousFlux -> Constr #

dataTypeOf :: LuminousFlux -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic LuminousFlux Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep LuminousFlux :: Type -> Type #

Read LuminousFlux Source # 
Instance details

Defined in Math.Number.Units

Show LuminousFlux Source # 
Instance details

Defined in Math.Number.Units

Binary LuminousFlux Source # 
Instance details

Defined in Math.Number.Units

NormedSpace LuminousFlux Source # 
Instance details

Defined in Math.Number.Units

VectorSpace LuminousFlux Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar LuminousFlux Source #

LiteralUnit LuminousFlux Source # 
Instance details

Defined in Math.Number.Units

Unit LuminousFlux Source # 
Instance details

Defined in Math.Number.Units

Eq LuminousFlux Source # 
Instance details

Defined in Math.Number.Units

Ord LuminousFlux Source # 
Instance details

Defined in Math.Number.Units

type Rep LuminousFlux Source # 
Instance details

Defined in Math.Number.Units

type Rep LuminousFlux = D1 ('MetaData "LuminousFlux" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Lumens" 'PrefixI 'True) (S1 ('MetaSel ('Just "lumens") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar LuminousFlux Source # 
Instance details

Defined in Math.Number.Units

newtype Illuminance Source #

Constructors

Luxes 

Fields

Instances

Instances details
Data Illuminance Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Illuminance -> Constr #

dataTypeOf :: Illuminance -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Illuminance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Illuminance :: Type -> Type #

Read Illuminance Source # 
Instance details

Defined in Math.Number.Units

Show Illuminance Source # 
Instance details

Defined in Math.Number.Units

Binary Illuminance Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Illuminance Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Illuminance Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Illuminance Source #

LiteralUnit Illuminance Source # 
Instance details

Defined in Math.Number.Units

Unit Illuminance Source # 
Instance details

Defined in Math.Number.Units

Eq Illuminance Source # 
Instance details

Defined in Math.Number.Units

Ord Illuminance Source # 
Instance details

Defined in Math.Number.Units

type Rep Illuminance Source # 
Instance details

Defined in Math.Number.Units

type Rep Illuminance = D1 ('MetaData "Illuminance" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Luxes" 'PrefixI 'True) (S1 ('MetaSel ('Just "luxes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Illuminance Source # 
Instance details

Defined in Math.Number.Units

newtype Radioactivity Source #

Constructors

Becquerels 

Fields

Instances

Instances details
Data Radioactivity Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: Radioactivity -> Constr #

dataTypeOf :: Radioactivity -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Radioactivity Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep Radioactivity :: Type -> Type #

Read Radioactivity Source # 
Instance details

Defined in Math.Number.Units

Show Radioactivity Source # 
Instance details

Defined in Math.Number.Units

Binary Radioactivity Source # 
Instance details

Defined in Math.Number.Units

NormedSpace Radioactivity Source # 
Instance details

Defined in Math.Number.Units

VectorSpace Radioactivity Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar Radioactivity Source #

LiteralUnit Radioactivity Source # 
Instance details

Defined in Math.Number.Units

Unit Radioactivity Source # 
Instance details

Defined in Math.Number.Units

Eq Radioactivity Source # 
Instance details

Defined in Math.Number.Units

Ord Radioactivity Source # 
Instance details

Defined in Math.Number.Units

type Rep Radioactivity Source # 
Instance details

Defined in Math.Number.Units

type Rep Radioactivity = D1 ('MetaData "Radioactivity" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Becquerels" 'PrefixI 'True) (S1 ('MetaSel ('Just "becquerels") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar Radioactivity Source # 
Instance details

Defined in Math.Number.Units

newtype AbsorbedDose Source #

Constructors

Grays 

Fields

Instances

Instances details
Data AbsorbedDose Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: AbsorbedDose -> Constr #

dataTypeOf :: AbsorbedDose -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic AbsorbedDose Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep AbsorbedDose :: Type -> Type #

Read AbsorbedDose Source # 
Instance details

Defined in Math.Number.Units

Show AbsorbedDose Source # 
Instance details

Defined in Math.Number.Units

Binary AbsorbedDose Source # 
Instance details

Defined in Math.Number.Units

NormedSpace AbsorbedDose Source # 
Instance details

Defined in Math.Number.Units

VectorSpace AbsorbedDose Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar AbsorbedDose Source #

LiteralUnit AbsorbedDose Source # 
Instance details

Defined in Math.Number.Units

Unit AbsorbedDose Source # 
Instance details

Defined in Math.Number.Units

Eq AbsorbedDose Source # 
Instance details

Defined in Math.Number.Units

Ord AbsorbedDose Source # 
Instance details

Defined in Math.Number.Units

type Rep AbsorbedDose Source # 
Instance details

Defined in Math.Number.Units

type Rep AbsorbedDose = D1 ('MetaData "AbsorbedDose" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Grays" 'PrefixI 'True) (S1 ('MetaSel ('Just "grays") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar AbsorbedDose Source # 
Instance details

Defined in Math.Number.Units

newtype EquivalentDose Source #

Constructors

Sieverts 

Fields

Instances

Instances details
Data EquivalentDose Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: EquivalentDose -> Constr #

dataTypeOf :: EquivalentDose -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic EquivalentDose Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep EquivalentDose :: Type -> Type #

Read EquivalentDose Source # 
Instance details

Defined in Math.Number.Units

Show EquivalentDose Source # 
Instance details

Defined in Math.Number.Units

Binary EquivalentDose Source # 
Instance details

Defined in Math.Number.Units

NormedSpace EquivalentDose Source # 
Instance details

Defined in Math.Number.Units

VectorSpace EquivalentDose Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar EquivalentDose Source #

LiteralUnit EquivalentDose Source # 
Instance details

Defined in Math.Number.Units

Unit EquivalentDose Source # 
Instance details

Defined in Math.Number.Units

Eq EquivalentDose Source # 
Instance details

Defined in Math.Number.Units

Ord EquivalentDose Source # 
Instance details

Defined in Math.Number.Units

type Rep EquivalentDose Source # 
Instance details

Defined in Math.Number.Units

type Rep EquivalentDose = D1 ('MetaData "EquivalentDose" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Sieverts" 'PrefixI 'True) (S1 ('MetaSel ('Just "sieverts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar EquivalentDose Source # 
Instance details

Defined in Math.Number.Units

newtype CatalyticActivity Source #

Constructors

Katals 

Fields

Instances

Instances details
Data CatalyticActivity Source # 
Instance details

Defined in Math.Number.Units

Methods

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

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

toConstr :: CatalyticActivity -> Constr #

dataTypeOf :: CatalyticActivity -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic CatalyticActivity Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Rep CatalyticActivity :: Type -> Type #

Read CatalyticActivity Source # 
Instance details

Defined in Math.Number.Units

Show CatalyticActivity Source # 
Instance details

Defined in Math.Number.Units

Binary CatalyticActivity Source # 
Instance details

Defined in Math.Number.Units

NormedSpace CatalyticActivity Source # 
Instance details

Defined in Math.Number.Units

VectorSpace CatalyticActivity Source # 
Instance details

Defined in Math.Number.Units

Associated Types

type Scalar CatalyticActivity Source #

LiteralUnit CatalyticActivity Source # 
Instance details

Defined in Math.Number.Units

Unit CatalyticActivity Source # 
Instance details

Defined in Math.Number.Units

Eq CatalyticActivity Source # 
Instance details

Defined in Math.Number.Units

Ord CatalyticActivity Source # 
Instance details

Defined in Math.Number.Units

type Rep CatalyticActivity Source # 
Instance details

Defined in Math.Number.Units

type Rep CatalyticActivity = D1 ('MetaData "CatalyticActivity" "Math.Number.Units" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'True) (C1 ('MetaCons "Katals" 'PrefixI 'True) (S1 ('MetaSel ('Just "katals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
type Scalar CatalyticActivity Source # 
Instance details

Defined in Math.Number.Units

Orphan instances