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 13124 for NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo – NEMO

Ignore:
Timestamp:
2020-06-17T16:46:58+02:00 (4 years ago)
Author:
smasson
Message:

Extra_Halo: merge with trunk@13115, see #2366

Location:
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo
Files:
23 edited
1 copied

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/cfgs/SHARED/field_def_nemo-oce.xml

    r12377 r13124  
    369369          <field id="taum_oce"     long_name="wind stress module over open ocean"           standard_name="magnitude_of_surface_downward_stress"               unit="N/m2"  /> 
    370370 
     371          <field id="Cd_oce"      long_name="Drag coefficient over open ocean"              standard_name="drag_coefficient_water"                 unit=""  /> 
     372          <field id="Ce_oce"      long_name="Evaporaion coefficient over open ocean"        standard_name="evap_coefficient_water"                 unit=""  /> 
     373          <field id="Ch_oce"      long_name="Sensible heat coefficient over open ocean"     standard_name="sensible_heat_coefficient_water"        unit=""  />           
     374 
     375          <field id="Cd_ice"      long_name="Drag coefficient over ice"                     standard_name="drag_coefficient_ice"                 unit=""  /> 
     376          <field id="Ce_ice"      long_name="Evaporaion coefficient over ice"               standard_name="evap_coefficient_ice"                 unit=""  /> 
     377          <field id="Ch_ice"      long_name="Sensible heat coefficient over ice"            standard_name="sensible_heat_coefficient_ice"        unit=""  />           
     378 
    371379          <!-- available key_oasis3 --> 
    372380          <field id="snow_ao_cea"  long_name="Snow over ice-free ocean (cell average)"   standard_name="snowfall_flux"                             unit="kg/m2/s"  /> 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/DIA/diaar5.F90

    r12939 r13124  
    7777      REAL(wp), ALLOCATABLE, DIMENSION(:,:)     :: zarea_ssh , zbotpres       ! 2D workspace  
    7878      REAL(wp), ALLOCATABLE, DIMENSION(:,:)     :: zpe, z2d                   ! 2D workspace  
    79       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   :: zrhd , zrhop, ztpot   ! 3D workspace 
     79      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   :: zrhd , ztpot               ! 3D workspace 
    8080      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) :: ztsn                       ! 4D workspace 
    8181 
     
    8787      IF( l_ar5 ) THEN  
    8888         ALLOCATE( zarea_ssh(jpi,jpj), zbotpres(jpi,jpj), z2d(jpi,jpj) ) 
    89          ALLOCATE( zrhd(jpi,jpj,jpk) , zrhop(jpi,jpj,jpk) ) 
     89         ALLOCATE( zrhd(jpi,jpj,jpk) ) 
    9090         ALLOCATE( ztsn(jpi,jpj,jpk,jpts) ) 
    9191         zarea_ssh(:,:) = e1e2t(:,:) * ssh(:,:,Kmm) 
     
    155155       
    156156         !                                         ! steric sea surface height 
    157          CALL eos( ts(:,:,:,:,Kmm), zrhd, zrhop, gdept(:,:,:,Kmm) )                 ! now in situ and potential density 
    158          zrhop(:,:,jpk) = 0._wp 
    159          CALL iom_put( 'rhop', zrhop ) 
    160          ! 
    161157         zbotpres(:,:) = 0._wp                        ! no atmospheric surface pressure, levitating sea-ice 
    162158         DO jk = 1, jpkm1 
    163             zbotpres(:,:) = zbotpres(:,:) + e3t(:,:,jk,Kmm) * zrhd(:,:,jk) 
     159            zbotpres(:,:) = zbotpres(:,:) + e3t(:,:,jk,Kmm) * rhd(:,:,jk) 
    164160         END DO 
    165161         IF( ln_linssh ) THEN 
     
    168164                  DO jj = 1,jpj 
    169165                     iks = mikt(ji,jj) 
    170                      zbotpres(ji,jj) = zbotpres(ji,jj) + ssh(ji,jj,Kmm) * zrhd(ji,jj,iks) + riceload(ji,jj) 
     166                     zbotpres(ji,jj) = zbotpres(ji,jj) + ssh(ji,jj,Kmm) * rhd(ji,jj,iks) + riceload(ji,jj) 
    171167                  END DO 
    172168               END DO 
    173169            ELSE 
    174                zbotpres(:,:) = zbotpres(:,:) + ssh(:,:,Kmm) * zrhd(:,:,1) 
     170               zbotpres(:,:) = zbotpres(:,:) + ssh(:,:,Kmm) * rhd(:,:,1) 
    175171            END IF 
    176172         END IF 
     
    293289      IF( l_ar5 ) THEN 
    294290        DEALLOCATE( zarea_ssh , zbotpres, z2d ) 
    295         DEALLOCATE( zrhd      , zrhop    ) 
    296291        DEALLOCATE( ztsn                 ) 
    297292      ENDIF 
     
    367362      IF(   iom_use( 'voltot'  ) .OR. iom_use( 'sshtot'    )  .OR. iom_use( 'sshdyn' )  .OR.  &  
    368363         &  iom_use( 'masstot' ) .OR. iom_use( 'temptot'   )  .OR. iom_use( 'saltot' ) .OR.  &     
    369          &  iom_use( 'botpres' ) .OR. iom_use( 'sshthster' )  .OR. iom_use( 'sshsteric' )  ) L_ar5 = .TRUE. 
     364         &  iom_use( 'botpres' ) .OR. iom_use( 'sshthster' )  .OR. iom_use( 'sshsteric' ) .OR. & 
     365         &  iom_use( 'rhop' )  ) L_ar5 = .TRUE. 
    370366   
    371367      IF( l_ar5 ) THEN 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/DIA/diawri.F90

    r12939 r13124  
    171171         CALL iom_put( "sbs", z2d )                ! bottom salinity 
    172172      ENDIF 
     173 
     174      CALL iom_put( "rhop", rhop(:,:,:) )          ! 3D potential density (sigma0) 
    173175 
    174176      IF ( iom_use("taubot") ) THEN                ! bottom stress 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/DOM/istate.F90

    r12489 r13124  
    2424   USE dom_oce        ! ocean space and time domain  
    2525   USE daymod         ! calendar 
    26    USE divhor         ! horizontal divergence            (div_hor routine) 
    2726   USE dtatsd         ! data temperature and salinity   (dta_tsd routine) 
    2827   USE dtauvd         ! data: U & V current             (dta_uvd routine) 
     
    121120         uu   (:,:,:,Kmm)   = uu  (:,:,:,Kbb) 
    122121         vv   (:,:,:,Kmm)   = vv  (:,:,:,Kbb) 
    123          hdiv(:,:,jpk) = 0._wp               ! bottom divergence set one for 0 to zero at jpk level 
    124          CALL div_hor( 0, Kbb, Kmm )         ! compute interior hdiv value   
    125 !!gm                                    hdiv(:,:,:) = 0._wp 
    126122 
    127123!!gm POTENTIAL BUG : 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/ICB/icbrst.F90

    r13015 r13124  
    193193      CHARACTER(len=256)     :: cl_path 
    194194      CHARACTER(len=256)     :: cl_filename 
    195       CHARACTER(len=256)     :: cl_kt 
     195      CHARACTER(len=)     :: cl_kt 
    196196      CHARACTER(LEN=12 )     :: clfmt            ! writing format 
    197197      TYPE(iceberg), POINTER :: this 
     
    214214         ! file name 
    215215         WRITE(cl_kt, '(i8.8)') kt 
    216          cl_filename = TRIM(cexper)//"_"//TRIM(ADJUSTL(cl_kt))//"_"//TRIM(cn_icbrst_out) 
     216         cl_filename = TRIM(cexper)//"_"//cl_kt//"_"//TRIM(cn_icbrst_out) 
    217217         IF( lk_mpp ) THEN 
    218218            idg = MAX( INT(LOG10(REAL(MAX(1,jpnij-1),wp))) + 1, 4 )          ! how many digits to we need to write? min=4, max=9 
    219219            WRITE(clfmt, "('(a,a,i', i1, '.', i1, ',a)')") idg, idg          ! '(a,a,ix.x,a)' 
    220             WRITE(cl_filename,clfmt) TRIM(cl_filename), '_', narea-1, '.nc' 
     220            WRITE(cl_filename,  clfmt) TRIM(cl_filename), '_', narea-1, '.nc' 
    221221         ELSE 
    222             WRITE(cl_filename,'(A,".nc")') TRIM(cl_filename) 
     222            WRITE(cl_filename,'(a,a)') TRIM(cl_filename),               '.nc' 
    223223         ENDIF 
    224224 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/ICB/icbtrj.F90

    r13015 r13124  
    6666      CHARACTER(len=80)      ::   cl_filename 
    6767      CHARACTER(LEN=12)      ::   clfmt            ! writing format 
    68       CHARACTER(LEN=20)      ::   cldate_ini, cldate_end 
     68      CHARACTER(LEN=8 )      ::   cldate_ini, cldate_end 
    6969      TYPE(iceberg), POINTER ::   this 
    7070      TYPE(point)  , POINTER ::   pt 
     
    8282 
    8383      ! define trajectory output name 
    84       cl_filename = 'trajectory_icebergs_'//TRIM(ADJUSTL(cldate_ini))//'-'//TRIM(ADJUSTL(cldate_end)) 
     84      cl_filename = 'trajectory_icebergs_'//cldate_ini//'-'//cldate_end 
    8585      IF ( lk_mpp ) THEN 
    8686         idg = MAX( INT(LOG10(REAL(MAX(1,jpnij-1),wp))) + 1, 4 )          ! how many digits to we need to write? min=4, max=9 
    8787         WRITE(clfmt, "('(a,a,i', i1, '.', i1, ',a)')") idg, idg          ! '(a,a,ix.x,a)' 
    88          WRITE(cl_filename,clfmt) TRIM(cl_filename), '_', narea-1, '.nc' 
     88         WRITE(cl_filename,  clfmt) TRIM(cl_filename), '_', narea-1, '.nc' 
    8989      ELSE 
    90          WRITE(cl_filename,'(A,".nc")') TRIM(cl_filename) 
     90         WRITE(cl_filename,'(a,a)') TRIM(cl_filename),               '.nc' 
    9191      ENDIF 
    9292      IF( lwp .AND. nn_verbose_level >= 0 )   WRITE(numout,'(2a)') 'icebergs, icb_trj_init: creating ',TRIM(cl_filename) 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/IOM/iom_def.F90

    r12939 r13124  
    2828   INTEGER, PARAMETER, PUBLIC ::   jpmax_vars   = 1200 !: maximum number of variables in one file 
    2929   INTEGER, PARAMETER, PUBLIC ::   jpmax_dims   =  4   !: maximum number of dimensions for one variable 
    30    INTEGER, PARAMETER, PUBLIC ::   jpmax_digits =  5   !: maximum number of digits for the cpu number in the file name 
     30   INTEGER, PARAMETER, PUBLIC ::   jpmax_digits =  9   !: maximum number of digits for the cpu number in the file name 
    3131 
    3232!$AGRIF_DO_NOT_TREAT 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/LBC/lib_mpp.F90

    r13015 r13124  
    12211221      CHARACTER(LEN=10) ::   clfmt            ! writing format 
    12221222      INTEGER           ::   iost 
    1223       INTEGER           ::   idg  ! number of digits 
     1223      INTEGER           ::   idg              ! number of digits 
    12241224      !!---------------------------------------------------------------------- 
    12251225      ! 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/SBC/sbcblk.F90

    r12939 r13124  
    628628      END SELECT 
    629629 
     630      CALL iom_put("Cd_oce", zcd_oce) 
     631      CALL iom_put("Ce_oce", zce_oce) 
     632      CALL iom_put("Ch_oce", zch_oce) 
     633       
    630634      IF( ln_skin_cs .OR. ln_skin_wl ) THEN 
    631635         !! ptsk and pssq have been updated!!! 
     
    878882         Ce_ice(:,:) = Ch_ice(:,:)       ! sensible and latent heat transfer coef. are considered identical 
    879883      ENDIF 
    880  
    881       !! IF ( iom_use("Cd_ice") ) CALL iom_put("Cd_ice", Cd_ice)   ! output value of pure ice-atm. transfer coef. 
    882       !! IF ( iom_use("Ch_ice") ) CALL iom_put("Ch_ice", Ch_ice)   ! output value of pure ice-atm. transfer coef. 
    883  
     884       
     885      CALL iom_put("Cd_ice", Cd_ice) 
     886      CALL iom_put("Ce_ice", Ce_ice) 
     887      CALL iom_put("Ch_ice", Ch_ice) 
     888       
    884889      ! local scalars ( place there for vector optimisation purposes) 
    885890      zcd_dui(:,:) = wndm_ice(:,:) * Cd_ice(:,:) 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/SBC/sbccpl.F90

    r12980 r13124  
    17851785            ENDDO 
    17861786         ELSE 
    1787             qns_tot(:,:) = qns_tot(:,:) + picefr(:,:) * frcv(jpr_qnsice)%z3(:,:,1) 
     1787            zqns_tot(:,:) = zqns_tot(:,:) + picefr(:,:) * frcv(jpr_qnsice)%z3(:,:,1) 
    17881788            DO jl = 1, jpl 
    1789                zqns_tot(:,:   ) = zqns_tot(:,:) + picefr(:,:) * frcv(jpr_qnsice)%z3(:,:,1) 
    17901789               zqns_ice(:,:,jl) = frcv(jpr_qnsice)%z3(:,:,1) 
    17911790            END DO 
     
    19281927            END DO 
    19291928         ELSE 
    1930             qsr_tot(:,:   ) = qsr_tot(:,:) + picefr(:,:) * frcv(jpr_qsrice)%z3(:,:,1) 
     1929            zqsr_tot(:,:) = zqsr_tot(:,:) + picefr(:,:) * frcv(jpr_qsrice)%z3(:,:,1) 
    19311930            DO jl = 1, jpl 
    1932                zqsr_tot(:,:   ) = zqsr_tot(:,:) + picefr(:,:) * frcv(jpr_qsrice)%z3(:,:,1) 
    19331931               zqsr_ice(:,:,jl) = frcv(jpr_qsrice)%z3(:,:,1) 
    19341932            END DO 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/TRD/trdtra.F90

    r12489 r13124  
    8282      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in), OPTIONAL ::   ptra    ! now tracer variable 
    8383      ! 
    84       INTEGER ::   jk   ! loop indices 
     84      INTEGER ::   jk    ! loop indices 
     85      INTEGER ::   i01   ! 0 or 1 
    8586      REAL(wp),        DIMENSION(jpi,jpj,jpk) ::   ztrds             ! 3D workspace 
    8687      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   zwt, zws, ztrdt   ! 3D workspace 
     
    9091         IF( trd_tra_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'trd_tra : unable to allocate arrays' ) 
    9192      ENDIF 
    92  
     93      ! 
     94      i01 = COUNT( (/ PRESENT(pu) .OR. ( ktrd /= jptra_xad .AND. ktrd /= jptra_yad .AND. ktrd /= jptra_zad ) /) ) 
     95      ! 
    9396      IF( ctype == 'TRA' .AND. ktra == jp_tem ) THEN   !==  Temperature trend  ==! 
    9497         ! 
    95          SELECT CASE( ktrd ) 
     98         SELECT CASE( ktrd*i01 ) 
    9699         !                            ! advection: transform the advective flux into a trend 
    97100         CASE( jptra_xad )   ;   CALL trd_tra_adv( ptrd, pu, ptra, 'X', trdtx, Kmm )  
     
    112115      IF( ctype == 'TRA' .AND. ktra == jp_sal ) THEN      !==  Salinity trends  ==! 
    113116         ! 
    114          SELECT CASE( ktrd ) 
     117         SELECT CASE( ktrd*i01 ) 
    115118         !                            ! advection: transform the advective flux into a trend 
    116119         !                            !            and send T & S trends to trd_tra_mng 
     
    163166      IF( ctype == 'TRC' ) THEN                           !==  passive tracer trend  ==! 
    164167         ! 
    165          SELECT CASE( ktrd ) 
     168         SELECT CASE( ktrd*i01 ) 
    166169         !                            ! advection: transform the advective flux into a masked trend 
    167170         CASE( jptra_xad )   ;   CALL trd_tra_adv( ptrd , pu , ptra, 'X', ztrds, Kmm )  
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/stpctl.F90

    r13015 r13124  
    130130      zmax(3) = MAXVAL( -ts(:,:,:,jp_sal,Kmm), mask = llmsk )                     ! minus salinity max 
    131131      zmax(4) = MAXVAL(  ts(:,:,:,jp_sal,Kmm), mask = llmsk )                     !       salinity max 
    132       IF( ll_colruns ) THEN     ! following variables are used only in the netcdf file 
     132      IF( ll_colruns .OR. jpnij == 1 ) THEN     ! following variables are used only in the netcdf file 
    133133         zmax(5) = MAXVAL( -ts(:,:,:,jp_tem,Kmm), mask = llmsk )                  ! minus temperature max 
    134134         zmax(6) = MAXVAL(  ts(:,:,:,jp_tem,Kmm), mask = llmsk )                  !       temperature max 
     
    220220         ! 
    221221         IF( ll_colruns .or. jpnij == 1 ) THEN   ! all processes synchronized -> use lwp to print in opened ocean.output files 
    222             IF(lwp)   CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
     222            IF(lwp) THEN   ;   CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
     223            ELSE           ;   nstop = MAX(1, nstop)   ! make sure nstop > 0 (automatically done when calling ctl_stop) 
     224            ENDIF 
    223225         ELSE                                    ! only mpi subdomains with errors are here -> STOP now 
    224226            CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
    225227         ENDIF 
    226228         ! 
    227          IF( nstop == 0 )   nstop = 1  
    228          ngrdstop = Agrif_Fixed() 
    229          ! 
     229      ENDIF 
     230      ! 
     231      IF( nstop > 0 ) THEN                                                  ! an error was detected and we did not abort yet... 
     232         ngrdstop = Agrif_Fixed()                                           ! store which grid got this error 
     233         IF( .NOT. ll_colruns .AND. jpnij > 1 )   CALL ctl_stop( 'STOP' )   ! we must abort here to avoid MPI deadlock 
    230234      ENDIF 
    231235      ! 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/SAS/stpctl.F90

    r13015 r13124  
    180180         ! 
    181181         IF( ll_colruns .or. jpnij == 1 ) THEN   ! all processes synchronized -> use lwp to print in opened ocean.output files 
    182             IF(lwp)   CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
     182            IF(lwp) THEN   ;   CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
     183            ELSE           ;   nstop = MAX(1, nstop)   ! make sure nstop > 0 (automatically done when calling ctl_stop) 
     184            ENDIF 
    183185         ELSE                                    ! only mpi subdomains with errors are here -> STOP now 
    184186            CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
    185187         ENDIF 
    186188         ! 
    187          IF( nstop == 0 )   nstop = 1  
    188          ngrdstop = Agrif_Fixed() 
    189          ! 
     189      ENDIF 
     190      ! 
     191      IF( nstop > 0 ) THEN                                                  ! an error was detected and we did not abort yet... 
     192         ngrdstop = Agrif_Fixed()                                           ! store which grid got this error 
     193         IF( .NOT. ll_colruns .AND. jpnij > 1 )   CALL ctl_stop( 'STOP' )   ! we must abort here to avoid MPI deadlock 
    190194      ENDIF 
    191195      ! 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/TOP/PISCES/P4Z/p4zsms.F90

    r12738 r13124  
    206206      IF( l_trdtrc ) THEN 
    207207         DO jn = jp_pcs0, jp_pcs1 
    208            ztrdt(:,:,:,jn) = ( tr(:,:,:,jn,Kbb) - ztrdt(:,:,:,jn) ) * rfact2r  
     208           ztrdt(:,:,:,jn) = ( tr(:,:,:,jn,Kbb) - ztrdt(:,:,:,jn) ) * rfactr  
    209209           CALL trd_trc( tr(:,:,:,jn,Krhs), jn, jptra_sms, kt, Kmm )   ! save trends 
    210210         END DO 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/tests/CANAL/MY_SRC/stpctl.F90

    r13015 r13124  
    130130      zmax(3) = MAXVAL( -ts(:,:,:,jp_sal,Kmm), mask = llmsk )                     ! minus salinity max 
    131131      zmax(4) = MAXVAL(  ts(:,:,:,jp_sal,Kmm), mask = llmsk )                     !       salinity max 
    132       IF( ll_colruns ) THEN     ! following variables are used only in the netcdf file 
     132      IF( ll_colruns .OR. jpnij == 1 ) THEN     ! following variables are used only in the netcdf file 
    133133         zmax(5) = MAXVAL( -ts(:,:,:,jp_tem,Kmm), mask = llmsk )                  ! minus temperature max 
    134134         zmax(6) = MAXVAL(  ts(:,:,:,jp_tem,Kmm), mask = llmsk )                  !       temperature max 
     
    220220         ! 
    221221         IF( ll_colruns .or. jpnij == 1 ) THEN   ! all processes synchronized -> use lwp to print in opened ocean.output files 
    222             IF(lwp)   CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
     222            IF(lwp) THEN   ;   CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
     223            ELSE           ;   nstop = MAX(1, nstop)   ! make sure nstop > 0 (automatically done when calling ctl_stop) 
     224            ENDIF 
    223225         ELSE                                    ! only mpi subdomains with errors are here -> STOP now 
    224226            CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
    225227         ENDIF 
    226228         ! 
    227          IF( nstop == 0 )   nstop = 1  
    228          ngrdstop = Agrif_Fixed() 
    229          ! 
     229      ENDIF 
     230      ! 
     231      IF( nstop > 0 ) THEN                                                  ! an error was detected and we did not abort yet... 
     232         ngrdstop = Agrif_Fixed()                                           ! store which grid got this error 
     233         IF( .NOT. ll_colruns .AND. jpnij > 1 )   CALL ctl_stop( 'STOP' )   ! we must abort here to avoid MPI deadlock 
    230234      ENDIF 
    231235      ! 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/tests/STATION_ASF/EXPREF/file_def_nemo-oce.xml

    r11930 r13124  
    2828      <field field_ref="empmr"        name="empmr" /> 
    2929      <!-- --> 
    30       <field field_ref="taum"         name="taum"     /> 
    31       <field field_ref="wspd"         name="windsp"   /> 
     30      <field field_ref="taum"         name="taum"   /> 
     31      <field field_ref="wspd"         name="windsp" /> 
     32      <!-- --> 
     33      <field field_ref="Cd_oce"       name="Cd_oce" /> 
     34      <field field_ref="Ce_oce"       name="Ce_oce" /> 
     35      <field field_ref="Ch_oce"       name="Ch_oce" /> 
    3236    </file> 
    3337 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/tests/STATION_ASF/EXPREF/launch_sasf.sh

    r12939 r13124  
    3333 
    3434 
    35 if [ ! -f ${NEMO_EXE} ]; then echo " Mhhh, no compiled nemo.exe found into ${NEMO_DIR}/tests/STATION_ASF/BLD/bin !"; exit; fi 
     35if [ ! -f ${NEMO_EXE} ]; then echo " Mhhh, no compiled 'nemo.exe' found into `dirname ${NEMO_EXE}` !"; exit; fi 
    3636 
    3737echo 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/tests/STATION_ASF/EXPREF/namelist_coare3p6-noskin_cfg

    r12939 r13124  
    2929   cn_exp      =  'STATION_ASF-COARE3p6-noskin'  !  experience name 
    3030   nn_it000    =    1   !  first time step 
    31    nn_itend    =    26280   !  last  time step (std 5840) 
    32    nn_date0    =    20160101   !  date at nit_0000 (format yyyymmdd) used if ln_rstart=F or (ln_rstart=T and nn_rstctl=0 or 1) 
     31!!!   nn_itend    =    26304   !  last  time step => 3 years (including 1 leap!) at dt=3600s 
     32!!!   nn_date0    =    20160101   !  date at nit_0000 (format yyyymmdd) used if ln_rstart=F or (ln_rstart=T and nn_rstctl=0 or 1) 
     33   nn_itend    =    8760   !  last  time step => 3 years (including 1 leap!) at dt=3600s 
     34   nn_date0    = 20180101  !  date at nit_0000 (format yyyymmdd) used if ln_rstart=F or (ln_rstart=T and nn_rstctl=0 or 1) 
    3335   nn_time0    =       0   !  initial time of day in hhmm 
    34    nn_leapy    =       0   !  Leap year calendar (1) or not (0) 
     36   nn_leapy    =       1   !  Leap year calendar (1) or not (0) 
    3537   ln_rstart   = .false.   !  start from rest (F) or from a restart file (T) 
    3638      ln_1st_euler = .false.  !  =T force a start with forward time step (ln_rstart=T) 
     
    4547   nn_istate   =       0   !  output the initial state (1) or not (0) 
    4648   ln_rst_list = .false.   !  output restarts at list of times using nn_stocklist (T) or at set frequency with nn_stock (F) 
    47    nn_stock    =    26280   ! 1year @ dt=3600 s / frequency of creation of a restart file (modulo referenced to 1) 
    48    nn_write    =    26280   ! 1year @ dt=3600 s / frequency of write in the output file   (modulo referenced to nn_it000) 
     49   !! 
     50!!!   nn_stock    =    26304   ! 3 years (including 1 leap!) at dt=3600s / frequency of creation of a restart file (modulo referenced to 1) 
     51!!!   nn_write    =    26304   ! 3 years (including 1 leap!) at dt=3600s / frequency of write in the output file   (modulo referenced to nn_it000) 
     52   nn_stock    =    8760   ! 1 year at dt=3600s / frequency of creation of a restart file (modulo referenced to 1) 
     53   nn_write    =    8760   ! 1 year at dt=3600s / frequency of write in the output file   (modulo referenced to nn_it000) 
     54   !! 
    4955   ln_mskland  = .false.   !  mask land points in NetCDF outputs (costly: + ~15%) 
    5056   ln_cfmeta   = .false.   !  output additional data to netCDF files required for compliance with the CF metadata standard 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/tests/STATION_ASF/EXPREF/namelist_coare3p6_cfg

    r12939 r13124  
    2929   cn_exp      =  'STATION_ASF-COARE3p6'  !  experience name 
    3030   nn_it000    =    1   !  first time step 
    31    nn_itend    =    26280   !  last  time step (std 5840) 
    32    nn_date0    =    20160101   !  date at nit_0000 (format yyyymmdd) used if ln_rstart=F or (ln_rstart=T and nn_rstctl=0 or 1) 
     31!!!   nn_itend    =    26304   !  last  time step => 3 years (including 1 leap!) at dt=3600s 
     32!!!   nn_date0    =    20160101   !  date at nit_0000 (format yyyymmdd) used if ln_rstart=F or (ln_rstart=T and nn_rstctl=0 or 1) 
     33   nn_itend    =    8760   !  last  time step => 3 years (including 1 leap!) at dt=3600s 
     34   nn_date0    = 20180101  !  date at nit_0000 (format yyyymmdd) used if ln_rstart=F or (ln_rstart=T and nn_rstctl=0 or 1) 
    3335   nn_time0    =       0   !  initial time of day in hhmm 
    34    nn_leapy    =       0   !  Leap year calendar (1) or not (0) 
     36   nn_leapy    =       1   !  Leap year calendar (1) or not (0) 
    3537   ln_rstart   = .false.   !  start from rest (F) or from a restart file (T) 
    3638      ln_1st_euler = .false.  !  =T force a start with forward time step (ln_rstart=T) 
     
    4547   nn_istate   =       0   !  output the initial state (1) or not (0) 
    4648   ln_rst_list = .false.   !  output restarts at list of times using nn_stocklist (T) or at set frequency with nn_stock (F) 
    47    nn_stock    =    26280   ! 1year @ dt=3600 s / frequency of creation of a restart file (modulo referenced to 1) 
    48    nn_write    =    26280   ! 1year @ dt=3600 s / frequency of write in the output file   (modulo referenced to nn_it000) 
     49   !! 
     50!!!   nn_stock    =    26304   ! 3 years (including 1 leap!) at dt=3600s / frequency of creation of a restart file (modulo referenced to 1) 
     51!!!   nn_write    =    26304   ! 3 years (including 1 leap!) at dt=3600s / frequency of write in the output file   (modulo referenced to nn_it000) 
     52   nn_stock    =    8760   ! 1 year at dt=3600s / frequency of creation of a restart file (modulo referenced to 1) 
     53   nn_write    =    8760   ! 1 year at dt=3600s / frequency of write in the output file   (modulo referenced to nn_it000) 
     54   !! 
    4955   ln_mskland  = .false.   !  mask land points in NetCDF outputs (costly: + ~15%) 
    5056   ln_cfmeta   = .false.   !  output additional data to netCDF files required for compliance with the CF metadata standard 
     
    134140      ln_humi_rlh = .true.  !  humidity specified below in "sn_humi" is relative humidity       [%]   if .true. 
    135141   ! 
    136    cn_dir      = './'      !  root directory for the bulk data location 
     142   cn_dir = './'  !  root directory for the bulk data location 
    137143   !___________!_________________________!___________________!___________!_____________!________!___________!______________________________________!__________!_______________! 
    138144   !           !  file name              ! frequency (hours) ! variable  ! time interp.!  clim  ! 'yearly'/ !       weights filename               ! rotation ! land/sea mask ! 
     
    163169      ln_read_frq = .false.   !  specify whether we must read frq or not 
    164170 
    165    cn_dir      = './'      !  root directory for the ocean data location 
     171   cn_dir      = './'     !  root directory for the ocean data location 
    166172   !___________!_________________________!___________________!___________!_____________!________!___________!__________________!__________!_______________! 
    167173   !           !  file name              ! frequency (hours) ! variable  ! time interp.!  clim  ! 'yearly'/ ! weights filename ! rotation ! land/sea mask ! 
     
    215221&nameos        !   ocean Equation Of Seawater                           (default: NO selection) 
    216222!----------------------------------------------------------------------- 
    217    ln_eos80    = .true.         !  = Use EOS80 
     223   ln_eos80    = .true.          !  = Use EOS80 
    218224/ 
    219225!!====================================================================== 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/tests/STATION_ASF/EXPREF/namelist_ecmwf-noskin_cfg

    r12939 r13124  
    2929   cn_exp      =  'STATION_ASF-ECMWF-noskin'  !  experience name 
    3030   nn_it000    =    1   !  first time step 
    31    nn_itend    =    26280   !  last  time step (std 5840) 
    32    nn_date0    =    20160101   !  date at nit_0000 (format yyyymmdd) used if ln_rstart=F or (ln_rstart=T and nn_rstctl=0 or 1) 
     31!!!   nn_itend    =    26304   !  last  time step => 3 years (including 1 leap!) at dt=3600s 
     32!!!   nn_date0    =    20160101   !  date at nit_0000 (format yyyymmdd) used if ln_rstart=F or (ln_rstart=T and nn_rstctl=0 or 1) 
     33   nn_itend    =    8760   !  last  time step => 3 years (including 1 leap!) at dt=3600s 
     34   nn_date0    = 20180101  !  date at nit_0000 (format yyyymmdd) used if ln_rstart=F or (ln_rstart=T and nn_rstctl=0 or 1) 
    3335   nn_time0    =       0   !  initial time of day in hhmm 
    34    nn_leapy    =       0   !  Leap year calendar (1) or not (0) 
     36   nn_leapy    =       1   !  Leap year calendar (1) or not (0) 
    3537   ln_rstart   = .false.   !  start from rest (F) or from a restart file (T) 
    3638      ln_1st_euler = .false.  !  =T force a start with forward time step (ln_rstart=T) 
     
    4547   nn_istate   =       0   !  output the initial state (1) or not (0) 
    4648   ln_rst_list = .false.   !  output restarts at list of times using nn_stocklist (T) or at set frequency with nn_stock (F) 
    47    nn_stock    =    26280   ! 1year @ dt=3600 s / frequency of creation of a restart file (modulo referenced to 1) 
    48    nn_write    =    26280   ! 1year @ dt=3600 s / frequency of write in the output file   (modulo referenced to nn_it000) 
     49   !! 
     50!!!   nn_stock    =    26304   ! 3 years (including 1 leap!) at dt=3600s / frequency of creation of a restart file (modulo referenced to 1) 
     51!!!   nn_write    =    26304   ! 3 years (including 1 leap!) at dt=3600s / frequency of write in the output file   (modulo referenced to nn_it000) 
     52   nn_stock    =    8760   ! 1 year at dt=3600s / frequency of creation of a restart file (modulo referenced to 1) 
     53   nn_write    =    8760   ! 1 year at dt=3600s / frequency of write in the output file   (modulo referenced to nn_it000) 
     54   !! 
    4955   ln_mskland  = .false.   !  mask land points in NetCDF outputs (costly: + ~15%) 
    5056   ln_cfmeta   = .false.   !  output additional data to netCDF files required for compliance with the CF metadata standard 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/tests/STATION_ASF/EXPREF/namelist_ecmwf_cfg

    r12939 r13124  
    2929   cn_exp      =  'STATION_ASF-ECMWF'  !  experience name 
    3030   nn_it000    =    1   !  first time step 
    31    nn_itend    =    26280   !  last  time step (std 5840) 
    32    nn_date0    =    20160101   !  date at nit_0000 (format yyyymmdd) used if ln_rstart=F or (ln_rstart=T and nn_rstctl=0 or 1) 
     31!!!   nn_itend    =    26304   !  last  time step => 3 years (including 1 leap!) at dt=3600s 
     32!!!   nn_date0    =    20160101   !  date at nit_0000 (format yyyymmdd) used if ln_rstart=F or (ln_rstart=T and nn_rstctl=0 or 1) 
     33   nn_itend    =    8760   !  last  time step => 3 years (including 1 leap!) at dt=3600s 
     34   nn_date0    = 20180101  !  date at nit_0000 (format yyyymmdd) used if ln_rstart=F or (ln_rstart=T and nn_rstctl=0 or 1) 
    3335   nn_time0    =       0   !  initial time of day in hhmm 
    34    nn_leapy    =       0   !  Leap year calendar (1) or not (0) 
     36   nn_leapy    =       1   !  Leap year calendar (1) or not (0) 
    3537   ln_rstart   = .false.   !  start from rest (F) or from a restart file (T) 
    3638      ln_1st_euler = .false.  !  =T force a start with forward time step (ln_rstart=T) 
     
    4547   nn_istate   =       0   !  output the initial state (1) or not (0) 
    4648   ln_rst_list = .false.   !  output restarts at list of times using nn_stocklist (T) or at set frequency with nn_stock (F) 
    47    nn_stock    =    26280   ! 1year @ dt=3600 s / frequency of creation of a restart file (modulo referenced to 1) 
    48    nn_write    =    26280   ! 1year @ dt=3600 s / frequency of write in the output file   (modulo referenced to nn_it000) 
     49   !! 
     50!!!   nn_stock    =    26304   ! 3 years (including 1 leap!) at dt=3600s / frequency of creation of a restart file (modulo referenced to 1) 
     51!!!   nn_write    =    26304   ! 3 years (including 1 leap!) at dt=3600s / frequency of write in the output file   (modulo referenced to nn_it000) 
     52   nn_stock    =    8760   ! 1 year at dt=3600s / frequency of creation of a restart file (modulo referenced to 1) 
     53   nn_write    =    8760   ! 1 year at dt=3600s / frequency of write in the output file   (modulo referenced to nn_it000) 
     54   !! 
    4955   ln_mskland  = .false.   !  mask land points in NetCDF outputs (costly: + ~15%) 
    5056   ln_cfmeta   = .false.   !  output additional data to netCDF files required for compliance with the CF metadata standard 
     
    134140      ln_humi_rlh = .true.  !  humidity specified below in "sn_humi" is relative humidity       [%]   if .true. 
    135141   ! 
    136    cn_dir      = './'      !  root directory for the bulk data location 
     142   cn_dir = './'  !  root directory for the bulk data location 
    137143   !___________!_________________________!___________________!___________!_____________!________!___________!______________________________________!__________!_______________! 
    138144   !           !  file name              ! frequency (hours) ! variable  ! time interp.!  clim  ! 'yearly'/ !       weights filename               ! rotation ! land/sea mask ! 
     
    163169      ln_read_frq = .false.   !  specify whether we must read frq or not 
    164170 
    165    cn_dir      = './'      !  root directory for the ocean data location 
     171   cn_dir      = './'     !  root directory for the ocean data location 
    166172   !___________!_________________________!___________________!___________!_____________!________!___________!__________________!__________!_______________! 
    167173   !           !  file name              ! frequency (hours) ! variable  ! time interp.!  clim  ! 'yearly'/ ! weights filename ! rotation ! land/sea mask ! 
     
    215221&nameos        !   ocean Equation Of Seawater                           (default: NO selection) 
    216222!----------------------------------------------------------------------- 
    217    ln_eos80    = .true.         !  = Use EOS80 
     223   ln_eos80    = .true.          !  = Use EOS80 
    218224/ 
    219225!!====================================================================== 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/tests/STATION_ASF/EXPREF/namelist_ncar_cfg

    r12939 r13124  
    2929   cn_exp      =  'STATION_ASF-NCAR'  !  experience name 
    3030   nn_it000    =    1   !  first time step 
    31    nn_itend    =    26280   !  last  time step (std 5840) 
    32    nn_date0    =    20160101   !  date at nit_0000 (format yyyymmdd) used if ln_rstart=F or (ln_rstart=T and nn_rstctl=0 or 1) 
     31!!!   nn_itend    =    26304   !  last  time step => 3 years (including 1 leap!) at dt=3600s 
     32!!!   nn_date0    =    20160101   !  date at nit_0000 (format yyyymmdd) used if ln_rstart=F or (ln_rstart=T and nn_rstctl=0 or 1) 
     33   nn_itend    =    8760   !  last  time step => 3 years (including 1 leap!) at dt=3600s 
     34   nn_date0    = 20180101  !  date at nit_0000 (format yyyymmdd) used if ln_rstart=F or (ln_rstart=T and nn_rstctl=0 or 1) 
    3335   nn_time0    =       0   !  initial time of day in hhmm 
    34    nn_leapy    =       0   !  Leap year calendar (1) or not (0) 
     36   nn_leapy    =       1   !  Leap year calendar (1) or not (0) 
    3537   ln_rstart   = .false.   !  start from rest (F) or from a restart file (T) 
    3638      ln_1st_euler = .false.  !  =T force a start with forward time step (ln_rstart=T) 
     
    4547   nn_istate   =       0   !  output the initial state (1) or not (0) 
    4648   ln_rst_list = .false.   !  output restarts at list of times using nn_stocklist (T) or at set frequency with nn_stock (F) 
    47    nn_stock    =    26280   ! 1year @ dt=3600 s / frequency of creation of a restart file (modulo referenced to 1) 
    48    nn_write    =    26280   ! 1year @ dt=3600 s / frequency of write in the output file   (modulo referenced to nn_it000) 
     49   !! 
     50!!!   nn_stock    =    26304   ! 3 years (including 1 leap!) at dt=3600s / frequency of creation of a restart file (modulo referenced to 1) 
     51!!!   nn_write    =    26304   ! 3 years (including 1 leap!) at dt=3600s / frequency of write in the output file   (modulo referenced to nn_it000) 
     52   nn_stock    =    8760   ! 1 year at dt=3600s / frequency of creation of a restart file (modulo referenced to 1) 
     53   nn_write    =    8760   ! 1 year at dt=3600s / frequency of write in the output file   (modulo referenced to nn_it000) 
     54   !! 
    4955   ln_mskland  = .false.   !  mask land points in NetCDF outputs (costly: + ~15%) 
    5056   ln_cfmeta   = .false.   !  output additional data to netCDF files required for compliance with the CF metadata standard 
     
    134140      ln_humi_rlh = .true.  !  humidity specified below in "sn_humi" is relative humidity       [%]   if .true. 
    135141   ! 
    136    cn_dir      = './'      !  root directory for the bulk data location 
     142   cn_dir = './'  !  root directory for the bulk data location 
    137143   !___________!_________________________!___________________!___________!_____________!________!___________!______________________________________!__________!_______________! 
    138144   !           !  file name              ! frequency (hours) ! variable  ! time interp.!  clim  ! 'yearly'/ !       weights filename               ! rotation ! land/sea mask ! 
     
    163169      ln_read_frq = .false.   !  specify whether we must read frq or not 
    164170 
    165    cn_dir      = './'      !  root directory for the ocean data location 
     171   cn_dir      = './'     !  root directory for the ocean data location 
    166172   !___________!_________________________!___________________!___________!_____________!________!___________!__________________!__________!_______________! 
    167173   !           !  file name              ! frequency (hours) ! variable  ! time interp.!  clim  ! 'yearly'/ ! weights filename ! rotation ! land/sea mask ! 
     
    215221&nameos        !   ocean Equation Of Seawater                           (default: NO selection) 
    216222!----------------------------------------------------------------------- 
    217    ln_eos80    = .true.         !  = Use EOS80 
     223   ln_eos80    = .true.          !  = Use EOS80 
    218224/ 
    219225!!====================================================================== 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/tests/STATION_ASF/MY_SRC/stpctl.F90

    r13015 r13124  
    179179         ! 
    180180         IF( ll_colruns .or. jpnij == 1 ) THEN   ! all processes synchronized -> use lwp to print in opened ocean.output files 
    181             IF(lwp)   CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
     181            IF(lwp) THEN   ;   CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
     182            ELSE           ;   nstop = MAX(1, nstop)   ! make sure nstop > 0 (automatically done when calling ctl_stop) 
     183            ENDIF 
    182184         ELSE                                    ! only mpi subdomains with errors are here -> STOP now 
    183185            CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
    184186         ENDIF 
    185187         ! 
    186          IF( nstop == 0 )   nstop = 1  
    187          ngrdstop = Agrif_Fixed() 
    188          ! 
     188      ENDIF 
     189      ! 
     190      IF( nstop > 0 ) THEN                                                  ! an error was detected and we did not abort yet... 
     191         ngrdstop = Agrif_Fixed()                                           ! store which grid got this error 
     192         IF( .NOT. ll_colruns .AND. jpnij > 1 )   CALL ctl_stop( 'STOP' )   ! we must abort here to avoid MPI deadlock 
    189193      ENDIF 
    190194      ! 
Note: See TracChangeset for help on using the changeset viewer.