algebraic-prelude-0.1.1.0: Algebraically structured Prelude

Safe HaskellNone
LanguageHaskell2010

AlgebraicPrelude

Contents

Description

This module provides drop-in replacement for Prelude module in base package, based on algebraic hierarchy provided by algebra package. You can use this module with NoImplicitPrelude language option.

This module implicitly exports following modules:

Synopsis

Basic types and renamed operations

type Rational = Fraction Integer Source #

We use Fraction instead of Ratio for consistency.

fromInteger :: Num r => Integer -> r Source #

To work with Num literals.

fromInteger' :: Ring r => Integer -> r Source #

algebra package's original fromInteger.

(^) :: Unital r => r -> Natural -> r infixr 8 Source #

Specialised version of pow which takes Naturals as a power.

(^^) :: Division r => r -> Integer -> r infixr 8 Source #

The original power function (^) of algebra

Combinator to use with RebindableSyntax extensions.

ifThenElse :: Bool -> a -> a -> a Source #

Wrapper types for conversion between Num family

newtype WrapNum a Source #

Wrapping Prelude's numerical types to treat with Algebra hierachy.

For Field or Euclidean instances, see WrapIntegral and WrapField.

N.B. This type provides a mean to convert from Nums to Rings, but there is no guarantee that WrapNum a is actually ring. For example, due to precision limitation, WrapPreldue Double even fails to be semigroup! For another simpler example, even though Natural comes with Num instance, but it doesn't support negate, so it cannot be Group.

Constructors

WrapNum 

Fields

Instances

Num a => LeftModule Integer (WrapNum a) Source # 

Methods

(.*) :: Integer -> WrapNum a -> WrapNum a #

Num a => LeftModule Natural (WrapNum a) Source # 

Methods

(.*) :: Natural -> WrapNum a -> WrapNum a #

Num a => RightModule Integer (WrapNum a) Source # 

Methods

(*.) :: WrapNum a -> Integer -> WrapNum a #

Num a => RightModule Natural (WrapNum a) Source # 

Methods

(*.) :: WrapNum a -> Natural -> WrapNum a #

Eq a => Eq (WrapNum a) Source # 

Methods

(==) :: WrapNum a -> WrapNum a -> Bool #

(/=) :: WrapNum a -> WrapNum a -> Bool #

Ord a => Ord (WrapNum a) Source # 

Methods

compare :: WrapNum a -> WrapNum a -> Ordering #

(<) :: WrapNum a -> WrapNum a -> Bool #

(<=) :: WrapNum a -> WrapNum a -> Bool #

(>) :: WrapNum a -> WrapNum a -> Bool #

(>=) :: WrapNum a -> WrapNum a -> Bool #

max :: WrapNum a -> WrapNum a -> WrapNum a #

min :: WrapNum a -> WrapNum a -> WrapNum a #

Read a => Read (WrapNum a) Source # 
Show a => Show (WrapNum a) Source # 

Methods

showsPrec :: Int -> WrapNum a -> ShowS #

show :: WrapNum a -> String #

showList :: [WrapNum a] -> ShowS #

Num a => Commutative (WrapNum a) Source # 
Num a => Ring (WrapNum a) Source # 

Methods

fromInteger :: Integer -> WrapNum a #

Num a => Rig (WrapNum a) Source # 

Methods

fromNatural :: Natural -> WrapNum a #

(Num a, Eq a) => DecidableZero (WrapNum a) Source # 

Methods

isZero :: WrapNum a -> Bool #

Num a => Unital (WrapNum a) Source # 

Methods

one :: WrapNum a #

pow :: WrapNum a -> Natural -> WrapNum a #

productWith :: Foldable f => (a -> WrapNum a) -> f a -> WrapNum a #

Num a => Group (WrapNum a) Source # 

Methods

(-) :: WrapNum a -> WrapNum a -> WrapNum a #

negate :: WrapNum a -> WrapNum a #

subtract :: WrapNum a -> WrapNum a -> WrapNum a #

times :: Integral n => n -> WrapNum a -> WrapNum a #

Num a => Multiplicative (WrapNum a) Source # 

Methods

(*) :: WrapNum a -> WrapNum a -> WrapNum a #

pow1p :: WrapNum a -> Natural -> WrapNum a #

productWith1 :: Foldable1 f => (a -> WrapNum a) -> f a -> WrapNum a #

Num a => Semiring (WrapNum a) Source # 
Num a => Monoidal (WrapNum a) Source # 

Methods

zero :: WrapNum a #

sinnum :: Natural -> WrapNum a -> WrapNum a #

sumWith :: Foldable f => (a -> WrapNum a) -> f a -> WrapNum a #

Num a => Additive (WrapNum a) Source # 

Methods

(+) :: WrapNum a -> WrapNum a -> WrapNum a #

sinnum1p :: Natural -> WrapNum a -> WrapNum a #

sumWith1 :: Foldable1 f => (a -> WrapNum a) -> f a -> WrapNum a #

Num a => Abelian (WrapNum a) Source # 
Wrapped (WrapNum a0) Source # 

Associated Types

type Unwrapped (WrapNum a0) :: * #

Methods

_Wrapped' :: Iso' (WrapNum a0) (Unwrapped (WrapNum a0)) #

(~) * (WrapNum a0) t0 => Rewrapped (WrapNum a1) t0 Source # 
type Unwrapped (WrapNum a0) Source # 
type Unwrapped (WrapNum a0) = a0

newtype WrapFractional a Source #

Similar to WrapNum, but produces Field instances from Fractionals.

See also: WrapIntegral and WrapNum.

Constructors

WrapFractional 

Fields

Instances

Num a => LeftModule Integer (WrapFractional a) Source # 
Num a => LeftModule Natural (WrapFractional a) Source # 
Num a => RightModule Integer (WrapFractional a) Source # 
Num a => RightModule Natural (WrapFractional a) Source # 
(Eq a, Fractional a) => IntegralDomain (WrapFractional a) Source # 
(Eq a, Fractional a) => GCDDomain (WrapFractional a) Source # 
(Eq a, Fractional a) => UFD (WrapFractional a) Source # 
(Eq a, Fractional a) => PID (WrapFractional a) Source # 
(Eq a, Fractional a) => Euclidean (WrapFractional a) Source # 
Num a => Commutative (WrapFractional a) Source # 
(Eq a, Fractional a) => UnitNormalForm (WrapFractional a) Source # 
(Eq a, Fractional a) => ZeroProductSemiring (WrapFractional a) Source # 
Num a => Ring (WrapFractional a) Source # 
Num a => Rig (WrapFractional a) Source # 
(Num a, Eq a) => DecidableZero (WrapFractional a) Source # 

Methods

isZero :: WrapFractional a -> Bool #

(Eq a, Fractional a) => DecidableUnits (WrapFractional a) Source # 
(Eq a, Fractional a) => DecidableAssociates (WrapFractional a) Source # 
Fractional a => Division (WrapFractional a) Source # 
Num a => Unital (WrapFractional a) Source # 
Num a => Group (WrapFractional a) Source # 
Num a => Multiplicative (WrapFractional a) Source # 
Num a => Semiring (WrapFractional a) Source # 
Num a => Monoidal (WrapFractional a) Source # 
Num a => Additive (WrapFractional a) Source # 
Num a => Abelian (WrapFractional a) Source # 
Wrapped (WrapFractional a0) Source # 

Associated Types

type Unwrapped (WrapFractional a0) :: * #

(~) * (WrapFractional a0) t0 => Rewrapped (WrapFractional a1) t0 Source # 
type Unwrapped (WrapFractional a0) Source # 
type Unwrapped (WrapFractional a0) = a0

newtype WrapIntegral a Source #

Similar to WrapNum, but produces Euclidean instances from Integrals.

See also: WrapFractional and WrapNum.

Constructors

WrapIntegral 

Fields

Instances

Num a => LeftModule Integer (WrapIntegral a) Source # 

Methods

(.*) :: Integer -> WrapIntegral a -> WrapIntegral a #

Num a => LeftModule Natural (WrapIntegral a) Source # 

Methods

(.*) :: Natural -> WrapIntegral a -> WrapIntegral a #

Num a => RightModule Integer (WrapIntegral a) Source # 

Methods

(*.) :: WrapIntegral a -> Integer -> WrapIntegral a #

Num a => RightModule Natural (WrapIntegral a) Source # 

Methods

(*.) :: WrapIntegral a -> Natural -> WrapIntegral a #

(Eq a, Integral a) => IntegralDomain (WrapIntegral a) Source # 
(Eq a, Integral a) => GCDDomain (WrapIntegral a) Source # 
(Eq a, Integral a) => UFD (WrapIntegral a) Source # 
(Eq a, Integral a) => PID (WrapIntegral a) Source # 
(Eq a, Integral a) => Euclidean (WrapIntegral a) Source # 
Num a => Commutative (WrapIntegral a) Source # 
(Eq a, Integral a) => UnitNormalForm (WrapIntegral a) Source # 
(Eq a, Integral a) => ZeroProductSemiring (WrapIntegral a) Source # 
Num a => Ring (WrapIntegral a) Source # 
Num a => Rig (WrapIntegral a) Source # 
(Num a, Eq a) => DecidableZero (WrapIntegral a) Source # 

Methods

isZero :: WrapIntegral a -> Bool #

(Eq a, Integral a) => DecidableUnits (WrapIntegral a) Source # 
(Eq a, Integral a) => DecidableAssociates (WrapIntegral a) Source # 
Num a => Unital (WrapIntegral a) Source # 

Methods

one :: WrapIntegral a #

pow :: WrapIntegral a -> Natural -> WrapIntegral a #

productWith :: Foldable f => (a -> WrapIntegral a) -> f a -> WrapIntegral a #

Num a => Group (WrapIntegral a) Source # 
Num a => Multiplicative (WrapIntegral a) Source # 
Num a => Semiring (WrapIntegral a) Source # 
Num a => Monoidal (WrapIntegral a) Source # 

Methods

zero :: WrapIntegral a #

sinnum :: Natural -> WrapIntegral a -> WrapIntegral a #

sumWith :: Foldable f => (a -> WrapIntegral a) -> f a -> WrapIntegral a #

Num a => Additive (WrapIntegral a) Source # 
Num a => Abelian (WrapIntegral a) Source # 
Wrapped (WrapIntegral a0) Source # 

Associated Types

type Unwrapped (WrapIntegral a0) :: * #

(~) * (WrapIntegral a0) t0 => Rewrapped (WrapIntegral a1) t0 Source # 
type Unwrapped (WrapIntegral a0) Source # 
type Unwrapped (WrapIntegral a0) = a0

newtype WrapAlgebra a Source #

Turning types from Algebra into Prelude's Num instances.

N.B. Since Real's toRational constraint is too tight, we won't provide the inverse of WrapIntegral and provide Fractional instance only.

Constructors

WrapAlgebra 

Fields

Instances

Eq a => Eq (WrapAlgebra a) Source # 
(DivisionRing a, UnitNormalForm a) => Fractional (WrapAlgebra a) Source # 
(Ring a, UnitNormalForm a) => Num (WrapAlgebra a) Source # 
Ord a => Ord (WrapAlgebra a) Source # 
Read a => Read (WrapAlgebra a) Source # 
Show a => Show (WrapAlgebra a) Source # 
Wrapped (WrapAlgebra a0) Source # 

Associated Types

type Unwrapped (WrapAlgebra a0) :: * #

(~) * (WrapAlgebra a0) t0 => Rewrapped (WrapAlgebra a1) t0 Source # 
type Unwrapped (WrapAlgebra a0) Source # 
type Unwrapped (WrapAlgebra a0) = a0

newtype Add a Source #

Monoid instances for Additives. N.B. Unlike WrapNum, Num instance is just inhereted from the unwrapped data.

Constructors

Add 

Fields

Instances

Eq a => Eq (Add a) Source # 

Methods

(==) :: Add a -> Add a -> Bool #

(/=) :: Add a -> Add a -> Bool #

Num a => Num (Add a) Source # 

Methods

(+) :: Add a -> Add a -> Add a #

(-) :: Add a -> Add a -> Add a #

(*) :: Add a -> Add a -> Add a #

negate :: Add a -> Add a #

abs :: Add a -> Add a #

signum :: Add a -> Add a #

fromInteger :: Integer -> Add a #

Ord a => Ord (Add a) Source # 

Methods

compare :: Add a -> Add a -> Ordering #

(<) :: Add a -> Add a -> Bool #

(<=) :: Add a -> Add a -> Bool #

(>) :: Add a -> Add a -> Bool #

(>=) :: Add a -> Add a -> Bool #

max :: Add a -> Add a -> Add a #

min :: Add a -> Add a -> Add a #

Read a => Read (Add a) Source # 
Show a => Show (Add a) Source # 

Methods

showsPrec :: Int -> Add a -> ShowS #

show :: Add a -> String #

showList :: [Add a] -> ShowS #

Additive a => Semigroup (Add a) Source # 

Methods

(<>) :: Add a -> Add a -> Add a #

sconcat :: NonEmpty (Add a) -> Add a #

stimes :: Integral b => b -> Add a -> Add a #

Monoidal a => Monoid (Add a) Source # 

Methods

mempty :: Add a #

mappend :: Add a -> Add a -> Add a #

mconcat :: [Add a] -> Add a #

Wrapped (Add a0) Source # 

Associated Types

type Unwrapped (Add a0) :: * #

Methods

_Wrapped' :: Iso' (Add a0) (Unwrapped (Add a0)) #

(~) * (Add a0) t0 => Rewrapped (Add a1) t0 Source # 
type Unwrapped (Add a0) Source # 
type Unwrapped (Add a0) = a0

newtype Mult a Source #

Monoid instances for Additives. N.B. Unlike WrapNum, Num instance is just inhereted from the unwrapped data.

Constructors

Mult 

Fields

Instances

Eq a => Eq (Mult a) Source # 

Methods

(==) :: Mult a -> Mult a -> Bool #

(/=) :: Mult a -> Mult a -> Bool #

Num a => Num (Mult a) Source # 

Methods

(+) :: Mult a -> Mult a -> Mult a #

(-) :: Mult a -> Mult a -> Mult a #

(*) :: Mult a -> Mult a -> Mult a #

negate :: Mult a -> Mult a #

abs :: Mult a -> Mult a #

signum :: Mult a -> Mult a #

fromInteger :: Integer -> Mult a #

Ord a => Ord (Mult a) Source # 

Methods

compare :: Mult a -> Mult a -> Ordering #

(<) :: Mult a -> Mult a -> Bool #

(<=) :: Mult a -> Mult a -> Bool #

(>) :: Mult a -> Mult a -> Bool #

(>=) :: Mult a -> Mult a -> Bool #

max :: Mult a -> Mult a -> Mult a #

min :: Mult a -> Mult a -> Mult a #

Read a => Read (Mult a) Source # 
Show a => Show (Mult a) Source # 

Methods

showsPrec :: Int -> Mult a -> ShowS #

show :: Mult a -> String #

showList :: [Mult a] -> ShowS #

Multiplicative a => Semigroup (Mult a) Source # 

Methods

(<>) :: Mult a -> Mult a -> Mult a #

sconcat :: NonEmpty (Mult a) -> Mult a #

stimes :: Integral b => b -> Mult a -> Mult a #

Unital a => Monoid (Mult a) Source # 

Methods

mempty :: Mult a #

mappend :: Mult a -> Mult a -> Mult a #

mconcat :: [Mult a] -> Mult a #

Wrapped (Mult a0) Source # 

Associated Types

type Unwrapped (Mult a0) :: * #

Methods

_Wrapped' :: Iso' (Mult a0) (Unwrapped (Mult a0)) #

(~) * (Mult a0) t0 => Rewrapped (Mult a1) t0 Source # 
type Unwrapped (Mult a0) Source # 
type Unwrapped (Mult a0) = a0

Old Prelude's Numeric type classes and functions, without confliction

class Num a where #

Basic numeric class.

Minimal complete definition

(+), (*), abs, signum, fromInteger, (negate | (-))

Methods

abs :: a -> a #

Absolute value.

signum :: a -> a #

Sign of a number. The functions abs and signum should satisfy the law:

abs x * signum x == x

For real numbers, the signum is either -1 (negative), 0 (zero) or 1 (positive).

Instances

Num Int 

Methods

(+) :: Int -> Int -> Int #

(-) :: Int -> Int -> Int #

(*) :: Int -> Int -> Int #

negate :: Int -> Int #

abs :: Int -> Int #

signum :: Int -> Int #

fromInteger :: Integer -> Int #

Num Int8 

Methods

(+) :: Int8 -> Int8 -> Int8 #

(-) :: Int8 -> Int8 -> Int8 #

(*) :: Int8 -> Int8 -> Int8 #

negate :: Int8 -> Int8 #

abs :: Int8 -> Int8 #

signum :: Int8 -> Int8 #

fromInteger :: Integer -> Int8 #

Num Int16 
Num Int32 
Num Int64 
Num Integer 
Num Word 

Methods

(+) :: Word -> Word -> Word #

(-) :: Word -> Word -> Word #

(*) :: Word -> Word -> Word #

negate :: Word -> Word #

abs :: Word -> Word #

signum :: Word -> Word #

fromInteger :: Integer -> Word #

Num Word8 
Num Word16 
Num Word32 
Num Word64 
Num Natural 
Num CDev 

Methods

(+) :: CDev -> CDev -> CDev #

(-) :: CDev -> CDev -> CDev #

(*) :: CDev -> CDev -> CDev #

negate :: CDev -> CDev #

abs :: CDev -> CDev #

signum :: CDev -> CDev #

fromInteger :: Integer -> CDev #

Num CIno 

Methods

(+) :: CIno -> CIno -> CIno #

(-) :: CIno -> CIno -> CIno #

(*) :: CIno -> CIno -> CIno #

negate :: CIno -> CIno #

abs :: CIno -> CIno #

signum :: CIno -> CIno #

fromInteger :: Integer -> CIno #

Num CMode 
Num COff 

Methods

(+) :: COff -> COff -> COff #

(-) :: COff -> COff -> COff #

(*) :: COff -> COff -> COff #

negate :: COff -> COff #

abs :: COff -> COff #

signum :: COff -> COff #

fromInteger :: Integer -> COff #

Num CPid 

Methods

(+) :: CPid -> CPid -> CPid #

(-) :: CPid -> CPid -> CPid #

(*) :: CPid -> CPid -> CPid #

negate :: CPid -> CPid #

abs :: CPid -> CPid #

signum :: CPid -> CPid #

fromInteger :: Integer -> CPid #

Num CSsize 
Num CGid 

Methods

(+) :: CGid -> CGid -> CGid #

(-) :: CGid -> CGid -> CGid #

(*) :: CGid -> CGid -> CGid #

negate :: CGid -> CGid #

abs :: CGid -> CGid #

signum :: CGid -> CGid #

fromInteger :: Integer -> CGid #

Num CNlink 
Num CUid 

Methods

(+) :: CUid -> CUid -> CUid #

(-) :: CUid -> CUid -> CUid #

(*) :: CUid -> CUid -> CUid #

negate :: CUid -> CUid #

abs :: CUid -> CUid #

signum :: CUid -> CUid #

fromInteger :: Integer -> CUid #

Num CCc 

Methods

(+) :: CCc -> CCc -> CCc #

(-) :: CCc -> CCc -> CCc #

(*) :: CCc -> CCc -> CCc #

negate :: CCc -> CCc #

abs :: CCc -> CCc #

signum :: CCc -> CCc #

fromInteger :: Integer -> CCc #

Num CSpeed 
Num CTcflag 
Num CRLim 
Num Fd 

Methods

(+) :: Fd -> Fd -> Fd #

(-) :: Fd -> Fd -> Fd #

(*) :: Fd -> Fd -> Fd #

negate :: Fd -> Fd #

abs :: Fd -> Fd #

signum :: Fd -> Fd #

fromInteger :: Integer -> Fd #

Num CChar 
Num CSChar 
Num CUChar 
Num CShort 
Num CUShort 
Num CInt 

Methods

(+) :: CInt -> CInt -> CInt #

(-) :: CInt -> CInt -> CInt #

(*) :: CInt -> CInt -> CInt #

negate :: CInt -> CInt #

abs :: CInt -> CInt #

signum :: CInt -> CInt #

fromInteger :: Integer -> CInt #

Num CUInt 
Num CLong 
Num CULong 
Num CLLong 
Num CULLong 
Num CFloat 
Num CDouble 
Num CPtrdiff 
Num CSize 
Num CWchar 
Num CSigAtomic 
Num CClock 
Num CTime 
Num CUSeconds 
Num CSUSeconds 
Num CIntPtr 
Num CUIntPtr 
Num CIntMax 
Num CUIntMax 
Integral a => Num (Ratio a) 

Methods

(+) :: Ratio a -> Ratio a -> Ratio a #

(-) :: Ratio a -> Ratio a -> Ratio a #

(*) :: Ratio a -> Ratio a -> Ratio a #

negate :: Ratio a -> Ratio a #

abs :: Ratio a -> Ratio a #

signum :: Ratio a -> Ratio a #

fromInteger :: Integer -> Ratio a #

Num a => Num (Identity a) 
Num a => Num (Min a) 

Methods

(+) :: Min a -> Min a -> Min a #

(-) :: Min a -> Min a -> Min a #

(*) :: Min a -> Min a -> Min a #

negate :: Min a -> Min a #

abs :: Min a -> Min a #

signum :: Min a -> Min a #

fromInteger :: Integer -> Min a #

Num a => Num (Max a) 

Methods

(+) :: Max a -> Max a -> Max a #

(-) :: Max a -> Max a -> Max a #

(*) :: Max a -> Max a -> Max a #

negate :: Max a -> Max a #

abs :: Max a -> Max a #

signum :: Max a -> Max a #

fromInteger :: Integer -> Max a #

RealFloat a => Num (Complex a) 

Methods

(+) :: Complex a -> Complex a -> Complex a #

(-) :: Complex a -> Complex a -> Complex a #

(*) :: Complex a -> Complex a -> Complex a #

negate :: Complex a -> Complex a #

abs :: Complex a -> Complex a #

signum :: Complex a -> Complex a #

fromInteger :: Integer -> Complex a #

Num a => Num (Sum a) 

Methods

(+) :: Sum a -> Sum a -> Sum a #

(-) :: Sum a -> Sum a -> Sum a #

(*) :: Sum a -> Sum a -> Sum a #

negate :: Sum a -> Sum a #

abs :: Sum a -> Sum a #

signum :: Sum a -> Sum a #

fromInteger :: Integer -> Sum a #

Num a => Num (Product a) 

Methods

(+) :: Product a -> Product a -> Product a #

(-) :: Product a -> Product a -> Product a #

(*) :: Product a -> Product a -> Product a #

negate :: Product a -> Product a #

abs :: Product a -> Product a #

signum :: Product a -> Product a #

fromInteger :: Integer -> Product a #

Num a => Num (Mult a) # 

Methods

(+) :: Mult a -> Mult a -> Mult a #

(-) :: Mult a -> Mult a -> Mult a #

(*) :: Mult a -> Mult a -> Mult a #

negate :: Mult a -> Mult a #

abs :: Mult a -> Mult a #

signum :: Mult a -> Mult a #

fromInteger :: Integer -> Mult a #

Num a => Num (Add a) # 

Methods

(+) :: Add a -> Add a -> Add a #

(-) :: Add a -> Add a -> Add a #

(*) :: Add a -> Add a -> Add a #

negate :: Add a -> Add a #

abs :: Add a -> Add a #

signum :: Add a -> Add a #

fromInteger :: Integer -> Add a #

(Ring a, UnitNormalForm a) => Num (WrapAlgebra a) # 
Num a => Num (Op a b) 

Methods

(+) :: Op a b -> Op a b -> Op a b #

(-) :: Op a b -> Op a b -> Op a b #

(*) :: Op a b -> Op a b -> Op a b #

negate :: Op a b -> Op a b #

abs :: Op a b -> Op a b #

signum :: Op a b -> Op a b #

fromInteger :: Integer -> Op a b #

Num a => Num (Const k a b) 

Methods

(+) :: Const k a b -> Const k a b -> Const k a b #

(-) :: Const k a b -> Const k a b -> Const k a b #

(*) :: Const k a b -> Const k a b -> Const k a b #

negate :: Const k a b -> Const k a b #

abs :: Const k a b -> Const k a b #

signum :: Const k a b -> Const k a b #

fromInteger :: Integer -> Const k a b #

Num (f a) => Num (Alt k f a) 

Methods

(+) :: Alt k f a -> Alt k f a -> Alt k f a #

(-) :: Alt k f a -> Alt k f a -> Alt k f a #

(*) :: Alt k f a -> Alt k f a -> Alt k f a #

negate :: Alt k f a -> Alt k f a #

abs :: Alt k f a -> Alt k f a #

signum :: Alt k f a -> Alt k f a #

fromInteger :: Integer -> Alt k f a #

Num a => Num (Tagged k s a) 

Methods

(+) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

(-) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

(*) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

negate :: Tagged k s a -> Tagged k s a #

abs :: Tagged k s a -> Tagged k s a #

signum :: Tagged k s a -> Tagged k s a #

fromInteger :: Integer -> Tagged k s a #

class (Real a, Enum a) => Integral a where #

Integral numbers, supporting integer division.

Minimal complete definition

quotRem, toInteger

Methods

div :: a -> a -> a infixl 7 #

integer division truncated toward negative infinity

mod :: a -> a -> a infixl 7 #

integer modulus, satisfying

(x `div` y)*y + (x `mod` y) == x

toInteger :: a -> Integer #

conversion to Integer

Instances

Integral Int 

Methods

quot :: Int -> Int -> Int #

rem :: Int -> Int -> Int #

div :: Int -> Int -> Int #

mod :: Int -> Int -> Int #

quotRem :: Int -> Int -> (Int, Int) #

divMod :: Int -> Int -> (Int, Int) #

toInteger :: Int -> Integer #

Integral Int8 

Methods

quot :: Int8 -> Int8 -> Int8 #

rem :: Int8 -> Int8 -> Int8 #

div :: Int8 -> Int8 -> Int8 #

mod :: Int8 -> Int8 -> Int8 #

quotRem :: Int8 -> Int8 -> (Int8, Int8) #

divMod :: Int8 -> Int8 -> (Int8, Int8) #

toInteger :: Int8 -> Integer #

Integral Int16 
Integral Int32 
Integral Int64 
Integral Integer 
Integral Word 

Methods

quot :: Word -> Word -> Word #

rem :: Word -> Word -> Word #

div :: Word -> Word -> Word #

mod :: Word -> Word -> Word #

quotRem :: Word -> Word -> (Word, Word) #

divMod :: Word -> Word -> (Word, Word) #

toInteger :: Word -> Integer #

Integral Word8 
Integral Word16 
Integral Word32 
Integral Word64 
Integral Natural 
Integral CDev 

Methods

quot :: CDev -> CDev -> CDev #

rem :: CDev -> CDev -> CDev #

div :: CDev -> CDev -> CDev #

mod :: CDev -> CDev -> CDev #

quotRem :: CDev -> CDev -> (CDev, CDev) #

divMod :: CDev -> CDev -> (CDev, CDev) #

toInteger :: CDev -> Integer #

Integral CIno 

Methods

quot :: CIno -> CIno -> CIno #

rem :: CIno -> CIno -> CIno #

div :: CIno -> CIno -> CIno #

mod :: CIno -> CIno -> CIno #

quotRem :: CIno -> CIno -> (CIno, CIno) #

divMod :: CIno -> CIno -> (CIno, CIno) #

toInteger :: CIno -> Integer #

Integral CMode 
Integral COff 

Methods

quot :: COff -> COff -> COff #

rem :: COff -> COff -> COff #

div :: COff -> COff -> COff #

mod :: COff -> COff -> COff #

quotRem :: COff -> COff -> (COff, COff) #

divMod :: COff -> COff -> (COff, COff) #

toInteger :: COff -> Integer #

Integral CPid 

Methods

quot :: CPid -> CPid -> CPid #

rem :: CPid -> CPid -> CPid #

div :: CPid -> CPid -> CPid #

mod :: CPid -> CPid -> CPid #

quotRem :: CPid -> CPid -> (CPid, CPid) #

divMod :: CPid -> CPid -> (CPid, CPid) #

toInteger :: CPid -> Integer #

Integral CSsize 
Integral CGid 

Methods

quot :: CGid -> CGid -> CGid #

rem :: CGid -> CGid -> CGid #

div :: CGid -> CGid -> CGid #

mod :: CGid -> CGid -> CGid #

quotRem :: CGid -> CGid -> (CGid, CGid) #

divMod :: CGid -> CGid -> (CGid, CGid) #

toInteger :: CGid -> Integer #

Integral CNlink 
Integral CUid 

Methods

quot :: CUid -> CUid -> CUid #

rem :: CUid -> CUid -> CUid #

div :: CUid -> CUid -> CUid #

mod :: CUid -> CUid -> CUid #

quotRem :: CUid -> CUid -> (CUid, CUid) #

divMod :: CUid -> CUid -> (CUid, CUid) #

toInteger :: CUid -> Integer #

Integral CTcflag 
Integral CRLim 
Integral Fd 

Methods

quot :: Fd -> Fd -> Fd #

rem :: Fd -> Fd -> Fd #

div :: Fd -> Fd -> Fd #

mod :: Fd -> Fd -> Fd #

quotRem :: Fd -> Fd -> (Fd, Fd) #

divMod :: Fd -> Fd -> (Fd, Fd) #

toInteger :: Fd -> Integer #

Integral CChar 
Integral CSChar 
Integral CUChar 
Integral CShort 
Integral CUShort 
Integral CInt 

Methods

quot :: CInt -> CInt -> CInt #

rem :: CInt -> CInt -> CInt #

div :: CInt -> CInt -> CInt #

mod :: CInt -> CInt -> CInt #

quotRem :: CInt -> CInt -> (CInt, CInt) #

divMod :: CInt -> CInt -> (CInt, CInt) #

toInteger :: CInt -> Integer #

Integral CUInt 
Integral CLong 
Integral CULong 
Integral CLLong 
Integral CULLong 
Integral CPtrdiff 
Integral CSize 
Integral CWchar 
Integral CSigAtomic 
Integral CIntPtr 
Integral CUIntPtr 
Integral CIntMax 
Integral CUIntMax 
Integral a => Integral (Identity a) 
Integral a => Integral (Const k a b) 

Methods

quot :: Const k a b -> Const k a b -> Const k a b #

rem :: Const k a b -> Const k a b -> Const k a b #

div :: Const k a b -> Const k a b -> Const k a b #

mod :: Const k a b -> Const k a b -> Const k a b #

quotRem :: Const k a b -> Const k a b -> (Const k a b, Const k a b) #

divMod :: Const k a b -> Const k a b -> (Const k a b, Const k a b) #

toInteger :: Const k a b -> Integer #

Integral a => Integral (Tagged k s a) 

Methods

quot :: Tagged k s a -> Tagged k s a -> Tagged k s a #

rem :: Tagged k s a -> Tagged k s a -> Tagged k s a #

div :: Tagged k s a -> Tagged k s a -> Tagged k s a #

mod :: Tagged k s a -> Tagged k s a -> Tagged k s a #

quotRem :: Tagged k s a -> Tagged k s a -> (Tagged k s a, Tagged k s a) #

divMod :: Tagged k s a -> Tagged k s a -> (Tagged k s a, Tagged k s a) #

toInteger :: Tagged k s a -> Integer #

toInteger :: Integral a => a -> Integer #

conversion to Integer

class (Num a, Ord a) => Real a where #

Minimal complete definition

toRational

Methods

toRational :: a -> Rational #

the rational equivalent of its real argument with full precision

Instances

Real Int 

Methods

toRational :: Int -> Rational #

Real Int8 

Methods

toRational :: Int8 -> Rational #

Real Int16 

Methods

toRational :: Int16 -> Rational #

Real Int32 

Methods

toRational :: Int32 -> Rational #

Real Int64 

Methods

toRational :: Int64 -> Rational #

Real Integer 
Real Word 

Methods

toRational :: Word -> Rational #

Real Word8 

Methods

toRational :: Word8 -> Rational #

Real Word16 
Real Word32 
Real Word64 
Real Natural 
Real CDev 

Methods

toRational :: CDev -> Rational #

Real CIno 

Methods

toRational :: CIno -> Rational #

Real CMode 

Methods

toRational :: CMode -> Rational #

Real COff 

Methods

toRational :: COff -> Rational #

Real CPid 

Methods

toRational :: CPid -> Rational #

Real CSsize 
Real CGid 

Methods

toRational :: CGid -> Rational #

Real CNlink 
Real CUid 

Methods

toRational :: CUid -> Rational #

Real CCc 

Methods

toRational :: CCc -> Rational #

Real CSpeed 
Real CTcflag 
Real CRLim 

Methods

toRational :: CRLim -> Rational #

Real Fd 

Methods

toRational :: Fd -> Rational #

Real CChar 

Methods

toRational :: CChar -> Rational #

Real CSChar 
Real CUChar 
Real CShort 
Real CUShort 
Real CInt 

Methods

toRational :: CInt -> Rational #

Real CUInt 

Methods

toRational :: CUInt -> Rational #

Real CLong 

Methods

toRational :: CLong -> Rational #

Real CULong 
Real CLLong 
Real CULLong 
Real CFloat 
Real CDouble 
Real CPtrdiff 
Real CSize 

Methods

toRational :: CSize -> Rational #

Real CWchar 
Real CSigAtomic 
Real CClock 
Real CTime 

Methods

toRational :: CTime -> Rational #

Real CUSeconds 
Real CSUSeconds 
Real CIntPtr 
Real CUIntPtr 
Real CIntMax 
Real CUIntMax 
Integral a => Real (Ratio a) 

Methods

toRational :: Ratio a -> Rational #

Real a => Real (Identity a) 

Methods

toRational :: Identity a -> Rational #

Real a => Real (Const k a b) 

Methods

toRational :: Const k a b -> Rational #

Real a => Real (Tagged k s a) 

Methods

toRational :: Tagged k s a -> Rational #

class Num a => Fractional a #

Fractional numbers, supporting real division.

Minimal complete definition

fromRational, (recip | (/))

Instances

Fractional CFloat 
Fractional CDouble 
Integral a => Fractional (Ratio a) 

Methods

(/) :: Ratio a -> Ratio a -> Ratio a #

recip :: Ratio a -> Ratio a #

fromRational :: Rational -> Ratio a #

Fractional a => Fractional (Identity a) 
RealFloat a => Fractional (Complex a) 

Methods

(/) :: Complex a -> Complex a -> Complex a #

recip :: Complex a -> Complex a #

fromRational :: Rational -> Complex a #

(DivisionRing a, UnitNormalForm a) => Fractional (WrapAlgebra a) # 
Fractional a => Fractional (Op a b) 

Methods

(/) :: Op a b -> Op a b -> Op a b #

recip :: Op a b -> Op a b #

fromRational :: Rational -> Op a b #

Fractional a => Fractional (Const k a b) 

Methods

(/) :: Const k a b -> Const k a b -> Const k a b #

recip :: Const k a b -> Const k a b #

fromRational :: Rational -> Const k a b #

Fractional a => Fractional (Tagged k s a) 

Methods

(/) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

recip :: Tagged k s a -> Tagged k s a #

fromRational :: Rational -> Tagged k s a #

class Fractional a => Floating a where #

Trigonometric and hyperbolic functions and related functions.

Minimal complete definition

pi, exp, log, sin, cos, asin, acos, atan, sinh, cosh, asinh, acosh, atanh

Methods

pi :: a #

exp :: a -> a #

log :: a -> a #

sqrt :: a -> a #

(**) :: a -> a -> a infixr 8 #

logBase :: a -> a -> a #

sin :: a -> a #

cos :: a -> a #

tan :: a -> a #

asin :: a -> a #

acos :: a -> a #

atan :: a -> a #

sinh :: a -> a #

cosh :: a -> a #

tanh :: a -> a #

asinh :: a -> a #

acosh :: a -> a #

atanh :: a -> a #

Instances

Floating Double 
Floating Float 
Floating CFloat 
Floating CDouble 
Floating a => Floating (Identity a) 
RealFloat a => Floating (Complex a) 

Methods

pi :: Complex a #

exp :: Complex a -> Complex a #

log :: Complex a -> Complex a #

sqrt :: Complex a -> Complex a #

(**) :: Complex a -> Complex a -> Complex a #

logBase :: Complex a -> Complex a -> Complex a #

sin :: Complex a -> Complex a #

cos :: Complex a -> Complex a #

tan :: Complex a -> Complex a #

asin :: Complex a -> Complex a #

acos :: Complex a -> Complex a #

atan :: Complex a -> Complex a #

sinh :: Complex a -> Complex a #

cosh :: Complex a -> Complex a #

tanh :: Complex a -> Complex a #

asinh :: Complex a -> Complex a #

acosh :: Complex a -> Complex a #

atanh :: Complex a -> Complex a #

log1p :: Complex a -> Complex a #

expm1 :: Complex a -> Complex a #

log1pexp :: Complex a -> Complex a #

log1mexp :: Complex a -> Complex a #

Floating a => Floating (Op a b) 

Methods

pi :: Op a b #

exp :: Op a b -> Op a b #

log :: Op a b -> Op a b #

sqrt :: Op a b -> Op a b #

(**) :: Op a b -> Op a b -> Op a b #

logBase :: Op a b -> Op a b -> Op a b #

sin :: Op a b -> Op a b #

cos :: Op a b -> Op a b #

tan :: Op a b -> Op a b #

asin :: Op a b -> Op a b #

acos :: Op a b -> Op a b #

atan :: Op a b -> Op a b #

sinh :: Op a b -> Op a b #

cosh :: Op a b -> Op a b #

tanh :: Op a b -> Op a b #

asinh :: Op a b -> Op a b #

acosh :: Op a b -> Op a b #

atanh :: Op a b -> Op a b #

log1p :: Op a b -> Op a b #

expm1 :: Op a b -> Op a b #

log1pexp :: Op a b -> Op a b #

log1mexp :: Op a b -> Op a b #

Floating a => Floating (Const k a b) 

Methods

pi :: Const k a b #

exp :: Const k a b -> Const k a b #

log :: Const k a b -> Const k a b #

sqrt :: Const k a b -> Const k a b #

(**) :: Const k a b -> Const k a b -> Const k a b #

logBase :: Const k a b -> Const k a b -> Const k a b #

sin :: Const k a b -> Const k a b #

cos :: Const k a b -> Const k a b #

tan :: Const k a b -> Const k a b #

asin :: Const k a b -> Const k a b #

acos :: Const k a b -> Const k a b #

atan :: Const k a b -> Const k a b #

sinh :: Const k a b -> Const k a b #

cosh :: Const k a b -> Const k a b #

tanh :: Const k a b -> Const k a b #

asinh :: Const k a b -> Const k a b #

acosh :: Const k a b -> Const k a b #

atanh :: Const k a b -> Const k a b #

log1p :: Const k a b -> Const k a b #

expm1 :: Const k a b -> Const k a b #

log1pexp :: Const k a b -> Const k a b #

log1mexp :: Const k a b -> Const k a b #

Floating a => Floating (Tagged k s a) 

Methods

pi :: Tagged k s a #

exp :: Tagged k s a -> Tagged k s a #

log :: Tagged k s a -> Tagged k s a #

sqrt :: Tagged k s a -> Tagged k s a #

(**) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

logBase :: Tagged k s a -> Tagged k s a -> Tagged k s a #

sin :: Tagged k s a -> Tagged k s a #

cos :: Tagged k s a -> Tagged k s a #

tan :: Tagged k s a -> Tagged k s a #

asin :: Tagged k s a -> Tagged k s a #

acos :: Tagged k s a -> Tagged k s a #

atan :: Tagged k s a -> Tagged k s a #

sinh :: Tagged k s a -> Tagged k s a #

cosh :: Tagged k s a -> Tagged k s a #

tanh :: Tagged k s a -> Tagged k s a #

asinh :: Tagged k s a -> Tagged k s a #

acosh :: Tagged k s a -> Tagged k s a #

atanh :: Tagged k s a -> Tagged k s a #

log1p :: Tagged k s a -> Tagged k s a #

expm1 :: Tagged k s a -> Tagged k s a #

log1pexp :: Tagged k s a -> Tagged k s a #

log1mexp :: Tagged k s a -> Tagged k s a #

class (Real a, Fractional a) => RealFrac a where #

Extracting components of fractions.

Minimal complete definition

properFraction

Methods

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

The function properFraction takes a real fractional number x and returns a pair (n,f) such that x = n+f, and:

  • n is an integral number with the same sign as x; and
  • f is a fraction with the same type and sign as x, and with absolute value less than 1.

The default definitions of the ceiling, floor, truncate and round functions are in terms of properFraction.

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

truncate x returns the integer nearest x between zero and x

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

round x returns the nearest integer to x; the even integer if x is equidistant between two integers

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

ceiling x returns the least integer not less than x

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

floor x returns the greatest integer not greater than x

Instances

RealFrac CFloat 

Methods

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

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

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

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

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

RealFrac CDouble 

Methods

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

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

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

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

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

Integral a => RealFrac (Ratio a) 

Methods

properFraction :: Integral b => Ratio a -> (b, Ratio a) #

