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

Changeset 2171


Ignore:
Timestamp:
2010-10-06T17:31:19+02:00 (14 years ago)
Author:
rfurner
Message:

Some variables renamed and some calculations moved to different modules following comments from Gurvan

Location:
branches/DEV_R1821_Rivers/NEMO/OPA_SRC
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • branches/DEV_R1821_Rivers/NEMO/OPA_SRC/DYN/divcur.F90

    r2118 r2171  
    1616   USE bdy_oce        ! Unstructured open boundaries variables 
    1717   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    18    USE sbcrnf, ONLY  : rnf_dep, rnf_mod_dep  ! River runoff 
    19    USE phycst,  ONLY : rau0                  ! physical constant 
    20    USE sbc_oce, ONLY : ln_rnf, rnf           ! surface boundary condition: ocean 
     18   USE sbcrnf         ! river runoff  
     19   USE sbc_oce, ONLY : ln_rnf   ! surface boundary condition: ocean 
    2120 
    2221   IMPLICIT NONE 
     
    9291      REAL(wp), DIMENSION(   jpi  ,1:jpj+2) ::   zwu   ! workspace 
    9392      REAL(wp), DIMENSION(-1:jpi+2,  jpj  ) ::   zwv   ! workspace 
    94       REAL(wp) ::  zraur,  zdep   ! temporary scalar 
    9593      !!---------------------------------------------------------------------- 
    9694 
     
    249247      !                                                ! =============== 
    250248 
    251       IF ( ln_rnf ) THEN 
    252       zraur = 1. / rau0 
    253         DO ji=1,jpi 
    254           DO jj=1,jpj 
    255             zdep = 1. / rnf_dep(ji,jj) 
    256             DO jk=1,rnf_mod_dep(ji,jj) 
    257               hdivn(ji,jj,jk) = hdivn(ji,jj,jk) - rnf(ji,jj)*zraur*zdep 
    258             ENDDO 
    259           ENDDO 
    260         ENDDO 
    261       ENDIF 
     249      IF( ln_rnf )  CALL sbc_rnf_div( hdivn )          ! runoffs (update hdivn field) 
    262250       
    263251      ! 4. Lateral boundary conditions on hdivn and rotn 
     
    317305      !! * Local declarations 
    318306      INTEGER  ::   ji, jj, jk          ! dummy loop indices 
    319       REAL(wp) ::  zraur,  zdep   ! temporary scalar 
    320307      !!---------------------------------------------------------------------- 
    321308 
     
    390377      !                                                ! =============== 
    391378 
    392       IF ( ln_rnf ) THEN 
    393       zraur = 1. / rau0 
    394         DO ji=1,jpi 
    395           DO jj=1,jpj 
    396             zdep = 1. / rnf_dep(ji,jj) 
    397             DO jk=1,rnf_mod_dep(ji,jj) 
    398               hdivn(ji,jj,jk) = hdivn(ji,jj,jk) - rnf(ji,jj)*zraur*zdep 
    399             ENDDO 
    400           ENDDO 
    401         ENDDO 
    402       ENDIF 
     379      IF( ln_rnf )  CALL sbc_rnf_div( hdivn )          ! runoffs (update hdivn field) 
    403380 
    404381      ! 4. Lateral boundary conditions on hdivn and rotn 
  • branches/DEV_R1821_Rivers/NEMO/OPA_SRC/DYN/sshwzv.F90

    r2118 r2171  
    2727   USE diaar5, ONLY :   lk_diaar5 
    2828   USE iom 
    29    USE sbcrnf, ONLY  : rnf_dep, rnf_mod_dep  ! River runoff  
     29   USE sbcrnf, ONLY  : h_rnf, nk_rnf  ! River runoff  
    3030 
    3131   IMPLICIT NONE 
     
    134134         hur(:,:) = umask(:,:,1) / ( hu(:,:) + 1.e0 - umask(:,:,1) ) 
    135135         hvr(:,:) = vmask(:,:,1) / ( hv(:,:) + 1.e0 - vmask(:,:,1) ) 
    136          ! 
    137          DO jj=1,jpj   
    138            DO ji=1,jpi   
    139              rnf_dep(ji,jj)=0  
    140              DO jk=1,rnf_mod_dep(ji,jj)                          ! recalculates rnf_dep to be the depth  
    141                rnf_dep(ji,jj)=rnf_dep(ji,jj)+fse3t(ji,jj,jk)    ! in metres to the bottom of the relevant grid box  
    142              ENDDO  
    143            ENDDO  
    144          ENDDO  
    145136         !  
    146137      ENDIF 
  • branches/DEV_R1821_Rivers/NEMO/OPA_SRC/SBC/sbcrnf.F90

    r2127 r2171  
    2525   PRIVATE 
    2626 
    27    PUBLIC sbc_rnf          ! routine call in step module 
    28  
    29    !                                                     !!* namsbc_rnf namelist * 
     27   PUBLIC sbc_rnf          ! routine call in sbcmod module 
     28   PUBLIC sbc_rnf_div      ! routine called in sshwzv module 
     29 
     30   !                                                      !!* namsbc_rnf namelist * 
    3031   CHARACTER(len=100), PUBLIC ::   cn_dir       = './'    !: Root directory for location of ssr files 
     32   LOGICAL           , PUBLIC ::   ln_rnf_depth = .false. !: depth       river runoffs attribute specified in a file 
     33   LOGICAL           , PUBLIC ::   ln_rnf_temp  = .false. !: temperature river runoffs attribute specified in a file  
     34   LOGICAL           , PUBLIC ::   ln_rnf_sal   = .false. !: salinity    river runoffs attribute specified in a file  
    3135   LOGICAL           , PUBLIC ::   ln_rnf_emp   = .false. !: runoffs into a file to be read or already into precipitation 
    3236   TYPE(FLD_N)       , PUBLIC ::   sn_rnf                 !: information about the runoff file to be read 
    3337   TYPE(FLD_N)       , PUBLIC ::   sn_cnf                 !: information about the runoff mouth file to be read 
    34    TYPE(FLD_N)                ::   sn_sal_rnf             !: information about the salinities of runoff file to be read   
    35    TYPE(FLD_N)                ::   sn_tmp_rnf             !: information about the temperatures of runoff file to be read   
     38   TYPE(FLD_N)                ::   sn_s_rnf               !: information about the salinities of runoff file to be read   
     39   TYPE(FLD_N)                ::   sn_t_rnf               !: information about the temperatures of runoff file to be read   
    3640   TYPE(FLD_N)                ::   sn_dep_rnf             !: information about the depth which river inflow affects 
    3741   LOGICAL           , PUBLIC ::   ln_rnf_mouth = .false. !: specific treatment in mouths vicinity 
    3842   REAL(wp)          , PUBLIC ::   rn_hrnf      = 0.e0    !: runoffs, depth over which enhanced vertical mixing is used 
    3943   REAL(wp)          , PUBLIC ::   rn_avt_rnf   = 0.e0    !: runoffs, value of the additional vertical mixing coef. [m2/s] 
    40    LOGICAL           , PUBLIC ::   ln_rnf_att   = .false. !: river runoffs attributes (temp, sal & depth) are specified in a file  
    4144   REAL(wp)          , PUBLIC ::   rn_rfact     = 1.e0    !: multiplicative factor for runoff 
    4245 
    43    INTEGER , PUBLIC                     ::   nkrnf = 0   !: number of levels over which Kz is increased at river mouths 
    44    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rnfmsk      !: river mouth mask (hori.) 
    45    REAL(wp), PUBLIC, DIMENSION(jpk)     ::   rnfmsk_z    !: river mouth mask (vert.) 
    46  
    47    TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_rnf        !: structure of input river runoff (file information, fields read) 
    48  
    49    TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_sal_rnf    !: structure of input river runoff salinity (file information, fields read)   
    50    TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_tmp_rnf    !: structure of input river runoff temperature (file information, fields read)   
     46   INTEGER , PUBLIC                     ::   nkrnf = 0    !: number of levels over which Kz is increased at river mouths 
     47   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rnfmsk       !: river mouth mask (hori.) 
     48   REAL(wp), PUBLIC, DIMENSION(jpk)     ::   rnfmsk_z     !: river mouth mask (vert.) 
     49 
     50   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_rnf       !: structure of input river runoff (file information, fields read) 
     51 
     52   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_s_rnf     !: structure of input river runoff salinity (file information, fields read)   
     53   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_t_rnf     !: structure of input river runoff temperature (file information, fields read)   
    5154  
    52    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  rnf_dep         !: depth of runoff in m 
    53    INTEGER,  PUBLIC, DIMENSION(jpi,jpj) ::  rnf_mod_dep     !: depth of runoff in model levels 
    54    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  rnf_sal         !: salinity of river runoff 
    55    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  rnf_tmp         !: temperature of river runoff 
     55   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   h_rnf        !: depth of runoff in m 
     56   INTEGER,  PUBLIC, DIMENSION(jpi,jpj) ::   nk_rnf       !: depth of runoff in model levels 
     57 
     58   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,2) ::  tsc_rnf  !: temperature & salinity content of river runoffs   [K.m/s & PSU.m/s] 
     59 
     60   INTEGER, PUBLIC                      :: jp_sal=1 
     61   INTEGER, PUBLIC                      :: jp_tem=2 
     62 
     63!   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rnf_sal      !: salinity of river runoff 
     64!   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rnf_tmp      !: temperature of river runoff 
    5665   
    5766   INTEGER  ::  ji, jj ,jk    ! dummy loop indices   
     
    8493      !! 
    8594      INTEGER  ::   ji, jj   ! dummy loop indices 
     95      REAL(wp) ::   z1_rau0  ! local scalar 
    8696      !!---------------------------------------------------------------------- 
    8797      !                                    
     
    94104         !                                                !-------------------! 
    95105         ! 
    96          CALL fld_read( kt, nn_fsbc, sf_rnf )   ! Read Runoffs data and provides it 
    97          !                                      ! at the current time-step 
    98          IF ( ln_rnf_att ) THEN   
    99             CALL fld_read ( kt, nn_fsbc, sf_sal_rnf )   
    100             CALL fld_read ( kt, nn_fsbc, sf_tmp_rnf )   
    101          ENDIF   
     106                             CALL fld_read ( kt, nn_fsbc, sf_rnf )      ! Read Runoffs data and provide it at kt  
     107         IF( ln_rnf_temp )   CALL fld_read ( kt, nn_fsbc, sf_t_rnf )    ! idem for runoffs temperature if required 
     108         IF( ln_rnf_sal  )   CALL fld_read ( kt, nn_fsbc, sf_s_rnf )    ! idem for runoffs salinity    if required 
    102109 
    103110         ! Runoff reduction only associated to the ORCA2_LIM configuration 
     
    115122         IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN 
    116123            rnf(:,:)  = rn_rfact * ( sf_rnf(1)%fnow(:,:) )   
    117             IF ( ln_rnf_att ) THEN   
    118                rnf_sal(:,:) = ( sf_sal_rnf(1)%fnow(:,:) )   
    119                rnf_tmp(:,:) = ( sf_tmp_rnf(1)%fnow(:,:) )   
    120             ELSE   
    121                rnf_sal(:,:) = 0.0 
    122                rnf_tmp(:,:) = -999   
     124            ! 
     125            z1_rau0 = 1.e0 / rau0 
     126            !                                                              ! set temperature & salinity content of runoffs 
     127            IF( ln_rnf_temp )   THEN                                       ! use runoffs temperature data 
     128               tsc_rnf(:,:,jp_tem) = ( sf_t_rnf(1)%fnow(:,:) ) * rnf(:,:) * z1_rau0 
     129               WHERE( sf_t_rnf(1)%fnow(:,:) == -999 )                      ! if missing data value use SST as runoffs temperature   
     130                   tsc_rnf(:,:,jp_tem) = sst_m(:,:) * rnf(:,:) * z1_rau0 
     131               ENDWHERE 
     132            ELSE                                                           ! use SST as runoffs temperature 
     133               tsc_rnf(:,:,jp_tem) = sst_m(:,:) * rnf(:,:) * z1_rau0 
    123134            ENDIF   
    124             CALL iom_put( "runoffs", rnf )         ! runoffs 
     135            !                                                              ! use runoffs salinity data  
     136            IF( ln_rnf_sal ) tsc_rnf(:,:,jp_sal) = ( sf_s_rnf(1)%fnow(:,:) ) * rnf(:,:) * z1_rau0 
     137            !                                                              ! else use S=0 for runoffs (done one for all in the init) 
     138            ! 
     139            IF( ln_rnf_temp .OR. ln_rnf_sal ) THEN                         ! runoffs as outflow: use ocean SST and SSS 
     140               WHERE( rnf(:,:) < 0.e0 )                                    ! example baltic model when flow is out of domain  
     141                  tsc_rnf(:,:,jp_tem) = sst_m(:,:) * rnf(:,:) * z1_rau0 
     142                  tsc_rnf(:,:,jp_sal) = sss_m(:,:) * rnf(:,:) * z1_rau0 
     143               ENDWHERE 
     144            ENDIF 
     145 
     146            CALL iom_put( "runoffs", rnf )         ! output runoffs arrays 
    125147         ENDIF 
    126148         ! 
     
    128150      ! 
    129151   END SUBROUTINE sbc_rnf 
     152 
     153   SUBROUTINE sbc_rnf_div( phdivn ) 
     154      !!---------------------------------------------------------------------- 
     155      !!                  ***  ROUTINE sbc_rnf  *** 
     156      !!        
     157      !! ** Purpose :   update the horizontal divergence with the runoff inflow 
     158      !! 
     159      !! ** Method  :    
     160      !!                CAUTION : rnf is positive (inflow) decreasing the  
     161      !!                          divergence and expressed in m/s 
     162      !! 
     163      !! ** Action  :   phdivn   decreased by the runoff inflow 
     164      !!---------------------------------------------------------------------- 
     165      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   phdivn   ! horizontal divergence 
     166      !! 
     167      INTEGER  ::   ji, jj, jk   ! dummy loop indices 
     168      REAL(wp) ::   z1_rau0   ! local scalar 
     169      !!---------------------------------------------------------------------- 
     170      ! 
     171      z1_rau0 = 1.e0 / rau0 
     172      IF( ln_rnf_depth ) THEN      !==   runoff distributed over several levels   ==! 
     173         IF( lk_vvl ) THEN             ! variable volume case  
     174            DO jj = 1, jpj                   ! update the depth over which runoffs are distributed 
     175               DO ji = 1, jpi 
     176                  h_rnf(ji,jj) = 0.e0  
     177                  DO jk = 1, nk_rnf(ji,jj)                           ! recalculates h_rnf to be the depth in metres 
     178                     h_rnf(ji,jj) = h_rnf(ji,jj) + fse3t(ji,jj,jk)   ! to the bottom of the relevant grid box  
     179                  END DO  
     180                  !                          ! apply the runoff input flow 
     181                  DO jk = 1, nk_rnf(ji,jj) 
     182                     phdivn(ji,jj,jk) = phdivn(ji,jj,jk) - rnf(ji,jj) * z1_rau0 / h_rnf(ji,jj) 
     183                  END DO 
     184               END DO 
     185            END DO 
     186         ELSE                          ! constant volume case : just apply the runoff input flow 
     187            DO jj = 1, jpj 
     188               DO ji = 1, jpi 
     189                  DO jk = 1, nk_rnf(ji,jj) 
     190                     phdivn(ji,jj,jk) = phdivn(ji,jj,jk) - rnf(ji,jj) * z1_rau0 / h_rnf(ji,jj) 
     191                  END DO 
     192               END DO 
     193            END DO 
     194         ENDIF 
     195      ELSE                       !==   runoff put only at the surface   ==! 
     196         phdivn(:,:,1) = phdivn(:,:,1) - rnf(:,:) * z1_rau0 / fse3t(:,:,1) 
     197      ENDIF 
     198      ! 
     199   END SUBROUTINE sbc_rnf_div 
    130200 
    131201 
     
    143213      INTEGER  ::   ierror   ! temporary integer 
    144214      !!  
    145       NAMELIST/namsbc_rnf/ cn_dir, ln_rnf_emp, sn_rnf, sn_cnf, sn_sal_rnf, sn_tmp_rnf, sn_dep_rnf,   &   
    146          &                 ln_rnf_mouth, ln_rnf_att, rn_hrnf, rn_avt_rnf, rn_rfact   
     215      NAMELIST/namsbc_rnf/ cn_dir, ln_rnf_emp, ln_rnf_depth, ln_rnf_temp, ln_rnf_sal,   & 
     216         &                 sn_rnf, sn_cnf    , sn_s_rnf    , sn_t_rnf   , sn_dep_rnf,   &   
     217         &                 ln_rnf_mouth      , rn_hrnf     , rn_avt_rnf , rn_rfact   
    147218      !!---------------------------------------------------------------------- 
    148219 
     
    156227      sn_cnf = FLD_N( 'runoffs',     0     , 'sorunoff' ,  .FALSE.   , .true. ,   'yearly'  , ''       , ''         ) 
    157228 
    158       sn_sal_rnf = FLD_N( 'runoffs',  24.  , 'rosaline' ,  .TRUE.    , .true. ,   'yearly'  , ''    , ''  )   
    159       sn_tmp_rnf = FLD_N( 'runoffs',  24.  , 'rotemper' ,  .TRUE.    , .true. ,   'yearly'  , ''    , ''  )   
     229      sn_s_rnf = FLD_N( 'runoffs',  24.  , 'rosaline' ,  .TRUE.    , .true. ,   'yearly'  , ''    , ''  )   
     230      sn_t_rnf = FLD_N( 'runoffs',  24.  , 'rotemper' ,  .TRUE.    , .true. ,   'yearly'  , ''    , ''  )   
    160231      sn_dep_rnf = FLD_N( 'runoffs',   0.  , 'rodepth'  ,  .FALSE.   , .true. ,   'yearly'  , ''    , ''  )   
    161232      ! 
     
    180251      !                                   ! ================== 
    181252      ! 
    182       IF( ln_rnf_emp ) THEN                     ! runoffs directly provided in the precipitations 
     253      IF( ln_rnf_emp ) THEN                     !==  runoffs directly provided in the precipitations  ==! 
    183254         IF(lwp) WRITE(numout,*) 
    184255         IF(lwp) WRITE(numout,*) '          runoffs directly provided in the precipitations' 
    185          IF ( ln_rnf_att ) THEN 
    186            CALL ctl_warn( 'runoffs already included in precipitations & so runoff attributes will not be used' )  
    187            ln_rnf_att = .FALSE. 
    188          ENDIF 
    189          ! 
    190       ELSE                                      ! runoffs read in a file : set sf_rnf structure  
    191          ! 
    192          ! Allocate sf_rnf structure and (if required) sf_sal_rnf and sf_tmp_rnf structures 
    193          ALLOCATE( sf_rnf(1), STAT=ierror ) 
     256         IF( ln_rnf_depth .OR. ln_rnf_temp .OR. ln_rnf_sal ) THEN 
     257           CALL ctl_warn( 'runoffs already included in precipitations, so runoff (T,S, depth) attributes will not be used' )  
     258           ln_rnf_depth = .FALSE.   ;   ln_rnf_temp = .FALSE.   ;   ln_rnf_sal = .FALSE. 
     259         ENDIF 
     260         ! 
     261      ELSE                                      !==  runoffs read in a file : set sf_rnf structure  ==! 
     262         ! 
     263         ALLOCATE( sf_rnf(1), STAT=ierror )         ! Create sf_rnf structure (runoff inflow) 
     264         IF(lwp) WRITE(numout,*) 
     265         IF(lwp) WRITE(numout,*) '          runoffs inflow read in a file' 
    194266         IF( ierror > 0 ) THEN 
    195267            CALL ctl_stop( 'sbc_rnf: unable to allocate sf_rnf structure' )   ;   RETURN 
    196268         ENDIF 
    197          ALLOCATE( sf_rnf(1)%fnow(jpi,jpj) ) 
    198          ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,2) ) 
    199  
    200          IF( ln_rnf_att ) THEN 
    201             ALLOCATE( sf_sal_rnf(1), STAT=ierror ) 
     269         ALLOCATE( sf_rnf(1)%fnow(jpi,jpj)   )   ;   ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,2) ) 
     270         !                                          ! fill sf_rnf with the namelist (sn_rnf) and control print 
     271         CALL fld_fill( sf_rnf, (/ sn_rnf /), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf' ) 
     272         ! 
     273         IF( ln_rnf_temp ) THEN                     ! Create (if required) sf_t_rnf structure 
     274            IF(lwp) WRITE(numout,*) 
     275            IF(lwp) WRITE(numout,*) '          runoffs temperatures read in a file' 
     276            ALLOCATE( sf_t_rnf(1), STAT=ierror  ) 
    202277            IF( ierror > 0 ) THEN 
    203                CALL ctl_stop( 'sbc_sal_rnf: unable to allocate sf_sal_rnf structure' )   ;   RETURN 
     278               CALL ctl_stop( 'sbc_rnf_init: unable to allocate sf_t_rnf structure' )   ;   RETURN 
    204279            ENDIF 
    205             ALLOCATE( sf_sal_rnf(1)%fnow(jpi,jpj) ) 
    206             ALLOCATE( sf_sal_rnf(1)%fdta(jpi,jpj,2) ) 
    207  
    208             ALLOCATE( sf_tmp_rnf(1), STAT=ierror ) 
     280            ALLOCATE( sf_t_rnf(1)%fnow(jpi,jpj)   )   ;   ALLOCATE( sf_t_rnf(1)%fdta(jpi,jpj,2) ) 
     281            CALL fld_fill (sf_t_rnf, (/ sn_t_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff temperature data', 'namsbc_rnf' )   
     282         ENDIF 
     283         ! 
     284         IF( ln_rnf_sal  ) THEN                     ! Create (if required) sf_s_rnf and sf_t_rnf structures 
     285            IF(lwp) WRITE(numout,*) 
     286            IF(lwp) WRITE(numout,*) '          runoffs salinities read in a file' 
     287            ALLOCATE( sf_s_rnf(1), STAT=ierror  ) 
    209288            IF( ierror > 0 ) THEN 
    210                 CALL ctl_stop( 'sbc_tmp_rnf: unable to allocate sf_tmp_rnf structure' )   ;   RETURN 
     289               CALL ctl_stop( 'sbc_rnf_init: unable to allocate sf_s_rnf structure' )   ;   RETURN 
    211290            ENDIF 
    212             ALLOCATE( sf_tmp_rnf(1)%fnow(jpi,jpj) ) 
    213             ALLOCATE( sf_tmp_rnf(1)%fdta(jpi,jpj,2) ) 
    214          ENDIF 
    215          ! fill sf_rnf with sn_rnf and control print 
    216          CALL fld_fill( sf_rnf, (/ sn_rnf /), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf' ) 
     291            ALLOCATE( sf_s_rnf(1)%fnow(jpi,jpj)   )   ;   ALLOCATE( sf_s_rnf(1)%fdta(jpi,jpj,2) ) 
     292            CALL fld_fill (sf_s_rnf, (/ sn_s_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff salinity data', 'namsbc_rnf' )   
     293         ENDIF 
     294 
    217295  
    218          IF ( ln_rnf_att ) THEN   
    219             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_tmp_rnf, (/ sn_tmp_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff temperature data', 'namsbc_rnf' )   
    221    
     296         IF ( ln_rnf_depth ) THEN                     ! depth of runoffs set from a file  
     297            IF(lwp) WRITE(numout,*) 
     298            IF(lwp) WRITE(numout,*) '          runoffs depth read in a file' 
    222299            rn_dep_file = TRIM( cn_dir )//TRIM( sn_dep_rnf%clname )   
    223300            CALL iom_open ( rn_dep_file, inum )                           ! open file   
    224             CALL iom_get  ( inum, jpdom_data, sn_dep_rnf%clvar, rnf_dep )    ! read the river mouth array   
     301            CALL iom_get  ( inum, jpdom_data, sn_dep_rnf%clvar, h_rnf )    ! read the river mouth array   
    225302            CALL iom_close( inum )                                      ! close file   
    226303   
    227             rnf_mod_dep(:,:)=0   
     304            nk_rnf(:,:)=0                              ! set the number of level over which river runoffs are applied 
    228305            DO jj=1,jpj   
    229306              DO ji=1,jpi   
    230                 IF ( rnf_dep(ji,jj) > 0.e0 ) THEN   
     307                IF ( h_rnf(ji,jj) > 0.e0 ) THEN   
    231308                  jk=2   
    232                   DO WHILE ( jk/=(mbathy(ji,jj)-1) .AND. fsdept(ji,jj,jk) < rnf_dep(ji,jj) );  jk=jk+1;   ENDDO   
    233                   rnf_mod_dep(ji,jj)=jk   
    234                 ELSE IF ( rnf_dep(ji,jj) .eq. -1 ) THEN   
    235                   rnf_mod_dep(ji,jj)=1   
    236                 ELSE IF ( rnf_dep(ji,jj) .eq. -999 ) THEN   
    237                   rnf_mod_dep(ji,jj)=mbathy(ji,jj)-1 
    238                 ELSE IF ( rnf_dep(ji,jj) /= 0 ) THEN   
     309                  DO WHILE ( jk/=(mbathy(ji,jj)-1) .AND. fsdept(ji,jj,jk) < h_rnf(ji,jj) );  jk=jk+1;   ENDDO   
     310                  nk_rnf(ji,jj)=jk   
     311                ELSE IF ( h_rnf(ji,jj) == -1   ) THEN   ;  nk_rnf(ji,jj)=1   
     312                ELSE IF ( h_rnf(ji,jj) == -999 ) THEN   ;  nk_rnf(ji,jj)=mbathy(ji,jj)-1 
     313                ELSE IF ( h_rnf(ji,jj) /= 0 ) THEN   
    239314                  CALL ctl_stop( 'runoff depth not positive, and not -999 or -1, rnf value in file fort.999'  )   
    240315                  WRITE(999,*) 'ji, jj, rnf(ji,jj) :', ji, jj, rnf(ji,jj)   
     
    242317              ENDDO   
    243318            ENDDO   
    244          ELSE   
    245             rnf_mod_dep(:,:)=1   
     319            DO jj=1,jpj                               ! set the associated depth  
     320              DO ji=1,jpi  
     321                h_rnf(ji,jj)=0.e0 
     322                DO jk=1,nk_rnf(ji,jj)                         
     323                   h_rnf(ji,jj)=h_rnf(ji,jj)+fse3t(ji,jj,jk)   
     324                ENDDO 
     325              ENDDO 
     326            ENDDO 
     327         ELSE                                       ! runoffs applied at the surface  
     328            nk_rnf(:,:)=1   
     329            h_rnf(:,:)=fse3t(:,:,1) 
    246330         ENDIF   
    247331      !  
    248332      ENDIF 
    249        
    250       ! recalculate rnf_dep to be the depth in metres to the bottom of the relevant grid box 
    251       DO jj=1,jpj  
    252         DO ji=1,jpi  
    253           rnf_dep(ji,jj)=0 
    254           DO jk=1,rnf_mod_dep(ji,jj)                         
    255             rnf_dep(ji,jj)=rnf_dep(ji,jj)+fse3t(ji,jj,jk)   
    256           ENDDO 
    257         ENDDO 
    258       ENDDO 
     333 
     334      tsc_rnf(:,:,:) = 0.e0                 ! runoffs temperature & salinty contents initilisation 
    259335      !                                   ! ======================== 
    260336      !                                   !   River mouth vicinity 
     
    266342         !                                      !    - mixed upstream-centered (ln_traadv_cen2=T) 
    267343         ! 
    268          !                                          ! Number of level over which Kz increase 
    269          IF ( ln_rnf_att )  &  
    270               &  CALL ctl_warn( 'increased mixing turned on but effects may already be spread through depth by ln_rnf_att' )  
    271          nkrnf = 0 
     344         IF ( ln_rnf_depth )   CALL ctl_warn( 'sbc_rnf_init: increased mixing turned on but effects may already',   & 
     345            &                                              'be spread through depth by ln_rnf_depth'               )  
     346         ! 
     347         nkrnf = 0                                  ! Number of level over which Kz increase 
    272348         IF( rn_hrnf > 0.e0 ) THEN 
    273349            nkrnf = 2 
  • branches/DEV_R1821_Rivers/NEMO/OPA_SRC/TRA/trasbc.F90

    r2127 r2171  
    2121   USE in_out_manager  ! I/O manager 
    2222   USE prtctl          ! Print control 
     23   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2324   USE sbcrnf          ! River runoff   
    2425   USE sbcmod          ! ln_rnf   
     
    106107      !! 
    107108      INTEGER  ::   ji, jj, jk           ! dummy loop indices   
    108       REAL(wp) ::   zta, zsa             ! temporary scalars, adjustment to temperature and salinity   
    109       REAL(wp) ::   zata, zasa           ! 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   
     109      REAL(wp) ::   zta, zsa             ! local scalars, adjustment to temperature and salinity   
     110      REAL(wp) ::   zata, zasa           ! local scalars, calculations of automatic change to temp & sal due to vvl (done elsewhere)   
     111      REAL(wp) ::   zsrau, zse3t, zdep   ! local scalars, 1/density, 1/height of box, 1/height of effected water column   
    111112      REAL(wp) ::   zdheat, zdsalt       ! total change of temperature and salinity   
    112113      !!---------------------------------------------------------------------- 
     
    149150      END DO 
    150151 
    151       IF ( ln_rnf ) THEN   
     152      !                             !==  Runoffs  ==! 
     153      ! Effect on (t,s) due to river runoff (dilution effect automatically applied via vertical tracer advection)  
     154      IF( ln_rnf ) THEN   
     155         DO jj = 2, jpj  
     156            DO ji = fs_2, fs_jpim1 
     157               zdep = 1. / h_rnf(ji,jj)   
     158               IF ( rnf(ji,jj) .ne. 0.0 ) THEN 
     159                  DO jk = 1, nk_rnf(ji,jj) 
     160                                        ta(ji,jj,jk) = ta(ji,jj,jk) + tsc_rnf(ji,jj,jp_tem) * zdep 
     161                     IF( ln_rnf_sal )   sa(ji,jj,jk) = sa(ji,jj,jk) + tsc_rnf(ji,jj,jp_sal) * zdep 
     162                  ENDDO 
     163               ENDIF 
     164            ENDDO   
     165         ENDDO   
     166      ENDIF   
    152167 
    153       ! Effect on (t,s) due to river runoff (dilution effect automatically applied via vertical tracer advection)  
    154         DO jj=1,jpj   
    155            DO ji=1,jpi   
    156               zdep = 1. / rnf_dep(ji,jj)   
    157               zse3t= 1. / fse3t(ji,jj,1)   
    158  
    159               IF ( rnf(ji,jj) .gt. 0.0 ) THEN 
    160                  ! ammend t and s due to direct tracer flux 
    161                  IF ( rnf_tmp(ji,jj) == -999 )   rnf_tmp(ji,jj)=tn(ji,jj,1)        ! if not specified set runoff temp to be sst 
    162                  DO jk=1, rnf_mod_dep(ji,jj) 
    163                     ta(ji,jj,jk) = ta(ji,jj,jk) + rnf_tmp(ji,jj) * rnf(ji,jj) * zsrau * zdep 
    164                     sa(ji,jj,jk) = sa(ji,jj,jk) + rnf_sal(ji,jj) * rnf(ji,jj) * zsrau * zdep 
    165                  ENDDO 
    166               ELSEIF (rnf(ji,jj) .lt. 0.) THEN   !! for use in baltic when flow is out of domain, want no change in temp and sal 
    167                  ! negate concentration/dilution effect from traadv, as the tracer leaves domain 
    168                  DO jk=1, rnf_mod_dep(ji,jj) 
    169                     ta(ji,jj,jk) = ta(ji,jj,jk) + tn(ji,jj,jk) * rnf(ji,jj) * zsrau * zdep 
    170                     sa(ji,jj,jk) = sa(ji,jj,jk) + sn(ji,jj,jk) * rnf(ji,jj) * zsrau * zdep 
    171                  ENDDO 
    172               ENDIF 
    173  
    174            ENDDO   
    175         ENDDO   
    176  
    177       ENDIF   
     168      CALL lbc_lnk( ta, 'T', 1. )    ;    CALL lbc_lnk( sa, 'T', 1. ) 
    178169 
    179170      IF( l_trdtra ) THEN      ! save the sbc trends for diagnostic 
Note: See TracChangeset for help on using the changeset viewer.