numeric-prelude-0.2.2: An experimental alternative hierarchy of numeric type classes

Portabilityportable
Stabilityprovisional
Maintainernumericprelude@henning-thielemann.de

Algebra.DimensionTerm

Contents

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

Documentation

class Show a => C a Source

Instances

C Voltage 
C Information 
C Temperature 
C Angle 
C Charge 
C Mass 
C Time 
C Length 
C Scalar 
C a => C (Recip a) 
(C a, C b) => C (Mul a b) 

noValue :: C a => aSource

Type constructors

data Scalar Source

Constructors

Scalar 

data Mul a b Source

Constructors

Mul 

Instances

(Show a, Show b) => Show (Mul a b) 
(C a, C b) => C (Mul a b) 

data Recip a Source

Constructors

Recip 

Instances

Show a => Show (Recip a) 
C a => C (Recip a) 

type Sqr a = Mul a aSource

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

cancelLeft :: C u => Mul (Recip u) u -> ScalarSource

invertRecip :: C u => Recip (Recip u) -> uSource

doubleRecip :: C u => u -> Recip (Recip u)Source

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

Instances

Basis dimensions

data Length Source

Constructors

Length 

Instances

data Time Source

Constructors

Time 

Instances

data Mass Source

Constructors

Mass 

Instances

data Charge Source

Constructors

Charge 

Instances

data Angle Source

Constructors

Angle 

Instances

Derived dimensions

data Voltage Source

Constructors

Voltage 

Instances