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

Changeset 9929


Ignore:
Timestamp:
2018-07-11T15:59:30+02:00 (6 years ago)
Author:
clem
Message:

remove unused variables

Location:
NEMO/trunk/src
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/ICE/icealb.F90

    r9910 r9929  
    149149               ! 
    150150               !                       !--- Snow-covered ice albedo (freezing, melting cases) 
    151                IF( pt_su(ji,jj,jl) < rt0_snow ) THEN 
     151               IF( pt_su(ji,jj,jl) < rt0 ) THEN 
    152152                  zalb_snw = rn_alb_sdry - ( rn_alb_sdry - zalb_ice ) * EXP( - ph_snw(ji,jj,jl) * z1_c3 ) 
    153153               ELSE 
  • NEMO/trunk/src/ICE/icedyn_adv_umx.F90

    r9866 r9929  
    136136      ! 
    137137   END SUBROUTINE ice_dyn_adv_umx 
     138 
    138139    
    139140   SUBROUTINE adv_umx( k_order, kt, pdt, puc, pvc, pubox, pvbox, ptc ) 
     
    159160      INTEGER  ::   ji, jj           ! dummy loop indices   
    160161      REAL(wp) ::   ztra             ! local scalar 
    161       REAL(wp) ::   zfp_ui, zfp_vj   !   -      - 
    162       REAL(wp) ::   zfm_ui, zfm_vj   !   -      - 
    163162      REAL(wp), DIMENSION(jpi,jpj) ::   zfu_ups, zfu_ho, zt_u, zt_ups 
    164163      REAL(wp), DIMENSION(jpi,jpj) ::   zfv_ups, zfv_ho, zt_v, ztrd 
     
    169168      DO jj = 1, jpjm1         ! upstream tracer flux in the i and j direction 
    170169         DO ji = 1, fs_jpim1   ! vector opt. 
    171             zfp_ui = puc(ji,jj) + ABS( puc(ji,jj) ) 
    172             zfm_ui = puc(ji,jj) - ABS( puc(ji,jj) ) 
    173             zfp_vj = pvc(ji,jj) + ABS( pvc(ji,jj) ) 
    174             zfm_vj = pvc(ji,jj) - ABS( pvc(ji,jj) ) 
    175             zfu_ups(ji,jj) = 0.5_wp * ( zfp_ui * ptc(ji,jj) + zfm_ui * ptc(ji+1,jj  ) ) 
    176             zfv_ups(ji,jj) = 0.5_wp * ( zfp_vj * ptc(ji,jj) + zfm_vj * ptc(ji  ,jj+1) ) 
     170            zfu_ups(ji,jj) = MAX( puc(ji,jj), 0._wp ) * ptc(ji,jj) + MIN( puc(ji,jj), 0._wp ) * ptc(ji+1,jj) 
     171            zfv_ups(ji,jj) = MAX( pvc(ji,jj), 0._wp ) * ptc(ji,jj) + MIN( pvc(ji,jj), 0._wp ) * ptc(ji,jj+1) 
    177172         END DO 
    178173      END DO 
  • NEMO/trunk/src/ICE/icethd_zdf_bl99.F90

    r9916 r9929  
    805805               cnd_ice_1d(ji) = 2._wp * zkappa_i(ji,0) 
    806806            ELSE 
    807                cnd_ice_1d(ji) = 2._wp * ztcond_i(ji,0) / 0.1_wp 
     807               cnd_ice_1d(ji) = 2._wp * ztcond_i(ji,0) * 10._wp 
    808808            ENDIF 
    809809         ENDIF 
  • NEMO/trunk/src/OCE/DOM/phycst.F90

    r9656 r9929  
    2323   PUBLIC   phy_cst     ! routine called by inipar.F90 
    2424 
    25    REAL(wp), PUBLIC ::   rpi = 3.141592653589793_wp             !: pi 
    26    REAL(wp), PUBLIC ::   rad = 3.141592653589793_wp / 180._wp   !: conversion from degre into radian 
    27    REAL(wp), PUBLIC ::   rsmall = 0.5 * EPSILON( 1.e0 )         !: smallest real computer value 
     25   REAL(wp), PUBLIC ::   rpi      = 3.141592653589793_wp             !: pi 
     26   REAL(wp), PUBLIC ::   rad      = 3.141592653589793_wp / 180._wp   !: conversion from degre into radian 
     27   REAL(wp), PUBLIC ::   rsmall   = 0.5 * EPSILON( 1.e0 )            !: smallest real computer value 
    2828    
    29    REAL(wp), PUBLIC ::   rday = 24.*60.*60.     !: day                                [s] 
    30    REAL(wp), PUBLIC ::   rsiyea                 !: sideral year                       [s] 
    31    REAL(wp), PUBLIC ::   rsiday                 !: sideral day                        [s] 
    32    REAL(wp), PUBLIC ::   raamo =  12._wp        !: number of months in one year 
    33    REAL(wp), PUBLIC ::   rjjhh =  24._wp        !: number of hours in one day 
    34    REAL(wp), PUBLIC ::   rhhmm =  60._wp        !: number of minutes in one hour 
    35    REAL(wp), PUBLIC ::   rmmss =  60._wp        !: number of seconds in one minute 
    36    REAL(wp), PUBLIC ::   omega                  !: earth rotation parameter           [s-1] 
    37    REAL(wp), PUBLIC ::   ra    = 6371229._wp    !: earth radius                       [m] 
    38    REAL(wp), PUBLIC ::   grav  = 9.80665_wp     !: gravity                            [m/s2] 
    39     
    40    REAL(wp), PUBLIC ::   rtt      = 273.16_wp        !: triple point of temperature   [Kelvin] 
     29   REAL(wp), PUBLIC ::   rday     = 24.*60.*60.      !: day                                [s] 
     30   REAL(wp), PUBLIC ::   rsiyea                      !: sideral year                       [s] 
     31   REAL(wp), PUBLIC ::   rsiday                      !: sideral day                        [s] 
     32   REAL(wp), PUBLIC ::   raamo    =  12._wp          !: number of months in one year 
     33   REAL(wp), PUBLIC ::   rjjhh    =  24._wp          !: number of hours in one day 
     34   REAL(wp), PUBLIC ::   rhhmm    =  60._wp          !: number of minutes in one hour 
     35   REAL(wp), PUBLIC ::   rmmss    =  60._wp          !: number of seconds in one minute 
     36   REAL(wp), PUBLIC ::   omega                       !: earth rotation parameter           [s-1] 
     37   REAL(wp), PUBLIC ::   ra       = 6371229._wp      !: earth radius                       [m] 
     38   REAL(wp), PUBLIC ::   grav     = 9.80665_wp       !: gravity                            [m/s2]    
    4139   REAL(wp), PUBLIC ::   rt0      = 273.15_wp        !: freezing point of fresh water [Kelvin] 
    42    REAL(wp), PUBLIC ::   rt0_snow = 273.15_wp        !: melting point of snow         [Kelvin] 
    43 #if defined key_si3 
    44    REAL(wp), PUBLIC ::   rt0_ice  = 273.15_wp        !: melting point of ice          [Kelvin] 
    45 #else 
    46    REAL(wp), PUBLIC ::   rt0_ice  = 273.05_wp        !: melting point of ice          [Kelvin] 
    47 #endif 
     40 
    4841   REAL(wp), PUBLIC ::   rau0                        !: volumic mass of reference     [kg/m3] 
    4942   REAL(wp), PUBLIC ::   r1_rau0                     !: = 1. / rau0                   [m3/kg] 
     
    5346   REAL(wp), PUBLIC ::   r1_rau0_rcp                 !: = 1. / ( rau0 * rcp ) 
    5447 
    55    REAL(wp), PUBLIC ::   rhosn    =  330._wp         !: volumic mass of snow          [kg/m3] 
    56    REAL(wp), PUBLIC ::   rhofw    = 1000._wp         !: volumic mass of freshwater in melt ponds [kg/m3] 
     48!clem: not sure these are needed for cice    
     49#if defined key_cice 
     50   REAL(wp), PUBLIC ::   rt0_snow = 273.15_wp        !: melting point of snow         [Kelvin] 
     51   REAL(wp), PUBLIC ::   rt0_ice  = 273.05_wp        !: melting point of ice          [Kelvin] 
    5752   REAL(wp), PUBLIC ::   emic     =    0.97_wp       !: emissivity of snow or ice 
    58    REAL(wp), PUBLIC ::   sice     =    6.0_wp        !: salinity of ice               [psu] 
    59    REAL(wp), PUBLIC ::   soce     =   34.7_wp        !: salinity of sea               [psu] 
     53   REAL(wp), PUBLIC ::   xlsn                        !: = lfus*rhosn (volumetric latent heat fusion of snow)  [J/m3] 
     54#endif 
     55 
     56   REAL(wp), PUBLIC ::   sice     =    6.0_wp        !: salinity of ice (for pisces)          [psu] 
     57   REAL(wp), PUBLIC ::   soce     =   34.7_wp        !: salinity of sea (for pisces and isf)  [psu] 
    6058   REAL(wp), PUBLIC ::   cevap    =    2.5e+6_wp     !: latent heat of evaporation (water) 
    6159   REAL(wp), PUBLIC ::   srgamma  =    0.9_wp        !: correction factor for solar radiation (Oberhuber, 1974) 
     
    6361   REAL(wp), PUBLIC ::   stefan   =    5.67e-8_wp    !: Stefan-Boltzmann constant  
    6462 
    65 #if defined key_si3 || defined key_cice 
     63   REAL(wp), PUBLIC ::   rhosn    =  330._wp         !: volumic mass of snow                                  [kg/m3] 
    6664   REAL(wp), PUBLIC ::   rhoic    =  917._wp         !: volumic mass of sea ice                               [kg/m3] 
     65   REAL(wp), PUBLIC ::   rhofw    = 1000._wp         !: volumic mass of freshwater in melt ponds              [kg/m3] 
    6766   REAL(wp), PUBLIC ::   rcdic    =    2.034396_wp   !: thermal conductivity of fresh ice                     [W/m/K] 
     67#if defined key_cice 
     68   REAL(wp), PUBLIC ::   rcdsn    =    0.31_wp       !: thermal conductivity of snow                          [W/m/K] 
     69#endif 
    6870   REAL(wp), PUBLIC ::   cpic     = 2067.0_wp        !: specific heat of fresh ice                            [J/kg/K] 
    6971   REAL(wp), PUBLIC ::   lsub     =    2.834e+6_wp   !: pure ice latent heat of sublimation                   [J/kg] 
    7072   REAL(wp), PUBLIC ::   lfus     =    0.334e+6_wp   !: latent heat of fusion of fresh ice                    [J/kg] 
    7173   REAL(wp), PUBLIC ::   tmut     =    0.054_wp      !: decrease of seawater meltpoint with salinity 
    72    REAL(wp), PUBLIC ::   xlsn                        !: = lfus*rhosn (volumetric latent heat fusion of snow)  [J/m3] 
    73 #else 
    74    REAL(wp), PUBLIC ::   rhoic    =  900._wp         !: volumic mass of sea ice                               [kg/m3] 
    75    REAL(wp), PUBLIC ::   rcdic    =    2.034396_wp   !: conductivity of the ice                               [W/m/K] 
    76    REAL(wp), PUBLIC ::   rcpic    =    1.8837e+6_wp  !: volumetric specific heat for ice                      [J/m3/K] 
    77    REAL(wp), PUBLIC ::   cpic                        !: = rcpic / rhoic  (specific heat for ice)              [J/Kg/K] 
    78    REAL(wp), PUBLIC ::   rcdsn    =    0.22_wp       !: conductivity of the snow                              [W/m/K] 
    79    REAL(wp), PUBLIC ::   rcpsn    =    6.9069e+5_wp  !: volumetric specific heat for snow                     [J/m3/K] 
    80    REAL(wp), PUBLIC ::   xlsn     =  110.121e+6_wp   !: volumetric latent heat fusion of snow                 [J/m3] 
    81    REAL(wp), PUBLIC ::   lfus                        !: = xlsn / rhosn   (latent heat of fusion of fresh ice) [J/Kg] 
    82    REAL(wp), PUBLIC ::   xlic     =  300.33e+6_wp    !: volumetric latent heat fusion of ice                  [J/m3] 
    83    REAL(wp), PUBLIC ::   xsn      =    2.8e+6_wp     !: volumetric latent heat of sublimation of snow         [J/m3] 
    84 #endif 
    85 #if defined key_cice 
    86    REAL(wp), PUBLIC ::   rcdsn    =    0.31_wp       !: thermal conductivity of snow                          [W/m/K] 
    87 #endif 
    88 #if defined key_si3 
     74 
    8975   REAL(wp), PUBLIC ::   r1_rhoic                    !: 1 / rhoic 
    9076   REAL(wp), PUBLIC ::   r1_rhosn                    !: 1 / rhosn 
    9177   REAL(wp), PUBLIC ::   r1_cpic                     !: 1 / cpic 
    92 #endif 
    9378   !!---------------------------------------------------------------------- 
    9479   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    10691      !!---------------------------------------------------------------------- 
    10792 
    108       IF(lwp) WRITE(numout,*) 
    109       IF(lwp) WRITE(numout,*) 'phy_cst : initialization of ocean parameters and constants' 
    110       IF(lwp) WRITE(numout,*) '~~~~~~~' 
    111  
    112       ! Define & print constants 
    113       ! ------------------------ 
    114       IF(lwp) WRITE(numout,*) 
    115       IF(lwp) WRITE(numout,*) '   Constants' 
    116  
    117       IF(lwp) WRITE(numout,*) 
    118       IF(lwp) WRITE(numout,*) '      mathematical constant                 rpi = ', rpi 
    119  
    12093      rsiyea = 365.25_wp * rday * 2._wp * rpi / 6.283076_wp 
    12194      rsiday = rday / ( 1._wp + rday / rsiyea ) 
     
    12598      omega  = 2._wp * rpi / rsiday  
    12699#endif 
    127       IF(lwp) WRITE(numout,*) 
    128       IF(lwp) WRITE(numout,*) '      day                                rday   = ', rday,   ' s' 
    129       IF(lwp) WRITE(numout,*) '      sideral year                       rsiyea = ', rsiyea, ' s' 
    130       IF(lwp) WRITE(numout,*) '      sideral day                        rsiday = ', rsiday, ' s' 
    131       IF(lwp) WRITE(numout,*) '      omega                              omega  = ', omega,  ' s^-1' 
    132       IF(lwp) WRITE(numout,*) 
    133       IF(lwp) WRITE(numout,*) '      nb of months per year               raamo = ', raamo, ' months' 
    134       IF(lwp) WRITE(numout,*) '      nb of hours per day                 rjjhh = ', rjjhh, ' hours' 
    135       IF(lwp) WRITE(numout,*) '      nb of minutes per hour              rhhmm = ', rhhmm, ' mn' 
    136       IF(lwp) WRITE(numout,*) '      nb of seconds per minute            rmmss = ', rmmss, ' s' 
    137       IF(lwp) WRITE(numout,*) 
    138       IF(lwp) WRITE(numout,*) '      earth radius                         ra   = ', ra, ' m' 
    139       IF(lwp) WRITE(numout,*) '      gravity                              grav = ', grav , ' m/s^2' 
    140       IF(lwp) WRITE(numout,*) 
    141       IF(lwp) WRITE(numout,*) '      triple point of temperature      rtt      = ', rtt     , ' K' 
    142       IF(lwp) WRITE(numout,*) '      freezing point of water          rt0      = ', rt0     , ' K' 
    143       IF(lwp) WRITE(numout,*) '      melting point of snow            rt0_snow = ', rt0_snow, ' K' 
    144       IF(lwp) WRITE(numout,*) '      melting point of ice             rt0_ice  = ', rt0_ice , ' K' 
    145       IF(lwp) WRITE(numout,*) 
    146       IF(lwp) WRITE(numout,*) '   reference density and heat capacity now defined in eosbn2.f90' 
    147                
    148 #if defined key_si3 || defined key_cice 
    149       xlsn = lfus * rhosn        ! volumetric latent heat fusion of snow [J/m3] 
    150 #else 
    151       cpic = rcpic / rhoic       ! specific heat for ice   [J/Kg/K] 
    152       lfus = xlsn / rhosn        ! latent heat of fusion of fresh ice 
     100 
     101#if defined key_cice 
     102      xlsn = lfus * rhosn 
    153103#endif 
    154 #if defined key_si3 
     104 
    155105      r1_rhoic = 1._wp / rhoic 
    156106      r1_rhosn = 1._wp / rhosn 
    157107      r1_cpic  = 1._wp / cpic 
    158 #endif 
     108 
    159109      IF(lwp) THEN 
     110         WRITE(numout,*) 
     111         WRITE(numout,*) 'phy_cst : initialization of ocean parameters and constants' 
     112         WRITE(numout,*) '~~~~~~~' 
     113         WRITE(numout,*) '      mathematical constant                 rpi = ', rpi 
     114         WRITE(numout,*) '      day                                rday   = ', rday,   ' s' 
     115         WRITE(numout,*) '      sideral year                       rsiyea = ', rsiyea, ' s' 
     116         WRITE(numout,*) '      sideral day                        rsiday = ', rsiday, ' s' 
     117         WRITE(numout,*) '      omega                              omega  = ', omega,  ' s^-1' 
     118         WRITE(numout,*) 
     119         WRITE(numout,*) '      nb of months per year               raamo = ', raamo, ' months' 
     120         WRITE(numout,*) '      nb of hours per day                 rjjhh = ', rjjhh, ' hours' 
     121         WRITE(numout,*) '      nb of minutes per hour              rhhmm = ', rhhmm, ' mn' 
     122         WRITE(numout,*) '      nb of seconds per minute            rmmss = ', rmmss, ' s' 
     123         WRITE(numout,*) 
     124         WRITE(numout,*) '      earth radius                         ra   = ', ra   , ' m' 
     125         WRITE(numout,*) '      gravity                              grav = ', grav , ' m/s^2' 
     126         WRITE(numout,*) 
     127         WRITE(numout,*) '      freezing point of water              rt0  = ', rt0  , ' K' 
     128         WRITE(numout,*) 
     129         WRITE(numout,*) '   reference density and heat capacity now defined in eosbn2.f90' 
    160130         WRITE(numout,*) 
    161131#if defined key_cice 
     
    165135         WRITE(numout,*) '      fresh ice specific heat                   = ', cpic    , ' J/kg/K' 
    166136         WRITE(numout,*) '      latent heat of fusion of fresh ice / snow = ', lfus    , ' J/kg' 
    167 #if defined key_si3 || defined key_cice 
    168137         WRITE(numout,*) '      latent heat of subl.  of fresh ice / snow = ', lsub    , ' J/kg' 
    169 #else 
    170          WRITE(numout,*) '      density times specific heat for snow      = ', rcpsn   , ' J/m^3/K'  
    171          WRITE(numout,*) '      density times specific heat for ice       = ', rcpic   , ' J/m^3/K' 
    172          WRITE(numout,*) '      volumetric latent heat fusion of sea ice  = ', xlic    , ' J/m'  
    173          WRITE(numout,*) '      latent heat of sublimation of snow        = ', xsn     , ' J/kg'  
    174 #endif 
    175          WRITE(numout,*) '      volumetric latent heat fusion of snow     = ', xlsn    , ' J/m^3'  
    176138         WRITE(numout,*) '      density of sea ice                        = ', rhoic   , ' kg/m^3' 
    177139         WRITE(numout,*) '      density of snow                           = ', rhosn   , ' kg/m^3' 
    178140         WRITE(numout,*) '      density of freshwater (in melt ponds)     = ', rhofw   , ' kg/m^3' 
    179          WRITE(numout,*) '      emissivity of snow or ice                 = ', emic   
    180          WRITE(numout,*) '      salinity of ice                           = ', sice    , ' psu' 
    181          WRITE(numout,*) '      salinity of sea                           = ', soce    , ' psu' 
     141         WRITE(numout,*) '      salinity of ice (for pisces)              = ', sice    , ' psu' 
     142         WRITE(numout,*) '      salinity of sea (for pisces and isf)      = ', soce    , ' psu' 
    182143         WRITE(numout,*) '      latent heat of evaporation (water)        = ', cevap   , ' J/m^3'  
    183144         WRITE(numout,*) '      correction factor for solar radiation     = ', srgamma  
  • NEMO/trunk/src/OCE/SBC/sbcblk.F90

    r9910 r9929  
    531531         &     * ( sf(jp_tair)%fnow(:,:,1) - rt0 ) * rcp                          & 
    532532         &     + sf(jp_snow)%fnow(:,:,1) * rn_pfac                                &   ! add solid  precip heat content at min(Tair,Tsnow) 
    533          &     * ( MIN( sf(jp_tair)%fnow(:,:,1), rt0_snow ) - rt0 ) * cpic 
     533         &     * ( MIN( sf(jp_tair)%fnow(:,:,1), rt0 ) - rt0 ) * cpic 
    534534      qns(:,:) = qns(:,:) * tmask(:,:,1) 
    535535      ! 
     
    884884         &          + ( tprecip(:,:) - sprecip(:,:) ) * ( sf(jp_tair)%fnow(:,:,1) - rt0 ) * rcp  & ! liquid precip at Tair 
    885885         &          +   sprecip(:,:) * ( 1._wp - zsnw ) *                                        & ! solid precip at min(Tair,Tsnow) 
    886          &              ( ( MIN( sf(jp_tair)%fnow(:,:,1), rt0_snow ) - rt0 ) * cpic * tmask(:,:,1) - lfus ) 
     886         &              ( ( MIN( sf(jp_tair)%fnow(:,:,1), rt0 ) - rt0 ) * cpic * tmask(:,:,1) - lfus ) 
    887887      qemp_ice(:,:) =   sprecip(:,:) * zsnw *                                                    & ! solid precip (only) 
    888          &              ( ( MIN( sf(jp_tair)%fnow(:,:,1), rt0_snow ) - rt0 ) * cpic * tmask(:,:,1) - lfus ) 
     888         &              ( ( MIN( sf(jp_tair)%fnow(:,:,1), rt0 ) - rt0 ) * cpic * tmask(:,:,1) - lfus ) 
    889889 
    890890      ! --- total solar and non solar fluxes --- ! 
     
    894894 
    895895      ! --- heat content of precip over ice in J/m3 (to be used in 1D-thermo) --- ! 
    896       qprec_ice(:,:) = rhosn * ( ( MIN( sf(jp_tair)%fnow(:,:,1), rt0_snow ) - rt0 ) * cpic * tmask(:,:,1) - lfus ) 
     896      qprec_ice(:,:) = rhosn * ( ( MIN( sf(jp_tair)%fnow(:,:,1), rt0 ) - rt0 ) * cpic * tmask(:,:,1) - lfus ) 
    897897 
    898898      ! --- heat content of evap over ice in W/m2 (to be used in 1D-thermo) --- 
Note: See TracChangeset for help on using the changeset viewer.