Changeset 4138764 in flexpart.git for src/netcdf_output_mod.f90


Ignore:
Timestamp:
Apr 7, 2021, 8:45:57 AM (3 years ago)
Author:
Sabine <sabine.eckhardt@…>
Branches:
dev
Children:
1228ef7
Parents:
03adec6 (diff), 759df5f (diff)
Note: this is a merge changeset, the changes displayed below correspond to the merge itself.
Use the (diff) links above to see all the changes relative to each parent.
Message:

Merge remote-tracking branch 'refs/remotes/origin/dev' into dev

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/netcdf_output_mod.f90

    ra7167e4 r4138764  
     1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
     2! SPDX-License-Identifier: GPL-3.0-or-later
     3
    14  !*****************************************************************************
    25  !                                                                            *
     
    3336  use outg_mod,  only: outheight,oroout,densityoutgrid,factor3d,volume,&
    3437                       wetgrid,wetgridsigma,drygrid,drygridsigma,grid,gridsigma,&
    35                        area,arean,volumen, orooutn, areaeast, areanorth
     38                       area,arean,volumen, orooutn, areaeast, areanorth, p0out, t0out
    3639  use par_mod,   only: dep_prec, sp, dp, maxspec, maxreceptor, nclassunc,&
    37                        unitoutrecept,unitoutreceptppt, nxmax,unittmp
     40                       unitoutrecept,unitoutreceptppt, nxmax,unittmp, &
     41                       write_p0t0
    3842  use com_mod,   only: path,length,ldirect,bdate,ibdate,ibtime,iedate,ietime, &
    3943                       loutstep,loutaver,loutsample,outlon0,outlat0,&
     
    5458                       ioutputforeachrelease, iflux, mdomainfill, mquasilag, &
    5559                       nested_output, ipout, surf_only, linit_cond, &
    56                        flexversion,mpi_mode,DRYBKDEP,WETBKDEP
     60                       flexversion,mpi_mode,DRYBKDEP,WETBKDEP, ps, tt2
    5761
    5862  use mean_mod
     
    7882  integer, dimension(maxspec) :: specID,specIDppt, wdspecID,ddspecID
    7983  integer, dimension(maxspec) :: specIDn,specIDnppt, wdspecIDn,ddspecIDn
     84  integer :: psID, tt2ID
    8085  integer                     :: timeID, timeIDn
    8186  integer, dimension(6)       :: dimids, dimidsn
     
    177182     call nf90_err(nf90_put_att(ncid, nf90_global, 'dyout', dyout))
    178183  endif
    179 !       vertical levels stored in grid structure
     184!   vertical levels stored in grid structure
    180185
    181186  ! COMMAND file settings
     
    385390  if (write_area) call nf90_err(nf90_def_var(ncid, 'area', nf90_float, &
    386391       &(/ lonDimID, latDimID /), areaID))
     392
     393    ! surfarce pressure / temperature
     394    if (write_p0t0) then
     395       call nf90_err(nf90_def_var(ncid, 'pressure', nf90_float, &
     396            &(/ lonDimID, latDimID, timeDimID /), psID))
     397       call nf90_err(nf90_def_var(ncid, 'temperature', nf90_float, &
     398            &(/ lonDimID, latDimID, timeDimID /), tt2ID))
     399    end if
    387400
    388401
     
    758771  ! real(sp)            :: wetgridtotal,wetgridsigmatotal
    759772  ! real(sp)            :: drygridtotal,drygridsigmatotal
     773    real :: ddx,ddy,p0h,t0h,p1,p2,p3,p4,rddx,rddy,xlon,xlat,ylat,xtn,ytn
     774    integer :: i1,ixp,j1,jyp,j
    760775
    761776  real, parameter     :: weightair=28.97
     
    10381053  end do
    10391054
     1055
     1056    if (write_p0t0) then
     1057       ! Loop over all output grid cells
     1058       !********************************
     1059
     1060       do jjy=0,numygrid-1
     1061          do iix=0,numxgrid-1
     1062             p0h=0.
     1063             t0h=0.
     1064
     1065             ! Take 100 samples of the topography in every grid cell
     1066             !******************************************************
     1067
     1068             do j1=1,10
     1069                ylat=outlat0+(real(jjy)+real(j1)/10.-0.05)*dyout
     1070                yl=(ylat-ylat0)/dy
     1071                do i1=1,10
     1072                   xlon=outlon0+(real(iix)+real(i1)/10.-0.05)*dxout
     1073                   xl=(xlon-xlon0)/dx
     1074
     1075                   ! Determine the nest we are in
     1076                   !*****************************
     1077
     1078                   ngrid=0
     1079                   do j=numbnests,1,-1
     1080                      if ((xl.gt.xln(j)+eps).and.(xl.lt.xrn(j)-eps).and. &
     1081                           (yl.gt.yln(j)+eps).and.(yl.lt.yrn(j)-eps)) then
     1082                         ngrid=j
     1083                         goto 43
     1084                      endif
     1085                   end do
     108643                 continue
     1087
     1088                   ! Determine (nested) grid coordinates and auxiliary parameters used for interpolation
     1089                   !*****************************************************************************
     1090
     1091                   if (ngrid.gt.0) then
     1092                      xtn=(xl-xln(ngrid))*xresoln(ngrid)
     1093                      ytn=(yl-yln(ngrid))*yresoln(ngrid)
     1094                      ix=int(xtn)
     1095                      jy=int(ytn)
     1096                      ddy=ytn-real(jy)
     1097                      ddx=xtn-real(ix)
     1098                   else
     1099                      ix=int(xl)
     1100                      jy=int(yl)
     1101                      ddy=yl-real(jy)
     1102                      ddx=xl-real(ix)
     1103                   endif
     1104                   ixp=ix+1
     1105                   jyp=jy+1
     1106                   rddx=1.-ddx
     1107                   rddy=1.-ddy
     1108                   p1=rddx*rddy
     1109                   p2=ddx*rddy
     1110                   p3=rddx*ddy
     1111                   p4=ddx*ddy
     1112
     1113                   p0h=p0h+p1*ps(ix ,jy,1,memind(1)) &
     1114                        + p2*ps(ixp,jy,1,memind(1)) &
     1115                        + p3*ps(ix ,jyp,1,memind(1)) &
     1116                        + p4*ps(ixp,jyp,1,memind(1))
     1117                   t0h=t0h+p1*tt2(ix ,jy,1,memind(1)) &
     1118                        + p2*tt2(ixp,jy,1,memind(1)) &
     1119                        + p3*tt2(ix ,jyp,1,memind(1)) &
     1120                        + p4*tt2(ixp,jyp,1,memind(1))
     1121                end do
     1122             end do
     1123
     1124             ! Divide by the number of samples taken
     1125             !**************************************
     1126             p0out(iix,jjy)=p0h/100.
     1127             t0out(iix,jjy)=t0h/100.
     1128          end do
     1129       end do
     1130
     1131       call nf90_err(nf90_put_var(ncid, psID, p0out, (/ 1,1,tpointer /), (/ numxgrid,numygrid,1 /)))
     1132       call nf90_err(nf90_put_var(ncid, tt2ID, t0out,(/ 1,1,tpointer /), (/ numxgrid,numygrid,1 /)))
     1133    end if
     1134
     1135
    10401136  ! Close netCDF file
    10411137  !**************************
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG