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 2148 for branches/DEV_r2106_LOCEAN2010/NEMO/OPA_SRC/SBC – NEMO

Ignore:
Timestamp:
2010-10-04T15:53:42+02:00 (14 years ago)
Author:
cetlod
Message:

merge LOCEAN 2010 developments branches

Location:
branches/DEV_r2106_LOCEAN2010/NEMO/OPA_SRC/SBC
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • branches/DEV_r2106_LOCEAN2010/NEMO/OPA_SRC/SBC/sbc_oce.F90

    r2000 r2148  
    66   !! History :  3.0   !  2006-06  (G. Madec)  Original code 
    77   !!             -    !  2008-08  (G. Madec)  namsbc moved from sbcmod 
     8   !!            3.3   !  2010-04  (M. Leclair, G. Madec)  Forcing averaged over 2 time steps 
    89   !!---------------------------------------------------------------------- 
    910   USE par_oce          ! ocean parameters 
     
    3738   !!              Ocean Surface Boundary Condition fields 
    3839   !!---------------------------------------------------------------------- 
    39    LOGICAL , PUBLIC ::   lhftau = .FALSE.              !: HF tau contribution: mean of stress module - module of the mean stress 
    40    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   utau      !: sea surface i-stress (ocean referential)     [N/m2] 
    41    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   vtau      !: sea surface j-stress (ocean referential)     [N/m2] 
    42    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   taum      !: module of sea surface stress (at T-point)    [N/m2]  
    43    !! wndm is used only in PISCES to compute gases exchanges at the surface of the free ocean or in the leads in sea-ice parts 
    44    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   wndm      !: wind speed module at T-point (=|U10m-Uoce|)  [m/s]  
    45    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qsr       !: sea heat flux:     solar                     [W/m2] 
    46    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qns       !: sea heat flux: non solar                     [W/m2] 
    47    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qsr_tot   !: total     solar heat flux (over sea and ice) [W/m2] 
    48    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qns_tot   !: total non solar heat flux (over sea and ice) [W/m2] 
    49    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   emp       !: freshwater budget: volume flux               [Kg/m2/s] 
    50    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   emps      !: freshwater budget: concentration/dillution   [Kg/m2/s] 
    51    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rnf       !: river runoff   [Kg/m2/s]   
    52    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   emp_tot   !: total evaporation - (liquid + solid) precpitation over oce and ice 
    53    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   tprecip   !: total precipitation           [Kg/m2/s] 
    54    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   sprecip   !: solid precipitation           [Kg/m2/s] 
    55 !!$   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rrunoff       !: runoff 
    56 !!$   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   calving       !: calving 
    57    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   fr_i      !: ice fraction  (between 0 to 1)               - 
     40   LOGICAL , PUBLIC ::   lhftau = .FALSE.              !: HF tau used in TKE: mean(stress module) - module(mean stress) 
     41   !!                                   !!   now    ! before   !! 
     42   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   utau   , utau_b   !: sea surface i-stress (ocean referential)     [N/m2] 
     43   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   vtau   , vtau_b   !: sea surface j-stress (ocean referential)     [N/m2] 
     44   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   taum              !: module of sea surface stress (at T-point)    [N/m2]  
     45   !! wndm is used only in PISCES to compute surface gases exchanges in ice-free ocean or leads 
     46   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   wndm              !: wind speed module at T-point (=|U10m-Uoce|)  [m/s] 
     47   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qsr               !: sea heat flux:     solar                     [W/m2] 
     48   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qns    , qns_b    !: sea heat flux: non solar                     [W/m2] 
     49   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qsr_tot           !: total     solar heat flux (over sea and ice) [W/m2] 
     50   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qns_tot           !: total non solar heat flux (over sea and ice) [W/m2] 
     51   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   emp    , emp_b    !: freshwater budget: volume flux               [Kg/m2/s] 
     52   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   emps   , emps_b   !: freshwater budget: concentration/dillution   [Kg/m2/s] 
     53   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   emp_tot           !: total E-P over ocean and ice                 [Kg/m2/s] 
     54   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rnf               !: river runoff   [Kg/m2/s]   
     55   ! - ML - begin 
     56   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   sbc_hc_n          !: sbc heat content trend now                   [K.m/s] 
     57   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   sbc_hc_b          !:  "   "      "      "   before                   " 
     58   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   sbc_sc_n          !: sbc salt content trend now                   [psu.m/s] 
     59   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   sbc_sc_b          !:  "   "      "      "   before                   " 
     60   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   qsr_hc_n      !: heat content trend due to qsr flux now       [K.m/s] 
     61   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   qsr_hc_b      !:  "      "      "    "  "   "   "   before       " 
     62   ! - ML - end 
     63   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   tprecip           !: total precipitation                          [Kg/m2/s] 
     64   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   sprecip           !: solid precipitation                          [Kg/m2/s] 
     65   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   fr_i              !: ice fraction = 1 - lead fraction      (between 0 to 1) 
    5866#if defined key_cpl_carbon_cycle 
    59    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   atm_co2   !: atmospheric pCO2                             [ppm] 
     67   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   atm_co2           !: atmospheric pCO2                             [ppm] 
    6068#endif 
     69!!$   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rrunoff        !: runoff 
     70!!$   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   calving        !: calving 
    6171 
    6272   !!---------------------------------------------------------------------- 
     
    7181 
    7282   !!---------------------------------------------------------------------- 
    73    !!   OPA 9.0 , LOCEAN-IPSL (2006)  
    74    !! $ Id: $ 
     83   !! NEMO/OPA 3.3 , LOCEAN-IPSL (2010)  
     84   !! $Id$ 
    7585   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    7686   !!====================================================================== 
    77  
    7887END MODULE sbc_oce 
  • branches/DEV_r2106_LOCEAN2010/NEMO/OPA_SRC/SBC/sbcmod.F90

    r2000 r2148  
    44   !! Surface module :  provide to the ocean its surface boundary condition 
    55   !!====================================================================== 
    6    !! History :  3.0   !  07-2006  (G. Madec)  Original code 
    7    !!             -    !  08-2008  (S. Masson, E. .... ) coupled interface 
     6   !! History :  3.0  !  2006-07  (G. Madec)  Original code 
     7   !!            3.1  !  2008-08  (S. Masson, E. Maisonnave, G. Madec) coupled interface 
     8   !!            3.3  !  2010-04  (M. Leclair, G. Madec)  Forcing averaged over 2 time steps 
    89   !!---------------------------------------------------------------------- 
    910 
     
    4950#  include "domzgr_substitute.h90" 
    5051   !!---------------------------------------------------------------------- 
    51    !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)  
     52   !! NEMO/OPA 3.3 , LOCEAN-IPSL (2010)  
    5253   !! $Id$ 
    5354   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     
    8687!!gm  IF( lk_sbc_cpl       ) THEN   ;   ln_cpl      = .TRUE.   ;   ELSE   ;   ln_cpl      = .FALSE.   ;   ENDIF 
    8788 
    88       IF ( Agrif_Root() ) THEN 
     89      IF( Agrif_Root() ) THEN 
    8990        IF( lk_lim2 )            nn_ice      = 2 
    9091        IF( lk_lim3 )            nn_ice      = 3 
     
    179180      !!                CAUTION : never mask the surface stress field (tke sbc) 
    180181      !! 
    181       !! ** Action  : - set the ocean surface boundary condition, i.e.   
    182       !!                utau, vtau, qns, qsr, emp, emps, qrp, erp 
     182      !! ** Action  : - set the ocean surface boundary condition at before and now  
     183      !!                time step, i.e.   
     184      !!                utau_b, vtau_b, qns_b, qsr_b, emp_n, emps_b, qrp_b, erp_b 
     185      !!                utau  , vtau  , qns  , qsr  , emp  , emps  , qrp  , erp 
    183186      !!              - updte the ice fraction : fr_i 
    184187      !!---------------------------------------------------------------------- 
     
    186189      !!--------------------------------------------------------------------- 
    187190 
    188       CALL iom_setkt( kt + nn_fsbc - 1 )         !  in sbc, iom_put is called every nn_fsbc time step 
    189       ! 
    190       ! ocean to sbc mean sea surface variables (ss._m) 
    191       ! --------------------------------------- 
    192       CALL sbc_ssm( kt )                         ! sea surface mean currents (at U- and V-points),  
    193       !                                          ! temperature and salinity (at T-point) over nf_sbc time-step 
    194       !                                          ! (i.e. sst_m, sss_m, ssu_m, ssv_m) 
    195  
    196       ! sbc formulation 
    197       ! --------------- 
    198           
    199       SELECT CASE( nsbc )                        ! Compute ocean surface boundary condition 
    200       !                                          ! (i.e. utau,vtau, qns, qsr, emp, emps) 
     191      !                                            ! ---------------------------------------- ! 
     192      IF( kt /= nit000 ) THEN                      !          Swap of forcing fields          ! 
     193         !                                         ! ---------------------------------------- ! 
     194         utau_b(:,:) = utau(:,:)                         ! Swap the ocean forcing fields 
     195         vtau_b(:,:) = vtau(:,:)                         ! (except at nit000 where before fields 
     196         qns_b (:,:) = qns (:,:)                         !  are set at the end of the routine) 
     197         ! The 3D heat content due to qsr forcing is treated in traqsr 
     198         ! qsr_b (:,:) = qsr (:,:) 
     199         emp_b (:,:) = emp (:,:) 
     200         emps_b(:,:) = emps(:,:) 
     201      ENDIF 
     202      !                                            ! ---------------------------------------- ! 
     203      !                                            !        forcing field computation         ! 
     204      !                                            ! ---------------------------------------- ! 
     205 
     206      CALL iom_setkt( kt + nn_fsbc - 1 )                 ! in sbc, iom_put is called every nn_fsbc time step 
     207      ! 
     208      CALL sbc_ssm( kt )                                 ! ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m) 
     209      !                                                  ! averaged over nf_sbc time-step 
     210 
     211                                                   !==  sbc formulation  ==! 
     212                                                             
     213      SELECT CASE( nsbc )                                ! Compute ocean surface boundary condition 
     214      !                                                  ! (i.e. utau,vtau, qns, qsr, emp, emps) 
    201215      CASE(  0 )   ;   CALL sbc_gyre    ( kt )                    ! analytical formulation : GYRE configuration 
    202216      CASE(  1 )   ;   CALL sbc_ana     ( kt )                    ! analytical formulation : uniform sbc 
     
    214228      END SELECT 
    215229 
    216       ! Misc. Options 
    217       ! ------------- 
     230      !                                            !==  Misc. Options  ==! 
    218231 
    219232!!gm  IF( ln_dm2dc       )   CALL sbc_dcy( kt )                 ! Daily mean qsr distributed over the Diurnal Cycle 
     
    236249      !                                                         ! (update freshwater fluxes) 
    237250      ! 
     251      IF( kt == nit000 ) THEN                          !   set the forcing field at nit000 - 1    ! 
     252         !                                             ! ---------------------------------------- ! 
     253         IF( ln_rstart .AND.    &                               !* Restart: read in restart file 
     254            & iom_varid( numror, 'utau_b', ldstop = .FALSE. ) > 0 ) THEN  
     255            IF(lwp) WRITE(numout,*) '          nit000-1 surface forcing fields red in the restart file' 
     256            CALL iom_get( numror, jpdom_autoglo, 'utau_b', utau_b )   ! before i-stress  (U-point) 
     257            CALL iom_get( numror, jpdom_autoglo, 'vtau_b', vtau_b )   ! before j-stress  (V-point) 
     258            CALL iom_get( numror, jpdom_autoglo, 'qns_b' , qns_b  )   ! before non solar heat flux (T-point) 
     259            ! The 3D heat content due to qsr forcing is treated in traqsr 
     260            ! CALL iom_get( numror, jpdom_autoglo, 'qsr_b' , qsr_b  )   ! before     solar heat flux (T-point) 
     261            CALL iom_get( numror, jpdom_autoglo, 'emp_b' , emp_b  )   ! before     freshwater flux (T-point) 
     262            CALL iom_get( numror, jpdom_autoglo, 'emps_b', emps_b )   ! before C/D freshwater flux (T-point) 
     263         ELSE                                                   !* no restart: set from nit000 values 
     264            IF(lwp) WRITE(numout,*) '          nit000-1 surface forcing fields set to nit000' 
     265            utau_b(:,:) = utau(:,:)  
     266            vtau_b(:,:) = vtau(:,:) 
     267            qns_b (:,:) = qns (:,:) 
     268            ! qsr_b (:,:) = qsr (:,:) 
     269            emp_b (:,:) = emp (:,:) 
     270            emps_b(:,:) = emps(:,:) 
     271         ENDIF 
     272      ENDIF 
     273      !                                                ! ---------------------------------------- ! 
     274      IF( lrst_oce ) THEN                              !      Write in the ocean restart file     ! 
     275         !                                             ! ---------------------------------------- ! 
     276         IF(lwp) WRITE(numout,*) 
     277         IF(lwp) WRITE(numout,*) 'sbc : ocean surface forcing fields written in ocean restart file ',   & 
     278            &                    'at it= ', kt,' date= ', ndastp 
     279         IF(lwp) WRITE(numout,*) '~~~~' 
     280         CALL iom_rstput( kt, nitrst, numrow, 'utau_b' , utau ) 
     281         CALL iom_rstput( kt, nitrst, numrow, 'vtau_b' , vtau ) 
     282         CALL iom_rstput( kt, nitrst, numrow, 'qns_b'  , qns  ) 
     283         ! The 3D heat content due to qsr forcing is treated in traqsr 
     284         ! CALL iom_rstput( kt, nitrst, numrow, 'qsr_b'  , qsr  ) 
     285         CALL iom_rstput( kt, nitrst, numrow, 'emp_b'  , emp  ) 
     286         CALL iom_rstput( kt, nitrst, numrow, 'emps_b' , emps ) 
     287      ENDIF 
     288 
     289      !                                                ! ---------------------------------------- ! 
     290      !                                                !        Outputs and control print         ! 
     291      !                                                ! ---------------------------------------- ! 
    238292      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN 
    239          CALL iom_put( "emp-rnf"  , (emp-rnf)  )                ! upward water flux  
    240          CALL iom_put( "emps-rnf" , (emps-rnf) )                ! c/d water flux  
    241          CALL iom_put( "qns+qsr"  , qns + qsr  )                ! total heat flux   (caution if ln_dm2dc=true, to be  
    242          CALL iom_put( "qns"      , qns        )                ! solar heat flux    moved after the call to iom_setkt) 
    243          CALL iom_put( "qsr"      ,       qsr  )                ! solar heat flux    moved after the call to iom_setkt) 
    244          IF(  nn_ice > 0 )   CALL iom_put( "ice_cover", fr_i )  ! ice fraction  
     293         CALL iom_put( "emp-rnf" , emp  - rnf )                   ! upward water flux 
     294         CALL iom_put( "emps-rnf", emps - rnf )                   ! c/d water flux 
     295         CALL iom_put( "qns+qsr" , qns  + qsr )                   ! total heat flux   (caution if ln_dm2dc=true, to be  
     296         CALL iom_put( "qns"     , qns        )                   ! solar heat flux    moved after the call to iom_setkt) 
     297         CALL iom_put( "qsr"     ,       qsr  )                   ! solar heat flux    moved after the call to iom_setkt) 
     298         IF( nn_ice > 0 )   CALL iom_put( "ice_cover", fr_i )   ! ice fraction  
    245299      ENDIF 
    246300      ! 
     
    253307      ! 
    254308      IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    255          CALL prt_ctl(tab2d_1=fr_i   , clinfo1=' fr_i - : ', mask1=tmask, ovlap=1 ) 
    256          CALL prt_ctl(tab2d_1=(emp-rnf) , clinfo1=' emp-rnf  - : ', mask1=tmask, ovlap=1 )  
    257          CALL prt_ctl(tab2d_1=(emps-rnf), clinfo1=' emps-rnf - : ', mask1=tmask, ovlap=1 )  
    258          CALL prt_ctl(tab2d_1=qns    , clinfo1=' qns  - : ', mask1=tmask, ovlap=1 ) 
    259          CALL prt_ctl(tab2d_1=qsr    , clinfo1=' qsr  - : ', mask1=tmask, ovlap=1 ) 
    260          CALL prt_ctl(tab3d_1=tmask  , clinfo1=' tmask : ', mask1=tmask, ovlap=1, kdim=jpk ) 
    261          CALL prt_ctl(tab3d_1=tn     , clinfo1=' sst  - : ', mask1=tmask, ovlap=1, kdim=1   ) 
    262          CALL prt_ctl(tab3d_1=sn     , clinfo1=' sss  - : ', mask1=tmask, ovlap=1, kdim=1   ) 
    263          CALL prt_ctl(tab2d_1=utau   , clinfo1=' utau - : ', mask1=umask,                      & 
    264             &         tab2d_2=vtau   , clinfo2=' vtau - : ', mask2=vmask, ovlap=1 ) 
     309         CALL prt_ctl(tab2d_1=fr_i      , clinfo1=' fr_i    - : ', mask1=tmask, ovlap=1 ) 
     310         CALL prt_ctl(tab2d_1=(emp-rnf) , clinfo1=' emp-rnf  - : ', mask1=tmask, ovlap=1 ) 
     311         CALL prt_ctl(tab2d_1=(emps-rnf), clinfo1=' emps-rnf - : ', mask1=tmask, ovlap=1 ) 
     312         CALL prt_ctl(tab2d_1=qns       , clinfo1=' qns      - : ', mask1=tmask, ovlap=1 ) 
     313         CALL prt_ctl(tab2d_1=qsr       , clinfo1=' qsr      - : ', mask1=tmask, ovlap=1 ) 
     314         CALL prt_ctl(tab3d_1=tmask     , clinfo1=' tmask    - : ', mask1=tmask, ovlap=1, kdim=jpk ) 
     315         CALL prt_ctl(tab3d_1=tn        , clinfo1=' sst      - : ', mask1=tmask, ovlap=1, kdim=1   ) 
     316         CALL prt_ctl(tab3d_1=sn        , clinfo1=' sss      - : ', mask1=tmask, ovlap=1, kdim=1   ) 
     317         CALL prt_ctl(tab2d_1=utau      , clinfo1=' utau    - : ', mask1=umask,                      & 
     318            &         tab2d_2=vtau      , clinfo2=' vtau    - : ', mask2=vmask, ovlap=1 ) 
    265319      ENDIF 
    266320      ! 
  • branches/DEV_r2106_LOCEAN2010/NEMO/OPA_SRC/SBC/sbcrnf.F90

    r2113 r2148  
    3333   TYPE(FLD_N)       , PUBLIC ::   sn_cnf                 !: information about the runoff mouth file to be read 
    3434   TYPE(FLD_N)                ::   sn_sal_rnf             !: information about the salinities of runoff file to be read   
    35    TYPE(FLD_N)                ::   sn_tem_rnf             !: information about the temperatures of runoff file to be read   
     35   TYPE(FLD_N)                ::   sn_tmp_rnf             !: information about the temperatures of runoff file to be read   
    3636   TYPE(FLD_N)                ::   sn_dep_rnf             !: information about the depth which river inflow affects 
    3737   LOGICAL           , PUBLIC ::   ln_rnf_mouth = .false. !: specific treatment in mouths vicinity 
     
    5353   INTEGER, PUBLIC, DIMENSION(jpi,jpj) ::  rnf_mod_dep     !: depth of runoff in model levels   
    5454   REAL,    PUBLIC, DIMENSION(jpi,jpj) ::  rnf_sal         !: salinity of river runoff   
    55    REAL,    PUBLIC, DIMENSION(jpi,jpj) ::  rnf_tem         !: temperature of river runoff   
     55   REAL,    PUBLIC, DIMENSION(jpi,jpj) ::  rnf_tmp         !: temperature of river runoff   
    5656   
    5757   INTEGER  ::  ji, jj ,jk    ! dummy loop indices   
     
    8686      !!---------------------------------------------------------------------- 
    8787      !                                    
    88       IF( kt == nit000 ) THEN   
    89          CALL sbc_rnf_init                      ! Read namelist and allocate structures 
    90       ENDIF 
     88      IF( kt == nit000 )  CALL sbc_rnf_init     ! Read namelist and allocate structures  
    9189 
    9290      !                                                   !-------------------! 
     
    117115            IF ( ln_rnf_att ) THEN   
    118116               rnf_sal(:,:) = ( sf_sal_rnf(1)%fnow(:,:,1) )   
    119                rnf_tem(:,:) = ( sf_tem_rnf(1)%fnow(:,:,1) )   
     117               rnf_tmp(:,:) = ( sf_tem_rnf(1)%fnow(:,:,1) )   
    120118            ELSE   
    121119               rnf_sal(:,:) = 0   
    122                rnf_tem(:,:) = -999   
     120               rnf_tmp(:,:) = -999   
    123121            ENDIF   
    124122            CALL iom_put( "runoffs", rnf )         ! runoffs 
     
    143141      CHARACTER(len=32) ::   rn_dep_file   ! runoff file name   
    144142      !!  
    145       NAMELIST/namsbc_rnf/ cn_dir, ln_rnf_emp, sn_rnf, sn_cnf, sn_sal_rnf, sn_tem_rnf, sn_dep_rnf,   &   
     143      NAMELIST/namsbc_rnf/ cn_dir, ln_rnf_emp, sn_rnf, sn_cnf, sn_sal_rnf, sn_tmp_rnf, sn_dep_rnf,   &   
    146144         &                 ln_rnf_mouth, ln_rnf_att, rn_hrnf, rn_avt_rnf, rn_rfact   
    147145      !!---------------------------------------------------------------------- 
     
    157155 
    158156      sn_sal_rnf = FLD_N( 'runoffs',  24.  , 'rosaline' ,  .TRUE.    , .true. ,   'yearly'  , ''    , ''  )   
    159       sn_tem_rnf = FLD_N( 'runoffs',  24.  , 'rotemper' ,  .TRUE.    , .true. ,   'yearly'  , ''    , ''  )   
     157      sn_tmp_rnf = FLD_N( 'runoffs',  24.  , 'rotemper' ,  .TRUE.    , .true. ,   'yearly'  , ''    , ''  )   
    160158      sn_dep_rnf = FLD_N( 'runoffs',   0.  , 'rodepth'  ,  .FALSE.   , .true. ,   'yearly'  , ''    , ''  )   
    161159      ! 
     
    218216         IF ( ln_rnf_att ) THEN   
    219217            CALL fld_fill (sf_sal_rnf, (/ sn_sal_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff salinity data', 'namsbc_rnf' )   
    220             CALL fld_fill (sf_tem_rnf, (/ sn_tem_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff temperature data', 'namsbc_rnf' )   
     218            CALL fld_fill (sf_tem_rnf, (/ sn_tmp_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff temperature data', 'namsbc_rnf' )   
    221219   
    222220            rn_dep_file = TRIM( cn_dir )//TRIM( sn_dep_rnf%clname )   
     
    248246      ENDIF 
    249247      ! 
    250       DO jj = 1, jpj 
    251          DO ji = 1, jpi 
    252             rnf_dep(ji,jj) = 0. 
    253             DO jk = 1, rnf_mod_dep(ji,jj)                          ! recalculates rnf_dep to be the depth  
    254                rnf_dep(ji,jj) = rnf_dep(ji,jj) + fse3t(ji,jj,jk)    ! in metres to the bottom of the relevant grid box  
    255             ENDDO 
    256          ENDDO 
    257       ENDDO 
    258       !  
    259248 
    260249      !                                   ! ======================== 
Note: See TracChangeset for help on using the changeset viewer.