source: flexpart.git/src/readoutgrid_nest.f90 @ 3481cc1

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

move license from headers to a different file

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