source: flexpart.git/src/readreceptors.f90 @ d7935de

univie
Last change on this file since d7935de was d7935de, checked in by pesei <petra seibert at univie ac at>, 6 years ago

modify most input read subroutines

changed some variable names (mostly for I-N reasons)
includes two names appearing also in timemanager, com_mod
corrected a few mistakes
simplified some parts of code
changed options/RELEASES which is in nml fmt correspondingly

  • Property mode set to 100644
File size: 7.0 KB
RevLine 
[e200b7a]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 readreceptors
23
24  !*****************************************************************************
25  !                                                                            *
26  !     This routine reads the user specifications for the receptor points.    *
27  !                                                                            *
28  !     Author: A. Stohl                                                       *
[d7935de]29  !     1 August 1996       
30  !                                                  *
31  !     HSO, 14 August 2013: Added optional namelist input
32  !     PS, 2/2015: access= -> position=
33  !     PS, 6/2015: variable names, simplify code
[e200b7a]34  !                                                                            *
35  !*****************************************************************************
36  !                                                                            *
37  ! Variables:                                                                 *
38  ! receptorarea(maxreceptor)  area of dx*dy at location of receptor           *
39  ! receptorname(maxreceptor)  names of receptors                              *
40  ! xreceptor,yreceptor  coordinates of receptor points                        *
41  !                                                                            *
42  ! Constants:                                                                 *
43  ! unitreceptor         unit connected to file RECEPTORS                      *
44  !                                                                            *
45  !*****************************************************************************
46
47  use par_mod
48  use com_mod
49
50  implicit none
51
52  integer :: j
53  real :: x,y,xm,ym
54  character(len=16) :: receptor
55
[d7935de]56  integer :: ios
57  real :: xlon,ylat   ! for namelist input, lon/lat are used instead of x,y
[b4d29ce]58  integer,parameter :: unitreceptorout=2
59
60  ! declare namelist
[d7935de]61  namelist /nml_receptors/ receptor, xlon, ylat
[b4d29ce]62
[d7935de]63!CPS I comment this out - why should we not have receptor output in bwd runs?
64  ! For backward runs, do not allow receptor output. Thus, set number of
65  ! receptors to zero
[e200b7a]66  !*****************************************************************************
67
[d7935de]68!  if (ldirect.lt.0) then
69!    numreceptor=0
70!    return
71!  endif
[e200b7a]72
73
74  ! Open the RECEPTORS file and read output grid specifications
75  !************************************************************
76
[d7935de]77  open(unitreceptor,file=path(1)(1:length(1))//'RECEPTORS',form='formatted',&
78    status='old',err=999)
[e200b7a]79
[b4d29ce]80  ! try namelist input
[d7935de]81  read(unitreceptor,nml_receptors,iostat=ios)
[b4d29ce]82
83  ! prepare namelist output if requested
[d7935de]84  if (nmlout) open(unitreceptorout,file=path(2)(1:length(2))// &
85    'RECEPTORS.namelist', position='append',status='new',err=1000)
[e200b7a]86
[d7935de]87  if (ios .ne. 0) then ! read as regular text file
[e200b7a]88
[b4d29ce]89    close(unitreceptor)
[d7935de]90    open(unitreceptor,file=path(1)(1:length(1))// &
91     'RECEPTORS',status='old',err=999)
92 
[b4d29ce]93    call skplin(5,unitreceptor)
[e200b7a]94
[b4d29ce]95    ! Read the names and coordinates of the receptors
96    !************************************************
97
98    j=0
99100 j=j+1
[e200b7a]100    read(unitreceptor,*,end=99)
101    read(unitreceptor,*,end=99)
102    read(unitreceptor,*,end=99)
103    read(unitreceptor,'(4x,a16)',end=99) receptor
104    call skplin(3,unitreceptor)
[d7935de]105      read(unitreceptor,'(4x,f11.4)',end=99) xlon
[e200b7a]106    call skplin(3,unitreceptor)
[d7935de]107      read(unitreceptor,'(4x,f11.4)',end=99) ylat
108      if ((xlon.eq.0.).and.(ylat.eq.0.).and. &
[e200b7a]109         (receptor.eq.'                ')) then
110      j=j-1
111      goto 100
112    endif
113    if (j.gt.maxreceptor) then
[b4d29ce]114      write(*,*) ' #### FLEXPART MODEL ERROR! TOO MANY RECEPTOR #### '
115      write(*,*) ' #### POINTS ARE GIVEN.                       #### '
116      write(*,*) ' #### MAXIMUM NUMBER IS ',maxreceptor,'       #### '
117      write(*,*) ' #### PLEASE MAKE CHANGES IN FILE RECEPTORS   #### '
[e200b7a]118    endif
119    receptorname(j)=receptor
[d7935de]120      xreceptor(j)=(xlon-xlon0)/dx       ! transform to grid coordinates
121      yreceptor(j)=(ylat-ylat0)/dy
122      xm=r_earth*cos(ylat*pi/180.)*dx/180.*pi
[e200b7a]123    ym=r_earth*dy/180.*pi
124    receptorarea(j)=xm*ym
[d7935de]125  ! write receptors file in namelist format to output directory if requested
126    if (nmlout.and.lroot) write(unitreceptorout,nml=nml_receptors)
[b4d29ce]127
[e200b7a]128    goto 100
129
[b4d29ce]13099  numreceptor=j-1
131
132  else ! continue with namelist input
133
134    j=0
[d7935de]135    do while (ios .eq. 0)
[b4d29ce]136      j=j+1
[d7935de]137      read(unitreceptor,nml_receptors,iostat=ios)
138      if (ios .eq. 0) then
[b4d29ce]139        if (j.gt.maxreceptor) then
140          write(*,*) ' #### FLEXPART MODEL ERROR! TOO MANY RECEPTOR #### '
141          write(*,*) ' #### POINTS ARE GIVEN.                       #### '
142          write(*,*) ' #### MAXIMUM NUMBER IS ',maxreceptor,'       #### '
143          write(*,*) ' #### PLEASE MAKE CHANGES IN FILE RECEPTORS   #### '
144        endif
145        receptorname(j)=receptor
[d7935de]146        xreceptor(j)=(xlon-xlon0)/dx       ! transform to grid coordinates
147        yreceptor(j)=(ylat-ylat0)/dy
148        xm=r_earth*cos(ylat*pi/180.)*dx/180.*pi
[b4d29ce]149        ym=r_earth*dy/180.*pi
150        receptorarea(j)=xm*ym
151      endif
152
[d7935de]153    ! write receptors file in namelist format to output directory if requested
154      if (nmlout.and.lroot) write(unitreceptorout,nml=nml_receptors)
[b4d29ce]155
156    end do
157    numreceptor=j-1
158    close(unitreceptor)
159
[d7935de]160  endif ! end no-nml / nml bloc
[b4d29ce]161
[d7935de]162  if (nmlout .and. lroot) close(unitreceptorout)
[b4d29ce]163
[e200b7a]164  return
165
166
[b4d29ce]167999 write(*,*) ' #### FLEXPART MODEL ERROR! FILE "RECEPTORS"  #### '
[d7935de]168  write(*,*)   ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
169  write(*,'(a)') trim(path(1))
[e200b7a]170  stop
171
[d7935de]1721000 write(*,*) ' #### FLEXPART MODEL ERROR! FILE "RECEPTORS"  #### '
173  write(*,*)    ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
174  write(*,'(a)') trim(path(2))
[b4d29ce]175  stop
176
[e200b7a]177end subroutine readreceptors
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG