Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 4 additions & 0 deletions fin/ChangeLog.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,9 @@
# Version history for fin

## 0.3.2

- Add `SS' :: SNat n -> SNat (S n)`, pattern synonym with explicit argument.

## 0.3.1

- Support GHC-8.6.5...9.10.1
Expand Down
3 changes: 1 addition & 2 deletions fin/fin.cabal
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
cabal-version: 2.2
name: fin
version: 0.3.1
x-revision: 1
version: 0.3.2
synopsis: Nat and Fin: peano naturals and finite numbers
category: Data, Dependent Types, Singletons, Math
description:
Expand Down
2 changes: 1 addition & 1 deletion fin/src/Data/Fin.hs
Original file line number Diff line number Diff line change
Expand Up @@ -81,7 +81,7 @@ import qualified Test.QuickCheck as QC
-- >>> import qualified Data.Universe.Helpers as U
-- >>> import Data.EqP (eqp)
-- >>> import Data.OrdP (comparep)
-- >>> :set -XTypeApplications
-- >>> :set -XTypeApplications -XGADTs

-------------------------------------------------------------------------------
-- Type
Expand Down
33 changes: 32 additions & 1 deletion fin/src/Data/Type/Nat.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,13 +3,15 @@
{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}
-- | 'Nat' numbers. @DataKinds@ stuff.
--
-- This module re-exports "Data.Nat", and adds type-level things.
Expand All @@ -23,7 +25,7 @@ module Data.Type.Nat (
explicitShow,
explicitShowsPrec,
-- * Singleton
SNat(..),
SNat(SZ,SS,SS'),
snatToNat,
snatToNatural,
-- * Implicit
Expand Down Expand Up @@ -177,6 +179,35 @@ snatToNatural :: forall n. SNat n -> Natural
snatToNatural SZ = 0
snatToNatural SS = unKonst (induction (Konst 0) (kmap succ) :: Konst Natural n)

-------------------------------------------------------------------------------
-- Explicit constructor
-------------------------------------------------------------------------------

data SNat_ (n :: Nat) where
SZ_ :: SNat_ 'Z
SS_ :: SNat n -> SNat_ ('S n)

snat_ :: SNat n -> SNat_ n
snat_ SZ = SZ_
snat_ SS = SS_ snat

-- | A pattern with explicit argument
--
-- >>> let predSNat :: SNat (S n) -> SNat n; predSNat (SS' n) = n
-- >>> predSNat (SS' (SS' SZ))
-- SS
--
-- >>> reflect $ predSNat (SS' (SS' SZ))
-- 1
--
--
-- @since 0.3.2
pattern SS' :: () => (m ~ 'S n) => SNat n -> SNat m
pattern SS' n <- (snat_ -> SS_ n)
where SS' n = withSNat n SS

{-# COMPLETE SZ, SS' #-}

-------------------------------------------------------------------------------
-- Equality
-------------------------------------------------------------------------------
Expand Down