path_operator.f90 Source File


Files dependent on this one

sourcefile~~path_operator.f90~~AfferentGraph sourcefile~path_operator.f90 path_operator.f90 sourcefile~dropletmotionsimulation.f90 dropletMotionSimulation.f90 sourcefile~dropletmotionsimulation.f90->sourcefile~path_operator.f90 sourcefile~flow_field.f90 flow_field.f90 sourcefile~dropletmotionsimulation.f90->sourcefile~flow_field.f90 sourcefile~unstructuredgrid.f90 unstructuredGrid.f90 sourcefile~dropletmotionsimulation.f90->sourcefile~unstructuredgrid.f90 sourcefile~flow_field.f90->sourcefile~path_operator.f90 sourcefile~flow_field.f90->sourcefile~unstructuredgrid.f90 sourcefile~kdtree_test.f90 kdTree_test.f90 sourcefile~kdtree_test.f90->sourcefile~path_operator.f90 sourcefile~kdtree_test.f90->sourcefile~unstructuredgrid.f90 sourcefile~unstructuredgrid.f90->sourcefile~path_operator.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~main.f90 MAIN.f90 sourcefile~main.f90->sourcefile~dropletmotionsimulation.f90

Contents

Source Code


Source Code

module path_operator_m
    implicit none

    character(7), parameter, private :: OS = 'Linux'

    contains

    subroutine make_directory(path)
        character(*), intent(in) :: path
        character(:), allocatable :: directory
    
        select case(trim(OS))
            case ('Linux')  !for_Linux
                directory =  replace_str(path, from='\', to='/' )
                call system('mkdir -p -v '//directory)

            case ('Windows')  !for_Windows
                directory =  replace_str(path, from='/', to='\' )
                call system('md '//directory)

            case default
                print*, 'OS ERROR : ', OS
                error stop
                
        end select

    end subroutine make_directory
    
    subroutine get_DirFromPath(path, directory, filename)
        character(*), intent(in) :: path
        character(:), intent(out), allocatable :: directory
        character(:), intent(out), allocatable , optional :: filename
        character(1) delimiter
        integer i

        if(index(path, '/') > 0) then
            delimiter = '/'

        else if(index(path, '\') > 0) then
            delimiter = '\'

        else
            print*, 'Delimiter was not found.'
            if(present(filename)) filename = path
            directory = ''
            return

        end if

        i = index(path, delimiter, back=.true.)

        if(present(filename)) filename = trim(path(i+1:))
        directory = path(:i)

        print*, 'Path= ', trim(path)
        print*, 'Directory= ', directory
        if(present(filename)) print*, 'Filename= ', filename

    end subroutine

    function replace_str( str, from, to )
        character (*),intent (in) :: str
        character (1),intent (in) :: from, to
        character (len_trim(str)) :: replace_str
        integer :: i, l

        replace_str = str
        l = len_trim(str)
        do i = 1, l
            if ( str(i:i) == from ) replace_str(i:i) = to
        end do

    end function

end module path_operator_m