Ignore:
Timestamp:
May 11, 2014, 2:37:58 PM (11 years ago)
Author:
aslmd
Message:

LMDZ.MARS. Made number of scatterers a free dimension not in need to be prescribe at compiling time. Instead it must be set in callphys.def. See README for further information about this commit.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/phymars/conf_phys.F

    r1240 r1246  
    1       SUBROUTINE conf_phys(nq)
     1      SUBROUTINE conf_phys(ngrid,nlayer,nq)
    22 
    33!=======================================================================
     
    3838      use surfdat_h, only: albedo_h2o_ice, inert_h2o_ice,
    3939     &                     frost_albedo_threshold
    40       use yomaer_h,only: tauvis
    4140      use control_mod, only: ecritphy
    4241      use planete_h
    4342      USE comcstfi_h, only: daysec,dtphys
     43      use dimradmars_mod, only: naerkind, name_iaer,
     44     &                      ini_scatterers,tauvis
    4445
    4546      IMPLICIT NONE
     
    5253!#include "surfdat.h"
    5354!#include "dimradmars.h"
    54 !#include "yomaer.h"
    5555#include "datafile.h"
    5656!#include "slope.h"
    5757#include "microphys.h"
    5858!#include "tracer.h"
    59 ! naerkind is set in scatterers.h (built when compiling with makegcm -s #)
    60 #include"scatterers.h"
    61 
    62       INTEGER,INTENT(IN) :: nq
    63       INTEGER ig,ierr
     59
     60      INTEGER,INTENT(IN) :: ngrid,nlayer,nq
     61      INTEGER ig,ierr,j
    6462 
    6563      CHARACTER ch1*12
     
    536534
    537535
     536! SCATTERERS
     537         write(*,*) "how many scatterers?"
     538         naerkind=1 ! default value
     539         call getin("naerkind",naerkind)
     540         write(*,*)" naerkind = ",naerkind
     541
     542! Test of incompatibility
     543c        Logical tests for radiatively active water-ice clouds:
     544         IF ( (activice.AND.(.NOT.water)).OR.
     545     &        (activice.AND.(naerkind.LT.2)) ) THEN
     546           WRITE(*,*) 'If activice is TRUE, water has to be set'
     547           WRITE(*,*) 'to TRUE, and "naerkind" must be at least'
     548           WRITE(*,*) 'equal to 2.'
     549           CALL ABORT
     550         ELSE IF ( (.NOT.activice).AND.(naerkind.GT.1) ) THEN
     551           WRITE(*,*) 'naerkind is greater than unity, but'
     552           WRITE(*,*) 'activice has not been set to .true.'
     553           WRITE(*,*) 'in callphys.def; this is not logical!'
     554           CALL ABORT
     555         ENDIF
     556
     557!------------------------------------------
     558!------------------------------------------
     559! once naerkind is known allocate arrays
     560! -- we do it here and not in phys_var_init
     561! -- because we need to know naerkind first
     562         CALL ini_scatterers(ngrid,nlayer)
     563!------------------------------------------
     564!------------------------------------------
     565
     566
     567c        Please name the different scatterers here ----------------
     568         name_iaer(1) = "dust_conrath"   !! default choice is good old Conrath profile
     569         IF (doubleq.AND.active) name_iaer(1) = "dust_doubleq" !! two-moment scheme
     570         if (nq.gt.1) then
     571          ! trick to avoid problems compiling with 1 tracer
     572          ! and picky compilers who know name_iaer(2) is out of bounds
     573          j=2
     574         IF (water.AND.activice) name_iaer(j) = "h2o_ice"      !! radiatively-active clouds
     575         IF (submicron.AND.active) name_iaer(j) = "dust_submicron" !! JBM experimental stuff
     576         endif ! of if (nq.gt.1)
     577c        ----------------------------------------------------------
     578
    538579! THERMOSPHERE
    539580
Note: See TracChangeset for help on using the changeset viewer.