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

Changeset 1732


Ignore:
Timestamp:
2009-11-16T16:15:24+01:00 (14 years ago)
Author:
smasson
Message:

supress useless variables in phycst, see ticket:602

Location:
trunk/NEMO/OPA_SRC
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/DOM/domain.F90

    r1604 r1732  
    184184#endif 
    185185 
    186       SELECT CASE ( nleapy )       ! year=raajj*days day=rjjhh*hours hour=rhhmm*minutes etc ... 
    187       CASE ( 1 ) 
    188          raajj = 365.25 
    189          raass = raajj * rjjss 
    190          rmoss = raass/raamo 
    191       CASE ( 0 ) 
    192          raajj = 365. 
    193          raass = raajj * rjjss 
    194          rmoss = raass/raamo 
    195       CASE DEFAULT 
    196          raajj = FLOAT( nleapy ) * raamo 
    197          raass =        raajj    * rjjss 
    198          rmoss = FLOAT( nleapy ) * rjjss 
    199       END SELECT 
    200       IF(lwp) THEN 
    201          WRITE(numout,*) 
    202          WRITE(numout,*) '   nb of days per year      raajj = ', raajj,' days' 
    203          WRITE(numout,*) '   nb of seconds per year   raass = ', raass, ' s' 
    204          WRITE(numout,*) '   nb of seconds per month  rmoss = ', rmoss, ' s' 
    205       ENDIF 
    206  
    207186      REWIND( numnam )             ! Namelist namdom : space & time domain (bathymetry, mesh, timestep) 
    208187      READ  ( numnam, namdom ) 
  • trunk/NEMO/OPA_SRC/DOM/phycst.F90

    r1613 r1732  
    3030      rsiyea              ,     & !: sideral year (s) 
    3131      rsiday              ,     & !: sideral day (s) 
    32       raajj = 365._wp     ,     & !: number of days in one year 
    3332      raamo =  12._wp     ,     & !: number of months in one year 
    3433      rjjhh =  24._wp     ,     & !: number of hours in one day 
    3534      rhhmm =  60._wp     ,     & !: number of minutes in one hour 
    3635      rmmss =  60._wp     ,     & !: number of seconds in one minute 
    37       raass               ,     & !: number of seconds in one year 
    38       rmoss               ,     & !: number of seconds in one month 
    39       rjjss               ,     & !: number of seconds in one day 
    4036!!!   omega = 7.292115083046061e-5_wp ,  &  !: change the last digit! 
    4137      omega               ,    &  !: earth rotation parameter 
     
    141137      IF(lwp) WRITE(numout,*) '          omega                              omega  = ', omega,  ' s-1' 
    142138 
    143       rjjss = rjjhh * rhhmm * rmmss 
    144139      IF(lwp) WRITE(numout,*) 
    145140      IF(lwp) WRITE(numout,*) '          nb of months per year               raamo = ', raamo, ' months' 
     
    147142      IF(lwp) WRITE(numout,*) '          nb of minutes per hour              rhhmm = ', rhhmm, ' mn' 
    148143      IF(lwp) WRITE(numout,*) '          nb of seconds per minute            rmmss = ', rmmss, ' s' 
    149       IF(lwp) WRITE(numout,*) '          nb of seconds per day               rjjss = ', rjjss, ' s' 
    150144 
    151145      IF(lwp) WRITE(numout,*) 
  • trunk/NEMO/OPA_SRC/OBC/obcdta.F90

    r1715 r1732  
    3737  INTEGER :: nt_a=2, nt_b=1, itobc, ndate0_cnes, nday_year0 
    3838  INTEGER ::  itobce, itobcw, itobcs, itobcn, itobc_b  ! number of time steps in OBC files 
    39   REAL(wp) :: zraaj=365. 
    4039 
    4140  INTEGER ::   & 
     
    170169    ! ------------------------------------ 
    171170    IF ( ln_obc_clim) THEN 
    172       znum= MOD(zjcnes           - zjcnes_obc(nt_b), zraaj ) ; IF ( znum < 0 ) znum = znum + zraaj 
    173       zden= MOD(zjcnes_obc(nt_a) - zjcnes_obc(nt_b), zraaj ) ; IF ( zden < 0 ) zden = zden + zraaj 
     171      znum= MOD(zjcnes           - zjcnes_obc(nt_b), REAL(nyear_len(1),wp) ) ; IF ( znum < 0 ) znum = znum + REAL(nyear_len(1),wp) 
     172      zden= MOD(zjcnes_obc(nt_a) - zjcnes_obc(nt_b), REAL(nyear_len(1),wp) ) ; IF ( zden < 0 ) zden = zden + REAL(nyear_len(1),wp) 
    174173    ELSE 
    175174      znum= zjcnes           - zjcnes_obc(nt_b) 
     
    258257    ENDIF 
    259258    nday_year0 = nday_year  ! to remember the day when kt=nit000 
    260     SELECT CASE (nleapy) 
    261     CASE ( 0 )  ; zraaj = 365.e0  
    262     CASE ( 1 )  ; zraaj = 366.e0   !! ERROR TO CORRECT:  NOT EVERY YEAR IS LEAP YEAR !! JMM 
    263     CASE DEFAULT; zraaj = 12.* nleapy 
    264     END SELECT 
    265259 
    266260    sedta(:,:,:) = 0.e0 ; tedta(:,:,:) = 0.e0 ; uedta(:,:,:) = 0.e0 ; vedta(:,:,:) = 0.e0 ! East 
  • trunk/NEMO/OPA_SRC/SBC/sbcana.F90

    r1715 r1732  
    146146      REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient 
    147147      REAL(wp) ::   ztx, zty, zmod, zcoef ! temporary variables 
     148      REAL(wp) ::   zyydd                 ! number of days in one year 
    148149      !!--------------------------------------------------------------------- 
    149           
     150      zyydd = REAL(nyear_len(1),wp) 
     151 
    150152      ! ---------------------------- ! 
    151153      !  heat and freshwater fluxes  ! 
     
    160162      ! current day (in hours) since january the 1st of the current year 
    161163      ztime = REAL( kt ) * rdt / (rmmss * rhhmm)   &       !  total incrementation (in hours) 
    162          &      - (nyear  - 1) * rjjhh * raajj             !  minus years since beginning of experiment (in hours) 
     164         &      - (nyear  - 1) * rjjhh * zyydd             !  minus years since beginning of experiment (in hours) 
    163165 
    164166      ztimemax1 = ((5.*30.)+21.)* 24.                      ! 21th june     at 24h in hours 
    165       ztimemin1 = ztimemax1 + rjjhh * raajj / 2            ! 21th december        in hours 
     167      ztimemin1 = ztimemax1 + rjjhh * zyydd / 2            ! 21th december        in hours 
    166168      ztimemax2 = ((6.*30.)+21.)* 24.                      ! 21th july     at 24h in hours 
    167       ztimemin2 = ztimemax2 - rjjhh * raajj / 2            ! 21th january         in hours 
    168       !                                                    ! NB: rjjhh * raajj / 4 = one seasonal cycle in hours 
     169      ztimemin2 = ztimemax2 - rjjhh * zyydd / 2            ! 21th january         in hours 
     170      !                                                    ! NB: rjjhh * zyydd / 4 = one seasonal cycle in hours 
    169171 
    170172      ! amplitudes 
     
    243245      ! day (in hours) since january the 1st 
    244246      ztime = FLOAT( kt ) * rdt / (rmmss * rhhmm)  &  ! incrementation in hour 
    245          &     - (nyear - 1) * rjjhh * raajj          !  - nber of hours the precedent years 
     247         &     - (nyear - 1) * rjjhh * zyydd          !  - nber of hours the precedent years 
    246248      ztimemax = ((5.*30.)+21.)* 24.               ! 21th june     in hours 
    247       ztimemin = ztimemax + rjjhh * raajj / 2      ! 21th december in hours 
    248       !                                            ! NB: rjjhh * raajj / 4 = 1 seasonal cycle in hours 
     249      ztimemin = ztimemax + rjjhh * zyydd / 2      ! 21th december in hours 
     250      !                                            ! NB: rjjhh * zyydd / 4 = 1 seasonal cycle in hours 
    249251 
    250252      ! mean intensity at 0.105 ; srqt(2) because projected with 45deg angle 
     
    287289         WRITE(numout,*)'           nmonth     = ', nmonth 
    288290         WRITE(numout,*)'           nday       = ', nday 
    289          WRITE(numout,*)'           nday_year  = ',nday_year 
     291         WRITE(numout,*)'           nday_year  = ', nday_year 
    290292         WRITE(numout,*)'           ztime      = ', ztime 
     293         WRITE(numout,*)'           ztimemax   = ', ztimemax 
     294         WRITE(numout,*)'           ztimemin   = ', ztimemin 
    291295         WRITE(numout,*)'           ztimemax1  = ', ztimemax1 
    292296         WRITE(numout,*)'           ztimemin1  = ', ztimemin1 
     
    297301         WRITE(numout,*)'           zday0      = ', zday0 
    298302         WRITE(numout,*)'           zday_year0 = ', zday_year0 
    299          WRITE(numout,*)'           raajj      = ', raajj 
     303         WRITE(numout,*)'           zyydd      = ', zyydd 
    300304         WRITE(numout,*)'           zemp_S     = ', zemp_S 
    301305         WRITE(numout,*)'           zemp_N     = ', zemp_N 
     
    306310         WRITE(numout,*)'           ztrp       = ', ztrp 
    307311         WRITE(numout,*)'           zconv      = ', zconv 
    308  
    309          WRITE(numout,*)'           ndastp     = ',ndastp 
    310          WRITE(numout,*)'           adatrj     = ',adatrj 
    311          WRITE(numout,*)'           ztime      = ',ztime 
    312  
    313          WRITE(numout,*)'           ztimemax   = ',ztimemax 
    314          WRITE(numout,*)'           ztimemin   = ',ztimemin 
    315          WRITE(numout,*)'           zyear0     = ', zyear0 
    316          WRITE(numout,*)'           zmonth0    = ', zmonth0 
    317          WRITE(numout,*)'           zday0      = ', zday0 
    318          WRITE(numout,*)'           zday_year0 = ',zday_year0 
    319          WRITE(numout,*)'           raajj  = ', raajj 
     312         WRITE(numout,*)'           ndastp     = ', ndastp 
     313         WRITE(numout,*)'           adatrj     = ', adatrj 
     314 
    320315      ENDIF 
    321316      ! 
  • trunk/NEMO/OPA_SRC/SBC/sbcblk_clio.F90

    r1730 r1732  
    6363#endif 
    6464 
    65    REAL(wp) ::   yearday     !: number of days per year    
    66    REAL(wp) ::   rdtbs2      !: number of days per year    
     65   REAL(wp) ::   rdtbs2      !:    
    6766    
    6867   REAL(wp), DIMENSION(19)  ::  budyko            ! BUDYKO's coefficient (cloudiness effect on LW radiation) 
     
    725724            END DO 
    726725         END DO 
    727          IF    ( nleapy == 1 ) THEN   ;   yearday = 366.e0 
    728          ELSEIF( nleapy == 0 ) THEN   ;   yearday = 365.e0 
    729          ELSEIF( nleapy == 30) THEN   ;   yearday = 360.e0 
    730          ENDIF 
    731726         lbulk_init = .FALSE. 
    732727      ENDIF 
     
    764759      !  correction factor added for computation of shortwave flux to take into account the variation of 
    765760      !  the distance between the sun and the earth during the year (Oberhuber 1988) 
    766       zdist    = zxday * 2. * rpi / yearday 
     761      zdist    = zxday * 2. * rpi / REAL(nyear_len(1), wp) 
    767762      zdaycor  = 1.0 + 0.0013 * SIN( zdist ) + 0.0342 * COS( zdist ) 
    768763 
     
    779774            zlsset (ji,jj) = - zlsrise(ji,jj) 
    780775            !  dividing the solar day into jp24 segments of length zdlha 
    781             zdlha  (ji,jj) = ( zlsrise(ji,jj) - zlsset(ji,jj) ) / REAL( jp24 ) 
     776            zdlha  (ji,jj) = ( zlsrise(ji,jj) - zlsset(ji,jj) ) / REAL( jp24, wp ) 
    782777         END DO 
    783778      END DO 
     
    894889      !  correction factor added for computation of shortwave flux to take into account the variation of 
    895890      !  the distance between the sun and the earth during the year (Oberhuber 1988) 
    896       zdist    = zxday * 2. * rpi / yearday 
     891      zdist    = zxday * 2. * rpi / REAL(nyear_len(1), wp) 
    897892      zdaycor  = 1.0 + 0.0013 * SIN( zdist ) + 0.0342 * COS( zdist ) 
    898893 
     
    909904            zlsset (ji,jj) = - zlsrise(ji,jj) 
    910905            !  dividing the solar day into jp24 segments of length zdlha 
    911             zdlha  (ji,jj) = ( zlsrise(ji,jj) - zlsset(ji,jj) ) / REAL( jp24 ) 
     906            zdlha  (ji,jj) = ( zlsrise(ji,jj) - zlsset(ji,jj) ) / REAL( jp24, wp ) 
    912907         END DO 
    913908      END DO 
     
    991986      !!--------------------------------------------------------------------- 
    992987             
    993       IF    ( ky == 1 )  THEN   ;   zday = REAL( kday ) - 0.5 
    994       ELSEIF( ky == 3 )  THEN   ;   zday = REAL( kday ) - 1. 
    995       ELSE                      ;   zday = REAL( kday ) 
     988      IF    ( ky == 1 )  THEN   ;   zday = REAL( kday, wp ) - 0.5 
     989      ELSEIF( ky == 3 )  THEN   ;   zday = REAL( kday, wp ) - 1. 
     990      ELSE                      ;   zday = REAL( kday, wp ) 
    996991      ENDIF 
    997992       
    998       zp = rpi * ( 2.0 * zday - 367.0 ) / yearday 
     993      zp = rpi * ( 2.0 * zday - 367.0 ) / REAL(nyear_len(1), wp) 
    999994       
    1000995      pdecl  = a0                                                                      & 
Note: See TracChangeset for help on using the changeset viewer.