half-0.3: Half-precision floating-point

Copyright(C) 2014 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
PortabilityPatternSynonyms
Safe HaskellNone
LanguageHaskell98

Numeric.Half

Description

Half-precision floating-point values. These arise commonly in GPU work and it is useful to be able to compute them and compute with them on the CPU as well.

Synopsis

Documentation

newtype Half Source #

Constructors

Half 

Fields

Instances

Eq Half Source # 

Methods

(==) :: Half -> Half -> Bool #

(/=) :: Half -> Half -> Bool #

Floating Half Source # 

Methods

pi :: Half #

exp :: Half -> Half #

log :: Half -> Half #

sqrt :: Half -> Half #

(**) :: Half -> Half -> Half #

logBase :: Half -> Half -> Half #

sin :: Half -> Half #

cos :: Half -> Half #

tan :: Half -> Half #

asin :: Half -> Half #

acos :: Half -> Half #

atan :: Half -> Half #

sinh :: Half -> Half #

cosh :: Half -> Half #

tanh :: Half -> Half #

asinh :: Half -> Half #

acosh :: Half -> Half #

atanh :: Half -> Half #

log1p :: Half -> Half #

expm1 :: Half -> Half #

log1pexp :: Half -> Half #

log1mexp :: Half -> Half #

Fractional Half Source # 

Methods

(/) :: Half -> Half -> Half #

recip :: Half -> Half #

fromRational :: Rational -> Half #

Num Half Source # 

Methods

(+) :: Half -> Half -> Half #

(-) :: Half -> Half -> Half #

(*) :: Half -> Half -> Half #

negate :: Half -> Half #

abs :: Half -> Half #

signum :: Half -> Half #

fromInteger :: Integer -> Half #

Ord Half Source # 

Methods

compare :: Half -> Half -> Ordering #

(<) :: Half -> Half -> Bool #

(<=) :: Half -> Half -> Bool #

(>) :: Half -> Half -> Bool #

(>=) :: Half -> Half -> Bool #

max :: Half -> Half -> Half #

min :: Half -> Half -> Half #

Read Half Source # 
Real Half Source # 

Methods

toRational :: Half -> Rational #

RealFloat Half Source # 
RealFrac Half Source # 

Methods

properFraction :: Integral b => Half -> (b, Half) #

truncate :: Integral b => Half -> b #

round :: Integral b => Half -> b #

ceiling :: Integral b => Half -> b #

floor :: Integral b => Half -> b #

Show Half Source # 

Methods

showsPrec :: Int -> Half -> ShowS #

show :: Half -> String #

showList :: [Half] -> ShowS #

Generic Half Source # 

Associated Types

type Rep Half :: * -> * #

Methods

from :: Half -> Rep Half x #

to :: Rep Half x -> Half #

Lift Half Source # 

Methods

lift :: Half -> Q Exp #

Storable Half Source # 

Methods

sizeOf :: Half -> Int #

alignment :: Half -> Int #

peekElemOff :: Ptr Half -> Int -> IO Half #

pokeElemOff :: Ptr Half -> Int -> Half -> IO () #

peekByteOff :: Ptr b -> Int -> IO Half #

pokeByteOff :: Ptr b -> Int -> Half -> IO () #

peek :: Ptr Half -> IO Half #

poke :: Ptr Half -> Half -> IO () #

NFData Half Source # 

Methods

rnf :: Half -> () #

type Rep Half Source # 
type Rep Half = D1 * (MetaData "Half" "Numeric.Half" "half-0.3-3luqzD8LSSdHO8DVtASdnL" True) (C1 * (MetaCons "Half" PrefixI True) (S1 * (MetaSel (Just Symbol "getHalf") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUShort)))

isZero :: Half -> Bool Source #

Is this Half equal to 0?

fromHalf :: Half -> Float Source #

Convert a Half to a Float while preserving NaN

toHalf :: Float -> Half Source #

Convert a Float to a Half with proper rounding, while preserving NaN and dealing appropriately with infinity

pattern POS_INF :: Half Source #

Positive infinity

pattern NEG_INF :: Half Source #

Negative infinity

pattern QNaN :: Half Source #

Quiet NaN

pattern SNaN :: Half Source #

Signalling NaN

pattern HALF_MIN :: Half Source #

Smallest positive half

pattern HALF_NRM_MIN :: Half Source #

Smallest positive normalized half

pattern HALF_MAX :: Half Source #

Largest positive half

pattern HALF_EPSILON :: Half Source #

Smallest positive e for which half (1.0 + e) != half (1.0)

pattern HALF_DIG :: forall a. (Num a, Eq a) => a Source #

Number of base 10 digits that can be represented without change

pattern HALF_MIN_10_EXP :: forall a. (Num a, Eq a) => a Source #

pattern HALF_MAX_10_EXP :: forall a. (Num a, Eq a) => a Source #