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/phylmd
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/atm2geo.F90

    • Property svn:keywords changed from Author Date Id Revision to Id
    r2346 r2429  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44SUBROUTINE atm2geo ( im, jm, pte, ptn, plon, plat, pxx, pyy, pzz )
     
    3232 
    3333! Value at North Pole 
    34   IF (is_north_pole) THEN
     34  IF (is_north_pole_dyn) THEN
    3535     pxx(:, 1) = - pte (1, 1)
    3636     pyy(:, 1) = - ptn (1, 1)
     
    3939
    4040! Value at South Pole
    41   IF (is_south_pole) THEN
     41  IF (is_south_pole_dyn) THEN
    4242     pxx(:,jm) = pxx(1,jm)
    4343     pyy(:,jm) = pyy(1,jm)
  • LMDZ5/trunk/libf/phylmd/cpl_mod.F90

    r2399 r2429  
    11151115   
    11161116      IF (is_parallel) THEN
    1117          IF (.NOT. is_north_pole) THEN
     1117         IF (.NOT. is_north_pole_dyn) THEN
    11181118#ifdef CPP_MPI
    11191119            CALL MPI_RECV(Up,1,MPI_REAL_LMDZ,mpi_rank-1,1234,COMM_LMDZ_PHY,status,error)
     
    11221122         ENDIF
    11231123       
    1124          IF (.NOT. is_south_pole) THEN
     1124         IF (.NOT. is_south_pole_dyn) THEN
    11251125#ifdef CPP_MPI
    11261126            CALL MPI_SEND(tmp_calv(1,jj_nb),1,MPI_REAL_LMDZ,mpi_rank+1,1234,COMM_LMDZ_PHY,error)
     
    11291129         ENDIF
    11301130         
    1131          IF (.NOT. is_north_pole .AND. ii_begin /=1) THEN
     1131         IF (.NOT. is_north_pole_dyn .AND. ii_begin /=1) THEN
    11321132            Up=Up+tmp_calv(nbp_lon,1)
    11331133            tmp_calv(:,1)=Up
    11341134         ENDIF
    11351135         
    1136          IF (.NOT. is_south_pole .AND. ii_end /= nbp_lon) THEN
     1136         IF (.NOT. is_south_pole_dyn .AND. ii_end /= nbp_lon) THEN
    11371137            Down=Down+tmp_calv(1,jj_nb)
    11381138            tmp_calv(:,jj_nb)=Down       
     
    12221222
    12231223    IF (is_sequential) THEN
    1224        IF (is_north_pole) tmp_lon(:,1)     = tmp_lon(:,2)
    1225        IF (is_south_pole) tmp_lon(:,nbp_lat) = tmp_lon(:,nbp_lat-1)
     1224       IF (is_north_pole_dyn) tmp_lon(:,1)     = tmp_lon(:,2)
     1225       IF (is_south_pole_dyn) tmp_lon(:,nbp_lat) = tmp_lon(:,nbp_lat-1)
    12261226    ENDIF
    12271227     
     
    13891389    CALL Grid1Dto2D_mpi(temp_mpi,champ_out)
    13901390   
    1391     IF (is_north_pole) champ_out(:,1)=temp_mpi(1)
    1392     IF (is_south_pole) champ_out(:,jj_nb)=temp_mpi(klon)
     1391    IF (is_north_pole_dyn) champ_out(:,1)=temp_mpi(1)
     1392    IF (is_south_pole_dyn) champ_out(:,jj_nb)=temp_mpi(klon)
    13931393!$OMP END MASTER
    13941394   
  • LMDZ5/trunk/libf/phylmd/geo2atm.F90

    r2346 r2429  
    3737
    3838  ! Value at North Pole
    39   IF (is_north_pole) THEN
     39  IF (is_north_pole_dyn) THEN
    4040     pu(:, 1) = -px (1,1)
    4141     pv(:, 1) = -py (1,1)
     
    4444 
    4545  ! Value at South Pole     
    46   IF (is_south_pole) THEN
     46  IF (is_south_pole_dyn) THEN
    4747     pu(:,jm) = -px (1,jm)
    4848     pv(:,jm) = -py (1,jm)
  • LMDZ5/trunk/libf/phylmd/iophy.F90

    r2350 r2429  
    4444                                jj_nb, jj_begin, jj_end, ii_begin, ii_end, &
    4545                                mpi_size, mpi_rank, klon_mpi, &
    46                                 is_sequential, is_south_pole
     46                                is_sequential, is_south_pole_dyn
    4747  USE mod_grid_phy_lmdz, only: nbp_lon, nbp_lat, klon_glo
    4848  USE print_control_mod, ONLY: prt_level,lunout
     
    144144      write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
    145145      write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
    146       write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," is_south_pole=",is_south_pole
     146      write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," is_south_pole=",is_south_pole_dyn
    147147    endif
    148148
     
    151151                            1, nbp_lon, ii_begin, ii_end, jj_begin, jj_end,             &
    152152                            klon_mpi+2*(nbp_lon-1), data_ibegin, data_iend,             &
    153                             io_lat, io_lon,is_south_pole,mpi_rank)
     153                            io_lat, io_lon,is_south_pole_dyn,mpi_rank)
    154154#endif
    155155!$OMP END MASTER
  • LMDZ5/trunk/libf/phylmd/oasis.F90

    r2371 r2429  
    342342   
    343343    istart=ii_begin
    344     IF (is_south_pole) THEN
     344    IF (is_south_pole_dyn) THEN
    345345       iend=(jj_end-jj_begin)*nbp_lon+nbp_lon
    346346    ELSE
     
    408408
    409409    istart=ii_begin
    410     IF (is_south_pole) THEN
     410    IF (is_south_pole_dyn) THEN
    411411       iend=(jj_end-jj_begin)*nbp_lon+nbp_lon
    412412    ELSE
     
    417417       wstart=istart
    418418       wend=iend
    419        IF (is_north_pole) wstart=istart+nbp_lon-1
    420        IF (is_south_pole) wend=iend-nbp_lon+1
     419       IF (is_north_pole_dyn) wstart=istart+nbp_lon-1
     420       IF (is_south_pole_dyn) wend=iend-nbp_lon+1
    421421       
    422422       DO i = 1, maxsend
  • LMDZ5/trunk/libf/phylmd/phys_output_write_mod.F90

    r2393 r2429  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44MODULE phys_output_write_mod
     
    2525
    2626    USE dimphy, only: klon, klev, klevp1, nslay
     27    USE mod_phys_lmdz_para, ONLY: is_north_pole_phy,is_south_pole_phy
    2728    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    2829    USE time_phylmdz_mod, only: day_step_phy, start_time, itau_phy
     
    348349!!! Champs 1D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    349350       CALL histwrite_phy(o_phis, pphis)
    350        CALL histwrite_phy(o_aire, cell_area)
     351
     352       zx_tmp_fi2d = cell_area
     353       if (is_north_pole_phy) then
     354         zx_tmp_fi2d(1) = cell_area(1)/nbp_lon
     355       endif
     356       if (is_south_pole_phy) then
     357         zx_tmp_fi2d(klon) = cell_area(klon)/nbp_lon
     358       endif
     359       CALL histwrite_phy(o_aire, zx_tmp_fi2d)
    351360
    352361       IF (vars_defined) THEN
Note: See TracChangeset for help on using the changeset viewer.