physics-0.1.2.1: dimensions, quantities and constants

Safe HaskellNone
LanguageHaskell2010

Physics.Units.Arithmetic

Documentation

value :: Coercible (f a) a => f a -> a Source #

unit :: (Num a, Functor f) => f b -> f a Source #

(*<) :: (Num x, Functor f, z ~ f x) => x -> z -> z infixl 7 Source #

(>/) :: (Fractional x, Functor f, z ~ f x) => z -> x -> z infixl 7 Source #

(/<) :: (Fractional x, Functor f, Coercible (f x) ((f ^- 1) x)) => x -> f x -> (f ^- 1) x infixl 7 Source #

(>*<) :: (Num x, Coercible (f x) x, Coercible (f' x) x, Applicative (f >*< f')) => f x -> f' x -> (f >*< f') x infixl 7 Source #

(>/<) :: (Fractional x, Coercible (f x) x, Coercible (f' x) x, Applicative (f >/< f')) => f x -> f' x -> (f >/< f') x infixl 7 Source #

(>+<) :: (Num x, Applicative f, z ~ f x) => z -> z -> z infixl 6 Source #

(>-<) :: (Num x, Applicative f, z ~ f x) => z -> z -> z infixl 6 Source #

nthRoot :: (KnownNat n, Floating x, Functor f, Coercible (f x) (NthRoot n f x)) => Proxy n -> f x -> NthRoot n f x Source #

type SquareRoot d = NthRoot 2 d Source #

squareRoot :: (Coercible (f x) (SquareRoot f x), Floating x, Functor f) => f x -> SquareRoot f x Source #

type CubeRoot d = NthRoot 3 d Source #

cubeRoot :: (Coercible (f x) (CubeRoot f x), Floating x, Functor f) => f x -> CubeRoot f x Source #

hypercube :: (KnownNat n, Num x, Functor f, Coercible (f x) ((f ^+ n) x)) => Proxy n -> f x -> (f ^+ n) x Source #

type Square d = d ^+ 2 Source #

square :: (Coercible (f x) (Square f x), Num x, Functor f) => f x -> Square f x Source #

type Cube d = d ^+ 3 Source #

cube :: (Coercible (f x) (Cube f x), Num x, Functor f) => f x -> Cube f x Source #

type Tesseract d = d ^+ 4 Source #

tesseract :: (Coercible (f x) (Tesseract f x), Num x, Functor f) => f x -> Tesseract f x Source #

type Penteract d = d ^+ 5 Source #

penteract :: (Coercible (f x) (Penteract f x), Num x, Functor f) => f x -> Penteract f x Source #

type family Plus a b where ... Source #

Equations

Plus (Negative 0) x = x 
Plus x (Negative 0) = x 
Plus (Positive 0) x = x 
Plus x (Positive 0) = x 
Plus (Positive m) (Positive n) = Positive (m + n) 
Plus (Positive m) (Negative n) = Plus (Positive (m - 1)) (Negative (n - 1)) 
Plus (Negative m) (Positive n) = Plus (Negative (m - 1)) (Positive (n - 1)) 
Plus (Negative m) (Negative n) = Negative (m + n) 

type family Negate a where ... Source #

Equations

Negate (Negative m) = Positive m 
Negate (Positive 0) = Positive 0 
Negate (Positive m) = Negative m 

type family Minus a b where ... Source #

Equations

Minus x (Negative m) = Plus x (Positive m) 
Minus x (Positive m) = Plus x (Negative m) 

type family d >*< d' where ... infixl 7 Source #

Equations

(SI i ii iii iv v vi vii) >*< (SI i' ii' iii' iv' v' vi' vii') = Pretty (SI (Plus i i') (Plus ii ii') (Plus iii iii') (Plus iv iv') (Plus v v') (Plus vi vi') (Plus vii vii')) 
(Planck i ii iii iv v) >*< (Planck i' ii' iii' iv' v') = Pretty (Planck (Plus i i') (Plus ii ii') (Plus iii iii') (Plus iv iv') (Plus v v')) 

type family d >/< d' where ... infixl 7 Source #

Equations

(SI i ii iii iv v vi vii) >/< (SI i' ii' iii' iv' v' vi' vii') = Pretty (SI (Minus i i') (Minus ii ii') (Minus iii iii') (Minus iv iv') (Minus v v') (Minus vi vi') (Minus vii vii')) 
(Planck i ii iii iv v) >/< (Planck i' ii' iii' iv' v') = Pretty (Planck (Minus i i') (Minus ii ii') (Minus iii iii') (Minus iv iv') (Minus v v')) 

type family d ^+ n where ... infixr 8 Source #

Equations

d ^+ 0 = d >/< d 
d ^+ n = d >*< (d ^+ (n - 1)) 

type family d ^- n where ... infixr 8 Source #

Equations

d ^- n = d >/< (d ^+ (n + 1)) 

type family NthRoot n d where ... Source #

Equations

NthRoot 1 d = d 
NthRoot n (SI i ii iii iv v vi vii) = SI (Divide i n) (Divide ii n) (Divide iii n) (Divide iv n) (Divide v n) (Divide vi n) (Divide vii n) 
NthRoot n (Planck i ii iii iv v) = Planck (Divide i n) (Divide ii n) (Divide iii n) (Divide iv n) (Divide v n) 

type family IsInteger a b c where ... Source #

Equations

IsInteger a b 0 = Div a b 
IsInteger a b c = TypeError (((ShowType a :<>: Text "/") :<>: ShowType b) :<>: Text ": Rational exponents are not yet supported.") 

type family Divide e n where ... Source #

Equations

Divide (Positive x) y = Positive (IsInteger x y (Mod x y)) 
Divide (Negative x) y = Negative (IsInteger x y (Mod x y)) 

type family Pretty d where ... Source #

Equations

Pretty (SI N2 N1 P3 P2 Z Z Z) = Siemens 
Pretty (SI N2 N1 P4 P2 Z Z Z) = Farad 
Pretty (SI N2 Z Z Z Z Z P1) = Lux 
Pretty (SI N1 P1 N2 Z Z Z Z) = Pascal 
Pretty (SI Z Z N1 Z Z P1 Z) = Katal 
Pretty (SI Z Z Z Z Z Z Z) = One 
Pretty (SI Z Z Z Z Z Z P1) = Candela 
Pretty (SI Z Z Z Z Z P1 Z) = Mole 
Pretty (SI Z Z Z Z P1 Z Z) = Kelvin 
Pretty (SI Z Z Z P1 Z Z Z) = Ampere 
Pretty (SI Z Z P1 Z Z Z Z) = Second 
Pretty (SI Z Z P1 P1 Z Z Z) = Coulomb 
Pretty (SI Z P1 N2 N1 Z Z Z) = Tesla 
Pretty (SI Z P1 Z Z Z Z Z) = Kilogram 
Pretty (SI P1 Z Z Z Z Z Z) = Metre 
Pretty (SI P1 P1 N2 Z Z Z Z) = Newton 
Pretty (SI P2 P1 N3 N2 Z Z Z) = Ohm 
Pretty (SI P2 P1 N3 N1 Z Z Z) = Volt 
Pretty (SI P2 P1 N3 Z Z Z Z) = Watt 
Pretty (SI P2 P1 N2 N2 Z Z Z) = Henry 
Pretty (SI P2 P1 N2 N1 Z Z Z) = Weber 
Pretty (SI P2 P1 N2 Z Z Z Z) = Joule 
Pretty d = d