source: flexpart.git/src/readoutgrid.f90

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file was 92fab65, checked in by Ignacio Pisso <ip@…>, 4 years ago

add SPDX-License-Identifier to all .f90 files

  • Property mode set to 100644
File size: 7.5 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4subroutine readoutgrid
5
6  !*****************************************************************************
7  !                                                                            *
8  !     This routine reads the user specifications for the output grid.        *
9  !                                                                            *
10  !     Author: A. Stohl                                                       *
11  !                                                                            *
12  !     4 June 1996                                                            *
13  !     HSO, 1 July 2014
14  !     Added optional namelist input
15  !                                                                            *
16  !*****************************************************************************
17  !                                                                            *
18  ! Variables:                                                                 *
19  ! dxout,dyout          grid distance                                         *
20  ! numxgrid,numygrid,numzgrid    grid dimensions                              *
21  ! outlon0,outlat0      lower left corner of grid                             *
22  ! outheight(maxzgrid)  height levels of output grid [m]                      *
23  !                                                                            *
24  ! Constants:                                                                 *
25  ! unitoutgrid          unit connected to file OUTGRID                        *
26  !                                                                            *
27  !*****************************************************************************
28
29  use outg_mod
30  use par_mod
31  use com_mod
32
33  implicit none
34
35  integer :: i,j,stat
36  real :: outhelp,xr,xr1,yr,yr1
37  real,parameter :: eps=1.e-4
38
39  ! namelist variables
40  integer, parameter :: maxoutlev=500
41  integer :: readerror
42  real,allocatable, dimension (:) :: outheights
43
44  ! declare namelist
45  namelist /outgrid/ &
46    outlon0,outlat0, &
47    numxgrid,numygrid, &
48    dxout,dyout, &
49    outheights
50
51  ! allocate large array for reading input
52  allocate(outheights(maxoutlev),stat=stat)
53  if (stat.ne.0) write(*,*)'ERROR: could not allocate outheights'
54
55  ! helps identifying failed namelist input
56  dxout=-1.0
57  outheights=-1.0
58
59  ! Open the OUTGRID file and read output grid specifications
60  !**********************************************************
61
62  open(unitoutgrid,file=path(1)(1:length(1))//'OUTGRID',status='old',form='formatted',err=999)
63
64  ! try namelist input
65  read(unitoutgrid,outgrid,iostat=readerror)
66  close(unitoutgrid)
67
68  if ((dxout.le.0).or.(readerror.ne.0)) then
69
70    readerror=1
71
72    open(unitoutgrid,file=path(1)(1:length(1))//'OUTGRID',status='old',err=999)
73
74    call skplin(5,unitoutgrid)
75
76    ! 1.  Read horizontal grid specifications
77    !****************************************
78
79    call skplin(3,unitoutgrid)
80    read(unitoutgrid,'(4x,f11.4)') outlon0
81    call skplin(3,unitoutgrid)
82    read(unitoutgrid,'(4x,f11.4)') outlat0
83    call skplin(3,unitoutgrid)
84    read(unitoutgrid,'(4x,i5)') numxgrid
85    call skplin(3,unitoutgrid)
86    read(unitoutgrid,'(4x,i5)') numygrid
87    call skplin(3,unitoutgrid)
88    read(unitoutgrid,'(4x,f12.5)') dxout
89    call skplin(3,unitoutgrid)
90    read(unitoutgrid,'(4x,f12.5)') dyout
91
92  endif
93
94  ! Check validity of output grid (shall be within model domain)
95  !*************************************************************
96
97  xr=outlon0+real(numxgrid)*dxout
98  yr=outlat0+real(numygrid)*dyout
99  xr1=xlon0+real(nxmin1)*dx
100  yr1=ylat0+real(nymin1)*dy
101  if ((outlon0+eps.lt.xlon0).or.(outlat0+eps.lt.ylat0) &
102       .or.(xr.gt.xr1+eps).or.(yr.gt.yr1+eps)) then
103    write(*,*) outlon0,outlat0
104    write(*,*) xr1,yr1,xlon0,ylat0,xr,yr,dxout,dyout
105    write(*,*) ' #### FLEXPART MODEL ERROR! PART OF OUTPUT    ####'
106    write(*,*) ' #### GRID IS OUTSIDE MODEL DOMAIN. CHANGE    ####'
107    write(*,*) ' #### FILE OUTGRID IN DIRECTORY               ####'
108    write(*,'(a)') path(1)(1:length(1))
109    stop
110  endif
111
112  ! 2. Count Vertical levels of output grid
113  !****************************************
114
115  if (readerror.ne.0) then
116    j=0
117100 j=j+1
118    do i=1,3
119      read(unitoutgrid,*,end=99)
120    end do
121    read(unitoutgrid,'(4x,f7.1)',end=99) outhelp
122    if (outhelp.eq.0.) goto 99
123    goto 100
12499  numzgrid=j-1
125  else
126    do i=1,maxoutlev
127      if (outheights(i).lt.0) exit
128    end do
129    numzgrid=i-1
130  end if
131
132  allocate(outheight(numzgrid),stat=stat)
133  if (stat.ne.0) write(*,*)'ERROR: could not allocate outheight'
134  allocate(outheighthalf(numzgrid),stat=stat)
135  if (stat.ne.0) write(*,*)'ERROR: could not allocate outheighthalf'
136
137  ! 2. Vertical levels of output grid
138  !**********************************
139
140  if (readerror.ne.0) then
141
142    rewind(unitoutgrid)
143    call skplin(29,unitoutgrid)
144
145    do j=1,numzgrid
146      do i=1,3
147        read(unitoutgrid,*)
148      end do
149      read(unitoutgrid,'(4x,f7.1)') outhelp
150      outheight(j)=outhelp
151      outheights(j)=outhelp
152    end do
153    close(unitoutgrid)
154
155  else
156
157    do j=1,numzgrid
158      outheight(j)=outheights(j)
159    end do
160
161  endif
162
163  ! write outgrid file in namelist format to output directory if requested
164  if (nmlout.and.lroot) then
165    ! reallocate outheights with actually required dimension for namelist writing
166    deallocate(outheights)
167    allocate(outheights(numzgrid),stat=stat)
168    if (stat.ne.0) write(*,*)'ERROR: could not allocate outheights'
169
170    do j=1,numzgrid
171      outheights(j)=outheight(j)
172    end do
173
174    open(unitoutgrid,file=path(2)(1:length(2))//'OUTGRID.namelist',err=1000)
175    write(unitoutgrid,nml=outgrid)
176    close(unitoutgrid)
177  endif
178
179  ! Check whether vertical levels are specified in ascending order
180  !***************************************************************
181
182  do j=2,numzgrid
183    if (outheight(j).le.outheight(j-1)) then
184    write(*,*) ' #### FLEXPART MODEL ERROR! YOUR SPECIFICATION#### '
185    write(*,*) ' #### OF OUTPUT LEVELS IS CORRUPT AT LEVEL    #### '
186    write(*,*) ' #### ',j,'                              #### '
187    write(*,*) ' #### PLEASE MAKE CHANGES IN FILE OUTGRID.    #### '
188    endif
189  end do
190
191  ! Determine the half levels, i.e. middle levels of the output grid
192  !*****************************************************************
193
194  outheighthalf(1)=outheight(1)/2.
195  do j=2,numzgrid
196    outheighthalf(j)=(outheight(j-1)+outheight(j))/2.
197  end do
198
199  xoutshift=xlon0-outlon0
200  youtshift=ylat0-outlat0
201
202  allocate(oroout(0:numxgrid-1,0:numygrid-1),stat=stat)
203  if (stat.ne.0) write(*,*)'ERROR: could not allocate oroout'
204  allocate(area(0:numxgrid-1,0:numygrid-1),stat=stat)
205  if (stat.ne.0) write(*,*)'ERROR: could not allocate area'
206  allocate(volume(0:numxgrid-1,0:numygrid-1,numzgrid),stat=stat)
207  if (stat.ne.0) write(*,*)'ERROR: could not allocate volume'
208  allocate(areaeast(0:numxgrid-1,0:numygrid-1,numzgrid),stat=stat)
209  if (stat.ne.0) write(*,*)'ERROR: could not allocate areaeast'
210  allocate(areanorth(0:numxgrid-1,0:numygrid-1,numzgrid),stat=stat)
211  if (stat.ne.0) write(*,*)'ERROR: could not allocate areanorth'
212  return
213
214
215999 write(*,*) ' #### FLEXPART MODEL ERROR! FILE "OUTGRID"    #### '
216  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
217  write(*,'(a)') path(1)(1:length(1))
218  stop
219
2201000 write(*,*) ' #### FLEXPART MODEL ERROR! FILE "OUTGRID"    #### '
221  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
222  write(*,'(a)') path(2)(1:length(2))
223  stop
224
225end subroutine readoutgrid
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG