source: flexpart.git/src/readoutgrid_nest.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: 4.8 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4subroutine readoutgrid_nest
5
6  !*****************************************************************************
7  !                                                                            *
8  !     This routine reads the user specifications for the output nest.        *
9  !                                                                            *
10  !     Author: A. Stohl                                                       *
11  !                                                                            *
12  !     4 June 1996                                                            *
13  !                                                                            *
14  !*****************************************************************************
15  !                                                                            *
16  ! Variables:                                                                 *
17  ! dxoutn,dyoutn        grid distances of output nest                         *
18  ! numxgridn,numygridn,numzgrid    nest dimensions                            *
19  ! outlon0n,outlat0n    lower left corner of nest                             *
20  ! outheight(maxzgrid)  height levels of output grid [m]                      *
21  !                                                                            *
22  ! Constants:                                                                 *
23  ! unitoutgrid          unit connected to file OUTGRID                        *
24  !                                                                            *
25  !*****************************************************************************
26
27  use outg_mod
28  use par_mod
29  use com_mod
30
31  implicit none
32
33  integer :: stat
34  real :: xr,xr1,yr,yr1
35  real,parameter :: eps=1.e-4
36
37  integer :: readerror
38
39  ! declare namelist
40  namelist /outgridn/ &
41    outlon0n,outlat0n, &
42    numxgridn,numygridn, &
43    dxoutn,dyoutn
44
45  ! helps identifying failed namelist input
46  dxoutn=-1.0
47
48  ! Open the OUTGRID file and read output grid specifications
49  !**********************************************************
50
51  open(unitoutgrid,file=path(1)(1:length(1))//'OUTGRID_NEST',form='formatted',status='old',err=999)
52
53  ! try namelist input
54  read(unitoutgrid,outgridn,iostat=readerror)
55  close(unitoutgrid)
56
57  if ((dxoutn.le.0).or.(readerror.ne.0)) then
58
59    open(unitoutgrid,file=path(1)(1:length(1))//'OUTGRID_NEST',status='old',err=999)
60    call skplin(5,unitoutgrid)
61
62    ! 1.  Read horizontal grid specifications
63    !****************************************
64
65    call skplin(3,unitoutgrid)
66    read(unitoutgrid,'(4x,f11.4)') outlon0n
67    call skplin(3,unitoutgrid)
68    read(unitoutgrid,'(4x,f11.4)') outlat0n
69    call skplin(3,unitoutgrid)
70    read(unitoutgrid,'(4x,i5)') numxgridn
71    call skplin(3,unitoutgrid)
72    read(unitoutgrid,'(4x,i5)') numygridn
73    call skplin(3,unitoutgrid)
74    read(unitoutgrid,'(4x,f12.5)') dxoutn
75    call skplin(3,unitoutgrid)
76    read(unitoutgrid,'(4x,f12.5)') dyoutn
77
78    close(unitoutgrid)
79  endif
80
81  ! write outgrid_nest file in namelist format to output directory if requested
82  if (nmlout.and.lroot) then
83    open(unitoutgrid,file=path(2)(1:length(2))//'OUTGRID_NEST.namelist',err=1000)
84    write(unitoutgrid,nml=outgridn)
85    close(unitoutgrid)
86  endif
87
88  allocate(orooutn(0:numxgridn-1,0:numygridn-1),stat=stat)
89  if (stat.ne.0) write(*,*)'ERROR: could not allocate orooutn'
90  allocate(arean(0:numxgridn-1,0:numygridn-1),stat=stat)
91  if (stat.ne.0) write(*,*)'ERROR: could not allocate arean'
92  allocate(volumen(0:numxgridn-1,0:numygridn-1,numzgrid),stat=stat)
93  if (stat.ne.0) write(*,*)'ERROR: could not allocate volumen'
94
95  ! Check validity of output grid (shall be within model domain)
96  !*************************************************************
97
98  xr=outlon0n+real(numxgridn)*dxoutn
99  yr=outlat0n+real(numygridn)*dyoutn
100  xr1=xlon0+real(nxmin1)*dx
101  yr1=ylat0+real(nymin1)*dy
102  if ((outlon0n+eps.lt.xlon0).or.(outlat0n+eps.lt.ylat0) &
103       .or.(xr.gt.xr1+eps).or.(yr.gt.yr1+eps)) then
104    write(*,*) ' #### FLEXPART MODEL ERROR! PART OF OUTPUT    ####'
105    write(*,*) ' #### NEST IS OUTSIDE MODEL DOMAIN. CHANGE    ####'
106    write(*,*) ' #### FILE OUTGRID IN DIRECTORY               ####'
107    write(*,'(a)') path(1)(1:length(1))
108    stop
109  endif
110
111  xoutshiftn=xlon0-outlon0n
112  youtshiftn=ylat0-outlat0n
113  return
114
115999 write(*,*) ' #### FLEXPART MODEL ERROR! FILE "OUTGRID"    #### '
116  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
117  write(*,'(a)') path(1)(1:length(1))
118  stop
119
1201000 write(*,*) ' #### FLEXPART MODEL ERROR! FILE "OUTGRID"    #### '
121  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
122  write(*,'(a)') path(2)(1:length(2))
123  stop
124
125end subroutine readoutgrid_nest
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG