Ignore:
Timestamp:
Jan 27, 2016, 1:43:09 PM (8 years ago)
Author:
Laurent Fairhead
Message:

Correction on the calculation of the surface of the grid at the poles (problem was introduced
in r2222).
Due to the different distribution of OMP tasks in the dynamics and the physics, had to
introduce 2 new logical variables, is_pole_north_phy and is_pole_south_phy, and so decided
to rename the old is_north_pole/is_south_pole to is_north_pole_dyn/is_south_pole_dyn to
stay coherent and, hopefully, clear things up a bit.
LF

Location:
LMDZ5/trunk/libf/phy_common
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phy_common/mod_phys_lmdz_mpi_data.F90

    • Property svn:keywords changed from Author Date Id Revision to Id
    r2352 r2429  
    11!
    2 !$Header$
     2!$Id$
    33!
    44MODULE mod_phys_lmdz_mpi_data
     
    4141 
    4242 
    43   LOGICAL,SAVE :: is_north_pole
    44   LOGICAL,SAVE :: is_south_pole
     43!  LOGICAL,SAVE :: is_north_pole
     44!  LOGICAL,SAVE :: is_south_pole
     45  LOGICAL,SAVE :: is_north_pole_dyn
     46  LOGICAL,SAVE :: is_south_pole_dyn
    4547  INTEGER,SAVE :: COMM_LMDZ_PHY
    4648  INTEGER,SAVE :: MPI_REAL_LMDZ   ! MPI_REAL8
     
    109111   
    110112    IF (mpi_rank == 0) THEN
    111       is_north_pole = .TRUE.
    112     ELSE
    113       is_north_pole = .FALSE.
     113      is_north_pole_dyn = .TRUE.
     114    ELSE
     115      is_north_pole_dyn = .FALSE.
    114116    ENDIF
    115117   
    116118    IF (mpi_rank == mpi_size-1) THEN
    117       is_south_pole = .TRUE.
    118     ELSE
    119       is_south_pole = .FALSE.
     119      is_south_pole_dyn = .TRUE.
     120    ELSE
     121      is_south_pole_dyn = .FALSE.
    120122    ENDIF
    121123   
     
    217219    WRITE(lunout,*) 'mpi_master =', mpi_master
    218220    WRITE(lunout,*) 'is_mpi_root =', is_mpi_root
    219     WRITE(lunout,*) 'is_north_pole =', is_north_pole
    220     WRITE(lunout,*) 'is_south_pole =', is_south_pole
     221    WRITE(lunout,*) 'is_north_pole =', is_north_pole_dyn
     222    WRITE(lunout,*) 'is_south_pole =', is_south_pole_dyn
    221223    WRITE(lunout,*) 'COMM_LMDZ_PHY =', COMM_LMDZ_PHY
    222224 
  • LMDZ5/trunk/libf/phy_common/mod_phys_lmdz_mpi_transfert.F90

    • Property svn:keywords changed from Author Date Id Revision to Id
    r2351 r2429  
    11!
    2 !$Header$
     2!$Id$
    33!
    44MODULE mod_phys_lmdz_mpi_transfert
     
    16931693   
    16941694    offset=ii_begin
    1695     IF (is_north_pole) Offset=nbp_lon
     1695    IF (is_north_pole_dyn) Offset=nbp_lon
    16961696   
    16971697   
     
    17031703   
    17041704   
    1705     IF (is_north_pole) THEN
     1705    IF (is_north_pole_dyn) THEN
    17061706      DO i=1,dimsize
    17071707        DO ij=1,nbp_lon
     
    17111711    ENDIF
    17121712   
    1713     IF (is_south_pole) THEN
     1713    IF (is_south_pole_dyn) THEN
    17141714      DO i=1,dimsize
    17151715        DO ij=nbp_lon*(jj_nb-1)+1,nbp_lon*jj_nb
     
    17371737   
    17381738    offset=ii_begin
    1739     IF (is_north_pole) Offset=nbp_lon
     1739    IF (is_north_pole_dyn) Offset=nbp_lon
    17401740   
    17411741   
     
    17471747   
    17481748   
    1749     IF (is_north_pole) THEN
     1749    IF (is_north_pole_dyn) THEN
    17501750      DO i=1,dimsize
    17511751        DO ij=1,nbp_lon
     
    17551755    ENDIF
    17561756   
    1757     IF (is_south_pole) THEN
     1757    IF (is_south_pole_dyn) THEN
    17581758      DO i=1,dimsize
    17591759        DO ij=nbp_lon*(jj_nb-1)+1,nbp_lon*jj_nb
     
    17821782   
    17831783    offset=ii_begin
    1784     IF (is_north_pole) Offset=nbp_lon
     1784    IF (is_north_pole_dyn) Offset=nbp_lon
    17851785   
    17861786   
     
    17921792   
    17931793   
    1794     IF (is_north_pole) THEN
     1794    IF (is_north_pole_dyn) THEN
    17951795      DO i=1,dimsize
    17961796        DO ij=1,nbp_lon
     
    18001800    ENDIF
    18011801   
    1802     IF (is_south_pole) THEN
     1802    IF (is_south_pole_dyn) THEN
    18031803      DO i=1,dimsize
    18041804        DO ij=nbp_lon*(jj_nb-1)+1,nbp_lon*jj_nb
     
    18241824
    18251825    offset=ii_begin
    1826     IF (is_north_pole) offset=nbp_lon
     1826    IF (is_north_pole_dyn) offset=nbp_lon
    18271827
    18281828    DO i=1,dimsize
     
    18321832    ENDDO
    18331833
    1834     IF (is_north_pole) THEN
     1834    IF (is_north_pole_dyn) THEN
    18351835      DO i=1,dimsize
    18361836        VarOut(1,i)=VarIn(1,i)
     
    18541854
    18551855    offset=ii_begin
    1856     IF (is_north_pole) offset=nbp_lon
     1856    IF (is_north_pole_dyn) offset=nbp_lon
    18571857
    18581858    DO i=1,dimsize
     
    18621862    ENDDO
    18631863
    1864     IF (is_north_pole) THEN
     1864    IF (is_north_pole_dyn) THEN
    18651865      DO i=1,dimsize
    18661866         VarOut(1,i)=VarIn(1,i)
     
    18831883
    18841884    offset=ii_begin
    1885     IF (is_north_pole) offset=nbp_lon
     1885    IF (is_north_pole_dyn) offset=nbp_lon
    18861886
    18871887    DO i=1,dimsize
     
    18911891    ENDDO
    18921892
    1893     IF (is_north_pole) THEN
     1893    IF (is_north_pole_dyn) THEN
    18941894      DO i=1,dimsize
    18951895        VarOut(1,i)=VarIn(1,i)
  • LMDZ5/trunk/libf/phy_common/mod_phys_lmdz_omp_data.F90

    r2326 r2429  
    88  LOGICAL,SAVE :: is_omp_root
    99  LOGICAL,SAVE :: is_using_omp
     10  LOGICAL,SAVE :: is_north_pole_phy, is_south_pole_phy
    1011 
    1112  INTEGER,SAVE,DIMENSION(:),ALLOCATABLE :: klon_omp_para_nb
     
    1718  INTEGER,SAVE :: klon_omp_end
    1819!$OMP  THREADPRIVATE(omp_rank,klon_omp,is_omp_root,klon_omp_begin,klon_omp_end)
     20!$OMP  THREADPRIVATE(is_north_pole_phy, is_south_pole_phy)
    1921
    2022CONTAINS
    2123 
    2224  SUBROUTINE Init_phys_lmdz_omp_data(klon_mpi)
    23     USE dimphy
     25    USE dimphy
     26    USE mod_phys_lmdz_mpi_data, ONLY : is_north_pole_dyn, is_south_pole_dyn
    2427    IMPLICIT NONE
    2528    INTEGER, INTENT(in) :: klon_mpi
     
    4346        omp_size=OMP_GET_NUM_THREADS()
    4447!$OMP END MASTER
     48!$OMP BARRIER
    4549        omp_rank=OMP_GET_THREAD_NUM()   
    4650#else   
     
    6266
    6367!$OMP MASTER
     68
    6469    ALLOCATE(klon_omp_para_nb(0:omp_size-1))
    6570    ALLOCATE(klon_omp_para_begin(0:omp_size-1))
     
    8085!$OMP END MASTER
    8186!$OMP BARRIER
     87
     88   if ((is_north_pole_dyn) .AND. (omp_rank == 0 )) then
     89      is_north_pole_phy = .TRUE.
     90    else
     91      is_north_pole_phy = .FALSE.
     92    endif
     93    if ((is_south_pole_dyn) .AND. (omp_rank == omp_size-1)) then
     94      is_south_pole_phy = .TRUE.
     95    else
     96      is_south_pole_phy = .FALSE.
     97    endif
    8298   
    8399    klon_omp=klon_omp_para_nb(omp_rank)
  • LMDZ5/trunk/libf/phy_common/mod_phys_lmdz_para.F90

    • Property svn:keywords changed from Author Date Id Revision to Id
    r2351 r2429  
    11!
    2 !$Header$
     2! $Id$
    33!
    44MODULE mod_phys_lmdz_para
     
    1111  LOGICAL,SAVE :: is_parallel
    1212  LOGICAL,SAVE :: is_master
     13
    1314 
    1415!$OMP THREADPRIVATE(klon_loc,is_master)
     
    4142       is_parallel=.FALSE.
    4243     ENDIF
     44
     45
    4346     
    4447  END SUBROUTINE Init_phys_lmdz_para
Note: See TracChangeset for help on using the changeset viewer.