Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Nat
- toNatural :: Nat -> Natural
- fromNatural :: Natural -> Nat
- cata :: a -> (a -> a) -> Nat -> a
- explicitShow :: Nat -> String
- explicitShowsPrec :: Int -> Nat -> ShowS
- data SNat (n :: Nat ) where
- snatToNat :: forall n. SNat n -> Nat
- snatToNatural :: forall n. SNat n -> Natural
- class SNatI (n :: Nat ) where
- withSNat :: SNat n -> ( SNatI n => r) -> r
- reify :: forall r. Nat -> ( forall n. SNatI n => Proxy n -> r) -> r
- reflect :: forall n proxy. SNatI n => proxy n -> Nat
- reflectToNum :: forall n m proxy. ( SNatI n, Num m) => proxy n -> m
- eqNat :: forall n m. ( SNatI n, SNatI m) => Maybe (n :~: m)
- type family EqNat (n :: Nat ) (m :: Nat ) where ...
- discreteNat :: forall n m. ( SNatI n, SNatI m) => Dec (n :~: m)
- induction :: forall n f. SNatI n => f ' Z -> ( forall m. SNatI m => f m -> f (' S m)) -> f n
- induction1 :: forall n f a. SNatI n => f ' Z a -> ( forall m. SNatI m => f m a -> f (' S m) a) -> f n a
-
class
SNatI
n =>
InlineInduction
(n ::
Nat
)
where
- inlineInduction1 :: f ' Z a -> ( forall m. InlineInduction m => f m a -> f (' S m) a) -> f n a
- inlineInduction :: forall n f. InlineInduction n => f ' Z -> ( forall m. InlineInduction m => f m -> f (' S m)) -> f n
- unfoldedFix :: forall n a proxy. InlineInduction n => proxy n -> (a -> a) -> a
- type family Plus (n :: Nat ) (m :: Nat ) :: Nat where ...
- type family Mult (n :: Nat ) (m :: Nat ) :: Nat where ...
- type family Mult2 (n :: Nat ) :: Nat where ...
- type family DivMod2 (n :: Nat ) :: ( Nat , Bool ) where ...
- type family ToGHC (n :: Nat ) :: Nat where ...
- type family FromGHC (n :: Nat ) :: Nat where ...
- nat0 :: Nat
- nat1 :: Nat
- nat2 :: Nat
- nat3 :: Nat
- nat4 :: Nat
- nat5 :: Nat
- nat6 :: Nat
- nat7 :: Nat
- nat8 :: Nat
- nat9 :: Nat
- type Nat0 = ' Z
- type Nat1 = ' S Nat0
- type Nat2 = ' S Nat1
- type Nat3 = ' S Nat2
- type Nat4 = ' S Nat3
- type Nat5 = ' S Nat4
- type Nat6 = ' S Nat5
- type Nat7 = ' S Nat6
- type Nat8 = ' S Nat7
- type Nat9 = ' S Nat8
- proofPlusZeroN :: Plus Nat0 n :~: n
- proofPlusNZero :: SNatI n => Plus n Nat0 :~: n
- proofMultZeroN :: Mult Nat0 n :~: Nat0
- proofMultNZero :: forall n proxy. SNatI n => proxy n -> Mult n Nat0 :~: Nat0
- proofMultOneN :: SNatI n => Mult Nat1 n :~: n
- proofMultNOne :: SNatI n => Mult n Nat1 :~: n
Natural, Nat numbers
Nat natural numbers.
Better than GHC's built-in
Nat
for some use cases.
Instances
Enum Nat Source # | |
Eq Nat Source # | |
Integral Nat Source # | |
Data Nat Source # | |
Defined in Data.Nat gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Nat -> c Nat Source # gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Nat Source # toConstr :: Nat -> Constr Source # dataTypeOf :: Nat -> DataType Source # dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Nat ) Source # dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Nat ) Source # gmapT :: ( forall b. Data b => b -> b) -> Nat -> Nat Source # gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Nat -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Nat -> r Source # gmapQ :: ( forall d. Data d => d -> u) -> Nat -> [u] Source # gmapQi :: Int -> ( forall d. Data d => d -> u) -> Nat -> u Source # gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Nat -> m Nat Source # gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Nat -> m Nat Source # gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Nat -> m Nat Source # |
|
Num Nat Source # | |
Ord Nat Source # | |
Real Nat Source # | |
Show Nat Source # |
To see explicit structure, use
|
Function Nat Source # | |
Arbitrary Nat Source # | |
CoArbitrary Nat Source # | |
NFData Nat Source # | |
Hashable Nat Source # | |
TestEquality SNat Source # | |
Defined in Data.Type.Nat |
fromNatural :: Natural -> Nat Source #
Showing
explicitShow :: Nat -> String Source #
Singleton
data SNat (n :: Nat ) where Source #
Singleton of
Nat
.
Instances
TestEquality SNat Source # | |
Defined in Data.Type.Nat |
|
Show ( SNat p) Source # | |
snatToNatural :: forall n. SNat n -> Natural Source #
Implicit
reify :: forall r. Nat -> ( forall n. SNatI n => Proxy n -> r) -> r Source #
Reify
Nat
.
>>>
reify nat3 reflect
3
reflect :: forall n proxy. SNatI n => proxy n -> Nat Source #
Reflect type-level
Nat
to the term level.
reflectToNum :: forall n m proxy. ( SNatI n, Num m) => proxy n -> m Source #
Equality
eqNat :: forall n m. ( SNatI n, SNatI m) => Maybe (n :~: m) Source #
Decide equality of type-level numbers.
>>>
eqNat :: Maybe (Nat3 :~: Plus Nat1 Nat2)
Just Refl
>>>
eqNat :: Maybe (Nat3 :~: Mult Nat2 Nat2)
Nothing
type family EqNat (n :: Nat ) (m :: Nat ) where ... Source #
Type family used to implement
==
from
Data.Type.Equality
module.
discreteNat :: forall n m. ( SNatI n, SNatI m) => Dec (n :~: m) Source #
Decide equality of type-level numbers.
>>>
decShow (discreteNat :: Dec (Nat3 :~: Plus Nat1 Nat2))
"Yes Refl"
Since: 0.0.3
Induction
:: forall n f. SNatI n | |
=> f ' Z |
zero case |
-> ( forall m. SNatI m => f m -> f (' S m)) |
induction step |
-> f n |
Induction on
Nat
.
Useful in proofs or with GADTs, see source of
proofPlusNZero
.
:: forall n f a. SNatI n | |
=> f ' Z a |
zero case |
-> ( forall m. SNatI m => f m a -> f (' S m) a) |
induction step |
-> f n a |
Induction on
Nat
, functor form. Useful for computation.
>>>
induction1 (Tagged 0) $ retagMap (+2) :: Tagged Nat3 Int
Tagged 6
class SNatI n => InlineInduction (n :: Nat ) where Source #
The induction will be fully inlined.
See
test/Inspection.hs
.
inlineInduction1 :: f ' Z a -> ( forall m. InlineInduction m => f m a -> f (' S m) a) -> f n a Source #
Instances
InlineInduction ' Z Source # | |
Defined in Data.Type.Nat inlineInduction1 :: f ' Z a -> ( forall (m :: Nat ). InlineInduction m => f m a -> f (' S m) a) -> f ' Z a Source # |
|
InlineInduction n => InlineInduction (' S n) Source # | |
Defined in Data.Type.Nat inlineInduction1 :: f ' Z a -> ( forall (m :: Nat ). InlineInduction m => f m a -> f (' S m) a) -> f (' S n) a Source # |
:: forall n f. InlineInduction n | |
=> f ' Z |
zero case |
-> ( forall m. InlineInduction m => f m -> f (' S m)) |
induction step |
-> f n |
See
InlineInduction
.
Example: unfoldedFix
unfoldedFix :: forall n a proxy. InlineInduction n => proxy n -> (a -> a) -> a Source #
Unfold
n
steps of a general recursion.
Note: Always benchmark . This function may give you both bad properties: a lot of code (increased binary size), and worse performance.
For known
n
unfoldedFix
will unfold recursion, for example
unfoldedFix
(Proxy
::Proxy
Nat3
) f = f (f (f (fix f)))
Arithmetic
type family Plus (n :: Nat ) (m :: Nat ) :: Nat where ... Source #
Addition.
>>>
reflect (snat :: SNat (Plus Nat1 Nat2))
3
type family Mult (n :: Nat ) (m :: Nat ) :: Nat where ... Source #
Multiplication.
>>>
reflect (snat :: SNat (Mult Nat2 Nat3))
6
type family Mult2 (n :: Nat ) :: Nat where ... Source #
Multiplication by two. Doubling.
>>>
reflect (snat :: SNat (Mult2 Nat4))
8
type family DivMod2 (n :: Nat ) :: ( Nat , Bool ) where ... Source #
Conversion to GHC Nat
type family ToGHC (n :: Nat ) :: Nat where ... Source #
Convert to GHC
Nat
.
>>>
:kind! ToGHC Nat5
ToGHC Nat5 :: GHC.Nat = 5
type family FromGHC (n :: Nat ) :: Nat where ... Source #
Convert from GHC
Nat
.
>>>
:kind! FromGHC 7
FromGHC 7 :: Nat = 'S ('S ('S ('S ('S ('S ('S 'Z))))))