numeric-prelude-0.4.4: An experimental alternative hierarchy of numeric type classes
Safe HaskellSafe-Inferred
LanguageHaskell98

Algebra.DimensionTerm

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

Instances details
C Voltage Source # 
Instance details

Defined in Algebra.DimensionTerm

C Information Source # 
Instance details

Defined in Algebra.DimensionTerm

C Temperature Source # 
Instance details

Defined in Algebra.DimensionTerm

C Angle Source # 
Instance details

Defined in Algebra.DimensionTerm

C Charge Source # 
Instance details

Defined in Algebra.DimensionTerm

C Mass Source # 
Instance details

Defined in Algebra.DimensionTerm

C Time Source # 
Instance details

Defined in Algebra.DimensionTerm

C Length Source # 
Instance details

Defined in Algebra.DimensionTerm

C Scalar Source # 
Instance details

Defined in Algebra.DimensionTerm

C a => C (Recip a) Source # 
Instance details

Defined in Algebra.DimensionTerm

(C a, C b) => C (Mul a b) Source # 
Instance details

Defined in Algebra.DimensionTerm

noValue :: C a => a Source #

Type constructors

data Scalar Source #

Constructors

Scalar 

Instances

Instances details
Show Scalar Source # 
Instance details

Defined in Algebra.DimensionTerm

IsScalar Scalar Source # 
Instance details

Defined in Algebra.DimensionTerm

C Scalar Source # 
Instance details

Defined in Algebra.DimensionTerm

data Mul a b Source #

Constructors

Mul 

Instances

Instances details
(Show a, Show b) => Show (Mul a b) Source # 
Instance details

Defined in Algebra.DimensionTerm

Methods

showsPrec :: Int -> Mul a b -> ShowS #

show :: Mul a b -> String #

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

(C a, C b) => C (Mul a b) Source # 
Instance details

Defined in Algebra.DimensionTerm

data Recip a Source #

Constructors

Recip 

Instances

Instances details
Show a => Show (Recip a) Source # 
Instance details

Defined in Algebra.DimensionTerm

Methods

showsPrec :: Int -> Recip a -> ShowS #

show :: Recip a -> String #

showList :: [Recip a] -> ShowS #

C a => C (Recip a) Source # 
Instance details

Defined in Algebra.DimensionTerm

type Sqr a = Mul a a Source #

mul :: (C a, C b) => a -> b -> Mul a b Source #

recip :: C a => a -> Recip a Source #

(%*%) :: (C a, C b) => a -> b -> Mul a b infixl 7 Source #

(%/%) :: (C a, C b) => a -> b -> Mul a (Recip b) infixl 7 Source #

Rewrites

applyLeftMul :: (C u0, C u1, C v) => (u0 -> u1) -> Mul u0 v -> Mul u1 v Source #

applyRightMul :: (C u0, C u1, C v) => (u0 -> u1) -> Mul v u0 -> Mul v u1 Source #

applyRecip :: (C u0, C u1) => (u0 -> u1) -> Recip u0 -> Recip u1 Source #

commute :: (C u0, C u1) => Mul u0 u1 -> Mul u1 u0 Source #

associateLeft :: (C u0, C u1, C u2) => Mul u0 (Mul u1 u2) -> Mul (Mul u0 u1) u2 Source #

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 -> u Source #

identityRight :: C u => Mul u Scalar -> u Source #

cancelLeft :: C u => Mul (Recip u) u -> Scalar Source #

cancelRight :: C u => Mul u (Recip u) -> Scalar Source #

invertRecip :: C u => Recip (Recip u) -> u Source #

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

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.

Methods

toScalar :: dim -> Scalar Source #

fromScalar :: Scalar -> dim Source #

Instances

Instances details
IsScalar Scalar Source # 
Instance details

Defined in Algebra.DimensionTerm

Basis dimensions

data Length Source #

Constructors

Length 

Instances

Instances details
Show Length Source # 
Instance details

Defined in Algebra.DimensionTerm

C Length Source # 
Instance details

Defined in Algebra.DimensionTerm

data Time Source #

Constructors

Time 

Instances

Instances details
Show Time Source # 
Instance details

Defined in Algebra.DimensionTerm

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

C Time Source # 
Instance details

Defined in Algebra.DimensionTerm

data Mass Source #

Constructors

Mass 

Instances

Instances details
Show Mass Source # 
Instance details

Defined in Algebra.DimensionTerm

Methods

showsPrec :: Int -> Mass -> ShowS #

show :: Mass -> String #

showList :: [Mass] -> ShowS #

C Mass Source # 
Instance details

Defined in Algebra.DimensionTerm

data Charge Source #

Constructors

Charge 

Instances

Instances details
Show Charge Source # 
Instance details

Defined in Algebra.DimensionTerm

C Charge Source # 
Instance details

Defined in Algebra.DimensionTerm

data Angle Source #

Constructors

Angle 

Instances

Instances details
Show Angle Source # 
Instance details

Defined in Algebra.DimensionTerm

Methods

showsPrec :: Int -> Angle -> ShowS #

show :: Angle -> String #

showList :: [Angle] -> ShowS #

C Angle Source # 
Instance details

Defined in Algebra.DimensionTerm

data Temperature Source #

Constructors

Temperature 

Instances

Instances details
Show Temperature Source # 
Instance details

Defined in Algebra.DimensionTerm

C Temperature Source # 
Instance details

Defined in Algebra.DimensionTerm

data Information Source #

Constructors

Information 

Instances

Instances details
Show Information Source # 
Instance details

Defined in Algebra.DimensionTerm

C Information Source # 
Instance details

Defined in Algebra.DimensionTerm

Derived dimensions

data Voltage Source #

Constructors

Voltage 

Instances

Instances details
Show Voltage Source # 
Instance details

Defined in Algebra.DimensionTerm

C Voltage Source # 
Instance details

Defined in Algebra.DimensionTerm