Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
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
Instances
C Voltage Source # | |
Defined in Algebra.DimensionTerm | |
C Information Source # | |
Defined in Algebra.DimensionTerm | |
C Temperature Source # | |
Defined in Algebra.DimensionTerm | |
C Angle Source # | |
Defined in Algebra.DimensionTerm | |
C Charge Source # | |
Defined in Algebra.DimensionTerm | |
C Mass Source # | |
Defined in Algebra.DimensionTerm | |
C Time Source # | |
Defined in Algebra.DimensionTerm | |
C Length Source # | |
Defined in Algebra.DimensionTerm | |
C Scalar Source # | |
Defined in Algebra.DimensionTerm | |
C a => C (Recip a) Source # | |
Defined in Algebra.DimensionTerm | |
(C a, C b) => C (Mul a b) Source # | |
Defined in Algebra.DimensionTerm |
Type constructors
Rewrites
Example dimensions
Scalar
class C dim => IsScalar dim where Source #
This class allows defining instances that are exclusively for Scalar
dimension.
You won't want to define instances by yourself.
Basis dimensions
data Temperature Source #
Instances
Show Temperature Source # | |
Defined in Algebra.DimensionTerm showsPrec :: Int -> Temperature -> ShowS # show :: Temperature -> String # showList :: [Temperature] -> ShowS # | |
C Temperature Source # | |
Defined in Algebra.DimensionTerm |
data Information Source #
Instances
Show Information Source # | |
Defined in Algebra.DimensionTerm showsPrec :: Int -> Information -> ShowS # show :: Information -> String # showList :: [Information] -> ShowS # | |
C Information Source # | |
Defined in Algebra.DimensionTerm |