source: flexpart.git/src/readOHfield.f90 @ fb0d416

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bugunivie
Last change on this file since fb0d416 was fb0d416, checked in by Espen Sollum ATMOS <eso@…>, 9 years ago

OH change suggested by Xuekun

  • Property mode set to 100644
File size: 6.5 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 readOHfield
23
24  !*****************************************************************************
25  !                                                                            *
26  ! Reads the OH field into memory                                             *
27  !                                                                            *
28  ! AUTHOR: R.L. Thompson, Nov 2014                                            *
29  !                                                                            *
30  !*****************************************************************************
31  !                                                                            *
32  ! Variables:                                                                 *
33  !                                                                            *
34  ! path(numpath)              contains the path names                         *
35  ! lonOH(nxOH)                longitude of OH fields                          *
36  ! latOH(nyOH)                latitude of OH fields                           *
37  ! altOH(nzOH)                altitude of OH fields                           *
38  ! etaOH(nzOH)                eta-levels of OH fields                         *
39  ! OH_field(nxOH,nyOH,nzOH,m) OH concentration (molecules/cm3)                *
40  !                                                                            *
41  !                                                                            *
42  !*****************************************************************************
43
44  use oh_mod
45  use par_mod
46  use com_mod
47
48  implicit none
49
50  include 'netcdf.inc'
51
52  character(len=150) :: thefile
53  character(len=2) :: mm
54  integer :: nid,ierr,xid,yid,zid,vid,m
55  real, dimension(:), allocatable :: etaOH
56
57!  real, parameter :: gasct=8.314   ! gas constant
58!  real, parameter :: mct=0.02894   ! kg mol-1
59!  real, parameter :: g=9.80665     ! m s-2
60!  real, parameter :: lrate=0.0065  ! K m-1
61  real, parameter :: scalehgt=7000. ! scale height in metres
62
63  ! Read OH fields and level heights
64  !********************************
65
66  do m=1,12
67 
68    ! open netcdf file
69    write(mm,fmt='(i2.2)') m
70    thefile=trim(path(1))//'OH_FIELDS/'//'geos-chem.OH.2005'//mm//'01.nc'
71    ierr=nf_open(trim(thefile),NF_NOWRITE,nid)
72    if(ierr.ne.0) then
73      write(*,*) nf_strerror(ierr)
74      stop
75    endif
76
77    ! inquire about variables
78    ierr=nf_inq_dimid(nid,'Lon-000',xid)
79    if(ierr.ne.0) then
80      write(*,*) nf_strerror(ierr)
81      stop
82    endif
83    ierr=nf_inq_dimid(nid,'Lat-000',yid)
84    if(ierr.ne.0) then
85      write(*,*) nf_strerror(ierr)
86      stop
87    endif
88    ierr=nf_inq_dimid(nid,'Alt-000',zid)
89    if(ierr.ne.0) then
90      write(*,*) nf_strerror(ierr)
91      stop
92    endif
93
94    if(m.eq.1) then
95
96      ! read dimension sizes
97      ierr=nf_inq_dimlen(nid,xid,nxOH)
98      if(ierr.ne.0) then
99        write(*,*) nf_strerror(ierr)
100        stop
101      endif
102      ierr=nf_inq_dimlen(nid,yid,nyOH)
103      if(ierr.ne.0) then
104        write(*,*) nf_strerror(ierr)
105        stop
106      endif
107      ierr=nf_inq_dimlen(nid,zid,nzOH)
108      if(ierr.ne.0) then
109        write(*,*) nf_strerror(ierr)
110        stop
111      endif 
112
113      ! allocate variables
114      allocate(lonOH(nxOH))
115      allocate(latOH(nyOH))
116      allocate(etaOH(nzOH))
117      allocate(altOH(nzOH))
118      allocate(OH_field(nxOH,nyOH,nzOH,12))
119      allocate(OH_hourly(nxOH,nyOH,nzOH,2))
120
121      ! read dimension variables
122      ierr=nf_inq_varid(nid,'LON',xid)
123      ierr=nf_get_var_real(nid,xid,lonOH)
124      if(ierr.ne.0) then
125        write(*,*) nf_strerror(ierr)
126        stop
127      endif
128      ierr=nf_inq_varid(nid,'LAT',yid)
129      ierr=nf_get_var_real(nid,yid,latOH)
130      if(ierr.ne.0) then
131        write(*,*) nf_strerror(ierr)
132        stop
133      endif
134      ierr=nf_inq_varid(nid,'ETAC',zid)
135      ierr=nf_get_var_real(nid,zid,etaOH)
136      if(ierr.ne.0) then
137        write(*,*) nf_strerror(ierr)
138        stop
139      endif
140
141      ! convert eta-level to altitude (assume surface pressure of 1010 hPa)
142      altOH=log(1010./(etaOH*1010.))*scalehgt
143
144    endif ! m.eq.1
145
146    ! read OH_field
147    ierr=nf_inq_varid(nid,'CHEM-L_S__OH',vid)
148    ierr=nf_get_var_real(nid,vid,OH_field(:,:,:,m))
149    if(ierr.ne.0) then
150      write(*,*) nf_strerror(ierr)
151      stop
152    endif
153
154    ierr=nf_close(nid)
155
156  end do
157 
158  deallocate(etaOH)
159
160  ! Read J(O1D) photolysis rates
161  !******************************** 
162
163  ! open netcdf file
164  thefile=trim(path(1))//'OH_FIELDS/jrate_average.nc'
165  ierr=nf_open(trim(thefile),NF_NOWRITE,nid)
166  if(ierr.ne.0) then
167    write(*,*) nf_strerror(ierr)
168    stop
169  endif
170
171  ! read dimension variables
172  ierr=nf_inq_varid(nid,'longitude',xid)
173  ierr=nf_get_var_real(nid,xid,lonjr)
174  if(ierr.ne.0) then
175    write(*,*) nf_strerror(ierr)
176    stop
177  endif
178  ierr=nf_inq_varid(nid,'latitude',yid)
179  ierr=nf_get_var_real(nid,yid,latjr)
180  if(ierr.ne.0) then
181    write(*,*) nf_strerror(ierr)
182    stop
183  endif
184
185  ! read jrate_average
186  ierr=nf_inq_varid(nid,'jrate',vid)
187  ierr=nf_get_var_real(nid,vid,jrate_average)
188  if(ierr.ne.0) then
189    write(*,*) nf_strerror(ierr)
190    stop
191  endif
192
193  ierr=nf_close(nid)
194
195  return
196
197end subroutine readOHfield
198
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG