Changeset 13124
- Timestamp:
- 2020-06-17T16:46:58+02:00 (5 years ago)
- 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 369 369 <field id="taum_oce" long_name="wind stress module over open ocean" standard_name="magnitude_of_surface_downward_stress" unit="N/m2" /> 370 370 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 371 379 <!-- available key_oasis3 --> 372 380 <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 77 77 REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zarea_ssh , zbotpres ! 2D workspace 78 78 REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zpe, z2d ! 2D workspace 79 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zrhd , z rhop, ztpot! 3D workspace79 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zrhd , ztpot ! 3D workspace 80 80 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) :: ztsn ! 4D workspace 81 81 … … 87 87 IF( l_ar5 ) THEN 88 88 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) ) 90 90 ALLOCATE( ztsn(jpi,jpj,jpk,jpts) ) 91 91 zarea_ssh(:,:) = e1e2t(:,:) * ssh(:,:,Kmm) … … 155 155 156 156 ! ! steric sea surface height 157 CALL eos( ts(:,:,:,:,Kmm), zrhd, zrhop, gdept(:,:,:,Kmm) ) ! now in situ and potential density158 zrhop(:,:,jpk) = 0._wp159 CALL iom_put( 'rhop', zrhop )160 !161 157 zbotpres(:,:) = 0._wp ! no atmospheric surface pressure, levitating sea-ice 162 158 DO jk = 1, jpkm1 163 zbotpres(:,:) = zbotpres(:,:) + e3t(:,:,jk,Kmm) * zrhd(:,:,jk)159 zbotpres(:,:) = zbotpres(:,:) + e3t(:,:,jk,Kmm) * rhd(:,:,jk) 164 160 END DO 165 161 IF( ln_linssh ) THEN … … 168 164 DO jj = 1,jpj 169 165 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) 171 167 END DO 172 168 END DO 173 169 ELSE 174 zbotpres(:,:) = zbotpres(:,:) + ssh(:,:,Kmm) * zrhd(:,:,1)170 zbotpres(:,:) = zbotpres(:,:) + ssh(:,:,Kmm) * rhd(:,:,1) 175 171 END IF 176 172 END IF … … 293 289 IF( l_ar5 ) THEN 294 290 DEALLOCATE( zarea_ssh , zbotpres, z2d ) 295 DEALLOCATE( zrhd , zrhop )296 291 DEALLOCATE( ztsn ) 297 292 ENDIF … … 367 362 IF( iom_use( 'voltot' ) .OR. iom_use( 'sshtot' ) .OR. iom_use( 'sshdyn' ) .OR. & 368 363 & 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. 370 366 371 367 IF( l_ar5 ) THEN -
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/DIA/diawri.F90
r12939 r13124 171 171 CALL iom_put( "sbs", z2d ) ! bottom salinity 172 172 ENDIF 173 174 CALL iom_put( "rhop", rhop(:,:,:) ) ! 3D potential density (sigma0) 173 175 174 176 IF ( iom_use("taubot") ) THEN ! bottom stress -
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/DOM/istate.F90
r12489 r13124 24 24 USE dom_oce ! ocean space and time domain 25 25 USE daymod ! calendar 26 USE divhor ! horizontal divergence (div_hor routine)27 26 USE dtatsd ! data temperature and salinity (dta_tsd routine) 28 27 USE dtauvd ! data: U & V current (dta_uvd routine) … … 121 120 uu (:,:,:,Kmm) = uu (:,:,:,Kbb) 122 121 vv (:,:,:,Kmm) = vv (:,:,:,Kbb) 123 hdiv(:,:,jpk) = 0._wp ! bottom divergence set one for 0 to zero at jpk level124 CALL div_hor( 0, Kbb, Kmm ) ! compute interior hdiv value125 !!gm hdiv(:,:,:) = 0._wp126 122 127 123 !!gm POTENTIAL BUG : -
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/ICB/icbrst.F90
r13015 r13124 193 193 CHARACTER(len=256) :: cl_path 194 194 CHARACTER(len=256) :: cl_filename 195 CHARACTER(len= 256) :: cl_kt195 CHARACTER(len=8 ) :: cl_kt 196 196 CHARACTER(LEN=12 ) :: clfmt ! writing format 197 197 TYPE(iceberg), POINTER :: this … … 214 214 ! file name 215 215 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) 217 217 IF( lk_mpp ) THEN 218 218 idg = MAX( INT(LOG10(REAL(MAX(1,jpnij-1),wp))) + 1, 4 ) ! how many digits to we need to write? min=4, max=9 219 219 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' 221 221 ELSE 222 WRITE(cl_filename,'( A,".nc")') TRIM(cl_filename)222 WRITE(cl_filename,'(a,a)') TRIM(cl_filename), '.nc' 223 223 ENDIF 224 224 -
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/ICB/icbtrj.F90
r13015 r13124 66 66 CHARACTER(len=80) :: cl_filename 67 67 CHARACTER(LEN=12) :: clfmt ! writing format 68 CHARACTER(LEN= 20) :: cldate_ini, cldate_end68 CHARACTER(LEN=8 ) :: cldate_ini, cldate_end 69 69 TYPE(iceberg), POINTER :: this 70 70 TYPE(point) , POINTER :: pt … … 82 82 83 83 ! 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 85 85 IF ( lk_mpp ) THEN 86 86 idg = MAX( INT(LOG10(REAL(MAX(1,jpnij-1),wp))) + 1, 4 ) ! how many digits to we need to write? min=4, max=9 87 87 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' 89 89 ELSE 90 WRITE(cl_filename,'( A,".nc")') TRIM(cl_filename)90 WRITE(cl_filename,'(a,a)') TRIM(cl_filename), '.nc' 91 91 ENDIF 92 92 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 28 28 INTEGER, PARAMETER, PUBLIC :: jpmax_vars = 1200 !: maximum number of variables in one file 29 29 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 name30 INTEGER, PARAMETER, PUBLIC :: jpmax_digits = 9 !: maximum number of digits for the cpu number in the file name 31 31 32 32 !$AGRIF_DO_NOT_TREAT -
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/LBC/lib_mpp.F90
r13015 r13124 1221 1221 CHARACTER(LEN=10) :: clfmt ! writing format 1222 1222 INTEGER :: iost 1223 INTEGER :: idg ! number of digits1223 INTEGER :: idg ! number of digits 1224 1224 !!---------------------------------------------------------------------- 1225 1225 ! -
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/SBC/sbcblk.F90
r12939 r13124 628 628 END SELECT 629 629 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 630 634 IF( ln_skin_cs .OR. ln_skin_wl ) THEN 631 635 !! ptsk and pssq have been updated!!! … … 878 882 Ce_ice(:,:) = Ch_ice(:,:) ! sensible and latent heat transfer coef. are considered identical 879 883 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 884 889 ! local scalars ( place there for vector optimisation purposes) 885 890 zcd_dui(:,:) = wndm_ice(:,:) * Cd_ice(:,:) -
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/SBC/sbccpl.F90
r12980 r13124 1785 1785 ENDDO 1786 1786 ELSE 1787 qns_tot(:,:) =qns_tot(:,:) + picefr(:,:) * frcv(jpr_qnsice)%z3(:,:,1)1787 zqns_tot(:,:) = zqns_tot(:,:) + picefr(:,:) * frcv(jpr_qnsice)%z3(:,:,1) 1788 1788 DO jl = 1, jpl 1789 zqns_tot(:,: ) = zqns_tot(:,:) + picefr(:,:) * frcv(jpr_qnsice)%z3(:,:,1)1790 1789 zqns_ice(:,:,jl) = frcv(jpr_qnsice)%z3(:,:,1) 1791 1790 END DO … … 1928 1927 END DO 1929 1928 ELSE 1930 qsr_tot(:,: ) =qsr_tot(:,:) + picefr(:,:) * frcv(jpr_qsrice)%z3(:,:,1)1929 zqsr_tot(:,:) = zqsr_tot(:,:) + picefr(:,:) * frcv(jpr_qsrice)%z3(:,:,1) 1931 1930 DO jl = 1, jpl 1932 zqsr_tot(:,: ) = zqsr_tot(:,:) + picefr(:,:) * frcv(jpr_qsrice)%z3(:,:,1)1933 1931 zqsr_ice(:,:,jl) = frcv(jpr_qsrice)%z3(:,:,1) 1934 1932 END DO -
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/TRD/trdtra.F90
r12489 r13124 82 82 REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in), OPTIONAL :: ptra ! now tracer variable 83 83 ! 84 INTEGER :: jk ! loop indices 84 INTEGER :: jk ! loop indices 85 INTEGER :: i01 ! 0 or 1 85 86 REAL(wp), DIMENSION(jpi,jpj,jpk) :: ztrds ! 3D workspace 86 87 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zwt, zws, ztrdt ! 3D workspace … … 90 91 IF( trd_tra_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'trd_tra : unable to allocate arrays' ) 91 92 ENDIF 92 93 ! 94 i01 = COUNT( (/ PRESENT(pu) .OR. ( ktrd /= jptra_xad .AND. ktrd /= jptra_yad .AND. ktrd /= jptra_zad ) /) ) 95 ! 93 96 IF( ctype == 'TRA' .AND. ktra == jp_tem ) THEN !== Temperature trend ==! 94 97 ! 95 SELECT CASE( ktrd )98 SELECT CASE( ktrd*i01 ) 96 99 ! ! advection: transform the advective flux into a trend 97 100 CASE( jptra_xad ) ; CALL trd_tra_adv( ptrd, pu, ptra, 'X', trdtx, Kmm ) … … 112 115 IF( ctype == 'TRA' .AND. ktra == jp_sal ) THEN !== Salinity trends ==! 113 116 ! 114 SELECT CASE( ktrd )117 SELECT CASE( ktrd*i01 ) 115 118 ! ! advection: transform the advective flux into a trend 116 119 ! ! and send T & S trends to trd_tra_mng … … 163 166 IF( ctype == 'TRC' ) THEN !== passive tracer trend ==! 164 167 ! 165 SELECT CASE( ktrd )168 SELECT CASE( ktrd*i01 ) 166 169 ! ! advection: transform the advective flux into a masked trend 167 170 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 130 130 zmax(3) = MAXVAL( -ts(:,:,:,jp_sal,Kmm), mask = llmsk ) ! minus salinity max 131 131 zmax(4) = MAXVAL( ts(:,:,:,jp_sal,Kmm), mask = llmsk ) ! salinity max 132 IF( ll_colruns ) THEN ! following variables are used only in the netcdf file132 IF( ll_colruns .OR. jpnij == 1 ) THEN ! following variables are used only in the netcdf file 133 133 zmax(5) = MAXVAL( -ts(:,:,:,jp_tem,Kmm), mask = llmsk ) ! minus temperature max 134 134 zmax(6) = MAXVAL( ts(:,:,:,jp_tem,Kmm), mask = llmsk ) ! temperature max … … 220 220 ! 221 221 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 223 225 ELSE ! only mpi subdomains with errors are here -> STOP now 224 226 CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 225 227 ENDIF 226 228 ! 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 230 234 ENDIF 231 235 ! -
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/SAS/stpctl.F90
r13015 r13124 180 180 ! 181 181 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 183 185 ELSE ! only mpi subdomains with errors are here -> STOP now 184 186 CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 185 187 ENDIF 186 188 ! 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 190 194 ENDIF 191 195 ! -
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/TOP/PISCES/P4Z/p4zsms.F90
r12738 r13124 206 206 IF( l_trdtrc ) THEN 207 207 DO jn = jp_pcs0, jp_pcs1 208 ztrdt(:,:,:,jn) = ( tr(:,:,:,jn,Kbb) - ztrdt(:,:,:,jn) ) * rfact 2r208 ztrdt(:,:,:,jn) = ( tr(:,:,:,jn,Kbb) - ztrdt(:,:,:,jn) ) * rfactr 209 209 CALL trd_trc( tr(:,:,:,jn,Krhs), jn, jptra_sms, kt, Kmm ) ! save trends 210 210 END DO -
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/tests/CANAL/MY_SRC/stpctl.F90
r13015 r13124 130 130 zmax(3) = MAXVAL( -ts(:,:,:,jp_sal,Kmm), mask = llmsk ) ! minus salinity max 131 131 zmax(4) = MAXVAL( ts(:,:,:,jp_sal,Kmm), mask = llmsk ) ! salinity max 132 IF( ll_colruns ) THEN ! following variables are used only in the netcdf file132 IF( ll_colruns .OR. jpnij == 1 ) THEN ! following variables are used only in the netcdf file 133 133 zmax(5) = MAXVAL( -ts(:,:,:,jp_tem,Kmm), mask = llmsk ) ! minus temperature max 134 134 zmax(6) = MAXVAL( ts(:,:,:,jp_tem,Kmm), mask = llmsk ) ! temperature max … … 220 220 ! 221 221 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 223 225 ELSE ! only mpi subdomains with errors are here -> STOP now 224 226 CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 225 227 ENDIF 226 228 ! 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 230 234 ENDIF 231 235 ! -
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/tests/STATION_ASF/EXPREF/file_def_nemo-oce.xml
r11930 r13124 28 28 <field field_ref="empmr" name="empmr" /> 29 29 <!-- --> 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" /> 32 36 </file> 33 37 -
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/tests/STATION_ASF/EXPREF/launch_sasf.sh
r12939 r13124 33 33 34 34 35 if [ ! -f ${NEMO_EXE} ]; then echo " Mhhh, no compiled nemo.exe found into ${NEMO_DIR}/tests/STATION_ASF/BLD/bin!"; exit; fi35 if [ ! -f ${NEMO_EXE} ]; then echo " Mhhh, no compiled 'nemo.exe' found into `dirname ${NEMO_EXE}` !"; exit; fi 36 36 37 37 echo -
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/tests/STATION_ASF/EXPREF/namelist_coare3p6-noskin_cfg
r12939 r13124 29 29 cn_exp = 'STATION_ASF-COARE3p6-noskin' ! experience name 30 30 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) 33 35 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) 35 37 ln_rstart = .false. ! start from rest (F) or from a restart file (T) 36 38 ln_1st_euler = .false. ! =T force a start with forward time step (ln_rstart=T) … … 45 47 nn_istate = 0 ! output the initial state (1) or not (0) 46 48 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 !! 49 55 ln_mskland = .false. ! mask land points in NetCDF outputs (costly: + ~15%) 50 56 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 29 29 cn_exp = 'STATION_ASF-COARE3p6' ! experience name 30 30 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) 33 35 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) 35 37 ln_rstart = .false. ! start from rest (F) or from a restart file (T) 36 38 ln_1st_euler = .false. ! =T force a start with forward time step (ln_rstart=T) … … 45 47 nn_istate = 0 ! output the initial state (1) or not (0) 46 48 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 !! 49 55 ln_mskland = .false. ! mask land points in NetCDF outputs (costly: + ~15%) 50 56 ln_cfmeta = .false. ! output additional data to netCDF files required for compliance with the CF metadata standard … … 134 140 ln_humi_rlh = .true. ! humidity specified below in "sn_humi" is relative humidity [%] if .true. 135 141 ! 136 cn_dir = './'! root directory for the bulk data location142 cn_dir = './' ! root directory for the bulk data location 137 143 !___________!_________________________!___________________!___________!_____________!________!___________!______________________________________!__________!_______________! 138 144 ! ! file name ! frequency (hours) ! variable ! time interp.! clim ! 'yearly'/ ! weights filename ! rotation ! land/sea mask ! … … 163 169 ln_read_frq = .false. ! specify whether we must read frq or not 164 170 165 cn_dir = './' 171 cn_dir = './' ! root directory for the ocean data location 166 172 !___________!_________________________!___________________!___________!_____________!________!___________!__________________!__________!_______________! 167 173 ! ! file name ! frequency (hours) ! variable ! time interp.! clim ! 'yearly'/ ! weights filename ! rotation ! land/sea mask ! … … 215 221 &nameos ! ocean Equation Of Seawater (default: NO selection) 216 222 !----------------------------------------------------------------------- 217 ln_eos80 = .true. ! = Use EOS80223 ln_eos80 = .true. ! = Use EOS80 218 224 / 219 225 !!====================================================================== -
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/tests/STATION_ASF/EXPREF/namelist_ecmwf-noskin_cfg
r12939 r13124 29 29 cn_exp = 'STATION_ASF-ECMWF-noskin' ! experience name 30 30 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) 33 35 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) 35 37 ln_rstart = .false. ! start from rest (F) or from a restart file (T) 36 38 ln_1st_euler = .false. ! =T force a start with forward time step (ln_rstart=T) … … 45 47 nn_istate = 0 ! output the initial state (1) or not (0) 46 48 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 !! 49 55 ln_mskland = .false. ! mask land points in NetCDF outputs (costly: + ~15%) 50 56 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 29 29 cn_exp = 'STATION_ASF-ECMWF' ! experience name 30 30 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) 33 35 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) 35 37 ln_rstart = .false. ! start from rest (F) or from a restart file (T) 36 38 ln_1st_euler = .false. ! =T force a start with forward time step (ln_rstart=T) … … 45 47 nn_istate = 0 ! output the initial state (1) or not (0) 46 48 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 !! 49 55 ln_mskland = .false. ! mask land points in NetCDF outputs (costly: + ~15%) 50 56 ln_cfmeta = .false. ! output additional data to netCDF files required for compliance with the CF metadata standard … … 134 140 ln_humi_rlh = .true. ! humidity specified below in "sn_humi" is relative humidity [%] if .true. 135 141 ! 136 cn_dir = './'! root directory for the bulk data location142 cn_dir = './' ! root directory for the bulk data location 137 143 !___________!_________________________!___________________!___________!_____________!________!___________!______________________________________!__________!_______________! 138 144 ! ! file name ! frequency (hours) ! variable ! time interp.! clim ! 'yearly'/ ! weights filename ! rotation ! land/sea mask ! … … 163 169 ln_read_frq = .false. ! specify whether we must read frq or not 164 170 165 cn_dir = './' 171 cn_dir = './' ! root directory for the ocean data location 166 172 !___________!_________________________!___________________!___________!_____________!________!___________!__________________!__________!_______________! 167 173 ! ! file name ! frequency (hours) ! variable ! time interp.! clim ! 'yearly'/ ! weights filename ! rotation ! land/sea mask ! … … 215 221 &nameos ! ocean Equation Of Seawater (default: NO selection) 216 222 !----------------------------------------------------------------------- 217 ln_eos80 = .true. ! = Use EOS80223 ln_eos80 = .true. ! = Use EOS80 218 224 / 219 225 !!====================================================================== -
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/tests/STATION_ASF/EXPREF/namelist_ncar_cfg
r12939 r13124 29 29 cn_exp = 'STATION_ASF-NCAR' ! experience name 30 30 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) 33 35 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) 35 37 ln_rstart = .false. ! start from rest (F) or from a restart file (T) 36 38 ln_1st_euler = .false. ! =T force a start with forward time step (ln_rstart=T) … … 45 47 nn_istate = 0 ! output the initial state (1) or not (0) 46 48 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 !! 49 55 ln_mskland = .false. ! mask land points in NetCDF outputs (costly: + ~15%) 50 56 ln_cfmeta = .false. ! output additional data to netCDF files required for compliance with the CF metadata standard … … 134 140 ln_humi_rlh = .true. ! humidity specified below in "sn_humi" is relative humidity [%] if .true. 135 141 ! 136 cn_dir = './'! root directory for the bulk data location142 cn_dir = './' ! root directory for the bulk data location 137 143 !___________!_________________________!___________________!___________!_____________!________!___________!______________________________________!__________!_______________! 138 144 ! ! file name ! frequency (hours) ! variable ! time interp.! clim ! 'yearly'/ ! weights filename ! rotation ! land/sea mask ! … … 163 169 ln_read_frq = .false. ! specify whether we must read frq or not 164 170 165 cn_dir = './' 171 cn_dir = './' ! root directory for the ocean data location 166 172 !___________!_________________________!___________________!___________!_____________!________!___________!__________________!__________!_______________! 167 173 ! ! file name ! frequency (hours) ! variable ! time interp.! clim ! 'yearly'/ ! weights filename ! rotation ! land/sea mask ! … … 215 221 &nameos ! ocean Equation Of Seawater (default: NO selection) 216 222 !----------------------------------------------------------------------- 217 ln_eos80 = .true. ! = Use EOS80223 ln_eos80 = .true. ! = Use EOS80 218 224 / 219 225 !!====================================================================== -
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/tests/STATION_ASF/MY_SRC/stpctl.F90
r13015 r13124 179 179 ! 180 180 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 182 184 ELSE ! only mpi subdomains with errors are here -> STOP now 183 185 CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 184 186 ENDIF 185 187 ! 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 189 193 ENDIF 190 194 !
Note: See TracChangeset
for help on using the changeset viewer.