{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_HADDOCK show-extensions #-}
{-# OPTIONS_GHC -Wno-orphans #-}
{-# LANGUAGE Trustworthy #-}
module GHC.TypeLits.Extra
(
Max
, Min
, Div
, Mod
, DivMod
, DivRU
, FLog
, CLog
, Log
, GCD
, LCM
)
where
import Data.Proxy (Proxy (..))
import Data.Type.Bool (If)
import GHC.Base (Int#,isTrue#,(==#),(+#))
import GHC.Integer.Logarithms (integerLogBase#)
#if MIN_VERSION_ghc(8,2,0)
import qualified GHC.TypeNats as N
import GHC.Natural
import GHC.Prim (int2Word#)
import GHC.TypeLits
#else
import GHC.Integer (smallInteger)
import GHC.TypeLits as N
#endif
(KnownNat, Nat, type (+), type (-), type (<=), type (<=?), natVal)
#if MIN_VERSION_ghc(8,4,0)
import GHC.TypeLits (Div, Mod)
#endif
import GHC.TypeLits.KnownNat (KnownNat2 (..), SNatKn (..), nameToSymbol)
#if MIN_VERSION_ghc(8,2,0)
intToNumber :: Int# -> Natural
intToNumber :: Int# -> Natural
intToNumber x :: Int#
x = GmpLimb# -> Natural
NatS# (Int# -> GmpLimb#
int2Word# Int#
x)
#else
intToNumber :: Int# -> Integer
intToNumber x = smallInteger x
#endif
{-# INLINE intToNumber #-}
type family Max (x :: Nat) (y :: Nat) :: Nat where
Max n n = n
Max x y = If (x <=? y) y x
instance (KnownNat x, KnownNat y) => KnownNat2 $(nameToSymbol ''Max) x y where
natSing2 :: SNatKn "GHC.TypeLits.Extra.Max"
natSing2 = Natural -> SNatKn "GHC.TypeLits.Extra.Max"
forall (f :: Symbol). Natural -> SNatKn f
SNatKn (Natural -> Natural -> Natural
forall a. Ord a => a -> a -> a
max (Proxy x -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
N.natVal (Proxy x
forall k (t :: k). Proxy t
Proxy @x)) (Proxy y -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
N.natVal (Proxy y
forall k (t :: k). Proxy t
Proxy @y)))
type family Min (x :: Nat) (y :: Nat) :: Nat where
Min n n = n
Min x y = If (x <=? y) x y
instance (KnownNat x, KnownNat y) => KnownNat2 $(nameToSymbol ''Min) x y where
natSing2 :: SNatKn "GHC.TypeLits.Extra.Min"
natSing2 = Natural -> SNatKn "GHC.TypeLits.Extra.Min"
forall (f :: Symbol). Natural -> SNatKn f
SNatKn (Natural -> Natural -> Natural
forall a. Ord a => a -> a -> a
min (Proxy x -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
N.natVal (Proxy x
forall k (t :: k). Proxy t
Proxy @x)) (Proxy y -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
N.natVal (Proxy y
forall k (t :: k). Proxy t
Proxy @y)))
#if !MIN_VERSION_ghc(8,4,0)
type family Div (x :: Nat) (y :: Nat) :: Nat where
Div x 1 = x
instance (KnownNat x, KnownNat y, 1 <= y) => KnownNat2 $(nameToSymbol ''Div) x y where
natSing2 = SNatKn (quot (N.natVal (Proxy @x)) (N.natVal (Proxy @y)))
#endif
type DivRU n d = Div (n + (d - 1)) d
#if !MIN_VERSION_ghc(8,4,0)
type family Mod (x :: Nat) (y :: Nat) :: Nat where
Mod x 1 = 0
instance (KnownNat x, KnownNat y, 1 <= y) => KnownNat2 $(nameToSymbol ''Mod) x y where
natSing2 = SNatKn (rem (N.natVal (Proxy @x)) (N.natVal (Proxy @y)))
#endif
type DivMod n d = '(Div n d, Mod n d)
type family FLog (x :: Nat) (y :: Nat) :: Nat where
FLog 2 1 = 0
instance (KnownNat x, KnownNat y, 2 <= x, 1 <= y) => KnownNat2 $(nameToSymbol ''FLog) x y where
#if MIN_VERSION_ghc (8,2,0)
natSing2 :: SNatKn "GHC.TypeLits.Extra.FLog"
natSing2 = Natural -> SNatKn "GHC.TypeLits.Extra.FLog"
forall (f :: Symbol). Natural -> SNatKn f
SNatKn (Int# -> Natural
intToNumber (Integer -> Integer -> Int#
integerLogBase# (Proxy x -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy x
forall k (t :: k). Proxy t
Proxy @x)) (Proxy y -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy y
forall k (t :: k). Proxy t
Proxy @y))))
#else
natSing2 = SNatKn (intToNumber (integerLogBase# (natVal (Proxy @x)) (natVal (Proxy @y))))
#endif
type family CLog (x :: Nat) (y :: Nat) :: Nat where
CLog 2 1 = 0
instance (KnownNat x, KnownNat y, 2 <= x, 1 <= y) => KnownNat2 $(nameToSymbol ''CLog) x y where
natSing2 :: SNatKn "GHC.TypeLits.Extra.CLog"
natSing2 = let x :: Integer
x = Proxy x -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy x
forall k (t :: k). Proxy t
Proxy @x)
y :: Integer
y = Proxy y -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy y
forall k (t :: k). Proxy t
Proxy @y)
z1 :: Int#
z1 = Integer -> Integer -> Int#
integerLogBase# Integer
x Integer
y
z2 :: Int#
z2 = Integer -> Integer -> Int#
integerLogBase# Integer
x (Integer
yInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
-1)
in case Integer
y of
1 -> Natural -> SNatKn "GHC.TypeLits.Extra.CLog"
forall (f :: Symbol). Natural -> SNatKn f
SNatKn 0
_ | Int# -> Bool
isTrue# (Int#
z1 Int# -> Int# -> Int#
==# Int#
z2) -> Natural -> SNatKn "GHC.TypeLits.Extra.CLog"
forall (f :: Symbol). Natural -> SNatKn f
SNatKn (Int# -> Natural
intToNumber (Int#
z1 Int# -> Int# -> Int#
+# 1#))
| Bool
otherwise -> Natural -> SNatKn "GHC.TypeLits.Extra.CLog"
forall (f :: Symbol). Natural -> SNatKn f
SNatKn (Int# -> Natural
intToNumber Int#
z1)
type family Log (x :: Nat) (y :: Nat) :: Nat where
Log 2 1 = 0
instance (KnownNat x, KnownNat y, FLog x y ~ CLog x y) => KnownNat2 $(nameToSymbol ''Log) x y where
natSing2 :: SNatKn "GHC.TypeLits.Extra.Log"
natSing2 = Natural -> SNatKn "GHC.TypeLits.Extra.Log"
forall (f :: Symbol). Natural -> SNatKn f
SNatKn (Int# -> Natural
intToNumber (Integer -> Integer -> Int#
integerLogBase# (Proxy x -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy x
forall k (t :: k). Proxy t
Proxy @x)) (Proxy y -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy y
forall k (t :: k). Proxy t
Proxy @y))))
type family GCD (x :: Nat) (y :: Nat) :: Nat where
GCD 0 x = x
GCD x 0 = x
GCD 1 x = 1
GCD x 1 = 1
GCD x x = x
instance (KnownNat x, KnownNat y) => KnownNat2 $(nameToSymbol ''GCD) x y where
natSing2 :: SNatKn "GHC.TypeLits.Extra.GCD"
natSing2 = Natural -> SNatKn "GHC.TypeLits.Extra.GCD"
forall (f :: Symbol). Natural -> SNatKn f
SNatKn (Natural -> Natural -> Natural
forall a. Integral a => a -> a -> a
gcd (Proxy x -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
N.natVal (Proxy x
forall k (t :: k). Proxy t
Proxy @x)) (Proxy y -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
N.natVal (Proxy y
forall k (t :: k). Proxy t
Proxy @y)))
type family LCM (x :: Nat) (y :: Nat) :: Nat where
LCM 0 x = 0
LCM x 0 = 0
LCM 1 x = x
LCM x 1 = x
LCM x x = x
instance (KnownNat x, KnownNat y) => KnownNat2 $(nameToSymbol ''LCM) x y where
natSing2 :: SNatKn "GHC.TypeLits.Extra.LCM"
natSing2 = Natural -> SNatKn "GHC.TypeLits.Extra.LCM"
forall (f :: Symbol). Natural -> SNatKn f
SNatKn (Natural -> Natural -> Natural
forall a. Integral a => a -> a -> a
lcm (Proxy x -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
N.natVal (Proxy x
forall k (t :: k). Proxy t
Proxy @x)) (Proxy y -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
N.natVal (Proxy y
forall k (t :: k). Proxy t
Proxy @y)))