{-# LANGUAGE ConstraintKinds            #-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE FlexibleContexts           #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures             #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE ScopedTypeVariables        #-}
{-# LANGUAGE StandaloneDeriving         #-}
{-# LANGUAGE TemplateHaskell            #-}
{-# LANGUAGE TypeApplications           #-}
{-# LANGUAGE TypeOperators              #-}
{-# LANGUAGE TypeFamilies               #-}
{-# LANGUAGE UndecidableInstances       #-}
{-# LANGUAGE Trustworthy #-}
{-# 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 Text.Read                  (Read(..))
import Data.List                  (find)
import Data.Maybe                 (fromJust)
import Data.Proxy                 (Proxy (..))
import Data.Ratio                 ((%), denominator, numerator)
import Data.Typeable              (Typeable, TypeRep, typeRep)
import GHC.TypeLits               (KnownNat, Nat, type (+), natVal)
import GHC.TypeLits.Extra         (Max)
import Language.Haskell.TH        (Q, TExp, TypeQ, appT, conT, litT, mkName,
                                   numTyLit, sigE)
import Language.Haskell.TH.Syntax (Lift(..))
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)
import Clash.Prelude.BitIndex     (msb, split)
import Clash.Prelude.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)
newtype Fixed (rep :: Nat -> *) (int :: Nat) (frac :: Nat) =
  Fixed { Fixed rep int frac -> rep (int + frac)
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 Enum (rep (int + frac))    => Enum (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 :: SNat frac -> Signed (int + frac) -> SFixed int frac
sf _ fRep :: Signed (int + frac)
fRep = Signed (int + frac) -> SFixed int frac
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed Signed (int + frac)
fRep
{-# INLINE unSF #-}
unSF :: SFixed int frac
     -> Signed (int + frac)
unSF :: SFixed int frac -> Signed (int + frac)
unSF (Fixed fRep :: Signed (int + frac)
fRep) = Signed (int + frac)
fRep
{-# INLINE uf #-}
uf
  :: SNat frac
  
  -> Unsigned (int + frac)
  
  -> UFixed int frac
uf :: SNat frac -> Unsigned (int + frac) -> UFixed int frac
uf _ fRep :: Unsigned (int + frac)
fRep = Unsigned (int + frac) -> UFixed int frac
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed Unsigned (int + frac)
fRep
{-# INLINE unUF #-}
unUF :: UFixed int frac
     -> Unsigned (int + frac)
unUF :: UFixed int frac -> Unsigned (int + frac)
unUF (Fixed fRep :: Unsigned (int + frac)
fRep) = Unsigned (int + frac)
fRep
{-# INLINE asRepProxy #-}
asRepProxy :: Fixed rep int frac -> Proxy rep
asRepProxy :: Fixed rep int frac -> Proxy rep
asRepProxy _ = Proxy rep
forall k (t :: k). Proxy t
Proxy
{-# INLINE asIntProxy #-}
asIntProxy :: Fixed rep int frac -> Proxy int
asIntProxy :: Fixed rep int frac -> Proxy int
asIntProxy _ = Proxy int
forall k (t :: k). Proxy t
Proxy
fracShift :: KnownNat frac => Fixed rep int frac -> Int
fracShift :: Fixed rep int frac -> Int
fracShift fx :: Fixed rep int frac
fx = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Fixed rep int frac -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal Fixed rep int frac
fx)
instance ( size ~ (int + frac), KnownNat frac, Integral (rep size)
         ) => Show (Fixed rep int frac) where
  show :: Fixed rep int frac -> String
show f :: Fixed rep int frac
f@(Fixed fRep :: rep (int + frac)
fRep) =
      String
i String -> ShowS
forall a. [a] -> [a] -> [a]
++ "." String -> ShowS
forall a. [a] -> [a] -> [a]
++ ((Int -> ShowS) -> (Int, String) -> String
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> ShowS
pad ((Int, String) -> String)
-> (Ratio Integer -> (Int, String)) -> Ratio Integer -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Ratio Integer -> String) -> (Int, Ratio Integer) -> (Int, String)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second (Integer -> String
forall a. Show a => a -> String
show (Integer -> String)
-> (Ratio Integer -> Integer) -> Ratio Integer -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Integer -> Integer
forall a. Ratio a -> a
numerator) ((Int, Ratio Integer) -> (Int, String))
-> (Ratio Integer -> (Int, Ratio Integer))
-> Ratio Integer
-> (Int, String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                   Maybe (Int, Ratio Integer) -> (Int, Ratio Integer)
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe (Int, Ratio Integer) -> (Int, Ratio Integer))
-> (Ratio Integer -> Maybe (Int, Ratio Integer))
-> Ratio Integer
-> (Int, Ratio Integer)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, Ratio Integer) -> Bool)
-> [(Int, Ratio Integer)] -> Maybe (Int, Ratio Integer)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
==1) (Integer -> Bool)
-> ((Int, Ratio Integer) -> Integer)
-> (Int, Ratio Integer)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Integer -> Integer
forall a. Ratio a -> a
denominator (Ratio Integer -> Integer)
-> ((Int, Ratio Integer) -> Ratio Integer)
-> (Int, Ratio Integer)
-> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, Ratio Integer) -> Ratio Integer
forall a b. (a, b) -> b
snd) ([(Int, Ratio Integer)] -> Maybe (Int, Ratio Integer))
-> (Ratio Integer -> [(Int, Ratio Integer)])
-> Ratio Integer
-> Maybe (Int, Ratio Integer)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                   ((Int, Ratio Integer) -> (Int, Ratio Integer))
-> (Int, Ratio Integer) -> [(Int, Ratio Integer)]
forall a. (a -> a) -> a -> [a]
iterate (Int -> Int
forall a. Enum a => a -> a
succ (Int -> Int)
-> (Ratio Integer -> Ratio Integer)
-> (Int, Ratio Integer)
-> (Int, Ratio Integer)
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** (Ratio Integer -> Ratio Integer -> Ratio Integer
forall a. Num a => a -> a -> a
*10)) ((Int, Ratio Integer) -> [(Int, Ratio Integer)])
-> (Ratio Integer -> (Int, Ratio Integer))
-> Ratio Integer
-> [(Int, Ratio Integer)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,) 0 (Ratio Integer -> String) -> Ratio Integer -> String
forall a b. (a -> b) -> a -> b
$ (Integer
nom Integer -> Integer -> Ratio Integer
forall a. Integral a => a -> a -> Ratio a
% Integer
denom))
    where
      pad :: Int -> ShowS
pad n :: Int
n str :: String
str = Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
str) '0' String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
str
      nF :: Int
nF        = Fixed rep int frac -> Int
forall (frac :: Nat) (rep :: Nat -> *) (int :: Nat).
KnownNat frac =>
Fixed rep int frac -> Int
fracShift Fixed rep int frac
f
      fRepI :: Integer
fRepI     = rep size -> Integer
forall a. Integral a => a -> Integer
toInteger rep size
rep (int + frac)
fRep
      fRepI_abs :: Integer
fRepI_abs = Integer -> Integer
forall a. Num a => a -> a
abs Integer
fRepI
      i :: String
i         = if Integer
fRepI Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< 0 then '-' Char -> ShowS
forall a. a -> [a] -> [a]
: Integer -> String
forall a. Show a => a -> String
show (Integer
fRepI_abs Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftR` Int
nF)
                               else Integer -> String
forall a. Show a => a -> String
show (Integer
fRepI Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftR` Int
nF)
      nom :: Integer
nom       = if Integer
fRepI Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< 0 then Integer
fRepI_abs Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
.&. ((2 Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ Int
nF) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- 1)
                               else Integer
fRepI Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
.&. ((2 Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ Int
nF) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- 1)
      denom :: Integer
denom     = 2 Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ Int
nF
instance ( size ~ (int + frac), KnownNat frac, Integral (rep size)
         ) => ShowX (Fixed rep int frac) where
  showsPrecX :: Int -> Fixed rep int frac -> ShowS
showsPrecX = (Int -> Fixed rep int frac -> ShowS)
-> Int -> Fixed rep int frac -> ShowS
forall a. (Int -> a -> ShowS) -> Int -> a -> ShowS
showsPrecXWith Int -> Fixed rep int frac -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec
instance NFDataX (rep (int + frac)) => NFDataX (Fixed rep int frac) where
  deepErrorX :: String -> Fixed rep int frac
deepErrorX = rep (int + frac) -> Fixed rep int frac
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed (rep (int + frac) -> Fixed rep int frac)
-> (String -> rep (int + frac)) -> String -> Fixed rep int frac
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> rep (int + frac)
forall a. HasCallStack => String -> a
errorX
  rnfX :: Fixed rep int frac -> ()
rnfX f :: Fixed rep int frac
f@(~(Fixed x :: rep (int + frac)
x)) = if Either String (Fixed rep int frac) -> Bool
forall a b. Either a b -> Bool
isLeft (Fixed rep int frac -> Either String (Fixed rep int frac)
forall a. a -> Either String a
isX Fixed rep int frac
f) then () else rep (int + frac) -> ()
forall a. NFDataX a => a -> ()
rnfX rep (int + frac)
x
instance (size ~ (int + frac), KnownNat frac, Bounded (rep size), Integral (rep size))
      => Read (Fixed rep int frac) where
  readPrec :: ReadPrec (Fixed rep int frac)
readPrec = Double -> Fixed rep int frac
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat) (size :: Nat).
(size ~ (int + frac), KnownNat frac, Bounded (rep size),
 Integral (rep size)) =>
Double -> Fixed rep int frac
fLitR (Double -> Fixed rep int frac)
-> ReadPrec Double -> ReadPrec (Fixed rep int frac)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec Double
forall a. Read a => ReadPrec a
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 rep int1 frac1
-> Fixed rep int2 frac2
-> AResult (Fixed rep int1 frac1) (Fixed rep int2 frac2)
add (Fixed f1 :: rep (int1 + frac1)
f1) (Fixed f2 :: rep (int2 + frac2)
f2) =
    let sh1 :: Int
sh1 = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy (Max frac1 frac2) -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy (Max frac1 frac2)
forall k (t :: k). Proxy t
Proxy @(Max frac1 frac2)) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Proxy frac1 -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy frac1
forall k (t :: k). Proxy t
Proxy @frac1)) :: Int
        f1R :: rep ((1 + Max int1 int2) + Max frac1 frac2)
f1R = rep ((1 + Max int1 int2) + Max frac1 frac2)
-> Int -> rep ((1 + Max int1 int2) + Max frac1 frac2)
forall a. Bits a => a -> Int -> a
shiftL (rep (int1 + frac1) -> rep ((1 + Max int1 int2) + Max frac1 frac2)
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize rep (int1 + frac1)
f1) Int
sh1 :: rep ((1 + Max int1 int2) + (Max frac1 frac2))
        sh2 :: Int
sh2 = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy (Max frac1 frac2) -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy (Max frac1 frac2)
forall k (t :: k). Proxy t
Proxy @(Max frac1 frac2)) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Proxy frac2 -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy frac2
forall k (t :: k). Proxy t
Proxy @frac2)) :: Int
        f2R :: rep ((1 + Max int1 int2) + Max frac1 frac2)
