Created
April 21, 2013 20:11
-
-
Save tmhedberg/5430903 to your computer and use it in GitHub Desktop.
Modular addition with statically inferred modulus
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE DataKinds | |
, GeneralizedNewtypeDeriving | |
, KindSignatures | |
, ScopedTypeVariables | |
#-} | |
-- | Modular addition with statically inferred modulus | |
-- | |
-- Usage example (with @DataKinds@ extension enabled): | |
-- | |
-- > (3 :: Modular 6) +% 4 == 1 -- True | |
-- | |
-- This is just an casual experiment with GHC's facilities for dependently | |
-- typed programming via singleton types; it is not production quality code! | |
module Modular where | |
import Data.Monoid | |
import GHC.TypeLits | |
newtype Modular (k :: Nat) = Mod {unMod :: Integer} deriving (Eq, Num) | |
instance Show (Modular k) where show (Mod n) = show n | |
class HasModulus m where modulus :: m | |
instance SingI k => HasModulus (Modular k) where | |
modulus = Mod $ fromSing (sing :: Sing k) | |
instance SingI k => Bounded (Modular k) where | |
minBound = Mod 0 | |
maxBound = Mod $ unMod (modulus :: Modular k) - 1 | |
(+%) :: SingI k => Modular k -> Modular k -> Modular k | |
(Mod a :: Modular k) +% Mod b = Mod $ (a + b) `mod` unMod (modulus :: Modular k) | |
instance SingI k => Monoid (Modular k) where mempty = Mod 0 | |
mappend = (+%) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment