Changeset 1565


Ignore:
Timestamp:
Aug 31, 2011, 2:53:29 PM (13 years ago)
Author:
jghattas
Message:

Added interface with chemestry model REPROBUS :

  • Compile LMDZ together with Reprobus code (dependecies in both directions) and cpp key REPROBUS :

./makelmdz_fcm -ext_src my_path_to_reprobus -cpp REPROBUS ...

  • For running, add type_trac=repr in run.def.

/Marion Marchand, JG

Location:
LMDZ5/trunk/libf
Files:
1 added
8 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3d/infotrac.F90

    r1563 r1565  
    3232  SUBROUTINE infotrac_init
    3333    USE control_mod
    34 
     34#ifdef REPROBUS
     35    USE CHEM_REP, ONLY : Init_chem_rep_trac
     36#endif
    3537    IMPLICIT NONE
    3638!=======================================================================
     
    9496          CALL abort_gcm('infotrac_init','Incoherence between type_trac and config_inca',1)
    9597       END IF
     98    ELSE IF (type_trac=='repr') THEN
     99       WRITE(lunout,*) 'You have choosen to couple with REPROBUS chemestry model : type_trac=', type_trac
    96100    ELSE IF (type_trac == 'lmdz') THEN
    97101       WRITE(lunout,*) 'Tracers are treated in LMDZ only : type_trac=', type_trac
     
    115119!
    116120!-----------------------------------------------------------------------
    117     IF (type_trac == 'lmdz') THEN
     121    IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    118122       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
    119123       IF(ierr.EQ.0) THEN
     
    147151    END IF
    148152   
     153! Transfert number of tracers to Reprobus
     154    IF (type_trac == 'repr') THEN
     155#ifdef REPROBUS
     156       CALL Init_chem_rep_trac(nbtr)
     157#endif
     158    END IF
    149159       
    150160!
     
    182192!    Get choice of advection schema from file tracer.def or from INCA
    183193!---------------------------------------------------------------------
    184     IF (type_trac == 'lmdz') THEN
     194    IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    185195       IF(ierr.EQ.0) THEN
    186196          ! Continue to read tracer.def
  • LMDZ5/trunk/libf/dyn3dpar/infotrac.F90

    r1563 r1565  
    3232  SUBROUTINE infotrac_init
    3333    USE control_mod
    34 
     34#ifdef REPROBUS
     35    USE CHEM_REP, ONLY : Init_chem_rep_trac
     36#endif
    3537    IMPLICIT NONE
    3638!=======================================================================
     
    9496          CALL abort_gcm('infotrac_init','Incoherence between type_trac and config_inca',1)
    9597       END IF
     98    ELSE IF (type_trac=='repr') THEN
     99       WRITE(lunout,*) 'You have choosen to couple with REPROBUS chemestry model : type_trac=', type_trac
    96100    ELSE IF (type_trac == 'lmdz') THEN
    97101       WRITE(lunout,*) 'Tracers are treated in LMDZ only : type_trac=', type_trac
     
    115119!
    116120!-----------------------------------------------------------------------
    117     IF (type_trac == 'lmdz') THEN
     121    IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    118122       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
    119123       IF(ierr.EQ.0) THEN
     
    147151    END IF
    148152   
     153! Transfert number of tracers to Reprobus
     154    IF (type_trac == 'repr') THEN
     155#ifdef REPROBUS
     156       CALL Init_chem_rep_trac(nbtr)
     157#endif
     158    END IF
    149159       
    150160!
     
    182192!    Get choice of advection schema from file tracer.def or from INCA
    183193!---------------------------------------------------------------------
    184     IF (type_trac == 'lmdz') THEN
     194    IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    185195       IF(ierr.EQ.0) THEN
    186196          ! Continue to read tracer.def
  • LMDZ5/trunk/libf/phylmd/init_phys_lmdz.F90

    r1146 r1565  
    66  USE mod_grid_phy_lmdz
    77  USE dimphy, ONLY : Init_dimphy
     8  USE infotrac, ONLY : type_trac
     9#ifdef REPROBUS
     10  USE CHEM_REP, ONLY : Init_chem_rep_phys
     11#endif
     12
    813  IMPLICIT NONE
    914 
     
    1924!$OMP PARALLEL
    2025    CALL Init_dimphy(klon_omp,nbp_lev)
     26
     27! Initialization of Reprobus
     28    IF (type_trac == 'repr') THEN
     29#ifdef REPROBUS
     30       CALL Init_chem_rep_phys(klon_omp,nbp_lev)
     31#endif
     32    END IF
     33
    2134!$OMP END PARALLEL
    2235 
  • LMDZ5/trunk/libf/phylmd/physiq.F

    r1563 r1565  
    4242      use radlwsw_m, only: radlwsw
    4343      USE control_mod
     44#ifdef REPROBUS
     45      USE CHEM_REP, ONLY : Init_chem_rep_xjour
     46#endif
    4447
    4548
     
    12151218      REAL, dimension(klon, klev) :: cldtaurad  ! epaisseur optique pour radlwsw,COSP
    12161219      REAL, dimension(klon, klev) :: cldemirad  ! emissivite pour radlwsw,COSP
     1220      INTEGER :: nbtr_tmp ! Number of tracer inside concvl
     1221      REAL, dimension(klon,klev) :: sh_in ! Specific humidity entering in phytrac
    12171222
    12181223cIM for NMC files
     
    17361741      CALL change_srf_frac(itap, dtime, days_elapsed+1,
    17371742     *     pctsrf, falb1, falb2, ftsol, u10m, v10m, pbl_tke)
     1743
     1744
     1745! Update time and other variables in Reprobus
     1746      IF (type_trac == 'repr') THEN
     1747#ifdef REPROBUS
     1748         CALL Init_chem_rep_xjour(jD_cur-jD_ref+day_ref)
     1749         print*,'xjour equivalent rjourvrai',jD_cur-jD_ref+day_ref
     1750         CALL Rtime(debut)
     1751#endif
     1752      END IF
     1753
    17381754
    17391755! Tendances bidons pour les processus qui n'affectent pas certaines
     
    22882304          IF (ok_cvl) THEN ! new driver for convectL
    22892305
     2306             IF (type_trac == 'repr') THEN
     2307                nbtr_tmp=ntra
     2308             ELSE
     2309                nbtr_tmp=nbtr
     2310             END IF
    22902311          CALL concvl (iflag_con,iflag_clos,
    22912312     .        dtime,paprs,pplay,t_undi,q_undi,
    22922313     .        t_wake,q_wake,wake_s,
    2293      .        u_seri,v_seri,tr_seri,nbtr,
     2314     .        u_seri,v_seri,tr_seri,nbtr_tmp,
    22942315     .        ALE,ALP,
    22952316     .        ema_work1,ema_work2,
     
    36643685C
    36653686
     3687       IF (type_trac=='repr') THEN
     3688          sh_in(:,:) = q_seri(:,:)
     3689       ELSE
     3690          sh_in(:,:) = qx(:,:,ivap)
     3691       END IF
     3692
    36663693      call phytrac (
    36673694     I     itap,     days_elapsed+1,    jH_cur,   debut,
     
    36733700     I     rlat,     frac_impa, frac_nucl,rlon,
    36743701     I     presnivs, pphis,     pphi,     albsol1,
    3675      I     qx(:,:,ivap),rhcl,   cldfra,   rneb,
     3702     I     sh_in,    rhcl,      cldfra,   rneb,
    36763703     I     diafra,   cldliq,    itop_con, ibas_con,
    36773704     I     pmflxr,   pmflxs,    prfl,     psfl,
  • LMDZ5/trunk/libf/phylmd/phytrac.F90

    r1454 r1565  
    3333  USE traclmdz_mod
    3434  USE tracinca_mod
     35  USE tracreprobus_mod
    3536  USE control_mod
    36 
    3737
    3838
     
    5555  INTEGER,INTENT(IN) :: nstep      ! Appel physique
    5656  INTEGER,INTENT(IN) :: julien     ! Jour julien
    57   REAL,INTENT(IN)    :: gmtime
     57  REAL,INTENT(IN)    :: gmtime     ! Heure courante
    5858  REAL,INTENT(IN)    :: pdtphys    ! Pas d'integration pour la physique (seconde)
    5959  LOGICAL,INTENT(IN) :: debutphy   ! le flag de l'initialisation de la physique
     
    217217        source(:,:)=0.
    218218        CALL tracinca_init(aerosol,lessivage)
     219     CASE('repr')
     220        source(:,:)=0.
    219221     END SELECT
    220222!
     
    257259          rfname,                                        &
    258260          tr_seri,  source,   solsym)     
     261
     262  CASE('repr')
     263     !   -- CHIMIE REPROBUS --
     264
     265     CALL tracreprobus(pdtphys, gmtime, debutphy, julien, &
     266          presnivs, xlat, xlon, pphis, pphi, &
     267          t_seri, pplay, paprs, sh , &
     268          tr_seri, solsym)
     269     
    259270  END SELECT
    260271
  • LMDZ5/trunk/libf/phylmd/radiation_AR4.F

    r1279 r1565  
    163163        allocate(ZFSUPAI(KDLON,KFLEV+1))
    164164        allocate(ZFSDNAI(KDLON,KFLEV+1))
    165         DO JK = 1 , KDLON*(KFLEV+1)
    166           ZFSUPAD(JK,1) = 0.0     ! ZFSUPAD(:,:)=0.
    167           ZFSDNAD(JK,1) = 0.0     ! ZFSDNAD(:,:)=0.
    168           ZFSUPAI(JK,1) = 0.0     ! ZFSUPAI(:,:)=0.
    169           ZFSDNAI(JK,1) = 0.0     ! ZFSDNAI(:,:)=0.
    170         END DO
     165
     166        ZFSUPAD(:,:)=0.
     167        ZFSDNAD(:,:)=0.
     168        ZFSUPAI(:,:)=0.
     169        ZFSDNAI(:,:)=0.
    171170      endif
    172 !rv
    173      
    174 c
     171
    175172      IF (appel1er) THEN
    176173         PRINT*, 'SW calling frequency : ', swpas
     
    526523      USE dimphy
    527524      USE radiation_AR4_param, only : RSUN, RRAY
     525      USE infotrac, ONLY : type_trac
     526#ifdef REPROBUS
     527      USE CHEM_REP, ONLY : RSUNTIME, ok_SUNTIME
     528#endif
     529
    528530      IMPLICIT none
    529531cym#include "dimensions.h"
     
    613615      INTEGER jl, jk, k, jaj, ikm1, ikl
    614616
     617C If running with Reporbus, overwrite default values of RSUN.
     618C Otherwise keep default values from radiation_AR4_param module. 
     619      IF (type_trac == 'repr') THEN
     620#ifdef REPROBUS
     621         IF (ok_SUNTIME) THEN
     622            RSUN(1) = RSUNTIME(1)
     623            RSUN(2) = RSUNTIME(2)
     624         ENDIF
     625         PRINT*,'RSUN(1): ',RSUN(1)
     626#endif
     627      END IF
     628
    615629C     ------------------------------------------------------------------
    616630C
     
    754768      USE dimphy
    755769      USE radiation_AR4_param, only : RSUN, RRAY
     770      USE infotrac, ONLY : type_trac
     771#ifdef REPROBUS
     772      use CHEM_REP, only : RSUNTIME, ok_SUNTIME
     773#endif
     774
    756775      IMPLICIT none
    757776cym#include "dimensions.h"
     
    873892      INTEGER jref, jkl, jklp1, jajp, jkki, jkkp4, jn2j, iabs
    874893      REAL(KIND=8) ZRMUM1, ZWH2O, ZCNEB, ZAA, ZBB, ZRKI, ZRE11
     894
     895C If running with Reporbus, overwrite default values of RSUN.
     896C Otherwise keep default values from radiation_AR4_param module. 
     897      IF (type_trac == 'repr') THEN
     898#ifdef REPROBUS
     899         IF (ok_SUNTIME) THEN
     900            RSUN(1)=RSUNTIME(1)
     901            RSUN(2)=RSUNTIME(2)
     902         END IF
     903#endif
     904      END IF
     905
    875906C
    876907
     
    24852516      USE dimphy
    24862517      USE radiation_AR4_param, only : TREF, RT1, RAER, AT, BT, OCT
     2518      USE infotrac, ONLY : type_trac
     2519#ifdef REPROBUS
     2520      USE CHEM_REP, ONLY: RCH42D,
     2521     $                    RN2O2D,
     2522     $                    RCFC112D,
     2523     $                    RCFC122D,
     2524     $                    ok_Rtime2D
     2525#endif
     2526
    24872527      IMPLICIT none
    24882528cym#include "dimensions.h"
     
    28002840     S                +ZUAER(JL,5)    *ZDUC(JL,JC)*ZDIFF
    28012841C
    2802       PABCU(JL,19,JC)=PABCU(JL,19,JCP1)
    2803      S               +ZABLY(JL,8,JC)*RCH4/RCO2*ZPHM6(JL)*ZDIFF
    2804       PABCU(JL,20,JC)=PABCU(JL,20,JCP1)
     2842C
     2843
     2844      IF (type_trac == 'repr') THEN
     2845         IF (ok_Rtime2D) THEN
     2846#ifdef REPROBUS
     2847            PABCU(JL,19,JC)=PABCU(JL,19,JCP1)
     2848     S           +ZABLY(JL,8,JC)*RCH42D(JL,JC)/RCO2*ZPHM6(JL)*ZDIFF
     2849            PABCU(JL,20,JC)=PABCU(JL,20,JCP1)
     2850     S           +ZABLY(JL,9,JC)*RCH42D(JL,JC)/RCO2*ZPSM6(JL)*ZDIFF
     2851            PABCU(JL,21,JC)=PABCU(JL,21,JCP1)
     2852     S           +ZABLY(JL,8,JC)*RN2O2D(JL,JC)/RCO2*ZPHN6(JL)*ZDIFF
     2853            PABCU(JL,22,JC)=PABCU(JL,22,JCP1)
     2854     S           +ZABLY(JL,9,JC)*RN2O2D(JL,JC)/RCO2*ZPSN6(JL)*ZDIFF
     2855C
     2856            PABCU(JL,23,JC)=PABCU(JL,23,JCP1)
     2857     S           +ZABLY(JL,8,JC)*RCFC112D(JL,JC)/RCO2         *ZDIFF
     2858            PABCU(JL,24,JC)=PABCU(JL,24,JCP1)
     2859     S           +ZABLY(JL,8,JC)*RCFC122D(JL,JC)/RCO2         *ZDIFF
     2860#endif
     2861         ELSE
     2862            ! Same calculation as for type_trac /= repr
     2863            PABCU(JL,19,JC)=PABCU(JL,19,JCP1)
     2864     S           +ZABLY(JL,8,JC)*RCH4/RCO2*ZPHM6(JL)*ZDIFF
     2865            PABCU(JL,20,JC)=PABCU(JL,20,JCP1)
     2866     S           +ZABLY(JL,9,JC)*RCH4/RCO2*ZPSM6(JL)*ZDIFF
     2867            PABCU(JL,21,JC)=PABCU(JL,21,JCP1)
     2868     S           +ZABLY(JL,8,JC)*RN2O/RCO2*ZPHN6(JL)*ZDIFF
     2869            PABCU(JL,22,JC)=PABCU(JL,22,JCP1)
     2870     S           +ZABLY(JL,9,JC)*RN2O/RCO2*ZPSN6(JL)*ZDIFF
     2871C     
     2872            PABCU(JL,23,JC)=PABCU(JL,23,JCP1)
     2873     S               +ZABLY(JL,8,JC)*RCFC11/RCO2         *ZDIFF
     2874            PABCU(JL,24,JC)=PABCU(JL,24,JCP1)
     2875     S           +ZABLY(JL,8,JC)*RCFC12/RCO2         *ZDIFF
     2876         END IF
     2877      ELSE
     2878         PABCU(JL,19,JC)=PABCU(JL,19,JCP1)
     2879     S        +ZABLY(JL,8,JC)*RCH4/RCO2*ZPHM6(JL)*ZDIFF
     2880         PABCU(JL,20,JC)=PABCU(JL,20,JCP1)
    28052881     S               +ZABLY(JL,9,JC)*RCH4/RCO2*ZPSM6(JL)*ZDIFF
    2806       PABCU(JL,21,JC)=PABCU(JL,21,JCP1)
    2807      S               +ZABLY(JL,8,JC)*RN2O/RCO2*ZPHN6(JL)*ZDIFF
    2808       PABCU(JL,22,JC)=PABCU(JL,22,JCP1)
    2809      S               +ZABLY(JL,9,JC)*RN2O/RCO2*ZPSN6(JL)*ZDIFF
    2810 C
    2811       PABCU(JL,23,JC)=PABCU(JL,23,JCP1)
    2812      S               +ZABLY(JL,8,JC)*RCFC11/RCO2         *ZDIFF
    2813       PABCU(JL,24,JC)=PABCU(JL,24,JCP1)
    2814      S               +ZABLY(JL,8,JC)*RCFC12/RCO2         *ZDIFF
     2882         PABCU(JL,21,JC)=PABCU(JL,21,JCP1)
     2883     S        +ZABLY(JL,8,JC)*RN2O/RCO2*ZPHN6(JL)*ZDIFF
     2884         PABCU(JL,22,JC)=PABCU(JL,22,JCP1)
     2885     S        +ZABLY(JL,9,JC)*RN2O/RCO2*ZPSN6(JL)*ZDIFF
     2886C     
     2887         PABCU(JL,23,JC)=PABCU(JL,23,JCP1)
     2888     S        +ZABLY(JL,8,JC)*RCFC11/RCO2         *ZDIFF
     2889         PABCU(JL,24,JC)=PABCU(JL,24,JCP1)
     2890     S        +ZABLY(JL,8,JC)*RCFC12/RCO2         *ZDIFF
     2891      END IF
     2892     
    28152893 523  CONTINUE
    28162894 524  CONTINUE
  • LMDZ5/trunk/libf/phylmd/radiation_AR4_param.F90

    r1279 r1565  
    159159      0.90811926E+01,  0.75073923E+02,  0.24654438E+03,  0.39332612E+03,  0.29385281E+03,  0.89107921E+02 /) , (/ 6,6 /) )
    160160
    161       REAL*8, dimension(2), parameter :: RSUN = (/ 0.441676 , 0.558324 /)
     161! If running with Reporbus type_trac=repr, values of RSUN might be overritten in radiation_AR4
     162      REAL*8, dimension(2) :: RSUN = (/ 0.441676 , 0.558324 /)
    162163      REAL*8, dimension(2,6), parameter :: RRAY = reshape ( &
    163164         (/ .428937E-01, .697200E-02,&
  • LMDZ5/trunk/libf/phylmd/radlwsw.F90

    r1279 r1565  
    3030
    3131  USE DIMPHY
    32   use assert_m, only: assert
     32  USE assert_m, ONLY : assert
     33  USE infotrac, ONLY : type_trac
     34#ifdef REPROBUS
     35  USE CHEM_REP, ONLY : solaireTIME, ok_SUNTIME, ndimozon
     36#endif
    3337
    3438  !======================================================================
     
    229233  !
    230234  PSCT = solaire/zdist/zdist
     235
     236  IF (type_trac == 'repr') THEN
     237#ifdef REPROBUS
     238     if(ok_SUNTIME) PSCT = solaireTIME/zdist/zdist
     239     print*,'Constante solaire: ',PSCT*zdist*zdist
     240#endif
     241  END IF
     242
    231243  DO j = 1, nb_gr
    232244    iof = kdlon*(j-1)
     
    281293      ENDDO
    282294    ENDDO
     295
     296    IF (type_trac == 'repr') THEN
     297#ifdef REPROBUS
     298       ndimozon = size(wo, 3)
     299       CALL RAD_INTERACTIF(POZON,iof)
     300#endif
     301    END IF
     302
    283303    !
    284304    DO k = 1, kflev+1
Note: See TracChangeset for help on using the changeset viewer.