units-2.0: A domain-specific type system for dimensional analysis

Copyright(C) 2013 Richard Eisenberg
LicenseBSD-style (see LICENSE)
MaintainerRichard Eisenberg (eir@cis.upenn.edu)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Metrology.Z

Description

This module defines a datatype and operations to represent type-level integers. Though it's defined as part of the units package, it may be useful beyond dimensional analysis. If you have a compelling non-units use of this package, please let me (Richard, eir at cis.upenn.edu) know.

Synopsis

Documentation

data Z Source

The datatype for type-level integers.

Constructors

Zero 
S Z 
P Z 

Instances

Eq Z 
SingI Z Zero 
SEq Z (KProxy Z) 
SDecide Z (KProxy Z) 
SingI Z n0 => SingI Z (P n) 
SingI Z n0 => SingI Z (S n) 
SingKind Z (KProxy Z) 
data Sing Z where 
type (==) Z a0 b0 = Equals_1627415457 a0 b0 
type DemoteRep Z (KProxy Z) = Z 

type SZ z = Sing z Source

type family Equals_1627415457 a b :: Bool Source

Equations

Equals_1627415457 Zero Zero = True 
Equals_1627415457 (S a) (S b) = (==) a b 
Equals_1627415457 (P a) (P b) = (==) a b 
Equals_1627415457 (a :: Z) (b :: Z) = False 

zToInt :: Z -> Int Source

Convert a Z to an Int

type family Succ z :: Z Source

Add one to an integer

Equations

Succ Zero = S Zero 
Succ (P z) = z 
Succ (S z) = S (S z) 

type family Pred z :: Z Source

Subtract one from an integer

Equations

Pred Zero = P Zero 
Pred (P z) = P (P z) 
Pred (S z) = z 

type family a #+ b :: Z infixl 6 Source

Add two integers

Equations

Zero #+ z = z 
(S z1) #+ (S z2) = S (S (z1 #+ z2)) 
(S z1) #+ Zero = S z1 
(S z1) #+ (P z2) = z1 #+ z2 
(P z1) #+ (S z2) = z1 #+ z2 
(P z1) #+ Zero = P z1 
(P z1) #+ (P z2) = P (P (z1 #+ z2)) 

type family a #- b :: Z infixl 6 Source

Subtract two integers

Equations

z #- Zero = z 
(S z1) #- (S z2) = z1 #- z2 
Zero #- (S z2) = P (Zero #- z2) 
(P z1) #- (S z2) = P (P (z1 #- z2)) 
(S z1) #- (P z2) = S (S (z1 #- z2)) 
Zero #- (P z2) = S (Zero #- z2) 
(P z1) #- (P z2) = z1 #- z2 

type family a #* b :: Z infixl 7 Source

Multiply two integers

Equations

Zero #* z = Zero 
(S z1) #* z2 = (z1 #* z2) #+ z2 
(P z1) #* z2 = (z1 #* z2) #- z2 

type family NegZ z :: Z Source

Negate an integer

Equations

NegZ Zero = Zero 
NegZ (S z) = P (NegZ z) 
NegZ (P z) = S (NegZ z) 

type family a #/ b :: Z Source

Divide two integers

Equations

Zero #/ b = Zero 
a #/ (P b') = NegZ (a #/ NegZ (P b')) 
a #/ b = ZDiv b b a 

type family ZDiv counter n z :: Z Source

Helper function for division

Equations

ZDiv One n (S z') = S (z' #/ n) 
ZDiv One n (P z') = P (z' #/ n) 
ZDiv (S count') n (S z') = ZDiv count' n z' 
ZDiv (S count') n (P z') = ZDiv count' n z' 

type family a < b :: Bool Source

Less-than comparison

Equations

Zero < Zero = False 
Zero < (S n) = True 
Zero < (P n) = False 
(S n) < Zero = False 
(S n) < (S n') = n < n' 
(S n) < (P n') = False 
(P n) < Zero = True 
(P n) < (S n') = True 
(P n) < (P n') = n < n' 

type One = S Zero Source

type Two = S One Source

type Three = S Two Source

type Five = S Four Source

type MOne = P Zero Source

type MTwo = P MOne Source

pZero :: Sing Z Zero Source

This is the singleton value representing Zero at the term level and at the type level, simultaneously. Used for raising units to powers.

pThree :: Sing Z (S (S (S Zero))) Source

pFour :: Sing Z (S (S (S (S Zero)))) Source

pFive :: Sing Z (S (S (S (S (S Zero))))) Source

pMFour :: Sing Z (P (P (P (P Zero)))) Source

pMFive :: Sing Z (P (P (P (P (P Zero))))) Source

pSucc :: Sing z -> Sing (Succ z) Source

Add one to a singleton Z.

pPred :: Sing z -> Sing (Pred z) Source

Subtract one from a singleton Z.

szToInt :: Sing (z :: Z) -> Int Source

Convert a singleton Z to an Int.