f2R = rep ((1 + Max int1 int2) + Max frac1 frac2)
-> Int -> rep ((1 + Max int1 int2) + Max frac1 frac2)
forall a. Bits a => a -> Int -> a
shiftL (rep (int2 + frac2) -> rep ((1 + Max int1 int2) + Max frac1 frac2)
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize rep (int2 + frac2)
f2) Int
sh2 :: rep ((1 + Max int1 int2) + (Max frac1 frac2))
    in  rep ((1 + Max int1 int2) + Max frac1 frac2)
-> Fixed rep (1 + Max int1 int2) (Max frac1 frac2)
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed (rep ((1 + Max int1 int2) + Max frac1 frac2)
f1R rep ((1 + Max int1 int2) + Max frac1 frac2)
-> rep ((1 + Max int1 int2) + Max frac1 frac2)
-> rep ((1 + Max int1 int2) + Max frac1 frac2)
forall a. Num a => a -> a -> a
+ rep ((1 + Max int1 int2) + Max frac1 frac2)
f2R)
  sub :: Fixed rep int1 frac1
-> Fixed rep int2 frac2
-> AResult (Fixed rep int1 frac1) (Fixed rep int2 frac2)
sub (Fixed f1 :: rep (int1 + frac1)
f1) (Fixed f2 :: rep (int2 + frac2)
f2) =
    let sh1 :: Int
sh1 = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy (Max frac1 frac2) -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy (Max frac1 frac2)
forall k (t :: k). Proxy t
Proxy @(Max frac1 frac2)) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Proxy frac1 -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy frac1
forall k (t :: k). Proxy t
Proxy @frac1)) :: Int
        f1R :: rep ((1 + Max int1 int2) + Max frac1 frac2)
f1R = rep ((1 + Max int1 int2) + Max frac1 frac2)
-> Int -> rep ((1 + Max int1 int2) + Max frac1 frac2)
forall a. Bits a => a -> Int -> a
shiftL (rep (int1 + frac1) -> rep ((1 + Max int1 int2) + Max frac1 frac2)
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize rep (int1 + frac1)
f1) Int
sh1 :: rep ((1 + Max int1 int2) + (Max frac1 frac2))
        sh2 :: Int
sh2 = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy (Max frac1 frac2) -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy (Max frac1 frac2)
forall k (t :: k). Proxy t
Proxy @(Max frac1 frac2)) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Proxy frac2 -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy frac2
forall k (t :: k). Proxy t
Proxy @frac2)) :: Int
        f2R :: rep ((1 + Max int1 int2) + Max frac1 frac2)
f2R = rep ((1 + Max int1 int2) + Max frac1 frac2)
-> Int -> rep ((1 + Max int1 int2) + Max frac1 frac2)
forall a. Bits a => a -> Int -> a
shiftL (rep (int2 + frac2) -> rep ((1 + Max int1 int2) + Max frac1 frac2)
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize rep (int2 + frac2)
f2) Int
sh2 :: rep ((1 + Max int1 int2) + (Max frac1 frac2))
    in  rep ((1 + Max int1 int2) + Max frac1 frac2)
-> Fixed rep (1 + Max int1 int2) (Max frac1 frac2)
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed (rep ((1 + Max int1 int2) + Max frac1 frac2)
f1R rep ((1 + Max int1 int2) + Max frac1 frac2)
-> rep ((1 + Max int1 int2) + Max frac1 frac2)
-> rep ((1 + Max int1 int2) + Max frac1 frac2)
forall a. Num a => a -> a -> a
- rep ((1 + Max int1 int2) + Max frac1 frac2)
f2R)
  type MResult (Fixed rep int1 frac1) (Fixed rep int2 frac2) =
               Fixed rep (int1 + int2) (frac1 + frac2)
  mul :: Fixed rep int1 frac1
-> Fixed rep int2 frac2
-> MResult (Fixed rep int1 frac1) (Fixed rep int2 frac2)
mul (Fixed fRep1 :: rep (int1 + frac1)
fRep1) (Fixed fRep2 :: rep (int2 + frac2)
fRep2) = rep ((int1 + int2) + (frac1 + frac2))
-> Fixed rep (int1 + int2) (frac1 + frac2)
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed (rep (int1 + frac1)
-> rep (int2 + frac2)
-> MResult (rep (int1 + frac1)) (rep (int2 + frac2))
forall a b. ExtendingNum a b => a -> b -> MResult a b
mul rep (int1 + frac1)
fRep1 rep (int2 + frac2)
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)))
    , KnownNat (BitSize (rep (int + frac)))
    , BitPack (rep (int + frac))
    , Enum    (rep (int + frac))
    , Bits    (rep (int + frac))
    , Ord     (rep (int + frac))
    , Resize  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
  + :: Fixed rep int frac -> Fixed rep int frac -> Fixed rep int frac
(+)              = Fixed rep int frac -> Fixed rep int frac -> Fixed rep int frac
forall a. SaturatingNum a => a -> a -> a
boundedAdd
  * :: Fixed rep int frac -> Fixed rep int frac -> Fixed rep int frac
(*)              = Fixed rep int frac -> Fixed rep int frac -> Fixed rep int frac
forall a. SaturatingNum a => a -> a -> a
boundedMul
  (-)              = Fixed rep int frac -> Fixed rep int frac -> Fixed rep int frac
forall a. SaturatingNum a => a -> a -> a
boundedSub
  negate :: Fixed rep int frac -> Fixed rep int frac
negate (Fixed a :: rep (int + frac)
a) = rep (int + frac) -> Fixed rep int frac
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed (rep (int + frac) -> rep (int + frac)
forall a. Num a => a -> a
negate rep (int + frac)
a)
  abs :: Fixed rep int frac -> Fixed rep int frac
abs    (Fixed a :: rep (int + frac)
a) = rep (int + frac) -> Fixed rep int frac
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed (rep (int + frac) -> rep (int + frac)
forall a. Num a => a -> a
abs rep (int + frac)
a)
  signum :: Fixed rep int frac -> Fixed rep int frac
signum (Fixed a :: rep (int + frac)
a)
    | rep (int + frac)
a rep (int + frac) -> rep (int + frac) -> Bool
forall a. Eq a => a -> a -> Bool
== 0       = 0
    | rep (int + frac)
a rep (int + frac) -> rep (int + frac) -> Bool
forall a. Ord a => a -> a -> Bool
<  0       = -1
    | Bool
otherwise    = 1
  fromInteger :: Integer -> Fixed rep int frac
fromInteger i :: Integer
i    = let fSH :: Int
fSH = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy frac -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy frac
forall k (t :: k). Proxy t
Proxy @frac))
                         res :: Fixed rep int frac
res = rep (int + frac) -> Fixed rep int frac
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed (Integer -> rep (int + frac)
forall a. Num a => Integer -> a
fromInteger Integer
i rep (int + frac) -> Int -> rep (int + frac)
forall a. Bits a => a -> Int -> a
`shiftL` Int
fSH)
                     in  Fixed rep int frac
res
instance (BitPack (rep (int + frac))) => BitPack (Fixed rep int frac) where
  type BitSize (Fixed rep int frac) = BitSize (rep (int + frac))
  pack :: Fixed rep int frac -> BitVector (BitSize (Fixed rep int frac))
pack   (Fixed fRep :: rep (int + frac)
fRep) = rep (int + frac) -> BitVector (BitSize (rep (int + frac)))
forall a. BitPack a => a -> BitVector (BitSize a)
pack rep (int + frac)
fRep
  unpack :: BitVector (BitSize (Fixed rep int frac)) -> Fixed rep int frac
unpack bv :: BitVector (BitSize (Fixed rep int frac))
bv           = rep (int + frac) -> Fixed rep int frac
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed (BitVector (BitSize (rep (int + frac))) -> rep (int + frac)
forall a. BitPack a => BitVector (BitSize a) -> a
unpack BitVector (BitSize (rep (int + frac)))
BitVector (BitSize (Fixed rep int frac))
bv)
instance (Lift (rep (int + frac)), KnownNat frac, KnownNat int, Typeable rep) =>
  Lift (Fixed rep int frac) where
  lift :: Fixed rep int frac -> Q Exp
lift f :: Fixed rep int frac
f@(Fixed fRep :: rep (int + frac)
fRep) = Q Exp -> TypeQ -> Q Exp
sigE [| Fixed fRep |]
                          (TypeRep -> Integer -> Integer -> TypeQ
decFixed (Proxy rep -> TypeRep
forall k (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (Fixed rep int frac -> Proxy rep
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
Fixed rep int frac -> Proxy rep
asRepProxy Fixed rep int frac
f))
                                    (Proxy int -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Fixed rep int frac -> Proxy int
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
Fixed rep int frac -> Proxy int
asIntProxy Fixed rep int frac
f))
                                    (Fixed rep int frac -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal Fixed rep int frac
f))
decFixed :: TypeRep -> Integer -> Integer -> TypeQ
decFixed :: TypeRep -> Integer -> Integer -> TypeQ
decFixed r :: TypeRep
r i :: Integer
i f :: Integer
f = do
  (TypeQ -> TypeQ -> TypeQ) -> TypeQ -> [TypeQ] -> TypeQ
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl TypeQ -> TypeQ -> TypeQ
appT (Name -> TypeQ
conT ''Fixed) [ Name -> TypeQ
conT (String -> Name
mkName (TypeRep -> String
forall a. Show a => a -> String
show TypeRep
r))
                            , TyLitQ -> TypeQ
litT (Integer -> TyLitQ
numTyLit Integer
i)
                            , TyLitQ -> TypeQ
litT (Integer -> TyLitQ
numTyLit Integer
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 rep int1 frac1 -> Fixed rep int2 frac2
resizeF (Fixed fRep :: rep (int1 + frac1)
fRep) = rep (int2 + frac2) -> Fixed rep int2 frac2
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed rep (int2 + frac2)
sat
  where
    fMin :: rep (int2 + frac2)
fMin  = rep (int2 + frac2)
forall a. Bounded a => a
minBound :: rep (int2 + frac2)
    fMax :: rep (int2 + frac2)
fMax  = rep (int2 + frac2)
forall a. Bounded a => a
maxBound :: rep (int2 + frac2)
    argSZ :: Integer
argSZ = Proxy (int1 + frac1) -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy (int1 + frac1)
forall k (t :: k). Proxy t
Proxy @(int1 + frac1))
    resSZ :: Integer
resSZ = Proxy (int2 + frac2) -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy (int2 + frac2)
forall k (t :: k). Proxy t
Proxy @(int2 + frac2))
    argFracSZ :: Int
argFracSZ = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy frac1 -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy frac1
forall k (t :: k). Proxy t
Proxy @frac1))
    resFracSZ :: Int
resFracSZ = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy frac2 -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy frac2
forall k (t :: k). Proxy t
Proxy @frac2))
    
    
    sat :: rep (int2 + frac2)
sat = if Integer
argSZ Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
resSZ
            
            then if Int
argFracSZ Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
resFracSZ
                    then rep (int1 + frac1) -> rep (int2 + frac2)
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize rep (int1 + frac1)
fRep rep (int2 + frac2) -> Int -> rep (int2 + frac2)
forall a. Bits a => a -> Int -> a
`shiftL` (Int
resFracSZ Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
argFracSZ)
                    else rep (int1 + frac1) -> rep (int2 + frac2)
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize rep (int1 + frac1)
fRep rep (int2 + frac2) -> Int -> rep (int2 + frac2)
forall a. Bits a => a -> Int -> a
`shiftR` (Int
argFracSZ Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
resFracSZ)
            
            else let mask :: rep (int1 + frac1)
mask = rep (int1 + frac1) -> rep (int1 + frac1)
forall a. Bits a => a -> a
complement (rep (int2 + frac2) -> rep (int1 + frac1)
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize rep (int2 + frac2)
fMax) :: rep (int1 + frac1)
                 in if Int
argFracSZ Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
resFracSZ
                       then let shiftedL :: rep (int1 + frac1)
shiftedL         = rep (int1 + frac1)
fRep rep (int1 + frac1) -> Int -> rep (int1 + frac1)
forall a. Bits a => a -> Int -> a
`shiftL`
                                                   (Int
resFracSZ Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
argFracSZ)
                                shiftedL_masked :: rep (int1 + frac1)
shiftedL_masked  = rep (int1 + frac1)
shiftedL rep (int1 + frac1) -> rep (int1 + frac1) -> rep (int1 + frac1)
forall a. Bits a => a -> a -> a
.&. rep (int1 + frac1)
mask
                                shiftedL_resized :: rep (int2 + frac2)
shiftedL_resized = rep (int1 + frac1) -> rep (int2 + frac2)
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize rep (int1 + frac1)
shiftedL
                            in if rep (int1 + frac1)
fRep rep (int1 + frac1) -> rep (int1 + frac1) -> Bool
forall a. Ord a => a -> a -> Bool
>= 0
                                  then if rep (int1 + frac1)
shiftedL_masked rep (int1 + frac1) -> rep (int1 + frac1) -> Bool
forall a. Eq a => a -> a -> Bool
== 0
                                          then rep (int2 + frac2)
shiftedL_resized
                                          else rep (int2 + frac2)
fMax
                                  else if rep (int1 + frac1)
shiftedL_masked rep (int1 + frac1) -> rep (int1 + frac1) -> Bool
forall a. Eq a => a -> a -> Bool
== rep (int1 + frac1)
mask
                                          then rep (int2 + frac2)
shiftedL_resized
                                          else rep (int2 + frac2)
fMin
                       else let shiftedR :: rep (int1 + frac1)
shiftedR         = rep (int1 + frac1)
fRep rep (int1 + frac1) -> Int -> rep (int1 + frac1)
forall a. Bits a => a -> Int -> a
`shiftR`
                                                   (Int
argFracSZ Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
resFracSZ)
                                shiftedR_masked :: rep (int1 + frac1)
shiftedR_masked  = rep (int1 + frac1)
shiftedR rep (int1 + frac1) -> rep (int1 + frac1) -> rep (int1 + frac1)
forall a. Bits a => a -> a -> a
.&. rep (int1 + frac1)
mask
                                shiftedR_resized :: rep (int2 + frac2)
shiftedR_resized = rep (int1 + frac1) -> rep (int2 + frac2)
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize rep (int1 + frac1)
shiftedR
                            in if rep (int1 + frac1)
fRep rep (int1 + frac1) -> rep (int1 + frac1) -> Bool
forall a. Ord a => a -> a -> Bool
>= 0
                                  then if rep (int1 + frac1)
shiftedR_masked rep (int1 + frac1) -> rep (int1 + frac1) -> Bool
forall a. Eq a => a -> a -> Bool
== 0
                                          then rep (int2 + frac2)
shiftedR_resized
                                          else rep (int2 + frac2)
fMax
                                  else if rep (int1 + frac1)
shiftedR_masked rep (int1 + frac1) -> rep (int1 + frac1) -> Bool
forall a. Eq a => a -> a -> Bool
== rep (int1 + frac1)
mask
                                          then rep (int2 + frac2)
shiftedR_resized
                                          else rep (int2 + frac2)
fMin
fLit
  :: forall rep int frac size
   . ( size ~ (int + frac)
     , KnownNat frac
     , Bounded (rep size)
     , Integral (rep size) )
  => Double
  -> Q (TExp (Fixed rep int frac))
fLit :: Double -> Q (TExp (Fixed rep int frac))
fLit a :: Double
a = [|| Fixed (fromInteger sat) ||]
  where
    rMax :: Integer
