Ignore:
Timestamp:
Mar 11, 2015, 3:55:23 PM (10 years ago)
Author:
Ehouarn Millour
Message:

Some cleanup and tidying up in the dynamics/physics interface.
EM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3dpar/gcm.F

    r2222 r2225  
    2424! Only INCA needs these informations (from the Earth's physics)
    2525      USE indice_sol_mod
     26      USE mod_phys_lmdz_omp_data, ONLY: klon_omp
    2627#endif
    2728
    2829#ifdef CPP_PHYS
    29       USE mod_grid_phy_lmdz
    30       USE mod_phys_lmdz_para, ONLY : klon_mpi_para_nb
    31       USE mod_phys_lmdz_omp_data, ONLY: klon_omp
    32       USE dimphy
    33       USE comgeomphy
     30!      USE mod_grid_phy_lmdz
     31!      USE mod_phys_lmdz_para, ONLY : klon_mpi_para_nb
     32!      USE dimphy
     33!      USE comgeomphy
    3434#endif
    3535      IMPLICIT NONE
     
    105105
    106106      LOGICAL lafin
    107 c      INTEGER ij,iq,l,i,j
    108       INTEGER i,j
    109 
    110107
    111108      real time_step, t_wrt, t_ops
    112109
    113 
    114       LOGICAL call_iniphys
    115       data call_iniphys/.true./
    116110
    117111c+jld variables test conservation energie
     
    136130
    137131c-----------------------------------------------------------------------
    138 c    variables pour l'initialisation de la physique :
    139 c    ------------------------------------------------
    140       INTEGER ngridmx
    141       PARAMETER( ngridmx = 2+(jjm-1)*iim - 1/jjm   )
    142       REAL zcufi(ngridmx),zcvfi(ngridmx)
    143       REAL latfi(ngridmx),lonfi(ngridmx)
    144       REAL airefi(ngridmx)
    145       SAVE latfi, lonfi, airefi
    146      
    147       INTEGER :: ierr
    148 
    149 
    150 c-----------------------------------------------------------------------
    151132c   Initialisations:
    152133c   ----------------
     
    181162#ifdef CPP_PHYS
    182163        CALL Init_Phys_lmdz(iim,jjp1,llm,mpi_size,distrib_phys)
    183 #endif
     164!#endif
     165!      CALL set_bands
     166!#ifdef CPP_PHYS
     167      CALL Init_interface_dyn_phys
     168#endif
     169      CALL barrier
     170
    184171      CALL set_bands
    185 #ifdef CPP_PHYS
    186       CALL Init_interface_dyn_phys
    187 #endif
    188       CALL barrier
    189 
    190172      if (mpi_rank==0) call WriteBands
    191173      call SetDistrib(jj_Nb_Caldyn)
     
    195177c$OMP END PARALLEL
    196178
    197 #ifdef CPP_PHYS
    198 c$OMP PARALLEL
    199       call InitComgeomphy
    200 c$OMP END PARALLEL
    201 #endif
     179!#ifdef CPP_PHYS
     180!c$OMP PARALLEL
     181!      call InitComgeomphy ! now done in iniphysiq
     182!c$OMP END PARALLEL
     183!#endif
    202184
    203185!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    419401c   Initialisation de la physique :
    420402c   -------------------------------
    421       IF (call_iniphys.and.(iflag_phys==1.or.iflag_phys>=100)) THEN
    422          latfi(1)=rlatu(1)
    423          lonfi(1)=0.
    424          zcufi(1) = cu(1)
    425          zcvfi(1) = cv(1)
    426          DO j=2,jjm
    427             DO i=1,iim
    428                latfi((j-2)*iim+1+i)= rlatu(j)
    429                lonfi((j-2)*iim+1+i)= rlonv(i)
    430                zcufi((j-2)*iim+1+i) = cu((j-1)*iip1+i)
    431                zcvfi((j-2)*iim+1+i) = cv((j-1)*iip1+i)
    432             ENDDO
    433          ENDDO
    434          latfi(ngridmx)= rlatu(jjp1)
    435          lonfi(ngridmx)= 0.
    436          zcufi(ngridmx) = cu(ip1jm+1)
    437          zcvfi(ngridmx) = cv(ip1jm-iim)
    438          CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,aire,airefi)
    439          ! Poles are single points on physics grid
    440          airefi(1)=sum(aire(1:iim))
    441          airefi(ngridmx)=sum(aire(ip1jmp1-(iim+1)+1:ip1jmp1-1))
    442 !         WRITE(lunout,*)
    443 !     .       'GCM: WARNING!!! vitesse verticale nulle dans la physique'
     403      IF ((iflag_phys==1).or.(iflag_phys>=100)) THEN
    444404! Physics:
    445405#ifdef CPP_PHYS
    446          CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys/nsplit_phys,
    447      &                latfi,lonfi,airefi,zcufi,zcvfi,rad,g,r,cpp,
     406         CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys/nsplit_phys,
     407     &                rlatu,rlonv,aire,cu,cv,rad,g,r,cpp,
    448408     &                iflag_phys)
    449409#endif
    450          call_iniphys=.false.
    451       ENDIF ! of IF (call_iniphys.and.(iflag_phys==1.or.iflag_phys>=100))
     410      ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100))
    452411
    453412
Note: See TracChangeset for help on using the changeset viewer.