{-# LANGUAGE TypeFamilies, DataKinds, TypeOperators, UndecidableInstances,
GADTs, PolyKinds, TemplateHaskell, ScopedTypeVariables,
EmptyCase, CPP, TypeSynonymInstances, FlexibleInstances #-}
#if __GLASGOW_HASKELL__ >= 800
{-# LANGUAGE TypeApplications #-}
#endif
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
#ifndef MIN_VERSION_singletons
#define MIN_VERSION_singletons(a,b,c) 1
#endif
module Data.Metrology.Z (
Z(..),
#if MIN_VERSION_singletons(2,6,0)
Sing, SZ(..),
#else
Sing(..), SZ,
#endif
#if MIN_VERSION_singletons(1,0,0)
ZeroSym0, SSym0, SSym1, PSym0, PSym1,
#endif
zToInt, szToInt,
Succ, Pred, Negate, type (#+), type (#-), type (#*), type (#/),
sSucc, sPred, sNegate,
type (Data.Metrology.Z.<), NonNegative,
One, Two, Three, Four, Five, MOne, MTwo, MThree, MFour, MFive,
sZero, sOne, sTwo, sThree, sFour, sFive, sMOne, sMTwo, sMThree, sMFour, sMFive,
pZero, pOne, pTwo, pThree, pFour, pFive, pMOne, pMTwo, pMThree, pMFour, pMFive,
pSucc, pPred
) where
import Data.Singletons.TH
import GHC.Exts ( Constraint )
$(singletons [d| data Z = Zero | S Z | P Z deriving Eq |])
zToInt :: Z -> Int
zToInt Zero = 0
zToInt (S z) = zToInt z + 1
zToInt (P z) = zToInt z - 1
type family Succ (z :: Z) :: Z where
Succ Zero = S Zero
Succ (P z) = z
Succ (S z) = S (S z)
type family Pred (z :: Z) :: Z where
Pred Zero = P Zero
Pred (P z) = P (P z)
Pred (S z) = z
infixl 6 #+
type family (a :: Z) #+ (b :: Z) :: Z where
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))
infixl 6 #-
type family (a :: Z) #- (b :: Z) :: Z where
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
infixl 7 #*
type family (a :: Z) #* (b :: Z) :: Z where
Zero #* z = Zero
(S z1) #* z2 = (z1 #* z2) #+ z2
(P z1) #* z2 = (z1 #* z2) #- z2
type family Negate (z :: Z) :: Z where
Negate Zero = Zero
Negate (S z) = P (Negate z)
Negate (P z) = S (Negate z)
type family (a :: Z) #/ (b :: Z) :: Z where
Zero #/ b = Zero
a #/ (P b') = Negate (a #/ (Negate (P b')))
a #/ b = ZDiv b b a
type family ZDiv (counter :: Z) (n :: Z) (z :: Z) :: Z where
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 :: Z) < (b :: Z) :: Bool where
Zero Data.Metrology.Z.< Zero = False
Zero Data.Metrology.Z.< (S n) = True
Zero Data.Metrology.Z.< (P n) = False
(S n) Data.Metrology.Z.< Zero = False
(S n) Data.Metrology.Z.< (S n') = n Data.Metrology.Z.< n'
(S n) Data.Metrology.Z.< (P n') = False
(P n) Data.Metrology.Z.< Zero = True
(P n) Data.Metrology.Z.< (S n') = True
(P n) Data.Metrology.Z.< (P n') = n Data.Metrology.Z.< n'
type family NonNegative z :: Constraint where
NonNegative Zero = ()
NonNegative (S z) = ()
type One = S Zero
type Two = S One
type Three = S Two
type Four = S Three
type Five = S Four
type MOne = P Zero
type MTwo = P MOne
type MThree = P MTwo
type MFour = P MThree
type MFive = P MFour
sZero = SZero
sOne = SS sZero
sTwo = SS sOne
sThree = SS sTwo
sFour = SS sThree
sFive = SS sFour
sMOne = SP sZero
sMTwo = SP sMOne
sMThree = SP sMTwo
sMFour = SP sMThree
sMFive = SP sMFour
sSucc :: Sing z -> Sing (Succ z)
sSucc SZero = sOne
sSucc (SS z') = SS (SS z')
sSucc (SP z') = z'
sPred :: Sing z -> Sing (Pred z)
sPred SZero = sMOne
sPred (SS z') = z'
sPred (SP z') = SP (SP z')
sNegate :: Sing z -> Sing (Negate z)
sNegate SZero = SZero
sNegate (SS z') = SP (sNegate z')
sNegate (SP z') = SS (sNegate z')
szToInt :: Sing (z :: Z) -> Int
szToInt = zToInt . fromSing
{-# DEPRECATED pZero, pOne, pTwo, pThree, pFour, pFive, pMOne, pMTwo, pMThree, pMFour, pMFive, pSucc, pPred "The singleton prefix is changing from 'p' to 's'. The 'p' versions will be removed in a future release." #-}
pZero = sZero
pOne = sOne
pTwo = sTwo
pThree = sThree
pFour = sFour
pFive = sFive
pMOne = sMOne
pMTwo = sMTwo
pMThree = sMThree
pMFour = sMFour
pMFive = sMFive
pSucc = sSucc
pPred = sPred