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.
#632 (weekly forcing files (Mercator contribution for 2009)) – NEMO

Opened 14 years ago

Closed 13 years ago

Last modified 2 years ago

#632 closed Enhancement (fixed)

weekly forcing files (Mercator contribution for 2009)

Reported by: cbricaud Owned by: cbricaud
Priority: low Milestone:
Component: OCE Version: v3.3
Severity: Keywords: 2010 OPA v3.3
Cc:

Description

modifiactions in daymod.F90 and fldread.F90 to read weekly forcing files with fldread.F90.
NVTK is ok.
I didn't see any paragraph in the documentation that correspnds to forcing files reading.

===================================================================
--- daymod.F90 (revision 1793)
+++ daymod.F90 (working copy)
@@ -40,6 +40,12 @@

PUBLIC day_init ! called by istate.F90


INTEGER
nsecd, nsecd05, ndt, ndt05
+ INTEGER , PUBLIC :: njuloffset !:
+ REAL(wp), PUBLIC :: fjulstartyear !: firt day of the current year in julian days
+ REAL(wp), PUBLIC :: fjulstartweek !: firt day of the current week in julian days
+ INTEGER , PUBLIC :: nsec_week !: current time step counted in second since 00h 1st day of the current week
+ CHARACTER(len=12),PARAMETER :: cfirstdayweek = 'thursday'
+ CHARACTER(len=15),DIMENSION(7) :: cl_week

!!----------------------------------------------------------------------
!! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)

@@ -66,6 +72,7 @@

!! - nsec1jan000 : second since Jan. 1st 00h of nit000 year and Jan. 1st 00h of the current year
!! - nmonth_len, nyear_len, nmonth_half, nmonth_end through day_mth
!!----------------------------------------------------------------------

+ REAL(wp):: rjulstartweek !: firt day of the current week in julian days

! all calendar staff is based on the fact that MOD( rday, rdttra(1) ) == 0
IF( MOD( rday , rdttra(1) ) /= 0. ) CALL ctl_stop( 'the time step must devide the number of second of in a day' )

@@ -84,8 +91,19 @@

nmonth = ( ndastp - (nyear * 10000) ) / 100
nday = ndastp - (nyear * 10000) - ( nmonth * 100 )


  • CALL ymds2ju( nyear, nmonth, nday, 0.0, fjulday ) ! we assume that we start run at 00:00
  • IF( ABS(fjulday - REAL(NINT(fjulday),wp)) < 0.1 / rday ) fjulday = REAL(NINT(fjulday),wp) ! avoid truncation error

+ !compute njuloffset: it is the julian day that corresponds to the first day of the first week in the calendar
+ IF( nleapy == 0 )THEN ; cl_week=(/"wednesday","thursday ","friday ","saturday ","sunday ","monday ","tuesday "/)
+ ELSE ; cl_week=(/"thursday ","friday ","saturday ","sunday ","monday ","tuesday ","wednesday"/)
+ ENDIF
+ DO njuloffset=1,7
+ IF( cl_week(njuloffset)==cfirstdayweek ) EXIT
+ ENDDO
+ IF( njuloffset .GT. 7 ) CALL ctl_stop( 'day_init: weekly file: wrong day for cfirstdayweek: ',TRIM(cfirstdayweek) )
+ njuloffset=njuloffset-1
+ CALL ymds2ju( nyear, nmonth, nday, 0.0, fjulday ) ! we assume that we start run at 00:00
+ IF( ABS(fjulday - REAL(NINT(fjulday),wp)) < 0.1 / rday ) fjulday = REAL(NINT(fjulday),wp) ! avoid truncation error
+ rjulstartweek=INT( (fjulday-njuloffset)/7 )*7 + njuloffset !compute fjulstart for nsec_week
+

fjulday = fjulday + 1. ! move back to the day at nit000 (and not at nit000 - 1)


nsec1jan000 = 0

@@ -108,6 +126,7 @@

! number of seconds since the beginning of current year/month at the middle of the time-step
nsec_year = nday_year * nsecd - ndt05 ! 1 time step before the middle of the first time step
nsec_month = nday * nsecd - ndt05 ! because day will be called at the beginning of step

+ nsec_week = REAL( fjulday - rjulstartweek ) *rday - 0.5 * rdttra(1)

nsec_day = nsecd - ndt05


! control print

@@ -194,11 +213,13 @@

!

CHARACTER (len=25)
charout
REAL(wp)
zprec ! fraction of day corresponding to 0.1 second

+ REAL(wp) :: rsec !temp variable

!!----------------------------------------------------------------------
zprec = 0.1 / rday
! ! New time-step
nsec_year = nsec_year + ndt
nsec_month = nsec_month + ndt

+ nsec_week = nsec_week + ndt

nsec_day = nsec_day + ndt
adatrj = adatrj + rdttra(1) / rday
fjulday = fjulday + rdttra(1) / rday

@@ -211,6 +232,7 @@

nday_year = nday_year + 1
nsec_day = ndt05
!

+ IF(nsec_week > 86400*7)nsec_week=0.5 * ndt

IF( nday == nmonth_len(nmonth) + 1 ) THEN ! NEW month

nday = 1
nmonth = nmonth + 1

@@ -227,10 +249,15 @@

!
ndastp = nyear * 10000 + nmonth * 100 + nday ! NEW date
!

+ !compute first day of the year in julian days
+ CALL ymds2ju( nyear, 01, 01, 0.0, fjulstartyear )
+ !compute first day of the week in julian days
+ fjulstartweek=INT( (fjulday-njuloffset)/7 )*7 + njuloffset !compute fjulstartweek
+

IF(lwp) WRITE(numout,'(a,i8,a,i4.4,a,i2.2,a,i2.2,a,i3.3)') '======>> time-step =', kt, &

& ' New day, DATE Y/M/D = ', nyear, '/', nmonth, '/', nday, ' nday_year = ', nday_year

  • IF(lwp) WRITE(numout,'(a,i8,a,i7,a,i5)') ' nsec_year = ', nsec_year, &
  • & ' nsec_month = ', nsec_month, ' nsec_day = ', nsec_day

+ IF(lwp) WRITE(numout,'(a,i8,a,i7,a,i7,a,i5)') ' nsec_year = ', nsec_year, &
+ & ' nsec_month = ', nsec_month, ' nsec_week = ', nsec_week, ' nsec_day = ', nsec_day

ENDIF


IF(ln_ctl) THEN

Index: fldread.F90
===================================================================
--- fldread.F90 (revision 1793)
+++ fldread.F90 (working copy)
@@ -14,6 +14,8 @@

!!----------------------------------------------------------------------
USE oce ! ocean dynamics and tracers
USE dom_oce ! ocean space and time domain

+ USE daymod ! calendar
+ USE ioipsl, ONLY : ymds2ju, ju2ymds ! for calendar

USE phycst ! ???
USE in_out_manager ! I/O manager
USE iom ! I/O manager library

@@ -159,6 +161,7 @@

IF( sd(jf)%nfreqh == -1 ) THEN ; ireclast = 12
ELSE

IF( sd(jf)%cltype == 'monthly' ) THEN ; ireclast = 24 * nmonth_len(nmonth) / sd(jf)%nfreqh

+ ELSEIF( sd(jf)%cltype == 'weekly' ) THEN ; ireclast = 24.* REAL( 7, wp ) / sd(jf)%nfreqh

ELSEIF( sd(jf)%cltype == 'daily' ) THEN ; ireclast = 24 / sd(jf)%nfreqh
ELSE ; ireclast = 24 * nyear_len( 1 ) / sd(jf)%nfreqh
ENDIF

@@ -314,6 +317,7 @@

!!

LOGICAL
llprevyr ! are we reading previous year file?
LOGICAL
llprevmth ! are we reading previous month file?

+ LOGICAL :: llprevweek ! are we reading previous week file?

LOGICAL
llprevday ! are we reading previous day file?
LOGICAL
llprev ! llprevyr .OR. llprevmth .OR. llprevday
INTEGER
idvar ! variable id
@@ -327,6 +331,7 @@

IF( sdjf%ln_clim ) sdjf%clname = TRIM( sdjf%clrootname ) ! file name defaut definition, never change in this case
llprevyr = .FALSE.
llprevmth = .FALSE.

+ llprevweek = .FALSE.

llprevday = .FALSE.


! define record informations

@@ -349,6 +354,11 @@

sdjf%nrec_b(1) = 24 * nmonth_len(nmonth-1) / sdjf%nfreqh ! last record of previous month
llprevmth = .NOT. sdjf%ln_clim ! use previous month file?
llprevyr = llprevmth .AND. nmonth == 1 ! use previous year file?

