Changes in src/readOHfield.f90 [d7aab4b:3f149cc] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/readOHfield.f90

    rd7aab4b r3f149cc  
    2222subroutine readOHfield
    2323
    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   !*****************************************************************************
     24!*****************************************************************************
     25!                                                                            *
     26! Reads the OH field into memory                                             *
     27!                                                                            *
     28! AUTHOR: R.L. Thompson, Nov 2014                                            *
     29!                                                                            *
     30! UPDATES:                                                                   *
     31!   03/2018 SEC: Converted original netCDF files to binary format            *
     32!*****************************************************************************
     33!                                                                            *
     34! Variables:                                                                 *
     35!                                                                            *
     36! path(numpath)              contains the path names                         *
     37! lonOH(nxOH)                longitude of OH fields                          *
     38! latOH(nyOH)                latitude of OH fields                           *
     39! altOH(nzOH)                altitude of OH fields                           *
     40! etaOH(nzOH)                eta-levels of OH fields                         *
     41! OH_field(nxOH,nyOH,nzOH,m) OH concentration (molecules/cm3)                *
     42!                                                                            *
     43!                                                                            *
     44!*****************************************************************************
    4345
    4446  use oh_mod
     
    4850  implicit none
    4951
    50   include 'netcdf.inc'
    51 
    52   character(len=150) :: thefile
    53   character(len=2) :: mm
    54   integer :: nid,ierr,xid,yid,zid,vid,m
     52  integer :: i,j,k,l,ierr
    5553  real, dimension(:), allocatable :: etaOH
    5654
     
    6159  real, parameter :: scalehgt=7000. ! scale height in metres
    6260
    63   ! Read OH fields and level heights
    64   !********************************
    6561
    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     thefile=trim(ohfields_path)//'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 (*,*) 'The OH field at: '//thefile// ' could not be opened'
    75       write (*,*) 'please copy the OH fields there, or change the path in the'
    76       write (*,*) 'COMMAND namelist!'
    77       write(*,*) nf_strerror(ierr)
    78       stop
    79     endif
     62  open(unitOH,file=trim(ohfields_path) &
     63       //'OH_FIELDS/OH_variables.bin',status='old', &
     64       form='UNFORMATTED', iostat=ierr, convert='little_endian')
    8065
    81     ! inquire about variables
    82     ierr=nf_inq_dimid(nid,'Lon-000',xid)
    83     if(ierr.ne.0) then
    84       write(*,*) nf_strerror(ierr)
    85       stop
    86     endif
    87     ierr=nf_inq_dimid(nid,'Lat-000',yid)
    88     if(ierr.ne.0) then
    89       write(*,*) nf_strerror(ierr)
    90       stop
    91     endif
    92     ierr=nf_inq_dimid(nid,'Alt-000',zid)
    93     if(ierr.ne.0) then
    94       write(*,*) nf_strerror(ierr)
    95       stop
    96     endif
    97 
    98     if(m.eq.1) then
    99 
    100       ! read dimension sizes
    101       ierr=nf_inq_dimlen(nid,xid,nxOH)
    102       if(ierr.ne.0) then
    103         write(*,*) nf_strerror(ierr)
    104         stop
    105       endif
    106       ierr=nf_inq_dimlen(nid,yid,nyOH)
    107       if(ierr.ne.0) then
    108         write(*,*) nf_strerror(ierr)
    109         stop
    110       endif
    111       ierr=nf_inq_dimlen(nid,zid,nzOH)
    112       if(ierr.ne.0) then
    113         write(*,*) nf_strerror(ierr)
    114         stop
    115       endif 
    116 
    117       ! allocate variables
    118       allocate(lonOH(nxOH))
    119       allocate(latOH(nyOH))
    120       allocate(etaOH(nzOH))
    121       allocate(altOH(nzOH))
    122       allocate(OH_field(nxOH,nyOH,nzOH,12))
    123       allocate(OH_hourly(nxOH,nyOH,nzOH,2))
    124 
    125       ! read dimension variables
    126       ierr=nf_inq_varid(nid,'LON',xid)
    127       ierr=nf_get_var_real(nid,xid,lonOH)
    128       if(ierr.ne.0) then
    129         write(*,*) nf_strerror(ierr)
    130         stop
    131       endif
    132       ierr=nf_inq_varid(nid,'LAT',yid)
    133       ierr=nf_get_var_real(nid,yid,latOH)
    134       if(ierr.ne.0) then
    135         write(*,*) nf_strerror(ierr)
    136         stop
    137       endif
    138       ierr=nf_inq_varid(nid,'ETAC',zid)
    139       ierr=nf_get_var_real(nid,zid,etaOH)
    140       if(ierr.ne.0) then
    141         write(*,*) nf_strerror(ierr)
    142         stop
    143       endif
    144 
    145       ! convert eta-level to altitude (assume surface pressure of 1010 hPa)
    146       altOH=log(1010./(etaOH*1010.))*scalehgt
    147 
    148     endif ! m.eq.1
    149 
    150     ! read OH_field
    151     ierr=nf_inq_varid(nid,'CHEM-L_S__OH',vid)
    152     ierr=nf_get_var_real(nid,vid,OH_field(:,:,:,m))
    153     if(ierr.ne.0) then
    154       write(*,*) nf_strerror(ierr)
    155       stop
    156     endif
    157 
    158     ierr=nf_close(nid)
    159 
    160   end do
    161  
    162   deallocate(etaOH)
    163 
    164   ! Read J(O1D) photolysis rates
    165   !******************************** 
    166 
    167   ! open netcdf file
    168 !  thefile=trim(path(1))//'OH_FIELDS/jrate_average.nc'
    169   thefile=trim(ohfields_path)//'OH_FIELDS/jrate_average.nc'
    170   ierr=nf_open(trim(thefile),NF_NOWRITE,nid)
    17166  if(ierr.ne.0) then
    172     write(*,*) nf_strerror(ierr)
     67    write(*,*) 'Cannot read binary OH fields in ',trim(ohfields_path)//'OH_FIELDS/OH_variables.bin'
    17368    stop
    17469  endif
    17570
    176   ! read dimension variables
    177   ierr=nf_inq_varid(nid,'longitude',xid)
    178   ierr=nf_get_var_real(nid,xid,lonjr)
    179   if(ierr.ne.0) then
    180     write(*,*) nf_strerror(ierr)
    181     stop
    182   endif
    183   ierr=nf_inq_varid(nid,'latitude',yid)
    184   ierr=nf_get_var_real(nid,yid,latjr)
    185   if(ierr.ne.0) then
    186     write(*,*) nf_strerror(ierr)
    187     stop
    188   endif
     71  read(unitOH) nxOH
     72  read(unitOH) nyOH
     73  read(unitOH) nzOH
     74  write(*,*) nxOH,nyOH,nzOH
    18975
    190   ! read jrate_average
    191   ierr=nf_inq_varid(nid,'jrate',vid)
    192   ierr=nf_get_var_real(nid,vid,jrate_average)
    193   if(ierr.ne.0) then
    194     write(*,*) nf_strerror(ierr)
    195     stop
    196   endif
     76! allocate variables
     77  allocate(lonOH(nxOH))
     78  allocate(latOH(nyOH))
     79  allocate(etaOH(nzOH))
     80  allocate(altOH(nzOH))
     81  allocate(OH_field(nxOH,nyOH,nzOH,12))
     82  allocate(OH_hourly(nxOH,nyOH,nzOH,2))
    19783
    198   ierr=nf_close(nid)
     84  read(unitOH) (lonjr(i),i=1,360)
     85  read(unitOH) (latjr(i),i=1,180)
     86  read(unitOH) (((jrate_average(i,j,k),i=1,360),j=1,180),k=1,12)
     87  read(unitOH) (lonOH(i),i=1,nxOH)
     88  read(unitOH) (latOH(i),i=1,nyOH)
     89  read(unitOH) (lonOH(i),i=1,nxOH)
    19990
    200   return
     91  read(unitOH) (altOH(i),i=1,nzOH)
     92  read(unitOH) ((((OH_field(i,j,k,l),i=1,nxOH),j=1,nyOH),k=1,nzOH),l=1,12)
     93  read(unitOH) ((((OH_hourly(i,j,k,l),i=1,nxOH),j=1,nyOH),k=1,nzOH),l=1,2)
    20194
    20295end subroutine readOHfield
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG