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

File:
1 moved

Legend:

Unmodified
Added
Removed
  • 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
Note: See TracChangeset for help on using the changeset viewer.