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/caldyn_gcm.f90

    r295 r327  
    201201      IF(caldyn_eta==eta_mass) THEN 
    202202         CALL send_message(f_ps,req_ps)  
    203          CALL wait_message(req_ps)   
    204203      ELSE 
    205204         CALL send_message(f_mass,req_mass)  
    206          CALL wait_message(req_mass)   
    207205      END IF 
    208206 
     207    CALL send_message(f_theta_rhodz,req_theta_rhodz)  
    209208    CALL send_message(f_u,req_u) 
    210     CALL wait_message(req_u) 
    211     CALL send_message(f_theta_rhodz,req_theta_rhodz)  
    212     CALL wait_message(req_theta_rhodz)  
    213      
    214 !    CALL wait_message(req_u) 
    215 !    CALL wait_message(req_theta_rhodz)  
    216209 
    217210    SELECT CASE(caldyn_conserv) 
     
    232225 
    233226       CALL send_message(f_qu,req_qu) 
    234        CALL wait_message(req_qu) 
     227!       CALL wait_message(req_qu) 
    235228 
    236229       DO ind=1,ndomain 
     
    364357 
    365358  IF(caldyn_eta==eta_mass) THEN 
    366 !     CALL wait_message(req_ps)   
     359     CALL wait_message(req_ps)   
    367360  ELSE 
    368 !     CALL wait_message(req_mass) 
     361     CALL wait_message(req_mass) 
    369362  END IF 
    370 !  CALL wait_message(req_theta_rhodz)  
     363  CALL wait_message(req_theta_rhodz)  
    371364 
    372365  IF(caldyn_eta==eta_mass) THEN ! Compute mass & theta 
    373366     DO l = ll_begin,ll_end 
    374 !        CALL test_message(req_u)  
     367        CALL test_message(req_u)  
    375368!DIR$ SIMD 
    376369        DO ij=ij_begin_ext,ij_end_ext 
     
    382375  ELSE ! Compute only theta 
    383376     DO l = ll_begin,ll_end 
    384 !        CALL test_message(req_u)  
     377        CALL test_message(req_u)  
    385378!DIR$ SIMD 
    386379       DO ij=ij_begin_ext,ij_end_ext 
     
    390383  END IF 
    391384 
    392 !  CALL wait_message(req_u)    
     385  CALL wait_message(req_u)    
    393386   
    394387!!! Compute shallow-water potential vorticity 
     
    446439    INTEGER :: i,j,ij,l 
    447440    REAL(rstd) :: p_ik, exner_ik 
     441    INTEGER,SAVE ::ij_omp_begin_ext, ij_omp_end_ext 
     442!$OMP THREADPRIVATE(ij_omp_begin_ext, ij_omp_end_ext) 
     443    LOGICAL,SAVE :: first=.TRUE. 
     444!$OMP THREADPRIVATE(first) 
     445 
    448446 
    449447    CALL trace_start("compute_geopot") 
     448     
     449    IF (first) THEN 
     450      first=.FALSE. 
     451      CALL distrib_level(ij_end_ext-ij_begin_ext+1,ij_omp_begin_ext,ij_omp_end_ext) 
     452      ij_omp_begin_ext=ij_omp_begin_ext+ij_begin_ext-1 
     453      ij_omp_end_ext=ij_omp_end_ext+ij_begin_ext-1 
     454    ENDIF 
    450455 
    451456    IF(caldyn_eta==eta_mass) THEN 
    452457 
    453458!!! Compute exner function and geopotential 
    454        IF (is_omp_level_master) THEN ! no openMP on vertical due to dependency 
    455459         DO l = 1,llm 
    456 !         !$OMP DO SCHEDULE(STATIC)  
    457460          !DIR$ SIMD 
    458             DO ij=ij_begin_ext,ij_end_ext          
     461            DO ij=ij_omp_begin_ext,ij_omp_end_ext          
    459462               p_ik = ptop + mass_ak(l) + mass_bk(l)*ps(ij) ! FIXME : leave ps for the moment ; change ps to Ms later 
    460463               !         p_ik = ptop + g*(mass_ak(l)+ mass_bk(l)*ps(i,j)) 
     
    465468          ENDDO 
    466469         ENDDO 
    467        ENDIF 
     470!       ENDIF 
    468471    ELSE  
    469472       ! We are using a Lagrangian vertical coordinate 
     
    474477       IF(boussinesq) THEN ! compute only geopotential : pressure pk will be computed in compute_caldyn_horiz 
    475478          ! specific volume 1 = dphi/g/rhodz 
    476          IF (is_omp_level_master) THEN ! no openMP on vertical due to dependency 
    477            DO l = 1,llm 
    478 !             !$OMP DO SCHEDULE(STATIC)  
    479              !DIR$ SIMD 
    480              DO ij=ij_begin_ext,ij_end_ext          
    481                 geopot(ij,l+1) = geopot(ij,l) + g*rhodz(ij,l) 
    482              ENDDO 
     479!         IF (is_omp_level_master) THEN ! no openMP on vertical due to dependency 
     480         DO l = 1,llm 
     481           !DIR$ SIMD 
     482           DO ij=ij_omp_begin_ext,ij_omp_end_ext          
     483              geopot(ij,l+1) = geopot(ij,l) + g*rhodz(ij,l) 
    483484           ENDDO 
    484          ENDIF 
     485         ENDDO 
    485486       ELSE ! non-Boussinesq, compute geopotential and Exner pressure 
    486487          ! uppermost layer 
    487          IF (is_omp_level_master) THEN  ! no openMP on vertical due to dependency 
    488  
     488 
     489         !DIR$ SIMD 
     490         DO ij=ij_omp_begin_ext,ij_omp_end_ext          
     491            pk(ij,llm) = ptop + (.5*g)*rhodz(ij,llm) 
     492         END DO 
     493         ! other layers 
     494         DO l = llm-1, 1, -1 
     495            !DIR$ SIMD 
     496            DO ij=ij_omp_begin_ext,ij_omp_end_ext          
     497               pk(ij,l) = pk(ij,l+1) + (.5*g)*(rhodz(ij,l)+rhodz(ij,l+1)) 
     498            END DO 
     499         END DO 
     500        ! surface pressure (for diagnostics) 
     501         DO ij=ij_omp_begin_ext,ij_omp_end_ext          
     502            ps(ij) = pk(ij,1) + (.5*g)*rhodz(ij,1) 
     503         END DO 
     504 
     505         ! specific volume v = kappa*theta*pi/p = dphi/g/rhodz 
     506         DO l = 1,llm 
    489507           !DIR$ SIMD 
    490            DO ij=ij_begin_ext,ij_end_ext          
    491               pk(ij,llm) = ptop + (.5*g)*rhodz(ij,llm) 
    492            END DO 
    493            ! other layers 
    494            DO l = llm-1, 1, -1 
    495  
    496 !           !$OMP DO SCHEDULE(STATIC)  
    497               !DIR$ SIMD 
    498               DO ij=ij_begin_ext,ij_end_ext          
    499                  pk(ij,l) = pk(ij,l+1) + (.5*g)*(rhodz(ij,l)+rhodz(ij,l+1)) 
    500               END DO 
    501            END DO 
    502           ! surface pressure (for diagnostics) 
    503            DO ij=ij_begin_ext,ij_end_ext          
    504               ps(ij) = pk(ij,1) + (.5*g)*rhodz(ij,1) 
    505            END DO 
    506  
    507           ! specific volume v = kappa*theta*pi/p = dphi/g/rhodz 
    508            DO l = 1,llm 
    509  
    510 !             !$OMP DO SCHEDULE(STATIC)  
    511              !DIR$ SIMD 
    512               DO ij=ij_begin_ext,ij_end_ext          
    513                  p_ik = pk(ij,l) 
    514                  exner_ik = cpp * (p_ik/preff) ** kappa 
    515                  geopot(ij,l+1) = geopot(ij,l) + (g*kappa)*rhodz(ij,l)*theta(ij,l)*exner_ik/p_ik  
    516                  pk(ij,l) = exner_ik 
    517               ENDDO 
     508            DO ij=ij_omp_begin_ext,ij_omp_end_ext          
     509               p_ik = pk(ij,l) 
     510               exner_ik = cpp * (p_ik/preff) ** kappa 
     511               geopot(ij,l+1) = geopot(ij,l) + (g*kappa)*rhodz(ij,l)*theta(ij,l)*exner_ik/p_ik  
     512               pk(ij,l) = exner_ik 
    518513            ENDDO 
    519           ENDIF 
     514          ENDDO 
    520515       END IF 
    521516 
     
    562557  DO l = ll_begin, ll_end 
    563558!!!  Compute mass and theta fluxes 
    564 !    IF (caldyn_conserv==energy) CALL test_message(req_qu)  
     559    IF (caldyn_conserv==energy) CALL test_message(req_qu)  
    565560!DIR$ SIMD 
    566561    DO ij=ij_begin_ext,ij_end_ext          
     
    602597    CASE(energy) ! energy-conserving TRiSK 
    603598 
    604 !       CALL wait_message(req_qu) 
     599       CALL wait_message(req_qu) 
    605600 
    606601        DO l=ll_begin,ll_end 
     
    796791    REAL(rstd),INTENT(INOUT) :: wflux(iim*jjm,llm+1) ! vertical mass flux (kg/m2/s) 
    797792    REAL(rstd),INTENT(INOUT) :: wwuu(iim*3*jjm,llm+1) 
    798     REAL(rstd),INTENT(OUT) :: du(iim*3*jjm,llm) 
    799     REAL(rstd),INTENT(OUT) :: dtheta_rhodz(iim*jjm,llm) 
     793    REAL(rstd),INTENT(INOUT) :: du(iim*3*jjm,llm) 
     794    REAL(rstd),INTENT(INOUT) :: dtheta_rhodz(iim*jjm,llm) 
    800795    REAL(rstd),INTENT(OUT) :: dps(iim*jjm) 
    801796 
     
    803798    INTEGER :: i,j,ij,l 
    804799    REAL(rstd) :: p_ik, exner_ik 
     800    INTEGER,SAVE ::ij_omp_begin, ij_omp_end 
     801!$OMP THREADPRIVATE(ij_omp_begin, ij_omp_end) 
     802    LOGICAL,SAVE :: first=.TRUE. 
     803!$OMP THREADPRIVATE(first) 
     804 
     805 
     806    CALL trace_start("compute_geopot") 
     807     
     808    IF (first) THEN 
     809      first=.FALSE. 
     810      CALL distrib_level(ij_end-ij_begin+1,ij_omp_begin,ij_omp_end) 
     811      ij_omp_begin=ij_omp_begin+ij_begin-1 
     812      ij_omp_end=ij_omp_end+ij_begin-1 
     813    ENDIF 
    805814 
    806815!    REAL(rstd) :: wwuu(iim*3*jjm,llm+1) ! tmp var, don't know why but gain 30% on the whole code in opemp 
     
    812821!$OMP BARRIER    
    813822!!! cumulate mass flux convergence from top to bottom 
    814   IF (is_omp_level_master) THEN 
     823!  IF (is_omp_level_master) THEN 
    815824    DO  l = llm-1, 1, -1 
    816825!    IF (caldyn_conserv==energy) CALL test_message(req_qu)  
     
    818827!!$OMP DO SCHEDULE(STATIC)  
    819828!DIR$ SIMD 
    820       DO ij=ij_begin,ij_end          
     829      DO ij=ij_omp_begin,ij_omp_end          
    821830          convm(ij,l) = convm(ij,l) + convm(ij,l+1) 
    822831      ENDDO 
    823832    ENDDO 
    824   ENDIF 
     833!  ENDIF 
    825834 
    826835!$OMP BARRIER 
Note: See TracChangeset for help on using the changeset viewer.