module Numeric.Units.Dimensional.Dimensions.TermLevel
(
Dimension'(..),
HasDimension(..),
(*), (/), (^), recip,
dOne,
dLength, dMass, dTime, dElectricCurrent, dThermodynamicTemperature, dAmountOfSubstance, dLuminousIntensity,
asList
)
where
import Data.Monoid (Monoid(..))
import Prelude (id, (+), (), Int, Show, Eq, Ord)
import qualified Prelude as P
data Dimension' = Dim' !Int !Int !Int !Int !Int !Int !Int
deriving (Show, Eq, Ord)
instance Monoid Dimension' where
mempty = dOne
mappend = (*)
class HasDimension a where
dimension :: a -> Dimension'
instance HasDimension Dimension' where
dimension = id
dOne :: Dimension'
dOne = Dim' 0 0 0 0 0 0 0
dLength, dMass, dTime, dElectricCurrent, dThermodynamicTemperature, dAmountOfSubstance, dLuminousIntensity :: Dimension'
dLength = Dim' 1 0 0 0 0 0 0
dMass = Dim' 0 1 0 0 0 0 0
dTime = Dim' 0 0 1 0 0 0 0
dElectricCurrent = Dim' 0 0 0 1 0 0 0
dThermodynamicTemperature = Dim' 0 0 0 0 1 0 0
dAmountOfSubstance = Dim' 0 0 0 0 0 1 0
dLuminousIntensity = Dim' 0 0 0 0 0 0 1
infixr 8 ^
infixl 7 *, /
(*) :: Dimension' -> Dimension' -> Dimension'
(Dim' l m t i th n j) * (Dim' l' m' t' i' th' n' j') = Dim' (l + l') (m + m') (t + t') (i + i') (th + th') (n + n') (j + j')
(/) :: Dimension' -> Dimension' -> Dimension'
(Dim' l m t i th n j) / (Dim' l' m' t' i' th' n' j') = Dim' (l l') (m m') (t t') (i i') (th th') (n n') (j j')
(^) :: Dimension' -> Int -> Dimension'
(Dim' l m t i th n j) ^ x = Dim' (x P.* l) (x P.* m) (x P.* t) (x P.* i) (x P.* th) (x P.* n) (x P.* j)
recip :: Dimension' -> Dimension'
recip = (dOne /)
asList :: Dimension' -> [Int]
asList (Dim' l m t i th n j) = [l, m, t, i, th, n, j]