numeric-prelude-0.1.3: An experimental alternative hierarchy of numeric type classesSource codeContentsIndex
Algebra.DimensionTerm
Portabilityportable
Stabilityprovisional
Maintainernumericprelude@henning-thielemann.de
Contents
Type constructors
Rewrites
Example dimensions
Scalar
Basis dimensions
Derived dimensions
Description

We already have the dynamically checked physical units provided by Number.Physical and the statically checked ones of the dimensional package of Buckwalter, which require multi-parameter type classes with functional dependencies.

Here we provide a poor man's approach: The units are presented by type terms. There is no canonical form and thus the type checker can not automatically check for equal units. However, if two unit terms represent the same unit, then you can tell the type checker to rewrite one into the other.

You can add more dimensions by introducing more types of class C.

This approach is not entirely safe because you can write your own flawed rewrite rules. It is however more safe than with no units at all.

Synopsis
class Show a => C a
noValue :: C a => a
data Scalar = Scalar
data Mul a b = Mul
data Recip a = Recip
type Sqr a = Mul a a
appPrec :: Int
scalar :: Scalar
mul :: (C a, C b) => a -> b -> Mul a b
recip :: C a => a -> Recip a
(%*%) :: (C a, C b) => a -> b -> Mul a b
(%/%) :: (C a, C b) => a -> b -> Mul a (Recip b)
applyLeftMul :: (C u0, C u1, C v) => (u0 -> u1) -> Mul u0 v -> Mul u1 v
applyRightMul :: (C u0, C u1, C v) => (u0 -> u1) -> Mul v u0 -> Mul v u1
applyRecip :: (C u0, C u1) => (u0 -> u1) -> Recip u0 -> Recip u1
commute :: (C u0, C u1) => Mul u0 u1 -> Mul u1 u0
associateLeft :: (C u0, C u1, C u2) => Mul u0 (Mul u1 u2) -> Mul (Mul u0 u1) u2
associateRight :: (C u0, C u1, C u2) => Mul (Mul u0 u1) u2 -> Mul u0 (Mul u1 u2)
recipMul :: (C u0, C u1) => Recip (Mul u0 u1) -> Mul (Recip u0) (Recip u1)
mulRecip :: (C u0, C u1) => Mul (Recip u0) (Recip u1) -> Recip (Mul u0 u1)
identityLeft :: C u => Mul Scalar u -> u
identityRight :: C u => Mul u Scalar -> u
cancelLeft :: C u => Mul (Recip u) u -> Scalar
cancelRight :: C u => Mul u (Recip u) -> Scalar
invertRecip :: C u => Recip (Recip u) -> u
doubleRecip :: C u => u -> Recip (Recip u)
recipScalar :: Recip Scalar -> Scalar
class C dim => IsScalar dim where
toScalar :: dim -> Scalar
fromScalar :: Scalar -> dim
data Length = Length
data Time = Time
data Mass = Mass
data Charge = Charge
data Angle = Angle
data Temperature = Temperature
data Information = Information
length :: Length
time :: Time
mass :: Mass
charge :: Charge
angle :: Angle
temperature :: Temperature
information :: Information
type Frequency = Recip Time
frequency :: Frequency
data Voltage = Voltage
type VoltageAnalytical = Mul (Mul (Sqr Length) Mass) (Recip (Mul (Sqr Time) Charge))
voltage :: Voltage
unpackVoltage :: Voltage -> VoltageAnalytical
packVoltage :: VoltageAnalytical -> Voltage
Documentation
class Show a => C a Source
show/hide Instances
noValue :: C a => aSource
Type constructors
data Scalar Source
Constructors
Scalar
show/hide Instances
data Mul a b Source
Constructors
Mul
show/hide Instances
(Show a, Show b) => Show (Mul a b)
(C a, C b) => C (Mul a b)
data Recip a Source
Constructors
Recip
show/hide Instances
Show a => Show (Recip a)
C a => C (Recip a)
type Sqr a = Mul a aSource
appPrec :: IntSource
scalar :: ScalarSource
mul :: (C a, C b) => a -> b -> Mul a bSource
recip :: C a => a -> Recip aSource
(%*%) :: (C a, C b) => a -> b -> Mul a bSource
(%/%) :: (C a, C b) => a -> b -> Mul a (Recip b)Source
Rewrites
applyLeftMul :: (C u0, C u1, C v) => (u0 -> u1) -> Mul u0 v -> Mul u1 vSource
applyRightMul :: (C u0, C u1, C v) => (u0 -> u1) -> Mul v u0 -> Mul v u1Source
applyRecip :: (C u0, C u1) => (u0 -> u1) -> Recip u0 -> Recip u1Source
commute :: (C u0, C u1) => Mul u0 u1 -> Mul u1 u0Source
associateLeft :: (C u0, C u1, C u2) => Mul u0 (Mul u1 u2) -> Mul (Mul u0 u1) u2Source
associateRight :: (C u0, C u1, C u2) => Mul (Mul u0 u1) u2 -> Mul u0 (Mul u1 u2)Source
recipMul :: (C u0, C u1) => Recip (Mul u0 u1) -> Mul (Recip u0) (Recip u1)Source
mulRecip :: (C u0, C u1) => Mul (Recip u0) (Recip u1) -> Recip (Mul u0 u1)Source
identityLeft :: C u => Mul Scalar u -> uSource
identityRight :: C u => Mul u Scalar -> uSource
cancelLeft :: C u => Mul (Recip u) u -> ScalarSource
cancelRight :: C u => Mul u (Recip u) -> ScalarSource
invertRecip :: C u => Recip (Recip u) -> uSource
doubleRecip :: C u => u -> Recip (Recip u)Source
recipScalar :: Recip Scalar -> ScalarSource
Example dimensions
Scalar
class C dim => IsScalar dim whereSource
This class allows defining instances that are exclusively for Scalar dimension. You won't want to define instances by yourself.
Methods
toScalar :: dim -> ScalarSource
fromScalar :: Scalar -> dimSource
show/hide Instances
Basis dimensions
data Length Source
Constructors
Length
show/hide Instances
data Time Source
Constructors
Time
show/hide Instances
data Mass Source
Constructors
Mass
show/hide Instances
data Charge Source
Constructors
Charge
show/hide Instances
data Angle Source
Constructors
Angle
show/hide Instances
data Temperature Source
Constructors
Temperature
show/hide Instances
data Information Source
Constructors
Information
show/hide Instances
length :: LengthSource
time :: TimeSource
mass :: MassSource
charge :: ChargeSource
angle :: AngleSource
temperature :: TemperatureSource
information :: InformationSource
Derived dimensions
type Frequency = Recip TimeSource
frequency :: FrequencySource
data Voltage Source
Constructors
Voltage
show/hide Instances
type VoltageAnalytical = Mul (Mul (Sqr Length) Mass) (Recip (Mul (Sqr Time) Charge))Source
voltage :: VoltageSource
unpackVoltage :: Voltage -> VoltageAnalyticalSource
packVoltage :: VoltageAnalytical -> VoltageSource
Produced by Haddock version 2.4.2