Skip to content

Commit

Permalink
add a license header, and fully qualify imports.
Browse files Browse the repository at this point in the history
  • Loading branch information
julialongtin committed Dec 19, 2023
1 parent 46f8d2b commit 93ec1f9
Showing 1 changed file with 20 additions and 7 deletions.
27 changes: 20 additions & 7 deletions src/Data/Bits/Floating/Ulp.hs
Original file line number Diff line number Diff line change
@@ -1,18 +1,31 @@
-----------------------------------------------------------------------------
-- |
-- Copyright : (C) 2015 Anselm Jonas Scholl, (C) 2023 Julia Longtin
-- License : BSD3
-- Maintainer : Julia Longtin <Julia.longtin@gmail.com>
-- Stability : experimental
-- Portability : GHC-specific
--
-- Provides increment-by-ulp, decrement-by-ulp, and get-ulp functions for
-- Doubles, and Floats.
----------------------------------------------------------------------------
{-# LANGUAGE ScopedTypeVariables #-}

module Data.Bits.Floating.Ulp (
doubleNextUlp
,doublePrevUlp
,doubleUlp

,floatNextUlp
,floatPrevUlp
,floatUlp
) where

import Data.Int
import Data.Bits
import Data.Bits.Floating.Prim
import Prelude (Double, Float, Integral, Num, RealFloat, Show, (<), (>), ($), (+), (-), (>=), (&&), (==), (||), abs, fromIntegral, isInfinite, isNaN, isNegativeZero, otherwise)
import Data.Int (Int64, Int32)
import Data.Bits (Bits, (.&.), shiftL, shiftR)
import Data.Bits.Floating.Prim (double2WordBitwise, float2WordBitwise, word2DoubleBitwise, word2FloatBitwise)

-- Tell HLint to ignore suggestions to eta-reduce expressions in this module.
{-# ANN module "HLint: ignore Eta reduce" #-}

---------------------
Expand Down Expand Up @@ -95,9 +108,9 @@ genericUlp mkW mkF expBitMask significandWidth expBias maxExponent minExponent m
powerOfTwo :: i -> f
powerOfTwo n = mkF $ fromIntegral $ ((n + expBias) `shiftL` fromIntegral (significandWidth - 1)) .&. expBitMask

----------------------------
-- * Specific implementation
----------------------------
-----------------------------
-- * Specific implementations
-----------------------------

-- | Advance a 'Double' by one ULP.
{-# INLINABLE doubleNextUlp #-}
Expand Down

0 comments on commit 93ec1f9

Please sign in to comment.