2

以下は、 をモデルにしたモジュール算術 Num インスタンスの実装ですData.Fixed

次のような別の実装を書きたいと思いfromRationalます。

fromRational r = case invertMod (denominator r) theModulus of
                   Just inv -> normalize $ (numerator r) * inv
                   Nothing -> error "..."

しかし、何に使うのかわかりませんtheModulus。他の型クラス関数とは異なり、Modular aを呼び出すことができるtype の値はありませんmodulus

{-# LANGUAGE NoMonomorphismRestriction #-}

import Math.NumberTheory.Moduli (invertMod)
import Data.Ratio (numerator, denominator)

class HasModulus a where
  modulus :: p a -> Integer

withType :: (p a -> f a) -> f a
withType foo = foo undefined

withModulus :: (HasModulus a) => (Integer -> f a) -> f a
withModulus foo = withType (foo . modulus)

newtype Modular a = M Integer

normalize :: HasModulus a => Integer -> Modular a
normalize x = withModulus $ \m -> M (x `mod` m)

instance (HasModulus a) => Num (Modular a) where
  (M a) + (M b) = normalize (a+b)
  (M a) - (M b) = normalize (a-b)
  (M a) * (M b) = normalize (a*b)
  negate (M a)  = normalize (-a)
  abs           = id
  signum _      = fromInteger 1
  fromInteger   = normalize

instance (HasModulus a) => Fractional (Modular a) where
  recip ma@(M a) = case invertMod a (modulus ma) of
                     Just inv -> normalize $ inv
                     Nothing  -> error "divide by zero error"
  ma / mb        = ma * (recip mb)
  fromRational r = (fromInteger $ numerator r) / (fromInteger $ denominator r)

instance (HasModulus a) => Show (Modular a) where
  show mx@(M x) = (show x) ++ " mod " ++ (show $ modulus mx)

data M5 = M5
data M7 = M7

instance HasModulus M5 where modulus _ = 5
instance HasModulus M7 where modulus _ = 7

bar = 1 / 3

main = do print $ (bar :: Modular M5)
          print $ (bar :: Modular M7)
4

2 に答える 2

1

fromRational最初の仮説に近づける方法は次のとおりです。

fromRational r = let x = case invertMod (denominator r) (modulus x) of
                           Just inv -> normalize $ (numerator r) * inv
                           Nothing -> error "..."
                 in x

結果はタイプModular aであるため、(検査せずに)それからモジュラスを取得できます。したがって、必要な場所で参照できるように、名前を付けるだけです。

于 2013-02-20T13:12:15.983 に答える
0

私はそれを理解しました...キーはwithModulus関数を使用することです:

mdivide :: HasModulus a => Integer -> Integer -> Modular a
mdivide x y = withModulus $ M . mdiv' x y
                where mdiv' x y m =
                        case invertMod y m of
                          Just inv -> (x * inv) `mod` m
                          Nothing  -> error "..."

その後...

fromRational r = mdivide (numerator r) (denominator r)
于 2013-02-20T04:35:30.150 に答える