source: flexpart.git/src/readoutgrid_nest.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: 6.2 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 readoutgrid_nest
23
24  !*****************************************************************************
25  !                                                                            *
26  !     This routine reads the user specifications for the output nest.        *
27  !                                                                            *
28  !     Author: A. Stohl                                                       *
29  !                                                                            *
30  !     4 June 1996                                                            *
31  !     HSO, 1 July 2014: Add optional namelist input                          *
32  !     PS, 6/2015-9/2018: read regular input with free format                 *
33  !       and rename some variables                                            *
34  !                                                                            *
35  !*****************************************************************************
36  !                                                                            *
37  ! Variables:                                                                 *
38  ! dxoutn,dyoutn        grid distances of output nest                         *
39  ! numxgridn,numygridn,numzgrid    nest dimensions                            *
40  ! outlon0n,outlat0n    lower left corner of nest                             *
41  ! outheight(maxzgrid)  height levels of output grid [m]                      *
42  !                                                                            *
43  ! Constants:                                                                 *
44  ! unitoutgrid          unit connected to file OUTGRID                        *
45  !                                                                            *
46  !*****************************************************************************
47
48  use outg_mod
49  use par_mod
50  use com_mod
51
52  implicit none
53
54  integer :: stat
55  real :: xr,xr1,yr,yr1
56  real,parameter :: eps=1.e-4
57
58  integer :: ios
59
60! declare namelist
61  namelist /nml_outgridn/ &
62    outlon0n,outlat0n,numxgridn,numygridn,dxoutn,dyoutn
63
64  ! helps identifying failed namelist input
65  dxoutn=-1.0
66
67  ! Open the OUTGRID file and read output grid specifications
68  !**********************************************************
69
70  open(unitoutgrid,file=path(1)(1:length(1))//'OUTGRID_NEST',form='formatted',&
71    status='old',err=999)
72
73  ! try namelist input
74  read(unitoutgrid,nml_outgridn,iostat=ios)
75  close(unitoutgrid)
76
77  if (dxoutn.le.0 .or.ios.ne.0) then
78
79    open(unitoutgrid,file=path(1)(1:length(1))//'OUTGRID_NEST',status='old',&
80      err=999)
81    call skplin(5,unitoutgrid)
82
83  ! Read horizontal grid specifications
84  ! ***********************************
85
86    call skplin(3,unitoutgrid)
87    read(unitoutgrid,*) outlon0n
88    call skplin(3,unitoutgrid)
89    read(unitoutgrid,*) outlat0n
90    call skplin(3,unitoutgrid)
91    read(unitoutgrid,*) numxgridn
92    call skplin(3,unitoutgrid)
93    read(unitoutgrid,*) numygridn
94    call skplin(3,unitoutgrid)
95    read(unitoutgrid,*) dxoutn
96    call skplin(3,unitoutgrid)
97    read(unitoutgrid,*) dyoutn
98
99    close(unitoutgrid)
100  endif
101
102  ! write outgrid_nest file in namelist format to output directory if requested
103  if (nmlout.and.lroot) then
104    open(unitoutgrid,file=path(2)(1:length(2))//'OUTGRID_NEST.namelist',&
105      err=1000)
106    write(unitoutgrid,nml=nml_outgridn)
107    close(unitoutgrid)
108  endif
109
110  allocate(orooutn(0:numxgridn-1,0:numygridn-1),stat=ios)
111  if (ios.ne.0) write(*,*)'ERROR: could not allocate orooutn'
112  allocate(arean(0:numxgridn-1,0:numygridn-1),stat=ios)
113  if (ios.ne.0) write(*,*)'ERROR: could not allocate arean'
114  allocate(volumen(0:numxgridn-1,0:numygridn-1,numzgrid),stat=ios)
115  if (ios.ne.0) write(*,*)'ERROR: could not allocate volumen'
116
117  ! Check validity of output grid (shall be within model domain)
118  !*************************************************************
119
120  xr=outlon0n+real(numxgridn)*dxoutn
121  yr=outlat0n+real(numygridn)*dyoutn
122  xr1=xlon0+real(nxmin1)*dx
123  yr1=ylat0+real(nymin1)*dy
124  if (outlon0n+eps.lt.xlon0 .or. outlat0n+eps.lt.ylat0 &
125    .or. xr.gt.xr1+eps .or. yr.gt.yr1+eps) then
126    write(*,*) ' #### FLEXPART MODEL ERROR! PART OF OUTPUT    ####'
127    write(*,*) ' #### NEST IS OUTSIDE MODEL DOMAIN. CHANGE    ####'
128    write(*,*) ' #### FILE OUTGRID IN DIRECTORY               ####'
129    write(*,'(a)') trim(path(1))
130    stop
131  endif
132
133  xoutshiftn=xlon0-outlon0n
134  youtshiftn=ylat0-outlat0n
135  return
136
137999 write(*,*) ' #### FLEXPART MODEL ERROR! FILE "OUTGRID"    #### '
138  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
139  write(*,'(a)') trim(path(1))
140  stop
141
1421000 write(*,*) ' #### FLEXPART MODEL ERROR! FILE "OUTGRID"    #### '
143  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
144  write(*,'(a)') trim(path(2))
145  stop
146
147end subroutine readoutgrid_nest
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG