diff --git a/math/fxp.act b/math/fxp.act index 540afd1..b51d76d 100644 --- a/math/fxp.act +++ b/math/fxp.act @@ -84,7 +84,7 @@ namespace math { chp { [ v >= 0.0 -> self := int(v * (1 << B) + 0.5) [] else -> self := int(-v * (1 << B) + 0.5); - self := (1 << (A+B)) - self + self := (1 << (A+B)) - self ] } } @@ -121,7 +121,7 @@ namespace math { function le(int x, y) : bool { chp { - [ x{A+B-1} = 1 & y{A+B-1} = 0 -> self := true + [ x{A+B-1} = 1 & y{A+B-1} = 0 -> self := true [] y{A+B-1} = 1 & x{A+B-1} = 0 -> self := false [] else -> self := (x <= y) ] @@ -146,16 +146,31 @@ namespace math { } } + template + function round(int<1> lsb; int off) : int<1> { + chp { + // trunc + [ FXP_ROUNDING_MODE = 0 -> self := 0 + [] FXP_ROUNDING_MODE = 1 -> // half to even + self := (off{N-1} = 0) | (off = int(1 << (N - 1), N) & lsb = 0) ? 0 : 1 + [] else -> assert(0) + ] + } + } + export template function mults (int x, y) : int { bool sx, sy; + int<2 * A + 2 * B> r; + chp { - [ x{A+B-1} = 1 -> sx+; x := ~x + 1 [] else -> sx- ]; - [ y{A+B-1} = 1 -> sy+; y := ~y + 1 [] else -> sy- ]; - self := (x * y) >> B; - [ sx != sy -> self := ~self + 1 [] else -> skip ] + [ x{A+B-1} = 1 -> sx+; x := ~x + 1 [] else -> sx- ]; + [ y{A+B-1} = 1 -> sy+; y := ~y + 1 [] else -> sy- ]; + r := (x * y); + self := (r >> B) + round(r{B}, r{B-1..0}); + [ sx != sy -> self := ~self + 1 [] else -> skip ] } } @@ -167,20 +182,20 @@ namespace math { self := (x * y) >> B } } - + export template function divs (int x, y) : int { bool sx, sy; chp { - [ x{A+B-1} = 1 -> sx+; x := ~x + 1 [] else -> sx- ]; - [ y{A+B-1} = 1 -> sy+; y := ~y + 1 [] else -> sy- ]; + [ x{A+B-1} = 1 -> sx+; x := ~x + 1 [] else -> sx- ]; + [ y{A+B-1} = 1 -> sy+; y := ~y + 1 [] else -> sy- ]; self := (x << B) / y; - [ sx != sy -> self := ~self + 1 [] else -> skip ] + [ sx != sy -> self := ~self + 1 [] else -> skip ] } } - + export template function divu (int x, y) : int @@ -198,73 +213,72 @@ namespace math { self := ~x + 1 } } - } export - template + template deftype fixpoint(int x) { methods { function plus(fixpoint rhs) : fixpoint { - chp { - self.x := fxp::add(x,rhs.x) - } + chp { + self.x := fxp::add(x,rhs.x) + } } function minus(fixpoint rhs) : fixpoint { - chp { - self.x := fxp::sub(x,rhs.x) - } + chp { + self.x := fxp::sub(x,rhs.x) + } } function mult(fixpoint rhs) : fixpoint { - chp { - self.x := fxp::mults(x,rhs.x) - } + chp { + self.x := fxp::mults(x,rhs.x) + } } function div(fixpoint rhs) : fixpoint { - chp { - self.x := fxp::divs(x,rhs.x) - } + chp { + self.x := fxp::divs(x,rhs.x) + } } function uminus() : fixpoint { - chp { - self.x := fxp::uminus(x) - } + chp { + self.x := fxp::uminus(x) + } } function le(fixpoint rhs) : bool { - chp { - self := fxp::le(x, rhs.x) - } + chp { + self := fxp::le(x, rhs.x) + } } function lt(fixpoint rhs) : bool { - chp { - self := (x != rhs.x) & fxp::le(x, rhs.x) - } + chp { + self := (x != rhs.x) & fxp::le(x, rhs.x) + } } function ne(fixpoint rhs) : bool { - chp { - self := (x != rhs.x) - } + chp { + self := (x != rhs.x) + } } function ge(fixpoint rhs) : bool { - chp { - self := fxp::le(rhs.x, x) - } + chp { + self := fxp::le(rhs.x, x) + } } function gt(fixpoint rhs) : bool { - chp { - self := (x != rhs.x) & fxp::le(rhs.x, x) - } + chp { + self := (x != rhs.x) & fxp::le(rhs.x, x) + } } macro set(int v) @@ -282,46 +296,77 @@ namespace math { function positive() : bool { chp { - self := fxp::positive(x) + self := fxp::positive(x) } } function negative() : bool { chp { - self := fxp::negative(x) + self := fxp::negative(x) } } function zero() : bool { chp { - self := fxp::zero(x) + self := fxp::zero(x) } } function const(preal v) : pint { - chp { - self := fxp::conv_to_fxp(A,B,v) - } + chp { + self := fxp::conv_to_fxp(A,B,v) + } } macro log() { - log_st(""); - [ x{A+B-1} = 1 -> log_p("-", int(~x+1,A+B)>>B) - [] else -> log_p("+", x >> B) - ]; - log_p (".{", (x{A+B-1} = 1 ? int(~x+1,A+B) : x) & int((1 << B)-1,B), "/", (1 << B), "}"); - log_nl("") + log_st(""); + [ x{A+B-1} = 1 -> log_p("-", int(~x+1, A+B)>>B) + [] else -> log_p("+", x >> B) + ]; + log_p (".{", (x{A+B-1} = 1 ? int(~x+1, A+B) : x) & int((1 << B)-1, B), "/", (1 << B), "}"); + log_nl("") } macro log_p() { - [ x{A+B-1} = 1 -> log_p("-", int(~x+1,A+B)>>B) - [] else -> log_p("+", x >> B) - ]; - log_p (".{", (x{A+B-1} = 1 ? int(~x+1,A+B) : x) & int((1 << B)-1,B), "/", (1 << B), "}") + [ x{A+B-1} = 1 -> log_p("-", int(~x+1, A+B)>>B) + [] else -> log_p("+", x >> B) + ]; + log_p (".{", (x{A+B-1} = 1 ? int(~x+1, A+B) : x) & int((1 << B)-1, B), "/", (1 << B), "}") + } + } + } + + export namespace fxp { + export + template + function sdowncast(fixpoint a) : fixpoint { + {A_FROM > A_TO}; + {B_FROM > B_TO}; + + int<1> rnd; + + chp { + rnd := round(a.x{B_FROM - B_TO}, a.x{B_FROM - B_TO - 1..0}); + self.x := {a.x{(A_TO + B_FROM - 1)..B_FROM}, a.x{B_FROM-1..(B_FROM - B_TO)}} + rnd + } + } + + export + template + function supcast(fixpoint a) : fixpoint { + {A_FROM < A_TO}; + {B_FROM < B_TO}; + + chp { + self.x := a.x{(A_FROM + B_FROM - 1)..B_FROM} << B_TO | a.x{(B_FROM - 1)..0} << (B_TO - B_FROM); + [ a.x{A_FROM + B_FROM - 1} = 0 -> skip + // sign extend + [] else -> self.x := self.x | (~int(0, A_TO - A_FROM) << (A_FROM + B_TO)) + ] } } }