P-Adic numbers, basic: Difference between revisions

→‎{{header|Haskell}}: changed to more complete version
(→‎{{header|Haskell}}: added Haskell solution)
(→‎{{header|Haskell}}: changed to more complete version)
Line 1,095:
 
=={{header|Haskell}}==
p-Adic numbers in this implementation are represented in floating point manner, with p-adic unit as mantissa and p-adic norm as an exponent. TextualThe presentationbase is givenencoded inimplicitly traditionalat formtype whithlevel, infiniteso partthat goingcombination toof thep-adics leftwith different bases won't typecheck.
 
Textual presentation is given in traditional form with infinite part going to the left.
<lang haskell>module Padic where
 
p-Adic arithmetics and conversion between rationals is implemented as instances of <code>Eq</code>, <code>Num</code>, <code>Fractional</code> and <code>Real</code> classes, so, they could be treated as usual real numbers (up to existence of some rationals for non-prime bases).
 
<lang haskell>{-# LANGUAGE KindSignatures, DataKinds #-}
module Padic where
 
import Data.Ratio
import Data.MaybeList (genericLength)
import GHC.TypeLits
 
data Padic =(n Padic:: {Nat) pBase ::= IntNull
, pUnit | Padic { unit :: [Int], order :: Int }
 
, pOrder :: Int }
-- valuation of the base
modulo :: (KnownNat p, Integral i) => Padic p -> i
modulo = fromIntegral . natVal
 
-- Constructor for zero value
pZero :: KnownNat p => Padic p
pZero = Padic (repeat 0) 0
 
-- Smart constructor, adjusts trailing zeros with the order.
mkPadic :: (KnownNat p, uIntegral ki) => go[i] 0-> uInt -> Padic p
mkPadic u k = go 0 (fromIntegral <$> u)
where
go 17 _ = pZero p
go i (0:u) = go (i+1) u
go i u = Padic p u (k-i)
 
-- Constructor for zerop-adic valueunit
pZeromkUnit :: Int(KnownNat p, Integral i) => [i] -> Padic p
pZeromkUnit pu = PadicmkPadic p []u 0
 
-- Zero test (up to 1/p^17)
isZero :: KnownNat p => Padic p -> Bool
isZero (Padic _ u _) = all (== 0) (take 17 u)
isZero _ = False
 
-- p-adic norm
pNorm :: KnownNat p => Padic p -> Ratio Int
pNorm (Padic p _ k)Null = fromIntegral p ^^ (-k)undefined
pNorm p = fromIntegral (modulo p) ^^ (- order p)
 
-- test for an integerness up to p^-17
isInteger :: KnownNat p => Padic p -> Bool
isInteger Null = False
isInteger (Padic s k) = case splitAt k s of
([],i) -> length (takeWhile (==0) $ reverse (take 20 i)) > 3
_ -> False
 
-- p-adics are shown with 1/p^17 precision
instance KnownNat p => Show (Padic p) where
show (PadicNull p= u k) ="Null"
show p ++x@(Padic "-adic:u "k) ++=
show (modulo x) ++ "-adic: " ++
(case si of {[] -> "0"; _ -> si})
++ "." ++
Line 1,142 ⟶ 1,166:
showD n = [(['0'..'9']++['a'..'z']) !! n]
 
instance KnownNat p => Eq (Padic p) where
--------------------------------------------------------------------------------
a == b = isZero (a - b)
-- basic arythmetic
 
instance EqKnownNat p => Ord (Padic p) where
compare = error "Ordering is undefined fo p-adics."
a == b = isZero (a - b)
 
instance KnownNat p => Num (Padic p) where
fromInteger _0 = undefinedpZero
fromInteger n = pAdic (fromInteger n)
 
x@(Padic p a ka) + Padic _ b kb = mkPadic p s k
where
k = ka `max` kb
s = addMod p (replicate (k-ka) 0 ++ a) (replicate (k-kb) 0 ++modulo bx)
(replicate (k-ka) 0 ++ a)
(replicate (k-kb) 0 ++ b)
_ + _ = Null
 
x@(Padic p a ka) * Padic _ b kb = mkPadic p (mulMod p a b) (ka + kb)
mkPadic (mulMod (modulo x) a b) (ka + kb)
_ * _ = Null
negate x@(Padic u k) =
case map (\y -> modulo x - 1 - y) u of
n:ns -> Padic ((n+1):ns) k
[] -> pZero
negate _ = Null
abs p = pAdic (pNorm p)
 
signum = undefined
negate (Padic p u k) =
case map (\x -> p - 1 - x) u of
n:ns -> Padic p ((n+1):ns) k
[] -> pZero p
 
------------------------------------------------------------
abs p = fromRat (pBase p) (pNorm p)
-- conversion from rationals to p-adics
 
instance KnownNat p => Fractional (Padic p) where
signum = undefined
fromRational = pAdic
recip Null = Null
recip x@(Padic (u:us) k)
| isZero x = Null
| gcd p u /= 1 = Null
| otherwise = mkPadic res (-k)
where
p = modulo x
res = longDivMod p (1:repeat 0) (u:us)
 
pAdic :: (Show i, Integral i, KnownNat p)
--------------------------------------------------------------------------------
=> Ratio i -> Padic p
-- conversion between rationals and p-adics
pAdic 0 = pZero
 
pAdic x = res
fromRat :: Int -> Ratio Int -> Padic
fromRat p 0 = pZero p
fromRat p x = mkPadic p (series n) k
where
p = modulo res
(k, q) = getUnit p x
(n, d) = (numerator q, denominator q)
res = maybe Null process $ recipMod p d
r = fromMaybe
(error $ concat [show x, " can't be represented as "
, show p, "-adic."])
(recipMod p d)
series n
| n == 0 = repeat 0
| n `mod` p == 0 = 0 : series (n `div` p)
| otherwise =
let m = (n * r) `mod` p
in m : series ((n - m * d) `div` p)
 
process r = mkPadic (series n) k
-- rational reconstruction
where
toRat :: Padic -> Ratio Int
series n
toRat x@(Padic p s k) =
| n == 0 = repeat 0
(fromBase p (pUnit i) * (p^(- pOrder i))) % length d
| n `mod` p == 0 = 0 : series (n `div` p)
where
| otherwise =
(d, i:_) = break isInteger $ iterate (x +) $ pZero p
fromBase p = foldr (\x r -> r*p + x) 0let .m take= 20(n * r) `mod` p
in m : series ((n - m * d) `div` p)
 
------------------------------------------------------------
-- conversion from p-adics to rationals
-- works for relatively small denominators
 
instance KnownNat p => Real (Padic p) where
toRational Null = error "no rational representation!"
toRational x@(Padic s k) = res
where
p = modulo x
res = case break isInteger $ take 10000 $ iterate (x +) x of
(_,[]) -> - toRational (- x)
(d, i:_) -> (fromBase p (unit i) * (p^(- order i))) % (genericLength d + 1)
fromBase p = foldr (\x r -> r*p + x) 0 .
take 20 . map fromIntegral
--------------------------------------------------------------------------------
-- helper functions
 
-- extracts p-adic unit from a rational number
getUnit :: IntIntegral i => i -> Ratio Inti -> (Int, Ratio Inti)
getUnit p x = (lengthgenericLength k1 - lengthgenericLength k2, c)
where
(k1,b:_) = span (\n -> denominator n `mod` p == 0) $
Line 1,204 ⟶ 1,260:
iterate (/ fromIntegral p) b
 
-- naive test for an integerness up to p^-17
isInteger :: Padic -> Bool
isInteger (Padic p s k) = case splitAt k s of
([],i) -> length (takeWhile (==0) $ reverse (take 20 i)) > 3
_ -> False
 
--------------------------------------------------------------------------------
-- helper functions
-- Reciprocal of a number modulo p (extended Euclidean algorythmalgorithm).
-- For non-prime p returns Nothing non-inveribleinvertible element of the ring.
recipMod :: IntIntegral i => i -> Inti -> Maybe Inti
recipMod p 1 = Just 1
recipMod p a | gcd p a == 1 = Just $ go 0 1 p a
Line 1,236 ⟶ 1,284:
in r : go q xs ys
 
-- MultiplicationSubtraction of sequencetwo by a numbersequences modulo p
subMod p a (b:bs) = addMod p a $ (p-b) : ((p - 1 -) <$> bs)
scaleMod p a = go 0
where
go s [] = [s]
go s (b:bs) =
let (q, r) = (a * b + s) `divMod` p
in r : go q bs
 
-- Multiplication of two sequences modulo p
mulMod p as [b] = gomulMod p [b] as
mulMod p as bs = case as of
where
go [0] =-> []repeat 0
[1] -> go (b:bs) =
[a] -> go 0 bs
let c:cs = scaleMod p b as
where
in c : addMod p (go bs) cs</lang>
go s [] = [s]
go s (b:bs) =
let (q, r) = (a * b + s) `divMod` p
in r : go q bs
as -> go bs
where
go [] = []
go (b:bs) =
let c:cs = mulMod p [b] as
in c : addMod p (go bs) cs
 
-- Division of two sequences modulo p
longDivMod p a (b:bs) = case recipMod p b of
Nothing -> error $
show b ++ " is not invertible modulo " ++ show p
Just r -> go a
where
go [] = []
go (0:xs) = 0 : go xs
go (x:xs) =
let m = (x*r) `mod` p
_:zs = subMod p (x:xs) (mulMod p [m] (b:bs))
in m : go zs</lang>
 
Convertation between rationals and p-adic numbers
<pre>λ> pZero0 :: Padic 5
5-adic: 0.0
λ> fromRat3 5:: (1/3)Padic 5
5-adic: 3.0
λ> 1/3 :: Padic 5
5-adic: 13131313131313132.0
λ> fromRat0.08 5:: (25/3)Padic 5
5-adic: 13131313131313200.0
λ> fromRat 5 (2/75)
5-adic: 31313131313131313.14
λ> fromRat 5 (2/25)
5-adic: 0.02
λ> fromRat0.08 2:: Padic (2/25)
2-adic: 1011100001010010.0
λ> fromRat0.08 7:: (2/25)Padic 7
7-adic: 36303630363036304.0
λ> toRattoRational it
2 % 25
λ> fromRatλ> 10 (25) :: Padic 10
10-adic: 25.0
λ> fromRat 10 (21/25) :: Padic 10
Null
*** Exception: 2 % 25 can't be represented as 10-adic.</pre>
λ> -12/23 :: Padic 3
3-adic: 21001011200210010.0
λ> toRational it
(-12) % 23</pre>
 
Arithmetic:
 
<pre>λ> pAdic (12/25) + pAdic (23/56) :: Padic 7
Addition and subtraction.
7-adic: 32523252325232524.2
<pre>λ> fromRat 7 (12/25) + fromRat 7 (23/567)
λ> pAdic (12/25 + 23/56) :: Padic 7
7-adic: 51251554136620421.4
7-adic: 32523252325232524.2
λ> fromRat 7 (12/25 + 23/567)
λ> toRational it
7-adic: 51251554136620421.4
1247 % 1400
λ> toRat it
λ> 12/25 + 23/56 :: Rational
7379 % 14175
1247 % 1400
λ> 12/25 + 23/567 :: Rational
λ> let x = 2/7 :: Padic 13
7379 % 14175
λ> fromRat(2*x 3- (12/25x^2) - fromRat/ 3 (23/567)
313-adic: 2021002121211001235ab53c972179036.1121
> toRational it
λ> fromRat 3 (23/567) - fromRat 3 (12/25)
8 % 49
3-adic: 2012201010112210.1102
λ> fromRatlet 17 1x == fromRat2/7 17in (1/2*x - x^2) +/ fromRat3 17:: (1/2)Rational
True8 % 49</pre>
 
=={{header|Julia}}==
Anonymous user