Changes in / [148cff2:2794246] in flexpart.git


Ignore:
Location:
src
Files:
3 deleted
17 edited

Legend:

Unmodified
Added
Removed
  • src/FLEXPART.f90

    r2eefa58 r0a94e13  
    137137    write(*,*) 'call readpaths'
    138138  endif
    139   call readpaths
     139  call readpaths(pathfile)
    140140 
    141141  if (verbosity.gt.1) then !show clock info
     
    452452  endif
    453453
    454   if (verbosity.gt.0) write (*,*) 'timemanager> call wetdepo'
    455454  call timemanager(metdata_format)
    456  
    457455
    458456  if (verbosity.gt.0) then
     
    469467      endif
    470468    end do
     469    write (*,*) 'timemanager> call wetdepo'
    471470  endif
    472471 
  • src/FLEXPART_MPI.f90

    r2eefa58 r0c8c7f2  
    146146    write(*,*) 'call readpaths'
    147147  endif
    148   call readpaths
     148  call readpaths(pathfile)
    149149 
    150150  if (verbosity.gt.1) then !show clock info
  • src/com_mod.f90

    r2eefa58 r0a94e13  
    124124  ! lnetcdfout   1 for netcdf grid output, 0 if not. Set in COMMAND (namelist input)
    125125
    126   integer :: linversionout
    127   ! linversionout 1 for one grid_time output file for each release containing all timesteps
    128 
    129126  integer :: nageclass,lage(maxageclass)
    130127
     
    179176  real :: ri(5,numclass),rac(5,numclass),rcl(maxspec,5,numclass)
    180177  real :: rgs(maxspec,5,numclass),rlu(maxspec,5,numclass)
    181   real :: rm(maxspec),dryvel(maxspec),kao(maxspec)
     178  real :: rm(maxspec),dryvel(maxspec)
    182179  real :: ohcconst(maxspec),ohdconst(maxspec),ohnconst(maxspec)
    183180
     
    364361  real :: ciwc(0:nxmax-1,0:nymax-1,nzmax,numwfmem)=0.0 !ice      [kg/kg]
    365362  real :: clw(0:nxmax-1,0:nymax-1,nzmax,numwfmem)=0.0  !combined [m3/m3]
    366 ! RLT add pressure and dry air density
    367   real :: prs(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
    368   real :: rho_dry(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     363
    369364  real :: pv(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
    370365  real :: rho(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     
    388383  ! uupol,vvpol [m/s]    wind components in polar stereographic projection
    389384  ! tt [K]               temperature data
    390   ! prs                  air pressure
    391385  ! qv                   specific humidity data
    392386  ! pv (pvu)             potential vorticity
  • src/concoutput.f90

    r2eefa58 r20963b1  
    7272  real :: sp_fact
    7373  real :: outnum,densityoutrecept(maxreceptor),xl,yl
    74 ! RLT
    75   real :: densitydryrecept(maxreceptor)
    76   real :: factor_dryrecept(maxreceptor)
    7774
    7875!real densityoutgrid(0:numxgrid-1,0:numygrid-1,numzgrid),
     
    109106  character(LEN=8),save :: file_stat='REPLACE'
    110107  logical :: ldates_file
    111   logical :: lexist
    112108  integer :: ierr
    113109  character(LEN=100) :: dates_char
     
    207203        densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,mind)*dz1+ &
    208204             rho(iix,jjy,kzz-1,mind)*dz2)/dz
    209 ! RLT
    210         densitydrygrid(ix,jy,kz)=(rho_dry(iix,jjy,kzz,mind)*dz1+ &
    211              rho_dry(iix,jjy,kzz-1,mind)*dz2)/dz 
    212205      end do
    213206    end do
     
    221214!densityoutrecept(i)=rho(iix,jjy,1,2)
    222215    densityoutrecept(i)=rho(iix,jjy,1,mind)
    223 ! RLT
    224     densitydryrecept(i)=rho_dry(iix,jjy,1,mind)
    225216  end do
    226217
    227 ! RLT
    228 ! conversion factor for output relative to dry air
    229   factor_drygrid=densityoutgrid/densitydrygrid
    230   factor_dryrecept=densityoutrecept/densitydryrecept
    231218
    232219! Output is different for forward and backward simulations
     
    366353! Concentration output
    367354!*********************
    368         if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5)) then
     355        if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5).or.(iout.eq.6)) then
    369356
    370357! Wet deposition
     
    627614  end do
    628615
    629 ! RLT Aug 2017
    630 ! Write out conversion factor for dry air
    631   inquire(file=path(2)(1:length(2))//'factor_drygrid',exist=lexist)
    632   if (lexist) then
    633     ! open and append
    634     open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid',form='unformatted',&
    635             status='old',action='write',access='append')
    636   else
    637     ! create new
    638     open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid',form='unformatted',&
    639             status='new',action='write')
    640   endif
    641   sp_count_i=0
    642   sp_count_r=0
    643   sp_fact=-1.
    644   sp_zer=.true.
    645   do kz=1,numzgrid
    646     do jy=0,numygrid-1
    647       do ix=0,numxgrid-1
    648         if (factor_drygrid(ix,jy,kz).gt.(1.+smallnum).or.factor_drygrid(ix,jy,kz).lt.(1.-smallnum)) then
    649           if (sp_zer.eqv..true.) then ! first value not equal to one
    650             sp_count_i=sp_count_i+1
    651             sparse_dump_i(sp_count_i)= &
    652                   ix+jy*numxgrid+kz*numxgrid*numygrid
    653             sp_zer=.false.
    654             sp_fact=sp_fact*(-1.)
    655           endif
    656           sp_count_r=sp_count_r+1
    657           sparse_dump_r(sp_count_r)= &
    658                sp_fact*factor_drygrid(ix,jy,kz)
    659         else ! factor is one
    660           sp_zer=.true.
    661         endif
    662       end do
    663     end do
    664   end do
    665   write(unitoutfactor) sp_count_i
    666   write(unitoutfactor) (sparse_dump_i(i),i=1,sp_count_i)
    667   write(unitoutfactor) sp_count_r
    668   write(unitoutfactor) (sparse_dump_r(i),i=1,sp_count_r)
    669   close(unitoutfactor)
    670 
    671 
    672616  if (gridtotal.gt.0.) gridtotalunc=gridsigmatotal/gridtotal
    673617  if (wetgridtotal.gt.0.) wetgridtotalunc=wetgridsigmatotal/ &
     
    696640  endif
    697641
    698 ! RLT Aug 2017
    699 ! Write out conversion factor for dry air
    700   if (numreceptor.gt.0) then
    701     inquire(file=path(2)(1:length(2))//'factor_dryreceptor',exist=lexist)
    702      if (lexist) then
    703      ! open and append
    704       open(unitoutfactor,file=path(2)(1:length(2))//'factor_dryreceptor',form='unformatted',&
    705               status='old',action='write',access='append')
    706     else
    707       ! create new
    708       open(unitoutfactor,file=path(2)(1:length(2))//'factor_dryreceptor',form='unformatted',&
    709               status='new',action='write')
    710     endif
    711     write(unitoutfactor) itime
    712     write(unitoutfactor) (factor_dryrecept(i),i=1,numreceptor)
    713     close(unitoutfactor)
    714   endif
     642
    715643
    716644! Reinitialization of grid
  • src/concoutput_mpi.f90

    r6741557 r20963b1  
    364364! Concentration output
    365365!*********************
    366         if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5)) then
     366        if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5).or.(iout.eq.6)) then
    367367
    368368! Wet deposition
  • src/concoutput_nest.f90

    r2eefa58 r7d02c2f  
    7070  real :: sp_fact
    7171  real :: outnum,densityoutrecept(maxreceptor),xl,yl
    72 ! RLT
    73   real :: densitydryrecept(maxreceptor)
    74   real :: factor_dryrecept(maxreceptor)
    7572
    7673  !real densityoutgrid(0:numxgrid-1,0:numygrid-1,numzgrid),
     
    9996  character :: adate*8,atime*6
    10097  character(len=3) :: anspec
    101   logical :: lexist
    10298  integer :: mind
    10399! mind        eso:added to ensure identical results between 2&3-fields versions
     
    168164        densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,mind)*dz1+ &
    169165             rho(iix,jjy,kzz-1,mind)*dz2)/dz
    170 ! RLT
    171         densitydrygrid(ix,jy,kz)=(rho_dry(iix,jjy,kzz,mind)*dz1+ &
    172              rho_dry(iix,jjy,kzz-1,mind)*dz2)/dz
    173166      end do
    174167    end do
     
    182175    !densityoutrecept(i)=rho(iix,jjy,1,2)
    183176    densityoutrecept(i)=rho(iix,jjy,1,mind)
    184 ! RLT
    185     densitydryrecept(i)=rho_dry(iix,jjy,1,mind)
    186177  end do
    187178
    188 ! RLT
    189 ! conversion factor for output relative to dry air
    190   factor_drygrid=densityoutgrid/densitydrygrid
    191   factor_dryrecept=densityoutrecept/densitydryrecept
    192179
    193180  ! Output is different for forward and backward simulations
     
    564551  end do
    565552
    566 ! RLT Aug 2017
    567 ! Write out conversion factor for dry air
    568   inquire(file=path(2)(1:length(2))//'factor_drygrid_nest',exist=lexist)
    569   if (lexist) then
    570     ! open and append
    571     open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid_nest',form='unformatted',&
    572             status='old',action='write',access='append')
    573   else
    574     ! create new
    575     open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid_nest',form='unformatted',&
    576             status='new',action='write')
    577   endif
    578   sp_count_i=0
    579   sp_count_r=0
    580   sp_fact=-1.
    581   sp_zer=.true.
    582   do kz=1,numzgrid
    583     do jy=0,numygridn-1
    584       do ix=0,numxgridn-1
    585         if (factor_drygrid(ix,jy,kz).gt.(1.+smallnum).or.factor_drygrid(ix,jy,kz).lt.(1.-smallnum)) then
    586           if (sp_zer.eqv..true.) then ! first value not equal to one
    587             sp_count_i=sp_count_i+1
    588             sparse_dump_i(sp_count_i)= &
    589                   ix+jy*numxgridn+kz*numxgridn*numygridn
    590             sp_zer=.false.
    591             sp_fact=sp_fact*(-1.)
    592           endif
    593           sp_count_r=sp_count_r+1
    594           sparse_dump_r(sp_count_r)= &
    595                sp_fact*factor_drygrid(ix,jy,kz)
    596         else ! factor is one
    597           sp_zer=.true.
    598         endif
    599       end do
    600     end do
    601   end do
    602   write(unitoutfactor) sp_count_i
    603   write(unitoutfactor) (sparse_dump_i(i),i=1,sp_count_i)
    604   write(unitoutfactor) sp_count_r
    605   write(unitoutfactor) (sparse_dump_r(i),i=1,sp_count_r)
    606   close(unitoutfactor)
    607553
    608554
  • src/concoutput_surf.f90

    r2eefa58 r16b61a5  
    7272  real :: sp_fact
    7373  real :: outnum,densityoutrecept(maxreceptor),xl,yl
    74 ! RLT
    75   real :: densitydryrecept(maxreceptor)
    76   real :: factor_dryrecept(maxreceptor)
    7774
    7875!real densityoutgrid(0:numxgrid-1,0:numygrid-1,numzgrid),
     
    104101  character :: adate*8,atime*6
    105102  character(len=3) :: anspec
    106   logical :: lexist
    107103
    108104
     
    184180        densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,2)*dz1+ &
    185181             rho(iix,jjy,kzz-1,2)*dz2)/dz
    186 ! RLT
    187         densitydrygrid(ix,jy,kz)=(rho_dry(iix,jjy,kzz,2)*dz1+ &
    188              rho_dry(iix,jjy,kzz-1,2)*dz2)/dz
    189182      end do
    190183    end do
     
    197190    jjy=max(min(nint(yl),nymin1),0)
    198191    densityoutrecept(i)=rho(iix,jjy,1,2)
    199 ! RLT
    200     densitydryrecept(i)=rho_dry(iix,jjy,1,2)
    201192  end do
    202193
    203 ! RLT
    204 ! conversion factor for output relative to dry air
    205   factor_drygrid=densityoutgrid/densitydrygrid
    206   factor_dryrecept=densityoutrecept/densitydryrecept
    207194
    208195! Output is different for forward and backward simulations
     
    609596  end do
    610597
    611 ! RLT Aug 2017
    612 ! Write out conversion factor for dry air
    613   inquire(file=path(2)(1:length(2))//'factor_drygrid',exist=lexist)
    614   if (lexist) then
    615     ! open and append
    616     open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid',form='unformatted',&
    617             status='old',action='write',access='append')
    618   else
    619     ! create new
    620     open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid',form='unformatted',&
    621             status='new',action='write')
    622   endif
    623   sp_count_i=0
    624   sp_count_r=0
    625   sp_fact=-1.
    626   sp_zer=.true.
    627   do kz=1,1
    628     do jy=0,numygrid-1
    629       do ix=0,numxgrid-1
    630         if (factor_drygrid(ix,jy,kz).gt.(1.+smallnum).or.factor_drygrid(ix,jy,kz).lt.(1.-smallnum)) then
    631           if (sp_zer.eqv..true.) then ! first value not equal to one
    632             sp_count_i=sp_count_i+1
    633             sparse_dump_i(sp_count_i)= &
    634                   ix+jy*numxgrid+kz*numxgrid*numygrid
    635             sp_zer=.false.
    636             sp_fact=sp_fact*(-1.)
    637           endif
    638           sp_count_r=sp_count_r+1
    639           sparse_dump_r(sp_count_r)= &
    640                sp_fact*factor_drygrid(ix,jy,kz)
    641         else ! factor is one
    642           sp_zer=.true.
    643         endif
    644       end do
    645     end do
    646   end do
    647   write(unitoutfactor) sp_count_i
    648   write(unitoutfactor) (sparse_dump_i(i),i=1,sp_count_i)
    649   write(unitoutfactor) sp_count_r
    650   write(unitoutfactor) (sparse_dump_r(i),i=1,sp_count_r)
    651   close(unitoutfactor)
    652 
    653 
    654598  if (gridtotal.gt.0.) gridtotalunc=gridsigmatotal/gridtotal
    655599  if (wetgridtotal.gt.0.) wetgridtotalunc=wetgridsigmatotal/ &
     
    678622  endif
    679623
    680 ! RLT Aug 2017
    681 ! Write out conversion factor for dry air
    682   if (numreceptor.gt.0) then
    683     inquire(file=path(2)(1:length(2))//'factor_dryreceptor',exist=lexist)
    684      if (lexist) then
    685      ! open and append
    686       open(unitoutfactor,file=path(2)(1:length(2))//'factor_dryreceptor',form='unformatted',&
    687               status='old',action='write',access='append')
    688     else
    689       ! create new
    690       open(unitoutfactor,file=path(2)(1:length(2))//'factor_dryreceptor',form='unformatted',&
    691               status='new',action='write')
    692     endif
    693     write(unitoutfactor) itime
    694     write(unitoutfactor) (factor_dryrecept(i),i=1,numreceptor)
    695     close(unitoutfactor)
    696   endif
     624
    697625
    698626! Reinitialization of grid
  • src/concoutput_surf_nest.f90

    r2eefa58 r6a678e3  
    7070  real :: sp_fact
    7171  real :: outnum,densityoutrecept(maxreceptor),xl,yl
    72 ! RLT
    73   real :: densitydryrecept(maxreceptor)
    74   real :: factor_dryrecept(maxreceptor)
    7572
    7673  !real densityoutgrid(0:numxgrid-1,0:numygrid-1,numzgrid),
     
    9996  character :: adate*8,atime*6
    10097  character(len=3) :: anspec
    101   logical :: lexist
     98
    10299
    103100  ! Determine current calendar date, needed for the file name
     
    162159        densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,2)*dz1+ &
    163160             rho(iix,jjy,kzz-1,2)*dz2)/dz
    164 ! RLT
    165         densitydrygrid(ix,jy,kz)=(rho_dry(iix,jjy,kzz,2)*dz1+ &
    166              rho_dry(iix,jjy,kzz-1,2)*dz2)/dz
    167161      end do
    168162    end do
     
    175169      jjy=max(min(nint(yl),nymin1),0)
    176170      densityoutrecept(i)=rho(iix,jjy,1,2)
    177 ! RLT
    178     densitydryrecept(i)=rho_dry(iix,jjy,1,2)
    179171    end do
    180172
    181 ! RLT
    182 ! conversion factor for output relative to dry air
    183   factor_drygrid=densityoutgrid/densitydrygrid
    184   factor_dryrecept=densityoutrecept/densitydryrecept
    185173
    186174  ! Output is different for forward and backward simulations
     
    329317         write(unitoutgrid) sp_count_r
    330318         write(unitoutgrid) (sparse_dump_r(i),i=1,sp_count_r)
    331 !         write(unitoutgrid) sp_count_r
    332 !         write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
     319         write(unitoutgrid) sp_count_r
     320         write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
    333321
    334322  ! Dry deposition
     
    366354         write(unitoutgrid) sp_count_r
    367355         write(unitoutgrid) (sparse_dump_r(i),i=1,sp_count_r)
    368 !         write(unitoutgrid) sp_count_r
    369 !         write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
     356         write(unitoutgrid) sp_count_r
     357         write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
    370358
    371359
     
    411399         write(unitoutgrid) sp_count_r
    412400         write(unitoutgrid) (sparse_dump_r(i),i=1,sp_count_r)
    413 !         write(unitoutgrid) sp_count_r
    414 !         write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
     401         write(unitoutgrid) sp_count_r
     402         write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
    415403         else
    416404
     
    452440         write(unitoutgrid) sp_count_r
    453441         write(unitoutgrid) (sparse_dump_r(i),i=1,sp_count_r)
    454 !         write(unitoutgrid) sp_count_r
    455 !         write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
     442         write(unitoutgrid) sp_count_r
     443         write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
    456444         endif ! surf_only
    457445
     
    499487         write(unitoutgridppt) sp_count_r
    500488         write(unitoutgridppt) (sparse_dump_r(i),i=1,sp_count_r)
    501 !         write(unitoutgridppt) sp_count_r
    502 !         write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
     489         write(unitoutgridppt) sp_count_r
     490         write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
    503491
    504492
     
    538526         write(unitoutgridppt) sp_count_r
    539527         write(unitoutgridppt) (sparse_dump_r(i),i=1,sp_count_r)
    540 !         write(unitoutgridppt) sp_count_r
    541 !         write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
     528         write(unitoutgridppt) sp_count_r
     529         write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
    542530
    543531
     
    582570         write(unitoutgridppt) sp_count_r
    583571         write(unitoutgridppt) (sparse_dump_r(i),i=1,sp_count_r)
    584 !         write(unitoutgridppt) sp_count_r
    585 !         write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
     572         write(unitoutgridppt) sp_count_r
     573         write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
    586574         else
    587575
     
    623611         write(unitoutgridppt) sp_count_r
    624612         write(unitoutgridppt) (sparse_dump_r(i),i=1,sp_count_r)
    625 !         write(unitoutgridppt) sp_count_r
    626 !         write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
     613         write(unitoutgridppt) sp_count_r
     614         write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
    627615         endif ! surf_only
    628616
     
    636624
    637625  end do
    638 
    639 ! RLT Aug 2017
    640 ! Write out conversion factor for dry air
    641   inquire(file=path(2)(1:length(2))//'factor_drygrid_nest',exist=lexist)
    642   if (lexist) then
    643     ! open and append
    644     open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid_nest',form='unformatted',&
    645             status='old',action='write',access='append')
    646   else
    647     ! create new
    648     open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid_nest',form='unformatted',&
    649             status='new',action='write')
    650   endif
    651   sp_count_i=0
    652   sp_count_r=0
    653   sp_fact=-1.
    654   sp_zer=.true.
    655   do kz=1,1
    656     do jy=0,numygridn-1
    657       do ix=0,numxgridn-1
    658         if (factor_drygrid(ix,jy,kz).gt.(1.+smallnum).or.factor_drygrid(ix,jy,kz).lt.(1.-smallnum)) then
    659           if (sp_zer.eqv..true.) then ! first value not equal to one
    660             sp_count_i=sp_count_i+1
    661             sparse_dump_i(sp_count_i)= &
    662                   ix+jy*numxgridn+kz*numxgridn*numygridn
    663             sp_zer=.false.
    664             sp_fact=sp_fact*(-1.)
    665           endif
    666           sp_count_r=sp_count_r+1
    667           sparse_dump_r(sp_count_r)= &
    668                sp_fact*factor_drygrid(ix,jy,kz)
    669         else ! factor is one
    670           sp_zer=.true.
    671         endif
    672       end do
    673     end do
    674   end do
    675   write(unitoutfactor) sp_count_i
    676   write(unitoutfactor) (sparse_dump_i(i),i=1,sp_count_i)
    677   write(unitoutfactor) sp_count_r
    678   write(unitoutfactor) (sparse_dump_r(i),i=1,sp_count_r)
    679   close(unitoutfactor)
    680626
    681627
  • src/getfields.f90

    r2eefa58 r6ecb30a  
    8787  real :: pvhn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,maxnests)
    8888  real :: wwhn(0:nxmaxn-1,0:nymaxn-1,nwzmax,maxnests)
    89 ! RLT added partial pressure water vapor
    90   real :: pwater(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
    91   integer :: kz, ix
    92   character(len=100) :: rowfmt
    9389
    9490  integer :: indmin = 1
     
    15715340  indmin=indj
    158154
    159     if (WETBKDEP) then
    160       call writeprecip(itime,memind(1))
    161     endif
     155   if (WETBKDEP) then
     156        call writeprecip(itime,memind(1))
     157   endif
    162158
    163159  else
     
    20820460  indmin=indj
    209205
    210     if (WETBKDEP) then
    211       call writeprecip(itime,memind(1))
    212     endif
    213 
    214   end if
    215 
    216   ! RLT calculate dry air density
    217   pwater=qv*prs/((r_air/r_water)*(1.-qv)+qv)
    218   rho_dry=(prs-pwater)/(r_air*tt)
    219 
    220   ! test density
    221 !  write(rowfmt,'(A,I6,A)') '(',nymax,'(E11.4,1X))'
    222 !  if(itime.eq.0) then
    223 !    open(500,file=path(2)(1:length(2))//'rho_dry.txt',status='replace',action='write')
    224 !    do kz=1,nzmax
    225 !      do ix=1,nxmax
    226 !        write(500,fmt=rowfmt) rho_dry(ix,:,kz,1)
    227 !      end do
    228 !    end do
    229 !    close(500)
    230 !    open(500,file=path(2)(1:length(2))//'rho.txt',status='replace',action='write')
    231 !    do kz=1,nzmax
    232 !      do ix=1,nxmax
    233 !        write(500,fmt=rowfmt) rho(ix,:,kz,1)
    234 !      end do
    235 !    end do
    236 !    close(500)
    237 !  endif
     206   if (WETBKDEP) then
     207        call writeprecip(itime,memind(1))
     208   endif
     209
     210  endif
    238211
    239212  lwindinterv=abs(memtime(2)-memtime(1))
  • src/makefile

    r2eefa58 r0a94e13  
    128128        redist.o                \
    129129        concoutput_surf.o       concoutput_surf_nest.o  \
    130         concoutput_inversion_nest.o     \
    131         concoutput_inversion.o \
    132130        getfields.o \
    133131        readwind_ecmwf.o
     
    202200drydepokernel_nest.o    zenithangle.o \
    203201ohreaction.o            getvdep_nests.o \
    204 initial_cond_calc.o     initial_cond_output.o initial_cond_output_inversion.o \
     202initial_cond_calc.o     initial_cond_output.o \
    205203dynamic_viscosity.o     get_settling.o  \
    206204initialize_cbl_vel.o    re_initialize_particle.o \
     
    274272conccalc_mpi.o: com_mod.o mpi_mod.o outg_mod.o par_mod.o unc_mod.o
    275273concoutput.o: com_mod.o outg_mod.o par_mod.o point_mod.o unc_mod.o mean_mod.o
    276 concoutput_inversion.o: com_mod.o outg_mod.o par_mod.o point_mod.o unc_mod.o mean_mod.o
    277274concoutput_mpi.o: com_mod.o mpi_mod.o outg_mod.o par_mod.o point_mod.o \
    278275        unc_mod.o mean_mod.o
    279276concoutput_nest.o: com_mod.o outg_mod.o par_mod.o point_mod.o unc_mod.o mean_mod.o
    280 concoutput_inversion_nest.o: com_mod.o outg_mod.o par_mod.o point_mod.o unc_mod.o mean_mod.o
    281277concoutput_nest_mpi.o: com_mod.o mpi_mod.o outg_mod.o par_mod.o point_mod.o \
    282278        unc_mod.o mean_mod.o
     
    325321initial_cond_calc.o: com_mod.o outg_mod.o par_mod.o unc_mod.o
    326322initial_cond_output.o: com_mod.o outg_mod.o par_mod.o point_mod.o unc_mod.o
    327 initial_cond_output_inversion.o: com_mod.o outg_mod.o par_mod.o point_mod.o unc_mod.o
    328323initialize.o: com_mod.o hanna_mod.o interpol_mod.o par_mod.o random_mod.o
    329324initialize_cbl_vel.o: com_mod.o par_mod.o random_mod.o
  • src/outg_mod.f90

    r2eefa58 r4c64400  
    3737  real,allocatable, dimension (:,:,:) :: areanorth
    3838  real,allocatable, dimension (:,:,:) :: densityoutgrid
    39   real,allocatable, dimension (:,:,:) :: densitydrygrid ! added RLT
    40   real,allocatable, dimension (:,:,:) :: factor_drygrid ! added RLT
    4139  real,allocatable, dimension (:,:,:) :: factor3d
    4240  real,allocatable, dimension (:,:,:) :: grid
  • src/outgrid_init.f90

    r2eefa58 rd2a5a83  
    268268    if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc'
    269269  allocate(densityoutgrid(0:max(numxgrid,numxgridn)-1, &
    270        0:max(numygrid,numygridn)-1,numzgrid),stat=stat)
    271     if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc'
    272 ! RLT
    273   allocate(densitydrygrid(0:max(numxgrid,numxgridn)-1, &
    274        0:max(numygrid,numygridn)-1,numzgrid),stat=stat)
    275     if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc'
    276   allocate(factor_drygrid(0:max(numxgrid,numxgridn)-1, &
    277270       0:max(numygrid,numygridn)-1,numzgrid),stat=stat)
    278271    if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc'
  • src/par_mod.f90

    r2eefa58 r0a94e13  
    3030!        Update 15 August 2013 IP                                              *
    3131!                                                                              *
     32!        ESO 2016:                                                             *
     33!          GFS specific parameters moved to gfs_mod.f90                        *
     34!          ECMWF specific parameters moved to ecmwf_mod.f90                    *
    3235!                                                                              *
    3336!*******************************************************************************
     
    7780  real,parameter :: pi=3.14159265, r_earth=6.371e6, r_air=287.05, ga=9.81
    7881  real,parameter :: cpa=1004.6, kappa=0.286, pi180=pi/180., vonkarman=0.4
    79   ! additional constants RLT Aug-2017
    80   real,parameter :: rgas=8.31447
    81   real,parameter :: r_water=461.495
    8282
    8383  ! pi                      number "pi"
     
    8989  ! kappa                   exponent of formula for potential temperature
    9090  ! vonkarman               von Karman constant
    91   ! rgas                    universal gas constant [J/mol/K]
    92   ! r_water                 specific gas constant for water vapor [J/kg/K]
    9391
    9492  real,parameter :: karman=0.40, href=15., convke=2.0
     
    292290  integer,parameter :: unitboundcond=89
    293291  integer,parameter :: unittmp=101
    294 ! RLT
    295   integer,parameter :: unitoutfactor=102
    296292
    297293!******************************************************
  • src/readcommand.f90

    r2eefa58 r0a94e13  
    114114  surf_only, &
    115115  cblflag, &
    116   linversionout, &
    117116  ohfields_path
    118117
     
    148147  surf_only=0
    149148  cblflag=0 ! if using old-style COMMAND file, set to 1 here to use mc cbl routine
    150   linversionout=0
    151149  ohfields_path="../../flexin/"
    152150
     
    416414  !**********************************************************************
    417415
    418   if ((iout.lt.1).or.(iout.gt.5)) then
     416  if ((iout.lt.1).or.(iout.gt.6)) then
    419417    write(*,*) ' #### FLEXPART MODEL ERROR! FILE COMMAND:     #### '
    420418    write(*,*) ' #### IOUT MUST BE 1, 2, 3, 4 OR 5 FOR        #### '
     
    476474      write(*,*) '#### FOR DOMAIN FILLING RUNS OUTPUT FOR      ####'
    477475      write(*,*) '#### EACH RELEASE IS FORBIDDEN !             ####'
    478       stop
    479   endif
    480 
    481   ! Inversion output format only for backward runs
    482   !*****************************************************************************
    483  
    484   if ((linversionout.eq.1).and.(ldirect.eq.1)) then
    485       write(*,*) '#### FLEXPART MODEL ERROR! FILE COMMAND:     ####'
    486       write(*,*) '#### INVERSION OUTPUT FORMAT ONLY FOR        ####'
    487       write(*,*) '#### BACKWARD RUNS                           ####'
    488476      stop
    489477  endif
  • src/readpaths.f90

    r2eefa58 r62e65c7  
    2020!**********************************************************************
    2121
    22 subroutine readpaths
     22subroutine readpaths !(pathfile)
    2323
    2424  !*****************************************************************************
  • src/timemanager.f90

    r2eefa58 r0a94e13  
    408408#endif
    409409            else
    410               if (linversionout.eq.1) then
    411                 call concoutput_inversion(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
    412                 if (verbosity.eq.1) then
    413                   print*,'called concoutput_inversion'
    414                   call system_clock(count_clock)
    415                   write(*,*) 'system clock',count_clock - count_clock0
    416                 endif
    417               else
    418410              call concoutput_surf(itime,outnum,gridtotalunc,wetgridtotalunc,drygridtotalunc)
    419               endif
    420411              if (verbosity.eq.1) then
    421412                print*,'called concoutput_surf '
     
    431422                call concoutput_nest(itime,outnum)
    432423              else
    433                 if(linversionout.eq.1) then
    434                   call concoutput_inversion_nest(itime,outnum)
    435                 else
    436424                call concoutput_surf_nest(itime,outnum)
    437               endif
    438425              endif
    439426            else
     
    752739  if (ipout.eq.2) call partoutput(itime)     ! dump particle positions
    753740
    754   if (linit_cond.ge.1) then
    755     if(linversionout.eq.1) then
    756       call initial_cond_output_inversion(itime)   ! dump initial cond. field
    757     else
    758       call initial_cond_output(itime)   ! dump initial cond. fielf
    759     endif
    760   endif
     741  if (linit_cond.ge.1) call initial_cond_output(itime)   ! dump initial cond. field
    761742
    762743  !close(104)
  • src/verttransform_ecmwf.f90

    r2eefa58 r0a94e13  
    8181  real,dimension(0:nxmax-1,0:nymax-1,nuvzmax) :: rhoh,uvzlev,wzlev
    8282  real,dimension(0:nxmax-1,0:nymax-1,nzmax) :: pinmconv
    83   ! RLT added pressure
    84   real,dimension(0:nxmax-1,0:nymax-1,nuvzmax) :: prsh
    8583  real,dimension(0:nxmax-1,0:nymax-1) ::  tvold,pold,pint,tv
    8684  real,dimension(0:nymax-1) :: cosf
     
    220218!*************************
    221219
     220
    222221  do jy=0,nymin1
    223222    do ix=0,nxmin1
     
    230229  wzlev(:,:,1)=0.
    231230  rhoh(:,:,1)=pold/(r_air*tvold)
    232   ! RLT add pressure
    233   prsh(:,:,1)=ps(:,:,1,n)
    234231
    235232
     
    239236  do kz=2,nuvz
    240237    pint=akz(kz)+bkz(kz)*ps(:,:,1,n)
    241     ! RLT add pressure
    242     prsh(:,:,kz)=pint
    243238    tv=tth(:,:,kz,n)*(1.+0.608*qvh(:,:,kz,n))
    244239    rhoh(:,:,kz)=pint(:,:)/(r_air*tv)
     
    292287  pv(:,:,1,n)=pvh(:,:,1)
    293288  rho(:,:,1,n)=rhoh(:,:,1)
    294 ! RLT add pressure
    295   prs(:,:,1,n)=prsh(:,:,1)
    296289
    297290  uu(:,:,nz,n)=uuh(:,:,nuvz)
     
    307300  pv(:,:,nz,n)=pvh(:,:,nuvz)
    308301  rho(:,:,nz,n)=rhoh(:,:,nuvz)
    309 ! RLT
    310   prs(:,:,nz,n)=prsh(:,:,nuvz)
     302
    311303
    312304  kmin=2
     
    328320          pv(ix,jy,iz,n)=pv(ix,jy,nz,n)
    329321          rho(ix,jy,iz,n)=rho(ix,jy,nz,n)
    330 ! RLT
    331           prs(ix,jy,iz,n)=prs(ix,jy,nz,n)
    332322        else
    333323          innuvz: do kz=idx(ix,jy),nuvz
     
    363353          pv(ix,jy,iz,n)=(pvh(ix,jy,kz-1)*dz2+pvh(ix,jy,kz)*dz1)/dz
    364354          rho(ix,jy,iz,n)=(rhoh(ix,jy,kz-1)*dz2+rhoh(ix,jy,kz)*dz1)/dz
    365 ! RLT add pressure
    366           prs(ix,jy,iz,n)=(prsh(ix,jy,kz-1)*dz2+prsh(ix,jy,kz)*dz1)/dz
    367355        endif
    368356      enddo
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG