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 6900 for branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC – NEMO

Ignore:
Timestamp:
2016-08-29T17:55:22+02:00 (8 years ago)
Author:
flavoni
Message:

#1692 and ROBUST-3 : Update OVERFLOW configuration, and some cleaning

Location:
branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC
Files:
12 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/DOM/daymod.F90

    r6140 r6900  
    22   !!====================================================================== 
    33   !!                       ***  MODULE  daymod  *** 
    4    !! Ocean        : calendar 
     4   !! Ocean :   management of the model calendar 
    55   !!===================================================================== 
    66   !! History :  OPA  ! 1994-09  (M. Pontaud M. Imbard)  Original code 
     
    1616   !!---------------------------------------------------------------------- 
    1717   !!   day        : calendar 
    18    !! 
    19    !!           ------------------------------- 
    20    !!           ----------- WARNING ----------- 
    21    !! 
    22    !!   we suppose that the time step is deviding the number of second of in a day 
    23    !!             ---> MOD( rday, rdt ) == 0 
    24    !! 
    25    !!           ----------- WARNING ----------- 
    26    !!           ------------------------------- 
    27    !! 
     18   !!---------------------------------------------------------------------- 
     19   !!                    ----------- WARNING ----------- 
     20   !!                    ------------------------------- 
     21   !!   sbcmod assume that the time step is dividing the number of second of  
     22   !!   in a day, i.e. ===> MOD( rday, rdt ) == 0  
     23   !!   except when user defined forcing is used (see sbcmod.F90) 
    2824   !!---------------------------------------------------------------------- 
    2925   USE dom_oce        ! ocean space and time domain 
    3026   USE phycst         ! physical constants 
     27   USE ioipsl  , ONLY :   ymds2ju      ! for calendar 
     28   USE trc_oce , ONLY :   lk_offline   ! offline flag 
     29   ! 
    3130   USE in_out_manager ! I/O manager 
     31   USE prtctl         ! Print control 
    3232   USE iom            ! 
    33    USE ioipsl  , ONLY :   ymds2ju   ! for calendar 
    34    USE prtctl         ! Print control 
    35    USE trc_oce , ONLY : lk_offline ! offline flag 
    3633   USE timing         ! Timing 
    3734   USE restart        ! restart 
     
    4744 
    4845   !!---------------------------------------------------------------------- 
    49    !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     46   !! NEMO/OPA 4.0 , NEMO Consortium (2016) 
    5047   !! $Id$ 
    5148   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    7067      !!              - nmonth_len, nyear_len, nmonth_half, nmonth_end through day_mth 
    7168      !!---------------------------------------------------------------------- 
    72       INTEGER  ::   inbday, idweek 
    73       REAL(wp) ::   zjul 
     69      INTEGER  ::   inbday, idweek   ! local integers 
     70      REAL(wp) ::   zjul             ! local scalar 
    7471      !!---------------------------------------------------------------------- 
    7572      ! 
     
    7976            &           'You must do a restart at higher frequency (or remove this stop and recompile the code in I8)' ) 
    8077      ENDIF 
    81       ! all calendar staff is based on the fact that MOD( rday, rdt ) == 0 
    82       IF( MOD( rday     , rdt   ) /= 0. )   CALL ctl_stop( 'the time step must devide the number of second of in a day' ) 
    83       IF( MOD( rday     , 2.    ) /= 0. )   CALL ctl_stop( 'the number of second of in a day must be an even number'    ) 
    84       IF( MOD( rdt      , 2.    ) /= 0. )   CALL ctl_stop( 'the time step (in second) must be an even number'           ) 
    85       nsecd   = NINT(rday       ) 
    86       nsecd05 = NINT(0.5 * rday ) 
    87       ndt     = NINT(      rdt  ) 
    88       ndt05   = NINT(0.5 * rdt  ) 
    89  
    90       IF( .NOT. lk_offline ) CALL day_rst( nit000, 'READ' ) 
     78      nsecd   = NINT( rday       ) 
     79      nsecd05 = NINT( 0.5 * rday ) 
     80      ndt     = NINT(       rdt  ) 
     81      ndt05   = NINT( 0.5 * rdt  ) 
     82 
     83      IF( .NOT. lk_offline )   CALL day_rst( nit000, 'READ' ) 
    9184 
    9285      ! set the calandar from ndastp (read in restart file and namelist) 
    93  
    9486      nyear   =   ndastp / 10000 
    9587      nmonth  = ( ndastp - (nyear * 10000) ) / 100 
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/OBS/obs_conv_functions.h90

    r2287 r6900  
    7171 
    7272      !! * Arguments 
    73       REAL(KIND=wp) :: pft   ! in situ temperature in degrees celcius 
     73      REAL(KIND=wp) :: pft   ! in situ temperature in degrees Celsius 
    7474      REAL(KIND=wp) :: pfs   ! salinity in psu 
    7575      REAL(KIND=wp) :: pfp   ! pressure in bars 
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/SBC/sbcblk_clio.F90

    r5836 r6900  
    215215      !!---------------------------------------------------------------------- 
    216216      TYPE(fld), INTENT(in), DIMENSION(:)       ::   sf    ! input data 
    217       REAL(wp) , INTENT(in), DIMENSION(jpi,jpj) ::   pst   ! surface temperature                      [Celcius] 
     217      REAL(wp) , INTENT(in), DIMENSION(jpi,jpj) ::   pst   ! surface temperature                      [Celsius] 
    218218      !! 
    219219      INTEGER  ::   ji, jj   ! dummy loop indices 
     
    279279         DO ji = 1, jpi 
    280280            ! 
    281             zsst  = pst(ji,jj)              + rt0           ! converte Celcius to Kelvin the SST 
     281            zsst  = pst(ji,jj)              + rt0           ! converte Celsius to Kelvin the SST 
    282282            ztatm = sf(jp_tair)%fnow(ji,jj,1)               ! and set minimum value far above 0 K (=rt0 over land) 
    283283            zcco1 = 1.0 - sf(jp_ccov)%fnow(ji,jj,1)         ! fraction of clear sky ( 1 - cloud cover) 
     
    371371      ! 
    372372      qns(:,:) = zqlw(:,:) - zqsb(:,:) - zqla(:,:)                        &   ! Downward Non Solar flux 
    373          &     - zqla(:,:)             * pst(:,:) * zcevap                &   ! remove evap.   heat content at SST in Celcius 
    374          &     + sf(jp_prec)%fnow(:,:,1) * sf(jp_tair)%fnow(:,:,1) * zcprec   ! add    precip. heat content at Tair in Celcius 
     373         &     - zqla(:,:)             * pst(:,:) * zcevap                &   ! remove evap.   heat content at SST in Celsius 
     374         &     + sf(jp_prec)%fnow(:,:,1) * sf(jp_tair)%fnow(:,:,1) * zcprec   ! add    precip. heat content at Tair in Celsius 
    375375      qns(:,:) = qns(:,:) * tmask(:,:,1) 
    376376#if defined key_lim3 
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/SBC/sbcblk_core.F90

    r6140 r6900  
    241241      INTEGER  , INTENT(in   )                 ::   kt    ! time step index 
    242242      TYPE(fld), INTENT(inout), DIMENSION(:)   ::   sf    ! input data 
    243       REAL(wp) , INTENT(in)   , DIMENSION(:,:) ::   pst   ! surface temperature                      [Celcius] 
     243      REAL(wp) , INTENT(in)   , DIMENSION(:,:) ::   pst   ! surface temperature                      [Celsius] 
    244244      REAL(wp) , INTENT(in)   , DIMENSION(:,:) ::   pu    ! surface current at U-point (i-component) [m/s] 
    245245      REAL(wp) , INTENT(in)   , DIMENSION(:,:) ::   pv    ! surface current at V-point (j-component) [m/s] 
     
    267267      zcoef_qsatw = 0.98 * 640380. / rhoa 
    268268       
    269       zst(:,:) = pst(:,:) + rt0      ! convert SST from Celcius to Kelvin (and set minimum value far above 0 K) 
     269      zst(:,:) = pst(:,:) + rt0      ! convert SST from Celsius to Kelvin (and set minimum value far above 0 K) 
    270270 
    271271      ! ----------------------------------------------------------------------------- ! 
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r6165 r6900  
    555555               WRITE(numout,*)'  Additional received fields from OPA component : ' 
    556556            ENDIF 
    557             WRITE(numout,*)'               sea surface temperature (Celcius) ' 
     557            WRITE(numout,*)'               sea surface temperature (Celsius) ' 
    558558            WRITE(numout,*)'               sea surface salinity '  
    559559            WRITE(numout,*)'               surface currents '  
     
    710710            WRITE(numout,*) 
    711711            WRITE(numout,*)'  sent fields to SAS component ' 
    712             WRITE(numout,*)'               sea surface temperature (T before, Celcius) ' 
     712            WRITE(numout,*)'               sea surface temperature (T before, Celsius) ' 
    713713            WRITE(numout,*)'               sea surface salinity '  
    714714            WRITE(numout,*)'               surface currents U,V on local grid and spherical coordinates'  
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_if.F90

    r6596 r6900  
    101101                                 ! ( d rho / dt ) / ( d rho / ds )      ( s = 34, t = -1.8 ) 
    102102          
    103          CALL eos_fzp( sss_m(:,:), fr_i(:,:) )       ! sea surface freezing temperature [Celcius] 
     103         CALL eos_fzp( sss_m(:,:), fr_i(:,:) )       ! sea surface freezing temperature [Celsius] 
    104104         fr_i(:,:) = fr_i(:,:) * tmask(:,:,1) 
    105105 
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r6717 r6900  
    1919   !!   sbc_init      : read namsbc namelist 
    2020   !!   sbc           : surface ocean momentum, heat and freshwater boundary conditions 
     21   !!   sbc_final     : Finalize CICE ice model (if used) 
    2122   !!---------------------------------------------------------------------- 
    2223   USE oce            ! ocean dynamics and tracers 
     
    3738   USE sbcice_cice    ! surface boundary condition: CICE    sea-ice model 
    3839   USE sbccpl         ! surface boundary condition: coupled florulation 
    39    USE usrdef_sbc     ! user defined: surface boundary condition 
    4040   USE cpl_oasis3     ! OASIS routines for coupling 
    4141   USE sbcssr         ! surface boundary condition: sea surface restoring 
     
    4747   USE sbcwave        ! Wave module 
    4848   USE bdy_par        ! Require lk_bdy 
    49    USE usrdef_closea  ! closed sea 
     49   USE usrdef_sbc     ! user defined: surface boundary condition 
     50   USE usrdef_closea  ! user defined: closed sea 
    5051   ! 
    5152   USE prtctl         ! Print control                    (prt_ctl routine) 
     
    5556   USE timing         ! Timing 
    5657 
    57    USE diurnal_bulk, ONLY: & 
    58       & ln_diurnal_only  
     58   USE diurnal_bulk, ONLY:   ln_diurnal_only   ! diurnal SST diagnostic 
    5959 
    6060   IMPLICIT NONE 
     
    6767       
    6868   !!---------------------------------------------------------------------- 
    69    !! NEMO/OPA 4.0 , NEMO-consortium (2011)  
     69   !! NEMO/OPA 4.0 , NEMO-consortium (2016)  
    7070   !! $Id$ 
    7171   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    105105      ENDIF 
    106106      ! 
    107       REWIND( numnam_ref )              ! Namelist namsbc in reference namelist : Surface boundary 
     107      REWIND( numnam_ref )       ! Namelist namsbc in reference namelist : Surface boundary 
    108108      READ  ( numnam_ref, namsbc, IOSTAT = ios, ERR = 901) 
    109109901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc in reference namelist', lwp ) 
    110110      ! 
    111       REWIND( numnam_cfg )              ! Namelist namsbc in configuration namelist : Parameters of the run 
     111      REWIND( numnam_cfg )       ! Namelist namsbc in configuration namelist : Parameters of the run 
    112112      READ  ( numnam_cfg, namsbc, IOSTAT = ios, ERR = 902 ) 
    113113902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc in configuration namelist', lwp ) 
     
    122122      ! 
    123123      IF(lwp) THEN               ! Control print 
    124          WRITE(numout,*) '        Namelist namsbc (partly overwritten with CPP key setting)' 
    125          WRITE(numout,*) '           frequency update of sbc (and ice)             nn_fsbc     = ', nn_fsbc 
    126          WRITE(numout,*) '           Type of air-sea fluxes : ' 
    127          WRITE(numout,*) '              user defined formulation                   ln_usr        = ', ln_usr 
    128          WRITE(numout,*) '              flux         formulation                   ln_flx        = ', ln_flx 
    129          WRITE(numout,*) '              CLIO bulk    formulation                   ln_blk_clio   = ', ln_blk_clio 
    130          WRITE(numout,*) '              CORE bulk    formulation                   ln_blk_core   = ', ln_blk_core 
    131          WRITE(numout,*) '              MFS  bulk    formulation                   ln_blk_mfs    = ', ln_blk_mfs 
    132          WRITE(numout,*) '           Type of coupling (Ocean/Ice/Atmosphere) : ' 
    133          WRITE(numout,*) '              ocean-atmosphere coupled formulation       ln_cpl        = ', ln_cpl 
    134          WRITE(numout,*) '              forced-coupled mixed formulation           ln_mixcpl     = ', ln_mixcpl 
    135          WRITE(numout,*) '              OASIS coupling (with atm or sas)           lk_oasis      = ', lk_oasis 
    136          WRITE(numout,*) '              components of your executable              nn_components = ', nn_components 
    137          WRITE(numout,*) '              Multicategory heat flux formulation (LIM3) nn_limflx     = ', nn_limflx 
    138          WRITE(numout,*) '           Sea-ice : ' 
    139          WRITE(numout,*) '              ice management in the sbc (=0/1/2/3)       nn_ice        = ', nn_ice  
    140          WRITE(numout,*) '              ice-ocean embedded/levitating (=0/1/2)     nn_ice_embd   = ', nn_ice_embd 
    141          WRITE(numout,*) '           Misc. options of sbc : ' 
    142          WRITE(numout,*) '              Light penetration in temperature Eq.       ln_traqsr     = ', ln_traqsr 
    143          WRITE(numout,*) '                 daily mean to diurnal cycle qsr            ln_dm2dc   = ', ln_dm2dc  
    144          WRITE(numout,*) '              Sea Surface Restoring on SST and/or SSS    ln_ssr        = ', ln_ssr 
    145          WRITE(numout,*) '              FreshWater Budget control  (=0/1/2)        nn_fwb        = ', nn_fwb 
    146          WRITE(numout,*) '              Patm gradient added in ocean & ice Eqs.    ln_apr_dyn    = ', ln_apr_dyn 
    147          WRITE(numout,*) '              runoff / runoff mouths                     ln_rnf        = ', ln_rnf 
    148          WRITE(numout,*) '              iceshelf formulation                       ln_isf        = ', ln_isf 
    149          WRITE(numout,*) '              closed sea (=0/1) (set in namdom)          nn_closea     = ', nn_closea 
    150          WRITE(numout,*) '              nb of iterations if land-sea-mask applied  nn_lsm        = ', nn_lsm 
    151          WRITE(numout,*) '              surface wave                               ln_wave       = ', ln_wave   
     124         WRITE(numout,*) '   Namelist namsbc (partly overwritten with CPP key setting)' 
     125         WRITE(numout,*) '      Frequency update of sbc (and ice)             nn_fsbc       = ', nn_fsbc 
     126         WRITE(numout,*) '      Type of air-sea fluxes : ' 
     127         WRITE(numout,*) '         user defined formulation                   ln_usr        = ', ln_usr 
     128         WRITE(numout,*) '         flux         formulation                   ln_flx        = ', ln_flx 
     129         WRITE(numout,*) '         CLIO bulk    formulation                   ln_blk_clio   = ', ln_blk_clio 
     130         WRITE(numout,*) '         CORE bulk    formulation                   ln_blk_core   = ', ln_blk_core 
     131         WRITE(numout,*) '         MFS  bulk    formulation                   ln_blk_mfs    = ', ln_blk_mfs 
     132         WRITE(numout,*) '      Type of coupling (Ocean/Ice/Atmosphere) : ' 
     133         WRITE(numout,*) '         ocean-atmosphere coupled formulation       ln_cpl        = ', ln_cpl 
     134         WRITE(numout,*) '         forced-coupled mixed formulation           ln_mixcpl     = ', ln_mixcpl 
     135         WRITE(numout,*) '         OASIS coupling (with atm or sas)           lk_oasis      = ', lk_oasis 
     136         WRITE(numout,*) '         components of your executable              nn_components = ', nn_components 
     137         WRITE(numout,*) '         Multicategory heat flux formulation (LIM3) nn_limflx     = ', nn_limflx 
     138         WRITE(numout,*) '      Sea-ice : ' 
     139         WRITE(numout,*) '         ice management in the sbc (=0/1/2/3)       nn_ice        = ', nn_ice  
     140         WRITE(numout,*) '         ice-ocean embedded/levitating (=0/1/2)     nn_ice_embd   = ', nn_ice_embd 
     141         WRITE(numout,*) '      Misc. options of sbc : ' 
     142         WRITE(numout,*) '         Light penetration in temperature Eq.       ln_traqsr     = ', ln_traqsr 
     143         WRITE(numout,*) '            daily mean to diurnal cycle qsr            ln_dm2dc   = ', ln_dm2dc  
     144         WRITE(numout,*) '         Sea Surface Restoring on SST and/or SSS    ln_ssr        = ', ln_ssr 
     145         WRITE(numout,*) '         FreshWater Budget control  (=0/1/2)        nn_fwb        = ', nn_fwb 
     146         WRITE(numout,*) '         Patm gradient added in ocean & ice Eqs.    ln_apr_dyn    = ', ln_apr_dyn 
     147         WRITE(numout,*) '         runoff / runoff mouths                     ln_rnf        = ', ln_rnf 
     148         WRITE(numout,*) '         iceshelf formulation                       ln_isf        = ', ln_isf 
     149         WRITE(numout,*) '         closed sea (=0/1) (set in namdom)          nn_closea     = ', nn_closea 
     150         WRITE(numout,*) '         nb of iterations if land-sea-mask applied  nn_lsm        = ', nn_lsm 
     151         WRITE(numout,*) '         surface wave                               ln_wave       = ', ln_wave   
     152      ENDIF 
     153      ! 
     154      IF( .NOT.ln_usr ) THEN     ! the model calendar needs some specificities (except in user defined case) 
     155         IF( MOD( rday , rdt ) /= 0. )   CALL ctl_stop( 'the time step must devide the number of second of in a day' ) 
     156         IF( MOD( rday , 2.  ) /= 0. )   CALL ctl_stop( 'the number of second of in a day must be an even number'    ) 
     157         IF( MOD( rdt  , 2.  ) /= 0. )   CALL ctl_stop( 'the time step (in second) must be an even number'           ) 
    152158      ENDIF 
    153159      ! 
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/SBC/sbcssm.F90

    r6140 r6900  
    4646      !!                 
    4747      !! ** Method  :   compute mean surface velocity (2 components at U and  
    48       !!      V-points) [m/s], temperature [Celcius] and salinity [psu] over 
     48      !!      V-points) [m/s], temperature [Celsius] and salinity [psu] over 
    4949      !!      the periode (kt - nn_fsbc) to kt 
    5050      !!         Note that the inverse barometer ssh (i.e. ssh associated with Patm) 
     
    137137            !                                             ! ---------------------------------------- ! 
    138138            zcoef = 1. / REAL( nn_fsbc, wp ) 
    139             sst_m(:,:) = sst_m(:,:) * zcoef     ! mean SST             [Celcius] 
     139            sst_m(:,:) = sst_m(:,:) * zcoef     ! mean SST             [Celsius] 
    140140            sss_m(:,:) = sss_m(:,:) * zcoef     ! mean SSS             [psu] 
    141141            ssu_m(:,:) = ssu_m(:,:) * zcoef     ! mean suface current  [m/s] 
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/TRA/eosbn2.F90

    r6140 r6900  
    195195      !! 
    196196      !!     nn_eos = -1 : polynomial TEOS-10 equation of state is used for rho(t,s,z). 
    197       !!         Check value: rho = 1028.21993233072 kg/m^3 for z=3000 dbar, ct=3 Celcius, sa=35.5 g/kg 
     197      !!         Check value: rho = 1028.21993233072 kg/m^3 for z=3000 dbar, ct=3 Celsius, sa=35.5 g/kg 
    198198      !! 
    199199      !!     nn_eos =  0 : polynomial EOS-80 equation of state is used for rho(t,s,z). 
    200       !!         Check value: rho = 1028.35011066567 kg/m^3 for z=3000 dbar, pt=3 Celcius, sp=35.5 psu 
     200      !!         Check value: rho = 1028.35011066567 kg/m^3 for z=3000 dbar, pt=3 Celsius, sp=35.5 psu 
    201201      !! 
    202202      !!     nn_eos =  1 : simplified equation of state 
     
    212212      !!                TEOS-10 Manual, 2010 
    213213      !!---------------------------------------------------------------------- 
    214       REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(in   ) ::   pts   ! 1 : potential temperature  [Celcius] 
     214      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(in   ) ::   pts   ! 1 : potential temperature  [Celsius] 
    215215      !                                                               ! 2 : salinity               [psu] 
    216216      REAL(wp), DIMENSION(jpi,jpj,jpk     ), INTENT(  out) ::   prd   ! in situ density            [-] 
     
    307307      !! 
    308308      !!---------------------------------------------------------------------- 
    309       REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(in   ) ::   pts    ! 1 : potential temperature  [Celcius] 
     309      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(in   ) ::   pts    ! 1 : potential temperature  [Celsius] 
    310310      !                                                                ! 2 : salinity               [psu] 
    311311      REAL(wp), DIMENSION(jpi,jpj,jpk     ), INTENT(  out) ::   prd    ! in situ density            [-] 
     
    472472      !! 
    473473      !!---------------------------------------------------------------------- 
    474       REAL(wp), DIMENSION(jpi,jpj,jpts), INTENT(in   ) ::   pts   ! 1 : potential temperature  [Celcius] 
     474      REAL(wp), DIMENSION(jpi,jpj,jpts), INTENT(in   ) ::   pts   ! 1 : potential temperature  [Celsius] 
    475475      !                                                           ! 2 : salinity               [psu] 
    476476      REAL(wp), DIMENSION(jpi,jpj)     , INTENT(in   ) ::   pdep  ! depth                      [m] 
     
    897897      !! 
    898898      !!---------------------------------------------------------------------- 
    899       REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(in   ) ::  pts   ! pot. temperature and salinity   [Celcius,psu] 
    900       REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(in   ) ::  pab   ! thermal/haline expansion coef.  [Celcius-1,psu-1] 
     899      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(in   ) ::  pts   ! pot. temperature and salinity   [Celsius,psu] 
     900      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(in   ) ::  pab   ! thermal/haline expansion coef.  [Celsius-1,psu-1] 
    901901      REAL(wp), DIMENSION(jpi,jpj,jpk     ), INTENT(  out) ::  pn2   ! Brunt-Vaisala frequency squared [1/s^2] 
    902902      ! 
     
    934934      !!                 ***  ROUTINE eos_pt_from_ct  *** 
    935935      !! 
    936       !! ** Purpose :   Compute pot.temp. from cons. temp. [Celcius] 
     936      !! ** Purpose :   Compute pot.temp. from cons. temp. [Celsius] 
    937937      !! 
    938938      !! ** Method  :   rational approximation (5/3th order) of TEOS-10 algorithm 
     
    942942      !!                Rational approximation to TEOS10 algorithm (rms error on WOA13 values: 4.0e-5 degC) 
    943943      !!---------------------------------------------------------------------- 
    944       REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) ::   ctmp   ! Cons. Temp [Celcius] 
     944      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) ::   ctmp   ! Cons. Temp 
     945[Celsius] 
    945946      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) ::   psal   ! salinity   [psu] 
    946947      ! Leave result array automatic rather than making explicitly allocated 
    947       REAL(wp), DIMENSION(jpi,jpj) ::   ptmp   ! potential temperature [Celcius] 
     948      REAL(wp), DIMENSION(jpi,jpj) ::   ptmp   ! potential temperature [Celsius] 
    948949      ! 
    949950      INTEGER  ::   ji, jj               ! dummy loop indices 
     
    993994      !!                 ***  ROUTINE eos_fzp  *** 
    994995      !! 
    995       !! ** Purpose :   Compute the freezing point temperature [Celcius] 
    996       !! 
    997       !! ** Method  :   UNESCO freezing point (ptf) in Celcius is given by 
     996      !! ** Purpose :   Compute the freezing point temperature [Celsius] 
     997      !! 
     998      !! ** Method  :   UNESCO freezing point (ptf) in Celsius is given by 
    998999      !!       ptf(t,z) = (-.0575+1.710523e-3*sqrt(abs(s))-2.154996e-4*s)*s - 7.53e-4*z 
    9991000      !!       checkvalue: tf=-2.588567 Celsius for s=40psu, z=500m 
     
    10031004      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   )           ::   psal   ! salinity   [psu] 
    10041005      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ), OPTIONAL ::   pdep   ! depth      [m] 
    1005       REAL(wp), DIMENSION(jpi,jpj), INTENT(out  )           ::   ptf    ! freezing temperature [Celcius] 
     1006      REAL(wp), DIMENSION(jpi,jpj), INTENT(out  )           ::   ptf    ! freezing temperature [Celsius] 
    10061007      ! 
    10071008      INTEGER  ::   ji, jj   ! dummy loop indices 
     
    10441045      !!                 ***  ROUTINE eos_fzp  *** 
    10451046      !! 
    1046       !! ** Purpose :   Compute the freezing point temperature [Celcius] 
    1047       !! 
    1048       !! ** Method  :   UNESCO freezing point (ptf) in Celcius is given by 
     1047      !! ** Purpose :   Compute the freezing point temperature [Celsius] 
     1048      !! 
     1049      !! ** Method  :   UNESCO freezing point (ptf) in Celsius is given by 
    10491050      !!       ptf(t,z) = (-.0575+1.710523e-3*sqrt(abs(s))-2.154996e-4*s)*s - 7.53e-4*z 
    10501051      !!       checkvalue: tf=-2.588567 Celsius for s=40psu, z=500m 
     
    10541055      REAL(wp), INTENT(in )           ::   psal         ! salinity   [psu] 
    10551056      REAL(wp), INTENT(in ), OPTIONAL ::   pdep         ! depth      [m] 
    1056       REAL(wp), INTENT(out)           ::   ptf          ! freezing temperature [Celcius] 
     1057      REAL(wp), INTENT(out)           ::   ptf          ! freezing temperature [Celsius] 
    10571058      ! 
    10581059      REAL(wp) :: zs   ! local scalars 
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/TRA/traadv_fct.F90

    r6140 r6900  
    149149            DO jj = 2, jpjm1 
    150150               DO ji = fs_2, fs_jpim1   ! vector opt. 
    151                   ! total intermediate advective trends 
     151                  !                             ! total intermediate advective trends 
    152152                  ztra = - (  zwx(ji,jj,jk) - zwx(ji-1,jj  ,jk  )   & 
    153153                     &      + zwy(ji,jj,jk) - zwy(ji  ,jj-1,jk  )   & 
    154                      &      + zwz(ji,jj,jk) - zwz(ji  ,jj  ,jk+1) ) * r1_e1e2t(ji,jj) / e3t_n(ji,jj,jk) 
    155                   ! update and guess with monotonic sheme 
    156 !!gm why tmask added in the two following lines ???    the mask is done in tranxt ! 
    157                   pta(ji,jj,jk,jn) =   pta(ji,jj,jk,jn)         + ztra   * tmask(ji,jj,jk) 
    158                   zwi(ji,jj,jk)    = ( ptb(ji,jj,jk,jn) + p2dt * ztra ) * tmask(ji,jj,jk) 
     154                     &      + zwz(ji,jj,jk) - zwz(ji  ,jj  ,jk+1) ) * r1_e1e2t(ji,jj) 
     155                  !                             ! update and guess with monotonic sheme 
     156                  pta(ji,jj,jk,jn) =                     pta(ji,jj,jk,jn) +        ztra   / e3t_n(ji,jj,jk) * tmask(ji,jj,jk) 
     157                  zwi(ji,jj,jk)    = ( e3t_b(ji,jj,jk) * ptb(ji,jj,jk,jn) + p2dt * ztra ) / e3t_a(ji,jj,jk) * tmask(ji,jj,jk) 
    159158               END DO 
    160159            END DO 
     
    163162         !                 
    164163         IF( l_trd )  THEN             ! trend diagnostics (contribution of upstream fluxes) 
    165             ztrdx(:,:,:) = zwx(:,:,:)   ;    ztrdy(:,:,:) = zwy(:,:,:)  ;   ztrdz(:,:,:) = zwz(:,:,:) 
     164            ztrdx(:,:,:) = zwx(:,:,:)   ;   ztrdy(:,:,:) = zwy(:,:,:)   ;   ztrdz(:,:,:) = zwz(:,:,:) 
    166165         END IF 
    167166         !                             ! "Poleward" heat and salt transports (contribution of upstream fluxes) 
     
    364363      ! 
    365364      CALL wrk_alloc( jpi,jpj,             zwx_sav, zwy_sav ) 
    366       CALL wrk_alloc( jpi,jpj, jpk,        zwx, zwy, zwz, zwi, zhdiv, zwzts, zwz_sav ) 
     365      CALL wrk_alloc( jpi,jpj,jpk,         zwx, zwy, zwz, zwi, zhdiv, zwzts, zwz_sav ) 
    367366      CALL wrk_alloc( jpi,jpj,jpk,kjpt+1,  ztrs ) 
    368367      ! 
     
    436435                  ztra = - (  zwx(ji,jj,jk) - zwx(ji-1,jj  ,jk  )   & 
    437436                     &      + zwy(ji,jj,jk) - zwy(ji  ,jj-1,jk  )   & 
    438                      &      + zwz(ji,jj,jk) - zwz(ji  ,jj  ,jk+1)   ) * r1_e1e2t(ji,jj) / e3t_n(ji,jj,jk) 
     437                     &      + zwz(ji,jj,jk) - zwz(ji  ,jj  ,jk+1)   ) * r1_e1e2t(ji,jj) 
    439438                  !                             ! update and guess with monotonic sheme 
    440                   pta(ji,jj,jk,jn) =   pta(ji,jj,jk,jn)         + ztra 
    441                   zwi(ji,jj,jk)    = ( ptb(ji,jj,jk,jn) + p2dt * ztra ) * tmask(ji,jj,jk) 
     439                  pta(ji,jj,jk,jn) =                     pta(ji,jj,jk,jn) +        ztra   / e3t_n(ji,jj,jk) * tmask(ji,jj,jk) 
     440                  zwi(ji,jj,jk)    = ( e3t_b(ji,jj,jk) * ptb(ji,jj,jk,jn) + p2dt * ztra ) / e3t_a(ji,jj,jk) * tmask(ji,jj,jk) 
    442441               END DO 
    443442            END DO 
     
    488487         zwz_sav(:,:,:)   = zwz(:,:,:) 
    489488         ztrs   (:,:,:,1) = ptb(:,:,:,jn) 
     489         ztrs   (:,:,1,2) = ptb(:,:,1,jn) 
     490         ztrs   (:,:,1,3) = ptb(:,:,1,jn) 
    490491         zwzts  (:,:,:)   = 0._wp 
    491492         ! 
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/USR/usrdef_istate.F90

    r6893 r6900  
    4040      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   pdept   ! depth of t-point               [m] 
    4141      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(in   ) ::   ptmask  ! t-point ocean mask             [m] 
    42       REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(  out) ::   pts     ! T & S fields      [Celcius ; g/kg] 
     42      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(  out) ::   pts     ! T & S fields      [Celsius ; g/kg] 
    4343      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(  out) ::   pu      ! i-component of the velocity  [m/s]  
    4444      REAL(wp), DIMENSION(jpi,jpj,jpk)     , INTENT(  out) ::   pv      ! j-component of the velocity  [m/s]  
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/oce.F90

    r6140 r6900  
    2323   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::           wn             !: vertical velocity            [m/s] 
    2424   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::           hdivn          !: horizontal divergence        [s-1] 
    25    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   tsb  ,  tsn   , tsa    !: 4D T-S fields                  [Celcius,psu]  
    26    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   rab_b,  rab_n          !: thermal/haline expansion coef. [Celcius-1,psu-1] 
     25   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   tsb  ,  tsn   , tsa    !: 4D T-S fields                  [Celsius,psu]  
     26   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   rab_b,  rab_n          !: thermal/haline expansion coef. [Celsius-1,psu-1] 
    2727   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   rn2b ,  rn2            !: brunt-vaisala frequency**2     [s-2] 
    2828   ! 
Note: See TracChangeset for help on using the changeset viewer.