source: trunk/src/readoutgrid_nest.f90 @ 28

Last change on this file since 28 was 27, checked in by hasod, 10 years ago
  • Implemented optional namelist input for COMMAND, RELEASES, SPECIES, AGECLASSES,OUTGRID,OUTGRID_NEST,RECEPTORS
  • Implemented com_mod switch nmlout to write input files as namelist to the output directory (.true. by default)
  • Proposed updated startup and runtime output (may change back to previous info if desired)
File size: 6.1 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  !                                                                            *
32  !*****************************************************************************
33  !                                                                            *
34  ! Variables:                                                                 *
35  ! dxoutn,dyoutn        grid distances of output nest                         *
36  ! numxgridn,numygridn,numzgrid    nest dimensions                            *
37  ! outlon0n,outlat0n    lower left corner of nest                             *
38  ! outheight(maxzgrid)  height levels of output grid [m]                      *
39  !                                                                            *
40  ! Constants:                                                                 *
41  ! unitoutgrid          unit connected to file OUTGRID                        *
42  !                                                                            *
43  !*****************************************************************************
44
45  use outg_mod
46  use par_mod
47  use com_mod
48
49  implicit none
50
51  integer :: stat
52  real :: xr,xr1,yr,yr1
53  real,parameter :: eps=1.e-4
54
55  integer :: readerror
56
57  ! declare namelist
58  namelist /outgridn/ &
59    outlon0n,outlat0n, &
60    numxgridn,numygridn, &
61    dxoutn,dyoutn
62
63  ! helps identifying failed namelist input
64  dxoutn=-1.0
65
66  ! Open the OUTGRID file and read output grid specifications
67  !**********************************************************
68
69  open(unitoutgrid,file=path(1)(1:length(1))//'OUTGRID_NEST',form='formatted',status='old',err=999)
70
71  ! try namelist input
72  read(unitoutgrid,outgridn,iostat=readerror)
73  close(unitoutgrid)
74
75  if ((dxoutn.le.0).or.(readerror.ne.0)) then
76
77    open(unitoutgrid,file=path(1)(1:length(1))//'OUTGRID_NEST',status='old',err=999)
78    call skplin(5,unitoutgrid)
79
80    ! 1.  Read horizontal grid specifications
81    !****************************************
82
83    call skplin(3,unitoutgrid)
84    read(unitoutgrid,'(4x,f11.4)') outlon0n
85    call skplin(3,unitoutgrid)
86    read(unitoutgrid,'(4x,f11.4)') outlat0n
87    call skplin(3,unitoutgrid)
88    read(unitoutgrid,'(4x,i5)') numxgridn
89    call skplin(3,unitoutgrid)
90    read(unitoutgrid,'(4x,i5)') numygridn
91    call skplin(3,unitoutgrid)
92    read(unitoutgrid,'(4x,f12.5)') dxoutn
93    call skplin(3,unitoutgrid)
94    read(unitoutgrid,'(4x,f12.5)') dyoutn
95
96    close(unitoutgrid)
97  endif
98
99  ! write outgrid_nest file in namelist format to output directory if requested
100  if (nmlout.eqv..true.) then
101    open(unitoutgrid,file=path(2)(1:length(2))//'OUTGRID_NEST.namelist',err=1000)
102    write(unitoutgrid,nml=outgridn)
103    close(unitoutgrid)
104  endif
105
106  allocate(orooutn(0:numxgridn-1,0:numygridn-1),stat=stat)
107  if (stat.ne.0) write(*,*)'ERROR: could not allocate orooutn'
108  allocate(arean(0:numxgridn-1,0:numygridn-1),stat=stat)
109  if (stat.ne.0) write(*,*)'ERROR: could not allocate arean'
110  allocate(volumen(0:numxgridn-1,0:numygridn-1,numzgrid),stat=stat)
111  if (stat.ne.0) write(*,*)'ERROR: could not allocate volumen'
112
113  ! Check validity of output grid (shall be within model domain)
114  !*************************************************************
115
116  xr=outlon0n+real(numxgridn)*dxoutn
117  yr=outlat0n+real(numygridn)*dyoutn
118  xr1=xlon0+real(nxmin1)*dx
119  yr1=ylat0+real(nymin1)*dy
120  if ((outlon0n+eps.lt.xlon0).or.(outlat0n+eps.lt.ylat0) &
121       .or.(xr.gt.xr1+eps).or.(yr.gt.yr1+eps)) then
122    write(*,*) ' #### FLEXPART MODEL ERROR! PART OF OUTPUT    ####'
123    write(*,*) ' #### NEST IS OUTSIDE MODEL DOMAIN. CHANGE    ####'
124    write(*,*) ' #### FILE OUTGRID IN DIRECTORY               ####'
125    write(*,'(a)') path(1)(1:length(1))
126    stop
127  endif
128
129  xoutshiftn=xlon0-outlon0n
130  youtshiftn=ylat0-outlat0n
131  return
132
133999 write(*,*) ' #### FLEXPART MODEL ERROR! FILE "OUTGRID"    #### '
134  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
135  write(*,'(a)') path(1)(1:length(1))
136  stop
137
1381000 write(*,*) ' #### FLEXPART MODEL ERROR! FILE "OUTGRID"    #### '
139  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
140  write(*,'(a)') path(2)(1:length(2))
141  stop
142
143end subroutine readoutgrid_nest
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG