New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 531 – NEMO

Changeset 531


Ignore:
Timestamp:
2006-10-19T14:55:25+02:00 (18 years ago)
Author:
opalod
Message:

nemo_v1_update_75 : CT : enables bit comparison between single and multiple processor runs adding nbit_cmp namelist parameter

Location:
trunk
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • trunk/CONFIG/GYRE/EXP00/namelist

    r523 r531  
    5555!  nbench     Bench parameter (0/1): CAUTION it must be zero except for bench 
    5656!             for which we don't care about physical meaning of the results 
     57!  nbit_cmp   bit comparison mode parameter (0/1): enables bit comparison between  
     58!             single and multiple processor runs. 
    5759&namctl 
    5860   ln_ctl =  .false. 
     
    6567   jsplt  =       1 
    6668   nbench =       0 
     69   nbit_cmp =     0 
    6770/ 
    6871!----------------------------------------------------------------------- 
  • trunk/CONFIG/ORCA2_LIM/EXP00/namelist

    r517 r531  
    5555!  nbench     Bench parameter (0/1): CAUTION it must be zero except for bench 
    5656!             for which we don't care about physical meaning of the results 
     57!  nbit_cmp   bit comparison mode parameter (0/1): enables bit comparison between  
     58!             single and multiple processor runs. 
    5759&namctl 
    5860   ln_ctl =  .false. 
     
    6567   jsplt  =       1 
    6668   nbench =       0 
     69   nbit_cmp =     0 
    6770/ 
    6871!----------------------------------------------------------------------- 
  • trunk/NEMO/LIM_SRC/limdyn.F90

    r508 r531  
    9191         ! --------------------------------------------------- 
    9292          
    93          IF( lk_mpp ) THEN                    ! mpp: compute over the whole domain 
     93         IF( lk_mpp .OR. nbit_cmp == 1 ) THEN                    ! mpp: compute over the whole domain 
    9494            i_j1 = 1    
    9595            i_jpj = jpj 
  • trunk/NEMO/OPA_SRC/DOM/domain.F90

    r516 r531  
    177177 
    178178      ndastp = ndate0                ! Assign initial date to current date 
    179  
    180 ! ... Control the sub-domain area indices for the print control 
    181       IF(ln_ctl)   THEN 
    182          IF( lk_mpp ) THEN 
    183             ! the domain is forced to the real splitted domain in MPI 
    184             isplt = jpni ; jsplt = jpnj ; ijsplt = jpni*jpnj 
    185          ELSE 
    186             IF( isplt == 1 .AND. jsplt == 1  ) THEN 
    187                IF(lwp) WRITE(numout,cform_war) 
    188                IF(lwp) WRITE(numout,*)'          - isplt & jsplt are equal to 1' 
    189                IF(lwp) WRITE(numout,*)'          - the print control will be done over the whole domain' 
    190                IF(lwp) WRITE(numout,*) 
    191             ENDIF 
    192  
    193             ! compute the total number of processors ijsplt 
    194             ijsplt = isplt*jsplt 
    195          ENDIF 
    196  
    197          IF(lwp) WRITE(numout,*)'          - The total number of processors over which the' 
    198          IF(lwp) WRITE(numout,*)'            print control will be done is ijsplt : ', ijsplt 
    199  
    200          ! Control the indices used for the SUM control 
    201          IF( nictls+nictle+njctls+njctle == 0 )   THEN 
    202             ! the print control is done over the default area 
    203             lsp_area = .FALSE. 
    204          ELSE 
    205             ! the print control is done over a specific  area 
    206             lsp_area = .TRUE. 
    207             IF( nictls < 1 .OR. nictls > jpiglo )   THEN 
    208                IF(lwp) WRITE(numout,cform_war) 
    209                IF(lwp) WRITE(numout,*)'          - nictls must be 1<=nictls>=jpiglo, it is forced to 1' 
    210                IF(lwp) WRITE(numout,*) 
    211                nwarn = nwarn + 1 
    212                nictls = 1 
    213             ENDIF 
    214  
    215             IF( nictle < 1 .OR. nictle > jpiglo )   THEN 
    216                IF(lwp) WRITE(numout,cform_war) 
    217                IF(lwp) WRITE(numout,*)'          - nictle must be 1<=nictle>=jpiglo, it is forced to jpiglo' 
    218                IF(lwp) WRITE(numout,*) 
    219                nwarn = nwarn + 1 
    220                nictle = jpjglo 
    221             ENDIF 
    222  
    223             IF( njctls < 1 .OR. njctls > jpjglo )   THEN 
    224                IF(lwp) WRITE(numout,cform_war) 
    225                IF(lwp) WRITE(numout,*)'          - njctls must be 1<=njctls>=jpjglo, it is forced to 1' 
    226                IF(lwp) WRITE(numout,*) 
    227                nwarn = nwarn + 1 
    228                njctls = 1 
    229             ENDIF 
    230  
    231             IF( njctle < 1 .OR. njctle > jpjglo )   THEN 
    232                IF(lwp) WRITE(numout,cform_war) 
    233                IF(lwp) WRITE(numout,*)'          - njctle must be 1<=njctle>= jpjglo, it is forced to jpjglo' 
    234                IF(lwp) WRITE(numout,*) 
    235                nwarn = nwarn + 1 
    236                njctle = jpjglo 
    237             ENDIF 
    238  
    239          ENDIF          ! IF( nictls+nictle+njctls+njctle == 0 ) 
    240        ENDIF            ! IF(ln_ctl) 
    241179 
    242180! ... Control of output frequency 
     
    342280      ENDIF 
    343281 
     282      IF( nbit_cmp == 1 .AND. n_cla /= 0 ) THEN 
     283         CALL ctl_stop( ' Reproductibility tests (nbit_cmp=1) require n_cla = 0' ) 
     284      END IF 
     285 
    344286   END SUBROUTINE dom_nam 
    345287 
  • trunk/NEMO/OPA_SRC/SBC/flxfwb.F90

    r474 r531  
    280280         IF(lwp) WRITE(numout,*) '               ln_fwb = .FALSE. is recommanded' 
    281281      ENDIF 
     282 
     283      IF( nbit_cmp == 1 .AND. ln_fwb ) THEN 
     284         CALL ctl_stop( ' Reproductibility tests (nbit_cmp=1) require ln_fwb = .false.' ) 
     285      END IF 
    282286 
    283287      !                                        ! ============================== 
  • trunk/NEMO/OPA_SRC/SBC/ocesbc.F90

    r473 r531  
    673673             END DO 
    674674          END DO 
    675            
    676           ! compute the emp flux such as its integration on the whole domain and at each time be zero 
    677           zsumemp = 0.e0 
    678           zsurf = 0.e0 
    679           DO jj = 1, jpj 
    680              DO ji = 1, jpi 
    681                 zsumemp = zsumemp + emp(ji,jj) * tmask(ji,jj,1) * tmask_i(ji,jj) 
    682                 zsurf =  zsurf + tmask(ji,jj,1) * tmask_i(ji,jj) 
     675 
     676          ! Compute the emp flux such as its integration on the whole domain at each time is zero 
     677          IF( nbench /= 1 .AND. nbit_cmp /= 1 ) THEN 
     678             zsumemp = 0.e0   ;   zsurf = 0.e0 
     679             DO jj = 1, jpj 
     680                DO ji = 1, jpi 
     681                   zsumemp = zsumemp + emp(ji,jj) * tmask(ji,jj,1) * tmask_i(ji,jj) 
     682                   zsurf =  zsurf + tmask(ji,jj,1) * tmask_i(ji,jj) 
     683                END DO 
    683684             END DO 
    684           END DO 
    685  
    686           IF( lk_mpp )   CALL mpp_sum( zsumemp  )       ! sum over the global domain 
    687           IF( lk_mpp )   CALL mpp_sum( zsurf    )       ! sum over the global domain 
    688  
    689           IF( nbench /= 0 ) THEN 
    690              ! Benchmark GYRE configuration (to allow the bit to bit comparison between Mpp/Mono case) 
    691              zsumemp = 0.e0 
    692           ELSE 
     685 
     686             IF( lk_mpp )   CALL mpp_sum( zsumemp  )       ! sum over the global domain 
     687             IF( lk_mpp )   CALL mpp_sum( zsurf    )       ! sum over the global domain 
     688 
    693689             ! Default GYRE configuration 
    694690             zsumemp = zsumemp / zsurf 
     691          ELSE 
     692             ! Benchmark GYRE configuration (to allow the bit to bit comparison between Mpp/Mono case) 
     693             zsumemp = 0.e0   ;    zsurf = 0.e0 
    695694          ENDIF 
    696695 
     
    857856      aplus  = 0.e0 
    858857      aminus = 0.e0 
    859       DO jj = 1, jpj 
    860          DO ji = 1, jpi 
    861             zwei   = e1t(ji,jj) * e2t(ji,jj) * tmask_i(ji,jj) 
    862             aplus  = aplus  + zerpplus (ji,jj) * zwei 
    863             aminus = aminus - zerpminus(ji,jj) * zwei 
     858       
     859      IF( nbit_cmp == 1) THEN 
     860          
     861         IF(ln_ctl)   THEN 
     862            WRITE(charout,FMT="('oce_sbc_dmp : a+ = ',D23.16, ' a- = ',D23.16)") aplus, aminus 
     863            CALL prt_ctl_info(charout) 
     864         ENDIF 
     865         erp(:,:) = 0.e0 
     866 
     867      ELSE 
     868 
     869         DO jj = 1, jpj 
     870            DO ji = 1, jpi 
     871               zwei   = e1t(ji,jj) * e2t(ji,jj) * tmask_i(ji,jj) 
     872               aplus  = aplus  + zerpplus (ji,jj) * zwei 
     873               aminus = aminus - zerpminus(ji,jj) * zwei 
     874            END DO 
    864875         END DO 
    865       END DO 
    866       IF( lk_mpp )   CALL mpp_sum( aplus  )   ! sums over the global domain 
    867       IF( lk_mpp )   CALL mpp_sum( aminus ) 
    868  
    869       IF(ln_ctl)   THEN 
    870          WRITE(charout,FMT="('oce_sbc_dmp : a+ = ',D23.16, ' a- = ',D23.16)") aplus, aminus 
    871          CALL prt_ctl_info(charout) 
    872       ENDIF 
    873  
    874       zadefi = MIN( aplus, aminus ) 
    875       IF( zadefi == 0.e0 ) THEN  
    876          erp(:,:) = 0.e0 
    877       ELSE 
    878          erp(:,:) = zadefi * ( zerpplus(:,:) / aplus + zerpminus(:,:) / aminus ) 
    879       ENDIF 
     876         IF( lk_mpp )   CALL mpp_sum( aplus  )   ! sums over the global domain 
     877         IF( lk_mpp )   CALL mpp_sum( aminus ) 
     878 
     879         IF(ln_ctl)   THEN 
     880            WRITE(charout,FMT="('oce_sbc_dmp : a+ = ',D23.16, ' a- = ',D23.16)") aplus, aminus 
     881            CALL prt_ctl_info(charout) 
     882         ENDIF 
     883 
     884         zadefi = MIN( aplus, aminus ) 
     885         IF( zadefi == 0.e0 ) THEN  
     886            erp(:,:) = 0.e0 
     887         ELSE 
     888            erp(:,:) = zadefi * ( zerpplus(:,:) / aplus + zerpminus(:,:) / aminus ) 
     889         ENDIF 
     890 
     891      END IF 
    880892#else 
    881893      ! Rigid-lid (emp=emps=E-P-R+Erp) 
  • trunk/NEMO/OPA_SRC/SOL/solver.F90

    r474 r531  
    108108#endif 
    109109 
    110  
    111110      ! 0. Parameter control and print 
    112111      !    --------------------------- 
     
    187186      END SELECT 
    188187 
     188      IF( nbit_cmp == 1 .AND. nsolv /= 2 ) THEN 
     189         CALL ctl_stop( ' Reproductibility tests (nbit_cmp=1) require the SOR solver: nsolv = 2' ) 
     190      END IF 
     191 
    189192      ! Grid-point at which the solver is applied 
    190193      ! ----------------------------------------- 
  • trunk/NEMO/OPA_SRC/in_out_manager.F90

    r508 r531  
    2323   !!---------------------------------------------------------------------- 
    2424   CHARACTER (len=16) ::   cexper    = "exp0"        !: experiment name used for output filename 
    25    LOGICAL            ::   ln_rstart = .FALSE. ,  &  !: start from (F) rest or (T) a restart file 
    26       &                    ln_ctl    = .FALSE.       !: run control for debugging 
     25   LOGICAL            ::   ln_rstart = .FALSE.       !: start from (F) rest or (T) a restart file 
    2726   INTEGER            ::   no     = 0        ,    &  !: job number 
    2827      &                    nrstdt = 0        ,    &  !: control of the time step (0, 1 or 2) 
     
    3231      &                    nleapy = 0        ,    &  !: Leap year calendar flag (0/1 or 30) 
    3332      &                    ninist = 0        ,    &  !: initial state output flag (0/1) 
    34       &                    nbench = 0                !: benchmark parameter (0/1) 
     33      &                    nstock = 10       ,    &  !: restart file frequency 
     34      &                    nwrite = 10               !: outputs file frequency 
    3535    
    3636   !!---------------------------------------------------------------------- 
    3737   !!                    output monitoring 
    3838   !!---------------------------------------------------------------------- 
    39    INTEGER ::   nstock =   10 ,        &  !: restart file frequency 
    40       &         nprint =    0 ,        &  !: level of print (0 no print) 
    41       &         nwrite =   10 ,        &  !: restart file frequency 
     39   LOGICAL ::   ln_ctl = .FALSE.          !: run control for debugging 
     40   INTEGER ::   nprint =    0 ,        &  !: level of print (0 no print) 
    4241      &         nictls =    0 ,        &  !: Start i indice for the SUM control 
    4342      &         nictle =    0 ,        &  !: End   i indice for the SUM control 
     
    4645      &         isplt  =    1 ,        &  !: number of processors following i 
    4746      &         jsplt  =    1 ,        &  !: number of processors following j 
    48       &         ijsplt =    1             !: nb of local domain = nb of processors 
     47      &         ijsplt =    1 ,        &  !: nb of local domain = nb of processors 
     48      &         nbench =    0 ,        &  !: benchmark parameter (0/1) 
     49      &         nbit_cmp =  0             !: bit comparison mode parameter (0/1) 
    4950 
    5051   !!---------------------------------------------------------------------- 
  • trunk/NEMO/OPA_SRC/opa.F90

    r516 r531  
    166166      CHARACTER (len=20) ::   namelistname 
    167167      CHARACTER (len=28) ::   file_out 
    168       NAMELIST/namctl/  ln_ctl, nprint, nictls, nictle,   & 
    169          &              isplt , jsplt , njctls, njctle, nbench 
     168      NAMELIST/namctl/ ln_ctl, nprint, nictls, nictle,   & 
     169         &             isplt , jsplt , njctls, njctle, nbench, nbit_cmp 
    170170      !!---------------------------------------------------------------------- 
    171171 
     
    229229      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA 
    230230 
     231      CALL opa_flg                          ! Control prints & Benchmark 
     232 
     233                                            ! Domain decomposition 
     234      IF( jpni*jpnj == jpnij ) THEN 
     235         CALL mpp_init                          ! standard cutting out 
     236      ELSE 
     237         CALL mpp_init2                         ! eliminate land processors 
     238      ENDIF 
     239       
     240      CALL phy_cst                          ! Physical constants 
     241 
     242      CALL dom_cfg                          ! Domain configuration 
     243       
     244      CALL dom_init                         ! Domain 
     245 
     246      IF( ln_ctl )      CALL prt_ctl_init   ! Print control 
     247 
     248      IF( lk_cfg_1d )   CALL fcorio_1d      ! redefine Coriolis at T-point 
     249 
     250      IF( lk_obc    )   CALL obc_init       ! Open boundaries  
     251 
     252      CALL day( nit000 )                    ! Calendar 
     253 
     254      CALL istate_init                      ! ocean initial state (Dynamics and tracers) 
     255 
     256!!add 
     257                       CALL eos( tb, sb, rhd, rhop )        ! before potential and in situ densities 
     258 
     259                       CALL bn2( tb, sb, rn2 )              ! before Brunt-Vaisala frequency 
     260 
     261      IF( ln_zps .AND. .NOT. lk_cfg_1d )   & 
     262         &             CALL zps_hde( nit000, tb, sb, rhd,  &  ! Partial steps: before Horizontal DErivative 
     263                                            gtu, gsu, gru, &  ! of t, s, rd at the bottom ocean level 
     264                                            gtv, gsv, grv ) 
     265!!add 
     266 
     267      CALL oc_fz_pt                         ! Surface freezing point 
     268 
     269#if defined key_ice_lim 
     270      CALL ice_init                         ! Sea ice model 
     271#endif 
     272 
     273      !                                     ! Ocean physics 
     274 
     275      CALL ldf_dyn_init                         ! Lateral ocean momentum physics 
     276 
     277      CALL ldf_tra_init                         ! Lateral ocean tracer physics 
     278 
     279      CALL zdf_init                             ! Vertical ocean physics 
     280 
     281      CALL trd_mod_init                         ! Mixed-layer/Vorticity/Integral constraints trends 
     282 
     283 
     284#if defined key_passivetrc 
     285      CALL ini_trc                           ! Passive tracers 
     286#endif 
     287 
     288#if defined key_coupled 
     289      itro  = nitend - nit000 + 1           ! Coupled 
     290      istp0 = NINT( rdt ) 
     291      CALL cpl_init( itro, nexco, istp0 )   ! Signal processing and process id exchange 
     292#endif 
     293 
     294      CALL flx_init                         ! Thermohaline forcing initialization 
     295 
     296      CALL flx_fwb_init                     ! FreshWater Budget correction 
     297 
     298      CALL dia_ptr_init                     ! Poleward TRansports initialization 
     299 
     300      !                                     ! =============== ! 
     301      !                                     !  time stepping  ! 
     302      !                                     ! =============== ! 
     303 
     304      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA 
     305 
     306      IF( lk_cfg_1d  )  THEN  
     307         CALL init_1d 
     308      ENDIF 
     309 
     310   END SUBROUTINE opa_init 
     311 
     312 
     313   SUBROUTINE opa_flg 
     314      !!---------------------------------------------------------------------- 
     315      !!                     ***  ROUTINE opa  *** 
     316      !! 
     317      !! ** Purpose :   Initialize logical flags that control the choice of 
     318      !!      some algorithm or control print 
     319      !! 
     320      !! ** Method  :    Read in namilist namflg logical flags 
     321      !! 
     322      !! History : 
     323      !!   9.0  !  03-11  (G. Madec)  Original code 
     324      !!---------------------------------------------------------------------- 
     325      !! * Local declarations 
     326 
     327      NAMELIST/namflg/ ln_dynhpg_imp 
     328      !!---------------------------------------------------------------------- 
     329 
     330      ! Parameter control and print 
     331      ! --------------------------- 
    231332      IF(lwp) THEN 
    232333         WRITE(numout,*) 
    233          WRITE(numout,*) 'opa_init: Control prints & Benchmark' 
    234          WRITE(numout,*) '~~~~~~~~ ' 
     334         WRITE(numout,*) 'opa_flg: Control prints & Benchmark' 
     335         WRITE(numout,*) '~~~~~~~ ' 
    235336         WRITE(numout,*) '          Namelist namctl' 
    236337         WRITE(numout,*) '             run control (for debugging)     ln_ctl    = ', ln_ctl 
     
    243344         WRITE(numout,*) '             number of proc. following j     jsplt     = ', jsplt 
    244345         WRITE(numout,*) '             benchmark parameter (0/1)       nbench    = ', nbench 
    245       ENDIF 
    246                                             ! Domain decomposition 
    247       IF( jpni*jpnj == jpnij ) THEN 
    248          CALL mpp_init                          ! standard cutting out 
    249       ELSE 
    250          CALL mpp_init2                         ! eliminate land processors 
    251       ENDIF 
    252        
    253       CALL phy_cst                          ! Physical constants 
    254  
    255       CALL dom_cfg                          ! Domain configuration 
    256        
    257       CALL dom_init                         ! Domain 
    258  
    259       IF( ln_ctl )      CALL prt_ctl_init   ! Print control 
    260  
    261       IF( lk_cfg_1d )   CALL fcorio_1d      ! redefine Coriolis at T-point 
    262  
    263       IF( lk_obc    )   CALL obc_init       ! Open boundaries  
    264  
    265       CALL day( nit000 )                    ! Calendar 
    266  
    267       CALL istate_init                      ! ocean initial state (Dynamics and tracers) 
    268  
    269 !!add 
    270                        CALL eos( tb, sb, rhd, rhop )        ! before potential and in situ densities 
    271  
    272                        CALL bn2( tb, sb, rn2 )              ! before Brunt-Vaisala frequency 
    273  
    274       IF( ln_zps .AND. .NOT. lk_cfg_1d )   & 
    275          &             CALL zps_hde( nit000, tb, sb, rhd,  &  ! Partial steps: before Horizontal DErivative 
    276                                             gtu, gsu, gru, &  ! of t, s, rd at the bottom ocean level 
    277                                             gtv, gsv, grv ) 
    278 !!add 
    279  
    280       CALL oc_fz_pt                         ! Surface freezing point 
    281  
    282 #if defined key_ice_lim 
    283       CALL ice_init                         ! Sea ice model 
    284 #endif 
    285  
    286       !                                     ! Ocean scheme 
    287  
    288       CALL opa_flg                              ! Choice of algorithms 
    289  
    290       !                                     ! Ocean physics 
    291  
    292       CALL ldf_dyn_init                         ! Lateral ocean momentum physics 
    293  
    294       CALL ldf_tra_init                         ! Lateral ocean tracer physics 
    295  
    296       CALL zdf_init                             ! Vertical ocean physics 
    297  
    298       CALL trd_mod_init                         ! Mixed-layer/Vorticity/Integral constraints trends 
    299  
    300  
    301 #if defined key_passivetrc 
    302       CALL ini_trc                           ! Passive tracers 
    303 #endif 
    304  
    305 #if defined key_coupled 
    306       itro  = nitend - nit000 + 1           ! Coupled 
    307       istp0 = NINT( rdt ) 
    308       CALL cpl_init( itro, nexco, istp0 )   ! Signal processing and process id exchange 
    309 #endif 
    310  
    311       CALL flx_init                         ! Thermohaline forcing initialization 
    312  
    313       CALL flx_fwb_init                     ! FreshWater Budget correction 
    314  
    315       CALL dia_ptr_init                     ! Poleward TRansports initialization 
    316  
    317       !                                     ! =============== ! 
    318       !                                     !  time stepping  ! 
    319       !                                     ! =============== ! 
    320  
    321       IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA 
    322  
    323       IF( lk_cfg_1d  )  THEN  
    324          CALL init_1d 
    325       ENDIF 
    326  
    327    END SUBROUTINE opa_init 
    328  
    329  
    330    SUBROUTINE opa_flg 
    331       !!---------------------------------------------------------------------- 
    332       !!                     ***  ROUTINE opa  *** 
    333       !! 
    334       !! ** Purpose :   Initialize logical flags that control the choice of 
    335       !!      some algorithm or control print 
    336       !! 
    337       !! ** Method  :    Read in namilist namflg logical flags 
    338       !! 
    339       !! History : 
    340       !!   9.0  !  03-11  (G. Madec)  Original code 
    341       !!---------------------------------------------------------------------- 
    342       !! * Local declarations 
    343  
    344       NAMELIST/namflg/ ln_dynhpg_imp 
    345       !!---------------------------------------------------------------------- 
     346         WRITE(numout,*) '             bit comparison mode (0/1)       nbit_cmp  = ', nbit_cmp 
     347      ENDIF 
     348 
     349      ! ... Control the sub-domain area indices for the control prints 
     350      IF( ln_ctl )   THEN 
     351         IF( lk_mpp )   THEN 
     352            ! the domain is forced to the real splitted domain in MPI 
     353            isplt = jpni ; jsplt = jpnj ; ijsplt = jpni*jpnj 
     354         ELSE 
     355            IF( isplt == 1 .AND. jsplt == 1  ) THEN 
     356               CALL ctl_warn( '          - isplt & jsplt are equal to 1',   & 
     357                    &         '          - the print control will be done over the whole domain' ) 
     358            ENDIF 
     359 
     360            ! compute the total number of processors ijsplt 
     361            ijsplt = isplt*jsplt 
     362         ENDIF 
     363 
     364         IF(lwp) WRITE(numout,*)'          - The total number of processors over which the' 
     365         IF(lwp) WRITE(numout,*)'            print control will be done is ijsplt : ', ijsplt 
     366 
     367         ! Control the indices used for the SUM control 
     368         IF( nictls+nictle+njctls+njctle == 0 )   THEN 
     369            ! the print control is done over the default area 
     370            lsp_area = .FALSE. 
     371         ELSE 
     372            ! the print control is done over a specific  area 
     373            lsp_area = .TRUE. 
     374            IF( nictls < 1 .OR. nictls > jpiglo )   THEN 
     375               CALL ctl_warn( '          - nictls must be 1<=nictls>=jpiglo, it is forced to 1' ) 
     376               nictls = 1 
     377            ENDIF 
     378 
     379            IF( nictle < 1 .OR. nictle > jpiglo )   THEN 
     380               CALL ctl_warn( '          - nictle must be 1<=nictle>=jpiglo, it is forced to jpiglo' ) 
     381               nictle = jpiglo 
     382            ENDIF 
     383 
     384            IF( njctls < 1 .OR. njctls > jpjglo )   THEN 
     385               CALL ctl_warn( '          - njctls must be 1<=njctls>=jpjglo, it is forced to 1' ) 
     386               njctls = 1 
     387            ENDIF 
     388 
     389            IF( njctle < 1 .OR. njctle > jpjglo )   THEN 
     390               CALL ctl_warn( '          - njctle must be 1<=njctle>=jpjglo, it is forced to jpjglo' ) 
     391               njctle = jpjglo 
     392            ENDIF 
     393 
     394         ENDIF          ! IF( nictls+nictle+njctls+njctle == 0 ) 
     395       ENDIF            ! IF(ln_ctl) 
     396 
     397      IF( nbench == 1 )   THEN 
     398         SELECT CASE ( cp_cfg ) 
     399         CASE ( 'gyre' ) 
     400            CALL ctl_warn( ' The Benchmark is activated ' ) 
     401         CASE DEFAULT 
     402            CALL ctl_stop( ' The Benchmark is based on the GYRE configuration: key_gyre must be used or set nbench = 0' ) 
     403         END SELECT 
     404      ENDIF 
     405 
     406      SELECT CASE ( nbit_cmp ) 
     407      CASE ( 1 ) 
     408         CALL ctl_warn( ' Bit comparison enabled Single and multiple processor results should bit compare', & 
     409              &         ' WARNING: RESULTS ARE NOT PHYSICAL.' ) 
     410      CASE DEFAULT 
     411         CALL ctl_warn( ' Bit comparison not enabled. Single and multiple processor results will differ.' ) 
     412      END SELECT 
     413 
    346414 
    347415      ! Read Namelist namflg : algorithm FLaG 
     
    352420      ! Parameter control and print 
    353421      ! --------------------------- 
    354       ! Control print 
    355422      IF(lwp) THEN 
    356423         WRITE(numout,*) 
    357          WRITE(numout,*) 'opa_flg : algorithm flag initialization' 
     424         WRITE(numout,*) 'opa_flg : Hydrostatic pressure gradient algorithm' 
    358425         WRITE(numout,*) '~~~~~~~' 
    359426         WRITE(numout,*) '          Namelist namflg : set algorithm flags' 
    360          WRITE(numout,*) 
    361427         WRITE(numout,*) '             centered (F) or semi-implicit (T)   ln_dynhpg_imp = ', ln_dynhpg_imp 
    362428         WRITE(numout,*) '             hydrostatic pressure gradient' 
Note: See TracChangeset for help on using the changeset viewer.