specialfunctions_activations

Special functions - Neural Networks activations and their gradients

Gaussian - Gaussian function

Status

Experimental

Description

Computes the gaussian function:

Syntax

result = gaussian (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Example

program example_gaussian
    use stdlib_kinds, only: sp
    use stdlib_math, only: linspace
    use stdlib_specialfunctions, only: gaussian
    implicit none
    integer, parameter :: n = 10
    real(sp) :: x(n), y(n)

    x = linspace(-2._sp, 2._sp, n)
    y = gaussian( x )
    print *, y
end program example_gaussian

Gaussian_grad - Gradient of the Gaussian function

Status

Experimental

Description

Computes the gradient of the gaussian function:

Syntax

result = gaussian_grad (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Elu - Exponential Linear Unit function

Status

Experimental

Description

Computes the gaussian function:

Syntax

result = elu (x,a)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind. a: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Example

program example_elu
    use stdlib_kinds, only: sp
    use stdlib_math, only: linspace
    use stdlib_specialfunctions, only: elu
    implicit none
    integer, parameter :: n = 10
    real(sp) :: x(n), y(n)

    x = linspace(-2._sp, 2._sp, n)
    y = elu( x , 1.0 )
    print *, y
end program example_elu

Elu_grad - Gradient of the Exponential Linear Unit function

Status

Experimental

Description

Computes the gradient of the gaussian function:

Syntax

result = elu_grad (x,a)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind. a: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Relu - Rectified Linear Unit function

Status

Experimental

Description

Computes the Rectified Linear Unit function:

Syntax

result = relu (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Example

program example_relu
    use stdlib_kinds, only: sp
    use stdlib_math, only: linspace
    use stdlib_specialfunctions, only: relu
    implicit none
    integer, parameter :: n = 10
    real(sp) :: x(n), y(n)

    x = linspace(-2._sp, 2._sp, n)
    y = relu( x )
    print *, y
end program example_relu

Relu_grad - Gradient of the Rectified Linear Unit function

Status

Experimental

Description

Computes the gradient of the gaussian function:

Syntax

result = relu_grad (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

leaky_relu - leaky Rectified Linear Unit function

Status

Experimental

Description

Computes the gaussian function:

Syntax

result = leaky_relu (x,a)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind. a: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Example

program example_gelu
    use stdlib_kinds, only: sp
    use stdlib_math, only: linspace
    use stdlib_specialfunctions, only: leaky_relu
    implicit none
    integer, parameter :: n = 10
    real(sp) :: x(n), y(n)

    x = linspace(-2._sp, 2._sp, n)
    y = leaky_relu( x , 0.1_sp )
    print *, y
end program example_gelu

leaky_relu_grad - Gradient of the leaky Rectified Linear Unit function

Status

Experimental

Description

Computes the gradient of the leaky_relu function:

Syntax

result = leaky_relu_grad (x,a)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind. a: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as the input argument.

Gelu - Gaussian Error Linear Unit function

Status

Experimental

Description

Computes the Gaussian Error Linear Unit function:

Syntax

result = gelu (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Example

program example_gelu
    use stdlib_kinds, only: sp
    use stdlib_math, only: linspace
    use stdlib_specialfunctions, only: gelu
    implicit none
    integer, parameter :: n = 10
    real(sp) :: x(n), y(n)

    x = linspace(-2._sp, 2._sp, n)
    y = gelu( x )
    print *, y
end program example_gelu

Gelu_grad - Gradient of the Gaussian Error Linear Unit function

Status

Experimental

Description

Computes the gradient of the gaussian error linear unit function:

Syntax

result = gelu_grad (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Gelu_approx - Approximation of the Gaussian Error Linear Unit function

Status

Experimental

Description

Computes a fast approximation of the Gaussian Error Linear Unit function using a fast $\text{erf}$ approximation:

Syntax

result = gelu_approx (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Gelu_approx_grad - Gradient of the Approximated Gaussian Error Linear Unit function

Status

Experimental

Description

Computes the gradient of the gaussian error linear unit function using a fast $\text{erf}$ approximation:

Syntax

result = gelu_approx_grad (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Selu - Scaled Exponential Linear Unit function

Status

Experimental

Description

Applies the Scaled Exponential Linear Unit activation function: Where, and

Syntax

result = selu (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Example

program example_selu
    use stdlib_kinds, only: sp
    use stdlib_math, only: linspace
    use stdlib_specialfunctions, only: selu
    implicit none
    integer, parameter :: n = 10
    real(sp) :: x(n), y(n)

    x = linspace(-2._sp, 2._sp, n)
    y = selu( x )
    print *, y
end program example_selu

selu_grad - Gradient of the Scaled Exponential Linear Unit function

Status

Experimental

Description

Applies the gradient of the Scaled Exponential Linear Unit activation function:

Syntax

result = selu_grad (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Sigmoid - Sigmoid function

Status

Experimental

Description

Computes the sigmoid function:

Syntax

result = sigmoid (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Sigmoid_grad - Gradient of the Sigmoid function

Status

Experimental

Description

Computes the gradient of the Sigmoid function:

Syntax

result = sigmoid_grad (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

SiLU - Sigmoid Linear Unit function

Status

Experimental

Description

Computes the Sigmoid Linear Unit function:

Syntax

result = silu (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Example

program example_silu
    use stdlib_kinds, only: sp
    use stdlib_math, only: linspace
    use stdlib_specialfunctions, only: silu
    implicit none
    integer, parameter :: n = 10
    real(sp) :: x(n), y(n)

    x = linspace(-2._sp, 2._sp, n)
    y = silu( x )
    print *, y
end program example_silu

Silu_grad - Gradient of the Sigmoid Linear Unit function

Status

Experimental

Description

Computes the gradient of the Sigmoid function:

Syntax

result = silu_grad (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Step - Step function

Status

Experimental

Description

Computes the step function:

Syntax

result = step (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Example

program example_step
    use stdlib_kinds, only: sp
    use stdlib_math, only: linspace
    use stdlib_specialfunctions, only: step
    implicit none
    integer, parameter :: n = 10
    real(sp) :: x(n), y(n)

    x = linspace(-2._sp, 2._sp, n)
    y = step( x )
    print *, y
end program example_step

step_grad - Gradient of the Step function

Status

Experimental

Description

Computes the gradient of the Sigmoid function:

Syntax

result = step_grad (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

softmax - softmax function

Status

Experimental

Description

Computes the softmax function:

Syntax

result = softmax (x,dim)

Class

Pure function for ranks 1 to 4.

Arguments

x: Shall be an array of rank 1 to 4 of any real kind. dim: integer scalar indicating upon which dimension to apply the normalization.

Return value

The function returns an array with the same rank and kind as the input argument x.

Example

program example_softmax
    use stdlib_kinds, only: sp
    use stdlib_math, only: linspace
    use stdlib_specialfunctions, only: softmax
    implicit none
    integer, parameter :: n = 10
    real(sp) :: x(n), y(n)

    x = linspace(-2._sp, 2._sp, n)
    y = softmax( x )
    print *, y
end program example_softmax

softmax_grad - Gradient of the softmax function

Status

Experimental

Description

Computes the gradient of the softmax function:

Syntax

result = softmax_grad (x,dim)

Class

Pure function for ranks 1 to 4.

Arguments

x: Shall be an array of rank 1 to 4 of any real kind. dim: integer scalar indicating upon which dimension to apply the normalization.

Return value

The function returns a value with the same type and kind as input argument.

softplus - softplus function

Status

Experimental

Description

Computes the softplus function:

Syntax

result = softplus (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Example

program example_softplus
    use stdlib_kinds, only: sp
    use stdlib_math, only: linspace
    use stdlib_specialfunctions, only: softplus
    implicit none
    integer, parameter :: n = 10
    real(sp) :: x(n), y(n)

    x = linspace(-2._sp, 2._sp, n)
    y = softplus( x )
    print *, y
end program example_softplus

softplus_grad - Gradient of the softplus function

Status

Experimental

Description

Computes the gradient of the softplus function:

Syntax

result = softplus_grad (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Fast tanh - Approximation of the hyperbolic tangent function

Status

Experimental

Description

Computes an approximated but faster solution to:

Syntax

result = fast_tanh (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

fast_tanh_grad - Gradient of the approximation of the hyperbolic tangent function

Status

Experimental

Description

Computes the gradient of the fast_tanh function:

Syntax

result = fast_tanh_grad (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.

Fast erf - Approximation of the error function

Status

Experimental

Description

Computes an approximated but faster solution to:

Syntax

result = fast_erf (x)

Class

Elemental function

Arguments

x: Shall be a scalar or array of any real kind.

Return value

The function returns a value with the same type and kind as input argument.