truncate :: Integral b => Ratio a -> b #

round :: Integral b => Ratio a -> b #

ceiling :: Integral b => Ratio a -> b #

floor :: Integral b => Ratio a -> b #

RealFrac a => RealFrac (Identity a) 

Methods

properFraction :: Integral b => Identity a -> (b, Identity a) #

truncate :: Integral b => Identity a -> b #

round :: Integral b => Identity a -> b #

ceiling :: Integral b => Identity a -> b #

floor :: Integral b => Identity a -> b #

RealFrac a => RealFrac (Const k a b) 

Methods

properFraction :: Integral b => Const k a b -> (b, Const k a b) #

truncate :: Integral b => Const k a b -> b #

round :: Integral b => Const k a b -> b #

ceiling :: Integral b => Const k a b -> b #

floor :: Integral b => Const k a b -> b #

RealFrac a => RealFrac (Tagged k s a) 

Methods

properFraction :: Integral b => Tagged k s a -> (b, Tagged k s a) #

truncate :: Integral b => Tagged k s a -> b #

round :: Integral b => Tagged k s a -> b #

ceiling :: Integral b => Tagged k s a -> b #

floor :: Integral b => Tagged k s a -> b #

class (RealFrac a, Floating a) => RealFloat a where #

Efficient, machine-independent access to the components of a floating-point number.

Methods

floatRadix :: a -> Integer #

a constant function, returning the radix of the representation (often 2)

floatDigits :: a -> Int #

a constant function, returning the number of digits of floatRadix in the significand

floatRange :: a -> (Int, Int) #

a constant function, returning the lowest and highest values the exponent may assume

decodeFloat :: a -> (Integer, Int) #

The function decodeFloat applied to a real floating-point number returns the significand expressed as an Integer and an appropriately scaled exponent (an Int). If decodeFloat x yields (m,n), then x is equal in value to m*b^^n, where b is the floating-point radix, and furthermore, either m and n are both zero or else b^(d-1) <= abs m < b^d, where d is the value of floatDigits x. In particular, decodeFloat 0 = (0,0). If the type contains a negative zero, also decodeFloat (-0.0) = (0,0). The result of decodeFloat x is unspecified if either of isNaN x or isInfinite x is True.

encodeFloat :: Integer -> Int -> a #

encodeFloat performs the inverse of decodeFloat in the sense that for finite x with the exception of -0.0, uncurry encodeFloat (decodeFloat x) = x. encodeFloat m n is one of the two closest representable floating-point numbers to m*b^^n (or ±Infinity if overflow occurs); usually the closer, but if m contains too many bits, the result may be rounded in the wrong direction.

exponent :: a -> Int #

exponent corresponds to the second component of decodeFloat. exponent 0 = 0 and for finite nonzero x, exponent x = snd (decodeFloat x) + floatDigits x. If x is a finite floating-point number, it is equal in value to significand x * b ^^ exponent x, where b is the floating-point radix. The behaviour is unspecified on infinite or NaN values.

significand :: a -> a #

The first component of decodeFloat, scaled to lie in the open interval (-1,1), either 0.0 or of absolute value >= 1/b, where b is the floating-point radix. The behaviour is unspecified on infinite or NaN values.

scaleFloat :: Int -> a -> a #

multiplies a floating-point number by an integer power of the radix

isNaN :: a -> Bool #

True if the argument is an IEEE "not-a-number" (NaN) value

isInfinite :: a -> Bool #

True if the argument is an IEEE infinity or negative infinity

isDenormalized :: a -> Bool #

True if the argument is too small to be represented in normalized format

isNegativeZero :: a -> Bool #

True if the argument is an IEEE negative zero

isIEEE :: a -> Bool #

True if the argument is an IEEE floating point number

atan2 :: a -> a -> a #

a version of arctangent taking two real floating-point arguments. For real floating x and y, atan2 y x computes the angle (from the positive x-axis) of the vector from the origin to the point (x,y). atan2 y x returns a value in the range [-pi, pi]. It follows the Common Lisp semantics for the origin when signed zeroes are supported. atan2 y 1, with y in a type that is RealFloat, should return the same value as atan y. A default definition of atan2 is provided, but implementors can provide a more accurate implementation.

Instances

RealFloat Double 
RealFloat Float 
RealFloat CFloat 
RealFloat CDouble 
RealFloat a => RealFloat (Identity a) 
RealFloat a => RealFloat (Const k a b) 

Methods

floatRadix :: Const k a b -> Integer #

floatDigits :: Const k a b -> Int #

floatRange :: Const k a b -> (Int, Int) #

decodeFloat :: Const k a b -> (Integer, Int) #

encodeFloat :: Integer -> Int -> Const k a b #

exponent :: Const k a b -> Int #

significand :: Const k a b -> Const k a b #

scaleFloat :: Int -> Const k a b -> Const k a b #

isNaN :: Const k a b -> Bool #

isInfinite :: Const k a b -> Bool #

isDenormalized :: Const k a b -> Bool #

isNegativeZero :: Const k a b -> Bool #

isIEEE :: Const k a b -> Bool #

atan2 :: Const k a b -> Const k a b -> Const k a b #

RealFloat a => RealFloat (Tagged k s a) 

Methods

floatRadix :: Tagged k s a -> Integer #

floatDigits :: Tagged k s a -> Int #

floatRange :: Tagged k s a -> (Int, Int) #

decodeFloat :: Tagged k s a -> (Integer, Int) #

encodeFloat :: Integer -> Int -> Tagged k s a #

exponent :: Tagged k s a -> Int #

significand :: Tagged k s a -> Tagged k s a #

scaleFloat :: Int -> Tagged k s a -> Tagged k s a #

isNaN :: Tagged k s a -> Bool #

isInfinite :: Tagged k s a -> Bool #

isDenormalized :: Tagged k s a -> Bool #

isNegativeZero :: Tagged k s a -> Bool #

isIEEE :: Tagged k s a -> Bool #

atan2 :: Tagged k s a -> Tagged k s a -> Tagged k s a #

Orphan instances