Ignore:
Timestamp:
12/02/14 19:21:00 (10 years ago)
Author:
milmd
Message:

Less output messages are written. On 20000 cores it is better. In LMDZ, only master of MPI and OpenMP can write.

Location:
codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/dyn3d_common
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/dyn3d_common/disvert_noterre.F

    r222 r298  
    1212      use ioipsl_getincom 
    1313#endif 
     14      use mod_phys_lmdz_para, only : is_master 
    1415 
    1516      IMPLICIT NONE 
     
    5960      hybrid=.true. ! default value for hybrid (ie: use hybrid coordinates) 
    6061      CALL getin('hybrid',hybrid) 
    61       write(lunout,*) trim(modname),': hybrid=',hybrid 
     62      if (is_master) write(lunout,*) trim(modname),': hybrid=',hybrid 
    6263 
    6364! Ouverture possible de fichiers typiquement E.T. 
     
    8283c        <-> energie cinetique, d'apres la note de Frederic Hourdin... 
    8384 
    84          write(lunout,*)'*****************************' 
    85          write(lunout,*)'WARNING reading esasig.def' 
    86          write(lunout,*)'*****************************' 
     85         if (is_master) write(lunout,*)'*****************************' 
     86         if (is_master) write(lunout,*)'WARNING reading esasig.def' 
     87         if (is_master) write(lunout,*)'*****************************' 
    8788         READ(99,*) scaleheight 
    8889         READ(99,*) dz0 
     
    131132 
    132133      ELSE IF(ierr4.eq.0) then 
    133          write(lunout,*)'****************************' 
    134          write(lunout,*)'Reading z2sig.def' 
    135          write(lunout,*)'****************************' 
     134         if (is_master) write(lunout,*)'****************************' 
     135         if (is_master) write(lunout,*)'Reading z2sig.def' 
     136         if (is_master) write(lunout,*)'****************************' 
    136137 
    137138         READ(99,*) scaleheight 
     
    174175 
    175176      if (hybrid) then  ! use hybrid coordinates 
    176          write(lunout,*) "*********************************" 
    177          write(lunout,*) "Using hybrid vertical coordinates" 
    178          write(lunout,*)  
     177         if (is_master) write(lunout,*) "***************************" 
     178         if (is_master) write(lunout,*) "Using hybrid vertical", 
     179     &          " coordinates" 
     180         if (is_master) write(lunout,*)  
    179181c        Coordonnees hybrides avec mod 
    180182         DO l = 1, llm 
     
    187189         ap(llmp1) = 0. 
    188190      else ! use sigma coordinates 
    189          write(lunout,*) "********************************" 
    190          write(lunout,*) "Using sigma vertical coordinates" 
    191          write(lunout,*)  
     191         if (is_master) write(lunout,*) "***************************" 
     192         if (is_master) write(lunout,*) "Using sigma vertical", 
     193     &          " coordinates" 
     194         if (is_master) write(lunout,*)  
    192195c        Pour ne pas passer en coordonnees hybrides 
    193196         DO l = 1, llm 
     
    200203      bp(llmp1) =   0. 
    201204 
    202       write(lunout,*) trim(modname),': BP ' 
    203       write(lunout,*)  bp 
    204       write(lunout,*) trim(modname),': AP ' 
    205       write(lunout,*)  ap 
     205      if (is_master) write(lunout,*) trim(modname),': BP ' 
     206      if (is_master) write(lunout,*)  bp 
     207      if (is_master) write(lunout,*) trim(modname),': AP ' 
     208      if (is_master) write(lunout,*)  ap 
    206209 
    207210c     Calcul au milieu des couches : 
     
    226229      end if 
    227230 
    228       write(lunout,*) trim(modname),': BPs ' 
    229       write(lunout,*)  bps 
    230       write(lunout,*) trim(modname),': APs' 
    231       write(lunout,*)  aps 
     231      if (is_master) write(lunout,*) trim(modname),': BPs ' 
     232      if (is_master) write(lunout,*)  bps 
     233      if (is_master) write(lunout,*) trim(modname),': APs' 
     234      if (is_master) write(lunout,*)  aps 
    232235 
    233236      DO l = 1, llm 
     
    236239      ENDDO 
    237240 
    238       write(lunout,*)trim(modname),' : PRESNIVS'  
    239       write(lunout,*)presnivs  
    240       write(lunout,*)'Pseudo altitude of Presnivs : (for a scale ', 
    241      &                'height of ',scaleheight,' km)'  
    242       write(lunout,*)pseudoalt 
     241      if (is_master) write(lunout,*)trim(modname),' : PRESNIVS'  
     242      if (is_master) write(lunout,*)presnivs  
     243      if (is_master) write(lunout,*)'Pseudo altitude of Presnivs : ', 
     244     &          '(for a scale height of ',scaleheight,' km)'  
     245      if (is_master) write(lunout,*)pseudoalt 
    243246 
    244247c     -------------------------------------------------- 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/dyn3d_common/inigeom.F

    r222 r298  
    1616c 
    1717c 
     18      use mod_phys_lmdz_para, only : is_master 
    1819      IMPLICIT NONE 
    1920c 
     
    160161c 
    161162c 
    162       WRITE(6,3)  
     163      if (is_master) WRITE(6,3)  
    163164 3    FORMAT( // 10x,' ....  INIGEOM  date du 01/06/98   ..... ', 
    164165     * //5x,'   Calcul des elongations cu et cv  comme sommes des 4 ' / 
     
    183184      ENDIF 
    184185 
    185       WRITE(6,*) ' gamdi_gd ',gamdi_gdiv,gamdi_grot,gamdi_h,coefdis, 
    186      *  nitergdiv,nitergrot,niterh 
     186      if (is_master) WRITE(6,*) ' gamdi_gd ',gamdi_gdiv,gamdi_grot, 
     187     *  gamdi_h,coefdis,nitergdiv,nitergrot,niterh 
    187188c 
    188189      pi    = 2.* ASIN(1.) 
    189190c 
    190       WRITE(6,990)  
     191      if (is_master) WRITE(6,990)  
    191192 
    192193c     ---------------------------------------------------------------- 
     
    197198       IF( ysinus )  THEN 
    198199c 
    199         WRITE(6,*) ' ***  Inigeom ,  Y = Sinus ( Latitude ) *** ' 
     200        if (is_master) WRITE(6,*) ' ***  Inigeom ,  Y = Sinus ', 
     201     *          '( Latitude ) *** ' 
    200202c 
    201203c   .... utilisation de f(x,y )  avec  y  =  sinus de la latitude  ..... 
     
    207209       ELSE 
    208210c 
    209         WRITE(6,*) '*** Inigeom ,  Y = Latitude  , der. sinusoid . ***' 
     211        if (is_master) WRITE(6,*) '*** Inigeom ,  Y = Latitude  ,', 
     212     *          ' der. sinusoid . ***' 
    210213 
    211214c  .... utilisation  de f(x,y) a tangente sinusoidale , y etant la latit. ... 
     
    262265c   ..................................................................... 
    263266 
    264       WRITE(6,*)'*** Inigeom , Y = Latitude  , der.tg. hyperbolique ***' 
     267      if (is_master) WRITE(6,*)'*** Inigeom , Y = Latitude  ,', 
     268     *          ' der.tg. hyperbolique ***' 
    265269  
    266270       CALL fxyhyper( clat, grossismy, dzoomy, tauy    ,  
     
    656660c----------------------------------------------------------------------- 
    657661c 
     662       if (is_master) then 
    658663       WRITE(6,*) '   ***  Coordonnees de la grille  *** ' 
    659664       WRITE(6,995) 
     
    661666       WRITE(6,*) '   LONGITUDES  aux pts.   V  ( degres )  ' 
    662667       WRITE(6,995) 
     668       end if 
    663669        DO i=1,iip1 
    664670         rlonvv(i) = rlonv(i)*180./pi 
    665671        ENDDO 
    666        WRITE(6,400) rlonvv 
    667 c 
    668        WRITE(6,995) 
    669        WRITE(6,*) '   LATITUDES   aux pts.   V  ( degres )  ' 
    670        WRITE(6,995) 
     672       if (is_master) WRITE(6,400) rlonvv 
     673c 
     674       if (is_master) WRITE(6,995) 
     675       if (is_master) WRITE(6,*) '   LATITUDES   aux pts.   V  ', 
     676     *          '( degres )  ' 
     677       if (is_master) WRITE(6,995) 
    671678        DO i=1,jjm 
    672679         rlatuu(i)=rlatv(i)*180./pi 
    673680        ENDDO 
    674        WRITE(6,400) (rlatuu(i),i=1,jjm) 
     681       if (is_master) WRITE(6,400) (rlatuu(i),i=1,jjm) 
    675682c 
    676683        DO i=1,iip1 
    677684          rlonvv(i)=rlonu(i)*180./pi 
    678685        ENDDO 
     686       if (is_master) then 
    679687       WRITE(6,995) 
    680688       WRITE(6,*) '   LONGITUDES  aux pts.   U  ( degres )  ' 
     
    685693       WRITE(6,*) '   LATITUDES   aux pts.   U  ( degres )  ' 
    686694       WRITE(6,995) 
     695       end if 
     696       if (is_master) WRITE(6,995) 
    687697        DO i=1,jjp1 
    688698         rlatuu(i)=rlatu(i)*180./pi 
    689699        ENDDO 
    690        WRITE(6,400) (rlatuu(i),i=1,jjp1) 
    691        WRITE(6,995) 
     700       if (is_master) WRITE(6,400) (rlatuu(i),i=1,jjp1) 
     701       if (is_master) WRITE(6,995) 
    692702c 
    693703444    format(f10.3,f6.0) 
Note: See TracChangeset for help on using the changeset viewer.