source: trunk/src/readpaths.f90 @ 25

Last change on this file since 25 was 20, checked in by igpis, 10 years ago

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

  • Property svn:executable set to *
File size: 5.0 KB
Line 
1!**********************************************************************
2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
3! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
4! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
5!                                                                     *
6! This file is part of FLEXPART.                                      *
7!                                                                     *
8! FLEXPART is free software: you can redistribute it and/or modify    *
9! it under the terms of the GNU General Public License as published by*
10! the Free Software Foundation, either version 3 of the License, or   *
11! (at your option) any later version.                                 *
12!                                                                     *
13! FLEXPART is distributed in the hope that it will be useful,         *
14! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
15! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
16! GNU General Public License for more details.                        *
17!                                                                     *
18! You should have received a copy of the GNU General Public License   *
19! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
20!**********************************************************************
21
22subroutine readpaths !(pathfile)
23
24  !*****************************************************************************
25  !                                                                            *
26  !     Reads the pathnames, where input/output files are expected to be.      *
27  !     The file pathnames must be available in the current working directory. *
28  !                                                                            *
29  !     Author: A. Stohl                                                       *
30  !                                                                            *
31  !     1 February 1994                                                        *
32  !     last modified                                                          *
33  !     HS, 7.9.2012                                                           *
34  !     option to give pathnames file as command line option                   *
35  !                                                                            *
36  !*****************************************************************************
37  !                                                                            *
38  ! Variables:                                                                 *
39  ! length(numpath)    lengths of the path names                               *
40  ! path(numpath)      pathnames of input/output files                         *
41  !                                                                            *
42  ! Constants:                                                                 *
43  ! numpath            number of pathnames to be read in                       *
44  !                                                                            *
45  !*****************************************************************************
46
47  use par_mod
48  use com_mod
49
50  implicit none
51
52  integer   :: i
53  character(256) :: string_test
54  character(1) :: character_test
55
56  ! Read the pathname information stored in unitpath
57  !*************************************************
58
59  open(unitpath,file=trim(pathfile),status='old',err=999)
60
61  do i=1,numpath
62    read(unitpath,'(a)',err=998) path(i)
63    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
78  end do
79
80  ! Check whether any nested subdomains are to be used
81  !***************************************************
82
83  do i=1,maxnests
84    read(unitpath,'(a)') path(numpath+2*(i-1)+1)
85    read(unitpath,'(a)') path(numpath+2*(i-1)+2)
86    if (path(numpath+2*(i-1)+1)(1:5).eq.'=====') goto 30
87    length(numpath+2*(i-1)+1)=index(path(numpath+2*(i-1)+1),' ')-1
88    length(numpath+2*(i-1)+2)=index(path(numpath+2*(i-1)+2),' ')-1
89  end do
90  print*,length(5),length(6)
91
92
93  ! Determine number of available nested domains
94  !*********************************************
95
9630   numbnests=i-1
97
98  close(unitpath)
99  return
100
101998   write(*,*) ' #### TRAJECTORY MODEL ERROR! ERROR WHILE     #### '
102  write(*,*) ' #### READING FILE PATHNAMES.                 #### '
103  stop
104
105999   write(*,*) ' #### TRAJECTORY MODEL ERROR! FILE "pathnames"#### '
106  write(*,*) ' #### CANNOT BE OPENED IN THE CURRENT WORKING #### '
107  write(*,*) ' #### DIRECTORY.                              #### '
108  stop
109
110end subroutine readpaths
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG