Changeset 8a65cb0 in flexpart.git for src/readOHfield.f90


Ignore:
Timestamp:
Mar 2, 2015, 3:11:55 PM (9 years ago)
Author:
Espen Sollum ATMOS <espen@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug, univie
Children:
1d207bb
Parents:
60403cd
Message:

Added code, makefile for dev branch

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/readOHfield.f90

    re200b7a r8a65cb0  
    2626  ! Reads the OH field into memory                                             *
    2727  !                                                                            *
    28   ! AUTHOR: Sabine Eckhardt, June 2007                                         *
     28  ! AUTHOR: R.L. Thompson, Nov 2014                                            *
    2929  !                                                                            *
    3030  !*****************************************************************************
    3131  !                                                                            *
    3232  ! Variables:                                                                 *
    33   ! i                       loop indices                                       *
    34   ! LENGTH(numpath)         length of the path names                           *
    35   ! PATH(numpath)           contains the path names                            *
    36   ! unitoh                  unit connected with OH field                       *
    3733  !                                                                            *
    38   ! -----                                                                      *
     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  !                                                                            *
    3941  !                                                                            *
    4042  !*****************************************************************************
     
    4446  use com_mod
    4547
     48
    4649  implicit none
    4750
    48   integer :: ix,jy,lev,m
     51  include 'netcdf.inc'
    4952
     53  character(len=150) :: thefile
     54  character(len=2) :: mm
     55  integer :: nid,ierr,xid,yid,zid,vid,m
     56  real, dimension(:), allocatable :: etaOH
    5057
    51   ! Read OH field and level heights
     58!  real, parameter :: gasct=8.314   ! gas constant
     59!  real, parameter :: mct=0.02894   ! kg mol-1
     60!  real, parameter :: g=9.80665     ! m s-2
     61!  real, parameter :: lrate=0.0065  ! K m-1
     62  real, parameter :: scalehgt=7000. ! scale height in metres
     63
     64  ! Read OH fields and level heights
    5265  !********************************
    5366
    54 ! write (*,*) 'reading OH'
    55   open(unitOH,file=path(1)(1:length(1))//'OH_7lev_agl.dat', &
    56        status='old',form='UNFORMATTED', err=998)
    5767  do m=1,12
    58     do lev=1,maxzOH
    59       do ix=0,maxxOH-1
    60   !      do 10 jy=0,maxyOH-1
    61           read(unitOH) (OH_field(m,ix,jy,lev),jy=0,maxyOH-1)
    62   !      if ((ix.eq.20).and.(lev.eq.1)) then
    63   !          write(*,*) 'reading: ', m, OH_field(m,ix,20,lev)
    64   !      endif
    65       end do
    66     end do
    67   end do
    68   close(unitOH)
     68 
     69    ! open netcdf file
     70    write(mm,fmt='(i2.2)') m
     71    thefile=trim(path(1))//'OH_FIELDS/'//'geos-chem.OH.2005'//mm//'01.nc'
     72    ierr=nf_open(trim(thefile),NF_NOWRITE,nid)
     73    if(ierr.ne.0) then
     74      write(*,*) nf_strerror(ierr)
     75      stop
     76    endif
    6977
    70   do lev=1,7
    71     OH_field_height(lev)=1000+real(lev-1)*2.*1000.
    72   end do
     78    ! inquire about variables
     79    ierr=nf_inq_dimid(nid,'Lon-000',xid)
     80    if(ierr.ne.0) then
     81      write(*,*) nf_strerror(ierr)
     82      stop
     83    endif
     84    ierr=nf_inq_dimid(nid,'Lat-000',yid)
     85    if(ierr.ne.0) then
     86      write(*,*) nf_strerror(ierr)
     87      stop
     88    endif
     89    ierr=nf_inq_dimid(nid,'Alt-000',zid)
     90    if(ierr.ne.0) then
     91      write(*,*) nf_strerror(ierr)
     92      stop
     93    endif
    7394
    74 !  write (*,*) 'OH read'
     95    if(m.eq.1) then
     96
     97      ! read dimension sizes
     98      ierr=nf_inq_dimlen(nid,xid,nxOH)
     99      if(ierr.ne.0) then
     100        write(*,*) nf_strerror(ierr)
     101        stop
     102      endif
     103      ierr=nf_inq_dimlen(nid,yid,nyOH)
     104      if(ierr.ne.0) then
     105        write(*,*) nf_strerror(ierr)
     106        stop
     107      endif
     108      ierr=nf_inq_dimlen(nid,zid,nzOH)
     109      if(ierr.ne.0) then
     110        write(*,*) nf_strerror(ierr)
     111        stop
     112      endif 
     113
     114      ! allocate variables
     115      allocate(lonOH(nxOH))
     116      allocate(latOH(nyOH))
     117      allocate(etaOH(nzOH))
     118      allocate(altOH(nzOH))
     119      allocate(OH_field(nxOH,nyOH,nzOH,12))
     120      allocate(OH_hourly(nxOH,nyOH,nzOH,2))
     121
     122      ! read dimension variables
     123      ierr=nf_inq_varid(nid,'LON',xid)
     124      ierr=nf_get_var_real(nid,xid,lonOH)
     125      if(ierr.ne.0) then
     126        write(*,*) nf_strerror(ierr)
     127        stop
     128      endif
     129      ierr=nf_inq_varid(nid,'LAT',yid)
     130      ierr=nf_get_var_real(nid,yid,latOH)
     131      if(ierr.ne.0) then
     132        write(*,*) nf_strerror(ierr)
     133        stop
     134      endif
     135      ierr=nf_inq_varid(nid,'ETAC',zid)
     136      ierr=nf_get_var_real(nid,zid,etaOH)
     137      if(ierr.ne.0) then
     138        write(*,*) nf_strerror(ierr)
     139        stop
     140      endif
     141
     142      ! convert eta-level to altitude (assume surface pressure of 1010 hPa)
     143      altOH=log(1010./(etaOH*1010.))*scalehgt
     144
     145    endif ! m.eq.1
     146
     147    ! read OH_field
     148    ierr=nf_inq_varid(nid,'CHEM-L_S__OH',vid)
     149    ierr=nf_get_var_real(nid,vid,OH_field(:,:,:,m))
     150    if(ierr.ne.0) then
     151      write(*,*) nf_strerror(ierr)
     152      stop
     153    endif
     154
     155    ierr=nf_close(nid)
     156
     157  end do
     158 
     159  deallocate(etaOH)
     160
     161  ! Read J(O1D) photolysis rates
     162  !******************************** 
     163
     164  ! open netcdf file
     165  thefile=trim(path(1))//'OH_FIELDS/jrate_average.nc'
     166  ierr=nf_open(trim(thefile),NF_NOWRITE,nid)
     167  if(ierr.ne.0) then
     168    write(*,*) nf_strerror(ierr)
     169    stop
     170  endif
     171
     172  ! read dimension variables
     173  ierr=nf_inq_varid(nid,'longitude',xid)
     174  ierr=nf_get_var_real(nid,xid,lonjr)
     175  if(ierr.ne.0) then
     176    write(*,*) nf_strerror(ierr)
     177    stop
     178  endif
     179  ierr=nf_inq_varid(nid,'latitude',yid)
     180  ierr=nf_get_var_real(nid,yid,latjr)
     181  if(ierr.ne.0) then
     182    write(*,*) nf_strerror(ierr)
     183    stop
     184  endif
     185
     186  ! read jrate_average
     187  ierr=nf_inq_varid(nid,'jrate',vid)
     188  ierr=nf_get_var_real(nid,vid,jrate_average)
     189  if(ierr.ne.0) then
     190    write(*,*) nf_strerror(ierr)
     191    stop
     192  endif
     193
     194  ierr=nf_close(nid)
     195
    75196  return
    76197
    77   ! Issue error messages
    78   !*********************
     198end subroutine readOHfield
    79199
    80 998   write(*,*) ' #### FLEXPART ERROR! FILE CONTAINING          ####'
    81   write(*,*) ' #### OH FIELD DOES NOT EXIST                  ####'
    82   stop
    83 
    84 end subroutine readohfield
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG