{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NegativeLiterals #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE Trustworthy #-}
{-# OPTIONS_GHC -fplugin=GHC.TypeLits.Normalise #-}
{-# OPTIONS_GHC -fplugin GHC.TypeLits.KnownNat.Solver #-}
{-# OPTIONS_HADDOCK show-extensions #-}
module Clash.Sized.Fixed
(
SFixed, sf, unSF
, UFixed, uf, unUF
, divide
, fLit
, fLitR
, Fixed (..), resizeF, fracShift
, NumSFixedC, ENumSFixedC, FracSFixedC, ResizeSFC, DivideSC
, NumUFixedC, ENumUFixedC, FracUFixedC, ResizeUFC, DivideUC
, NumFixedC, ENumFixedC, FracFixedC, ResizeFC, DivideC
, asRepProxy, asIntProxy
)
where
import Control.DeepSeq (NFData)
import Control.Arrow ((***), second)
import Data.Bits (Bits (..), FiniteBits)
import Data.Data (Data)
import Data.Default.Class (Default (..))
import Data.Either (isLeft)
import Data.Kind (Type)
import Text.Read (Read(..))
import Data.List (find)
import Data.Proxy (Proxy (..))
import Data.Ratio ((%), denominator, numerator)
import Data.Typeable (Typeable, TypeRep, typeRep, typeOf)
import GHC.TypeLits (KnownNat, Nat, type (+), natVal)
import GHC.TypeLits.Extra (Max)
import Language.Haskell.TH (Q, appT, conT, litT, mkName,
numTyLit, sigE)
import Language.Haskell.TH.Syntax (Lift(..))
#if MIN_VERSION_template_haskell(2,16,0)
import Language.Haskell.TH.Compat
#endif
#if MIN_VERSION_template_haskell(2,17,0)
import Language.Haskell.TH (Quote)
import qualified Language.Haskell.TH as TH
#else
import Language.Haskell.TH (TExp, TypeQ)
#endif
import Test.QuickCheck (Arbitrary, CoArbitrary)
import Clash.Class.BitPack (BitPack (..))
import Clash.Class.Num (ExtendingNum (..), SaturatingNum (..),
SaturationMode (..), boundedAdd, boundedSub,
boundedMul)
import Clash.Class.Resize (Resize (..))
import Clash.Promoted.Nat (SNat, natToNum, natToInteger)
import Clash.Class.BitPack.BitIndex (lsb, msb, split)
import Clash.Class.BitPack.BitReduction (reduceAnd, reduceOr)
import Clash.Sized.BitVector (BitVector, (++#))
import Clash.Sized.Signed (Signed)
import Clash.Sized.Unsigned (Unsigned)
import Clash.XException
(ShowX (..), NFDataX (..), isX, errorX, showsPrecXWith, fromJustX)
newtype Fixed (rep :: Nat -> Type) (int :: Nat) (frac :: Nat) =
Fixed { unFixed :: rep (int + frac) }
deriving instance NFData (rep (int + frac)) => NFData (Fixed rep int frac)
deriving instance (Typeable rep, Typeable int, Typeable frac
, Data (rep (int + frac))) => Data (Fixed rep int frac)
deriving instance Eq (rep (int + frac)) => Eq (Fixed rep int frac)
deriving instance Ord (rep (int + frac)) => Ord (Fixed rep int frac)
deriving instance Bounded (rep (int + frac)) => Bounded (Fixed rep int frac)
deriving instance Default (rep (int + frac)) => Default (Fixed rep int frac)
deriving instance Arbitrary (rep (int + frac)) => Arbitrary (Fixed rep int frac)
deriving instance CoArbitrary (rep (int + frac)) => CoArbitrary (Fixed rep int frac)
deriving instance FiniteBits (rep (int + frac)) => FiniteBits (Fixed rep int frac)
deriving instance Bits (rep (int + frac)) => Bits (Fixed rep int frac)
type SFixed = Fixed Signed
type UFixed = Fixed Unsigned
{-# INLINE sf #-}
sf
:: SNat frac
-> Signed (int + frac)
-> SFixed int frac
sf _ fRep = Fixed fRep
{-# INLINE unSF #-}
unSF :: SFixed int frac
-> Signed (int + frac)
unSF (Fixed fRep) = fRep
{-# INLINE uf #-}
uf
:: SNat frac
-> Unsigned (int + frac)
-> UFixed int frac
uf _ fRep = Fixed fRep
{-# INLINE unUF #-}
unUF :: UFixed int frac
-> Unsigned (int + frac)
unUF (Fixed fRep) = fRep
{-# INLINE asRepProxy #-}
asRepProxy :: Fixed rep int frac -> Proxy rep
asRepProxy _ = Proxy
{-# INLINE asIntProxy #-}
asIntProxy :: Fixed rep int frac -> Proxy int
asIntProxy _ = Proxy
fracShift :: KnownNat frac => Fixed rep int frac -> Int
fracShift fx = fromInteger (natVal fx)
instance ( size ~ (int + frac), KnownNat frac, Integral (rep size)
) => Show (Fixed rep int frac) where
show f@(Fixed fRep) =
i ++ "." ++ (uncurry pad . second (show . numerator) .
fromJustX . find ((==1) . denominator . snd) .
iterate (succ *** (*10)) . (,) 0 $ (nom % denom))
where
pad n str = replicate (n - length str) '0' ++ str
nF = fracShift f
fRepI = toInteger fRep
fRepI_abs = abs fRepI
i = if fRepI < 0 then '-' : show (fRepI_abs `shiftR` nF)
else show (fRepI `shiftR` nF)
nom = if fRepI < 0 then fRepI_abs .&. ((2 ^ nF) - 1)
else fRepI .&. ((2 ^ nF) - 1)
denom = 2 ^ nF
instance ( size ~ (int + frac), KnownNat frac, Integral (rep size)
) => ShowX (Fixed rep int frac) where
showsPrecX = showsPrecXWith showsPrec
instance NFDataX (rep (int + frac)) => NFDataX (Fixed rep int frac) where
deepErrorX = Fixed . errorX
rnfX f@(~(Fixed x)) = if isLeft (isX f) then () else rnfX x
hasUndefined f@(~(Fixed x)) = if isLeft (isX f) then True else hasUndefined x
ensureSpine ~(Fixed x) = Fixed x
instance (size ~ (int + frac), KnownNat frac, Bounded (rep size), Integral (rep size))
=> Read (Fixed rep int frac) where
readPrec = fLitR <$> readPrec
type ENumFixedC rep int1 frac1 int2 frac2
= ( Bounded (rep ((1 + Max int1 int2) + Max frac1 frac2))
, Num (rep ((1 + Max int1 int2) + Max frac1 frac2))
, Bits (rep ((1 + Max int1 int2) + Max frac1 frac2))
, ExtendingNum (rep (int1 + frac1)) (rep (int2 + frac2))
, MResult (rep (int1 + frac1)) (rep (int2 + frac2)) ~
rep ((int1 + int2) + (frac1 + frac2))
, KnownNat int1
, KnownNat int2
, KnownNat frac1
, KnownNat frac2
, Resize rep
)
type ENumSFixedC int1 frac1 int2 frac2
= ( KnownNat (int2 + frac2)
, KnownNat (1 + Max int1 int2 + Max frac1 frac2)
, KnownNat (Max frac1 frac2)
, KnownNat (1 + Max int1 int2)
, KnownNat (int1 + frac1)
, KnownNat frac2
, KnownNat int2
, KnownNat frac1
, KnownNat int1
)
type ENumUFixedC int1 frac1 int2 frac2 =
ENumSFixedC int1 frac1 int2 frac2
instance ENumFixedC rep int1 frac1 int2 frac2 =>
ExtendingNum (Fixed rep int1 frac1) (Fixed rep int2 frac2) where
type AResult (Fixed rep int1 frac1) (Fixed rep int2 frac2) =
Fixed rep (1 + Max int1 int2) (Max frac1 frac2)
add (Fixed f1) (Fixed f2) =
let sh1 = natToNum @(Max frac1 frac2) - natToNum @frac1 :: Int
f1R = shiftL (resize f1) sh1 :: rep ((1 + Max int1 int2) + (Max frac1 frac2))
sh2 = natToNum @(Max frac1 frac2) - natToNum @frac2 :: Int
f2R = shiftL (resize f2) sh2 :: rep ((1 + Max int1 int2) + (Max frac1 frac2))
in Fixed (f1R + f2R)
sub (Fixed f1) (Fixed f2) =
let sh1 = natToNum @(Max frac1 frac2) - natToNum @frac1 :: Int
f1R = shiftL (resize f1) sh1 :: rep ((1 + Max int1 int2) + (Max frac1 frac2))
sh2 = natToNum @(Max frac1 frac2) - natToNum @frac2 :: Int
f2R = shiftL (resize f2) sh2 :: rep ((1 + Max int1 int2) + (Max frac1 frac2))
in Fixed (f1R - f2R)
type MResult (Fixed rep int1 frac1) (Fixed rep int2 frac2) =
Fixed rep (int1 + int2) (frac1 + frac2)
mul (Fixed fRep1) (Fixed fRep2) = Fixed (mul fRep1 fRep2)
type NumFixedC rep int frac
= ( SaturatingNum (rep (int + frac))
, ExtendingNum (rep (int + frac)) (rep (int + frac))
, MResult (rep (int + frac)) (rep (int + frac)) ~
rep ((int + int) + (frac + frac))
, BitSize (rep ((int + int) + (frac + frac))) ~
(int + ((int + frac) + frac))
, BitPack (rep ((int + int) + (frac + frac)))
, Bits (rep ((int + int) + (frac + frac)))
, BitPack (rep (int + frac))
, Bits (rep (int + frac))
, Integral (rep (int + frac))
, Resize rep
, Typeable rep
, KnownNat int
, KnownNat frac
)
type NumSFixedC int frac =
( KnownNat ((int + int) + (frac + frac))
, KnownNat (frac + frac)
, KnownNat (int + int)
, KnownNat (int + frac)
, KnownNat frac
, KnownNat int
)
type NumUFixedC int frac =
NumSFixedC int frac
instance (NumFixedC rep int frac) => Num (Fixed rep int frac) where
(+) = boundedAdd
(*) = boundedMul
(-) = boundedSub
negate = boundedSub (Fixed 0)
abs (Fixed a) = Fixed (abs a)
signum (Fixed a)
| a == 0 = 0
| a < 0 = -1
| otherwise = 1
fromInteger i = let fSH = natToNum @frac
res = i `shiftL` fSH
rMax = toInteger (maxBound :: rep (int + frac))
rMin = toInteger (minBound :: rep (int + frac))
sat | res > rMax = rMax
| res < rMin = rMin
| otherwise = res
in Fixed (fromInteger sat)
instance (BitPack (rep (int + frac))) => BitPack (Fixed rep int frac) where
type BitSize (Fixed rep int frac) = BitSize (rep (int + frac))
pack (Fixed fRep) = pack fRep
unpack bv = Fixed (unpack bv)
instance (Lift (rep (int + frac)), KnownNat frac, KnownNat int, Typeable rep) =>
Lift (Fixed rep int frac) where
lift f@(Fixed fRep) = sigE [| Fixed fRep |]
(decFixed (typeRep (asRepProxy f))
(natVal (asIntProxy f))
(natVal f))
#if MIN_VERSION_template_haskell(2,16,0)
liftTyped = liftTypedFromUntyped
#endif
#if MIN_VERSION_template_haskell(2,17,0)
decFixed :: Quote m => TypeRep -> Integer -> Integer -> m TH.Type
#else
decFixed :: TypeRep -> Integer -> Integer -> TypeQ
#endif
decFixed r i f = do
foldl appT (conT ''Fixed) [ conT (mkName (show r))
, litT (numTyLit i)
, litT (numTyLit f)
]
type ResizeFC rep int1 frac1 int2 frac2
= ( Resize rep
, Ord (rep (int1 + frac1))
, Num (rep (int1 + frac1))
, Bits (rep (int1 + frac1))
, Bits (rep (int2 + frac2))
, Bounded (rep (int2 + frac2))
, KnownNat int1
, KnownNat frac1
, KnownNat int2
, KnownNat frac2
)
type ResizeSFC int1 frac1 int2 frac2
= ( KnownNat int1
, KnownNat frac1
, KnownNat int2
, KnownNat frac2
, KnownNat (int2 + frac2)
, KnownNat (int1 + frac1)
)
type ResizeUFC int1 frac1 int2 frac2 =
ResizeSFC int1 frac1 int2 frac2
{-# INLINE resizeF #-}
resizeF
:: forall rep int1 frac1 int2 frac2
. ResizeFC rep int1 frac1 int2 frac2
=> Fixed rep int1 frac1
-> Fixed rep int2 frac2
resizeF (Fixed fRep) = Fixed sat
where
fMin = minBound :: rep (int2 + frac2)
fMax = maxBound :: rep (int2 + frac2)
argSZ = natToInteger @(int1 + frac1)
resSZ = natToInteger @(int2 + frac2)
argFracSZ = natToNum @frac1
resFracSZ = natToNum @frac2
sat = if argSZ <= resSZ
then if argFracSZ <= resFracSZ
then resize fRep `shiftL` (resFracSZ - argFracSZ)
else resize fRep `shiftR` (argFracSZ - resFracSZ)
else let mask = complement (resize fMax) :: rep (int1 + frac1)
in if argFracSZ <= resFracSZ
then let shiftedL = fRep `shiftL`
(resFracSZ - argFracSZ)
shiftedL_masked = shiftedL .&. mask
shiftedL_resized = resize shiftedL
in if fRep >= 0
then if shiftedL_masked == 0
then shiftedL_resized
else fMax
else if shiftedL_masked == mask
then shiftedL_resized
else fMin
else let shiftedR = fRep `shiftR`
(argFracSZ - resFracSZ)
shiftedR_masked = shiftedR .&. mask
shiftedR_resized = resize shiftedR
in if fRep >= 0
then if shiftedR_masked == 0
then shiftedR_resized
else fMax
else if shiftedR_masked == mask
then shiftedR_resized
else fMin
fLit
:: forall rep int frac size
. ( size ~ (int + frac)
, KnownNat frac
, Bounded (rep size)
, Integral (rep size) )
=> Double
#if MIN_VERSION_template_haskell(2,17,0)
-> TH.Code Q (Fixed rep int frac)
#else
-> Q (TExp (Fixed rep int frac))
#endif
fLit a = [|| Fixed (fromInteger sat) ||]
where
rMax = toInteger (maxBound :: rep size)
rMin = toInteger (minBound :: rep size)
sat = if truncated > rMax
then rMax
else if truncated < rMin
then rMin
else truncated
truncated = truncate shifted :: Integer
shifted = a * (2 ^ (natToInteger @frac))
fLitR
:: forall rep int frac size
. ( size ~ (int + frac)
, KnownNat frac
, Bounded (rep size)
, Integral (rep size))
=> Double
-> Fixed rep int frac
fLitR a = Fixed (fromInteger sat)
where
rMax = toInteger (maxBound :: rep size)
rMin = toInteger (minBound :: rep size)
sat = if truncated > rMax
then rMax
else if truncated < rMin
then rMin
else truncated
truncated = truncate shifted :: Integer
shifted = a * (2 ^ (natToInteger @frac))
instance NumFixedC rep int frac => Enum (Fixed rep int frac) where
succ f =
let err = error $
"Enum.succ{" ++ show (typeOf f) ++ "}: tried to take 'succ' of "
++ show f ++ ", causing overflow. Use 'satSucc' and specify a "
++ "SaturationMode if you need other behavior."
in case natToInteger @int of
0 -> err
_ -> if f > satPred SatBound maxBound then
err
else
satSucc SatWrap f
pred f =
let err = error $
"Enum.pred{" ++ show (typeOf f) ++ "}: tried to take 'pred' of "
++ show f ++ ", causing negative overflow. Use 'satPred' and "
++ "specify a SaturationMode if you need other behavior."
in case natToInteger @int of
0 -> err
_ -> if f < satSucc SatBound minBound then
err
else
satPred SatWrap f
toEnum i =
if res > rMax || res < rMin then
error $ "Enum.toEnum{"
++ show (typeRep $ Proxy @(Fixed rep int frac)) ++ "}: tag ("
++ show i ++ ") is outside of bounds "
++ show ( minBound :: Fixed rep int frac
, maxBound :: Fixed rep int frac)
else
Fixed (fromInteger res)
where
sh = natToNum @frac
res = toInteger i `shiftL` sh
rMax = toInteger (maxBound :: rep (int + frac))
rMin = toInteger (minBound :: rep (int + frac))
fromEnum f@(Fixed fRep) =
if res > rMax || res < rMin then
error $ "Enum.fromEnum{" ++ show (typeOf f) ++ "}: value ("
++ show f ++ ") is outside of Int's bounds "
++ show (rMin, rMax)
else
fromInteger res
where
nF = natToNum @frac
frMask = fromInteger $ (1 `shiftL` nF) - 1
offset = if f < 0 && fRep .&. frMask /= 0 then 1 else 0
res = toInteger $ (fRep `shiftR` nF) + offset
rMax = toInteger (maxBound :: Int)
rMin = toInteger (minBound :: Int)
enumFrom x1 = enumFromTo x1 maxBound
enumFromThen (Fixed x1Rep) (Fixed x2Rep) =
map Fixed $ enumFromThen x1Rep x2Rep
enumFromTo x1@(Fixed x1Rep) y@(Fixed yRep)
| yPlusHalf < x1 = []
| closeToMax = [x1]
| otherwise = map Fixed $ enumFromThenTo
x1Rep
(unFixed $ satSucc SatWrap x1)
(unFixed $ yPlusHalf)
where
closeToMax = natToInteger @int == 0 || x1 > satPred SatBound maxBound
nF = natToNum @frac
yPlusHalf | nF == 0 = y
| isSigned yRep = y - (Fixed $ -1 `shiftL` (nF - 1))
| otherwise = y + (Fixed $ 1 `shiftL` (nF - 1))
enumFromThenTo = enumFromThenTo#
enumFromThenTo#
:: forall f rep int frac
. ( NumFixedC rep int frac
, f ~ Fixed rep int frac)
=> f
-> f
-> f
-> [f]
enumFromThenTo# x1 x2 y
| x2 == x1 = if y < x1 then
[]
else
repeat x1
| x2 > x1 = enumFromThenToUp x1 x2 y
| otherwise = enumFromThenToDown x1 x2 y
enumFromThenToUp
:: forall f rep int frac
. ( NumFixedC rep int frac
, f ~ Fixed rep int frac)
=> f
-> f
-> f
-> [f]
enumFromThenToUp x1 x2 y
| y < x1 = let y' = satAdd SatWrap y halfDelta
in if y' < x1 || (isMinusHalf && y' <= x1) then
[]
else
[x1]
| y < x2 = let x2' = satSub SatWrap x2 halfDelta
in if y > x2' || (not isMinusHalf && y >= x2') then
[x1, x2]
else
[x1]
| otherwise = let y' = satSub SatWrap y (delta `shiftR` 1)
go_up x
| x' < x = [x]
| isHalf && x >= y' = [x]
| x > y' = [x]
| otherwise = x : go_up x'
where
x' = satAdd SatWrap x delta
in x1 : go_up x2
where
delta = satSub SatWrap x2 x1
halfDelta = satSub SatWrap (x2 `shiftR` 1) (x1 `shiftR` 1)
isHalf = lsb delta == 1
isMinusHalf = lsb x2 == 0 && lsb x1 == 1
enumFromThenToDown
:: forall f rep int frac
. ( NumFixedC rep int frac
, f ~ Fixed rep int frac)
=> f
-> f
-> f
-> [f]
enumFromThenToDown x1 x2 y
| y > x1 = let y' = satSub SatWrap y halfDelta
in if y' > x1 || (isMinusHalf && y' >= x1) then
[]
else
[x1]
| y > x2 = let x2' = satAdd SatWrap x2 halfDelta
in if y < x2' || (not isMinusHalf && y <= x2') then
[x1, x2]
else
[x1]
| otherwise = let y' = satAdd SatWrap y (delta `shiftR` 1)
go_dn x
| x' > x = [x]
| isHalf && x <= y' = [x]
| x < y' = [x]
| otherwise = x : go_dn x'
where
x' = satSub SatWrap x delta
in x1 : go_dn x2
where
delta = satSub SatWrap x1 x2
halfDelta = satSub SatWrap (x1 `shiftR` 1) (x2 `shiftR` 1)
isHalf = lsb delta == 1
isMinusHalf = lsb x1 == 0 && lsb x2 == 1
instance NumFixedC rep int frac => SaturatingNum (Fixed rep int frac) where
satAdd w (Fixed a) (Fixed b) = Fixed (satAdd w a b)
satSub w (Fixed a) (Fixed b) = Fixed (satSub w a b)
satMul SatWrap (Fixed a) (Fixed b) =
let res = a `mul` b
sh = natToNum @frac
res' = shiftR res sh
in Fixed (resize res')
satMul SatBound (Fixed a) (Fixed b) =
let res = a `mul` b
sh = natToNum @frac
(rL,rR) = split res :: (BitVector int, BitVector (int + frac + frac))
in case isSigned a of
True -> let overflow = complement (reduceOr (pack (msb rR) ++# pack rL)) .|.
reduceAnd (pack (msb rR) ++# pack rL)
in case overflow of
1 -> unpack (resize (shiftR rR sh))
_ -> case msb rL of
0 -> maxBound
_ -> minBound
False -> case rL of
0 -> unpack (resize (shiftR rR sh))
_ -> maxBound
satMul SatZero (Fixed a) (Fixed b) =
let res = a `mul` b
sh = natToNum @frac
(rL,rR) = split res :: (BitVector int, BitVector (int + frac + frac))
in case isSigned a of
True -> let overflow = complement (reduceOr (pack (msb rR) ++# pack rL)) .|.
reduceAnd (pack (msb rR) ++# pack rL)
in case overflow of
1 -> unpack (resize (shiftR rR sh))
_ -> 0
False -> case rL of
0 -> unpack (resize (shiftR rR sh))
_ -> 0
satMul SatError (Fixed a) (Fixed b) =
let res = a `mul` b
sh = natToNum @frac
(rL,rR) = split res :: (BitVector int, BitVector (int + frac + frac))
in case isSigned a of
True -> let overflow = complement (reduceOr (pack (msb rR) ++# pack rL)) .|.
reduceAnd (pack (msb rR) ++# pack rL)
in case overflow of
1 -> unpack (resize (shiftR rR sh))
_ -> errorX "Fixed.satMul: result exceeds bounds"
False -> case rL of
0 -> unpack (resize (shiftR rR sh))
_ -> errorX "Fixed.satMul: result exceeds maxBound"
satMul SatSymmetric (Fixed a) (Fixed b) =
let res = a `mul` b
sh = natToNum @frac
(rL,rR) = split res :: (BitVector int, BitVector (int + frac + frac))
in case isSigned a of
True -> let overflow = complement (reduceOr (pack (msb rR) ++# pack rL)) .|.
reduceAnd (pack (msb rR) ++# pack rL)
in case overflow of
1 -> unpack (resize (shiftR rR sh))
_ -> case msb rL of
0 -> maxBound
_ -> Fixed $ succ minBound
False -> case rL of
0 -> unpack (resize (shiftR rR sh))
_ -> maxBound
satSucc satMode f@(Fixed fRep) =
let sh = natToNum @frac
in case natToInteger @int of
0 -> case satMode of
SatWrap -> f
SatZero -> 0
SatError -> errorX "Fixed.satSucc: result exceeds maxBound"
_ -> maxBound
_ -> if isSigned fRep
then satSub satMode f $ Fixed $ fromInteger $ (-1) `shiftL` sh
else satAdd satMode f $ Fixed $ fromInteger $ 1 `shiftL` sh
{-# INLINE satSucc #-}
satPred satMode f@(Fixed fRep) =
let sh = natToNum @frac
symBound = if isSigned fRep
then Fixed $ minBound + 1
else minBound
in case natToInteger @int of
0 -> case satMode of
SatWrap -> f
SatBound -> minBound
SatZero -> 0
SatError -> errorX "Fixed.satPred: result exceeds minBound"
SatSymmetric -> symBound
_ -> if isSigned fRep
then satAdd satMode f $ Fixed $ fromInteger $ (-1) `shiftL` sh
else satSub satMode f $ Fixed $ fromInteger $ 1 `shiftL` sh
{-# INLINE satPred #-}
type DivideC rep int1 frac1 int2 frac2
= ( Resize rep
, Integral (rep (((int1 + frac2) + 1) + (int2 + frac1)))
, Bits (rep (((int1 + frac2) + 1) + (int2 + frac1)))
, KnownNat int1
, KnownNat frac1
, KnownNat int2
, KnownNat frac2
)
type DivideSC int1 frac1 int2 frac2
= ( KnownNat (((int1 + frac2) + 1) + (int2 + frac1))
, KnownNat frac2
, KnownNat int2
, KnownNat frac1
, KnownNat int1
)
type DivideUC int1 frac1 int2 frac2 =
DivideSC int1 frac1 int2 frac2
divide
:: DivideC rep int1 frac1 int2 frac2
=> Fixed rep int1 frac1
-> Fixed rep int2 frac2
-> Fixed rep (int1 + frac2 + 1) (int2 + frac1)
divide (Fixed fr1) fx2@(Fixed fr2) =
let int2 = fromInteger (natVal (asIntProxy fx2))
frac2 = fromInteger (natVal fx2)
fr1' = resize fr1
fr2' = resize fr2
fr1SH = shiftL fr1' ((int2 + frac2))
res = fr1SH `quot` fr2'
in Fixed res
type FracFixedC rep int frac
= ( NumFixedC rep int frac
, DivideC rep int frac int frac
)
type FracSFixedC int frac
= ( NumSFixedC int frac
, KnownNat ((int + frac + 1) + (int + frac))
)
type FracUFixedC int frac
= FracSFixedC int frac
instance FracFixedC rep int frac => Fractional (Fixed rep int frac) where
f1 / f2 = resizeF (divide f1 f2)
recip fx = resizeF (divide (1 :: Fixed rep int frac) fx)
fromRational r = res
where
res = Fixed (fromInteger sat)
sat = if res' > rMax
then rMax
else if res' < rMin then rMin else res'
rMax = toInteger (maxBound :: rep (int + frac))
rMin = toInteger (minBound :: rep (int + frac))
res' = n `div` d
frac = fromInteger (natVal res)
n = numerator r `shiftL` (2 * frac)
d = denominator r `shiftL` frac
instance NumFixedC rep int frac => Real (Fixed rep int frac) where
toRational f@(Fixed fRep) = nom % denom
where
nF = fracShift f
denom = 1 `shiftL` nF
nom = toInteger fRep
instance FracFixedC rep int frac => RealFrac (Fixed rep int frac) where
properFraction f@(Fixed fRep) = (fromIntegral whole, fract)
where
whole = (fRep `shiftR` fracShift f) + offset
fract = Fixed $ fRep - (whole `shiftL` fracShift f)
frMask = fromInteger $ (1 `shiftL` fracShift f) - 1
offset = if f < 0 && fRep .&. frMask /= 0 then 1 else 0