array.f90 Source File


Files dependent on this one

sourcefile~~array.f90~~AfferentGraph sourcefile~array.f90 array.f90 sourcefile~cube2usg.f90 CUBE2USG.f90 sourcefile~cube2usg.f90->sourcefile~array.f90 sourcefile~dropletgenerator.f90 dropletGenerator.f90 sourcefile~dropletgenerator.f90->sourcefile~array.f90 sourcefile~sort_test.f90 sort_test.f90 sourcefile~sort_test.f90->sourcefile~array.f90 sourcefile~unstructuredgrid.f90 unstructuredGrid.f90 sourcefile~unstructuredgrid.f90->sourcefile~array.f90 sourcefile~boxflowfield.f90 boxFlowField.f90 sourcefile~boxflowfield.f90->sourcefile~unstructuredgrid.f90 sourcefile~cellcentercalc_test.f90 cellCenterCalc_test.f90 sourcefile~cellcentercalc_test.f90->sourcefile~unstructuredgrid.f90 sourcefile~dropletmotionsimulation.f90 dropletMotionSimulation.f90 sourcefile~dropletmotionsimulation.f90->sourcefile~dropletgenerator.f90 sourcefile~dropletmotionsimulation.f90->sourcefile~unstructuredgrid.f90 sourcefile~flow_field.f90 flow_field.f90 sourcefile~dropletmotionsimulation.f90->sourcefile~flow_field.f90 sourcefile~flow_field.f90->sourcefile~unstructuredgrid.f90 sourcefile~kdtree_test.f90 kdTree_test.f90 sourcefile~kdtree_test.f90->sourcefile~unstructuredgrid.f90 sourcefile~main.f90 MAIN.f90 sourcefile~main.f90->sourcefile~dropletmotionsimulation.f90

Contents

Source Code


Source Code

module array_m
    implicit none

    contains

    subroutine output_2dArray_asBinary(fname, array)
        character(*), intent(in)  :: fname
        real, intent(in) :: array(:,:)
        integer n_unit

        print*, 'output_bin2dArray : ', fname

        open(newunit=n_unit, file=fname, form='unformatted', status='replace')

            write(n_unit) shape(array)

            write(n_unit) array

        close(n_unit)

    end subroutine

    subroutine read_2dArray_asBinary(fname, array)
        character(*), intent(in)  :: fname
        real, allocatable, intent(out) :: array(:,:)
        integer n_unit, arrayShape(2)

        print*, 'read_bin2dArray : ', fname

        open(newunit=n_unit, file=fname, form='unformatted', status='old', action='read')

            read(n_unit) arrayShape(:)

            allocate(array(arrayShape(1), arrayShape(2)))

            read(n_unit) array

        close(n_unit)

    end subroutine

    subroutine read_1dArray_real(fname, array)
        character(*), intent(in)  :: fname
        real, allocatable, intent(out) :: array(:)
        integer n_unit, size

        print*, 'read_1darray : ', fname

        open(newunit=n_unit, file=fname, status='old', action='read')

            read(n_unit, *) size

            allocate(array(size))

            read(n_unit, *) array

        close(n_unit)

    end subroutine

    function mean_2dArray(array) result(mean)
        real, intent(in) :: array(:,:)
        real mean(size(array, dim=2))
        integer i

        do i = 1, size(array, dim=1)
            mean(i) = sum(array(i, :)) / size(array, dim=2)
        end do

    end function

    function FisherYates_shuffle(a) result(b)
        !!フィッシャー・イェーツのシャッフル
        !!参考:https://programming-place.net/ppp/contents/algorithm/other/002.html
        real, intent(in) :: a(:)
        real b(size(a)), rand, tmp
        integer i, index

        b = a

        do i = size(b), 2, -1
            call random_number(rand)
            index = int(rand * (i-1)) + 1
            ! print *, index, i

            !SWAP
            tmp = b(index)
            b(index) = b(i)
            b(i) = tmp

        end do

    end function

end module array_m