Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type UnitSet = Set UnitInfo
- type Dim = Map UnitInfo Integer
- type Sub = Map UnitInfo Dim
- identDim :: Dim
- isIdentDim :: Dim -> Bool
- dimFromUnitInfo :: UnitInfo -> Dim
- dimFromUnitInfos :: [UnitInfo] -> Dim
- dimToUnitInfo :: Dim -> UnitInfo
- dimToUnitInfos :: Dim -> [UnitInfo]
- subFromList :: [(UnitInfo, Dim)] -> Sub
- subToList :: Sub -> [(UnitInfo, UnitInfo)]
- identSub :: Sub
- applySub :: Sub -> Dim -> Dim
- composeSubs :: Sub -> Sub -> Sub
- prop_composition :: Dim -> Sub -> Sub -> Bool
- freeDimVars :: Dim -> [UnitInfo]
- dimSimplify :: UnitSet -> Dim -> Sub
- dimToConstraint :: Dim -> Constraint
- constraintToDim :: Constraint -> Dim
- dimMultiply :: Dim -> Dim -> Dim
- dimRaisePow :: Integer -> Dim -> Dim
- dimParamEq :: Dim -> Dim -> Bool
- dimParamEqCon :: Dim -> Dim -> Bool
- normaliseDim :: Dim -> Dim
- dimFromList :: [(UnitInfo, Integer)] -> Dim
Documentation
type Dim = Map UnitInfo Integer Source #
Represents a dimension: collection of units raised to a power, multiplied together. Implemented as a map of unit -> power.
type Sub = Map UnitInfo Dim Source #
Represents a substitution: map of unit to be replaced -> dimension to replace it with.
isIdentDim :: Dim -> Bool Source #
Test for identity.
dimFromUnitInfo :: UnitInfo -> Dim Source #
Convert a UnitInfo to a Dim.
dimFromUnitInfos :: [UnitInfo] -> Dim Source #
Convert from list of implicitly multipled units into a Dim.
dimToUnitInfo :: Dim -> UnitInfo Source #
Convert a Dim into a UnitInfo.
dimToUnitInfos :: Dim -> [UnitInfo] Source #
Convert a Dim into an implicitly multipled list of units.
subFromList :: [(UnitInfo, Dim)] -> Sub Source #
Convert a list of units paired with their corresponding substitution (as a Dim) into a Sub. Note that this is equivalent to repeatedly composing substitutions, so earlier substitutions will affect later ones.
subToList :: Sub -> [(UnitInfo, UnitInfo)] Source #
Convert a Sub into an association-list format of unit mapped to unit.
prop_composition :: Dim -> Sub -> Sub -> Bool Source #
Test the composition property: f (g x) == (f . g) x
freeDimVars :: Dim -> [UnitInfo] Source #
Extract a list of 'free dimension variables' from a given Dim.
dimSimplify :: UnitSet -> Dim -> Sub Source #
The dimSimplify
algorithm as shown in Kennedy's technical report Fig 3.4.
dimToConstraint :: Dim -> Constraint Source #
Create a constraint that the given Dim is equal to the identity unit.
constraintToDim :: Constraint -> Dim Source #
Convert a Constraint into a Dim where lhs/rhs is implicitly equal to 1. Also normalise the powers by dividing by the gcd and making the largest absolute value power be positive.
dimParamEq :: Dim -> Dim -> Bool Source #
Compare two Dims, not minding the difference between UnitParam*Abs and UnitParam*Use versions of the polymorphic constructors. Varies from a 'constraint parametric equality' operator because it doesn't assume that dimRaisePow can be used arbitrarily.
dimParamEqCon :: Dim -> Dim -> Bool Source #
Similar to dimParamEq but assume that dimRaisePow can be arbitrarily applied to each of the parameters, because they now represent the unit equation 'd = 1'. In practice this means computing the GCD of the powers and dividing.
normaliseDim :: Dim -> Dim Source #
Divide the powers of a dimension by their collective GCD.