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 1938 for branches/DEV_R1821_Rivers/NEMO/OPA_SRC/TRA/trasbc.F90 – NEMO

Ignore:
Timestamp:
2010-06-16T16:34:29+02:00 (14 years ago)
Author:
rfurner
Message:

rnf has been separated from emp and emps. Also temperature and salinity of runoff can be specified, and runoff can be added to a user specified depth

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/DEV_R1821_Rivers/NEMO/OPA_SRC/TRA/trasbc.F90

    r1739 r1938  
    2121   USE in_out_manager  ! I/O manager 
    2222   USE prtctl          ! Print control 
     23   USE sbcrnf          ! River runoff   
     24   USE sbcmod          ! ln_rnf   
    2325 
    2426   IMPLICIT NONE 
     
    103105      INTEGER, INTENT(in) ::   kt     ! ocean time-step index 
    104106      !! 
    105       INTEGER  ::   ji, jj                   ! dummy loop indices 
    106       REAL(wp) ::   zta, zsa, zsrau, zse3t   ! temporary scalars 
     107      INTEGER  ::   ji, jj, jk           ! dummy loop indices   
     108      REAL(wp) ::   zta, zsa             ! temporary scalars, adjustment to temperature and salinity   
     109      REAL(wp) ::   azta, azsa           ! temporary scalars, calculations of automatic change to temp & sal due to vvl (done elsewhere)   
     110      REAL(wp) ::   zsrau, zse3t, zdep   ! temporary scalars, 1/density, 1/height of box, 1/height of effected water column   
     111      REAL(wp) ::   dheat, dsalt          ! total change of temperature and salinity   
     112      REAL(wp) ::   tot_sal1, tot_tmp1   
    107113      !!---------------------------------------------------------------------- 
    108114 
     
    125131      IF( .NOT.ln_traqsr )   qsr(:,:) = 0.e0   ! no solar radiation penetration 
    126132 
    127       ! Concentration dillution effect on (t,s) 
     133      ! Concentration dillution effect on (t,s) due to evapouration, precipitation and qns, but not river runoff   
    128134      DO jj = 2, jpj 
    129135         DO ji = fs_2, fs_jpim1   ! vector opt. 
     
    132138#endif 
    133139            IF( lk_vvl) THEN 
    134                zta = ro0cpr * qns(ji,jj) * zse3t &                   ! temperature : heat flux 
    135                 &    - emp(ji,jj) * zsrau * tn(ji,jj,1)  * zse3t     ! & cooling/heating effet of EMP flux 
     140               zta =  ro0cpr * qns(ji,jj) * zse3t &                  ! temperature : heat flux  
     141                &    - emp(ji,jj) * zsrau * tn(ji,jj,1) * zse3t      ! & cooling/heating effet of EMP flux  
    136142               zsa = 0.e0                                            ! No salinity concent./dilut. effect 
    137143            ELSE 
    138                zta = ro0cpr * qns(ji,jj) * zse3t     ! temperature : heat flux 
    139                zsa = emps(ji,jj) * zsrau * sn(ji,jj,1)   * zse3t     ! salinity :  concent./dilut. effect 
     144               zta =  ro0cpr * qns(ji,jj) * zse3t                    ! temperature : heat flux  
     145               zsa =  emps(ji,jj) * zsrau * sn(ji,jj,1) * zse3t      ! salinity :  concent./dilut. effect  
    140146            ENDIF 
    141147            ta(ji,jj,1) = ta(ji,jj,1) + zta                          ! add the trend to the general tracer trend 
     
    143149         END DO 
    144150      END DO 
     151 
     152      IF ( ln_rnf ) THEN   
     153      ! Concentration / dilution effect on (t,s) due to river runoff   
     154        DO jj=1,jpj   
     155           DO ji=1,jpi   
     156              rnf_dep(ji,jj)=0   
     157              DO jk=1,rnf_mod_dep(ji,jj)                          ! recalculates rnf_dep to be the depth   
     158                rnf_dep(ji,jj)=rnf_dep(ji,jj)+fse3t(ji,jj,jk)    ! in metres to the bottom of the relevant grid box   
     159              ENDDO   
     160              zdep = 1. / rnf_dep(ji,jj)   
     161              zse3t= 1. / fse3t(ji,jj,1)   
     162              IF ( rnf_tmp(ji,jj) == -999 )   rnf_tmp(ji,jj)=tn(ji,jj,1)        ! if not specified set runoff temp to be sst   
     163   
     164              IF ( rnf(ji,jj) .gt. 0.0 ) THEN   
     165   
     166                IF( lk_vvl) THEN   
     167                  !!!indirect flux, concentration or dilution effect   
     168                  !!!force a dilution effect in all levels;   
     169                  dheat=0.0   
     170                  dsalt=0.0   
     171                  DO jk=1, rnf_mod_dep(ji,jj)   
     172                    zta = -tn(ji,jj,jk) * rnf(ji,jj) * zsrau * zdep   
     173                    zsa = -sn(ji,jj,jk) * rnf(ji,jj) * zsrau * zdep   
     174                    ta(ji,jj,jk)=ta(ji,jj,jk)+zta   
     175                    sa(ji,jj,jk)=sa(ji,jj,jk)+zsa   
     176                    dheat=dheat+zta*fse3t(ji,jj,jk)   
     177                    dsalt=dsalt+zsa*fse3t(ji,jj,jk)   
     178                  ENDDO   
     179                  !!!negate this total change in heat and salt content from top level   
     180                  zta=-dheat*zse3t   
     181                  zsa=-dsalt*zse3t   
     182                  ta(ji,jj,1)=ta(ji,jj,1)+zta   
     183                  sa(ji,jj,1)=sa(ji,jj,1)+zsa   
     184     
     185                  !!!direct flux   
     186                  zta = rnf_tmp(ji,jj) * rnf(ji,jj) * zsrau * zdep   
     187                  zsa = rnf_sal(ji,jj) * rnf(ji,jj) * zsrau * zdep   
     188     
     189                  DO jk=1, rnf_mod_dep(ji,jj)   
     190                    ta(ji,jj,jk) = ta(ji,jj,jk) + zta   
     191                    sa(ji,jj,jk) = sa(ji,jj,jk) + zsa   
     192                  ENDDO   
     193    
     194                ELSE   
     195                  DO jk=1, rnf_mod_dep(ji,jj)   
     196                    zta = ( rnf_tmp(ji,jj)-tn(ji,jj,jk) ) * rnf(ji,jj) * zsrau * zdep   
     197                    zsa = ( rnf_sal(ji,jj)-sn(ji,jj,jk) ) * rnf(ji,jj) * zsrau * zdep   
     198                    ta(ji,jj,jk) = ta(ji,jj,jk) + zta   
     199                    sa(ji,jj,jk) = sa(ji,jj,jk) + zsa   
     200                  ENDDO   
     201                ENDIF   
     202   
     203              ELSEIF (rnf(ji,jj) .lt. 0.) THEN   !! for use in baltic when flow is out of domain, want no change in temp and sal   
     204   
     205                IF( lk_vvl) THEN   
     206                  !calculate automatic adjustment to sal and temp due to dilution/concentraion effect    
     207                  azta = -tn(ji,jj,1) * rnf(ji,jj) * zsrau * zse3t   
     208                  azsa = -sn(ji,jj,1) * rnf(ji,jj) * zsrau * zse3t   
     209                  !!!negate this change in sal and temp    
     210                  ta(ji,jj,1)=ta(ji,jj,1)-azta   
     211                  sa(ji,jj,1)=sa(ji,jj,1)-azsa   
     212                ENDIF   
     213   
     214              ENDIF   
     215   
     216           ENDDO   
     217        ENDDO   
     218        
     219      ENDIF   
    145220 
    146221      IF( l_trdtra ) THEN      ! save the sbc trends for diagnostic 
Note: See TracChangeset for help on using the changeset viewer.