rMax      = rep size -> Integer
forall a. Integral a => a -> Integer
toInteger (rep size
forall a. Bounded a => a
maxBound :: rep size)
    rMin :: Integer
rMin      = rep size -> Integer
forall a. Integral a => a -> Integer
toInteger (rep size
forall a. Bounded a => a
minBound :: rep size)
    sat :: Integer
sat       = if Integer
truncated Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
rMax
                   then Integer
rMax
                   else if Integer
truncated Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
rMin
                           then Integer
rMin
                           else Integer
truncated
    truncated :: Integer
truncated = Double -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
truncate Double
shifted :: Integer
    shifted :: Double
shifted   = Double
a Double -> Double -> Double
forall a. Num a => a -> a -> a
* (2 Double -> Integer -> Double
forall a b. (Num a, Integral b) => a -> b -> a
^ (Proxy frac -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy frac
forall k (t :: k). Proxy t
Proxy @frac)))
fLitR
  :: forall rep int frac size
   . ( size ~ (int + frac)
     , KnownNat frac
     , Bounded (rep size)
     , Integral (rep size))
  => Double
  -> Fixed rep int frac
fLitR :: Double -> Fixed rep int frac
fLitR a :: Double
a = rep (int + frac) -> Fixed rep int frac
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed (Integer -> rep size
forall a. Num a => Integer -> a
fromInteger Integer
sat)
  where
    rMax :: Integer
rMax      = rep size -> Integer
forall a. Integral a => a -> Integer
toInteger (rep size
forall a. Bounded a => a
maxBound :: rep size)
    rMin :: Integer
rMin      = rep size -> Integer
forall a. Integral a => a -> Integer
toInteger (rep size
forall a. Bounded a => a
minBound :: rep size)
    sat :: Integer
sat       = if Integer
truncated Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
rMax
                   then Integer
rMax
                   else if Integer
truncated Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
rMin
                           then Integer
rMin
                           else Integer
truncated
    truncated :: Integer
truncated = Double -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
truncate Double
shifted :: Integer
    shifted :: Double
shifted   = Double
a Double -> Double -> Double
forall a. Num a => a -> a -> a
* (2 Double -> Integer -> Double
forall a b. (Num a, Integral b) => a -> b -> a
^ (Proxy frac -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy frac
forall k (t :: k). Proxy t
Proxy @frac)))
instance NumFixedC rep int frac => SaturatingNum (Fixed rep int frac) where
  satAdd :: SaturationMode
-> Fixed rep int frac -> Fixed rep int frac -> Fixed rep int frac
satAdd w :: SaturationMode
w (Fixed a :: rep (int + frac)
a) (Fixed b :: rep (int + frac)
b) = rep (int + frac) -> Fixed rep int frac
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed (SaturationMode
-> rep (int + frac) -> rep (int + frac) -> rep (int + frac)
forall a. SaturatingNum a => SaturationMode -> a -> a -> a
satAdd SaturationMode
w rep (int + frac)
a rep (int + frac)
b)
  satSub :: SaturationMode
-> Fixed rep int frac -> Fixed rep int frac -> Fixed rep int frac
satSub  w :: SaturationMode
w (Fixed a :: rep (int + frac)
a) (Fixed b :: rep (int + frac)
b) = rep (int + frac) -> Fixed rep int frac
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed (SaturationMode
-> rep (int + frac) -> rep (int + frac) -> rep (int + frac)
forall a. SaturatingNum a => SaturationMode -> a -> a -> a
satSub SaturationMode
w rep (int + frac)
a rep (int + frac)
b)
  satMul :: SaturationMode
-> Fixed rep int frac -> Fixed rep int frac -> Fixed rep int frac
satMul SatWrap (Fixed a :: rep (int + frac)
a) (Fixed b :: rep (int + frac)
b) =
    let res :: MResult (rep (int + frac)) (rep (int + frac))
res  = rep (int + frac)
a rep (int + frac)
-> rep (int + frac)
-> MResult (rep (int + frac)) (rep (int + frac))
forall a b. ExtendingNum a b => a -> b -> MResult a b
`mul` rep (int + frac)
b
        sh :: Int
sh   = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy frac -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy frac
forall k (t :: k). Proxy t
Proxy @frac))
        res' :: rep ((int + int) + (frac + frac))
res' = rep ((int + int) + (frac + frac))
-> Int -> rep ((int + int) + (frac + frac))
forall a. Bits a => a -> Int -> a
shiftR rep ((int + int) + (frac + frac))
MResult (rep (int + frac)) (rep (int + frac))
res Int
sh
    in  rep (int + frac) -> Fixed rep int frac
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed (rep ((int + int) + (frac + frac)) -> rep (int + frac)
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize rep ((int + int) + (frac + frac))
res')
  satMul SatBound (Fixed a :: rep (int + frac)
a) (Fixed b :: rep (int + frac)
b) =
    let res :: MResult (rep (int + frac)) (rep (int + frac))
res     = rep (int + frac)
a rep (int + frac)
-> rep (int + frac)
-> MResult (rep (int + frac)) (rep (int + frac))
forall a b. ExtendingNum a b => a -> b -> MResult a b
`mul` rep (int + frac)
b
        sh :: Int
sh      = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy frac -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy frac
forall k (t :: k). Proxy t
Proxy @frac))
        (rL :: BitVector int
rL,rR :: BitVector ((int + frac) + frac)
rR) = rep ((int + int) + (frac + frac))
-> (BitVector int, BitVector ((int + frac) + frac))
forall a (m :: Nat) (n :: Nat).
(BitPack a, BitSize a ~ (m + n), KnownNat n) =>
a -> (BitVector m, BitVector n)
split rep ((int + int) + (frac + frac))
MResult (rep (int + frac)) (rep (int + frac))
res :: (BitVector int, BitVector (int + frac + frac))
    in  case rep (int + frac) -> Bool
forall a. Bits a => a -> Bool
isSigned rep (int + frac)
a of
          True  -> let overflow :: Bit
overflow = Bit -> Bit
forall a. Bits a => a -> a
complement (BitVector (1 + int) -> Bit
forall a. (BitPack a, KnownNat (BitSize a)) => a -> Bit
reduceOr (Bit -> BitVector (BitSize Bit)
forall a. BitPack a => a -> BitVector (BitSize a)
pack (BitVector ((int + frac) + frac) -> Bit
forall a. (BitPack a, KnownNat (BitSize a)) => a -> Bit
msb BitVector ((int + frac) + frac)
rR) BitVector 1 -> BitVector int -> BitVector (1 + int)
forall (m :: Nat) (n :: Nat).
KnownNat m =>
BitVector n -> BitVector m -> BitVector (n + m)
++# BitVector int -> BitVector (BitSize (BitVector int))
forall a. BitPack a => a -> BitVector (BitSize a)
pack BitVector int
rL)) Bit -> Bit -> Bit
forall a. Bits a => a -> a -> a
.|.
                                             BitVector (1 + int) -> Bit
forall a. (BitPack a, KnownNat (BitSize a)) => a -> Bit
reduceAnd (Bit -> BitVector (BitSize Bit)
forall a. BitPack a => a -> BitVector (BitSize a)
pack (BitVector ((int + frac) + frac) -> Bit
forall a. (BitPack a, KnownNat (BitSize a)) => a -> Bit
msb BitVector ((int + frac) + frac)
rR) BitVector 1 -> BitVector int -> BitVector (1 + int)
forall (m :: Nat) (n :: Nat).
KnownNat m =>
BitVector n -> BitVector m -> BitVector (n + m)
++# BitVector int -> BitVector (BitSize (BitVector int))
forall a. BitPack a => a -> BitVector (BitSize a)
pack BitVector int
rL)
                   in  case Bit
overflow of
                         1 -> BitVector (BitSize (Fixed rep int frac)) -> Fixed rep int frac
forall a. BitPack a => BitVector (BitSize a) -> a
unpack (BitVector ((int + frac) + frac)
-> BitVector (BitSize (rep (int + frac)))
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize (BitVector ((int + frac) + frac)
-> Int -> BitVector ((int + frac) + frac)
forall a. Bits a => a -> Int -> a
shiftR BitVector ((int + frac) + frac)
rR Int
sh))
                         _ -> case BitVector int -> Bit
forall a. (BitPack a, KnownNat (BitSize a)) => a -> Bit
msb BitVector int
rL of
                                0 -> Fixed rep int frac
forall a. Bounded a => a
maxBound
                                _ -> Fixed rep int frac
forall a. Bounded a => a
minBound
          False -> case BitVector int
rL of
                     0 -> BitVector (BitSize (Fixed rep int frac)) -> Fixed rep int frac
forall a. BitPack a => BitVector (BitSize a) -> a
unpack (BitVector ((int + frac) + frac)
-> BitVector (BitSize (rep (int + frac)))
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize (BitVector ((int + frac) + frac)
-> Int -> BitVector ((int + frac) + frac)
forall a. Bits a => a -> Int -> a
shiftR BitVector ((int + frac) + frac)
rR Int
sh))
                     _ -> Fixed rep int frac
forall a. Bounded a => a
maxBound
  satMul SatZero (Fixed a :: rep (int + frac)
a) (Fixed b :: rep (int + frac)
b) =
    let res :: MResult (rep (int + frac)) (rep (int + frac))
res     = rep (int + frac)
a rep (int + frac)
-> rep (int + frac)
-> MResult (rep (int + frac)) (rep (int + frac))
forall a b. ExtendingNum a b => a -> b -> MResult a b
`mul` rep (int + frac)
b
        sh :: Int
sh      = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy frac -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy frac
forall k (t :: k). Proxy t
Proxy @frac))
        (rL :: BitVector int
rL,rR :: BitVector ((int + frac) + frac)
rR) = rep ((int + int) + (frac + frac))
-> (BitVector int, BitVector ((int + frac) + frac))
forall a (m :: Nat) (n :: Nat).
(BitPack a, BitSize a ~ (m + n), KnownNat n) =>
a -> (BitVector m, BitVector n)
split rep ((int + int) + (frac + frac))
MResult (rep (int + frac)) (rep (int + frac))
res :: (BitVector int, BitVector (int + frac + frac))
    in  case rep (int + frac) -> Bool
forall a. Bits a => a -> Bool
isSigned rep (int + frac)
a of
          True  -> let overflow :: Bit
overflow = Bit -> Bit
forall a. Bits a => a -> a
complement (BitVector (1 + int) -> Bit
forall a. (BitPack a, KnownNat (BitSize a)) => a -> Bit
reduceOr (Bit -> BitVector (BitSize Bit)
forall a. BitPack a => a -> BitVector (BitSize a)
pack (BitVector ((int + frac) + frac) -> Bit
forall a. (BitPack a, KnownNat (BitSize a)) => a -> Bit
msb BitVector ((int + frac) + frac)
rR) BitVector 1 -> BitVector int -> BitVector (1 + int)
forall (m :: Nat) (n :: Nat).
KnownNat m =>
BitVector n -> BitVector m -> BitVector (n + m)
++# BitVector int -> BitVector (BitSize (BitVector int))
forall a. BitPack a => a -> BitVector (BitSize a)
pack BitVector int
rL)) Bit -> Bit -> Bit
forall a. Bits a => a -> a -> a
.|.
                                             BitVector (1 + int) -> Bit
forall a. (BitPack a, KnownNat (BitSize a)) => a -> Bit
reduceAnd (Bit -> BitVector (BitSize Bit)
forall a. BitPack a => a -> BitVector (BitSize a)
pack (BitVector ((int + frac) + frac) -> Bit
forall a. (BitPack a, KnownNat (BitSize a)) => a -> Bit
msb BitVector ((int + frac) + frac)
rR) BitVector 1 -> BitVector int -> BitVector (1 + int)
forall (m :: Nat) (n :: Nat).
KnownNat m =>
BitVector n -> BitVector m -> BitVector (n + m)
++# BitVector int -> BitVector (BitSize (BitVector int))
forall a. BitPack a => a -> BitVector (BitSize a)
pack BitVector int
rL)
                   in  case Bit
overflow of
                         1 -> BitVector (BitSize (Fixed rep int frac)) -> Fixed rep int frac
forall a. BitPack a => BitVector (BitSize a) -> a
unpack (BitVector ((int + frac) + frac)
-> BitVector (BitSize (rep (int + frac)))
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize (BitVector ((int + frac) + frac)
-> Int -> BitVector ((int + frac) + frac)
forall a. Bits a => a -> Int -> a
shiftR BitVector ((int + frac) + frac)
rR Int
sh))
                         _ -> 0
          False -> case BitVector int
rL of
                     0 -> BitVector (BitSize (Fixed rep int frac)) -> Fixed rep int frac
forall a. BitPack a => BitVector (BitSize a) -> a
unpack (BitVector ((int + frac) + frac)
-> BitVector (BitSize (rep (int + frac)))
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize (BitVector ((int + frac) + frac)
-> Int -> BitVector ((int + frac) + frac)
forall a. Bits a => a -> Int -> a
shiftR BitVector ((int + frac) + frac)
rR Int
sh))
                     _ -> 0
  satMul SatSymmetric (Fixed a :: rep (int + frac)
a) (Fixed b :: rep (int + frac)
b) =
    let res :: MResult (rep (int + frac)) (rep (int + frac))
res     = rep (int + frac)
a rep (int + frac)
-> rep (int + frac)
-> MResult (rep (int + frac)) (rep (int + frac))
forall a b. ExtendingNum a b => a -> b -> MResult a b
`mul` rep (int + frac)
b
        sh :: Int
sh      = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy frac -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy frac
forall k (t :: k). Proxy t
Proxy @frac))
        (rL :: BitVector int
rL,rR :: BitVector ((int + frac) + frac)
rR) = rep ((int + int) + (frac + frac))
-> (BitVector int, BitVector ((int + frac) + frac))
forall a (m :: Nat) (n :: Nat).
(BitPack a, BitSize a ~ (m + n), KnownNat n) =>
a -> (BitVector m, BitVector n)
split rep ((int + int) + (frac + frac))
MResult (rep (int + frac)) (rep (int + frac))
res :: (BitVector int, BitVector (int + frac + frac))
    in  case rep (int + frac) -> Bool
forall a. Bits a => a -> Bool
isSigned rep (int + frac)
a of
          True  -> let overflow :: Bit
overflow = Bit -> Bit
forall a. Bits a => a -> a
complement (BitVector (1 + int) -> Bit
forall a. (BitPack a, KnownNat (BitSize a)) => a -> Bit
reduceOr (Bit -> BitVector (BitSize Bit)
forall a. BitPack a => a -> BitVector (BitSize a)
pack (BitVector ((int + frac) + frac) -> Bit
forall a. (BitPack a, KnownNat (BitSize a)) => a -> Bit
msb BitVector ((int + frac) + frac)
rR) BitVector 1 -> BitVector int -> BitVector (1 + int)
forall (m :: Nat) (n :: Nat).
KnownNat m =>
BitVector n -> BitVector m -> BitVector (n + m)
++# BitVector int -> BitVector (BitSize (BitVector int))
forall a. BitPack a => a -> BitVector (BitSize a)
pack BitVector int
rL)) Bit -> Bit -> Bit
forall a. Bits a => a -> a -> a
.|.
                                             BitVector (1 + int) -> Bit
forall a. (BitPack a, KnownNat (BitSize a)) => a -> Bit
reduceAnd (Bit -> BitVector (BitSize Bit)
forall a. BitPack a => a -> BitVector (BitSize a)
pack (BitVector ((int + frac) + frac) -> Bit
forall a. (BitPack a, KnownNat (BitSize a)) => a -> Bit
msb BitVector ((int + frac) + frac)
rR) BitVector 1 -> BitVector int -> BitVector (1 + int)
forall (m :: Nat) (n :: Nat).
KnownNat m =>
BitVector n -> BitVector m -> BitVector (n + m)
++# BitVector int -> BitVector (BitSize (BitVector int))
forall a. BitPack a => a -> BitVector (BitSize a)
pack BitVector int
rL)
                   in  case Bit
overflow of
                         1 -> BitVector (BitSize (Fixed rep int frac)) -> Fixed rep int frac
forall a. BitPack a => BitVector (BitSize a) -> a
unpack (BitVector ((int + frac) + frac)
-> BitVector (BitSize (rep (int + frac)))
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize (BitVector ((int + frac) + frac)
-> Int -> BitVector ((int + frac) + frac)
forall a. Bits a => a -> Int -> a
shiftR BitVector ((int + frac) + frac)
rR Int
sh))
                         _ -> case BitVector int -> Bit
forall a. (BitPack a, KnownNat (BitSize a)) => a -> Bit
msb BitVector int
rL of
                                0 -> Fixed rep int frac
forall a. Bounded a => a
maxBound
                                _ -> Fixed rep int frac -> Fixed rep int frac
forall a. Enum a => a -> a
succ Fixed rep int frac
forall a. Bounded a => a
minBound
          False -> case BitVector int
rL of
                     0 -> BitVector (BitSize (Fixed rep int frac)) -> Fixed rep int frac
forall a. BitPack a => BitVector (BitSize a) -> a
unpack (BitVector ((int + frac) + frac)
-> BitVector (BitSize (rep (int + frac)))
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize (BitVector ((int + frac) + frac)
-> Int -> BitVector ((int + frac) + frac)
forall a. Bits a => a -> Int -> a
shiftR BitVector ((int + frac) + frac)
rR Int
sh))
                     _ -> Fixed rep int frac
forall a. Bounded a => a
maxBound
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 rep int1 frac1
-> Fixed rep int2 frac2
-> Fixed rep ((int1 + frac2) + 1) (int2 + frac1)
divide (Fixed fr1 :: rep (int1 + frac1)
fr1) fx2 :: Fixed rep int2 frac2
fx2@(Fixed fr2 :: rep (int2 + frac2)
fr2) =
  let int2 :: Int
int2  = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy int2 -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Fixed rep int2 frac2 -> Proxy int2
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
Fixed rep int frac -> Proxy int
asIntProxy Fixed rep int2 frac2
fx2))
      frac2 :: Int
frac2 = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Fixed rep int2 frac2 -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal Fixed rep int2 frac2
fx2)
      fr1' :: rep (((int1 + frac2) + 1) + (int2 + frac1))
fr1'  = rep (int1 + frac1) -> rep (((int1 + frac2) + 1) + (int2 + frac1))
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize rep (int1 + frac1)
fr1
      fr2' :: rep (((int1 + frac2) + 1) + (int2 + frac1))
fr2'  = rep (int2 + frac2) -> rep (((int1 + frac2) + 1) + (int2 + frac1))
forall (f :: Nat -> *) (a :: Nat) (b :: Nat).
(Resize f, KnownNat a, KnownNat b) =>
f a -> f b
resize rep (int2 + frac2)
fr2
      fr1SH :: rep (((int1 + frac2) + 1) + (int2 + frac1))
fr1SH = rep (((int1 + frac2) + 1) + (int2 + frac1))
-> Int -> rep (((int1 + frac2) + 1) + (int2 + frac1))
forall a. Bits a => a -> Int -> a
shiftL rep (((int1 + frac2) + 1) + (int2 + frac1))
fr1' ((Int
int2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
frac2))
      res :: rep (((int1 + frac2) + 1) + (int2 + frac1))
res   = rep (((int1 + frac2) + 1) + (int2 + frac1))
fr1SH rep (((int1 + frac2) + 1) + (int2 + frac1))
-> rep (((int1 + frac2) + 1) + (int2 + frac1))
-> rep (((int1 + frac2) + 1) + (int2 + frac1))
forall a. Integral a => a -> a -> a
`quot` rep (((int1 + frac2) + 1) + (int2 + frac1))
fr2'
  in  rep (((int1 + frac2) + 1) + (int2 + frac1))
-> Fixed rep ((int1 + frac2) + 1) (int2 + frac1)
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed rep (((int1 + frac2) + 1) + (int2 + frac1))
res
type FracFixedC rep int frac
  = ( NumFixedC rep int frac
    , DivideC   rep int frac int frac
    , Integral  (rep (int + frac))
    , KnownNat  int
    , KnownNat  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 :: Fixed rep int frac
f1 / :: Fixed rep int frac -> Fixed rep int frac -> Fixed rep int frac
/ f2 :: Fixed rep int frac
f2        = Fixed rep ((int + frac) + 1) (int + frac) -> Fixed rep int frac
forall (rep :: Nat -> *) (int1 :: Nat) (frac1 :: Nat) (int2 :: Nat)
       (frac2 :: Nat).
ResizeFC rep int1 frac1 int2 frac2 =>
Fixed rep int1 frac1 -> Fixed rep int2 frac2
resizeF (Fixed rep int frac
-> Fixed rep int frac -> Fixed rep ((int + frac) + 1) (int + frac)
forall (rep :: Nat -> *) (int1 :: Nat) (frac1 :: Nat) (int2 :: Nat)
       (frac2 :: Nat).
DivideC rep int1 frac1 int2 frac2 =>
Fixed rep int1 frac1
-> Fixed rep int2 frac2
-> Fixed rep ((int1 + frac2) + 1) (int2 + frac1)
divide Fixed rep int frac
f1 Fixed rep int frac
f2)
  recip :: Fixed rep int frac -> Fixed rep int frac
recip fx :: Fixed rep int frac
fx       = Fixed rep ((int + frac) + 1) (int + frac) -> Fixed rep int frac
forall (rep :: Nat -> *) (int1 :: Nat) (frac1 :: Nat) (int2 :: Nat)
       (frac2 :: Nat).
ResizeFC rep int1 frac1 int2 frac2 =>
Fixed rep int1 frac1 -> Fixed rep int2 frac2
resizeF (Fixed rep int frac
-> Fixed rep int frac -> Fixed rep ((int + frac) + 1) (int + frac)
forall (rep :: Nat -> *) (int1 :: Nat) (frac1 :: Nat) (int2 :: Nat)
       (frac2 :: Nat).
DivideC rep int1 frac1 int2 frac2 =>
Fixed rep int1 frac1
-> Fixed rep int2 frac2
-> Fixed rep ((int1 + frac2) + 1) (int2 + frac1)
divide (1 :: Fixed rep int frac) Fixed rep int frac
fx)
  fromRational :: Ratio Integer -> Fixed rep int frac
fromRational r :: Ratio Integer
r = Fixed rep int frac
res
    where
      res :: Fixed rep int frac
res  = rep (int + frac) -> Fixed rep int frac
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed (Integer -> rep (int + frac)
forall a. Num a => Integer -> a
fromInteger Integer
sat)
      sat :: Integer
sat  = if Integer
res' Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
rMax
                then Integer
rMax
                else if Integer
res' Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
rMin then Integer
rMin else Integer
res'
      rMax :: Integer
rMax = rep (int + frac) -> Integer
forall a. Integral a => a -> Integer
toInteger (rep (int + frac)
forall a. Bounded a => a
maxBound :: rep (int + frac))
      rMin :: Integer
rMin = rep (int + frac) -> Integer
forall a. Integral a => a -> Integer
toInteger (rep (int + frac)
forall a. Bounded a => a
minBound :: rep (int + frac))
      res' :: Integer
res' = Integer
n Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`div` Integer
d
      frac :: Int
frac = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Fixed rep int frac -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal Fixed rep int frac
res)
      n :: Integer
n    = Ratio Integer -> Integer
forall a. Ratio a -> a
numerator   Ratio Integer
r Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftL` (2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
frac)
      d :: Integer
d    = Ratio Integer -> Integer
forall a. Ratio a -> a
denominator Ratio Integer
r Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftL` Int
frac
instance (NumFixedC rep int frac, Integral (rep (int + frac))) =>
         Real (Fixed rep int frac) where
  toRational :: Fixed rep int frac -> Ratio Integer
toRational f :: Fixed rep int frac
f@(Fixed fRep :: rep (int + frac)
fRep) = Integer
nom Integer -> Integer -> Ratio Integer
forall a. Integral a => a -> a -> Ratio a
% Integer
denom
   where
     nF :: Int
nF        = Fixed rep int frac -> Int
forall (frac :: Nat) (rep :: Nat -> *) (int :: Nat).
KnownNat frac =>
Fixed rep int frac -> Int
fracShift Fixed rep int frac
f
     denom :: Integer
denom     = 1 Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftL` Int
nF
     nom :: Integer
nom       = rep (int + frac) -> Integer
forall a. Integral a => a -> Integer
toInteger rep (int + frac)
fRep
instance (FracFixedC rep int frac, NumFixedC rep int frac, Integral (rep (int + frac))) =>
         RealFrac (Fixed rep int frac) where
  properFraction :: Fixed rep int frac -> (b, Fixed rep int frac)
properFraction f :: Fixed rep int frac
f@(Fixed fRep :: rep (int + frac)
fRep) = (rep (int + frac) -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral rep (int + frac)
whole, Fixed rep int frac
fract)
    where
      whole :: rep (int + frac)
whole = (rep (int + frac)
fRep rep (int + frac) -> Int -> rep (int + frac)
forall a. Bits a => a -> Int -> a
`shiftR` Fixed rep int frac -> Int
forall (frac :: Nat) (rep :: Nat -> *) (int :: Nat).
KnownNat frac =>
Fixed rep int frac -> Int
fracShift Fixed rep int frac
f) rep (int + frac) -> rep (int + frac) -> rep (int + frac)
forall a. Num a => a -> a -> a
+ rep (int + frac)
offset
      fract :: Fixed rep int frac
fract = rep (int + frac) -> Fixed rep int frac
forall (rep :: Nat -> *) (int :: Nat) (frac :: Nat).
rep (int + frac) -> Fixed rep int frac
Fixed (rep (int + frac) -> Fixed rep int frac)
-> rep (int + frac) -> Fixed rep int frac
forall a b. (a -> b) -> a -> b
$ rep (int + frac)
fRep rep (int + frac) -> rep (int + frac) -> rep (int + frac)
forall a. Num a => a -> a -> a
- (rep (int + frac)
whole rep (int + frac) -> Int -> rep (int + frac)
forall a. Bits a => a -> Int -> a
`shiftL` Fixed rep int frac -> Int
forall (frac :: Nat) (rep :: Nat -> *) (int :: Nat).
KnownNat frac =>
Fixed rep int frac -> Int
fracShift Fixed rep int frac
f)
      offset :: rep (int + frac)
offset = if Fixed rep int frac
f Fixed rep int frac -> Fixed rep int frac -> Bool
forall a. Ord a => a -> a -> Bool
< 0 then 1 else 0