numeric-prelude-0.4.3: An experimental alternative hierarchy of numeric type classes

Safe HaskellNone
LanguageHaskell98

NumericPrelude.Numeric

Synopsis

Documentation

(+), (-) :: C a => a -> a -> a infixl 6 +, - Source #

add and subtract elements

(+), (-) :: C a => a -> a -> a infixl 6 +, - Source #

add and subtract elements

negate :: C a => a -> a Source #

inverse with respect to +

zero :: C a => a Source #

zero element of the vector space

subtract :: C a => a -> a -> a Source #

subtract is (-) with swapped operand order. This is the operand order which will be needed in most cases of partial application.

sum :: C a => [a] -> a Source #

Sum up all elements of a list. An empty list yields zero.

This function is inappropriate for number types like Peano. Maybe we should make sum a method of Additive. This would also make lengthLeft and lengthRight superfluous.

sum1 :: C a => [a] -> a Source #

Sum up all elements of a non-empty list. This avoids including a zero which is useful for types where no universal zero is available. ToDo: Should have NonEmpty type.

isZero :: C a => a -> Bool Source #

(*) :: C a => a -> a -> a infixl 7 Source #

one :: C a => a Source #

(^) :: C a => a -> Integer -> a infixr 8 Source #

The exponent has fixed type Integer in order to avoid an arbitrarily limitted range of exponents, but to reduce the need for the compiler to guess the type (default type). In practice the exponent is most oftenly fixed, and is most oftenly 2. Fixed exponents can be optimized away and thus the expensive computation of Integers doesn't matter. The previous solution used a C constrained type and the exponent was converted to Integer before computation. So the current solution is not less efficient.

A variant of ^ with more flexibility is provided by ringPower.

ringPower :: (C a, C b) => b -> a -> a Source #

A prefix function of '(Algebra.Ring.^)' with a parameter order that fits the needs of partial application and function composition. It has generalised exponent.

See: Argument order of expNat on http://www.haskell.org/pipermail/haskell-cafe/2006-September/018022.html

sqr :: C a => a -> a Source #

product :: C a => [a] -> a Source #

product1 :: C a => [a] -> a Source #

div, mod :: C a => a -> a -> a infixl 7 `div`, `mod` Source #

div, mod :: C a => a -> a -> a infixl 7 `div`, `mod` Source #

divMod :: C a => a -> a -> (a, a) Source #

divides :: (C a, C a) => a -> a -> Bool Source #

even :: (C a, C a) => a -> Bool Source #

odd :: (C a, C a) => a -> Bool Source #

(/) :: C a => a -> a -> a infixl 7 Source #

recip :: C a => a -> a Source #

(^-) :: C a => a -> Integer -> a infixr 8 Source #

fieldPower :: (C a, C b) => b -> a -> a Source #

A prefix function of '(Algebra.Field.^-)'. It has a generalised exponent.

fromRational :: C a => Rational -> a Source #

Needed to work around shortcomings in GHC.

(^/) :: C a => a -> Rational -> a infixr 8 Source #

sqrt :: C a => a -> a Source #

pi :: C a => a Source #

exp, log :: C a => a -> a Source #

exp, log :: C a => a -> a Source #

logBase, (**) :: C a => a -> a -> a infixr 8 Source #

logBase, (**) :: C a => a -> a -> a infixr 8 Source #

(^?) :: C a => a -> a -> a infixr 8 Source #

sin, cos, tan :: C a => a -> a Source #

sin, cos, tan :: C a => a -> a Source #

sin, cos, tan :: C a => a -> a Source #

asin, acos, atan :: C a => a -> a Source #

asin, acos, atan :: C a => a -> a Source #

asin, acos, atan :: C a => a -> a Source #

sinh, cosh, tanh :: C a => a -> a Source #

sinh, cosh, tanh :: C a => a -> a Source #

sinh, cosh, tanh :: C a => a -> a Source #

asinh, acosh, atanh :: C a => a -> a Source #

asinh, acosh, atanh :: C a => a -> a Source #

asinh, acosh, atanh :: C a => a -> a Source #

abs :: C a => a -> a Source #

signum :: C a => a -> a Source #

quot, rem :: C a => a -> a -> a infixl 7 `quot`, `rem` Source #

quot, rem :: C a => a -> a -> a infixl 7 `quot`, `rem` Source #

quotRem :: C a => a -> a -> (a, a) Source #

splitFraction :: (C a, C b) => a -> (b, a) Source #

fraction :: C a => a -> a Source #

truncate :: (C a, C b) => a -> b Source #

round :: (C a, C b) => a -> b Source #

ceiling, floor :: (C a, C b) => a -> b Source #

ceiling, floor :: (C a, C b) => a -> b Source #

approxRational :: (C a, C a) => a -> a -> Rational Source #

TODO: Should be moved to a continued fraction module.

atan2 :: C a => a -> a -> a Source #

toRational :: C a => a -> Rational Source #

Lossless conversion from any representation of a rational to Rational

toInteger :: C a => a -> Integer Source #

fromIntegral :: (C a, C b) => a -> b Source #

isUnit :: C a => a -> Bool Source #

extendedGCD :: C a => a -> a -> (a, (a, a)) Source #

Compute the greatest common divisor and solve a respective Diophantine equation.

  (g,(a,b)) = extendedGCD x y ==>
       g==a*x+b*y   &&  g == gcd x y

TODO: This method is not appropriate for the PID class, because there are rings like the one of the multivariate polynomials, where for all x and y greatest common divisors of x and y exist, but they cannot be represented as a linear combination of x and y. TODO: The definition of extendedGCD does not return the canonical associate.

gcd :: C a => a -> a -> a Source #

The Greatest Common Divisor is defined by:

  gcd x y == gcd y x
  divides z x && divides z y ==> divides z (gcd x y)   (specification)
  divides (gcd x y) x

lcm :: C a => a -> a -> a Source #

Least common multiple

euclid :: (C a, C a) => (a -> a -> a) -> a -> a -> a Source #

extendedEuclid :: (C a, C a) => (a -> a -> (a, a)) -> a -> a -> (a, (a, a)) Source #

(%) :: C a => a -> a -> T a infixl 7 Source #

numerator :: T a -> a Source #

denominator :: T a -> a Source #

data Integer :: * #

Invariant: Jn# and Jp# are used iff value doesn't fit in S#

Useful properties resulting from the invariants:

Instances

Enum Integer

Since: 2.1

Eq Integer 

Methods

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

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

Integral Integer

Since: 2.0.1

Num Integer

Since: 2.1

Ord Integer 
Read Integer

Since: 2.1

Real Integer

Since: 2.0.1

Show Integer

Since: 2.1

Ix Integer

Since: 2.1

Lift Integer 

Methods

lift :: Integer -> Q Exp #

Arbitrary Integer 
CoArbitrary Integer 

Methods

coarbitrary :: Integer -> Gen b -> Gen b #

NFData Integer 

Methods

rnf :: Integer -> () #

Random Integer 

Methods

randomR :: RandomGen g => (Integer, Integer) -> g -> (Integer, g) #

random :: RandomGen g => g -> (Integer, g) #

randomRs :: RandomGen g => (Integer, Integer) -> g -> [Integer] #

randoms :: RandomGen g => g -> [Integer] #

randomRIO :: (Integer, Integer) -> IO Integer #

randomIO :: IO Integer #

C Integer Source # 
C Integer Source # 
C Integer Source # 

Methods

isZero :: Integer -> Bool Source #

C Integer Source # 
C Integer Source # 
C Integer Source # 
C Integer Source # 
C Integer Source # 
C Integer Source # 
C Integer Source # 
C Integer Source # 
C Integer Source # 

Methods

splitFraction :: C b => Integer -> (b, Integer) Source #

fraction :: Integer -> Integer Source #

ceiling :: C b => Integer -> b Source #

floor :: C b => Integer -> b Source #

