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

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

Please see the README on GitHub at https://github.com/minoki/haskell-floating-point/tree/master/rounded-hw#readme


[Skip to Readme]

Properties

Versions 0.1.0.0, 0.2.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:43:43Z

Modules

[Index] [Quick Jump]

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


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.

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"