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/dyn3dmem/gcm.F

    r2222 r2225  
    11!
    2 ! $Id$
     2! $Id: $
    33!
    44c
     
    2323! Only INCA needs these informations (from the Earth's physics)
    2424      USE indice_sol_mod
     25      USE mod_phys_lmdz_omp_data, ONLY: klon_omp
    2526#endif
    2627
    2728#ifdef CPP_PHYS
    28       USE mod_grid_phy_lmdz
    29       USE mod_phys_lmdz_para, ONLY : klon_mpi_para_nb
    30       USE mod_phys_lmdz_omp_data, ONLY: klon_omp
    31       USE dimphy
    32       USE comgeomphy
     29!      USE mod_grid_phy_lmdz
     30!      USE mod_phys_lmdz_para, ONLY : klon_mpi_para_nb
     31!      USE dimphy
     32!      USE comgeomphy
    3333#endif
    3434      IMPLICIT NONE
     
    104104
    105105      LOGICAL lafin
    106 c      INTEGER ij,iq,l,i,j
    107       INTEGER i,j
    108 
    109106
    110107      real time_step, t_wrt, t_ops
    111 
    112 
    113       LOGICAL call_iniphys
    114       data call_iniphys/.true./
    115108
    116109c+jld variables test conservation energie
     
    135128
    136129c-----------------------------------------------------------------------
    137 c    variables pour l'initialisation de la physique :
    138 c    ------------------------------------------------
    139       INTEGER ngridmx
    140       PARAMETER( ngridmx = 2+(jjm-1)*iim - 1/jjm   )
    141       REAL zcufi(ngridmx),zcvfi(ngridmx)
    142       REAL latfi(ngridmx),lonfi(ngridmx)
    143       REAL airefi(ngridmx)
    144       SAVE latfi, lonfi, airefi
    145      
    146       INTEGER :: ierr
    147 
    148 
    149 c-----------------------------------------------------------------------
    150130c   Initialisations:
    151131c   ----------------
     
    164144c  ---------------------------------------
    165145c
    166 ! Ehouarn: dump possibility of using defrun
    167146      CALL conf_gcm( 99, .TRUE. )
    168147      if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm",
     
    181160#ifdef CPP_PHYS
    182161        CALL Init_Phys_lmdz(iim,jjp1,llm,mpi_size,distrib_phys)
    183 #endif
     162!#endif
     163!      CALL set_bands
     164!#ifdef CPP_PHYS
     165      CALL Init_interface_dyn_phys
     166#endif
     167      CALL barrier
     168
    184169      CALL set_bands
    185 #ifdef CPP_PHYS
    186       CALL Init_interface_dyn_phys
    187 #endif
    188       CALL barrier
    189 
    190170      if (mpi_rank==0) call WriteBands
    191171      call Set_Distrib(distrib_caldyn)
     
    195175c$OMP END PARALLEL
    196176
    197 #ifdef CPP_PHYS
    198 c$OMP PARALLEL
    199       call InitComgeomphy
    200 c$OMP END PARALLEL
    201 #endif
     177!#ifdef CPP_PHYS
     178!c$OMP PARALLEL
     179!      call InitComgeomphy ! now done in iniphysiq
     180!c$OMP END PARALLEL
     181!#endif
    202182
    203183c-----------------------------------------------------------------------
     
    420400c   Initialisation de la physique :
    421401c   -------------------------------
    422       IF (call_iniphys.and.(iflag_phys==1.or.iflag_phys>=100)) THEN
    423          latfi(1)=rlatu(1)
    424          lonfi(1)=0.
    425          zcufi(1) = cu(1)
    426          zcvfi(1) = cv(1)
    427          DO j=2,jjm
    428             DO i=1,iim
    429                latfi((j-2)*iim+1+i)= rlatu(j)
    430                lonfi((j-2)*iim+1+i)= rlonv(i)
    431                zcufi((j-2)*iim+1+i) = cu((j-1)*iip1+i)
    432                zcvfi((j-2)*iim+1+i) = cv((j-1)*iip1+i)
    433             ENDDO
    434          ENDDO
    435          latfi(ngridmx)= rlatu(jjp1)
    436          lonfi(ngridmx)= 0.
    437          zcufi(ngridmx) = cu(ip1jm+1)
    438          zcvfi(ngridmx) = cv(ip1jm-iim)
    439          CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,aire,airefi)
    440          ! Poles are single points on physics grid
    441          airefi(1)=sum(aire(1:iim))
    442          airefi(ngridmx)=sum(aire(ip1jmp1-(iim+1)+1:ip1jmp1-1))
    443 !         WRITE(lunout,*)
    444 !     .       'GCM: WARNING!!! vitesse verticale nulle dans la physique'
     402      IF ((iflag_phys==1).or.(iflag_phys>=100)) THEN
    445403! Physics:
    446404#ifdef CPP_PHYS
    447          CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys/nsplit_phys,
    448      &                latfi,lonfi,airefi,zcufi,zcvfi,rad,g,r,cpp,
    449      &                iflag_phys)
    450 #endif
    451          call_iniphys=.false.
    452       ENDIF ! of IF (call_iniphys.and.(iflag_phys==1.or.iflag_phys>=100))
     405         CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys/nsplit_phys,
     406     &                rlatu,rlonv,aire,cu,cv,rad,g,r,cpp,
     407     &                iflag_phys)
     408#endif
     409      ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100))
    453410
    454411
Note: See TracChangeset for help on using the changeset viewer.