Changeset 20 for trunk/src/readpaths.f90


Ignore:
Timestamp:
Dec 23, 2013, 6:23:38 PM (10 years ago)
Author:
igpis
Message:

move version 9.1.8 form branches to trunk. Contributions from HSO, saeck, pesei, NIK, RT, XKF, IP and others

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/readpaths.f90

    r4 r20  
    2020!**********************************************************************
    2121
    22 subroutine readpaths
     22subroutine readpaths !(pathfile)
    2323
    2424  !*****************************************************************************
     
    3030  !                                                                            *
    3131  !     1 February 1994                                                        *
     32  !     last modified                                                          *
     33  !     HS, 7.9.2012                                                           *
     34  !     option to give pathnames file as command line option                   *
    3235  !                                                                            *
    3336  !*****************************************************************************
     
    4750  implicit none
    4851
    49   integer :: i
     52  integer   :: i
     53  character(256) :: string_test
     54  character(1) :: character_test
    5055
    5156  ! Read the pathname information stored in unitpath
    5257  !*************************************************
    5358
    54 
    55   open(unitpath,file='pathnames',status='old',err=999)
     59  open(unitpath,file=trim(pathfile),status='old',err=999)
    5660
    5761  do i=1,numpath
    5862    read(unitpath,'(a)',err=998) path(i)
    5963    length(i)=index(path(i),' ')-1
     64
     65   
     66    string_test = path(i)
     67    character_test = string_test(length(i):length(i))
     68    !print*, 'character_test,  string_test ', character_test,  string_test
     69      if ((character_test .NE. '/') .AND. (i .LT. 4))  then
     70         print*, 'WARNING: path not ending in /'
     71         print*, path(i)
     72         path(i) = string_test(1:length(i)) // '/'
     73         length(i)=length(i)+1
     74         print*, 'fix: padded with /'
     75         print*, path(i)
     76         print*, 'length(i) increased 1'
     77      endif
    6078  end do
    6179
     
    7088    length(numpath+2*(i-1)+2)=index(path(numpath+2*(i-1)+2),' ')-1
    7189  end do
     90  print*,length(5),length(6)
    7291
    7392
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG