array_generation_m.f90 Source File


Source Code

module array_generation_m
    !! Contains functions which create arrays

    use precision_m, only : FP

    public :: linspace

contains

    function linspace(left, right, npoints, endpoint, stagger) result(points)
        !! Returns an array of evenly spaced points over an interval from
        !! left to right. The endpoints on both sides can optionally be
        !! included. Optionally staggering can be used which effectively shifts
        !! all points by half the grid spacing to the right, creating a
        !! staggered grid. In that case the rightmost point will exceed the
        !! right boundary specified.
        real(kind=FP), intent(in) :: left
        !! Starting point (from)
        real(kind=FP), intent(in) :: right
        !! Ending point (to)
        integer, intent(in) :: npoints
        !! Number of points. Should be >1, for =1 the left point is returned.
        logical, optional, intent(in) :: endpoint
        !! If true, the endpoint is included in the points (default = false)
        logical, optional, intent(in) :: stagger
        !! If true, points are staggered (default = false)

        real(kind=FP), dimension(npoints) :: points
        !! Array of points generated (output)

        logical :: endpoint_local, stagger_local
        ! Local variables for optionals
        integer :: i
        ! Loop index
        real(kind=FP) :: delta
        ! Spacing

        if (present(endpoint)) then
            endpoint_local = endpoint
        else
            endpoint_local = .false.
        endif
        if (present(stagger)) then
            stagger_local = stagger
        else
            stagger_local = .false.
        endif

        ! If only 1 point is specified, return the left one
        if (npoints == 1) then
            points = left
            return
        endif

        ! Calculate the spacing based on if the endpoint should be included
        ! or not
        if (endpoint_local .eqv. .false.) then
            delta = (right - left) / npoints
        else
            delta = (right - left) / (npoints - 1.0_FP)
        endif

        ! Create the points. Start from the left and add the spacing i times.
        ! If staggering is wished we shift the index by 1/2.
        do i = 1, npoints
            if (stagger_local .eqv. .false.) then
                points(i) = left + (i - 1.0_FP) * delta
            else
                points(i) = left + (i - 0.5_FP) * delta
            endif
        enddo

    end function

end module