Changeset 1983


Ignore:
Timestamp:
Aug 1, 2018, 3:35:24 PM (6 years ago)
Author:
mvals
Message:

Mars GCM:
Cosmetic/practical changes:

  • swmain and lwmain become modules swmain_mod, lwmain_mod
  • Addition of the intent in/out characteristics of variables in swmain_mod and lwmain_mod subroutines

Correction:

  • in callsedim_mod, declaration of variable tau(ngrid,nlay) corrected to tau(ngrid,naerkind)

MV

Location:
trunk/LMDZ.MARS
Files:
3 edited
2 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r1977 r1983  
    26262626Update xvik.F main program to work with current diagfi outputs.
    26272627
     2628== 01/08/2018 == MV
     2629Cosmetic/practical changes:
     2630- swmain and lwmain become modules swmain_mod, lwmain_mod
     2631- Addition of the intent in/out characteristics of variables in swmain_mod and lwmain_mod subroutines
     2632Correction:
     2633- in callsedim_mod, declaration of variable tau(ngrid,nlay) corrected to tau(ngrid,naerkind)
  • trunk/LMDZ.MARS/libf/phymars/callradite_mod.F

    r1974 r1983  
    2323      use comcstfi_h, only: g,cpp
    2424      use time_phylmdz_mod, only: daysec
     25      use lwmain_mod, only: lwmain
     26      use swmain_mod, only: swmain
    2527      IMPLICIT NONE
    2628c=======================================================================
  • trunk/LMDZ.MARS/libf/phymars/callsedim_mod.F

    r1974 r1983  
    2222      USE newsedim_mod, ONLY: newsedim
    2323      USE comcstfi_h, ONLY: g
     24      USE dimradmars_mod, only: naerkind
    2425      IMPLICIT NONE
    2526
     
    7475      real,intent(out) :: pdqs_sed(ngrid,nq)    ! flux at surface (kg.m-2.s-1)
    7576      integer,intent(in) :: nq  ! number of tracers
    76       real,intent(in) :: tau(ngrid,nlay) ! dust opacity
     77      real,intent(in) :: tau(ngrid,naerkind) ! dust opacity
    7778      real,intent(in) :: tauscaling(ngrid)
    7879     
  • trunk/LMDZ.MARS/libf/phymars/lwmain_mod.F

    r1982 r1983  
     1       MODULE lwmain_mod
     2
     3       IMPLICIT NONE
     4
     5       CONTAINS
     6       
    17       subroutine lwmain (ig0,icount,kdlon,kflev
    28     .                   ,dp,dt0,emis
     
    1622      use yomlw_h, only: nlaylte, xi
    1723      implicit none
    18  
    19 #include "callkeys.h"
    20 #include "comg1d.h"
     24     
     25c     declarations
     26c     -------------   
     27      include "callkeys.h"
     28      include "comg1d.h"
    2129
    2230c----------------------------------------------------------------------
    2331c         0.1   arguments
    2432c               ---------
    25 c                                                            inputs:
    26 c                                                            -------
    27       integer ig0
    28       integer icount
    29       integer kdlon            ! part of ngrid
    30       integer kflev            ! part of nlayer
    31 
    32       real dp (ndlo2,kflev)         ! layer pressure thickness (Pa)
    33       real dt0 (ndlo2)              ! surface temperature discontinuity (K)
    34       real emis (ndlo2)             ! surface emissivity
    35       real plev (ndlo2,kflev+1)     ! level pressure (Pa)
    36       real tlev (ndlo2,kflev+1)     ! level temperature (K)
    37       real tlay (ndlo2,kflev)       ! layer temperature (K)
    38       real aerosol(ndlo2,kflev,naerkind)      !  aerosol extinction optical
     33c     inputs/outputs:
     34c     -------
     35      integer, intent(in) :: ig0
     36      integer, intent(in) :: icount
     37      integer, intent(in) :: kdlon            ! part of ngrid
     38      integer, intent(in) :: kflev            ! part of nlayer
     39
     40      real, intent(in) :: dp (ndlo2,kflev)         ! layer pressure thickness (Pa)
     41      real, intent(in) :: dt0 (ndlo2)              ! surface temperature discontinuity (K)
     42      real, intent(in) :: emis (ndlo2)             ! surface emissivity
     43      real, intent(in) :: plev (ndlo2,kflev+1)     ! level pressure (Pa)
     44      real, intent(in) :: tlev (ndlo2,kflev+1)     ! level temperature (K)
     45      real, intent(in) :: tlay (ndlo2,kflev)       ! layer temperature (K)
     46      real, intent(in) :: aerosol(ndlo2,kflev,naerkind)      !  aerosol extinction optical
    3947c                         depth at reference wavelength "longrefvis" set
    4048c                         in dimradmars_mod , in each layer, for one of
     
    4452c                                                            outputs:
    4553c                                                            --------
    46       real coolrate(ndlo2,kflev)      ! cooling rate (K/s)
    47       real fluxground(ndlo2)          ! downward ground flux (W/m2)
    48       real fluxtop(ndlo2)             ! outgoing upward flux (W/m2) ("OLR")
    49       real netrad (ndlo2,kflev)       ! radiative budget (W/m2)
     54      real, intent(out) :: coolrate(ndlo2,kflev)      ! cooling rate (K/s)
     55      real, intent(out) :: fluxground(ndlo2)          ! downward ground flux (W/m2)
     56      real, intent(out) :: fluxtop(ndlo2)             ! outgoing upward flux (W/m2) ("OLR")
     57      real, intent(out) :: netrad (ndlo2,kflev)       ! radiative budget (W/m2)
    5058c     Aerosol optical properties
    51       REAL :: QIRsQREF3d(ndlo2,kflev,nir,naerkind)
    52       REAL :: omegaIR3d(ndlo2,kflev,nir,naerkind)
    53       REAL :: gIR3d(ndlo2,kflev,nir,naerkind)
    54 
     59      real, intent(in) :: QIRsQREF3d(ndlo2,kflev,nir,naerkind)
     60      real, intent(in) :: omegaIR3d(ndlo2,kflev,nir,naerkind)
     61      real, intent(in) :: gIR3d(ndlo2,kflev,nir,naerkind)
     62      real, intent(in) :: co2ice(ndlo2)           ! co2 ice surface layer (kg.m-2)
    5563c----------------------------------------------------------------------
    5664c         0.2   local arrays
     
    7583      real newcoolrate(ndlon,nflev) ! cooling rate (K/s) / with implicite scheme
    7684
    77       REAL co2ice(ndlo2)           ! co2 ice surface layer (kg.m-2)
    78       REAL emis_gaz(ndlo2)         ! emissivity for gaz computations
     85      real emis_gaz(ndlo2)         ! emissivity for gaz computations
    7986
    8087      integer jk,jkk,ja,jl
     
    193200c----------------------------------------------------------------------
    194201
    195       return
    196       end
     202      END SUBROUTINE lwmain
     203
     204      END MODULE lwmain_mod
     205
  • trunk/LMDZ.MARS/libf/phymars/swmain_mod.F

    r1982 r1983  
     1      MODULE swmain_mod
     2     
     3      IMPLICIT NONE
     4
     5      CONTAINS
     6
    17      SUBROUTINE SWMAIN ( KDLON, KFLEV,
    28     $                PCST, albedo,
     
    915      use yomlw_h, only: nlaylte, gcp
    1016      IMPLICIT NONE
    11      
    12 #include "callkeys.h"
     17
     18c     DECLARATIONS
     19c     -------------     
     20      include "callkeys.h"
    1321c     
    1422c     PURPOSE.
     
    5967C     ARGUMENTS
    6068C     ---------
     69c     INPUTS/OUTPUTS:
     70c     ---------
    6171     
    62       INTEGER KDLON, KFLEV
    63       REAL ZPSOL(NDLO2), aerosol(NDLO2,KFLEV,naerkind),PRMU0(NDLO2)
    64       real PCST
    65       REAL albedo(NDLO2,2)
    66       REAL PDP(NDLO2,KFLEV)
    67       REAL PPLEV(NDLO2,KFLEV+1)
    68       REAL PHEAT(NDLO2,KFLEV)
    69       REAL PFRACT(NDLO2)
    70       real PFLUXD(NDLON,NFLEV+1,2)
    71       real PFLUXU(NDLON,NFLEV+1,2)
    72       REAL :: QVISsQREF3d(NDLO2,KFLEV,nsun,naerkind)
    73       REAL :: omegaVIS3d(NDLO2,KFLEV,nsun,naerkind)
    74       REAL :: gVIS3d(NDLO2,KFLEV,nsun,naerkind)
     72      INTEGER, iNTENT(IN) :: KDLON, KFLEV
     73      REAL, iNTENT(IN) :: aerosol(NDLO2,KFLEV,naerkind),PRMU0(NDLO2)
     74      REAL, iNTENT(IN) :: PCST
     75      REAL, iNTENT(IN) :: albedo(NDLO2,2)
     76      REAL, iNTENT(IN) :: PDP(NDLO2,KFLEV)
     77      REAL, iNTENT(IN) :: PPLEV(NDLO2,KFLEV+1)
     78      REAL, iNTENT(OUT) :: PHEAT(NDLO2,KFLEV)
     79      REAL, iNTENT(IN) :: PFRACT(NDLO2)
     80      REAL, iNTENT(OUT) :: PFLUXD(NDLON,NFLEV+1,2)
     81      REAL, iNTENT(OUT) :: PFLUXU(NDLON,NFLEV+1,2)
     82      REAL, iNTENT(IN) :: QVISsQREF3d(NDLO2,KFLEV,nsun,naerkind)
     83      REAL, iNTENT(IN) :: omegaVIS3d(NDLO2,KFLEV,nsun,naerkind)
     84      REAL, iNTENT(IN) :: gVIS3d(NDLO2,KFLEV,nsun,naerkind)
    7585     
    7686C     LOCAL ARRAYS
    7787C     ------------
    78      
     88      REAL ZPSOL(NDLO2)
    7989      REAL ZDSIG(NDLON,NFLEV), ZFACT(NDLON)
    8090     S     ,  ZFD(NDLON,NFLEV+1)
     
    183193      END DO
    184194
    185       RETURN
    186       END
     195      END SUBROUTINE SWMAIN
     196
     197      END MODULE swmain_mod
Note: See TracChangeset for help on using the changeset viewer.