truncate :: C b => Integer -> b Source #

round :: C b => Integer -> b Source #

C Integer Source # 
C Integer Integer Source # 
C Integer Integer Source # 
C Integer Integer Source # 

Methods

norm :: Integer -> Integer Source #

C Integer Integer Source # 

Methods

norm :: Integer -> Integer Source #

C Integer Integer Source # 

Methods

norm :: Integer -> Integer Source #

Sqr Integer Integer Source # 
C a => C Integer (T a) Source # 

Methods

(*>) :: Integer -> T a -> T a Source #

data Int :: * #

A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]. The exact range for a given implementation can be determined by using minBound and maxBound from the Bounded class.

Instances

Bounded Int

Since: 2.1

Methods

minBound :: Int #

maxBound :: Int #

Enum Int

Since: 2.1

Methods

succ :: Int -> Int #

pred :: Int -> Int #

toEnum :: Int -> Int #

fromEnum :: Int -> Int #

enumFrom :: Int -> [Int] #

enumFromThen :: Int -> Int -> [Int] #

enumFromTo :: Int -> Int -> [Int] #

enumFromThenTo :: Int -> Int -> Int -> [Int] #

Eq Int 

Methods

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

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

Integral Int

Since: 2.0.1

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 #

Num Int

Since: 2.1

Methods

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

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

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

negate :: Int -> Int #

abs :: Int -> Int #

signum :: Int -> Int #

fromInteger :: Integer -> Int #

Ord Int 

Methods

compare :: Int -> Int -> Ordering #

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

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

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

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

max :: Int -> Int -> Int #

min :: Int -> Int -> Int #

Read Int

Since: 2.1

Real Int

Since: 2.0.1

Methods

toRational :: Int -> Rational #

Show Int

Since: 2.1

Methods

showsPrec :: Int -> Int -> ShowS #

show :: Int -> String #

showList :: [Int] -> ShowS #

Ix Int

Since: 2.1

Methods

range :: (Int, Int) -> [Int] #

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

unsafeIndex :: (Int, Int) -> Int -> Int

inRange :: (Int, Int) -> Int -> Bool #

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

unsafeRangeSize :: (Int, Int) -> Int

Lift Int 

Methods

lift :: Int -> Q Exp #

Arbitrary Int 

Methods

arbitrary :: Gen Int #

shrink :: Int -> [Int] #

CoArbitrary Int 

Methods

coarbitrary :: Int -> Gen b -> Gen b #

Storable Int

Since: 2.1

Methods

sizeOf :: Int -> Int #

alignment :: Int -> Int #

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

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

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

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

peek :: Ptr Int -> IO Int #

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

NFData Int 

Methods

rnf :: Int -> () #

Random Int 

Methods

randomR :: RandomGen g => (Int, Int) -> g -> (Int, g) #

random :: RandomGen g => g -> (Int, g) #

randomRs :: RandomGen g => (Int, Int) -> g -> [Int] #

randoms :: RandomGen g => g -> [Int] #

randomRIO :: (Int, Int) -> IO Int #

randomIO :: IO Int #

C Int Source # 

Methods

zero :: Int Source #

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

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

negate :: Int -> Int Source #

C Int Source # 

Methods

isZero :: Int -> Bool Source #

C Int Source # 
C Int Source # 

Methods

div :: Int -> Int -> Int Source #

mod :: Int -> Int -> Int Source #

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

C Int Source # 
C Int Source # 

Methods

extendedGCD :: Int -> Int -> (Int, (Int, Int)) Source #

gcd :: Int -> Int -> Int Source #

lcm :: Int -> Int -> Int Source #

C Int Source # 

Methods

abs :: Int -> Int Source #

signum :: Int -> Int Source #

C Int Source # 
C Int Source # 

Methods

quot :: Int -> Int -> Int Source #

rem :: Int -> Int -> Int Source #

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

C Int Source # 
C Int Source # 

Methods

splitFraction :: C b => Int -> (b, Int) Source #

