hmpfr-0.4.4: Haskell binding to the MPFR library

Copyright(c) Aleš Bizjak
LicenseBSD3
Maintainermikkonecny@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell98

Data.Number.MPFR

Contents

Description

This module exports a pure interface to the MPFR library functions. Functions return new MPFR structures instead of modifying existing ones and so all functions which produce a new MPFR structure take one more parameter than their original C counterparts. This parameter, Precision, is the precision of the resulting MPFR.

This is naturally slower than modifying in-place, especially when dealing with lower precisions, so a "mutable" interface is provided in Data.Number.MPFR.Mutable module.

Naming conventions

  • functions ending with _ (underscore) usually return a pair (MPFR, Int), where Int is a return value of a corresponding mpfr_ function. See the MPFR manual for a description of return values.
  • the same functions without the _ return just the MPFR.
  • mpfr_ prefix in functions is removed
  • _ui and ui_ in function becomes w (stands for Word). For example mpfr_sub_ui becomes subw and mpfr_ui_sub becomes wsub.
  • si_ and _si in functions becomes i (stands for Int). For example mpfr_sub_si becomes subi and mpfr_si_sub becomes isub.
  • comparison functions which have _p appended loose it. For example mpfr_less_p becomes less.

Instances

Eq
  • NaN /= NaN,
  • Infinity = Infinity,
  • -Infinity = -Infinity
  • otherwise normal comparison
Ord
  • compare NaN _ = GT
  • compare _ NaN = GT
  • infinity < _ = False
  • -infinity > _ = False
  • NaN [<,>,>=,<=] _ = False

This mimics the behaviour of built in Haskell Float and Double.

If you need instances of numeric typeclasses import one of the Data.Number.MPFR.Instances.* modules.

Synopsis

Documentation

data MPFR Source #

Instances

Generic MPFR Source # 

Associated Types

type Rep MPFR :: * -> * #

Methods

from :: MPFR -> Rep MPFR x #

to :: Rep MPFR x -> MPFR #

Storable MPFR Source # 

Methods

sizeOf :: MPFR -> Int #

alignment :: MPFR -> Int #

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

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

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

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

peek :: Ptr MPFR -> IO MPFR #

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

type Rep MPFR Source # 
type Rep MPFR = D1 * (MetaData "MPFR" "Data.Number.MPFR.FFIhelper" "hmpfr-0.4.4-CVSKNSw033MEWP1hktuXpF" False) (C1 * (MetaCons "MP" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "precision") SourceUnpack SourceStrict DecidedStrict) (Rec0 * CPrecision)) (S1 * (MetaSel (Just Symbol "sign") SourceUnpack SourceStrict DecidedStrict) (Rec0 * Sign))) ((:*:) * (S1 * (MetaSel (Just Symbol "exponent") SourceUnpack SourceStrict DecidedStrict) (Rec0 * Exp)) (S1 * (MetaSel (Just Symbol "limbs") SourceUnpack SourceStrict DecidedStrict) (Rec0 * (ForeignPtr Limb))))))

data Precision Source #

Instances

Enum Precision Source # 
Eq Precision Source # 
Integral Precision Source # 
Num Precision Source # 
Ord Precision Source # 
Real Precision Source # 
Show Precision Source # 

type Exp = Int64 Source #

Assignment functions

See http://www.mpfr.org/mpfr-current/mpfr.html#Assignment-Functions documentation on particular functions.

Conversion functions

See http://www.mpfr.org/mpfr-current/mpfr.html#Conversion-Functions documentation on particular functions.

Basic arithmetic functions

For documentation on particular functions see http://www.mpfr.org/mpfr-current/mpfr.html#Basic-Arithmetic-Functions.

Comparison functions

For documentation on particular functions see http://www.mpfr.org/mpfr-current/mpfr.html#Comparison-Functions

Special functions

For documentation on particular functions see http://www.mpfr.org/mpfr-current/mpfr.html#Special-Functions.

Integer related functions

Miscellaneous functions

For documentation on particular functions see http://www.mpfr.org/mpfr-current/mpfr.html#Miscellaneous-Functions.