Ignore:
Timestamp:
02/09/15 20:18:34 (9 years ago)
Author:
ymipsl
Message:

Merge recent developments from saturn branch onto trunk.

  • lmdz generic physics interface
  • performance improvment on mix mpi/openmp
  • asynchrone and overlaping communication
  • best domain distribution between process and threads
  • ....

This version is compatible with the actual saturn version and the both branches are considered merged on dynamico component.

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/timeloop_gcm.f90

    r326 r327  
    4040  USE write_field 
    4141  USE theta2theta_rhodz_mod 
     42  USE sponge_mod 
    4243  IMPLICIT NONE 
    4344 
     
    111112           f_psm2 => f_phis 
    112113        END IF 
     114      CASE ('none') 
     115        nb_stage=0 
    113116 
    114117    CASE default 
     
    120123    CALL init_theta2theta_rhodz 
    121124    CALL init_dissip 
     125    CALL init_sponge 
    122126    CALL init_caldyn 
    123127    CALL init_guided 
    124128    CALL init_advect_tracer 
    125129    CALL init_check_conserve 
    126     CALL init_physics 
    127      
    128130 
    129131    CALL etat0(f_ps,f_mass,f_phis,f_theta_rhodz,f_u, f_q) 
     
    144146  USE icosa 
    145147  USE dissip_gcm_mod 
     148  USE sponge_mod 
    146149  USE disvert_mod 
    147150  USE caldyn_mod 
     
    176179    INTEGER :: rate_clock 
    177180    INTEGER :: l 
     181    LOGICAL,SAVE :: first_physic=.TRUE. 
     182!$OMP THREADPRIVATE(first_physic)     
    178183     
    179      
    180 !    CALL write_etat0(f_ps, f_phis,f_theta_rhodz,f_u,f_q)  
    181 !    CALL read_start(f_ps,f_mass,f_phis,f_theta_rhodz,f_u,f_q)  
    182 !    CALL write_restart(f_ps,f_mass,f_phis,f_theta_rhodz,f_u,f_q)  
    183      
     184    
    184185    CALL switch_omp_distrib_level 
    185186    CALL caldyn_BC(f_phis, f_wflux) ! set constant values in first/last interfaces 
     
    228229      CALL wait_message(req_q0)  
    229230 
    230 !      CALL wait_message(req_ps0) 
    231 !      CALL wait_message(req_mass0) 
    232 !      CALL wait_message(req_theta_rhodz0)  
    233 !      CALL wait_message(req_u0) 
    234 !      CALL wait_message(req_q0)  
    235231    ENDIF 
    236232 
     
    264260 
    265261    IF (MOD(it,itau_dissip)==0) THEN 
    266 !         CALL send_message(f_ps,req_ps) 
    267 !         CALL wait_message(req_ps)   
    268262        
    269263       IF(caldyn_eta==eta_mass) THEN 
     
    278272          END DO 
    279273       ENDIF 
    280 !       CALL send_message(f_mass,req_mass) 
    281 !       CALL wait_message(req_mass)   
     274 
    282275       CALL dissip(f_u,f_du,f_mass,f_phis, f_theta_rhodz,f_dtheta_rhodz) 
    283276 
    284 !       CALL send_message(f_mass,req_mass) 
    285 !       CALL wait_message(req_mass)   
    286277       CALL euler_scheme(.FALSE.)  ! update only u, theta 
     278       IF (iflag_sponge > 0) THEN 
     279         CALL sponge(f_u,f_du,f_theta_rhodz,f_dtheta_rhodz) 
     280         CALL euler_scheme(.FALSE.)  ! update only u, theta 
     281       ENDIF 
    287282    END IF 
    288283 
     
    308303    END IF 
    309304 
    310     CALL physics(it,f_phis, f_ps, f_theta_rhodz, f_u,  f_q) 
    311305 
    312306    IF (MOD(it,itau_check_conserv)==0) THEN 
    313       CALL check_conserve(f_ps,f_dps,f_u,f_theta_rhodz,f_phis,it)   
     307      CALL check_conserve(f_ps,f_dps,f_u,f_theta_rhodz,f_phis,it)  
     308    ENDIF 
     309      
     310    IF (MOD(it,itau_physics)==0) THEN 
     311      CALL physics(it,f_phis, f_ps, f_theta_rhodz, f_u, f_wflux, f_q) 
     312 
     313!$OMP MASTER 
     314   IF (first_physic) CALL SYSTEM_CLOCK(start_clock) 
     315!$OMP END MASTER    
     316      first_physic=.FALSE. 
    314317    ENDIF 
    315318     
     
    354357          ELSE ! update mass 
    355358             mass=f_mass(ind) ; dmass=f_dmass(ind) ;               
    356              DO l=1,llm 
     359             DO l=ll_begin,ll_end 
    357360!$SIMD 
    358361                DO ij=ij_begin,ij_end 
     
    606609  END SUBROUTINE accumulate_fluxes 
    607610   
    608 !  FUNCTION maxval_i(p) 
    609 !    USE icosa 
    610 !    IMPLICIT NONE 
    611 !    REAL(rstd), DIMENSION(iim*jjm) :: p 
    612 !    REAL(rstd) :: maxval_i 
    613 !    INTEGER :: j, ij 
    614 !     
    615 !    maxval_i=p((jj_begin-1)*iim+ii_begin) 
    616 !     
    617 !    DO j=jj_begin-1,jj_end+1 
    618 !       ij=(j-1)*iim 
    619 !       maxval_i = MAX(maxval_i, MAXVAL(p(ij+ii_begin:ij+ii_end))) 
    620 !    END DO 
    621 !  END FUNCTION maxval_i 
    622  
    623 !  FUNCTION maxval_ik(p) 
    624 !    USE icosa 
    625 !    IMPLICIT NONE 
    626 !    REAL(rstd) :: p(iim*jjm, llm) 
    627 !    REAL(rstd) :: maxval_ik(llm) 
    628 !    INTEGER :: l,j, ij 
    629 !     
    630 !    DO l=1,llm 
    631 !       maxval_ik(l)=p((jj_begin-1)*iim+ii_begin,l) 
    632 !       DO j=jj_begin-1,jj_end+1 
    633 !          ij=(j-1)*iim 
    634 !          maxval_ik(l) = MAX(maxval_ik(l), MAXVAL(p(ij+ii_begin:ij+ii_end,l))) 
    635 !       END DO 
    636 !    END DO 
    637 !  END FUNCTION maxval_ik 
    638  
    639611END MODULE timeloop_gcm_mod 
Note: See TracChangeset for help on using the changeset viewer.