Changeset 1851


Ignore:
Timestamp:
Aug 29, 2013, 4:48:39 PM (11 years ago)
Author:
Ehouarn Millour
Message:

OpenMP bug fix in iniaqua: local variables are shared by all threads only if they are static (ie with "save" attribute).
While at it, changed phyaqua.F into module phyaqua_mod.F
EM

Location:
LMDZ5/trunk/libf/phylmd
Files:
2 edited
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/iniphysiq.F

    r1671 r1851  
    1414     &                               klon_omp_end,klon_mpi_begin
    1515      USE comgeomphy, only : airephy,cuphy,cvphy,rlond,rlatd
    16 
     16      USE phyaqua_mod, only: iniaqua
    1717      IMPLICIT NONE
    1818c
  • LMDZ5/trunk/libf/phylmd/phyaqua_mod.F

    r1849 r1851  
     1      module phyaqua_mod
    12! Routines complementaires pour la physique planetaire.
    2 
     3      implicit none
     4
     5      contains
    36
    47      subroutine iniaqua(nlon,latfi,lonfi,iflag_phys)
     
    8992      integer, save::  read_climoz=0 ! read ozone climatology
    9093
    91 ! intermediate variables to use getin
    92       integer :: nbapp_rad_omp
    93       real :: co2_ppm_omp,solaire_omp
    94       logical :: alb_ocean_omp
    95       real :: rugos_omp
     94! intermediate variables to use getin (need to be "save" to be shared by all threads)
     95      integer,save :: nbapp_rad_omp
     96      real,save :: co2_ppm_omp,solaire_omp
     97      logical,save :: alb_ocean_omp
     98      real,save :: rugos_omp
    9699!-------------------------------------------------------------------------
    97100!  declaration pour l'appel a phyredem
     
    187190!$OMP BARRIER
    188191      co2_ppm=co2_ppm_omp
     192      write(*,*)"iniaqua: co2_ppm=",co2_ppm
    189193      solaire=solaire_omp
     194      write(*,*)"iniaqua: solaire=",solaire
    190195      alb_ocean=alb_ocean_omp
     196      write(*,*)"iniaqua: alb_ocean=",alb_ocean
    191197
    192198      radsol=0.
     
    229235!$OMP BARRIER
    230236      rugos=rugos_omp
     237      write(*,*) "iniaqua: rugos=",rugos
    231238      zmasq(:)=pctsrf(:,is_oce)
    232239
     
    359366
    360367      return
    361       end
     368      end subroutine iniaqua
    362369
    363370
     
    475482
    476483      RETURN
    477       END
     484      END subroutine zenang_an
    478485
    479486!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    486493      use mod_grid_phy_lmdz, only : klon_glo
    487494      use mod_phys_lmdz_transfert_para, only : gather
     495      implicit none
    488496!#include "dimensions.h"
    489497!#include "dimphy.h"
     
    504512      real :: phy_glo(klon_glo,360) ! temporary variable, to store phy_***(:)
    505513                                    ! on the whole physics grid
     514      integer :: k
    506515      INTEGER ierr
    507516      INTEGER dimfirst(3)
     
    564573c
    565574        ierr = NF_ENDDEF(nid)
     575        if (ierr.ne.NF_NOERR) then
     576          write(*,*) "writelim error: failed to end define mode"
     577          write(*,*) NF_STRERROR(ierr)
     578        endif
    566579c
    567580
     
    573586          ierr = NF_PUT_VAR1_REAL (nid,id_tim,k,FLOAT(k))
    574587#endif
     588         if (ierr.ne.NF_NOERR) then
     589           write(*,*) "writelim error with temps(k),k=",k
     590           write(*,*) NF_STRERROR(ierr)
     591         endif
    575592        enddo
    576593
     
    701718      endif
    702719
    703       end
     720      end subroutine writelim
    704721
    705722!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    717734c
    718735      if (klon.ne.nlon) stop'probleme de dimensions dans iniaqua'
     736      write(*,*)" profil_sst: type_profil=",type_profil
    719737      do i=1,360
    720738c      phy_sst(:,i) = 260.+50.*cos(rlatd(:))**2
     
    887905       amn=MIN(phy_sst(1,1),1000.)
    888906       amx=MAX(phy_sst(1,1),-1000.)
     907       imn=1 ; kmn=1 ; imx=1 ; kmx=1
    889908       DO k=1, 360
    890909       DO i=2, nlon
     
    902921       ENDDO
    903922c
    904        PRINT*,' debut avant writelim min max phy_sst',imn,kmn,amn,
    905      & imx,kmx,amx
     923       PRINT*,'profil_sst: imn, kmn, phy_sst(imn,kmn) ',imn,kmn,amn
     924       PRINT*,'profil_sst: imx, kmx, phy_sst(imx,kmx) ',imx,kmx,amx
    906925cIM end : verif profil SST: phy_sst
    907926
    908927       return
    909        end
     928       end subroutine profil_sst
     929     
     930      end module phyaqua_mod
  • LMDZ5/trunk/libf/phylmd/physiq.F

    r1849 r1851  
    4545      use conf_phys_m, only: conf_phys
    4646      use radlwsw_m, only: radlwsw
     47      use phyaqua_mod, only: zenang_an
    4748      USE control_mod
    4849#ifdef REPROBUS
Note: See TracChangeset for help on using the changeset viewer.