Ignore:
Timestamp:
Jan 11, 2017, 3:33:51 PM (8 years ago)
Author:
jvatant
Message:

+ Major clean of the new LMDZ.TITAN from too-generic options and routines (water, co2, ocean, surface type ...)
+ From this revision LMDZ.TITAN begins to be really separated from LMDZ.GENERIC
+ Partial desactivation of aerosols, only the dummy case is still enabled to keep the code running ( new aerosol routines to come in followings commits )

JVO

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/libf/phytitan/callsedim.F

    r1477 r1647  
    44
    55      use radinc_h, only : naerkind
    6       use radii_mod, only: h2o_reffrad
    7       use aerosol_mod, only : iaero_h2o
    8       USE tracer_h, only : igcm_co2_ice,igcm_h2o_ice,radius,rho_q
     6      USE tracer_h, only : radius, rho_q
    97      use comcstfi_mod, only: g
    10       use callkeys_mod, only : water
    118
    129      IMPLICIT NONE
     
    6259      real epaisseur (ngrid,nlay) ! Layer thickness (m)
    6360      real wq(ngrid,nlay+1) ! displaced tracer mass (kg.m-2)
    64 c      real dens(ngrid,nlay) ! Mean density of the ice part. accounting for dust core
    6561
    6662
     
    7369      IF (firstcall) THEN
    7470        firstcall=.false.
    75         ! add some tests on presence of required tracers/aerosols:
    76         if (water) then
    77           if (igcm_h2o_ice.eq.0) then
    78             write(*,*) "callsedim error: water=.true.",
    79      &                 " but igcm_h2o_ice=0"
    80           stop
    81           endif
    82           if (iaero_h2o.eq.0) then
    83             write(*,*) "callsedim error: water=.true.",
    84      &                 " but iaero_ho2=0"
    85           stop
    86           endif
    87         endif
    8871      ENDIF ! of IF (firstcall)
    8972     
     
    10689 
    10790      do iq=1,nq
    108        if((radius(iq).gt.1.e-9).and.(iq.ne.igcm_co2_ice)) then   
    109 !         (no sedim for gases, and co2_ice sedim is done in condense_co2)     
     91       if(radius(iq).gt.1.e-9) then   
     92!         (no sedim for gases)     
    11093
    11194! store locally updated tracers
     
    120103! Sedimentation
    121104!======================================================================
    122 ! Water         
    123           if (water.and.(iq.eq.igcm_h2o_ice)) then
    124             ! compute radii for h2o_ice
    125              call h2o_reffrad(ngrid,nlay,zqi(1,1,igcm_h2o_ice),zt,
    126      &                reffrad(1,1,iaero_h2o),nueffrad(1,1,iaero_h2o))
    127             ! call sedimentation for h2o_ice
    128              call newsedim(ngrid,nlay,ngrid*nlay,ptimestep,
    129      &            pplev,masse,epaisseur,zt,reffrad(1,1,iaero_h2o),
    130      &            rho_q(iq),zqi(1,1,igcm_h2o_ice),wq)
    131 
    132105! General Case
    133           else
    134106             call newsedim(ngrid,nlay,1,ptimestep,
    135107     &            pplev,masse,epaisseur,zt,radius(iq),rho_q(iq),
    136108     &            zqi(1,1,iq),wq)
    137           endif
    138109
    139110!=======================================================================
     
    152123            ENDDO
    153124          ENDDO
    154        endif ! of no gases no co2_ice
     125       endif ! of no gases
    155126      enddo ! of do iq=1,nq
    156127      return
Note: See TracChangeset for help on using the changeset viewer.