Ignore:
Timestamp:
10/31/14 14:52:01 (10 years ago)
Author:
ymipsl
Message:

Merging OpenMP parallisme mode : by subdomain and on vertical level.
This feature is actually experimental but may be retro-compatible with the last method based only on subdomain

YM

File:
1 edited

Legend:

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

    r286 r295  
    3333    USE exner_mod 
    3434    USE mpipara 
     35    USE omp_para 
    3536    IMPLICIT NONE 
    3637    CHARACTER(len=255) :: def 
     
    5051       STOP 
    5152    END SELECT 
    52     IF (is_mpi_root) PRINT *, 'caldyn_conserv=',def 
     53    IF (is_master) PRINT *, 'caldyn_conserv=',def 
    5354 
    5455    CALL allocate_caldyn 
     
    7273    CALL allocate_field(f_qv,field_z,type_real,llm)  
    7374   
    74     CALL allocate_field(f_buf_i,   field_t,type_real,llm) 
     75    CALL allocate_field(f_buf_i,   field_t,type_real,llm,name="buffer_i") 
    7576    CALL allocate_field(f_buf_p,   field_t,type_real,llm+1)  
    7677    CALL allocate_field(f_buf_u3d, field_t,type_real,3,llm)  ! 3D vel at cell centers 
     
    102103    INTEGER :: ind,i,j,ij,l 
    103104 
    104     IF (omp_first) THEN 
     105    IF (is_omp_first_level) THEN 
    105106       DO ind=1,ndomain 
    106107          IF (.NOT. assigned_domain(ind)) CYCLE 
     
    128129    ENDIF 
    129130 
    130 !    !$OMP BARRIER 
     131    !$OMP BARRIER 
    131132  END SUBROUTINE caldyn_BC 
    132133    
     
    143144    USE omp_para 
    144145    USE output_field_mod 
     146    USE checksum_mod 
    145147    IMPLICIT NONE 
    146148    LOGICAL,INTENT(IN)    :: write_out 
     
    291293    END SELECT 
    292294 
    293 !!$OMP BARRIER 
     295!$OMP BARRIER 
    294296    IF (write_out) THEN 
    295297 
    296        IF (is_mpi_root) PRINT *,'CALL write_output_fields' 
     298       IF (is_master) PRINT *,'CALL write_output_fields' 
    297299 
    298300! ---> for openMP test to fix later 
     
    450452 
    451453!!! Compute exner function and geopotential 
    452        DO l = 1,llm 
     454       IF (is_omp_level_master) THEN ! no openMP on vertical due to dependency 
     455         DO l = 1,llm 
    453456!         !$OMP DO SCHEDULE(STATIC)  
    454457          !DIR$ SIMD 
    455           DO ij=ij_begin_ext,ij_end_ext          
    456              p_ik = ptop + mass_ak(l) + mass_bk(l)*ps(ij) ! FIXME : leave ps for the moment ; change ps to Ms later 
    457              !         p_ik = ptop + g*(mass_ak(l)+ mass_bk(l)*ps(i,j)) 
    458              exner_ik = cpp * (p_ik/preff) ** kappa 
    459              pk(ij,l) = exner_ik 
     458            DO ij=ij_begin_ext,ij_end_ext          
     459               p_ik = ptop + mass_ak(l) + mass_bk(l)*ps(ij) ! FIXME : leave ps for the moment ; change ps to Ms later 
     460               !         p_ik = ptop + g*(mass_ak(l)+ mass_bk(l)*ps(i,j)) 
     461               exner_ik = cpp * (p_ik/preff) ** kappa 
     462               pk(ij,l) = exner_ik 
    460463             ! specific volume v = kappa*theta*pi/p = dphi/g/rhodz 
    461              geopot(ij,l+1) = geopot(ij,l) + (g*kappa)*rhodz(ij,l)*theta(ij,l)*exner_ik/p_ik 
     464               geopot(ij,l+1) = geopot(ij,l) + (g*kappa)*rhodz(ij,l)*theta(ij,l)*exner_ik/p_ik 
    462465          ENDDO 
    463        ENDDO 
    464  
     466         ENDDO 
     467       ENDIF 
    465468    ELSE  
    466469       ! We are using a Lagrangian vertical coordinate 
     
    471474       IF(boussinesq) THEN ! compute only geopotential : pressure pk will be computed in compute_caldyn_horiz 
    472475          ! specific volume 1 = dphi/g/rhodz 
    473           DO l = 1,llm 
     476         IF (is_omp_level_master) THEN ! no openMP on vertical due to dependency 
     477           DO l = 1,llm 
    474478!             !$OMP DO SCHEDULE(STATIC)  
    475479             !DIR$ SIMD 
     
    477481                geopot(ij,l+1) = geopot(ij,l) + g*rhodz(ij,l) 
    478482             ENDDO 
    479           ENDDO 
     483           ENDDO 
     484         ENDIF 
    480485       ELSE ! non-Boussinesq, compute geopotential and Exner pressure 
    481486          ! uppermost layer 
    482           !DIR$ SIMD 
    483           DO ij=ij_begin_ext,ij_end_ext          
    484              pk(ij,llm) = ptop + (.5*g)*rhodz(ij,llm) 
    485           END DO 
    486           ! other layers 
    487           DO l = llm-1, 1, -1 
    488  
    489 !          !$OMP DO SCHEDULE(STATIC)  
    490              !DIR$ SIMD 
    491              DO ij=ij_begin_ext,ij_end_ext          
    492                 pk(ij,l) = pk(ij,l+1) + (.5*g)*(rhodz(ij,l)+rhodz(ij,l+1)) 
    493              END DO 
    494           END DO 
     487         IF (is_omp_level_master) THEN  ! no openMP on vertical due to dependency 
     488 
     489           !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 
    495502          ! surface pressure (for diagnostics) 
    496           DO ij=ij_begin_ext,ij_end_ext          
    497              ps(ij) = pk(ij,1) + (.5*g)*rhodz(ij,1) 
    498           END DO 
     503           DO ij=ij_begin_ext,ij_end_ext          
     504              ps(ij) = pk(ij,1) + (.5*g)*rhodz(ij,1) 
     505           END DO 
    499506 
    500507          ! specific volume v = kappa*theta*pi/p = dphi/g/rhodz 
    501           DO l = 1,llm 
     508           DO l = 1,llm 
    502509 
    503510!             !$OMP DO SCHEDULE(STATIC)  
    504511             !DIR$ SIMD 
    505              DO ij=ij_begin_ext,ij_end_ext          
    506                 p_ik = pk(ij,l) 
    507                 exner_ik = cpp * (p_ik/preff) ** kappa 
    508                 geopot(ij,l+1) = geopot(ij,l) + (g*kappa)*rhodz(ij,l)*theta(ij,l)*exner_ik/p_ik  
    509                 pk(ij,l) = exner_ik 
    510              ENDDO 
    511           ENDDO 
     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 
     518            ENDDO 
     519          ENDIF 
    512520       END IF 
    513521 
    514522    END IF 
     523 
     524!ym flush geopot 
     525!$OMP BARRIER 
    515526 
    516527  CALL trace_end("compute_geopot") 
     
    799810  CALL trace_start("compute_caldyn_vert") 
    800811 
    801 !!$OMP BARRIER    
     812!$OMP BARRIER    
    802813!!! cumulate mass flux convergence from top to bottom 
    803   DO  l = llm-1, 1, -1 
     814  IF (is_omp_level_master) THEN 
     815    DO  l = llm-1, 1, -1 
    804816!    IF (caldyn_conserv==energy) CALL test_message(req_qu)  
    805817 
    806818!!$OMP DO SCHEDULE(STATIC)  
    807819!DIR$ SIMD 
    808     DO ij=ij_begin,ij_end          
    809         convm(ij,l) = convm(ij,l) + convm(ij,l+1) 
     820      DO ij=ij_begin,ij_end          
     821          convm(ij,l) = convm(ij,l) + convm(ij,l+1) 
     822      ENDDO 
    810823    ENDDO 
    811   ENDDO 
    812  
    813 ! IMPLICIT FLUSH on convm 
     824  ENDIF 
     825 
     826!$OMP BARRIER 
     827! FLUSH on convm 
    814828!!!!!!!!!!!!!!!!!!!!!!!!! 
    815829 
    816830! compute dps 
    817   IF (omp_first) THEN 
     831  IF (is_omp_first_level) THEN 
    818832!DIR$ SIMD 
    819833     DO ij=ij_begin,ij_end          
     
    834848  ENDDO 
    835849 
     850 !--> flush wflux   
     851 !$OMP BARRIER 
     852 
    836853  DO l=ll_begin,ll_endm1 
    837854!DIR$ SIMD 
     
    847864    ENDDO 
    848865  ENDDO 
     866 
    849867   
    850868! Compute vertical transport 
     
    859877 
    860878 !--> flush wwuu   
    861  ! !$OMP BARRIER 
     879 !$OMP BARRIER 
    862880 
    863881! Add vertical transport to du 
     
    10181036       ps = f_ps(ind) 
    10191037       p  = f_p(ind) 
     1038!$OMP BARRIER 
    10201039       CALL compute_pression(ps,p,0) 
    10211040       pk = f_pk(ind) 
    10221041       pks = f_pks(ind) 
     1042!$OMP BARRIER 
    10231043       CALL compute_exner(ps,p,pks,pk,0) 
     1044!$OMP BARRIER 
    10241045       theta_rhodz = f_theta_rhodz(ind) 
    10251046       theta = f_theta(ind) 
Note: See TracChangeset for help on using the changeset viewer.