{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
#if MIN_VERSION_ghc(8,6,0)
{-# LANGUAGE NoStarIsType #-}
#endif
#if !MIN_VERSION_ghc(8,2,0)
{-# LANGUAGE BangPatterns #-}
#endif
{-# LANGUAGE Trustworthy #-}
{-# OPTIONS_GHC -Wno-unused-top-binds -fexpose-all-unfoldings #-}
{-# OPTIONS_HADDOCK show-extensions #-}
module GHC.TypeLits.KnownNat
(
SNatKn (..)
, KnownNat1 (..)
, KnownNat2 (..)
, KnownNat3 (..)
, SBool (..)
, boolVal
, KnownBool (..)
, SBoolKb (..)
, KnownNat2Bool (..)
, KnownBoolNat2 (..)
, nameToSymbol
)
where
#if MIN_VERSION_ghc(8,6,0)
import GHC.Natural (shiftLNatural)
#elif MIN_VERSION_ghc(8,2,0)
import Data.Bits (shiftL)
#else
import GHC.Int (Int (..))
import GHC.Integer (shiftLInteger)
#endif
import Data.Proxy (Proxy (..))
import Data.Type.Bool (If)
import GHC.Prim (Proxy#)
#if MIN_VERSION_ghc(8,2,0)
import GHC.TypeNats
(KnownNat, Nat, type (+), type (*), type (^), type (-), type (<=?), type (<=),
natVal)
#if MIN_VERSION_base(4,11,0)
import GHC.TypeNats (Div, Mod)
#endif
import GHC.TypeLits (Symbol)
import Numeric.Natural (Natural)
#else
import GHC.TypeLits
(KnownNat, Nat, Symbol, type (+), type (*), type (^), type (-), type (<=?),
type (<=), natVal)
#endif
#if MIN_VERSION_base(4,16,0)
import Data.Type.Ord (OrdCond)
#endif
import GHC.TypeLits.KnownNat.TH
newtype SNatKn (f :: Symbol) =
#if MIN_VERSION_ghc(8,2,0)
SNatKn Natural
#else
SNatKn Integer
#endif
class KnownNat1 (f :: Symbol) (a :: Nat) where
natSing1 :: SNatKn f
class KnownNat2 (f :: Symbol) (a :: Nat) (b :: Nat) where
natSing2 :: SNatKn f
class KnownNat3 (f :: Symbol) (a :: Nat) (b :: Nat) (c :: Nat) where
natSing3 :: SNatKn f
instance (KnownNat a, KnownNat b) => KnownNat2 $(nameToSymbol ''(+)) a b where
natSing2 :: SNatKn "GHC.TypeNats.+"
natSing2 = forall (f :: Symbol). Nat -> SNatKn f
SNatKn (forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @a) forall a. Num a => a -> a -> a
+ forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @b))
{-# INLINE natSing2 #-}
instance (KnownNat a, KnownNat b) => KnownNat2 $(nameToSymbol ''(*)) a b where
natSing2 :: SNatKn "GHC.TypeNats.*"
natSing2 = forall (f :: Symbol). Nat -> SNatKn f
SNatKn (forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @a) forall a. Num a => a -> a -> a
* forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @b))
{-# INLINE natSing2 #-}
instance (KnownNat a, KnownNat b) => KnownNat2 $(nameToSymbol ''(^)) a b where
natSing2 :: SNatKn "GHC.TypeNats.^"
natSing2 = let x :: Nat
x = forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @a)
y :: Nat
y = forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @b)
z :: Nat
z = case Nat
x of
Nat
2 ->
#if MIN_VERSION_ghc(8,6,0)
Nat -> Int -> Nat
shiftLNatural Nat
1 (forall a b. (Integral a, Num b) => a -> b
fromIntegral Nat
y)
#elif MIN_VERSION_ghc(8,2,0)
shiftL 1 (fromIntegral y)
#else
let !(I# y#) = fromIntegral y
in shiftLInteger 1 y#
#endif
Nat
_ -> Nat
x forall a b. (Num a, Integral b) => a -> b -> a
^ Nat
y
in forall (f :: Symbol). Nat -> SNatKn f
SNatKn Nat
z
{-# INLINE natSing2 #-}
instance (KnownNat a, KnownNat b, b <= a) => KnownNat2 $(nameToSymbol ''(-)) a b where
natSing2 :: SNatKn "GHC.TypeNats.-"
natSing2 = forall (f :: Symbol). Nat -> SNatKn f
SNatKn (forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @a) forall a. Num a => a -> a -> a
- forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @b))
{-# INLINE natSing2 #-}
#if MIN_VERSION_base(4,11,0)
instance (KnownNat x, KnownNat y, 1 <= y) => KnownNat2 $(nameToSymbol ''Div) x y where
natSing2 :: SNatKn "GHC.TypeNats.Div"
natSing2 = forall (f :: Symbol). Nat -> SNatKn f
SNatKn (forall a. Integral a => a -> a -> a
quot (forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @x)) (forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @y)))
instance (KnownNat x, KnownNat y, 1 <= y) => KnownNat2 $(nameToSymbol ''Mod) x y where
natSing2 :: SNatKn "GHC.TypeNats.Mod"
natSing2 = forall (f :: Symbol). Nat -> SNatKn f
SNatKn (forall a. Integral a => a -> a -> a
rem (forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @x)) (forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @y)))
#endif
data SBool (b :: Bool) where
SFalse :: SBool 'False
STrue :: SBool 'True
class KnownBool (b :: Bool) where
boolSing :: SBool b
instance KnownBool 'False where
boolSing :: SBool 'False
boolSing = SBool 'False
SFalse
instance KnownBool 'True where
boolSing :: SBool 'True
boolSing = SBool 'True
STrue
boolVal :: forall b proxy . KnownBool b => proxy b -> Bool
boolVal :: forall (b :: Bool) (proxy :: Bool -> Type).
KnownBool b =>
proxy b -> Bool
boolVal proxy b
_ = case forall (b :: Bool). KnownBool b => SBool b
boolSing :: SBool b of
SBool b
SFalse -> Bool
False
SBool b
_ -> Bool
True
boolVal' :: forall b . KnownBool b => Proxy# b -> Bool
boolVal' :: forall (b :: Bool). KnownBool b => Proxy# b -> Bool
boolVal' Proxy# b
_ = case forall (b :: Bool). KnownBool b => SBool b
boolSing :: SBool b of
SBool b
SFalse -> Bool
False
SBool b
_ -> Bool
True
newtype SBoolKb (f :: Symbol) = SBoolKb Bool
class KnownBoolNat2 (f :: Symbol) (a :: k) (b :: k) where
boolNatSing2 :: SBoolKb f
instance (KnownNat a, KnownNat b) => KnownBoolNat2 $(nameToSymbol ''(<=?)) a b where
boolNatSing2 :: SBoolKb "Data.Type.Ord.<=?"
boolNatSing2 = forall (f :: Symbol). Bool -> SBoolKb f
SBoolKb (forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @a) forall a. Ord a => a -> a -> Bool
<= forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @b))
{-# INLINE boolNatSing2 #-}
#if MIN_VERSION_base(4,16,0)
instance (KnownNat a, KnownNat b) => KnownBoolNat2 $(nameToSymbol ''OrdCond) a b where
boolNatSing2 :: SBoolKb "Data.Type.Ord.OrdCond"
boolNatSing2 = forall (f :: Symbol). Bool -> SBoolKb f
SBoolKb (forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @a) forall a. Ord a => a -> a -> Bool
<= forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @b))
{-# INLINE boolNatSing2 #-}
#endif
class KnownNat2Bool (f :: Symbol) (a :: Bool) (b :: k) (c :: k) where
natBoolSing3 :: SNatKn f
instance (KnownBool a, KnownNat b, KnownNat c) => KnownNat2Bool $(nameToSymbol ''If) a b c where
natBoolSing3 :: SNatKn "Data.Type.Bool.If"
natBoolSing3 = forall (f :: Symbol). Nat -> SNatKn f
SNatKn (if forall (b :: Bool) (proxy :: Bool -> Type).
KnownBool b =>
proxy b -> Bool
boolVal (forall {k} (t :: k). Proxy t
Proxy @a) then forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @b) else forall (n :: Nat) (proxy :: Nat -> Type).
KnownNat n =>
proxy n -> Nat
natVal (forall {k} (t :: k). Proxy t
Proxy @c))