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 1713 – NEMO

Changeset 1713


Ignore:
Timestamp:
2009-11-05T14:49:10+01:00 (14 years ago)
Author:
smasson
Message:

suppress nbiss and nobis, see ticket:589

Location:
trunk/NEMO
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OFF_SRC/daymod.F90

    r1450 r1713  
    5656   REAL(wp), PUBLIC, DIMENSION(0:13) ::   rmonth_end   !: second since the beginning of the year and the end of the months 
    5757   REAL(wp), PUBLIC                  ::   sec1jan000   !: second since Jan. 1st 00h of nit000 year and Jan. 1st 00h of the current year 
    58  
    59    ! this two variables are wrong DO NOT USE THEM !!! 
    60    INTEGER, PUBLIC, DIMENSION(12) ::   nbiss = (/ 31, 29, 31, 30, 31, 30,    &  !: number of days per month 
    61       &                                           31, 31, 30, 31, 30, 31 /)     !: (leap-year) 
    62    INTEGER, PUBLIC, DIMENSION(12) ::   nobis = (/ 31, 28, 31, 30, 31, 30,    &  !: number of days per month 
    63       &                                           31, 31, 30, 31, 30, 31 /)     !: (365 days a year) 
    64  
    6558 
    6659   !!---------------------------------------------------------------------- 
  • trunk/NEMO/OPA_SRC/BDY/bdydta.F90

    r1241 r1713  
    107107      iman = INT( raamo )      ! Number of months in a year 
    108108 
    109       i15 = INT( 2*FLOAT( nday ) / ( FLOAT( nobis(nmonth) ) + 0.5 ) ) 
     109      i15 = INT( 2*REAL( nday, wp ) / ( REAL( nmonth_len(nmonth), wp ) + 0.5 ) ) 
    110110      ! i15=0 if the current day is in the first half of the month, else i15=1 
    111111 
     
    140140            IF(lwp) WRITE(numout,*) '          Bdy data are read in netcdf files' 
    141141            ! 
    142             dayfrac = adatrj  - FLOAT( itimer ) / 86400.   ! day fraction at time step kt-1 
    143             dayfrac = dayfrac - INT  ( dayfrac )           ! 
    144             totime  = ( nitend - nit000 + 1 ) * rdt        ! Total time of the run to verify that all the 
    145             !                                              ! necessary time dumps in file are included 
     142            dayfrac = adatrj  - REAL( itimer, wp ) / 86400.   ! day fraction at time step kt-1 
     143            dayfrac = dayfrac - INT ( dayfrac )               ! 
     144            totime  = ( nitend - nit000 + 1 ) * rdt           ! Total time of the run to verify that all the 
     145            !                                                 ! necessary time dumps in file are included 
    146146            ! 
    147147            clfile(1) = filbdy_data_T 
     
    178178               ! Convert time origin in file to julian days  
    179179               isec0 = isec0 + ihours0*60.*60. + iminutes0*60. 
    180                CALL ymds2ju(iyear0, imonth0, iday0, real(isec0), dayjul0) 
     180               CALL ymds2ju(iyear0, imonth0, iday0, REAL(isec0, wp), dayjul0) 
    181181               ! Compute model initialization time  
    182182               iyear  = ndastp / 10000 
     
    184184               iday   = ndastp - iyear * 10000 - imonth * 100 
    185185               isecs  = dayfrac * 86400 
    186                CALL ymds2ju(iyear, imonth, iday, real(isecs) , zdayjulini) 
     186               CALL ymds2ju(iyear, imonth, iday, REAL(isecs, wp) , zdayjulini) 
    187187               ! offset from initialization date: 
    188188               zoffset = (dayjul0-zdayjulini)*86400 
     
    560560       ! ******************** 
    561561       !  
    562        IF( ln_bdy_clim ) THEN   ;   zxy = FLOAT( nday                  ) / FLOAT( nobis(nbdy_b) ) + 0.5 - i15 
    563        ELSE                     ;   zxy = FLOAT( istep(nbdy_b) - itimer ) / FLOAT( istep(nbdy_b) - istep(nbdy_a) ) 
     562       IF( ln_bdy_clim ) THEN   ;   zxy = REAL( nday                  , wp ) / REAL( nmonth_len(nbdy_b), wp ) + 0.5 - i15 
     563       ELSE                     ;   zxy = REAL( istep(nbdy_b) - itimer, wp ) / REAL( istep(nbdy_b) - istep(nbdy_a), wp ) 
    564564       END IF 
    565565 
     
    660660      iman  = INT( raamo ) ! Number of months in a year 
    661661 
    662       i15 = INT( 2*FLOAT( nday ) / ( FLOAT( nobis(nmonth) ) + 0.5 ) ) 
     662      i15 = INT( 2*REAL( nday, wp ) / ( REAL( nmonth_len(nmonth), wp ) + 0.5 ) ) 
    663663      ! i15=0 if the current day is in the first half of the month, else i15=1 
    664664 
     
    708708          IF(lwp) WRITE(numout,*)  'Bdy data are read in netcdf files' 
    709709 
    710           dayfrac = adatrj-float(itimer)/86400. ! day fraction at time step kt-1 
    711           dayfrac = dayfrac - INT(dayfrac)      ! 
    712           totime = (nitend-nit000+1)*rdt ! Total time of the run to verify that all the 
    713                                            ! necessary time dumps in file are included 
     710          dayfrac = adatrj  - REAL(itimer,wp)/86400. ! day fraction at time step kt-1 
     711          dayfrac = dayfrac - INT (dayfrac)          ! 
     712          totime = (nitend-nit000+1)*rdt             ! Total time of the run to verify that all the 
     713                                                     ! necessary time dumps in file are included 
    714714 
    715715          clfile(1) = filbdy_data_bt_T 
     
    735735            ! Convert time origin in file to julian days  
    736736            isec0 = isec0 + ihours0*60.*60. + iminutes0*60. 
    737             CALL ymds2ju(iyear0, imonth0, iday0, real(isec0), dayjul0) 
     737            CALL ymds2ju(iyear0, imonth0, iday0, REAL(isec0, wp), dayjul0) 
    738738            ! Compute model initialization time  
    739739            iyear  = ndastp / 10000 
     
    741741            iday   = ndastp - iyear * 10000 - imonth * 100 
    742742            isecs  = dayfrac * 86400 
    743             CALL ymds2ju(iyear, imonth, iday, real(isecs) , zdayjulini) 
     743            CALL ymds2ju(iyear, imonth, iday, REAL(isecs, wp) , zdayjulini) 
    744744            ! zoffset from initialization date: 
    745745            zoffset = (dayjul0-zdayjulini)*86400 
     
    10601060     
    10611061        IF (ln_bdy_clim) THEN 
    1062           zxy = FLOAT( nday ) / FLOAT( nobis(nbdy_b_bt) ) + 0.5 - i15 
     1062          zxy = REAL( nday, wp ) / REAL( nmonth_len(nbdy_b_bt), wp ) + 0.5 - i15 
    10631063        ELSE           
    1064           zxy = FLOAT(istep_bt(nbdy_b_bt)-itimer) / FLOAT(istep_bt(nbdy_b_bt)-istep_bt(nbdy_a_bt)) 
     1064          zxy = REAL(istep_bt(nbdy_b_bt)-itimer, wp) / REAL(istep_bt(nbdy_b_bt)-istep_bt(nbdy_a_bt), wp) 
    10651065        END IF 
    10661066 
  • trunk/NEMO/OPA_SRC/daymod.F90

    r1559 r1713  
    5858   REAL(wp), PUBLIC                  ::   sec1jan000   !: second since Jan 1st 0h of nit000 year and Jan 1st 0h the current year 
    5959 
    60    ! this two variables are wrong DO NOT USE THEM !!! 
    61    INTEGER, PUBLIC, DIMENSION(12) ::   nbiss = (/ 31, 29, 31, 30, 31, 30,    &  !: number of days per month 
    62       &                                           31, 31, 30, 31, 30, 31 /)     !: (leap-year) 
    63    INTEGER, PUBLIC, DIMENSION(12) ::   nobis = (/ 31, 28, 31, 30, 31, 30,    &  !: number of days per month 
    64       &                                           31, 31, 30, 31, 30, 31 /)     !: (365 days a year) 
    65  
    6660   !!---------------------------------------------------------------------- 
    6761   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)  
Note: See TracChangeset for help on using the changeset viewer.