Ignore:
Timestamp:
07/16/14 18:05:01 (10 years ago)
Author:
milmd
Message:

Last LMDZ version (1315) with OpenMP directives and other stuff

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/condense_cloud.F90

    r222 r227  
    3232!     ptsrf(ngrid)          Surface temperature 
    3333!      
    34 !     pdt(ngrid,nlayermx)   Time derivative before condensation/sublimation of pt 
     34!     pdt(ngrid,nlayer)   Time derivative before condensation/sublimation of pt 
    3535!     pdtsrf(ngrid)         Time derivative before condensation/sublimation of ptsrf 
    3636!     pqsurf(ngrid,nq)      Sedimentation flux at the surface (kg.m-2.s-1) 
     
    3838!     Outputs 
    3939!     ------- 
    40 !     pdpsrf(ngrid)         \  Contribution of condensation/sublimation 
    41 !     pdtc(ngrid,nlayermx)  /  to the time derivatives of Ps, pt, and ptsrf 
    42 !     pdtsrfc(ngrid)       / 
     40!     pdpsrf(ngrid)       \  Contribution of condensation/sublimation 
     41!     pdtc(ngrid,nlayer)  /  to the time derivatives of Ps, pt, and ptsrf 
     42!     pdtsrfc(ngrid)     / 
    4343!      
    4444!     Both 
     
    5656!================================================================== 
    5757 
    58 #include "dimensions.h" 
    59 #include "dimphys.h" 
     58!#include "dimensions.h" 
     59!#include "dimphys.h" 
    6060#include "comcstfi.h" 
    61 #include "comvert.h" 
     61!#include "comvert.h" 
    6262#include "callkeys.h" 
    6363 
     
    9999 
    100100      REAL reffrad(ngrid,nlayer) ! radius (m) of the co2 ice particles 
    101       REAL*8 zt(ngrid,nlayermx) 
    102       REAL zq(ngrid,nlayermx,nq) 
     101      REAL*8 zt(ngrid,nlayer) 
     102      REAL zq(ngrid,nlayer,nq) 
    103103      REAL zcpi 
    104       REAL ztcond (ngrid,nlayermx) 
    105       REAL ztnuc (ngrid,nlayermx) 
     104      REAL ztcond (ngrid,nlayer) 
     105      REAL ztnuc (ngrid,nlayer) 
    106106      REAL ztcondsol(ngrid)  
    107107      REAL zdiceco2(ngrid) 
    108       REAL zcondicea(ngrid,nlayermx), zcondices(ngrid) 
     108      REAL zcondicea(ngrid,nlayer), zcondices(ngrid) 
    109109      REAL zfallice(ngrid), Mfallice(ngrid)  
    110       REAL zmflux(nlayermx+1) 
    111       REAL zu(nlayermx),zv(nlayermx) 
     110      REAL zmflux(nlayer+1) 
     111      REAL zu(nlayer),zv(nlayer) 
    112112      REAL ztsrf(ngrid) 
    113       REAL ztc(nlayermx), ztm(nlayermx+1)  
    114       REAL zum(nlayermx+1) , zvm(nlayermx+1) 
     113      REAL ztc(nlayer), ztm(nlayer+1)  
     114      REAL zum(nlayer+1) , zvm(nlayer+1) 
    115115      LOGICAL condsub(ngrid) 
    116116      REAL subptimestep 
    117117      Integer Ntime 
    118       real masse (ngrid,nlayermx), w(ngrid,nlayermx,nq) 
    119       real wq(ngrid,nlayermx+1) 
     118      real masse (ngrid,nlayer), w(ngrid,nlayer,nq) 
     119      real wq(ngrid,nlayer+1) 
    120120      real vstokes,reff 
    121121 
    122122!     Special diagnostic variables 
    123       real tconda1(ngrid,nlayermx) 
    124       real tconda2(ngrid,nlayermx) 
    125       real zdtsig (ngrid,nlayermx) 
    126       real zdt (ngrid,nlayermx) 
     123      real tconda1(ngrid,nlayer) 
     124      real tconda2(ngrid,nlayer) 
     125      real zdtsig (ngrid,nlayer) 
     126      real zdt (ngrid,nlayer) 
    127127 
    128128!----------------------------------------------------------------------- 
     
    133133      REAL,SAVE :: cpice=1000. 
    134134      REAL,SAVE,ALLOCATABLE,DIMENSION(:) :: emisref 
     135!$OMP THREADPRIVATE(latcond,ccond,cpice,emisref) 
    135136 
    136137      LOGICAL,SAVE :: firstcall=.true. 
     138!$OMP THREADPRIVATE(firstcall) 
    137139      REAL,EXTERNAL :: SSUM 
    138140 
     
    140142 
    141143      INTEGER,SAVE :: i_co2ice=0      ! co2 ice 
     144!$OMP THREADPRIVATE(i_co2ice) 
    142145      CHARACTER(LEN=20) :: tracername ! to temporarily store text 
    143146 
     
    205208!     zcondices(ngrid)     condensation rate on the ground  (kg/m2/s) 
    206209!     zfallice(ngrid)      flux of ice falling on surface   (kg/m2/s) 
    207 !     pdtc(ngrid,nlayermx) dT/dt due to phase changes       (K/s) 
     210!     pdtc(ngrid,nlayer) dT/dt due to phase changes       (K/s) 
    208211      
    209212 
     
    301304             
    302305!     sedimentation computed from radius computed from q in module radii_mod 
    303          call co2_reffrad(ngrid,nq,zq,reffrad) 
     306         call co2_reffrad(ngrid,nlayer,nq,zq,reffrad) 
    304307          
    305308         do  ilay=1,nlayer 
     
    321324!     Computing q after sedimentation 
    322325 
    323          call vlz_fi(ngrid,zq(1,1,i_co2ice),2.,masse,w(1,1,i_co2ice),wq) 
     326         call vlz_fi(ngrid,nlayer,zq(1,1,i_co2ice),2.,masse,w(1,1,i_co2ice),wq) 
    324327 
    325328 
Note: See TracChangeset for help on using the changeset viewer.