VRPOSMITS7VRSIJU6YNEBELCUBTHPMPJD6F6F5PE35R2KECS42KAC {-# OPTIONS_GHC -Wno-orphans #-}module Main (main) whereimport Nimbersimport Test.QuickCheckimport System.Exit (exitFailure)import Control.Monad (unless)instance Arbitrary Nimber wherearbitrary = fromInteger <$> arbitraryprop_neg :: Nimber -> Boolprop_neg a = a+a == 0prop_assoc_add :: Nimber -> Nimber -> Nimber -> Boolprop_assoc_add a b c = a+(b+c) == (a+b)+cprop_assoc_mul :: Nimber -> Nimber -> Nimber -> Boolprop_assoc_mul a b c = a*(b*c) == (a*b)*cprop_distrib :: Nimber -> Nimber -> Nimber -> Boolprop_distrib a b c = a*(b+c) == a*b+a*cmain :: IO ()main = check prop_neg >> check prop_assoc_add >> check prop_assoc_mul >> check prop_distribwhere check prop = do result <- verboseCheckResult propunless (isSuccess result) exitFailure
-- | In combinatorial game theory, nimbers represent the values of impartial games. They are the simplest way of making the ordinals into a Field.-- See /On Numbers and Games/ by John Conway.---- Nimber addition is defined by \(\alpha+\beta = \operatorname{mex}\{\alpha'+\beta, \alpha+\beta'\}\).---- Nimber multiplication is defined by \(\alpha\cdot\beta = \operatorname{mex}\{\alpha'\cdot\beta + \alpha\cdot\beta' - \alpha'\cdot\beta'\}\).---- This module implements /finite/ nimbers. The set of finite nimbers is the quadratic closure of the field with two elements.module Nimbers whereimport Data.Set qualified as Stype Natural = Int-- | A finite nimber is represented as a sum of distinct 2-powers, each of which is represented as a product of distinct Fermat 2-powers.-- Hence @'Nimber' {'getNimber' = s}@ represents \(\sum\limits_{t \in s} \prod\limits_{n \in t} 2^{2^n}\). This representation makes sums and products easy to calculate.newtype Nimber = Nimber {getNimber :: S.Set (S.Set Natural)}deriving (Show, Eq)nimberToNatural :: Nimber -> Natural-- nimberToInteger = sum . S.map ((^) @_ @Integer 2 . sum . S.map (2^)) . getNimbernimberToNatural = sum . S.map (product . S.map ((^) @_ @Natural 2 . (2 ^))) . getNimber-- | Nimbers are ordinals, so they are ordered. They also form a field, but they are not an ordered field.instance Ord Nimber wheren `compare` m = nimberToNatural n `compare` nimberToNatural minstance Enum Nimber wheretoEnum = fromInteger . fromIntegralfromEnum = fromIntegral . nimberToNaturaltwoPowers :: Natural -> S.Set NaturaltwoPowers 0 = S.emptytwoPowers m =if even mthen S.map (+ 1) $ twoPowers (m `div` 2)else S.insert 0 . S.map (+ 1) $ twoPowers (m `div` 2)delta :: (Ord a) => S.Set a -> S.Set a -> S.Set adelta x y = (x S.\\ y) `S.union` (y S.\\ x)instance Num Nimber wherefromInteger = Nimber . S.map twoPowers . twoPowers . abs . fromIntegral-- \| Finite nimber addition is calculated as follows: the nimber sum of a two-power and itself is 0, while the nimber sum of two distinct two-powers is their ordinary sum.Nimber a + Nimber b = Nimber $ (a S.\\ b) `S.union` (b S.\\ a)(-) = (+)-- \| Finite nimber multiplication is calculated as follows: the nimber square of a Fermat two-power is its sesquimultiple, while the nimber product of two distinct Fermat two-powers is their ordinary product.a * b| a == 1 = b| b == 1 = a| otherwise = sum $ dox <- S.toList $ getNimber ay <- S.toList $ getNimber blet cs = x `S.intersection` yp = product $ S.map (\c -> Nimber $ S.fromList [S.singleton c, S.fromList [0 .. c - 1]]) csd = Nimber $ S.singleton $ x `delta` y-- (*d) . Nimber . S.singleton <$> S.toList (getNimber p)pure $ p * dnegate = idabs = idsignum = idmex :: S.Set Int -> Intmex s = if 0 `notElem` s then 0 else 1 + mex (S.map (+ (-1)) s)-- | Compute nimber sum directly from the definition. This is very slow.nimberAdd :: Int -> Int -> IntnimberAdd = (!!) . (nimberSumTable !!)nimberSumTable :: [[Int]]nimberSumTable = fmap add <$> [(i,) <$> [0 ..] | i <- [0 ..]]whereadd (a, b) = mex $ S.fromList [nimberSumTable !! a' !! b | a' <- [0 .. a - 1]] `S.union` S.fromList [nimberSumTable !! a !! b' | b' <- [0 .. b - 1]]-- | Compute nimber product directly from the definition. This is very slow.nimberMul :: Int -> Int -> IntnimberMul = (!!) . (nimberProdTable !!)nimberProdTable :: [[Int]]nimberProdTable = fmap mul <$> [(i,) <$> [0 ..] | i <- [0 ..]]wheremul (a, b) = mex $ S.fromList [(nimberProdTable !! a' !! b) `nimberAdd` (nimberProdTable !! a !! b') `nimberAdd` (nimberProdTable !! a' !! b') | a' <- [0 .. a - 1], b' <- [0 .. b - 1]]
cabal-version: 3.4-- The cabal-version field refers to the version of the .cabal specification,-- and can be different from the cabal-install (the tool) version and the-- Cabal (the library) version you are using. As such, the Cabal (the library)-- version used must be equal or greater than the version stated in this field.-- Starting from the specification version 2.2, the cabal-version field must be-- the first thing in the cabal file.-- Initial package description 'nimbers' generated by-- 'cabal init'. For further documentation, see:-- http://haskell.org/cabal/users-guide/---- The name of the package.name: nimbers-- The package version.-- See the Haskell package versioning policy (PVP) for standards-- guiding when and how versions should be incremented.-- https://pvp.haskell.org-- PVP summary: +-+------- breaking API changes-- | | +----- non-breaking API additions-- | | | +--- code changes with no API changeversion: 0.1.0.0-- A short (one-line) description of the package.synopsis: finite nimbers-- A longer description of the package.-- description:-- The license under which the package is released.license: ISC-- The file containing the license text.license-file: LICENSE-- The package author(s).author: noiioiu-- An email address to which users can send suggestions, bug reports, and patches.maintainer: noiioiu@-- A copyright notice.-- copyright:category: Mathbuild-type: Simple-- Extra doc files to be distributed with the package, such as a CHANGELOG or a README.extra-doc-files: CHANGELOG.md-- Extra source files to be distributed with the package, such as examples, or a tutorial module.-- extra-source-files:common warningsghc-options: -Walllibrary-- Import common warning flags.import: warnings-- Modules exported by the library.exposed-modules: Nimbers-- Modules included in this library but not exported.-- other-modules:-- LANGUAGE extensions used by modules in this package.-- other-extensions:-- Other library packages from which modules are imported.build-depends: base >=4.16.4.0,containers,-- Directories containing source files.hs-source-dirs: src-- Base language which the package is written in.default-language: GHC2021test-suite nimbers-test-- Import common warning flags.import: warnings-- Base language which the package is written in.default-language: GHC2021-- Modules included in this executable, other than Main.-- other-modules:-- LANGUAGE extensions used by modules in this package.-- other-extensions:-- The interface type and version of the test suite.type: exitcode-stdio-1.0-- Directories containing source files.hs-source-dirs: test-- The entrypoint to the test suite.main-is: Main.hs-- Test dependencies.build-depends:base >=4.16.4.0,QuickCheck,nimbers
Copyright (c) 2024 noiioiuPermission to use, copy, modify, and/or distribute this software for any purposewith or without fee is hereby granted, provided that the above copyright noticeand this permission notice appear in all copies.THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES WITHREGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY ANDFITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY SPECIAL, DIRECT,INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER RESULTING FROM LOSSOF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF CONTRACT, NEGLIGENCE OR OTHERTORTIOUS ACTION, ARISING OUT OF OR IN CONNECTION WITH THE USE OR PERFORMANCE OFTHIS SOFTWARE.
# Revision history for nimbers## 0.1.0.0 -- YYYY-mm-dd* First version. Released on an unsuspecting world.