Ignore:
Timestamp:
12/02/14 19:21:00 (9 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
Files:
27 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/branches/SATURN_DYNAMICO/ICOSAGCM/src/caldyn_gcm.f90

    r260 r298  
    3333    USE exner_mod 
    3434    USE mpipara 
     35    USE omp_para, ONLY: omp_master 
    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_mpi_root .AND. omp_master) PRINT *, 'caldyn_conserv=',def 
    5354 
    5455    CALL allocate_caldyn 
     
    294295    IF (write_out) THEN 
    295296 
    296        IF (is_mpi_root) PRINT *,'CALL write_output_fields' 
     297!       IF (is_mpi_root) PRINT *,'CALL write_output_fields' 
    297298 
    298299! ---> for openMP test to fix later 
     
    892893  USE icosa 
    893894  USE mpipara 
     895  USE omp_para, ONLY: omp_master 
    894896  IMPLICIT NONE 
    895897    TYPE(t_field),POINTER :: f_ps(:) 
     
    924926    
    925927    ENDDO 
    926     IF (is_mpi_root) PRINT*, "mass_tot ", mass_tot,"      dmass_tot ",dmass_tot         
     928    IF (is_mpi_root .AND. omp_master) PRINT*, "mass_tot ", mass_tot,"      dmass_tot ",dmass_tot         
    927929 
    928930  END SUBROUTINE check_mass_conservation   
  • codes/icosagcm/branches/SATURN_DYNAMICO/ICOSAGCM/src/check_conserve.f90

    r262 r298  
    8888       WRITE(134,*)mtot,rmsdpdt,etot,ztot,stot,rmsv,ang  
    8989       WRITE(134,*)"==================================================" 
    90        WRITE(*,4000)mtot,rmsdpdt,etot,ztot,stot,rmsv,ang 
     90!       WRITE(*,4000)mtot,rmsdpdt,etot,ztot,stot,rmsv,ang 
    9191        
    92924000   FORMAT(10x,'masse',5x,'rmsdpdt',5x,'energie',5x,'enstrophie'  & 
  • codes/icosagcm/branches/SATURN_DYNAMICO/ICOSAGCM/src/dissip_gcm.f90

    r267 r298  
    6868  USE mpi_mod 
    6969  USE mpipara 
     70  USE omp_para, ONLY: omp_master 
    7071  USE transfert_mod 
    7172  USE time_mod 
     
    100101   CASE('none') 
    101102      rayleigh_friction_type=0 
    102       IF (is_mpi_root) PRINT *, 'No Rayleigh friction' 
     103      IF (is_mpi_root .AND. omp_master) PRINT *, 'No Rayleigh friction' 
    103104   CASE('dcmip2_schaer_noshear') 
    104105      rayleigh_friction_type=1 
    105106      rayleigh_shear=0 
    106       IF (is_mpi_root) PRINT *, 'Rayleigh friction : Schaer-like mountain without shear DCMIP2.1' 
     107      IF (is_mpi_root .AND. omp_master) PRINT *, 'Rayleigh friction : Schaer-like mountain without shear DCMIP2.1' 
    107108   CASE('dcmip2_schaer_shear') 
    108109      rayleigh_shear=1 
    109110      rayleigh_friction_type=2 
    110       IF (is_mpi_root) PRINT *, 'Rayleigh friction : Schaer-like mountain with shear DCMIP2.2' 
     111      IF (is_mpi_root .AND. omp_master) PRINT *, 'Rayleigh friction : Schaer-like mountain with shear DCMIP2.2' 
    111112   CASE DEFAULT 
    112       IF (is_mpi_root) PRINT *, 'Bad selector : rayleigh_friction_type =', TRIM(rayleigh_friction_key), ' in dissip_gcm.f90/init_dissip' 
     113      IF (is_mpi_root .AND. omp_master) PRINT *, 'Bad selector : rayleigh_friction_type =', TRIM(rayleigh_friction_key), ' in dissip_gcm.f90/init_dissip' 
    113114      STOP 
    114115   END SELECT 
     
    119120      rayleigh_tau = rayleigh_tau / scale_factor 
    120121      IF(rayleigh_tau<=0) THEN 
    121          IF (is_mpi_root) PRINT *, 'Forbidden : negative value for rayleigh_friction_tau =',rayleigh_tau 
     122         IF (is_mpi_root .AND. omp_master) PRINT *, 'Forbidden : negative value for rayleigh_friction_tau =',rayleigh_tau 
    122123         STOP 
    123124      END IF 
     
    232233        u=du/dumax 
    233234      ENDDO 
    234       IF (is_mpi_root) PRINT *,"gradiv : it :",it ,": dumax",dumax 
     235      IF (is_mpi_root .AND. omp_master) PRINT *,"gradiv : it :",it ,": dumax",dumax 
    235236 
    236237    ENDDO  
    237     IF (is_mpi_root) PRINT *,"gradiv : dumax",dumax 
    238     IF (is_mpi_root) PRINT *, 'mean T-cell edge size (km)', 1.45*radius/iim_glo/1000., & 
     238    IF (is_mpi_root .AND. omp_master) PRINT *,"gradiv : dumax",dumax 
     239    IF (is_mpi_root .AND. omp_master) PRINT *, 'mean T-cell edge size (km)', 1.45*radius/iim_glo/1000., & 
    239240                              'effective T-cell half-edge size (km)', dumax**(-.5/nitergdiv)/1000 
    240     IF (is_mpi_root)  PRINT *, 'Max. time step assuming c=340 m/s and Courant number=2.8 :', & 
     241    IF (is_mpi_root .AND. omp_master)  PRINT *, 'Max. time step assuming c=340 m/s and Courant number=2.8 :', & 
    241242                               2.8/340.*dumax**(-.5/nitergdiv) 
    242243 
    243244    cgraddiv=dumax**(-1./nitergdiv) 
    244     IF (is_mpi_root) PRINT *,"cgraddiv : ",cgraddiv 
     245    IF (is_mpi_root .AND. omp_master) PRINT *,"cgraddiv : ",cgraddiv 
    245246 
    246247    DO ind=1,ndomain 
     
    320321      ENDDO 
    321322       
    322       IF (is_mpi_root) PRINT *,"gradrot : it :",it ,": dumax",dumax 
     323      IF (is_mpi_root .AND. omp_master) PRINT *,"gradrot : it :",it ,": dumax",dumax 
    323324 
    324325    ENDDO  
    325     IF (is_mpi_root) PRINT *,"gradrot : dumax",dumax 
     326    IF (is_mpi_root .AND. omp_master) PRINT *,"gradrot : dumax",dumax 
    326327   
    327328    cgradrot=dumax**(-1./nitergrot)  
    328     IF (is_mpi_root) PRINT *,"cgradrot : ",cgradrot 
     329    IF (is_mpi_root .AND. omp_master) PRINT *,"cgradrot : ",cgradrot 
    329330    
    330331 
     
    389390      ENDIF   
    390391       
    391       IF (is_mpi_root) PRINT *,"divgrad : it :",it ,": dthetamax",dthetamax 
     392      IF (is_mpi_root .AND. omp_master) PRINT *,"divgrad : it :",it ,": dthetamax",dthetamax 
    392393 
    393394      DO ind=1,ndomain 
     
    401402    ENDDO  
    402403 
    403     IF (is_mpi_root) PRINT *,"divgrad : divgrad",dthetamax 
     404    IF (is_mpi_root .AND. omp_master) PRINT *,"divgrad : divgrad",dthetamax 
    404405   
    405406    cdivgrad=dthetamax**(-1./niterdivgrad)  
    406     IF (is_mpi_root) PRINT *,"cdivgrad : ",cdivgrad 
     407    IF (is_mpi_root .AND. omp_master) PRINT *,"cdivgrad : ",cdivgrad 
    407408 
    408409      
     
    431432       dtdissip=itau_dissip*dt 
    432433    ELSE 
    433        IF (is_mpi_root) PRINT *,"No dissipation time set, setting itau_dissip to 1000000000" 
     434       IF (is_mpi_root .AND. omp_master) PRINT *,"No dissipation time set, setting itau_dissip to 1000000000" 
    434435       itau_dissip=100000000 
    435436    END IF 
    436437    itau_dissip=MAX(1,itau_dissip) 
    437     IF (is_mpi_root) PRINT *,"mintau ",mintau,"itau_dissip",itau_dissip," dtdissip ",dtdissip 
     438    IF (is_mpi_root .AND. omp_master) PRINT *,"mintau ",mintau,"itau_dissip",itau_dissip," dtdissip ",dtdissip 
    438439 
    439440  END SUBROUTINE init_dissip  
  • codes/icosagcm/branches/SATURN_DYNAMICO/ICOSAGCM/src/sponge.f90

    r291 r298  
    2929    tau_sponge = 1.e-4 
    3030    CALL getin("tau_sponge",tau_sponge) 
    31     PRINT*,'tau_sponge = ',tau_sponge 
     31    IF (is_mpi_master .AND. omp_master) PRINT*,'tau_sponge = ',tau_sponge 
    3232 
    3333    iflag_sponge = 0 
    3434    CALL getin("iflag_sponge",iflag_sponge) 
    35     PRINT*,'iflag_sponge = ',iflag_sponge 
     35    IF (is_mpi_master .AND. omp_master) PRINT*,'iflag_sponge = ',iflag_sponge 
    3636     
    3737    mode_sponge = 1 
    3838    CALL getin("mode_sponge",mode_sponge) 
    39     PRINT*,'mode_sponge = ',mode_sponge 
     39    IF (is_mpi_master .AND. omp_master) PRINT*,'mode_sponge = ',mode_sponge 
    4040 
    4141    IF (iflag_sponge == 0) THEN 
    42       PRINT*,'init_sponge: no sponge' 
     42      IF (is_mpi_master .AND. omp_master) PRINT*,'init_sponge: no sponge' 
    4343      RETURN 
    4444    ENDIF 
  • codes/icosagcm/branches/SATURN_DYNAMICO/ICOSAGCM/src/time.f90

    r267 r298  
    5151  USE getin_mod 
    5252  USE mpipara 
     53  USE omp_para, ONLY: omp_master 
    5354  IMPLICIT NONE 
    5455  REAL(rstd) :: run_length 
     
    7475    write_period=write_period/scale_factor 
    7576    itau_out=FLOOR(.5+write_period/dt) 
    76     IF (is_mpi_root) PRINT *, 'Output frequency (scaled) set to ',write_period, ' : itau_out = ',itau_out 
     77    IF (is_mpi_root .AND. omp_master) PRINT *, 'Output frequency (scaled) set to ',write_period, ' : itau_out = ',itau_out 
    7778    ENDIF  
    7879 
     
    8687    CALL getin('itau_physics',itau_physics) 
    8788 
    88     IF (is_mpi_root)  THEN 
     89    IF (is_mpi_root .AND. omp_master)  THEN 
    8990       PRINT *, 'itaumax=',itaumax 
    9091       PRINT *, 'itau_adv=',itau_adv, 'itau_dissip=',itau_dissip, 'itau_physics=',itau_physics 
  • 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) 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/dyn3dpar/conf_gcm.F

    r222 r298  
    1919      use assert_m, only: assert 
    2020      use sponge_mod_p, only: callsponge,mode_sponge,nsponge,tetasponge 
     21      use mod_phys_lmdz_para, only : is_master 
    2122      IMPLICIT NONE 
    2223!----------------------------------------------------------------------- 
     
    952953 
    953954 
     955      if (is_master) then 
    954956      write(lunout,*)' #########################################' 
    955957      write(lunout,*)' Configuration des parametres lus via run.def ' 
     
    10071009       write(lunout,*)' moyzon_ch = ', moyzon_ch 
    10081010      endif 
     1011      end if !of if (is_master) 
    10091012 
    10101013      RETURN 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/dyn3dpar/dynredem_p.F

    r222 r298  
    1111      use netcdf95, only: NF95_PUT_VAR 
    1212      use control_mod, only : planet_type 
     13      use mod_phys_lmdz_para, only : is_master 
    1314 
    1415      IMPLICIT NONE 
     
    8182      !!!     .... while keeping everything OK for LMDZ EARTH 
    8283      if ((planet_type.eq."generic").or.(planet_type.eq."mars")) then 
    83           write(lunout,*) trim(modname),' : Planeto-like start file' 
     84          if (is_master) write(lunout,*) trim(modname), 
     85     &          ' : Planeto-like start file' 
    8486          start_file_type="planeto" 
    8587          idecal = 4 
    8688      else 
    87           write(lunout,*) trim(modname),' : Earth-like start file' 
     89          if (is_master) write(lunout,*) trim(modname), 
     90     &          ' : Earth-like start file' 
    8891          idecal = 5 
    8992      endif 
     
    573576      ierr = NF_CLOSE(nid) ! fermer le fichier 
    574577 
    575       PRINT*,'iim,jjm,llm,iday_end',iim,jjm,llm,iday_end 
    576       PRINT*,'rad,omeg,g,cpp,kappa', 
     578      if (is_master) PRINT*,'iim,jjm,llm,iday_end',iim,jjm,llm,iday_end 
     579      if (is_master) PRINT*,'rad,omeg,g,cpp,kappa', 
    577580     ,        rad,omeg,g,cpp,kappa 
    578581 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/aeropacity.F90

    r227 r298  
    66       USE comgeomfi_h 
    77       USE tracer_h, only: noms,rho_co2,rho_ice 
     8       use mod_phys_lmdz_para, only : is_master 
    89                   
    910       implicit none 
     
    8687      IF (firstcall) THEN 
    8788 
    88         write(*,*) "Tracers found in aeropacity:" 
     89        if (is_master) write(*,*) "Tracers found in aeropacity:" 
    8990        do iq=1,nq 
    9091          tracername=noms(iq) 
    9192          if (tracername.eq."co2_ice") then 
    9293            i_co2ice=iq 
    93           write(*,*) "i_co2ice=",i_co2ice 
     94          if (is_master) write(*,*) "i_co2ice=",i_co2ice 
    9495 
    9596          endif 
    9697          if (tracername.eq."h2o_ice") then 
    9798            i_h2oice=iq 
    98             write(*,*) "i_h2oice=",i_h2oice 
     99            if (is_master) write(*,*) "i_h2oice=",i_h2oice 
    99100          endif 
    100101        enddo 
    101102 
    102103        if (noaero) then 
    103           print*, "No active aerosols found in aeropacity" 
     104          if (is_master) print*, "No active aerosols found in aeropacity" 
    104105        else 
    105           print*, "If you would like to use aerosols, make sure any old" 
    106           print*, "start files are updated in newstart using the option" 
    107           print*, "q=0" 
    108           write(*,*) "Active aerosols found in aeropacity:" 
     106          if (is_master) print*, "If you would like to use aerosols, make sure any old" 
     107          if (is_master) print*, "start files are updated in newstart using the option" 
     108          if (is_master) print*, "q=0" 
     109          if (is_master) write(*,*) "Active aerosols found in aeropacity:" 
    109110        endif 
    110111 
    111112        if ((iaero_co2.ne.0).and.(.not.noaero)) then 
    112           print*, 'iaero_co2=  ',iaero_co2 
     113          if (is_master) print*, 'iaero_co2=  ',iaero_co2 
    113114        endif 
    114115        if (iaero_h2o.ne.0) then 
    115           print*,'iaero_h2o=  ',iaero_h2o     
     116          if (is_master) print*,'iaero_h2o=  ',iaero_h2o     
    116117        endif 
    117118        if (iaero_dust.ne.0) then 
    118           print*,'iaero_dust= ',iaero_dust 
     119          if (is_master) print*,'iaero_dust= ',iaero_dust 
    119120        endif 
    120121        if (iaero_h2so4.ne.0) then 
    121           print*,'iaero_h2so4= ',iaero_h2so4 
     122          if (is_master) print*,'iaero_h2so4= ',iaero_h2so4 
    122123        endif 
    123124        if (iaero_back2lay.ne.0) then 
    124           print*,'iaero_back2lay= ',iaero_back2lay 
     125          if (is_master) print*,'iaero_back2lay= ',iaero_back2lay 
    125126        endif 
    126127 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/calc_cpp_mugaz.F90

    r227 r298  
    1818 
    1919      use gases_h 
     20      use mod_phys_lmdz_para, only : is_master 
    2021      implicit none 
    2122 
     
    8687      cpp_c = 1000.0*cpp_c 
    8788 
     89      if (is_master) then 
    8890      print*,'Cp in calc_cpp_mugaz is ',cpp_c,'J kg^-1 K^-1' 
    8991      print*,'Mg in calc_cpp_mugaz is ',mugaz_c,'amu' 
    9092      print*,'Predefined Cp in physics is ',cpp,'J kg^-1 K^-1' 
    9193      print*,'Predefined Mg in physics is ',mugaz,'amu' 
     94      end if 
    9295 
    9396      if (check_cpp_match) then 
    94          print*,'REQUEST TO CHECK cpp_match :' 
     97         if (is_master) print*,'REQUEST TO CHECK cpp_match :' 
    9598         if((abs(1.-cpp/cpp_c).gt.1.e-6) .or.  & 
    9699              (abs(1.-mugaz/mugaz_c).gt.1.e-6)) then 
     
    101104            stop 
    102105         else 
    103             print*,'--> OK. Settings match composition.' 
     106            if (is_master) print*,'--> OK. Settings match composition.' 
    104107         endif 
    105108      endif 
    106109 
    107110      if (.not.force_cpp) then 
    108           print*,'*** Setting cpp & mugaz to computations in calc_cpp_mugaz.' 
     111          if (is_master) print*,'*** Setting cpp & mugaz to computations in calc_cpp_mugaz.' 
    109112          mugaz = mugaz_c 
    110113          cpp = cpp_c 
    111114      else 
    112           print*,'*** Setting cpp & mugaz to predefined values.' 
     115          if (is_master) print*,'*** Setting cpp & mugaz to predefined values.' 
    113116      endif 
    114117 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/calc_rayleigh.F90

    r222 r298  
    2828      use radcommon_h, only: WAVEV, BWNV, DWNV, tstellar, tauray, taurayvar, scalep 
    2929      use gases_h 
     30      use mod_phys_lmdz_para, only : is_master 
    3031 
    3132      implicit none 
     
    5556      do igas=1,ngasmx 
    5657         if(igas.eq.vgas)then 
    57             print*,'variable gas is ',trim(gnom(igas)),' in Rayleigh scattering ' 
     58            if (is_master) print*,'variable gas is ',trim(gnom(igas)),' in Rayleigh scattering ' 
    5859         endif 
    5960         if((igas/=vgas).and.(gfrac(igas).lt.5.e-2))then 
    60             print*,'Ignoring ',trim(gnom(igas)),' in Rayleigh scattering '// & 
     61            if (is_master) print*,'Ignoring ',trim(gnom(igas)),' in Rayleigh scattering '// & 
    6162            'as its mixing ratio is less than 0.05.'  
    6263            ! ignore variable gas in Rayleigh calculation 
     
    8485 
    8586            if((gfrac(igas).eq.1.0).and.(vgas.eq.0))then 
    86                print*,'Rayleigh scattering is for a pure ',trim(gnom(igas)),' atmosphere.' 
     87               if (is_master) print*,'Rayleigh scattering is for a pure ',trim(gnom(igas)),' atmosphere.' 
    8788               typeknown=.true. 
    8889            endif 
     
    9293 
    9394      if(.not.typeknown)then 
    94          print*,'Rayleigh scattering is for a mixed gas atmosphere.' 
     95         if (is_master) print*,'Rayleigh scattering is for a mixed gas atmosphere.' 
    9596         typeknown=.true. 
    9697      endif 
     
    159160      IF (L_NSPECTV > 6) THEN 
    160161        icantbewrong = L_NSPECTV-6 
    161         print*,'At 1 atm and lambda = ',WAVEV(icantbewrong),' um' 
    162         print*,'tau_R = ',TAURAY(icantbewrong)*1013.25 
    163         print*,'sig_R = ',TAURAY(icantbewrong)*g*mugaz*1.67e-27*100, & 
     162        if (is_master) print*,'At 1 atm and lambda = ',WAVEV(icantbewrong),' um' 
     163        if (is_master) print*,'tau_R = ',TAURAY(icantbewrong)*1013.25 
     164        if (is_master) print*,'sig_R = ',TAURAY(icantbewrong)*g*mugaz*1.67e-27*100, & 
    164165               'cm^2 molecule^-1' 
    165166      ENDIF 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/callcorrk.F90

    r240 r298  
    1818      use aerosol_mod, only : iaero_co2,iaero_h2o,iaero_dust,iaero_h2so4, iaero_back2lay 
    1919      USE tracer_h 
     20      USE mod_phys_lmdz_para, only : is_master 
    2021 
    2122      implicit none 
     
    218219!-------------------------------------------------- 
    219220!     set up correlated k 
    220          print*, "callcorrk: Correlated-k data base folder:",trim(datadir) 
     221         if (is_master) print*, "callcorrk: Correlated-k data base folder:",trim(datadir) 
    221222         call getin_p("corrkdir",corrkdir) 
    222          print*, "corrkdir = ",corrkdir 
     223         if (is_master) print*, "corrkdir = ",corrkdir 
    223224         write( tmp1, '(i3)' ) L_NSPECTI 
    224225         write( tmp2, '(i3)' ) L_NSPECTV 
     
    272273         if ((iaer.eq.iaero_co2).and.tracer.and.(igcm_co2_ice.gt.0)) then ! treat condensed co2 particles. 
    273274            call co2_reffrad(ngrid,nlayer,nq,pq,reffrad(1,1,iaero_co2)) 
    274             print*,'Max. CO2 ice particle size = ',maxval(reffrad(1:ngrid,1:nlayer,iaer))/1.e-6,' um' 
    275             print*,'Min. CO2 ice particle size = ',minval(reffrad(1:ngrid,1:nlayer,iaer))/1.e-6,' um' 
     275            if (is_master) print*,'Max. CO2 ice particle size = ',maxval(reffrad(1:ngrid,1:nlayer,iaer))/1.e-6,' um' 
     276            if (is_master) print*,'Min. CO2 ice particle size = ',minval(reffrad(1:ngrid,1:nlayer,iaer))/1.e-6,' um' 
    276277         end if 
    277278         if ((iaer.eq.iaero_h2o).and.water) then ! treat condensed water particles. to be generalized for other aerosols 
    278279            call h2o_reffrad(ngrid,nlayer,pq(1,1,igcm_h2o_ice),pt, & 
    279280                             reffrad(1,1,iaero_h2o),nueffrad(1,1,iaero_h2o)) 
    280             print*,'Max. H2O cloud particle size = ',maxval(reffrad(1:ngrid,1:nlayer,iaer))/1.e-6,' um' 
    281             print*,'Min. H2O cloud particle size = ',minval(reffrad(1:ngrid,1:nlayer,iaer))/1.e-6,' um' 
     281            if (is_master) print*,'Max. H2O cloud particle size = ',maxval(reffrad(1:ngrid,1:nlayer,iaer))/1.e-6,' um' 
     282            if (is_master) print*,'Min. H2O cloud particle size = ',minval(reffrad(1:ngrid,1:nlayer,iaer))/1.e-6,' um' 
    282283         endif 
    283284         if(iaer.eq.iaero_dust)then 
    284285            call dust_reffrad(ngrid,nlayer,reffrad(1,1,iaero_dust)) 
    285             print*,'Dust particle size = ',reffrad(1,1,iaer)/1.e-6,' um' 
     286            if (is_master) print*,'Dust particle size = ',reffrad(1,1,iaer)/1.e-6,' um' 
    286287         endif 
    287288         if(iaer.eq.iaero_h2so4)then 
    288289            call h2so4_reffrad(ngrid,nlayer,reffrad(1,1,iaero_h2so4)) 
    289             print*,'H2SO4 particle size =',reffrad(1,1,iaer)/1.e-6,' um' 
     290            if (is_master) print*,'H2SO4 particle size =',reffrad(1,1,iaer)/1.e-6,' um' 
    290291         endif 
    291292          if(iaer.eq.iaero_back2lay)then 
     
    548549            muvarrad(2*nlayer+1)=muvar(ig,1) 
    549550 
    550             print*,'Recalculating qvar with VARIABLE epsi for kastprof' 
    551             print*,'Assumes that the variable gas is H2O!!!' 
    552             print*,'Assumes that there is only one tracer' 
     551            if (is_master) print*,'Recalculating qvar with VARIABLE epsi for kastprof' 
     552            if (is_master) print*,'Assumes that the variable gas is H2O!!!' 
     553            if (is_master) print*,'Assumes that there is only one tracer' 
    553554            !i_var=igcm_h2o_vap 
    554555            i_var=1 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/iniaerosol.F

    r222 r298  
    44      use radinc_h, only: naerkind 
    55      use aerosol_mod 
     6      use mod_phys_lmdz_para, only : is_master 
    67 
    78      IMPLICIT NONE 
     
    2627         iaero_co2=ia 
    2728      endif 
    28       write(*,*) '--- CO2 aerosol = ', iaero_co2 
     29      if (is_master) write(*,*) '--- CO2 aerosol = ', iaero_co2 
    2930  
    3031      if (aeroh2o) then 
     
    3233         iaero_h2o=ia 
    3334      endif 
    34       write(*,*) '--- H2O aerosol = ', iaero_h2o 
     35      if (is_master) write(*,*) '--- H2O aerosol = ', iaero_h2o 
    3536 
    3637      if (dusttau.gt.0) then 
     
    3839         iaero_dust=ia 
    3940      endif 
    40       write(*,*) '--- Dust aerosol = ', iaero_dust 
     41      if (is_master) write(*,*) '--- Dust aerosol = ', iaero_dust 
    4142 
    4243      if (aeroh2so4) then 
     
    4445         iaero_h2so4=ia 
    4546      endif 
    46       write(*,*) '--- H2SO4 aerosol = ', iaero_h2so4 
     47      if (is_master) write(*,*) '--- H2SO4 aerosol = ', iaero_h2so4 
    4748       
    4849      if (aeroback2lay) then 
     
    5051         iaero_back2lay=ia 
    5152      endif 
    52       write(*,*) '--- Two-layer aerosol = ', iaero_back2lay 
     53      if (is_master) write(*,*) '--- Two-layer aerosol = ', 
     54     &           iaero_back2lay 
    5355 
    54       write(*,*) '=== Number of aerosols= ', ia 
     56      if (is_master) write(*,*) '=== Number of aerosols= ', ia 
    5557       
    5658! For the zero aerosol case, we currently make a dummy co2 aerosol which is zero everywhere. 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/inifis.F

    r273 r298  
    5252!      USE ioipsl_getincom  
    5353      USE ioipsl_getincom_p 
     54      use mod_phys_lmdz_para, only : is_master 
    5455      IMPLICIT NONE 
    5556!#include "dimensions.h" 
     
    8990      rcp=r/cpp 
    9091      ! Ehouarn debug: 
     92      if (is_master) then 
    9193      write(*,*) "inifis: rad=",rad 
    9294      write(*,*) "        daysec=",daysec 
     
    9698      write(*,*) "        r=",r 
    9799      write(*,*) "        rcp=",rcp 
     100      end if 
    98101 
    99102      avocado = 6.02214179e23   ! added by RW 
     
    121124!!!      IF(ierr.EQ.0) THEN 
    122125      IF(iscallphys) THEN 
     126         if (is_master) then 
    123127         PRINT* 
    124128         PRINT* 
     
    126130         PRINT*,' inifis: Parametres pour la physique (callphys.def)' 
    127131         PRINT*,'--------------------------------------------' 
    128  
    129          write(*,*) "Directory where external input files are:" 
     132         end if 
     133 
     134         if (is_master) write(*,*) "Directory where external input", 
     135     &          " files are:" 
     136 
    130137         ! default 'datadir' is set in "datadir_mod" 
    131138         call getin_p("datadir",datadir) ! default path 
    132          write(*,*) " datadir = ",trim(datadir) 
    133  
    134          write(*,*) "Run with or without tracer transport ?" 
     139         if (is_master) write(*,*) " datadir = ",trim(datadir) 
     140 
     141         if (is_master) write(*,*) "Run with or without tracer", 
     142     &          " transport ?" 
    135143         tracer=.false. ! default value 
    136144         call getin_p("tracer",tracer) 
    137          write(*,*) " tracer = ",tracer 
    138  
    139          write(*,*) "Run with or without atm mass update ", 
    140      &      " due to tracer evaporation/condensation?" 
     145         if (is_master) write(*,*) " tracer = ",tracer 
     146 
     147         if (is_master) write(*,*) "Run with or without atm mass", 
     148     &          " update due to tracer evaporation/condensation?" 
    141149         mass_redistrib=.false. ! default value 
    142150         call getin_p("mass_redistrib",mass_redistrib) 
    143          write(*,*) " mass_redistrib = ",mass_redistrib 
    144  
    145          write(*,*) "Diurnal cycle ?" 
    146          write(*,*) "(if diurnal=false, diurnal averaged solar heating)" 
     151         if (is_master) write(*,*) " mass_redistrib = ",mass_redistrib 
     152 
     153         if (is_master) write(*,*) "Diurnal cycle ?" 
     154         if (is_master) write(*,*) "(if diurnal=false, diurnal", 
     155     &          " averaged solar heating)" 
    147156         diurnal=.true. ! default value 
    148157         call getin_p("diurnal",diurnal) 
    149          write(*,*) " diurnal = ",diurnal 
    150  
    151          write(*,*) "Seasonal cycle ?" 
    152          write(*,*) "(if season=false, Ls stays constant, to value ", 
    153      &   "set in 'start'" 
     158         if (is_master) write(*,*) " diurnal = ",diurnal 
     159 
     160         if (is_master) write(*,*) "Seasonal cycle ?" 
     161         if (is_master) write(*,*) "(if season=false, Ls stays", 
     162     &          " constant, to value set in 'start'" 
    154163         season=.true. ! default value 
    155164         call getin_p("season",season) 
    156          write(*,*) " season = ",season 
    157  
    158          write(*,*) "Tidally resonant rotation ?" 
     165         if (is_master) write(*,*) " season = ",season 
     166 
     167         if (is_master) write(*,*) "Tidally resonant rotation ?" 
    159168         tlocked=.false. ! default value 
    160169         call getin_p("tlocked",tlocked) 
    161          write(*,*) "tlocked = ",tlocked 
    162  
    163          write(*,*) "Saturn ring shadowing ?" 
     170         if (is_master) write(*,*) "tlocked = ",tlocked 
     171 
     172         if (is_master) write(*,*) "Saturn ring shadowing ?" 
    164173         rings_shadow = .false. 
    165174         call getin_p("rings_shadow", rings_shadow) 
    166          write(*,*) "rings_shadow = ", rings_shadow 
     175         if (is_master) write(*,*) "rings_shadow = ", rings_shadow 
    167176          
    168          write(*,*) "Compute latitude-dependent gravity field?" 
     177         if (is_master) write(*,*) "Compute latitude-dependent", 
     178     &          " gravity field?" 
    169179         oblate = .false. 
    170180         call getin_p("oblate", oblate) 
    171          write(*,*) "oblate = ", oblate 
    172  
    173          write(*,*) "Flattening of the planet (a-b)/a " 
     181         if (is_master) write(*,*) "oblate = ", oblate 
     182 
     183         if (is_master) write(*,*) "Flattening of the planet (a-b)/a " 
    174184         flatten = 0.0 
    175185         call getin_p("flatten", flatten) 
    176          write(*,*) "flatten = ", flatten 
     186         if (is_master) write(*,*) "flatten = ", flatten 
    177187          
    178188 
    179          write(*,*) "Needed if oblate=.true.: J2" 
     189         if (is_master) write(*,*) "Needed if oblate=.true.: J2" 
    180190         J2 = 0.0 
    181191         call getin_p("J2", J2) 
    182          write(*,*) "J2 = ", J2 
     192         if (is_master) write(*,*) "J2 = ", J2 
    183193          
    184          write(*,*) "Needed if oblate=.true.: Planet mass (*1e24 kg)" 
     194         if (is_master) write(*,*) "Needed if oblate=.true.: Planet", 
     195     &          " mass (*1e24 kg)" 
    185196         MassPlanet = 0.0 
    186197         call getin_p("MassPlanet", MassPlanet) 
    187          write(*,*) "MassPlanet = ", MassPlanet          
    188  
    189          write(*,*) "Needed if oblate=.true.: Planet mean radius (m)" 
     198         if (is_master) write(*,*) "MassPlanet = ", MassPlanet          
     199 
     200         if (is_master) write(*,*) "Needed if oblate=.true.: Planet", 
     201     &          " mean radius (m)" 
    190202         Rmean = 0.0 
    191203         call getin_p("Rmean", Rmean) 
    192          write(*,*) "Rmean = ", Rmean 
     204         if (is_master) write(*,*) "Rmean = ", Rmean 
    193205          
    194206! Test of incompatibility: 
    195207! if tlocked, then diurnal should be false 
    196208         if (tlocked.and.diurnal) then 
    197            print*,'If diurnal=true, we should turn off tlocked.' 
     209           if (is_master) print*,'If diurnal=true, we should turn off', 
     210     &          ' tlocked.' 
    198211           stop 
    199212         endif 
    200213 
    201          write(*,*) "Tidal resonance ratio ?" 
     214         if (is_master) write(*,*) "Tidal resonance ratio ?" 
    202215         nres=0          ! default value 
    203216         call getin_p("nres",nres) 
    204          write(*,*) "nres = ",nres 
    205  
    206          write(*,*) "Write some extra output to the screen ?" 
     217         if (is_master) write(*,*) "nres = ",nres 
     218 
     219         if (is_master) write(*,*) "Write some extra output to the", 
     220     &          " screen ?" 
    207221         lwrite=.false. ! default value 
    208222         call getin_p("lwrite",lwrite) 
    209          write(*,*) " lwrite = ",lwrite 
    210  
    211          write(*,*) "Save statistics in file stats.nc ?" 
     223         if (is_master) write(*,*) " lwrite = ",lwrite 
     224 
     225         if (is_master) write(*,*) "Save statistics in file stats.nc ?" 
    212226         callstats=.true. ! default value 
    213227         call getin_p("callstats",callstats) 
    214          write(*,*) " callstats = ",callstats 
    215  
    216          write(*,*) "Test energy conservation of model physics ?" 
     228         if (is_master) write(*,*) " callstats = ",callstats 
     229 
     230         if (is_master) write(*,*) "Test energy conservation of model", 
     231     &          " physics ?" 
    217232         enertest=.false. ! default value 
    218233         call getin_p("enertest",enertest) 
    219          write(*,*) " enertest = ",enertest 
    220  
    221          write(*,*) "Check to see if cpp values used match gases.def ?" 
     234         if (is_master) write(*,*) " enertest = ",enertest 
     235 
     236         if (is_master) write(*,*) "Check to see if cpp values used", 
     237     &          " match gases.def ?" 
    222238         check_cpp_match=.true. ! default value 
    223239         call getin_p("check_cpp_match",check_cpp_match) 
    224          write(*,*) " check_cpp_match = ",check_cpp_match 
    225  
    226          write(*,*) "call radiative transfer ?" 
     240         if (is_master) write(*,*) " check_cpp_match = ",check_cpp_match 
     241 
     242         if (is_master) write(*,*) "call radiative transfer ?" 
    227243         callrad=.true. ! default value 
    228244         call getin_p("callrad",callrad) 
    229          write(*,*) " callrad = ",callrad 
    230  
    231          write(*,*) "call correlated-k radiative transfer ?" 
     245         if (is_master) write(*,*) " callrad = ",callrad 
     246 
     247         if (is_master) write(*,*) "call correlated-k radiative", 
     248     &          " transfer ?" 
    232249         corrk=.true. ! default value 
    233250         call getin_p("corrk",corrk) 
    234          write(*,*) " corrk = ",corrk 
    235  
    236          write(*,*) "prohibit calculations outside corrk T grid?" 
     251         if (is_master) write(*,*) " corrk = ",corrk 
     252 
     253         if (is_master) write(*,*) "prohibit calculations outside", 
     254     &          " corrk T grid?" 
    237255         strictboundcorrk=.true. ! default value 
    238256         call getin_p("strictboundcorrk",strictboundcorrk) 
    239          write(*,*) "strictboundcorrk = ",strictboundcorrk 
    240  
    241          write(*,*) "call gaseous absorption in the visible bands?", 
    242      &              "(matters only if callrad=T)" 
     257         if (is_master) write(*,*) "strictboundcorrk = ", 
     258     &          strictboundcorrk 
     259 
     260         if (is_master) write(*,*) "call gaseous absorption in the", 
     261     &          " visible bands? (matters only if callrad=T)" 
    243262         callgasvis=.false. ! default value 
    244263         call getin_p("callgasvis",callgasvis) 
    245          write(*,*) " callgasvis = ",callgasvis 
     264         if (is_master) write(*,*) " callgasvis = ",callgasvis 
    246265         
    247          write(*,*) "call continuum opacities in radiative transfer ?", 
    248      &              "(matters only if callrad=T)" 
     266         if (is_master) write(*,*) "call continuum opacities in", 
     267     &          " radiative transfer ? (matters only if callrad=T)" 
    249268         continuum=.true. ! default value 
    250269         call getin_p("continuum",continuum) 
    251          write(*,*) " continuum = ",continuum 
    252  
    253          write(*,*) "use analytic function for H2O continuum ?" 
     270         if (is_master) write(*,*) " continuum = ",continuum 
     271 
     272         if (is_master) write(*,*) "use analytic function for H2O", 
     273     &          " continuum ?" 
    254274         H2Ocont_simple=.false. ! default value 
    255275         call getin_p("H2Ocont_simple",H2Ocont_simple) 
    256          write(*,*) " H2Ocont_simple = ",H2Ocont_simple 
     276         if (is_master) write(*,*) " H2Ocont_simple = ",H2Ocont_simple 
    257277  
    258          write(*,*) "call turbulent vertical diffusion ?" 
     278         if (is_master) write(*,*) "call turbulent vertical", 
     279     &          " diffusion ?" 
    259280         calldifv=.true. ! default value 
    260281         call getin_p("calldifv",calldifv) 
    261          write(*,*) " calldifv = ",calldifv 
    262  
    263          write(*,*) "use turbdiff instead of vdifc ?" 
     282         if (is_master) write(*,*) " calldifv = ",calldifv 
     283 
     284         if (is_master) write(*,*) "use turbdiff instead of vdifc ?" 
    264285         UseTurbDiff=.true. ! default value 
    265286         call getin_p("UseTurbDiff",UseTurbDiff) 
    266          write(*,*) " UseTurbDiff = ",UseTurbDiff 
    267  
    268          write(*,*) "call convective adjustment ?" 
     287         if (is_master) write(*,*) " UseTurbDiff = ",UseTurbDiff 
     288 
     289         if (is_master) write(*,*) "call convective adjustment ?" 
    269290         calladj=.true. ! default value 
    270291         call getin_p("calladj",calladj) 
    271          write(*,*) " calladj = ",calladj 
    272  
    273          write(*,*) "call CO2 condensation ?" 
     292         if (is_master) write(*,*) " calladj = ",calladj 
     293 
     294         if (is_master) write(*,*) "call CO2 condensation ?" 
    274295         co2cond=.false. ! default value 
    275296         call getin_p("co2cond",co2cond) 
    276          write(*,*) " co2cond = ",co2cond 
     297         if (is_master) write(*,*) " co2cond = ",co2cond 
    277298! Test of incompatibility 
    278299         if (co2cond.and.(.not.tracer)) then 
    279             print*,'We need a CO2 ice tracer to condense CO2' 
     300            if (is_master) print*,'We need a CO2 ice tracer to', 
     301     &          ' condense CO2' 
    280302            call abort 
    281303         endif  
    282304  
    283          write(*,*) "CO2 supersaturation level ?" 
     305         if (is_master) write(*,*) "CO2 supersaturation level ?" 
    284306         co2supsat=1.0 ! default value 
    285307         call getin_p("co2supsat",co2supsat) 
    286          write(*,*) " co2supsat = ",co2supsat 
    287  
    288          write(*,*) "Radiative timescale for Newtonian cooling ?" 
     308         if (is_master) write(*,*) " co2supsat = ",co2supsat 
     309 
     310         if (is_master) write(*,*) "Radiative timescale for Newtonian", 
     311     &          " cooling ?" 
    289312         tau_relax=30. ! default value 
    290313         call getin_p("tau_relax",tau_relax) 
    291          write(*,*) " tau_relax = ",tau_relax 
     314         if (is_master) write(*,*) " tau_relax = ",tau_relax 
    292315         tau_relax=tau_relax*24*3600 ! convert Earth days --> seconds 
    293316 
    294          write(*,*)"call thermal conduction in the soil ?" 
     317         if (is_master) write(*,*)"call thermal conduction in", 
     318     &          " the soil ?" 
    295319         callsoil=.true. ! default value 
    296320         call getin_p("callsoil",callsoil) 
    297          write(*,*) " callsoil = ",callsoil 
     321         if (is_master) write(*,*) " callsoil = ",callsoil 
    298322          
    299          write(*,*)"Rad transfer is computed every iradia", 
    300      &             " physical timestep" 
     323         if (is_master) write(*,*)"Rad transfer is computed", 
     324     &          " every iradia physical timestep" 
    301325         iradia=1 ! default value 
    302326         call getin_p("iradia",iradia) 
    303          write(*,*)" iradia = ",iradia 
     327         if (is_master) write(*,*)" iradia = ",iradia 
    304328        
    305          write(*,*)"Rayleigh scattering ?" 
     329         if (is_master) write(*,*)"Rayleigh scattering ?" 
    306330         rayleigh=.false. 
    307331         call getin_p("rayleigh",rayleigh) 
    308          write(*,*)" rayleigh = ",rayleigh 
    309  
    310          write(*,*) "Use blackbody for stellar spectrum ?" 
     332         if (is_master) write(*,*)" rayleigh = ",rayleigh 
     333 
     334         if (is_master) write(*,*) "Use blackbody for stellar", 
     335     &          " spectrum ?" 
    311336         stelbbody=.false. ! default value 
    312337         call getin_p("stelbbody",stelbbody) 
    313          write(*,*) " stelbbody = ",stelbbody 
    314  
    315          write(*,*) "Stellar blackbody temperature ?" 
     338         if (is_master) write(*,*) " stelbbody = ",stelbbody 
     339 
     340         if (is_master) write(*,*) "Stellar blackbody temperature ?" 
    316341         stelTbb=5800.0 ! default value 
    317342         call getin_p("stelTbb",stelTbb) 
    318          write(*,*) " stelTbb = ",stelTbb 
    319  
    320          write(*,*)"Output mean OLR in 1D?" 
     343         if (is_master) write(*,*) " stelTbb = ",stelTbb 
     344 
     345         if (is_master) write(*,*)"Output mean OLR in 1D?" 
    321346         meanOLR=.false. 
    322347         call getin_p("meanOLR",meanOLR) 
    323          write(*,*)" meanOLR = ",meanOLR 
    324  
    325          write(*,*)"Output spectral OLR in 3D?" 
     348         if (is_master) write(*,*)" meanOLR = ",meanOLR 
     349 
     350         if (is_master) write(*,*)"Output spectral OLR in 3D?" 
    326351         specOLR=.false. 
    327352         call getin_p("specOLR",specOLR) 
    328          write(*,*)" specOLR = ",specOLR 
    329  
    330          write(*,*)"Operate in kastprof mode?" 
     353         if (is_master) write(*,*)" specOLR = ",specOLR 
     354 
     355         if (is_master) write(*,*)"Operate in kastprof mode?" 
    331356         kastprof=.false. 
    332357         call getin_p("kastprof",kastprof) 
    333          write(*,*)" kastprof = ",kastprof 
    334  
    335          write(*,*)"Uniform absorption in radiative transfer?" 
     358         if (is_master) write(*,*)" kastprof = ",kastprof 
     359 
     360         if (is_master) write(*,*)"Uniform absorption in", 
     361     &          " radiative transfer?" 
    336362         graybody=.false. 
    337363         call getin_p("graybody",graybody) 
    338          write(*,*)" graybody = ",graybody 
     364         if (is_master) write(*,*)" graybody = ",graybody 
    339365 
    340366! Slab Ocean  
    341          write(*,*) "Use slab-ocean ?" 
     367         if (is_master) write(*,*) "Use slab-ocean ?" 
    342368         ok_slab_ocean=.false.         ! default value 
    343369         call getin_p("ok_slab_ocean",ok_slab_ocean) 
    344          write(*,*) "ok_slab_ocean = ",ok_slab_ocean 
    345  
    346          write(*,*) "Use slab-sea-ice ?" 
     370         if (is_master) write(*,*) "ok_slab_ocean = ",ok_slab_ocean 
     371 
     372         if (is_master) write(*,*) "Use slab-sea-ice ?" 
    347373         ok_slab_sic=.true.         ! default value 
    348374         call getin_p("ok_slab_sic",ok_slab_sic) 
    349          write(*,*) "ok_slab_sic = ",ok_slab_sic 
    350  
    351          write(*,*) "Use heat transport for the ocean ?" 
     375         if (is_master) write(*,*) "ok_slab_sic = ",ok_slab_sic 
     376 
     377         if (is_master) write(*,*) "Use heat transport for the ocean ?" 
    352378         ok_slab_heat_transp=.true.   ! default value 
    353379         call getin_p("ok_slab_heat_transp",ok_slab_heat_transp) 
    354          write(*,*) "ok_slab_heat_transp = ",ok_slab_heat_transp 
     380         if (is_master) write(*,*) "ok_slab_heat_transp = ", 
     381     &          ok_slab_heat_transp 
    355382 
    356383 
     
    359386! if kastprof used, we must be in 1D 
    360387         if (kastprof.and.(ngrid.gt.1)) then 
    361            print*,'kastprof can only be used in 1D!' 
     388           if (is_master) print*,'kastprof can only be used in 1D!' 
    362389           call abort 
    363390         endif 
    364391 
    365          write(*,*)"Stratospheric temperature for kastprof mode?" 
     392         if (is_master) write(*,*)"Stratospheric temperature", 
     393     &          " for kastprof mode?" 
    366394         Tstrat=167.0 
    367395         call getin_p("Tstrat",Tstrat) 
    368          write(*,*)" Tstrat = ",Tstrat 
    369  
    370          write(*,*)"Remove lower boundary?" 
     396         if (is_master) write(*,*)" Tstrat = ",Tstrat 
     397 
     398         if (is_master) write(*,*)"Remove lower boundary?" 
    371399         nosurf=.false. 
    372400         call getin_p("nosurf",nosurf) 
    373          write(*,*)" nosurf = ",nosurf 
     401         if (is_master) write(*,*)" nosurf = ",nosurf 
    374402 
    375403! Tests of incompatibility: 
    376404         if (nosurf.and.callsoil) then 
    377            print*,'nosurf not compatible with soil scheme!' 
    378            print*,'... got to make a choice!' 
     405           if (is_master) print*,'nosurf not compatible with soil', 
     406     &          ' scheme! ... got to make a choice!' 
    379407           call abort 
    380408         endif 
    381409 
    382          write(*,*)"Add an internal heat flux?", 
     410         if (is_master) write(*,*)"Add an internal heat flux?", 
    383411     .             "... matters only if callsoil=F" 
    384412         intheat=0. 
    385413         call getin_p("intheat",intheat) 
    386          write(*,*)" intheat = ",intheat 
    387  
    388          write(*,*)"Use Newtonian cooling for radiative transfer?" 
     414         if (is_master) write(*,*)" intheat = ",intheat 
     415 
     416         if (is_master) write(*,*)"Use Newtonian cooling for", 
     417     &          " radiative transfer?" 
    389418         newtonian=.false. 
    390419         call getin_p("newtonian",newtonian) 
    391          write(*,*)" newtonian = ",newtonian 
     420         if (is_master) write(*,*)" newtonian = ",newtonian 
    392421 
    393422! Tests of incompatibility: 
    394423         if (newtonian.and.corrk) then 
    395            print*,'newtonian not compatible with correlated-k!' 
     424           if (is_master) print*,'newtonian not compatible with ', 
     425     &          'correlated-k!' 
    396426           call abort 
    397427         endif 
    398428         if (newtonian.and.calladj) then 
    399            print*,'newtonian not compatible with adjustment!' 
     429           if (is_master) print*,'newtonian not compatible with ', 
     430     &          'adjustment!' 
    400431           call abort 
    401432         endif 
    402433         if (newtonian.and.calldifv) then 
    403            print*,'newtonian not compatible with a boundary layer!' 
     434           if (is_master) print*,'newtonian not compatible with a ', 
     435     &          'boundary layer!' 
    404436           call abort 
    405437         endif 
    406438 
    407          write(*,*)"Test physics timescale in 1D?" 
     439         if (is_master) write(*,*)"Test physics timescale in 1D?" 
    408440         testradtimes=.false. 
    409441         call getin_p("testradtimes",testradtimes) 
    410          write(*,*)" testradtimes = ",testradtimes 
     442         if (is_master) write(*,*)" testradtimes = ",testradtimes 
    411443 
    412444! Test of incompatibility: 
    413445! if testradtimes used, we must be in 1D 
    414446         if (testradtimes.and.(ngrid.gt.1)) then 
    415            print*,'testradtimes can only be used in 1D!' 
     447           if (is_master) print*,'testradtimes can only be used in 1D!' 
    416448           call abort 
    417449         endif 
    418450 
    419          write(*,*)"Default planetary temperature?" 
     451         if (is_master) write(*,*)"Default planetary temperature?" 
    420452         tplanet=215.0 
    421453         call getin_p("tplanet",tplanet) 
    422          write(*,*)" tplanet = ",tplanet 
    423  
    424          write(*,*)"Which star?" 
     454         if (is_master) write(*,*)" tplanet = ",tplanet 
     455 
     456         if (is_master) write(*,*)"Which star?" 
    425457         startype=1 ! default value = Sol 
    426458         call getin_p("startype",startype) 
    427          write(*,*)" startype = ",startype 
    428  
    429          write(*,*)"Value of stellar flux at 1 AU?" 
     459         if (is_master) write(*,*)" startype = ",startype 
     460 
     461         if (is_master) write(*,*)"Value of stellar flux at 1 AU?" 
    430462         Fat1AU=1356.0 ! default value = Sol today 
    431463         call getin_p("Fat1AU",Fat1AU) 
    432          write(*,*)" Fat1AU = ",Fat1AU 
     464         if (is_master) write(*,*)" Fat1AU = ",Fat1AU 
    433465 
    434466 
    435467! TRACERS: 
    436468 
    437          write(*,*)"Varying H2O cloud fraction?" 
     469         if (is_master) write(*,*)"Varying H2O cloud fraction?" 
    438470         CLFvarying=.false.     ! default value 
    439471         call getin_p("CLFvarying",CLFvarying) 
    440          write(*,*)" CLFvarying = ",CLFvarying 
    441  
    442          write(*,*)"Value of fixed H2O cloud fraction?" 
     472         if (is_master) write(*,*)" CLFvarying = ",CLFvarying 
     473 
     474         if (is_master) write(*,*)"Value of fixed H2O cloud fraction?" 
    443475         CLFfixval=1.0                ! default value 
    444476         call getin_p("CLFfixval",CLFfixval) 
    445          write(*,*)" CLFfixval = ",CLFfixval 
    446  
    447          write(*,*)"fixed radii for Cloud particles?" 
     477         if (is_master) write(*,*)" CLFfixval = ",CLFfixval 
     478 
     479         if (is_master) write(*,*)"fixed radii for Cloud particles?" 
    448480         radfixed=.false. ! default value 
    449481         call getin_p("radfixed",radfixed) 
    450          write(*,*)" radfixed = ",radfixed 
     482         if (is_master) write(*,*)" radfixed = ",radfixed 
    451483 
    452484         if(kastprof)then 
     
    454486         endif   
    455487 
    456          write(*,*)"Number mixing ratio of CO2 ice particles:" 
     488         if (is_master) write(*,*)"Number mixing ratio of CO2 ice particles:" 
    457489         Nmix_co2=1.e6 ! default value 
    458490         call getin_p("Nmix_co2",Nmix_co2) 
    459          write(*,*)" Nmix_co2 = ",Nmix_co2 
     491         if (is_master) write(*,*)" Nmix_co2 = ",Nmix_co2 
    460492 
    461493!         write(*,*)"Number of radiatively active aerosols:" 
     
    464496!         write(*,*)" naerkind = ",naerkind 
    465497 
    466          write(*,*)"Opacity of dust (if used):" 
     498         if (is_master) write(*,*)"Opacity of dust (if used):" 
    467499         dusttau=0. ! default value 
    468500         call getin_p("dusttau",dusttau) 
    469          write(*,*)" dusttau = ",dusttau 
    470  
    471          write(*,*)"Radiatively active CO2 aerosols?" 
     501         if (is_master) write(*,*)" dusttau = ",dusttau 
     502 
     503         if (is_master) write(*,*)"Radiatively active CO2 aerosols?" 
    472504         aeroco2=.false.     ! default value 
    473505         call getin_p("aeroco2",aeroco2) 
    474          write(*,*)" aeroco2 = ",aeroco2 
    475  
    476          write(*,*)"Fixed CO2 aerosol distribution?" 
     506         if (is_master) write(*,*)" aeroco2 = ",aeroco2 
     507 
     508         if (is_master) write(*,*)"Fixed CO2 aerosol distribution?" 
    477509         aerofixco2=.false.     ! default value 
    478510         call getin_p("aerofixco2",aerofixco2) 
    479          write(*,*)" aerofixco2 = ",aerofixco2 
    480  
    481          write(*,*)"Radiatively active water ice?" 
     511         if (is_master) write(*,*)" aerofixco2 = ",aerofixco2 
     512 
     513         if (is_master) write(*,*)"Radiatively active water ice?" 
    482514         aeroh2o=.false.     ! default value 
    483515         call getin_p("aeroh2o",aeroh2o) 
    484          write(*,*)" aeroh2o = ",aeroh2o 
    485  
    486          write(*,*)"Fixed H2O aerosol distribution?" 
     516         if (is_master) write(*,*)" aeroh2o = ",aeroh2o 
     517 
     518         if (is_master) write(*,*)"Fixed H2O aerosol distribution?" 
    487519         aerofixh2o=.false.     ! default value 
    488520         call getin_p("aerofixh2o",aerofixh2o) 
    489          write(*,*)" aerofixh2o = ",aerofixh2o 
    490  
    491          write(*,*)"Radiatively active sulfuric acid aersols?" 
     521         if (is_master) write(*,*)" aerofixh2o = ",aerofixh2o 
     522 
     523         if (is_master) write(*,*)"Radiatively active sulfuric", 
     524     &          " acid aersols?" 
    492525         aeroh2so4=.false.     ! default value 
    493526         call getin_p("aeroh2so4",aeroh2so4) 
    494          write(*,*)" aeroh2so4 = ",aeroh2so4 
     527         if (is_master) write(*,*)" aeroh2so4 = ",aeroh2so4 
    495528          
    496529!================================= 
    497530 
    498          write(*,*)"Radiatively active two-layer aersols?" 
     531         if (is_master) write(*,*)"Radiatively active two-layer aersols?" 
    499532         aeroback2lay=.false.     ! default value 
    500533         call getin_p("aeroback2lay",aeroback2lay) 
    501          write(*,*)" aeroback2lay = ",aeroback2lay 
    502  
    503          write(*,*)"TWOLAY AEROSOL: total optical depth ", 
     534         if (is_master) write(*,*)" aeroback2lay = ",aeroback2lay 
     535 
     536         if (is_master) write(*,*)"TWOLAY AEROSOL: total optical depth ", 
    504537     &              "in the tropospheric layer (visible)" 
    505538         obs_tau_col_tropo=8.D0 
    506539         call getin_p("obs_tau_col_tropo",obs_tau_col_tropo) 
    507          write(*,*)" obs_tau_col_tropo = ",obs_tau_col_tropo 
    508  
    509          write(*,*)"TWOLAY AEROSOL: total optical depth ", 
     540         if (is_master) write(*,*)" obs_tau_col_tropo = ", 
     541     &          obs_tau_col_tropo 
     542 
     543         if (is_master) write(*,*)"TWOLAY AEROSOL: total optical depth ", 
    510544     &              "in the stratospheric layer (visible)" 
    511545         obs_tau_col_strato=0.08D0 
    512546         call getin_p("obs_tau_col_strato",obs_tau_col_strato) 
    513          write(*,*)" obs_tau_col_strato = ",obs_tau_col_strato 
    514  
    515          write(*,*)"TWOLAY AEROSOL: pres_bottom_tropo? in pa" 
     547         if (is_master) write(*,*)" obs_tau_col_strato = ", 
     548     &          obs_tau_col_strato 
     549 
     550         if (is_master) write(*,*)"TWOLAY AEROSOL: pres_bottom_tropo?", 
     551     &          " in pa" 
    516552         pres_bottom_tropo=66000.0 
    517553         call getin_p("pres_bottom_tropo",pres_bottom_tropo) 
    518          write(*,*)" pres_bottom_tropo = ",pres_bottom_tropo 
    519  
    520          write(*,*)"TWOLAY AEROSOL: pres_top_tropo? in pa" 
     554         if (is_master) write(*,*)" pres_bottom_tropo = ", 
     555     &          pres_bottom_tropo 
     556 
     557         if (is_master) write(*,*)"TWOLAY AEROSOL: pres_top_tropo?", 
     558     &          " in pa" 
    521559         pres_top_tropo=18000.0 
    522560         call getin_p("pres_top_tropo",pres_top_tropo) 
    523          write(*,*)" pres_top_tropo = ",pres_top_tropo 
    524  
    525          write(*,*)"TWOLAY AEROSOL: pres_bottom_strato? in pa" 
     561         if (is_master) write(*,*)" pres_top_tropo = ",pres_top_tropo 
     562 
     563         if (is_master) write(*,*)"TWOLAY AEROSOL: pres_bottom_strato?", 
     564     &          " in pa" 
    526565         pres_bottom_strato=2000.0 
    527566         call getin_p("pres_bottom_strato",pres_bottom_strato) 
    528          write(*,*)" pres_bottom_strato = ",pres_bottom_strato 
    529  
    530          write(*,*)"TWOLAY AEROSOL: pres_top_strato? in pa" 
     567         if (is_master) write(*,*)" pres_bottom_strato = ", 
     568     &          pres_bottom_strato 
     569 
     570         if (is_master) write(*,*)"TWOLAY AEROSOL: pres_top_strato?", 
     571     &          " in pa" 
    531572         pres_top_strato=100.0 
    532573         call getin_p("pres_top_strato",pres_top_strato) 
    533          write(*,*)" pres_top_strato = ",pres_top_strato 
    534  
    535          write(*,*)"TWOLAY AEROSOL: particle size in the ", 
    536      &              "tropospheric layer, in meters" 
     574         if (is_master) write(*,*)" pres_top_strato = ",pres_top_strato 
     575 
     576         if (is_master) write(*,*)"TWOLAY AEROSOL: particle size", 
     577     &          " in the tropospheric layer, in meters" 
    537578         size_tropo=2.e-6 
    538579         call getin_p("size_tropo",size_tropo) 
    539          write(*,*)" size_tropo = ",size_tropo 
    540  
    541          write(*,*)"TWOLAY AEROSOL: particle size in the ", 
    542      &              "stratospheric layer, in meters" 
     580         if (is_master) write(*,*)" size_tropo = ",size_tropo 
     581 
     582         if (is_master) write(*,*)"TWOLAY AEROSOL: particle size", 
     583     &           "in the stratospheric layer, in meters" 
    543584         size_strato=1.e-7 
    544585         call getin_p("size_strato",size_strato) 
    545          write(*,*)" size_strato = ",size_strato 
     586         if (is_master) write(*,*)" size_strato = ",size_strato 
    546587 
    547588!================================= 
    548589 
    549          write(*,*)"Cloud pressure level (with kastprof only):" 
     590         if (is_master) write(*,*)"Cloud pressure level (with ", 
     591     &          "kastprof only):" 
    550592         cloudlvl=0. ! default value 
    551593         call getin_p("cloudlvl",cloudlvl) 
    552          write(*,*)" cloudlvl = ",cloudlvl 
    553  
    554          write(*,*)"Is the variable gas species radiatively active?" 
     594         if (is_master) write(*,*)" cloudlvl = ",cloudlvl 
     595 
     596         if (is_master) write(*,*)"Is the variable gas species", 
     597     &          " radiatively active?" 
    555598         Tstrat=167.0 
    556599         varactive=.false. 
    557600         call getin_p("varactive",varactive) 
    558          write(*,*)" varactive = ",varactive 
    559  
    560          write(*,*)"Is the variable gas species distribution set?" 
     601         if (is_master) write(*,*)" varactive = ",varactive 
     602 
     603         if (is_master) write(*,*)"Is the variable gas species", 
     604     &          " distribution set?" 
    561605         varfixed=.false. 
    562606         call getin_p("varfixed",varfixed) 
    563          write(*,*)" varfixed = ",varfixed 
    564  
    565          write(*,*)"What is the saturation % of the variable species?" 
     607         if (is_master) write(*,*)" varfixed = ",varfixed 
     608 
     609         if (is_master) write(*,*)"What is the saturation % of", 
     610     &          " the variable species?" 
    566611         satval=0.8 
    567612         call getin_p("satval",satval) 
    568          write(*,*)" satval = ",satval 
     613         if (is_master) write(*,*)" satval = ",satval 
    569614 
    570615 
     
    572617! if varactive, then varfixed should be false 
    573618         if (varactive.and.varfixed) then 
    574            print*,'if varactive, varfixed must be OFF!' 
     619           if (is_master) print*,'if varactive, varfixed must be OFF!' 
    575620           stop 
    576621         endif 
    577622 
    578          write(*,*) "Gravitationnal sedimentation ?" 
     623         if (is_master) write(*,*) "Gravitationnal sedimentation ?" 
    579624         sedimentation=.false. ! default value 
    580625         call getin_p("sedimentation",sedimentation) 
    581          write(*,*) " sedimentation = ",sedimentation 
    582  
    583          write(*,*) "Compute water cycle ?" 
     626         if (is_master) write(*,*) " sedimentation = ",sedimentation 
     627 
     628         if (is_master) write(*,*) "Compute water cycle ?" 
    584629         water=.false. ! default value 
    585630         call getin_p("water",water) 
    586          write(*,*) " water = ",water 
     631         if (is_master) write(*,*) " water = ",water 
    587632          
    588633! Test of incompatibility: 
    589634! if water is true, there should be at least a tracer 
    590635         if (water.and.(.not.tracer)) then 
    591            print*,'if water is ON, tracer must be ON too!' 
     636           if (is_master) print*,'if water is ON, tracer must be ', 
     637     &          'ON too!' 
    592638           stop 
    593639         endif 
    594640 
    595          write(*,*) "Include water condensation ?" 
     641         if (is_master) write(*,*) "Include water condensation ?" 
    596642         watercond=.false. ! default value 
    597643         call getin_p("watercond",watercond) 
    598          write(*,*) " watercond = ",watercond 
     644         if (is_master) write(*,*) " watercond = ",watercond 
    599645 
    600646! Test of incompatibility: 
    601647! if watercond is used, then water should be used too 
    602648         if (watercond.and.(.not.water)) then 
    603            print*,'if watercond is used, water should be used too' 
     649           if (is_master) print*,'if watercond is used, water should ', 
     650     &          'be used too' 
    604651           stop 
    605652         endif 
    606653 
    607          write(*,*) "Include water precipitation ?" 
     654         if (is_master) write(*,*) "Include water precipitation ?" 
    608655         waterrain=.false. ! default value 
    609656         call getin_p("waterrain",waterrain) 
    610          write(*,*) " waterrain = ",waterrain 
    611  
    612          write(*,*) "Include surface hydrology ?" 
     657         if (is_master) write(*,*) " waterrain = ",waterrain 
     658 
     659         if (is_master) write(*,*) "Include surface hydrology ?" 
    613660         hydrology=.false. ! default value 
    614661         call getin_p("hydrology",hydrology) 
    615          write(*,*) " hydrology = ",hydrology 
    616  
    617          write(*,*) "Evolve surface water sources ?" 
     662         if (is_master) write(*,*) " hydrology = ",hydrology 
     663 
     664         if (is_master) write(*,*) "Evolve surface water sources ?" 
    618665         sourceevol=.false. ! default value 
    619666         call getin_p("sourceevol",sourceevol) 
    620          write(*,*) " sourceevol = ",sourceevol 
    621  
    622          write(*,*) "Ice evolution timestep ?" 
     667         if (is_master) write(*,*) " sourceevol = ",sourceevol 
     668 
     669         if (is_master) write(*,*) "Ice evolution timestep ?" 
    623670         icetstep=100.0 ! default value 
    624671         call getin_p("icetstep",icetstep) 
    625          write(*,*) " icetstep = ",icetstep 
    626  
    627          write(*,*) "Snow albedo ?" 
     672         if (is_master) write(*,*) " icetstep = ",icetstep 
     673 
     674         if (is_master) write(*,*) "Snow albedo ?" 
    628675         albedosnow=0.5         ! default value 
    629676         call getin_p("albedosnow",albedosnow) 
    630          write(*,*) " albedosnow = ",albedosnow 
    631  
    632          write(*,*) "Maximum ice thickness ?" 
     677         if (is_master) write(*,*) " albedosnow = ",albedosnow 
     678 
     679         if (is_master) write(*,*) "Maximum ice thickness ?" 
    633680         maxicethick=2.0         ! default value 
    634681         call getin_p("maxicethick",maxicethick) 
    635          write(*,*) " maxicethick = ",maxicethick 
    636  
    637          write(*,*) "Freezing point of seawater ?" 
     682         if (is_master) write(*,*) " maxicethick = ",maxicethick 
     683 
     684         if (is_master) write(*,*) "Freezing point of seawater ?" 
    638685         Tsaldiff=-1.8          ! default value 
    639686         call getin_p("Tsaldiff",Tsaldiff) 
    640          write(*,*) " Tsaldiff = ",Tsaldiff 
    641  
    642          write(*,*) "Does user want to force cpp and mugaz?" 
     687         if (is_master) write(*,*) " Tsaldiff = ",Tsaldiff 
     688 
     689         if (is_master) write(*,*) "Does user want to force", 
     690     &          " cpp and mugaz?" 
    643691         force_cpp=.false. ! default value 
    644692         call getin_p("force_cpp",force_cpp) 
    645          write(*,*) " force_cpp = ",force_cpp 
     693         if (is_master) write(*,*) " force_cpp = ",force_cpp 
    646694 
    647695         if (force_cpp) then 
    648696           mugaz = -99999. 
    649            PRINT *,'MEAN MOLECULAR MASS in g mol-1 ?' 
     697           if (is_master) PRINT *,'MEAN MOLECULAR MASS in g mol-1 ?' 
    650698           call getin_p("mugaz",mugaz) 
    651699           IF (mugaz.eq.-99999.) THEN 
    652                PRINT *, "mugaz must be set if force_cpp = T" 
     700               if (is_master) PRINT *, "mugaz must be set if ', 
     701     &          'force_cpp = T" 
    653702               STOP 
    654703           ELSE 
    655                write(*,*) "inifis: mugaz=",mugaz 
     704               if (is_master) write(*,*) "inifis: mugaz=",mugaz 
    656705           ENDIF 
    657706           !Ehouarn: once mugaz has been set, r, the specific 
    658707           ! gas constant must be computed 
    659708           r=8.3144622/(mugaz*1.e-3) 
    660            write(*,*) "inifis: r=",r 
     709           if (is_master) write(*,*) "inifis: r=",r 
    661710            
    662711           cpp = -99999. 
    663            PRINT *,'SPECIFIC HEAT CAPACITY in J K-1 kg-1 ?' 
     712           if (is_master) PRINT *,'SPECIFIC HEAT CAPACITY in ', 
     713     &          'J K-1 kg-1 ?' 
    664714           call getin_p("cpp",cpp) 
    665715           IF (cpp.eq.-99999.) THEN 
    666                PRINT *, "cpp must be set if force_cpp = T" 
     716               if (is_master) PRINT *, "cpp must be set if ', 
     717     &          'force_cpp = T" 
    667718               STOP 
    668719           ELSE 
    669                write(*,*) "inifis: cpp=",cpp 
     720               if (is_master) write(*,*) "inifis: cpp=",cpp 
    670721           ENDIF 
    671722!         else 
     
    675726         call calc_cpp_mugaz 
    676727 
    677          PRINT*,'--------------------------------------------' 
    678          PRINT* 
    679          PRINT* 
     728         if (is_master) PRINT*,'------------------------------------' 
     729         if (is_master) PRINT* 
     730         if (is_master) PRINT* 
    680731      ELSE 
    681          write(*,*) 
    682          write(*,*) 'Cannot read file callphys.def. Is it here ?' 
     732         if (is_master) write(*,*) 
     733         if (is_master) write(*,*) 'Cannot read file callphys.def.", 
     734     &          " Is it here ?' 
    683735         stop 
    684736      ENDIF 
     
    6877398001  FORMAT(t5,a12,i8) 
    688740 
     741      if (is_master) then 
    689742      PRINT* 
    690743      PRINT*,'inifis: daysec',daysec 
     
    694747      PRINT*,'        or each ',iradia*dtphys,' seconds' 
    695748      PRINT* 
     749      end if 
    696750 
    697751 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/iniorbit.F

    r227 r298  
    44      USE planete_mod, only: apoastr, periastr, year_day, obliquit, 
    55     &                       peri_day, e_elips, p_elips, timeperi 
     6      USE mod_phys_lmdz_para, only : is_master 
    67      IMPLICIT NONE 
    78 
     
    6768      !!!! We hope that all cases are above 25 Mkm [OK with Gliese 581d] 
    6869      IF ( apoastr .gt. 25.) THEN 
     70        IF (is_master) THEN 
    6971        PRINT*,'!!!!! WARNING !!!!!' 
    7072        PRINT*,'!!!!! YOU ARE ABOUT TO WITNESS A DIRT HACK !!!!!' 
     
    7375        PRINT*,'So I am assuming units are in Mkm here' 
    7476        PRINT*,'and I am performing a conversion towards AU.' 
     77        END IF 
    7578        periastr = periastr / 149.598 ! Mkm to AU 
    7679        apoastr = apoastr / 149.598 ! Mkm to AU 
     
    8083 
    8184  
    82       PRINT*,'Periastron in AU  ',periastr 
    83       PRINT*,'Apoastron in AU  ',apoastr  
    84       PRINT*,'Obliquity in degrees  :',obliquit 
     85      IF (is_master) PRINT*,'Periastron in AU  ',periastr 
     86      IF (is_master) PRINT*,'Apoastron in AU  ',apoastr  
     87      IF (is_master) PRINT*,'Obliquity in degrees  :',obliquit 
    8588 
    8689 
     
    8891      p_elips=0.5*(periastr+apoastr)*(1-e_elips*e_elips) 
    8992 
    90       print*,'e_elips',e_elips 
    91       print*,'p_elips',p_elips 
     93      IF (is_master) print*,'e_elips',e_elips 
     94      IF (is_master) print*,'p_elips',p_elips 
    9295 
    9396c----------------------------------------------------------------------- 
     
    100103      zanom=2.*pi*(zz-nint(zz)) 
    101104      zxref=abs(zanom) 
    102       PRINT*,'zanom  ',zanom 
     105      IF (is_master) PRINT*,'zanom  ',zanom 
    103106 
    104107c  resolution de l'equation horaire  zx0 - e * sin (zx0) = zxref 
     
    114117      zx0=zx0+zdx 
    115118      if(zanom.lt.0.) zx0=-zx0 
    116       PRINT*,'zx0   ',zx0 
     119      IF (is_master) PRINT*,'zx0   ',zx0 
    117120 
    118121c zteta est la longitude solaire 
    119122 
    120123      timeperi=2.*atan(sqrt((1.+e_elips)/(1.-e_elips))*tan(zx0/2.)) 
    121       PRINT*,'Solar longitude of periastron timeperi = ',timeperi 
     124      IF (is_master) PRINT*,'Solar longitude of periastron', 
     125     &          ' timeperi = ',timeperi 
    122126 
    123127      RETURN 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/interpolateH2H2.F90

    r227 r298  
    1515 
    1616      use datafile_mod, only: datadir 
     17      use mod_phys_lmdz_para, only : is_master 
    1718 
    1819      implicit none 
     
    6667 
    6768      if(firstcall)then ! called by sugas_corrk only 
    68          print*,'----------------------------------------------------' 
    69          print*,'Initialising H2-H2 continuum from HITRAN database...' 
     69         if (is_master) print*,'----------------------------------------------------' 
     70         if (is_master) print*,'Initialising H2-H2 continuum from HITRAN database...' 
    7071 
    7172!     1.1 Open the ASCII files 
     
    106107!$OMP BARRIER 
    107108 
    108          print*,'interpolateH2H2: At wavenumber ',wn,' cm^-1' 
    109          print*,'   temperature ',temp,' K' 
    110          print*,'   pressure ',pres,' Pa' 
     109         if (is_master) print*,'interpolateH2H2: At wavenumber ',wn,' cm^-1' 
     110         if (is_master) print*,'   temperature ',temp,' K' 
     111         if (is_master) print*,'   pressure ',pres,' Pa' 
    111112 
    112113      endif 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/interpolateH2He.F90

    r227 r298  
    1515 
    1616      use datafile_mod, only: datadir 
     17      use mod_phys_lmdz_para, only : is_master 
    1718 
    1819      implicit none 
     
    6869 
    6970      if(firstcall)then ! called by sugas_corrk only 
    70          print*,'----------------------------------------------------' 
    71          print*,'Initialising H2-He continuum from HITRAN database...' 
     71         if (is_master) print*,'----------------------------------------------------' 
     72         if (is_master) print*,'Initialising H2-He continuum from HITRAN database...' 
    7273 
    7374!     1.1 Open the ASCII files 
     
    108109!$OMP BARRIER 
    109110 
     111         if (is_master) then  
    110112         print*,'interpolateH2He: At wavenumber ',wn,' cm^-1' 
    111113         print*,'   temperature                 ',temp,' K' 
    112114         print*,'   H2 partial pressure         ',presH2,' Pa' 
    113115         print*,'   and He partial pressure     ',presHe,' Pa' 
     116         end if 
    114117 
    115118      endif 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/phyetat0_academic.F90

    r270 r298  
    1111                     inquire_dimension, inquire_dimension_length 
    1212  use slab_ice_h, only: noceanmx 
     13  use mod_phys_lmdz_para, only : is_master 
    1314 
    1415  implicit none 
     
    102103! Ehouarn, if file not found, then call tabfi with nid_start==0 
    103104if (.not.found_file) then 
    104   write(*,*) 'phyetat0_academic: call tabfi with nid_start=0' 
     105  if (is_master) write(*,*) 'phyetat0_academic: call tabfi with nid_start=0' 
    105106  call tabfi (ngrid,0,Lmodif,tab0,day_ini,lmax,p_rad, & 
    106107                   p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time) 
    107108else 
    108109  ! possibility to modify tab_cntrl in tabfi 
    109   write(*,*) 
    110   write(*,*) 'TABFI in phyeta0: Lmodif=',Lmodif," tab0=",tab0 
     110  if (is_master) write(*,*) 
     111  if (is_master) write(*,*) 'TABFI in phyeta0: Lmodif=',Lmodif," tab0=",tab0 
    111112  call tabfi (ngrid,nid_start,Lmodif,tab0,day_ini,lmax,p_rad, & 
    112113                   p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time) 
     
    176177endif 
    177178if (.not.found) then 
    178   write(*,*) "phyetat0: Failed loading <phisfi>" 
     179  if (is_master) write(*,*) "phyetat0: Failed loading <phisfi>" 
    179180  phisfi(:)=0 
    180181else 
    181   write(*,*) "phyetat0: surface geopotential <phisfi> range:", & 
     182  if (is_master) write(*,*) "phyetat0: surface geopotential <phisfi> range:", & 
    182183             minval(phisfi), maxval(phisfi) 
    183184endif 
     
    190191endif 
    191192if (.not.found) then 
    192   write(*,*) "phyetat0: Failed loading <albedodat>" 
     193  if (is_master) write(*,*) "phyetat0: Failed loading <albedodat>" 
    193194  do ig=1,ngrid 
    194195    albedodat(ig)=0. 
    195196  enddo 
    196197else 
    197   write(*,*) "phyetat0: Bare ground albedo <albedodat> range:", & 
     198  if (is_master) write(*,*) "phyetat0: Bare ground albedo <albedodat> range:", & 
    198199             minval(albedodat), maxval(albedodat) 
    199200endif 
     
    208209    zmea(:)=0. 
    209210else 
    210   write(*,*) "phyetat0: <ZMEA> range:", & 
     211  if (is_master) write(*,*) "phyetat0: <ZMEA> range:", & 
    211212             minval(zmea), maxval(zmea) 
    212213endif 
     
    219220endif 
    220221if (.not.found) then 
    221   write(*,*) "phyetat0: Failed loading <ZSTD>" 
     222  if (is_master) write(*,*) "phyetat0: Failed loading <ZSTD>" 
    222223   zstd(:)=0. 
    223224else 
    224   write(*,*) "phyetat0: <ZSTD> range:", & 
     225  if (is_master) write(*,*) "phyetat0: <ZSTD> range:", & 
    225226             minval(zstd), maxval(zstd) 
    226227endif 
     
    233234endif 
    234235if (.not.found) then 
    235   write(*,*) "phyetat0: Failed loading <ZSIG>" 
     236  if (is_master) write(*,*) "phyetat0: Failed loading <ZSIG>" 
    236237  zsig(:)=0. 
    237238else 
    238   write(*,*) "phyetat0: <ZSIG> range:", & 
     239  if (is_master) write(*,*) "phyetat0: <ZSIG> range:", & 
    239240             minval(zsig), maxval(zsig) 
    240241endif 
     
    247248endif 
    248249if (.not.found) then 
    249   write(*,*) "phyetat0: Failed loading <ZGAM>" 
     250  if (is_master) write(*,*) "phyetat0: Failed loading <ZGAM>" 
    250251  zgam(:)=0. 
    251252else 
    252   write(*,*) "phyetat0: <ZGAM> range:", & 
     253  if (is_master) write(*,*) "phyetat0: <ZGAM> range:", & 
    253254             minval(zgam), maxval(zgam) 
    254255endif 
     
    261262endif 
    262263if (.not.found) then 
    263   write(*,*) "phyetat0: Failed loading <ZTHE>" 
     264  if (is_master) write(*,*) "phyetat0: Failed loading <ZTHE>" 
    264265  zthe(:)=0. 
    265266else 
    266   write(*,*) "phyetat0: <ZTHE> range:", & 
     267  if (is_master) write(*,*) "phyetat0: <ZTHE> range:", & 
    267268             minval(zthe), maxval(zthe) 
    268269endif 
     
    278279  !tsurf(:)=175.0 
    279280else 
    280   write(*,*) "phyetat0: Surface temperature <tsurf> range:", & 
     281  if (is_master) write(*,*) "phyetat0: Surface temperature <tsurf> range:", & 
    281282             minval(tsurf), maxval(tsurf) 
    282283endif 
     
    289290endif 
    290291if (.not.found) then 
    291   write(*,*) "phyetat0: Failed loading <emis>" 
     292  if (is_master) write(*,*) "phyetat0: Failed loading <emis>" 
    292293  emis(:)=0.5 
    293294else 
    294   write(*,*) "phyetat0: Surface emissivity <emis> range:", & 
     295  if (is_master) write(*,*) "phyetat0: Surface emissivity <emis> range:", & 
    295296             minval(emis), maxval(emis) 
    296297endif 
     
    303304endif 
    304305if (.not.found) then 
    305   write(*,*) "phyetat0: Failed loading <cloudfrac>" 
     306  if (is_master) write(*,*) "phyetat0: Failed loading <cloudfrac>" 
    306307  cloudfrac(:,:)=0. 
    307308else 
    308   write(*,*) "phyetat0: Cloud fraction <cloudfrac> range:", & 
     309  if (is_master) write(*,*) "phyetat0: Cloud fraction <cloudfrac> range:", & 
    309310             minval(cloudfrac), maxval(cloudfrac) 
    310311endif 
     
    317318endif 
    318319if (.not.found) then 
    319   write(*,*) "phyetat0: Failed loading <totcloudfrac>" 
     320  if (is_master) write(*,*) "phyetat0: Failed loading <totcloudfrac>" 
    320321  totcloudfrac(:)=0.5 
    321322else 
    322   write(*,*) "phyetat0: Total cloud fraction <totcloudfrac> range:", & 
     323  if (is_master) write(*,*) "phyetat0: Total cloud fraction <totcloudfrac> range:", & 
    323324             minval(totcloudfrac), maxval(totcloudfrac) 
    324325endif 
     
    331332endif 
    332333if (.not.found) then 
    333   write(*,*) "phyetat0: Failed loading <hice>" 
     334  if (is_master) write(*,*) "phyetat0: Failed loading <hice>" 
    334335!  call abort 
    335336      do ig=1,ngrid 
     
    337338      enddo 
    338339else 
    339   write(*,*) "phyetat0: Height of oceanic ice <hice> range:", & 
     340  if (is_master) write(*,*) "phyetat0: Height of oceanic ice <hice> range:", & 
    340341             minval(hice), maxval(hice) 
    341342endif 
     
    349350endif 
    350351if (.not.found) then 
    351   write(*,*) "phyetat0: Failed loading <rnat>" 
     352  if (is_master) write(*,*) "phyetat0: Failed loading <rnat>" 
    352353      do ig=1,ngrid 
    353354        rnat(ig)=1. 
     
    362363      enddo 
    363364 
    364   write(*,*) "phyetat0: Nature of surface <rnat> range:", & 
     365  if (is_master) write(*,*) "phyetat0: Nature of surface <rnat> range:", & 
    365366             minval(rnat), maxval(rnat) 
    366367endif 
     
    372373endif 
    373374if (.not.found) then 
    374   write(*,*) "phyetat0: Failed loading <pctsrf_sic>" 
     375  if (is_master) write(*,*) "phyetat0: Failed loading <pctsrf_sic>" 
    375376      do ig=1,ngrid 
    376377      pctsrf_sic(ig)=0. 
    377378      enddo 
    378379else 
    379   write(*,*) "phyetat0: Pourcentage of sea ice cover <pctsrf_sic> range:", & 
     380  if (is_master) write(*,*) "phyetat0: Pourcentage of sea ice cover <pctsrf_sic> range:", & 
    380381             minval(pctsrf_sic), maxval(pctsrf_sic) 
    381382endif 
     
    387388endif 
    388389if (.not.found) then 
    389   write(*,*) "phyetat0: Failed loading <tslab>" 
     390  if (is_master) write(*,*) "phyetat0: Failed loading <tslab>" 
    390391      do ig=1,ngrid 
    391392      do iq=1,noceanmx 
     
    394395      enddo 
    395396else 
    396   write(*,*) "phyetat0: Slab ocean temperature <tslab> range:", & 
     397  if (is_master) write(*,*) "phyetat0: Slab ocean temperature <tslab> range:", & 
    397398             minval(tslab), maxval(tslab) 
    398399endif 
     
    404405endif 
    405406if (.not.found) then 
    406   write(*,*) "phyetat0: Failed loading <tsea_ice>" 
     407  if (is_master) write(*,*) "phyetat0: Failed loading <tsea_ice>" 
    407408      do ig=1,ngrid 
    408409      tsea_ice(ig)=273.15-1.8 
    409410      enddo 
    410411else 
    411   write(*,*) "phyetat0: Oceanic ice temperature <tsea_ice> range:", & 
     412  if (is_master) write(*,*) "phyetat0: Oceanic ice temperature <tsea_ice> range:", & 
    412413             minval(tsea_ice), maxval(tsea_ice) 
    413414endif 
     
    419420endif 
    420421if (.not.found) then 
    421   write(*,*) "phyetat0: Failed loading <sea_ice>" 
     422  if (is_master) write(*,*) "phyetat0: Failed loading <sea_ice>" 
    422423      do ig=1,ngrid 
    423424      tsea_ice(ig)=0. 
    424425      enddo 
    425426else 
    426   write(*,*) "phyetat0: Oceanic ice quantity <sea_ice> range:", & 
     427  if (is_master) write(*,*) "phyetat0: Oceanic ice quantity <sea_ice> range:", & 
    427428             minval(sea_ice), maxval(sea_ice) 
    428429endif 
     
    438439endif 
    439440if (.not.found) then 
    440   write(*,*) "phyetat0: Failed loading <q2>" 
     441  if (is_master) write(*,*) "phyetat0: Failed loading <q2>" 
    441442  q2(:,:)=0.001 
    442443else 
    443   write(*,*) "phyetat0: PBL wind variance <q2> range:", & 
     444  if (is_master) write(*,*) "phyetat0: PBL wind variance <q2> range:", & 
    444445             minval(q2), maxval(q2) 
    445446endif 
     
    453454      ! "h2o_ice" should be loaded instead 
    454455      txt="h2o_ice" 
    455       write(*,*) 'phyetat0: loading surface tracer', & 
     456      if (is_master) write(*,*) 'phyetat0: loading surface tracer', & 
    456457                           ' h2o_ice instead of h2o_vap' 
    457458    endif 
     
    462463    endif 
    463464    if (.not.found) then 
    464       write(*,*) "phyetat0: Failed loading <",trim(txt),">" 
    465       write(*,*) "         ",trim(txt)," is set to zero" 
     465      if (is_master) write(*,*) "phyetat0: Failed loading <",trim(txt),">" 
     466      if (is_master) write(*,*) "         ",trim(txt)," is set to zero" 
    466467    else 
    467       write(*,*) "phyetat0: Surface tracer <",trim(txt),"> range:", & 
     468      if (is_master) write(*,*) "phyetat0: Surface tracer <",trim(txt),"> range:", & 
    468469                 minval(qsurf(:,iq)), maxval(qsurf(:,iq)) 
    469470    endif 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/physiq.F90

    r270 r298  
    569569!ym               rnat,pctsrf_sic,tslab, tsea_ice,sea_ice) 
    570570 
    571          write(*,*) "physiq: firstcall, call phyetat0_academic" 
     571         if (is_master) write(*,*) "physiq: firstcall, call phyetat0_academic" 
    572572         call phyetat0_academic(ngrid,nlayer,"startfi.nc",0,0,nsoilmx,nq,   & 
    573573               day_ini,time_phys,tsurf,tsoil,emis,q2,qsurf,   & 
     
    576576 
    577577!mi initialising tsurf with pt 
    578          write(*,*) "Physiq: initializing tsurf(:) to pt(:,1) !!" 
     578         if (is_master) write(*,*) "Physiq: initializing tsurf(:) to pt(:,1) !!" 
    579579         tsurf(:)=pt(:,1) 
    580580 
    581581         if (pday.ne.day_ini) then 
    582            write(*,*) "ERROR in physiq.F90:" 
    583            write(*,*) "bad synchronization between physics and dynamics" 
    584            write(*,*) "dynamics day: ",pday 
    585            write(*,*) "physics day:  ",day_ini 
    586            write(*,*) "taking dynamics day for physics:  ",day_ini 
     582           if (is_master) write(*,*) "ERROR in physiq.F90:" 
     583           if (is_master) write(*,*) "bad synchronization between physics and dynamics" 
     584           if (is_master) write(*,*) "dynamics day: ",pday 
     585           if (is_master) write(*,*) "physics day:  ",day_ini 
     586           if (is_master) write(*,*) "taking dynamics day for physics:  ",day_ini 
    587587           day_ini=pday 
    588588!ym           stop 
    589589         endif 
    590590 
    591          write (*,*) 'In physiq day_ini =', day_ini 
     591         if (is_master) write (*,*) 'In physiq day_ini =', day_ini 
    592592 
    593593!        Initialize albedo and orbital calculation 
     
    598598         albedo(:)=albedo0(:) 
    599599 
    600          if(tlocked)then 
     600         if(tlocked .and. is_master)then 
    601601            print*,'Planet is tidally locked at resonance n=',nres 
    602602            print*,'Make sure you have the right rotation rate!!!' 
     
    652652 
    653653         else 
    654             print*,'WARNING! Thermal conduction in the soil turned off' 
     654            if (is_master) print*,'WARNING! Thermal conduction in the soil turned off' 
    655655            capcal(:)=1.e6 
    656656            fluxgrd(:)=intheat 
    657             print*,'Flux from ground = ',intheat,' W m^-2' 
     657            if (is_master) print*,'Flux from ground = ',intheat,' W m^-2' 
    658658         endif 
    659659         icount=1 
     
    667667                     status="old",iostat=ierr) 
    668668            if (ierr.ne.0) then 
    669               write(*,*) "physiq: Error! No num_run file!" 
    670               write(*,*) " (which is needed for sourceevol option)" 
     669              if (is_master) write(*,*) "physiq: Error! No num_run file!" 
     670              if (is_master) write(*,*) " (which is needed for sourceevol option)" 
    671671              stop 
    672672            endif 
     
    678678            if(num_run.ne.0.and.mod(num_run,2).eq.0)then 
    679679            !if(num_run.ne.0.and.mod(num_run,3).eq.0)then 
    680                print*,'Updating ice at end of this year!' 
     680               if (is_master) print*,'Updating ice at end of this year!' 
    681681               ice_update=.true. 
    682682               ice_min(:)=1.e4 
     
    696696           enddo 
    697697 
    698            print*,'WARNING! Surface type currently decided by surface inertia' 
    699            print*,'This should be improved e.g. in newstart.F' 
     698           if (is_master) print*,'WARNING! Surface type currently decided by surface inertia' 
     699           if (is_master) print*,'This should be improved e.g. in newstart.F' 
    700700         endif!(.not.ok_slab_ocean) 
    701701 
     
    711711!        ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 
    712712         if(nearco2cond) then 
    713             write(*,*)' WARNING! Starting at Tcond+1K' 
     713            if (is_master) write(*,*)' WARNING! Starting at Tcond+1K' 
    714714            do l=1, nlayer 
    715715               do ig=1,ngrid 
     
    892892 
    893893           if(rings_shadow) then  
    894                 write(*,*) 'Rings shadow activated' 
     894                if (is_master) write(*,*) 'Rings shadow activated' 
    895895                if(diurnal .eqv. .false.) then ! we need to compute the daily average insolation  
    896896                    pas = 1./nb_hours 
     
    19201920 
    19211921 
    1922            print*,'--> Ls =',zls*180./pi 
     1922           if (is_master) print*,'--> Ls =',zls*180./pi 
    19231923!        ------------------------------------------------------------------- 
    19241924!        Writing NetCDF file  "RESTARTFI" at the end of the run 
     
    23592359      endif 
    23602360 
    2361       write(*,*) "physiq: done, zday=",zday 
     2361      if (is_master) write(*,*) "physiq: done, zday=",zday 
    23622362      return 
    23632363    end subroutine physiq 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/radii_mod.F90

    r227 r298  
    3737      use radinc_h, only: naerkind 
    3838      use aerosol_mod 
     39      use mod_phys_lmdz_para, only : is_master 
    3940!      USE tracer_h 
    4041      Implicit none 
     
    5455      integer :: iaer    
    5556       
    56       print*,'enter su_aer_radii' 
     57      if (is_master) print*,'enter su_aer_radii' 
    5758          do iaer=1,naerkind 
    5859!     these values will change once the microphysics gets to work 
     
    100101         if (radfixed) then 
    101102 
    102             write(*,*)"radius of H2O water particles:" 
     103            if (is_master) write(*,*)"radius of H2O water particles:" 
    103104            rad_h2o=13. ! default value 
    104105            call getin_p("rad_h2o",rad_h2o) 
    105             write(*,*)" rad_h2o = ",rad_h2o 
    106  
    107             write(*,*)"radius of H2O ice particles:" 
     106            if (is_master) write(*,*)" rad_h2o = ",rad_h2o 
     107 
     108            if (is_master) write(*,*)"radius of H2O ice particles:" 
    108109            rad_h2o_ice=35. ! default value 
    109110            call getin_p("rad_h2o_ice",rad_h2o_ice) 
    110             write(*,*)" rad_h2o_ice = ",rad_h2o_ice 
     111            if (is_master) write(*,*)" rad_h2o_ice = ",rad_h2o_ice 
    111112 
    112113         else 
    113114 
    114             write(*,*)"Number mixing ratio of H2O water particles:" 
     115            if (is_master) write(*,*)"Number mixing ratio of H2O water particles:" 
    115116            Nmix_h2o=1.e6 ! default value 
    116117            call getin_p("Nmix_h2o",Nmix_h2o) 
    117             write(*,*)" Nmix_h2o = ",Nmix_h2o 
    118  
    119             write(*,*)"Number mixing ratio of H2O ice particles:" 
     118            if (is_master) write(*,*)" Nmix_h2o = ",Nmix_h2o 
     119 
     120            if (is_master) write(*,*)"Number mixing ratio of H2O ice particles:" 
    120121            Nmix_h2o_ice=Nmix_h2o ! default value 
    121122            call getin_p("Nmix_h2o_ice",Nmix_h2o_ice) 
    122             write(*,*)" Nmix_h2o_ice = ",Nmix_h2o_ice 
     123            if (is_master) write(*,*)" Nmix_h2o_ice = ",Nmix_h2o_ice 
    123124         endif 
    124125 
    125       print*,'exit su_aer_radii' 
     126      if (is_master) print*,'exit su_aer_radii' 
    126127 
    127128   end subroutine su_aer_radii 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/setspi.F90

    r227 r298  
    2525      use radcommon_h, only: BWNI,BLAMI,WNOI,DWNI,WAVEI,planckir,sigma 
    2626      use datafile_mod, only: datadir 
     27      use mod_phys_lmdz_para, only : is_master 
    2728 
    2829      implicit none 
     
    105106      close(131) 
    106107 
    107       write(*,*) 'setspi: L_NSPECTI = ',L_NSPECTI, 'in the model ' 
    108       write(*,*) '        there are   ',nb, 'entries in ',TRIM(file_path) 
     108      if (is_master) write(*,*) 'setspi: L_NSPECTI = ',L_NSPECTI, 'in the model ' 
     109      if (is_master) write(*,*) '        there are   ',nb, 'entries in ',TRIM(file_path) 
    109110      if(nb.ne.L_NSPECTI) then 
    110111         write(*,*) 'MISMATCH !! I stop here' 
     
    125126!$OMP BARRIER 
    126127 
     128      if (is_master) then 
    127129      print*,'' 
    128130      print*,'setspi: IR band limits:' 
     
    130132         print*,m,'-->',BWNI(M),' cm^-1' 
    131133      end do 
     134      end if 
    132135 
    133136!     Set up mean wavenumbers and wavenumber deltas.  Units of  
     
    149152!     original planck.f; W m^-2 wavenumber^-1, where wavenumber is in CM^-1. 
    150153 
     154      if (is_master) then 
    151155      print*,'' 
    152156      print*,'setspi: Current Planck integration range:' 
    153157      print*,'T = ',dble(NTstar)/NTfac, ' to ',dble(NTstop)/NTfac,' K.' 
     158      end if 
    154159 
    155160      do NW=1,L_NSPECTI 
     
    173178      ! force planck=sigma*eps*T^4 for each temperature in array 
    174179      if(forceEC)then 
    175          print*,'setspi: Force F=sigma*eps*T^4 for all values of T!' 
     180         if (is_master) print*,'setspi: Force F=sigma*eps*T^4 for all values of T!' 
    176181         do nt=NTstar,NTstop 
    177182            plancksum=0.0D0 
     
    198203            plancksum=plancksum+planckir(NW,nt-NTstar+1)*DWNI(NW)*pi 
    199204         end do 
    200          print*,'setspi: At lower limit:' 
    201          print*,'in model sig*T^4 = ',plancksum,' W m^-2' 
    202          print*,'actual sig*T^4   = ',sigma*(dble(nt)/NTfac)**4,' W m^-2' 
     205         if (is_master) print*,'setspi: At lower limit:' 
     206         if (is_master) print*,'in model sig*T^4 = ',plancksum,' W m^-2' 
     207         if (is_master) print*,'actual sig*T^4   = ',sigma*(dble(nt)/NTfac)**4,' W m^-2' 
    203208          
    204209         ! check energy conservation at upper temperature boundary 
     
    208213            plancksum=plancksum+planckir(NW,nt-NTstar+1)*DWNI(NW)*pi 
    209214         end do 
    210          print*,'setspi: At upper limit:' 
    211          print*,'in model sig*T^4 = ',plancksum,' W m^-2' 
    212          print*,'actual sig*T^4   = ',sigma*(dble(nt)/NTfac)**4,' W m^-2' 
    213          print*,'' 
     215         if (is_master) print*,'setspi: At upper limit:' 
     216         if (is_master) print*,'in model sig*T^4 = ',plancksum,' W m^-2' 
     217         if (is_master) print*,'actual sig*T^4   = ',sigma*(dble(nt)/NTfac)**4,' W m^-2' 
     218         if (is_master) print*,'' 
    214219      endif 
    215220 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/setspv.F90

    r227 r298  
    2727                             STELLARF,TAURAY 
    2828      use datafile_mod, only: datadir 
     29      use mod_phys_lmdz_para, only : is_master 
    2930 
    3031      implicit none 
     
    8283      close(131) 
    8384 
    84       write(*,*) 'setspv: L_NSPECTV = ',L_NSPECTV, 'in the model ' 
    85       write(*,*) '        there are   ',nb, 'entries in ',TRIM(file_path) 
     85      if (is_master) write(*,*) 'setspv: L_NSPECTV = ',L_NSPECTV, 'in the model ' 
     86      if (is_master) write(*,*) '        there are   ',nb, 'entries in ',TRIM(file_path) 
    8687      if(nb.ne.L_NSPECTV) then 
    8788         write(*,*) 'MISMATCH !! I stop here' 
     
    102103!$OMP BARRIER 
    103104 
     105      if (is_master) then 
    104106      print*,'setspv: VI band limits:' 
    105107      do M=1,L_NSPECTV+1 
     
    107109      end do 
    108110      print*,' ' 
     111      end if 
    109112 
    110113!     Set up mean wavenumbers and wavenumber deltas.  Units of  
     
    123126!     Set up stellar spectrum 
    124127 
    125       write(*,*)'setspv: Interpolating stellar spectrum from the hires data...' 
     128      if (is_master) write(*,*)'setspv: Interpolating stellar spectrum from the hires data...' 
    126129      call ave_stelspec(STELLAR) 
    127130 
     
    132135         sum         = sum+STELLARF(N) 
    133136      end do 
    134       write(6,'("setspv: Stellar flux at 1 AU = ",f7.2," W m-2")') sum 
    135       print*,' ' 
     137      if (is_master) write(6,'("setspv: Stellar flux at 1 AU = ",f7.2," W m-2")') sum 
     138      if (is_master) print*,' ' 
    136139 
    137140 
     
    144147         call calc_rayleigh 
    145148      else 
    146          print*,'setspv: No Rayleigh scattering, check for NaN in output!' 
     149         if (is_master) print*,'setspv: No Rayleigh scattering, check for NaN in output!' 
    147150         do N=1,L_NSPECTV 
    148151            TAURAY(N) = 1E-16 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/suaer_corrk.F90

    r227 r298  
    1111      use radcommon_h, only: qrefvis,qrefir,omegarefvis,omegarefir 
    1212      use aerosol_mod 
     13      use mod_phys_lmdz_para, only : is_master 
    1314 
    1415      implicit none 
     
    170171 
    171172       if (iaer.eq.iaero_back2lay) then 
    172          print*, 'naerkind= back2lay', iaer 
     173         if (is_master) print*, 'naerkind= back2lay', iaer 
    173174 
    174175!     visible 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/sugas_corrk.F90

    r227 r298  
    3030!      use ioipsl_getincom 
    3131      use ioipsl_getincom_p  
     32      use mod_phys_lmdz_para, only : is_master 
    3233      implicit none 
    3334 
     
    105106      do igas=1,ngas 
    106107         read(111,*) gastype(igas) 
    107          print*,'Gas ',igas,' is ',gastype(igas) 
     108         if (is_master) print*,'Gas ',igas,' is ',gastype(igas) 
    108109      enddo 
    109110 
     
    135136 
    136137      ! display the values 
     138      if (is_master) then  
    137139      print*,'Variable gas volume mixing ratios:' 
    138140      do n=1,L_REFVAR 
     
    141143      end do 
    142144      print*,'' 
     145      end if 
    143146 
    144147!======================================================================= 
     
    172175  
    173176      ! display the values 
     177      if (is_master) then 
    174178      print*,'Correlated-k g-space grid:' 
    175179      do n=1,L_NGAUSS 
     
    177181      end do 
    178182      print*,'' 
     183      end if 
    179184 
    180185!======================================================================= 
     
    210215 
    211216      ! display the values 
     217      if (is_master) then 
    212218      print*,'Correlated-k pressure grid (mBar):' 
    213219      do n=1,L_NPREF 
     
    215221      end do 
    216222      print*,'' 
     223      end if 
    217224 
    218225      ! save the min / max matrix values 
     
    255262 
    256263      ! display the values 
     264      if (is_master) then 
    257265      print*,'Correlated-k temperature grid:' 
    258266      do n=1,L_NTREF 
    259267         print*,n,'.',tgasref(n),' K' 
    260268      end do 
     269      end if 
    261270 
    262271      ! save the min / max matrix values 
     
    275284 
    276285      ! display the values 
    277       print*,'' 
    278       print*,'Correlated-k matrix size:'  
    279       print*,'[',L_NTREF,',',L_NPREF,',',L_REFVAR,',',L_NGAUSS,']'  
     286      if (is_master) print*,'' 
     287      if (is_master) print*,'Correlated-k matrix size:'  
     288      if (is_master) print*,'[',L_NTREF,',',L_NPREF,',',L_REFVAR,',',L_NGAUSS,']'  
    280289 
    281290!======================================================================= 
     
    285294!        wavelength used to separate IR from VI in graybody. We will need that anyway 
    286295         IR_VI_wnlimit=3000. 
    287          write(*,*)"graybody: Visible / Infrared separation set at",10000./IR_VI_wnlimit,"um" 
     296         if (is_master) write(*,*)"graybody: Visible / Infrared separation set at",10000./IR_VI_wnlimit,"um" 
    288297          
    289298         nVI_limit=0 
     
    304313      if (graybody) then 
    305314!        constant absorption coefficient in visible 
    306          write(*,*)"graybody: constant absorption coefficient in visible:" 
     315         if (is_master) write(*,*)"graybody: constant absorption coefficient in visible:" 
    307316         kappa_VI=-100000. 
    308317         call getin_p("kappa_VI",kappa_VI) 
    309          write(*,*)" kappa_VI = ",kappa_VI 
     318         if (is_master) write(*,*)" kappa_VI = ",kappa_VI 
    310319         kappa_VI=kappa_VI*1.e4* mugaz * 1.672621e-27    ! conversion from m^2/kg to cm^2/molecule          
    311320       
    312321!        constant absorption coefficient in IR 
    313          write(*,*)"graybody: constant absorption coefficient in InfraRed:" 
     322         if (is_master) write(*,*)"graybody: constant absorption coefficient in InfraRed:" 
    314323         kappa_IR=-100000. 
    315324         call getin_p("kappa_IR",kappa_IR) 
    316          write(*,*)" kappa_IR = ",kappa_IR        
     325         if (is_master) write(*,*)" kappa_IR = ",kappa_IR         
    317326         kappa_IR=kappa_IR*1.e4* mugaz * 1.672621e-27    ! conversion from m^2/kg to cm^2/molecule  
    318327 
    319          write(*,*)"graybody: Visible / Infrared separation set at band: IR=",nIR_limit,", VI=",nVI_limit 
     328         if (is_master) write(*,*)"graybody: Visible / Infrared separation set at band: IR=",nIR_limit,", VI=",nVI_limit 
    320329                
    321330      Else 
     
    330339         if ((corrkdir(1:4).eq.'null'))then   !(TRIM(corrkdir).eq.'null_LowTeffStar')) then 
    331340            gasv8(1:L_NTREF,1:L_NPREF,1:L_REFVAR,1:L_NSPECTV,1:L_NGAUSS)=0.0 
    332             print*,'using no corrk data' 
    333             print*,'Visible corrk gaseous absorption is set to zero if graybody=F' 
     341            if (is_master) print*,'using no corrk data' 
     342            if (is_master) print*,'Visible corrk gaseous absorption is set to zero if graybody=F' 
    334343         else 
    335344            file_id='/corrk_data/'//trim(adjustl(banddir))//'/corrk_gcm_VI.dat'  
     
    363372         end if 
    364373      else 
    365          print*,'Visible corrk gaseous absorption is set to zero.' 
     374         if (is_master) print*,'Visible corrk gaseous absorption is set to zero.' 
    366375         gasv8(1:L_NTREF,1:L_NPREF,1:L_REFVAR,1:L_NSPECTV,1:L_NGAUSS)=0.0 
    367376      endif 
     
    371380      ! INFRA-RED 
    372381      if ((corrkdir(1:4).eq.'null'))then       !.or.(TRIM(corrkdir).eq.'null_LowTeffStar')) then 
    373          print*,'Infrared corrk gaseous absorption is set to zero if graybody=F' 
     382         if (is_master) print*,'Infrared corrk gaseous absorption is set to zero if graybody=F' 
    374383!$OMP MASTER          
    375384         gasi8(1:L_NTREF,1:L_NPREF,1:L_REFVAR,1:L_NSPECTI,1:L_NGAUSS)=0.0 
     
    662671      endif 
    663672 
     673      if (is_master) then 
    664674      print*,'----------------------------------------------------' 
    665675      print*,'And that`s all we have. It`s possible that other' 
     
    667677      print*,'don`t yet have data for it...' 
    668678      print*,'' 
     679      end if 
    669680 
    670681!     Deallocate local arrays 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/surfini.F

    r227 r298  
    55      use comgeomfi_h, only: lati 
    66      use planetwide_mod, only: planetwide_maxval, planetwide_minval 
     7      use mod_phys_lmdz_para, only : is_master 
    78 
    89      IMPLICIT NONE 
     
    3637      call planetwide_minval(albedodat,min_albedo) 
    3738      call planetwide_maxval(albedodat,max_albedo) 
     39      if (is_master) then 
    3840      write(*,*) 'surfini: minimum corrected albedo',min_albedo 
    3941      write(*,*) 'surfini: maximum corrected albedo',max_albedo 
     42      end if 
    4043 
    4144      if (igcm_co2_ice.ne.0) then 
     
    5255        ENDDO ! of DO ig=1,ngrid      
    5356      else 
     57        if (is_master) then 
    5458        write(*,*) "surfini: No CO2 ice tracer on surface  ..." 
    5559        write(*,*) "         and therefore no albedo change." 
     60        end if 
    5661      endif 
    5762 
    5863      call planetwide_minval(psolaralb,min_albedo) 
    5964      call planetwide_maxval(psolaralb,max_albedo) 
     65      if (is_master) then 
    6066      write(*,*) 'surfini: minimum corrected albedo',min_albedo 
    6167      write(*,*) 'surfini: maximum corrected albedo',max_albedo 
     68      end if 
    6269 
    6370      END 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/tabfi.F

    r273 r298  
    5353      use planete_mod, only: year_day, periastr, apoastr, peri_day, 
    5454     &                       obliquit, z0, lmixmin, emin_turb 
     55      use mod_phys_lmdz_para, only : is_master 
    5556 
    5657      implicit none 
     
    8283      LOGICAL :: found 
    8384       
    84       write(*,*)"tabfi: nid=",nid," tab0=",tab0," Lmodif=",Lmodif 
     85      if (is_master) write(*,*)"tabfi: nid=",nid," tab0=",tab0, 
     86     &          " Lmodif=",Lmodif 
    8587 
    8688      IF (nid.eq.0) then 
     
    9092        ! Ehouarn: Default Saturn values: 
    9193        tab_cntrl(:)=0 
    92         write(*,*) "Using default Saturn values..." 
     94        if (is_master) write(*,*) "Using default Saturn values..." 
    9395        ! these should be read in a def file I guess... 
    9496        lmax=0 ! not used anyways 
     
    164166         call abort 
    165167       else 
    166          write(*,*)'tabfi: tab_cntrl',tab_cntrl 
     168         if (is_master) write(*,*)'tabfi: tab_cntrl',tab_cntrl 
    167169       endif 
    168170c 
     
    227229   5  FORMAT(a20,f12.2,f12.2) 
    228230  
     231      if (is_master) then 
    229232      write(*,*) '*****************************************************' 
    230233      write(*,*) 'Reading tab_cntrl when calling tabfi before changes' 
     
    265268      write(*,*) 
    266269      write(*,*) 'Lmodif in tabfi!!!!!!!',Lmodif 
     270      end if !of if (is_master) 
    267271 
    268272c----------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.