Changeset 2162


Ignore:
Timestamp:
Sep 24, 2019, 7:36:09 PM (5 years ago)
Author:
emillour
Message:

Mars GCM:
Some code cleanup (and preparing next steps):

  • Turn calchim into a module and make tendencies module variables in calchim_mod and watercloud_mod
  • Externalize in "physiq" the computation of solar zenithal angle (it should be computed at every physics timestep, regardless of iradia)

AB+EM

Location:
trunk/LMDZ.MARS
Files:
4 edited
1 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r2161 r2162  
    27452745== 24/09/2019 == EM
    27462746- Reactivate output of density scaled opacity
     2747
     2748== 24/09/2019 == AB+EM
     2749Some code cleanup (and preparing next steps):
     2750- Turn calchim into a module and make tendencies module variables
     2751  in calchim_mod and watercloud_mod
     2752- Externalize in "physiq" the computation of solar zenithal angle
     2753  (it should be computed at every physics timestep, regardless of iradia)
  • trunk/LMDZ.MARS/libf/aeronomars/calchim_mod.F90

    r2160 r2162  
     1MODULE calchim_mod
     2
     3  IMPLICIT NONE
     4
     5  REAL,SAVE,ALLOCATABLE :: zdqchim(:,:,:) ! Tendancy on pq due to photochemistry
     6  REAL,SAVE,ALLOCATABLE :: zdqschim(:,:) ! Tendancy on qsurf due to photochemistry
     7
     8  CONTAINS
     9
    110      subroutine calchim(ngrid,nlayer,nq,                           &
    211                         ptimestep,pplay,pplev,pt,pdt,dist_sol,mu0,         &
     
    1524
    1625      use conc_mod, only: mmean ! mean molecular mass of the atmosphere
    17       use comcstfi_h
    18       use photolysis_mod
     26      use comcstfi_h, only: pi
     27      use photolysis_mod, only: jonline, init_photolysis
    1928      use iono_h, only: temp_elect
    2029
     
    6978!=======================================================================
    7079
    71 #include "callkeys.h"
     80include "callkeys.h"
    7281
    7382!     input:
     
    637646      end if ! of if (output)
    638647
    639       return
    640       end
     648      end subroutine calchim
     649
     650
     651    subroutine ini_calchim_mod(ngrid,nlayer,nq)
     652 
     653      implicit none
     654 
     655      integer,intent(in) :: ngrid ! number of atmospheric columns
     656      integer,intent(in) :: nlayer ! number of atmospheric layers
     657      integer,intent(in) :: nq ! number of tracers
     658
     659      allocate(zdqchim(ngrid,nlayer,nq))
     660      zdqchim(:,:,:)=0
     661      allocate(zdqschim(ngrid,nq))
     662      zdqschim(:,:)=0
     663
     664    end subroutine ini_calchim_mod
     665
     666
     667    subroutine end_calchim_mod
     668
     669      implicit none
     670
     671      if (allocated(zdqchim))      deallocate(zdqchim)
     672      if (allocated(zdqschim))      deallocate(zdqschim)
     673
     674    end subroutine end_calchim_mod
     675
     676END MODULE calchim_mod
     677
  • trunk/LMDZ.MARS/libf/phymars/phys_state_var_init_mod.F90

    r1974 r2162  
    4949      use rocketduststorm_mod, only: ini_rocketduststorm_mod, &
    5050                                     end_rocketduststorm_mod
     51      use calchim_mod, only: ini_calchim_mod,end_calchim_mod
     52      use watercloud_mod, only: ini_watercloud_mod, &
     53                                end_watercloud_mod
    5154
    5255      IMPLICIT NONE
     
    118121      call ini_rocketduststorm_mod(ngrid)
    119122     
     123      ! allocate arrays in "calchim_mod" (aeronomars)
     124      call end_calchim_mod
     125      call ini_calchim_mod(ngrid,nlayer,nq)
     126
     127      ! allocate arrays in "watercloud_mod"
     128      call end_watercloud_mod
     129      call ini_watercloud_mod(ngrid,nlayer,nq)
     130
    120131      END SUBROUTINE phys_state_var_init
    121132
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r2161 r2162  
    1414     $            ,pdu,pdv,pdt,pdq,pdpsrf)
    1515
    16       use watercloud_mod, only: watercloud
     16      use watercloud_mod, only: watercloud, zdqcloud, zdqscloud
     17      use calchim_mod, only: calchim, zdqchim, zdqschim
    1718      use watersat_mod, only: watersat
    1819      use co2condens_mod, only: co2condens
     
    308309      REAL zdqadj(ngrid,nlayer,nq)
    309310      REAL zdqc(ngrid,nlayer,nq)
    310       REAL zdqcloud(ngrid,nlayer,nq),zdqcloudco2(ngrid,nlayer,nq)
    311       REAL zdqscloud(ngrid,nq)
    312       REAL zdqchim(ngrid,nlayer,nq)
    313       REAL zdqschim(ngrid,nq)
     311      REAL zdqcloudco2(ngrid,nlayer,nq)
    314312
    315313      REAL zdteuv(ngrid,nlayer)    ! (K/s)
     
    705703
    706704      IF (callrad) THEN
     705
     706c       Local Solar zenith angle
     707c       ~~~~~~~~~~~~~~~~~~~~~~~~
     708        CALL orbite(zls,dist_sol,declin)
     709
     710        IF (diurnal) THEN
     711            ztim1=SIN(declin)
     712            ztim2=COS(declin)*COS(2.*pi*(zday-.5))
     713            ztim3=-COS(declin)*SIN(2.*pi*(zday-.5))
     714
     715            CALL solang(ngrid,sinlon,coslon,sinlat,coslat,
     716     &                  ztim1,ztim2,ztim3, mu0,fract)
     717
     718        ELSE
     719            CALL mucorr(ngrid,declin,latitude,mu0,fract,10000.,rad)
     720        ENDIF ! of IF (diurnal)
     721
    707722         IF( MOD(icount-1,iradia).EQ.0) THEN
    708 
    709 c          Local Solar zenith angle
    710 c          ~~~~~~~~~~~~~~~~~~~~~~~~
    711            CALL orbite(zls,dist_sol,declin)
    712 
    713            IF(diurnal) THEN
    714                ztim1=SIN(declin)
    715                ztim2=COS(declin)*COS(2.*pi*(zday-.5))
    716                ztim3=-COS(declin)*SIN(2.*pi*(zday-.5))
    717 
    718                CALL solang(ngrid,sinlon,coslon,sinlat,coslat,
    719      s         ztim1,ztim2,ztim3, mu0,fract)
    720 
    721            ELSE
    722                CALL mucorr(ngrid,declin,latitude,mu0,fract,10000.,rad)
    723            ENDIF
    724723
    725724c          NLTE cooling from CO2 emission
  • trunk/LMDZ.MARS/libf/phymars/watercloud_mod.F

    r1996 r2162  
    22
    33       IMPLICIT NONE
     4
     5       REAL,SAVE,ALLOCATABLE :: zdqcloud(:,:,:) ! tendencies on pq due to condensation of H2O(kg/kg.s-1)
     6       REAL,SAVE,ALLOCATABLE :: zdqscloud(:,:) ! tendencies on qsurf (calculated only by calchim but declared here)
    47
    58       CONTAINS
     
    641644      END SUBROUTINE watercloud
    642645     
     646      subroutine ini_watercloud_mod(ngrid,nlayer,nq)
     647        implicit none
     648 
     649        integer,intent(in) :: ngrid ! number of atmospheric columns
     650        integer,intent(in) :: nlayer ! number of atmospheric layers
     651        integer,intent(in) :: nq ! number of tracers
     652
     653        allocate(zdqcloud(ngrid,nlayer,nq))
     654        zdqcloud(:,:,:)=0
     655        allocate(zdqscloud(ngrid,nq))
     656        zdqscloud(:,:)=0
     657
     658       end subroutine ini_watercloud_mod
     659
     660
     661       subroutine end_watercloud_mod
     662         implicit none
     663
     664         if (allocated(zdqcloud))      deallocate(zdqcloud)
     665         if (allocated(zdqscloud))      deallocate(zdqscloud)
     666
     667       end subroutine end_watercloud_mod
     668
    643669      END MODULE watercloud_mod
Note: See TracChangeset for help on using the changeset viewer.