rounded-hw: Directed rounding for built-in floating types

[ bsd3, library, math, numeric ] [ Propose Tags ]

Flags

Manual Flags

NameDescriptionDefault
avx512

Use AVX512 EVEX encoding

Disabled
c99

Restrict use of platform-dependent features (e.g. SSE2) and only use C99 features

Disabled
float128

Support Float128

Disabled
ghc-prim

Use GHC's "foreign import prim" on the supported platform

Enabled
pure-hs

Disable FFI

Disabled
x87-long-double

Support x87 "long double"

Enabled

Use -f <flag> to enable a flag, or -f -<flag> to disable that flag. More info

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.2.0, 0.3.0, 0.4.0
Change log ChangeLog.md
Dependencies array, base (>=4.12 && <5), deepseq, fp-ieee (>=0.1 && <0.2), long-double, primitive, tagged, vector [details]
License BSD-3-Clause
Copyright 2020 ARATA Mizuki
Author ARATA Mizuki
Maintainer minorinoki@gmail.com
Category Numeric, Math
Home page https://github.com/minoki/haskell-floating-point#readme
Bug tracker https://github.com/minoki/haskell-floating-point/issues
Source repo head: git clone https://github.com/minoki/haskell-floating-point
Uploaded by aratamizuki at 2020-12-27T13:50:14Z
Distributions
Downloads 563 total (12 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for rounded-hw-0.2.0

[back to package description]

rounded-hw: Rounding control for built-in floating-point types

This package provides directed rounding and interval arithmetic for built-in floating-point types (i.e. Float, Double). Unlike rounded, this package does not depend on an external C library.

In addition to Float and Double, LongDouble from long-double package is supported on x86. There is also support for Float128 from float128 package under a package flag.

API overview

Controlling the rounding direction

The type RoundingMode represents the four rounding directions.

The type Rounded (r :: RoundingMode) a is a wrapper for a, with instances honoring the rounding direction given by r.

module Numeric.Rounded.Hardware where

data RoundingMode
  = ToNearest     -- ^ Round to the nearest value (IEEE754 roundTiesToEven)
  | TowardNegInf  -- ^ Round downward (IEEE754 roundTowardNegative)
  | TowardInf     -- ^ Round upward (IEEE754 roundTowardPositive)
  | TowardZero    -- ^ Round toward zero (IEEE754 roundTowardZero)

newtype Rounded (r :: RoundingMode) a = Rounded { getRounded :: a }

instance ... => Num (Rounded r a)
instance ... => Fractional (Rounded r a)
instance ... => Real (Rounded r a)
instance ... => RealFrac (Rounded r a)

Interval arithmetic

This library also provides basic interval types. See Numeric.Rounded.Hardware.Interval and Numeric.Rounded.Hardware.Interval.NonEmpty.

Usage

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE HexFloatLiterals #-}
import Numeric
import Numeric.Rounded.Hardware

main = do
  putStrLn $ showHFloat (1 + 0x1p-100 :: Double) "" -- -> 0x1p0
  putStrLn $ showHFloat (1 + 0x1p-100 :: Rounded TowardInf Double) "" -- -> 0x1.0000000000001p0

Backends

There are several options to control the rounding direction.

  • Pure Haskell (via Rational)
    • Very slow, but does not depend on FFI and therefore can be used on non-native backends.
    • This implementation is always available via a newtype in Numeric.Rounded.Hardware.Backend.ViaRational.
  • C FFI
    • One of the technologies below is used:
      • C99 (fesetround)
      • SSE2 (_mm_setcsr)
      • AVX512 EVEX encoding (_mm_*_round_*)
      • x87 Control Word (for x87 long double)
      • AArch64 FPCR
    • On x86_64, foreign import prim is used to provide faster interval addition/subtraction.

By default, C FFI is used and an appropriate technology is detected. To disable use of C FFI, set pure-hs flag when building.

The name of the backend used can be obtained with Numeric.Rounded.Hardware.Backend.backendName.

>>> backendName (Proxy :: Proxy Double)
"FastFFI+SSE2"