module Hardware.SiClock.Divider
where
import Data.Word
import Data.Ratio
import qualified Data.List
dividerToPVal :: Rational -> (Word32, Word32, Word32)
dividerToPVal d = (fromInteger p1,fromInteger p2,fromInteger c)
where
(a,b,c) = dividerToABC d
fl = ((128*b) `div` c)
p1 = 128 * a + fl 512
p2 = 128 * b c * fl
dividerToABC :: Rational -> (Integer, Integer, Integer)
dividerToABC divider = (a, b, c)
where
d = denominator divider
n = numerator divider
a = n `div` d
rest = (n `mod` d) % d
fraction = last $ filter (\r -> (denominator r < 0x100000))
$ approximations rest
b = numerator fraction
c = denominator fraction
approximations :: Rational -> [Rational]
approximations r
= map (\l -> fromContinuedFraction (n,l)) $ Data.List.inits cf
where
(n,cf) = toContinuedFraction r
toContinuedFraction :: Rational -> (Integer,[Integer])
toContinuedFraction r = (n `div` d , cf (n `mod` d) d)
where
n = numerator r
d = denominator r
cf 0 _ = []
cf a b = (b `div` a) : cf (b `mod` a) a
fromContinuedFraction :: (Integer,[Integer]) -> Rational
fromContinuedFraction (n,cf ) = fromInteger n + toRat cf
where
toRat :: [Integer] -> Rational
toRat [] = 0
toRat (h:r) = 1 / ( fromInteger h + toRat r)