goal-core-0.20: Common, non-geometric tools for use with Goal
Safe HaskellNone
LanguageHaskell2010

Goal.Core.Util

Description

A collection of generic numerical and list manipulation functions.

Synopsis

List Manipulation

takeEvery :: Int -> [x] -> [x] Source #

Takes every nth element, starting with the head of the list.

breakEvery :: Int -> [x] -> [[x]] Source #

Break the list up into lists of length n.

kFold :: Int -> [x] -> [([x], [x])] Source #

Returns k (training,validation) pairs. k should be greater than or equal to 2.

kFold' :: Int -> [x] -> [([x], [x], [x])] Source #

Returns k (training,test,validation) pairs for early stopping algorithms. k should be greater than or equal to 3.

Numeric

roundSD :: RealFloat x => Int -> x -> x Source #

Rounds the number to the specified significant digit.

toPi :: RealFloat x => x -> x Source #

Value of a point on a circle, minus rotations.

circularDistance :: RealFloat x => x -> x -> x Source #

Distance between two points on a circle, removing rotations.

integrate Source #

Arguments

:: Double

Error Tolerance

-> (Double -> Double)

Function

-> Double

Interval beginning

-> Double

Interval end

-> (Double, Double)

Integral

Numerically integrates a 1-d function over an interval.

logistic :: Floating x => x -> x Source #

A standard sigmoid function.

logit :: Floating x => x -> x Source #

The inverse of the logistic.

square :: Floating x => x -> x Source #

The square of a number (for avoiding endless default values).

triangularNumber :: Int -> Int Source #

Triangular number.

List Numerics

average :: (Foldable f, Fractional x) => f x -> x Source #

Average value of a Traversable of Fractionals.

weightedAverage :: (Foldable f, Fractional x) => f (x, x) -> x Source #

Weighted Average given a Traversable of (weight,value) pairs.

circularAverage :: (Traversable f, RealFloat x) => f x -> x Source #

Circular average value of a Traversable of radians.

weightedCircularAverage :: (Traversable f, RealFloat x) => f (x, x) -> x Source #

Weighted Circular average value of a Traversable of radians.

range :: RealFloat x => x -> x -> Int -> [x] Source #

Returns n numbers which uniformly partitions the interval [mn,mx].

discretizeFunction :: Double -> Double -> Int -> (Double -> Double) -> [(Double, Double)] Source #

Takes range information in the form of a minimum, maximum, and sample count, a function to sample, and returns a list of pairs (x,f(x)) over the specified range.

logSumExp :: (Ord x, Floating x, Traversable f) => f x -> x Source #

Given a set of values, computes the "soft maximum" by way of taking the exponential of every value, summing the results, and then taking the logarithm. Incorporates some tricks to improve numerical stability.

logIntegralExp Source #

Arguments

:: Traversable f 
=> Double

Error Tolerance

-> (Double -> Double)

Function

-> Double

Interval beginning

-> Double

Interval end

-> f Double

Samples (for approximating the max)

-> Double

Log-Integral-Exp

Given a function, computes the "soft maximum" of the function by computing the integral of the exponential of the function, and taking the logarithm of the result. The maximum is first approximated on a given set of samples to improve numerical stability. Pro tip: If you want to compute the normalizer of a an exponential family probability density, provide the unnormalized log-density to this function.

Tracing

traceGiven :: Show a => a -> a Source #

Runs traceShow on the given element.

TypeNats

finiteInt :: KnownNat n => Finite n -> Int Source #

getFinite and fromIntegral.

natValInt :: KnownNat n => Proxy n -> Int Source #

'natVal and fromIntegral.

type Triangular n = Div (n * (n + 1)) 2 Source #

Type-level triangular number.

Type Rationals

data Rat (n :: Nat) (d :: Nat) Source #

Type level rational numbers. This implementation does not currently permit negative numbers.

type (/) n d = Rat n d Source #

Infix Rat.

ratVal :: (KnownNat n, KnownNat d) => Proxy (n / d) -> Rational Source #

Recover a rational value from a Proxy.