fraction :: Int -> Int Source #

ceiling :: C b => Int -> b Source #

floor :: C b => Int -> b Source #

truncate :: C b => Int -> b Source #

round :: C b => Int -> b Source #

C Int Int Source # 

Methods

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

C Int Int Source # 

Methods

basis :: Int -> [Int] Source #

flatten :: Int -> [Int] Source #

dimension :: Int -> Int -> Int Source #

C Int Int Source # 

Methods

norm :: Int -> Int Source #

C Int Int Source # 

Methods

norm :: Int -> Int Source #

C Int Int Source # 

Methods

norm :: Int -> Int Source #

Sqr Int Int Source # 

Methods

normSqr :: Int -> Int Source #

Generic1 k (URec k Int) 

Associated Types

type Rep1 (URec k Int) (f :: URec k Int -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (URec k Int) f a #

to1 :: Rep1 (URec k Int) f a -> f a #

Functor (URec * Int) 

Methods

fmap :: (a -> b) -> URec * Int a -> URec * Int b #

(<$) :: a -> URec * Int b -> URec * Int a #

Foldable (URec * Int) 

Methods

fold :: Monoid m => URec * Int m -> m #

foldMap :: Monoid m => (a -> m) -> URec * Int a -> m #

foldr :: (a -> b -> b) -> b -> URec * Int a -> b #

foldr' :: (a -> b -> b) -> b -> URec * Int a -> b #

foldl :: (b -> a -> b) -> b -> URec * Int a -> b #

foldl' :: (b -> a -> b) -> b -> URec * Int a -> b #

foldr1 :: (a -> a -> a) -> URec * Int a -> a #

foldl1 :: (a -> a -> a) -> URec * Int a -> a #

toList :: URec * Int a -> [a] #

null :: URec * Int a -> Bool #

length :: URec * Int a -> Int #

elem :: Eq a => a -> URec * Int a -> Bool #

maximum :: Ord a => URec * Int a -> a #

minimum :: Ord a => URec * Int a -> a #

sum :: Num a => URec * Int a -> a #

product :: Num a => URec * Int a -> a #

Traversable (URec * Int) 

Methods

traverse :: Applicative f => (a -> f b) -> URec * Int a -> f (URec * Int b) #

sequenceA :: Applicative f => URec * Int (f a) -> f (URec * Int a) #

mapM :: Monad m => (a -> m b) -> URec * Int a -> m (URec * Int b) #

sequence :: Monad m => URec * Int (m a) -> m (URec * Int a) #

Eq (URec k Int p) 

Methods

(==) :: URec k Int p -> URec k Int p -> Bool #

(/=) :: URec k Int p -> URec k Int p -> Bool #

Ord (URec k Int p) 

Methods

compare :: URec k Int p -> URec k Int p -> Ordering #

(<) :: URec k Int p -> URec k Int p -> Bool #

(<=) :: URec k Int p -> URec k Int p -> Bool #

(>) :: URec k Int p -> URec k Int p -> Bool #

(>=) :: URec k Int p -> URec k Int p -> Bool #

max :: URec k Int p -> URec k Int p -> URec k Int p #

min :: URec k Int p -> URec k Int p -> URec k Int p #

Show (URec k Int p) 

Methods

showsPrec :: Int -> URec k Int p -> ShowS #

show :: URec k Int p -> String #

showList :: [URec k Int p] -> ShowS #

Generic (URec k Int p) 

Associated Types

type Rep (URec k Int p) :: * -> * #

Methods

from :: URec k Int p -> Rep (URec k Int p) x #

to :: Rep (URec k Int p) x -> URec k Int p #

data URec k Int

Used for marking occurrences of Int#

Since: 4.9.0.0

data URec k Int = UInt {}
type Rep1 k (URec k Int) 
type Rep1 k (URec k Int) = D1 k (MetaData "URec" "GHC.Generics" "base" False) (C1 k (MetaCons "UInt" PrefixI True) (S1 k (MetaSel (Just Symbol "uInt#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UInt k)))
type Rep (URec k Int p) 
type Rep (URec k Int p) = D1 * (MetaData "URec" "GHC.Generics" "base" False) (C1 * (MetaCons "UInt" PrefixI True) (S1 * (MetaSel (Just Symbol "uInt#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UInt *)))

data Float :: * #

Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.

Instances

Eq Float 

Methods

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

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

Floating Float

Since: 2.1

Ord Float 

Methods

compare :: Float -> Float -> Ordering #

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

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

(>) :: Float -> Float -> Bool #

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

max :: Float -> Float -> Float #

min :: Float -> Float -> Float #

Read Float

Since: 2.1

RealFloat Float

Since: 2.1

Lift Float 

Methods

lift :: Float -> Q Exp #

Arbitrary Float 

Methods

arbitrary :: Gen Float #

shrink :: Float -> [Float] #

CoArbitrary Float 

Methods

coarbitrary :: Float -> Gen b -> Gen b #

Storable Float

Since: 2.1

Methods

sizeOf :: Float -> Int #

alignment :: Float -> Int #

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

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

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

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

peek :: Ptr Float -> IO Float #

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

NFData Float 

Methods

rnf :: Float -> () #

Random Float 

Methods

randomR :: RandomGen g => (Float, Float) -> g -> (Float, g) #

random :: RandomGen g => g -> (Float, g) #

randomRs :: RandomGen g => (Float, Float) -> g -> [Float] #

randoms :: RandomGen g => g -> [Float] #

randomRIO :: (Float, Float) -> IO Float #

randomIO :: IO Float #

C Float Source # 
C Float Source # 

Methods

isZero :: Float -> Bool Source #

C Float Source # 
C Float Source # 
C Float Source # 
C Float Source # 
C Float Source # 
C Float Source # 
C Float Source # 

Methods

splitFraction :: C b => Float -> (b, Float) Source #

fraction :: Float -> Float Source #

ceiling :: C b => Float -> b Source #

floor :: C b => Float -> b Source #

truncate :: C b => Float -> b Source #

round :: C b => Float -> b Source #

C Float Source # 
C Float Source # 

Methods

atan2 :: Float -> Float -> Float Source #

C Float Source # 
Power Float Source # 

Methods

power :: Rational -> T Float -> T Float Source #

C Float Float Source # 

Methods

(*>) :: Float -> Float -> Float Source #

C Float Float Source # 
C Float Float Source # 
C Float Float Source # 
C Float Float Source # 

Methods

norm :: Float -> Float Source #

C Float Float Source # 

Methods

norm :: Float -> Float Source #

C Float Float Source # 

Methods

norm :: Float -> Float Source #

Sqr Float Float Source # 

Methods

normSqr :: Float -> Float Source #

Generic1 k (URec k Float) 

Associated Types

type Rep1 (URec k Float) (f :: URec k Float -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (URec k Float) f a #

to1 :: Rep1 (URec k Float) f a -> f a #

Functor (URec * Float) 

Methods

fmap :: (a -> b) -> URec * Float a -> URec * Float b #

(<$) :: a -> URec * Float b -> URec * Float a #

Foldable (URec * Float) 

Methods

fold :: Monoid m => URec * Float m -> m #

foldMap :: Monoid m => (a -> m) -> URec * Float a -> m #

foldr :: (a -> b -> b) -> b -> URec * Float a -> b #

foldr' :: (a -> b -> b) -> b -> URec * Float a -> b #

foldl :: (b -> a -> b) -> b -> URec * Float a -> b #

foldl' :: (b -> a -> b) -> b -> URec * Float a -> b #

foldr1 :: (a -> a -> a) -> URec * Float a -> a #

foldl1 :: (a -> a -> a) -> URec * Float a -> a #

toList :: URec * Float a -> [a] #

null :: URec * Float a -> Bool #

length :: URec * Float a -> Int #

elem :: Eq a => a -> URec * Float a -> Bool #

maximum :: Ord a => URec * Float a -> a #

minimum :: Ord a => URec * Float a -> a #

sum :: Num a => URec * Float a -> a #

product :: Num a => URec * Float a -> a #

Traversable (URec * Float) 

Methods

traverse :: Applicative f => (a -> f b) -> URec * Float a -> f (URec * Float b) #

sequenceA :: Applicative f => URec * Float (f a) -> f (URec * Float a) #

mapM :: Monad m => (a -> m b) -> URec * Float a -> m (URec * Float b) #

sequence :: Monad m => URec * Float (m a) -> m (URec * Float a) #

Eq (URec k Float p) 

Methods

(==) :: URec k Float p -> URec k Float p -> Bool #

(/=) :: URec k Float p -> URec k Float p -> Bool #

Ord (URec k Float p) 

Methods

compare :: URec k Float p -> URec k Float p -> Ordering #

(<) :: URec k Float p -> URec k Float p -> Bool #

(<=) :: URec k Float p -> URec k Float p -> Bool #

(>) :: URec k Float p -> URec k Float p -> Bool #

(>=) :: URec k Float p -> URec k Float p -> Bool #

max :: URec k Float p -> URec k Float p -> URec k Float p #

min :: URec k Float p -> URec k Float p -> URec k Float p #

Show (URec k Float p) 

Methods

showsPrec :: Int -> URec k Float p -> ShowS #

show :: URec k Float p -> String #

showList :: [URec k Float p] -> ShowS #

Generic (URec k Float p) 

Associated Types

type Rep (URec k Float p) :: * -> * #

Methods

from :: URec k Float p -> Rep (URec k Float p) x #

to :: Rep (URec k Float p) x -> URec k Float p #

data URec k Float

Used for marking occurrences of Float#

Since: 4.9.0.0

type Rep1 k (URec k Float) 
type Rep1 k (URec k Float) = D1 k (MetaData "URec" "GHC.Generics" "base" False) (C1 k (MetaCons "UFloat" PrefixI True) (S1 k (MetaSel (Just Symbol "uFloat#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UFloat k)))
type Rep (URec k Float p) 
type Rep (URec k Float p) = D1 * (MetaData "URec" "GHC.Generics" "base" False) (C1 * (MetaCons "UFloat" PrefixI True) (S1 * (MetaSel (Just Symbol "uFloat#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UFloat *)))

data Double :: * #

Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.

Instances

Eq Double 

Methods

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

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

Floating Double

Since: 2.1

Ord Double 
Read Double

Since: 2.1

RealFloat Double

Since: 2.1

Lift Double 

Methods

lift :: Double -> Q Exp #

Arbitrary Double 
CoArbitrary Double 

Methods

coarbitrary :: Double -> Gen b -> Gen b #

Storable Double

Since: 2.1

NFData Double 

Methods

rnf :: Double -> () #

Random Double 

Methods

randomR :: RandomGen g => (Double, Double) -> g -> (Double, g) #

random :: RandomGen g => g -> (Double, g) #

randomRs :: RandomGen g => (Double, Double) -> g -> [Double] #

randoms :: RandomGen g => g -> [Double] #

randomRIO :: (Double, Double) -> IO Double #

randomIO :: IO Double #

C Double Source # 
C Double Source # 

Methods

isZero :: Double -> Bool Source #

C Double Source # 
C Double Source # 
C Double Source # 
C Double Source # 
C Double Source # 
C Double Source # 
C Double Source # 

Methods

splitFraction :: C b => Double -> (b, Double) Source #

fraction :: Double -> Double Source #

ceiling :: C b => Double -> b Source #

floor :: C b => Double -> b Source #

truncate :: C b => Double -> b Source #

round :: C b => Double -> b Source #

C Double Source # 
C Double Source # 

Methods

atan2 :: Double -> Double -> Double Source #

C Double Source # 
Power Double Source # 

Methods

power :: Rational -> T Double -> T Double Source #

C Double Double Source # 

Methods

(*>) :: Double -> Double -> Double Source #

C Double Double Source # 
C Double Double Source # 
C Double Double Source # 
C Double Double Source # 

Methods

norm :: Double -> Double Source #

C Double Double Source # 

Methods

norm :: Double -> Double Source #

C Double Double Source # 

Methods

norm :: Double -> Double Source #

Sqr Double Double Source # 
Generic1 k (URec k Double) 

Associated Types

type Rep1 (URec k Double) (f :: URec k Double -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (URec k Double) f a #

to1 :: Rep1 (URec k Double) f a -> f a #

Functor (URec * Double) 

Methods

fmap :: (a -> b) -> URec * Double a -> URec * Double b #

(<$) :: a -> URec * Double b -> URec * Double a #

Foldable (URec * Double) 

Methods

fold :: Monoid m => URec * Double m -> m #

foldMap :: Monoid m => (a -> m) -> URec * Double a -> m #

foldr :: (a -> b -> b) -> b -> URec * Double a -> b #

foldr' :: (a -> b -> b) -> b -> URec * Double a -> b #

foldl :: (b -> a -> b) -> b -> URec * Double a -> b #

foldl' :: (b -> a -> b) -> b -> URec * Double a -> b #

foldr1 :: (a -> a -> a) -> URec * Double a -> a #

foldl1 :: (a -> a -> a) -> URec * Double a -> a #

toList :: URec * Double a -> [a] #

null :: URec * Double a -> Bool #

length :: URec * Double a -> Int #

elem :: Eq a => a -> URec * Double a -> Bool #

maximum :: Ord a => URec * Double a -> a #

minimum :: Ord a => URec * Double a -> a #

sum :: Num a => URec * Double a -> a #

product :: Num a => URec * Double a -> a #

Traversable (URec * Double) 

Methods

traverse :: Applicative f => (a -> f b) -> URec * Double a -> f (URec * Double b) #

sequenceA :: Applicative f => URec * Double (f a) -> f (URec * Double a) #

mapM :: Monad m => (a -> m b) -> URec * Double a -> m (URec * Double b) #

sequence :: Monad m => URec * Double (m a) -> m (URec * Double a) #

Eq (URec k Double p) 

Methods

(==) :: URec k Double p -> URec k Double p -> Bool #

(/=) :: URec k Double p -> URec k Double p -> Bool #

Ord (URec k Double p) 

Methods

compare :: URec k Double p -> URec k Double p -> Ordering #

(<) :: URec k Double p -> URec k Double p -> Bool #

(<=) :: URec k Double p -> URec k Double p -> Bool #

(>) :: URec k Double p -> URec k Double p -> Bool #

(>=) :: URec k Double p -> URec k Double p -> Bool #

max :: URec k Double p -> URec k Double p -> URec k Double p #

min :: URec k Double p -> URec k Double p -> URec k Double p #

Show (URec k Double p) 

Methods

showsPrec :: Int -> URec k Double p -> ShowS #

show :: URec k Double p -> String #

showList :: [URec k Double p] -> ShowS #

Generic (URec k Double p) 

Associated Types

type Rep (URec k Double p) :: * -> * #

Methods

from :: URec k Double p -> Rep (URec k Double p) x #

to :: Rep (URec k Double p) x -> URec k Double p #

data URec k Double

Used for marking occurrences of Double#

Since: 4.9.0.0

type Rep1 k (URec k Double) 
type Rep1 k (URec k Double) = D1 k (MetaData "URec" "GHC.Generics" "base" False) (C1 k (MetaCons "UDouble" PrefixI True) (S1 k (MetaSel (Just Symbol "uDouble#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UDouble k)))
type Rep (URec k Double p) 
type Rep (URec k Double p) = D1 * (MetaData "URec" "GHC.Generics" "base" False) (C1 * (MetaCons "UDouble" PrefixI True) (S1 * (MetaSel (Just Symbol "uDouble#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UDouble *)))

(*>) :: C a v => a -> v -> v infixr 7 Source #

scale a vector by a scalar