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

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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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  
Note: See TracChangeset for help on using the changeset viewer.