Portability | portable |
---|---|
Stability | provisional |
Maintainer | ross@soi.city.ac.uk |
Safe Haskell | Safe-Infered |
Prelude.YAP
Description
A replacement for the standard Prelude, aiming to preserve
compatibility for clients as far as possible.
To use this module, you'll need to turn on RebindableSyntax
, which
also turns off the implicit import of the standard Prelude
.
For greater backwards compatibility, this module hides the names of
the classes AbelianGroup
, Ring
, Field
and EuclideanDomain
,
and their new methods zero
, unit
and associate
. To use
those names, e.g. to define instances, you'll also need to import
Data.YAP.Algebra.
- module Prelude
- module Data.YAP.Algebra
- class Ring a => Num a where
- class (Num a, Ord a) => Real a where
- toRational :: a -> Rational
- class (Num a, Field a) => Fractional a where
- fromRational :: Rational -> a
- class (Real a, Enum a, EuclideanDomain a) => Integral a where
- class (Real a, Fractional a) => RealFrac a where
- class Fractional a => Floating a where
- class (RealFrac a, Floating a) => RealFloat a where
- floatRadix :: a -> Integer
- floatDigits :: a -> Int
- floatRange :: a -> (Int, Int)
- decodeFloat :: a -> (Integer, Int)
- encodeFloat :: Integer -> Int -> a
- exponent :: a -> Int
- significand :: a -> a
- scaleFloat :: Int -> a -> a
- isNaN, isIEEE, isNegativeZero, isDenormalized, isInfinite :: a -> Bool
- atan2 :: a -> a -> a
- even, odd :: Integral a => a -> Bool
- (^) :: (Ring a, Integral b) => a -> b -> a
- (^^) :: (Field a, Integral b) => a -> b -> a
- fromIntegral :: (Integral a, Ring b) => a -> b
- realToFrac :: (Real a, Fractional b) => a -> b
Standard Haskell prelude
module Prelude
Compatibility classes
module Data.YAP.Algebra
class (Num a, Ord a) => Real a whereSource
unchanged from Haskell 98
Methods
toRational :: a -> RationalSource
The rational equivalent of its real argument with full precision
class (Num a, Field a) => Fractional a whereSource
Haskell 98 compatibility class
Methods
fromRational :: Rational -> aSource
Convert from Rational
A floating point numeric literal represents the application of
the function fromRational
to the appropriate value of type
Rational
, so such literals have type (
.
Field
a) => a
Instances
Fractional Double | |
Fractional Float | |
(Integral a, Integral a) => Fractional (Ratio a) | |
RealFloat a => Fractional (Complex a) |
class (Real a, Enum a, EuclideanDomain a) => Integral a whereSource
Integral numbers, supporting integer division.
Minimal complete definition: toInteger
.
Unchanged classes
class (Real a, Fractional a) => RealFrac a whereSource
unchanged from Haskell 98
class Fractional a => Floating a whereSource
unchanged from Haskell 98
class (RealFrac a, Floating a) => RealFloat a whereSource
unchanged from Haskell 98
Methods
floatRadix :: a -> IntegerSource
floatDigits :: a -> IntSource
floatRange :: a -> (Int, Int)Source
decodeFloat :: a -> (Integer, Int)Source
encodeFloat :: Integer -> Int -> aSource
significand :: a -> aSource
scaleFloat :: Int -> a -> aSource
isNaN, isIEEE, isNegativeZero, isDenormalized, isInfinite :: a -> BoolSource
Numeric functions
fromIntegral :: (Integral a, Ring b) => a -> bSource
General conversion from integral types, via the Integer
type.
realToFrac :: (Real a, Fractional b) => a -> bSource
General conversion to fields, via the Rational
type.