+ ELSE IF ( sdjf%cltype == 'weekly' ) THEN !weekly file
+ sdjf%nrec_b(1) = 24. / sdjf%nfreqh * REAL( 7, wp ) ! last record of previous week
+ llprevweek = .NOT. sdjf%ln_clim ! use previous week file?
+ llprevmth = .NOT. sdjf%ln_clim .AND. nday == 1 ! use previous month file?
+ llprevyr = .NOT. sdjf%ln_clim .AND. nmonth == 1 ! use previous year file?

ELSEIF( sdjf%cltype == 'daily' ) THEN ! daily file

sdjf%nrec_b(1) = 24 / sdjf%nfreqh ! last record of previous day
llprevday = .NOT. sdjf%ln_clim ! use previous day file?

@@ -360,7 +370,7 @@

ENDIF

ENDIF

ENDIF

  • llprev = llprevyr .OR. llprevmth .OR. llprevday

+ llprev = llprevyr .OR. llprevmth .OR. llprevweek .OR. llprevday

CALL fld_clopn( sdjf, nyear - COUNT((/llprevyr /)) , &

& nmonth - COUNT((/llprevmth/)) + 12 * COUNT((/llprevyr /)), &

@@ -454,6 +464,7 @@

ifreq_sec = sdjf%nfreqh * 3600 ! frequency mean (in seconds)
! number of second since the beginning of the file
IF( sdjf%cltype == 'monthly' ) THEN ; ztmp = REAL(nsec_month,wp) ! since 00h on the 1st day of the current month

+ ELSEIF( sdjf%cltype == 'weekly' ) THEN ; ztmp = REAL(nsec_week ,wp) ! since the first day of the current week

ELSEIF( sdjf%cltype == 'daily' ) THEN ; ztmp = REAL(nsec_day ,wp) ! since 00h of the current day
ELSE ; ztmp = REAL(nsec_year ,wp) ! since 00h on Jan 1 of the current year
ENDIF

@@ -493,6 +504,8 @@

sdjf%nrec_a(:) = (/ irec, ifreq_sec * irec - ifreq_sec / 2 + nsec1jan000 /)
IF( sdjf%cltype == 'monthly' ) & ! add the number of seconds between 00h Jan 1 and the end of previous month

sdjf%nrec_a(2) = sdjf%nrec_a(2) + isecd * SUM(nmonth_len(1:nmonth -1)) ! ok if nmonth=1

+ IF( sdjf%cltype == 'weekly' ) & ! add the number of seconds between 00h Jan 1 and the end of previous week
+ sdjf%nrec_a(2) = sdjf%nrec_a(2) + rday * ( fjulstartweek-fjulstartyear )

IF( sdjf%cltype == 'daily' ) & ! add the number of seconds between 00h Jan 1 and the end of previous day

sdjf%nrec_a(2) = sdjf%nrec_a(2) + isecd * ( nday_year - 1 )


@@ -501,6 +514,8 @@

sdjf%nrec_b(:) = (/ irec, ifreq_sec * irec - ifreq_sec / 2 + nsec1jan000 /)
IF( sdjf%cltype == 'monthly' ) & ! add the number of seconds between 00h Jan 1 and the end of previous month

sdjf%nrec_b(2) = sdjf%nrec_b(2) + isecd * SUM(nmonth_len(1:nmonth -1)) ! ok if nmonth=1

+ IF( sdjf%cltype == 'weekly' ) & ! add the number of seconds between 00h Jan 1 and the end of previous week
+ sdjf%nrec_b(2) = sdjf%nrec_b(2) + rday * ( fjulstartweek-fjulstartyear )

IF( sdjf%cltype == 'daily' ) & ! add the number of seconds between 00h Jan 1 and the end of previous day

sdjf%nrec_b(2) = sdjf%nrec_b(2) + isecd * ( nday_year - 1 )


@@ -522,17 +537,36 @@

!!
!! Method :
!!----------------------------------------------------------------------

  • TYPE(FLD), INTENT(inout) :: sdjf ! input field related variables
  • INTEGER , INTENT(in ) :: kyear ! year value
  • INTEGER , INTENT(in ) :: kmonth ! month value
  • INTEGER , INTENT(in ) :: kday ! day value
  • LOGICAL , INTENT(in ), OPTIONAL :: ldstop ! stop if open to read a non-existing file (default = .TRUE.)

+ TYPE(FLD), INTENT(inout) :: sdjf ! input field related variables
+ INTEGER , INTENT(in ) :: kyear ! year value
+ INTEGER , INTENT(in ) :: kmonth ! month value
+ INTEGER , INTENT(in ) :: kday ! day value
+ LOGICAL , INTENT(in ), OPTIONAL :: ldstop ! stop if open to read a non-existing file (default = .TRUE.)
+ INTEGER :: nystart, nmstart, ndstart ! firt day of the current week in yyyy mm dd
+ INTEGER :: nyend, nmend, ndend ! last day of the current week in yyyy mm dd
+ REAL(wp) :: rjulstartweek ! firt day of the current week in julian days
+ REAL(wp) :: rjulendweek ! last day of the current week in julian days
+ REAL(wp) :: rsec, rjul !temp variable

IF( sdjf%num /= 0 ) CALL iom_close( sdjf%num ) ! close file if already open
! build the new filename if not climatological data

  • IF( .NOT. sdjf%ln_clim ) THEN ; WRITE(sdjf%clname, '(a,"_y",i4.4)' ) TRIM( sdjf%clrootname ), kyear ! add year
  • IF( sdjf%cltype /= 'yearly' ) WRITE(sdjf%clname, '(a,"m" ,i2.2)' ) TRIM( sdjf%clname ), kmonth ! add month
  • IF( sdjf%cltype == 'daily' ) WRITE(sdjf%clname, '(a,"d" ,i2.2)' ) TRIM( sdjf%clname ), kday ! add day

+ sdjf%clname=TRIM(sdjf%clrootname)
+ IF( .NOT. sdjf%ln_clim ) THEN
+ IF( sdjf%cltype /= 'weekly' )THEN
+ WRITE(sdjf%clname, '(a,"_y",i4.4)' ) TRIM( sdjf%clrootname ), kyear ! add year
+ IF( sdjf%cltype /= 'yearly' ) WRITE(sdjf%clname, '(a,"m" ,i2.2)' ) TRIM( sdjf%clname ), kmonth ! add month
+ IF( sdjf%cltype == 'daily' ) WRITE(sdjf%clname, '(a,"d" ,i2.2)' ) TRIM( sdjf%clname ), kday ! add day
+ ELSE
+ CALL ymds2ju( kyear, kmonth, kday, 0.0 , rjul )
+ rjulstartweek=INT( (rjul-njuloffset)/7 )*7 + njuloffset !compute rjulstartweek
+ CALL ju2ymds(rjulstartweek,nystart,nmstart,ndstart,rsec)
+ rjulendweek = rjulstartweek + 6 !compute rjulendweek
+ CALL ju2ymds(rjulendweek,nyend,nmend,ndend,rsec)
+ ! add first day of the week
+ WRITE(sdjf%clname, '(a,"_y",i4.4,"m",i2.2,"d",i2.2)' ) TRIM( sdjf%clname ), nystart, nmstart, ndstart
+ ! add last day of the week
+ WRITE(sdjf%clname, '(a,"_y",i4.4,"m",i2.2,"d",i2.2)' ) TRIM( sdjf%clname ), nyend , nmend , ndend
+ ENDIF

ENDIF
CALL iom_open( sdjf%clname, sdjf%num, ldstop = ldstop, ldiof = LEN(TRIM(sdjf%wgtname)) > 0 )
!

############################

EXPERIENCE NAME: 2TEST
############################


#################################################
FILES STORED UNDER NVTK/2TEST DIRECTORY & TESTED
#################################################


  • daymod.F90
  • fldread.F90


#################################################
CPP KEYS USED FOR 2TEST EXPERIENCE
#################################################


  • key_zco
  • key_gyre
  • key_dynspg_flt
  • key_ldfslp
  • key_zdftke
  • key_vectopt_loop
  • key_vectopt_memory


#############################
NEMO MPI DECOMPOSITION USED
#############################


jpni = 2 ; jpnj = 4 ; jpnij = 8


#############################
NEMO SOURCE FILES INFORMATION
#############################


NEMO downloaded from server:
NEMO revision :


############################
CHECK EXECUTABLE MEMORY SIZE
############################


List memory_size.txt files and check date creation:
-rw-r--r-- 1 smer860 113 2010-01-07 14:56 mon/LONG/2TEST/memory_size.txt
-rw-r--r-- 1 smer860 113 2010-01-07 14:56 mon/LONG/nemo_v3/memory_size.txt
-rw-r--r-- 1 smer860 18377 2010-01-07 14:56 mon/LONG/2TEST/monGYREO_err

  • file mon/LONG/nemo_v3/monGYREO_err doesn't exist


Memory Current version

Stack (Mo) : 150.9
Static (Mo) : 150.9
Max. used (Mo) : 1472.0
Max. used (Mo) : 1.1


######################
CHECK REPRODUCTIBILITY
######################



---> Ocean Reproductibility mon .vs. mpi ? :

-------------------------------------------
List solver.stat files and check date creation: Num. time steps: done / expected
-rw-r--r-- 1 smer860 22320 2010-01-07 14:56 mon/LONG/2TEST/solver.stat 0360 / 0360
-rw-r--r-- 1 smer860 22320 2010-01-07 14:56 mpi/LONG/2TEST/solver.stat 0360 / 0360


YES YES YES YES YES YES YES YES for the current version



####################
CHECK RESTARTABILITY
####################



---> mon ocean restartability ? :

--------------------------------
List solver.stat files and check date creation: Num. time steps: done / expected
-rw-r--r-- 1 smer860 11160 2010-01-07 14:56 mon/1_SHORT/2TEST/solver.stat 0180 / 0180
-rw-r--r-- 1 smer860 11160 2010-01-07 15:04 mon/2_SHORT/2TEST/solver.stat 0360 / 0360


YES YES YES YES YES YES YES YES for the current version i.e. LONG stream = ( 1_SHORT + 2_SHORT ) streams



---> mpi ocean restartability ? :

--------------------------------
List solver.stat files and check date creation: Num. time steps: done / expected
-rw-r--r-- 1 smer860 11160 2010-01-07 14:56 mpi/1_SHORT/2TEST/solver.stat 0180 / 0180
-rw-r--r-- 1 smer860 11160 2010-01-07 15:04 mpi/2_SHORT/2TEST/solver.stat 0360 / 0360


YES YES YES YES YES YES YES YES for the current version i.e. LONG stream = ( 1_SHORT + 2_SHORT ) streams



####################################################
COMPARE CURRENT VERSION RESULTS TO THE nemo_v3 ONES
####################################################


-----------------------------------------------------------------------------
---> mon results : current version | nemo_v3 version STREAM 1 & 2

solver.stat .vs. solver.stat
ocean.output .vs. ocean.output


STREAM 1 results :
-----------------
List solver.stat files and check date creation:
-rw-r--r-- 1 smer860 11160 2010-01-07 14:56 mon/1_SHORT/2TEST/solver.stat
-rw-r--r-- 1 smer860 11160 2010-01-07 14:56 mon/1_SHORT/nemo_v3/solver.stat


STREAM_1 solver.stat IS IDENTICAL to the version nemo_v3 one


List ocean.output files and check date creation:
-rw-r--r-- 1 smer860 44654 2010-01-07 14:56 mon/1_SHORT/2TEST/ocean.output
-rw-r--r-- 1 smer860 44324 2010-01-07 14:56 mon/1_SHORT/nemo_v3/ocean.output


STREAM_1 ocean.output is NOT identical to the version nemo_v3 one

See ./infos/inter/cvref_ocean_STREAM_1_mon_2TEST.txt file for full difference


Make difference between ocean.output files

STREAM_1 mon run

Current run nemo_v3 run
----------- --------------


nsec_year = 3600 nsec_month = 3600 nsec_w | nsec_year = 3600 nsec_month = 3600 nsec_d
nsec_year = 90000 nsec_month = 90000 nsec_w | nsec_year = 90000 nsec_month = 90000 nsec_d
nsec_year = 176400 nsec_month = 176400 nsec_w | nsec_year = 176400 nsec_month = 176400 nsec_d
nsec_year = 262800 nsec_month = 262800 nsec_w | nsec_year = 262800 nsec_month = 262800 nsec_d
nsec_year = 349200 nsec_month = 349200 nsec_w | nsec_year = 349200 nsec_month = 349200 nsec_d
nsec_year = 435600 nsec_month = 435600 nsec_w | nsec_year = 435600 nsec_month = 435600 nsec_d
nsec_year = 522000 nsec_month = 522000 nsec_w | nsec_year = 522000 nsec_month = 522000 nsec_d
nsec_year = 608400 nsec_month = 608400 nsec_w | nsec_year = 608400 nsec_month = 608400 nsec_d
nsec_year = 694800 nsec_month = 694800 nsec_w | nsec_year = 694800 nsec_month = 694800 nsec_d
nsec_year = 781200 nsec_month = 781200 nsec_w | nsec_year = 781200 nsec_month = 781200 nsec_d
nsec_year = 867600 nsec_month = 867600 nsec_w | nsec_year = 867600 nsec_month = 867600 nsec_d
nsec_year = 954000 nsec_month = 954000 nsec_w | nsec_year = 954000 nsec_month = 954000 nsec_d
nsec_year = 1040400 nsec_month = 1040400 nsec_w | nsec_year = 1040400 nsec_month = 1040400 nsec_d
nsec_year = 1126800 nsec_month = 1126800 nsec_w | nsec_year = 1126800 nsec_month = 1126800 nsec_d
nsec_year = 1213200 nsec_month = 1213200 nsec_w | nsec_year = 1213200 nsec_month = 1213200 nsec_d




STREAM 2 results :
-----------------
List solver.stat files and check date creation:
-rw-r--r-- 1 smer860 11160 2010-01-07 15:04 mon/2_SHORT/2TEST/solver.stat
-rw-r--r-- 1 smer860 11160 2010-01-07 15:04 mon/2_SHORT/nemo_v3/solver.stat


STREAM_2 solver.stat IS IDENTICAL to the version nemo_v3 one


List ocean.output files and check date creation:
-rw-r--r-- 1 smer860 43292 2010-01-07 15:04 mon/2_SHORT/2TEST/ocean.output
-rw-r--r-- 1 smer860 42962 2010-01-07 15:04 mon/2_SHORT/nemo_v3/ocean.output


STREAM_2 ocean.output is NOT identical to the version nemo_v3 one

See ./infos/inter/cvref_ocean_STREAM_2_mon_2TEST.txt file for full difference


Make difference between ocean.output files

STREAM_2 mon run

Current run nemo_v3 run
----------- --------------


nsec_year = 1299600 nsec_month = 1299600 nsec_w | nsec_year = 1299600 nsec_month = 1299600 nsec_d
nsec_year = 1386000 nsec_month = 1386000 nsec_w | nsec_year = 1386000 nsec_month = 1386000 nsec_d
nsec_year = 1472400 nsec_month = 1472400 nsec_w | nsec_year = 1472400 nsec_month = 1472400 nsec_d
nsec_year = 1558800 nsec_month = 1558800 nsec_w | nsec_year = 1558800 nsec_month = 1558800 nsec_d
nsec_year = 1645200 nsec_month = 1645200 nsec_w | nsec_year = 1645200 nsec_month = 1645200 nsec_d
nsec_year = 1731600 nsec_month = 1731600 nsec_w | nsec_year = 1731600 nsec_month = 1731600 nsec_d
nsec_year = 1818000 nsec_month = 1818000 nsec_w | nsec_year = 1818000 nsec_month = 1818000 nsec_d
nsec_year = 1904400 nsec_month = 1904400 nsec_w | nsec_year = 1904400 nsec_month = 1904400 nsec_d
nsec_year = 1990800 nsec_month = 1990800 nsec_w | nsec_year = 1990800 nsec_month = 1990800 nsec_d
nsec_year = 2077200 nsec_month = 2077200 nsec_w | nsec_year = 2077200 nsec_month = 2077200 nsec_d
nsec_year = 2163600 nsec_month = 2163600 nsec_w | nsec_year = 2163600 nsec_month = 2163600 nsec_d
nsec_year = 2250000 nsec_month = 2250000 nsec_w | nsec_year = 2250000 nsec_month = 2250000 nsec_d
nsec_year = 2336400 nsec_month = 2336400 nsec_w | nsec_year = 2336400 nsec_month = 2336400 nsec_d
nsec_year = 2422800 nsec_month = 2422800 nsec_w | nsec_year = 2422800 nsec_month = 2422800 nsec_d
nsec_year = 2509200 nsec_month = 2509200 nsec_w | nsec_year = 2509200 nsec_month = 2509200 nsec_d



-----------------------------------------------------------------------------
---> mpi results : current version | nemo_v3 version STREAM 1 & 2

solver.stat .vs. solver.stat
ocean.output .vs. ocean.output


STREAM 1 results :
-----------------
List solver.stat files and check date creation:
-rw-r--r-- 1 smer860 11160 2010-01-07 14:56 mpi/1_SHORT/2TEST/solver.stat
-rw-r--r-- 1 smer860 11160 2010-01-07 14:56 mpi/1_SHORT/nemo_v3/solver.stat


STREAM_1 solver.stat IS IDENTICAL to the version nemo_v3 one


List ocean.output files and check date creation:
-rw-r--r-- 1 smer860 46271 2010-01-07 14:56 mpi/1_SHORT/2TEST/ocean.output
-rw-r--r-- 1 smer860 45941 2010-01-07 14:56 mpi/1_SHORT/nemo_v3/ocean.output


STREAM_1 ocean.output is NOT identical to the version nemo_v3 one

See ./infos/inter/cvref_ocean_STREAM_1_mpi_2TEST.txt file for full difference


Make difference between ocean.output files

STREAM_1 mpi run

Current run nemo_v3 run
----------- --------------


nsec_year = 3600 nsec_month = 3600 nsec_w | nsec_year = 3600 nsec_month = 3600 nsec_d
nsec_year = 90000 nsec_month = 90000 nsec_w | nsec_year = 90000 nsec_month = 90000 nsec_d
nsec_year = 176400 nsec_month = 176400 nsec_w | nsec_year = 176400 nsec_month = 176400 nsec_d
nsec_year = 262800 nsec_month = 262800 nsec_w | nsec_year = 262800 nsec_month = 262800 nsec_d
nsec_year = 349200 nsec_month = 349200 nsec_w | nsec_year = 349200 nsec_month = 349200 nsec_d
nsec_year = 435600 nsec_month = 435600 nsec_w | nsec_year = 435600 nsec_month = 435600 nsec_d
nsec_year = 522000 nsec_month = 522000 nsec_w | nsec_year = 522000 nsec_month = 522000 nsec_d
nsec_year = 608400 nsec_month = 608400 nsec_w | nsec_year = 608400 nsec_month = 608400 nsec_d
nsec_year = 694800 nsec_month = 694800 nsec_w | nsec_year = 694800 nsec_month = 694800 nsec_d
nsec_year = 781200 nsec_month = 781200 nsec_w | nsec_year = 781200 nsec_month = 781200 nsec_d
nsec_year = 867600 nsec_month = 867600 nsec_w | nsec_year = 867600 nsec_month = 867600 nsec_d
nsec_year = 954000 nsec_month = 954000 nsec_w | nsec_year = 954000 nsec_month = 954000 nsec_d
nsec_year = 1040400 nsec_month = 1040400 nsec_w | nsec_year = 1040400 nsec_month = 1040400 nsec_d
nsec_year = 1126800 nsec_month = 1126800 nsec_w | nsec_year = 1126800 nsec_month = 1126800 nsec_d
nsec_year = 1213200 nsec_month = 1213200 nsec_w | nsec_year = 1213200 nsec_month = 1213200 nsec_d




STREAM 2 results :
-----------------
List solver.stat files and check date creation:
-rw-r--r-- 1 smer860 11160 2010-01-07 15:04 mpi/2_SHORT/2TEST/solver.stat
-rw-r--r-- 1 smer860 11160 2010-01-07 15:05 mpi/2_SHORT/nemo_v3/solver.stat


STREAM_2 solver.stat IS IDENTICAL to the version nemo_v3 one


List ocean.output files and check date creation:
-rw-r--r-- 1 smer860 45523 2010-01-07 15:04 mpi/2_SHORT/2TEST/ocean.output
-rw-r--r-- 1 smer860 45193 2010-01-07 15:05 mpi/2_SHORT/nemo_v3/ocean.output


STREAM_2 ocean.output is NOT identical to the version nemo_v3 one

See ./infos/inter/cvref_ocean_STREAM_2_mpi_2TEST.txt file for full difference


Make difference between ocean.output files

STREAM_2 mpi run

Current run nemo_v3 run
----------- --------------


nsec_year = 1299600 nsec_month = 1299600 nsec_w | nsec_year = 1299600 nsec_month = 1299600 nsec_d
nsec_year = 1386000 nsec_month = 1386000 nsec_w | nsec_year = 1386000 nsec_month = 1386000 nsec_d
nsec_year = 1472400 nsec_month = 1472400 nsec_w | nsec_year = 1472400 nsec_month = 1472400 nsec_d
nsec_year = 1558800 nsec_month = 1558800 nsec_w | nsec_year = 1558800 nsec_month = 1558800 nsec_d
nsec_year = 1645200 nsec_month = 1645200 nsec_w | nsec_year = 1645200 nsec_month = 1645200 nsec_d
nsec_year = 1731600 nsec_month = 1731600 nsec_w | nsec_year = 1731600 nsec_month = 1731600 nsec_d
nsec_year = 1818000 nsec_month = 1818000 nsec_w | nsec_year = 1818000 nsec_month = 1818000 nsec_d
nsec_year = 1904400 nsec_month = 1904400 nsec_w | nsec_year = 1904400 nsec_month = 1904400 nsec_d
nsec_year = 1990800 nsec_month = 1990800 nsec_w | nsec_year = 1990800 nsec_month = 1990800 nsec_d
nsec_year = 2077200 nsec_month = 2077200 nsec_w | nsec_year = 2077200 nsec_month = 2077200 nsec_d
nsec_year = 2163600 nsec_month = 2163600 nsec_w | nsec_year = 2163600 nsec_month = 2163600 nsec_d
nsec_year = 2250000 nsec_month = 2250000 nsec_w | nsec_year = 2250000 nsec_month = 2250000 nsec_d
nsec_year = 2336400 nsec_month = 2336400 nsec_w | nsec_year = 2336400 nsec_month = 2336400 nsec_d
nsec_year = 2422800 nsec_month = 2422800 nsec_w | nsec_year = 2422800 nsec_month = 2422800 nsec_d
nsec_year = 2509200 nsec_month = 2509200 nsec_w | nsec_year = 2509200 nsec_month = 2509200 nsec_d

Commit History (0)

(No commits)

Attachments (5)

daymod.F90_new (18.2 KB) - added by cbricaud 14 years ago.
fldread.F90_new (54.7 KB) - added by cbricaud 14 years ago.
WEEK_FORC_FILES.tar (150.0 KB) - added by cbricaud 14 years ago.
WEEK_FORC_FILES.2.tar (100.0 KB) - added by cbricaud 14 years ago.
WEEK_FORC_FILES3.tar (100.0 KB) - added by cbricaud 14 years ago.

Download all attachments as: .zip

Change History (19)

Changed 14 years ago by cbricaud

Changed 14 years ago by cbricaud

Changed 14 years ago by cbricaud

comment:1 Changed 14 years ago by cbricaud

this is the new version, as seen with Sebastien.

Changed 14 years ago by cbricaud

Changed 14 years ago by cbricaud

comment:2 Changed 14 years ago by cbricaud

  • Milestone set to 2010 Stream 3: Developments & Implementation of new features
  • Owner changed from NEMO team to cbricaud

here it is a new version. nvtk is ok.

comment:3 Changed 13 years ago by cbricaud

  • Resolution set to fixed
  • Status changed from new to closed
  • Version changed from v3.2 to v3.3

comment:4 Changed 8 years ago by nicolasmartin

  • Keywords 2010 3: Developments Implementation Stream features new of added

comment:5 Changed 8 years ago by nicolasmartin

  • Keywords 3: removed

comment:6 Changed 8 years ago by nicolasmartin

  • Keywords developments added; Developments removed

comment:7 Changed 8 years ago by nicolasmartin

  • Keywords of removed

comment:8 Changed 8 years ago by nicolasmartin

  • Keywords nemo_v3_3* added

comment:9 Changed 8 years ago by nicolasmartin

  • Keywords nemo_v3_3_beta added; Implementation Stream developments features removed

comment:10 Changed 8 years ago by nicolasmartin

  • Keywords new removed

comment:11 Changed 8 years ago by nicolasmartin

  • Milestone 2010 Stream 3: Developments & Implementation of new features deleted

Milestone 2010 Stream 3: Developments & Implementation of new features deleted

comment:12 Changed 8 years ago by nicolasmartin

  • Keywords nemo_v3_3_beta removed

comment:13 Changed 6 years ago by nemo

  • Keywords nemo_v3_3* removed

comment:14 Changed 2 years ago by nemo

  • Keywords OPA v3.3 added
Note: See TracTickets for help on using tickets.