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/SBC – 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

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

Legend:

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

    r1705 r1938  
    4949   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   emp       !: freshwater budget: volume flux               [Kg/m2/s] 
    5050   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]   
    5152   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   emp_tot   !: total evaporation - (liquid + solid) precpitation over oce and ice 
    5253   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   tprecip   !: total precipitation           [Kg/m2/s] 
  • branches/DEV_R1821_Rivers/NEMO/OPA_SRC/SBC/sbcfwb.F90

    r1715 r1938  
    3131   REAL(wp) ::   a_fwb_b            ! annual domain averaged freshwater budget 
    3232   REAL(wp) ::   a_fwb              ! for 2 year before (_b) and before year. 
    33    REAL(wp) ::   empold             ! empold to be suppressed 
     33   REAL(wp) ::   fwfold             ! fwfold to be suppressed 
    3434   REAL(wp) ::   area               ! global mean ocean surface (interior domain) 
    3535 
     
    6565      INTEGER  ::   inum                  ! temporary logical unit 
    6666      INTEGER  ::   ikty, iyear           !  
    67       REAL(wp) ::   z_emp, z_emp_nsrf       ! temporary scalars 
     67      REAL(wp) ::   z_fwf, z_fwf_nsrf       ! temporary scalars 
    6868      REAL(wp) ::   zsurf_neg, zsurf_pos, zsurf_tospread 
    6969      REAL(wp), DIMENSION(jpi,jpj) ::   ztmsk_neg, ztmsk_pos, ztmsk_tospread 
     
    7979            IF( kn_fwb == 1 )   WRITE(numout,*) '          instantaneously set to zero' 
    8080            IF( kn_fwb == 2 )   WRITE(numout,*) '          adjusted from previous year budget' 
    81             IF( kn_fwb == 3 )   WRITE(numout,*) '          emp set to zero and spread out over erp area' 
     81            IF( kn_fwb == 3 )   WRITE(numout,*) '          fwf set to zero and spread out over erp area' 
    8282            ! 
    8383            IF( kn_fwb == 3 .AND. nn_sssr /= 2 )   & 
     
    101101          
    102102      ! 
    103       CASE ( 1 )                               ! global mean emp set to zero 
     103      CASE ( 1 )                               ! global mean fwf set to zero 
    104104         IF( MOD( kt-1, kn_fsbc ) == 0 ) THEN 
    105             z_emp = SUM( e1e2_i(:,:) * emp(:,:) ) / area 
    106             IF( lk_mpp )   CALL  mpp_sum( z_emp    )   ! sum over the global domain 
    107             emp (:,:) = emp (:,:) - z_emp 
    108             emps(:,:) = emps(:,:) - z_emp 
    109          ENDIF 
    110          ! 
    111       CASE ( 2 )                               ! emp budget adjusted from the previous year 
     105            z_fwf = SUM( e1e2_i(:,:) * ( emp(:,:)-rnf(:,:) ) ) / area  
     106            IF( lk_mpp )   CALL  mpp_sum( z_fwf    )   ! sum over the global domain  
     107            emp (:,:) = emp (:,:) - z_fwf  
     108            emps(:,:) = emps(:,:) - z_fwf  
     109         ENDIF 
     110         ! 
     111      CASE ( 2 )                               ! fwf budget adjusted from the previous year 
    112112         ! initialisation 
    113113         IF( kt == nit000 ) THEN 
    114             ! Read the corrective factor on precipitations (empold) 
     114            ! Read the corrective factor on precipitations (fwfold) 
    115115            CALL ctl_opn( inum, 'EMPave_old.dat', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
    116116            READ ( inum, "(24X,I8,2ES24.16)" ) iyear, a_fwb_b, a_fwb 
    117117            CLOSE( inum ) 
    118             empold = a_fwb                  ! current year freshwater budget correction 
     118            fwfold = a_fwb                  ! current year freshwater budget correction 
    119119            !                               ! estimate from the previous year budget 
    120120            IF(lwp)WRITE(numout,*) 
    121             IF(lwp)WRITE(numout,*)'sbc_fwb : year = ',iyear  , ' freshwater budget correction = ', empold 
     121            IF(lwp)WRITE(numout,*)'sbc_fwb : year = ',iyear  , ' freshwater budget correction = ', fwfold 
    122122            IF(lwp)WRITE(numout,*)'          year = ',iyear-1, ' freshwater budget read       = ', a_fwb 
    123123            IF(lwp)WRITE(numout,*)'          year = ',iyear-2, ' freshwater budget read       = ', a_fwb_b 
    124124         ENDIF    
    125125         !  
    126          ! Update empold if new year start 
     126         ! Update fwfold if new year start 
    127127         ikty = 365 * 86400 / rdttra(1)    !!bug  use of 365 days leap year or 360d year !!!!!!! 
    128128         IF( MOD( kt, ikty ) == 0 ) THEN 
     
    132132            a_fwb   = a_fwb * 1.e+3 / ( area * 86400. * 365. )     ! convert in Kg/m3/s = mm/s 
    133133!!gm        !                                                      !!bug 365d year  
    134             empold =  a_fwb                 ! current year freshwater budget correction 
     134            fwfold =  a_fwb                 ! current year freshwater budget correction 
    135135            !                               ! estimate from the previous year budget 
    136136         ENDIF 
     
    138138         ! correct the freshwater fluxes 
    139139         IF( MOD( kt-1, kn_fsbc ) == 0 ) THEN 
    140             emp (:,:) = emp (:,:) + empold 
    141             emps(:,:) = emps(:,:) + empold 
    142          ENDIF 
    143          ! 
    144          ! save empold value in a file 
     140            emp (:,:) = emp (:,:) + fwfold 
     141            emps(:,:) = emps(:,:) + fwfold 
     142         ENDIF 
     143         ! 
     144         ! save fwfold value in a file 
    145145         IF( kt == nitend .AND. lwp ) THEN 
    146146            CALL ctl_opn( inum, 'EMPave.dat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., narea ) 
     
    149149         ENDIF 
    150150         ! 
    151       CASE ( 3 )                               ! global emp set to zero and spread out over erp area 
     151      CASE ( 3 )                               ! global fwf set to zero and spread out over erp area 
    152152         ! 
    153153         IF( MOD( kt-1, kn_fsbc ) == 0 ) THEN 
     
    161161            zsurf_pos = SUM( e1e2_i(:,:)*ztmsk_pos(:,:) ) 
    162162         
    163             ! emp global mean  
    164             z_emp = SUM( e1e2_i(:,:) * emp(:,:) ) / area 
     163            ! fwf global mean  
     164            z_fwf = SUM( e1e2_i(:,:) * ( emp(:,:)-rnf(:,:) ) ) / area  
    165165            ! 
    166             IF( lk_mpp )   CALL  mpp_sum( z_emp ) 
     166            IF( lk_mpp )   CALL  mpp_sum( z_fwf ) 
    167167             
    168             IF( z_emp < 0.e0 ) THEN 
     168            IF( z_fwf < 0.e0 ) THEN 
    169169                ! to spread out over >0 erp area to increase evaporation damping process 
    170170                zsurf_tospread = zsurf_pos 
     
    176176            ENDIF 
    177177 
    178             ! emp global mean over <0 or >0 erp area 
    179             z_emp_nsrf = SUM( e1e2_i(:,:) * z_emp ) / ( zsurf_tospread + rsmall ) 
     178            ! fwf global mean over <0 or >0 erp area 
     179            z_fwf_nsrf = SUM( e1e2_i(:,:) * z_fwf ) / ( zsurf_tospread + rsmall ) 
    180180            ! weight to respect erp field 2D structure  
    181181            z_wgt(:,:) = ztmsk_tospread(:,:) * erp(:,:) / ( SUM( ztmsk_tospread(:,:) * erp(:,:) * e1e2_i(:,:) ) + rsmall ) 
    182182            ! final correction term to apply 
    183             zerp_cor(:,:) = -1. * z_emp_nsrf * zsurf_tospread * z_wgt(:,:) 
     183            zerp_cor(:,:) = -1. * z_fwf_nsrf * zsurf_tospread * z_wgt(:,:) 
    184184 
    185185            CALL lbc_lnk( zerp_cor, 'T', 1. ) 
     
    190190             
    191191            IF( nprint == 1 .AND. lwp ) THEN 
    192                IF( z_emp < 0.e0 ) THEN 
    193                   WRITE(numout,*)'       z_emp < 0' 
     192               IF( z_fwf < 0.e0 ) THEN 
     193                  WRITE(numout,*)'       z_fwf < 0' 
    194194                  WRITE(numout,*)'       SUM(erp+)        = ', SUM( ztmsk_tospread(:,:)*erp(:,:)*e1e2_i(:,:) )*1.e-3,' m3.s-1' 
    195195               ELSE 
    196                    WRITE(numout,*)'      z_emp >= 0' 
     196                   WRITE(numout,*)'      z_fwf >= 0' 
    197197                   WRITE(numout,*)'      SUM(erp-)        = ', SUM( ztmsk_tospread(:,:)*erp(:,:)*e1e2_i(:,:) )*1.e-3,' m3.s-1' 
    198198               ENDIF 
    199                WRITE(numout,*)'      SUM(empG)        = ', SUM( z_emp*e1e2_i(:,:) )*1.e-3,' m3.s-1' 
    200                WRITE(numout,*)'      z_emp            = ', z_emp      ,' mm.s-1' 
    201                WRITE(numout,*)'      z_emp_nsrf       = ', z_emp_nsrf ,' mm.s-1' 
     199               WRITE(numout,*)'      SUM(empG)        = ', SUM( z_fwf*e1e2_i(:,:) )*1.e-3,' m3.s-1' 
     200               WRITE(numout,*)'      z_fwf            = ', z_fwf      ,' mm.s-1' 
     201               WRITE(numout,*)'      z_fwf_nsrf       = ', z_fwf_nsrf ,' mm.s-1' 
    202202               WRITE(numout,*)'      MIN(zerp_cor)    = ', MINVAL(zerp_cor)  
    203203               WRITE(numout,*)'      MAX(zerp_cor)    = ', MAXVAL(zerp_cor)  
  • branches/DEV_R1821_Rivers/NEMO/OPA_SRC/SBC/sbcmod.F90

    r1792 r1938  
    185185      INTEGER, INTENT(in) ::   kt       ! ocean time step 
    186186      !!--------------------------------------------------------------------- 
     187 
     188      emp(:,:)=0.0   
     189      emps(:,:)=0.0   
     190      rnf(:,:)=0.0  
    187191 
    188192      CALL iom_setkt( kt + nn_fsbc - 1 )         !  in sbc, iom_put is called every nn_fsbc time step 
     
    237241      ! 
    238242      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN 
    239          CALL iom_put( "emp"    , emp       )                   ! upward water flux 
    240          CALL iom_put( "emps"   , emps      )                   ! 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) 
     243         CALL iom_put( "emp-rnf"  , (emp-rnf)  )                ! upward water flux  
     244         CALL iom_put( "emps-rnf" , (emps-rnf) )                ! c/d water flux  
     245         CALL iom_put( "qns+qsr"  , qns + qsr  )                ! total heat flux   (caution if ln_dm2dc=true, to be  
     246         CALL iom_put( "qns"      , qns        )                ! solar heat flux    moved after the call to iom_setkt) 
     247         CALL iom_put( "qsr"      ,       qsr  )                ! solar heat flux    moved after the call to iom_setkt) 
    244248         IF(  nn_ice > 0 )   CALL iom_put( "ice_cover", fr_i )  ! ice fraction  
    245249      ENDIF 
     
    254258      IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    255259         CALL prt_ctl(tab2d_1=fr_i   , clinfo1=' fr_i - : ', mask1=tmask, ovlap=1 ) 
    256          CALL prt_ctl(tab2d_1=emp    , clinfo1=' emp  - : ', mask1=tmask, ovlap=1 ) 
    257          CALL prt_ctl(tab2d_1=emps   , clinfo1=' emps - : ', mask1=tmask, ovlap=1 ) 
     260         CALL prt_ctl(tab2d_1=(emp-rnf) , clinfo1=' emp-rnf  - : ', mask1=tmask, ovlap=1 )  
     261         CALL prt_ctl(tab2d_1=(emps-rnf), clinfo1=' emps-rnf - : ', mask1=tmask, ovlap=1 )  
    258262         CALL prt_ctl(tab2d_1=qns    , clinfo1=' qns  - : ', mask1=tmask, ovlap=1 ) 
    259263         CALL prt_ctl(tab2d_1=qsr    , clinfo1=' qsr  - : ', mask1=tmask, ovlap=1 ) 
  • branches/DEV_R1821_Rivers/NEMO/OPA_SRC/SBC/sbcrnf.F90

    r1730 r1938  
    3232   TYPE(FLD_N)       , PUBLIC ::   sn_rnf                 !: information about the runoff file to be read 
    3333   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   
     36   TYPE(FLD_N)                ::   sn_dep_rnf             !: information about the depth which river inflow affects 
    3437   LOGICAL           , PUBLIC ::   ln_rnf_mouth = .false. !: specific treatment in mouths vicinity 
    3538   REAL(wp)          , PUBLIC ::   rn_hrnf      = 0.e0    !: runoffs, depth over which enhanced vertical mixing is used 
    3639   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  
    3741   REAL(wp)          , PUBLIC ::   rn_rfact     = 1.e0    !: multiplicative factor for runoff 
    3842 
     
    4246 
    4347   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_rnf   ! structure of input SST (file information, fields read) 
     48 
     49   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_sal_rnf    !: structure of input salinity (file information, fields read)   
     50   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_tmp_rnf    !: structure of input tmeperature (file information, fields read)   
     51  
     52!   REAL,    PUBLIC, DIMENSION(jpi,jpj) ::  rnf             !: mass flux of river runoff (in kg/m2/s)   
     53   REAL,    PUBLIC, DIMENSION(jpi,jpj) ::  rnf_dep         !: depth of runoff in m   
     54   INTEGER, PUBLIC, DIMENSION(jpi,jpj) ::  rnf_mod_dep     !: depth of runoff in model levels   
     55   REAL,    PUBLIC, DIMENSION(jpi,jpj) ::  rnf_sal         !: salinity of river runoff   
     56   REAL,    PUBLIC, DIMENSION(jpi,jpj) ::  rnf_tmp         !: temperature of river runoff   
     57   
     58   INTEGER  ::  ji, jj ,jk    ! dummy loop indices   
     59   INTEGER  ::  inum          ! temporary logical unit   
     60   
     61   !! * Substitutions   
     62#  include "domzgr_substitute.h90"   
    4463 
    4564   !!---------------------------------------------------------------------- 
     
    7796            ALLOCATE( sf_rnf(1)%fnow(jpi,jpj) ) 
    7897            ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,2) ) 
    79          ENDIF 
    80          CALL sbc_rnf_init(sf_rnf) 
     98  
     99            ALLOCATE( sf_sal_rnf(1), STAT=ierror )   
     100            IF( ierror > 0 ) THEN   
     101               CALL ctl_stop( 'sbc_sal_rnf: unable to allocate sf_sal_rnf structure' )   ;   RETURN   
     102            ENDIF   
     103            ALLOCATE( sf_sal_rnf(1)%fnow(jpi,jpj) )   
     104            ALLOCATE( sf_sal_rnf(1)%fdta(jpi,jpj,2) )   
     105    
     106            ALLOCATE( sf_tmp_rnf(1), STAT=ierror )   
     107            IF( ierror > 0 ) THEN   
     108                CALL ctl_stop( 'sbc_tmp_rnf: unable to allocate sf_tmp_rnf structure' )   ;   RETURN   
     109            ENDIF   
     110            ALLOCATE( sf_tmp_rnf(1)%fnow(jpi,jpj) )   
     111            ALLOCATE( sf_tmp_rnf(1)%fdta(jpi,jpj,2) )   
     112         ENDIF   
     113         CALL sbc_rnf_init( sf_rnf, sf_tmp_rnf, sf_sal_rnf )   
    81114      ENDIF 
    82115 
     
    87120         CALL fld_read( kt, nn_fsbc, sf_rnf )   ! Read Runoffs data and provides it 
    88121         !                                      ! at the current time-step 
     122         IF ( ln_rnf_att ) THEN   
     123            CALL fld_read ( kt, nn_fsbc, sf_sal_rnf )   
     124            CALL fld_read ( kt, nn_fsbc, sf_tmp_rnf )   
     125         ENDIF   
    89126 
    90127         ! Runoff reduction only associated to the ORCA2_LIM configuration 
     
    101138 
    102139         IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN 
    103             emp (:,:) = emp (:,:) - rn_rfact * ABS( sf_rnf(1)%fnow(:,:) ) 
    104             emps(:,:) = emps(:,:) - rn_rfact * ABS( sf_rnf(1)%fnow(:,:) ) 
     140            rnf(:,:)  = rn_rfact * ( sf_rnf(1)%fnow(:,:) )   
     141            IF ( ln_rnf_att ) THEN   
     142               rnf_sal(:,:) = ( sf_sal_rnf(1)%fnow(:,:) )   
     143               rnf_tmp(:,:) = ( sf_tmp_rnf(1)%fnow(:,:) )   
     144            ELSE   
     145               rnf_sal(:,:) = 0   
     146               rnf_tmp(:,:) = -999   
     147            ENDIF   
    105148            CALL iom_put( "runoffs", sf_rnf(1)%fnow )         ! runoffs 
    106149         ENDIF 
     
    111154 
    112155 
    113    SUBROUTINE sbc_rnf_init( sf_rnf ) 
     156   SUBROUTINE sbc_rnf_init( sf_rnf, sf_tmp_rnf, sf_sal_rnf )   
    114157      !!---------------------------------------------------------------------- 
    115158      !!                  ***  ROUTINE sbc_rnf_init  *** 
     
    121164      !! ** Action  : - read parameters 
    122165      !!---------------------------------------------------------------------- 
    123       TYPE(FLD), INTENT(inout), DIMENSION(:) :: sf_rnf   ! input data 
    124       !! 
    125       NAMELIST/namsbc_rnf/ cn_dir, ln_rnf_emp, sn_rnf, sn_cnf, ln_rnf_mouth,   & 
    126          &                 rn_hrnf, rn_avt_rnf, rn_rfact 
     166      TYPE(FLD), INTENT(inout), DIMENSION(:) :: sf_rnf, sf_tmp_rnf, sf_sal_rnf   ! input data   
     167      CHARACTER(len=32) ::   rn_dep_file   ! runoff file name   
     168      !!  
     169      NAMELIST/namsbc_rnf/ cn_dir, ln_rnf_emp, sn_rnf, sn_cnf, sn_sal_rnf, sn_tmp_rnf, sn_dep_rnf,   &   
     170         &                 ln_rnf_mouth, ln_rnf_att, rn_hrnf, rn_avt_rnf, rn_rfact   
    127171      !!---------------------------------------------------------------------- 
    128172 
     
    136180      sn_cnf = FLD_N( 'runoffs',     0     , 'sorunoff' ,  .FALSE.   , .true. ,   'yearly'  , ''       , ''         ) 
    137181 
     182      sn_sal_rnf = FLD_N( 'runoffs',  24.  , 'rosaline' ,  .TRUE.    , .true. ,   'yearly'  , ''    , ''  )   
     183      sn_tmp_rnf = FLD_N( 'runoffs',  24.  , 'rotemper' ,  .TRUE.    , .true. ,   'yearly'  , ''    , ''  )   
     184      sn_dep_rnf = FLD_N( 'runoffs',   0.  , 'rodepth'  ,  .FALSE.   , .true. ,   'yearly'  , ''    , ''  )   
    138185      ! 
    139186      REWIND ( numnam )                         ! Read Namelist namsbc_rnf 
     
    160207         IF(lwp) WRITE(numout,*) 
    161208         IF(lwp) WRITE(numout,*) '          runoffs directly provided in the precipitations' 
     209         IF ( ln_rnf_att ) CALL ctl_warn( 'runoffs already included in precipitations & so runoff attributes not included' )  
    162210         ! 
    163211      ELSE                                      ! runoffs read in a file : set sf_rnf structure  
     
    166214         ! fill sf_rnf with sn_rnf and control print 
    167215         CALL fld_fill( sf_rnf, (/ sn_rnf /), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf' ) 
    168          ! 
     216  
     217         IF ( ln_rnf_att ) THEN   
     218            CALL fld_fill (sf_sal_rnf, (/ sn_sal_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff salinity data', 'namsbc_rnf' )   
     219            CALL fld_fill (sf_tmp_rnf, (/ sn_tmp_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff temperature data', 'namsbc_rnf' )   
     220   
     221            rn_dep_file = TRIM( cn_dir )//TRIM( sn_dep_rnf%clname )   
     222            CALL iom_open ( rn_dep_file, inum )                           ! open file   
     223            CALL iom_get  ( inum, jpdom_data, sn_dep_rnf%clvar, rnf_dep )    ! read the river mouth array   
     224            CALL iom_close( inum )                                      ! close file   
     225   
     226            rnf_mod_dep(:,:)=0   
     227            DO jj=1,jpj   
     228              DO ji=1,jpi   
     229                IF ( rnf_dep(ji,jj) > 0.e0 ) THEN   
     230                  jk=2   
     231                  DO WHILE ( jk/=jpkm1 .AND. fsdept(ji,jj,jk) < rnf_dep(ji,jj) );  jk=jk+1;   ENDDO   
     232                  rnf_mod_dep(ji,jj)=jk   
     233                ELSE IF ( rnf_dep(ji,jj) .eq. -1 ) THEN   
     234                  rnf_mod_dep(ji,jj)=1   
     235                ELSE IF ( rnf_dep(ji,jj) .eq. -999 ) THEN   
     236                  rnf_mod_dep(ji,jj)=jpkm1   
     237                ELSE IF ( rnf_dep(ji,jj) /= 0 ) THEN   
     238                  CALL ctl_stop( 'runoff depth not positive, and not -999 or -1, rnf value in file fort.999'  )   
     239                  WRITE(999,*) 'ji, jj, rnf(ji,jj) :', ji, jj, rnf(ji,jj)   
     240                ENDIF   
     241              ENDDO   
     242            ENDDO   
     243         ELSE   
     244            rnf_mod_dep(:,:)=1   
     245         ENDIF   
     246      !  
    169247      ENDIF 
    170248 
     
    179257         ! 
    180258         !                                          ! Number of level over which Kz increase 
     259         IF ( ln_rnf_att )  &   
     260              &  CALL ctl_warn( 'increased mixing turned on but effects may already be spread through depth by ln_rnf_att' )  
    181261         nkrnf = 0 
    182262         IF( rn_hrnf > 0.e0 ) THEN 
Note: See TracChangeset for help on using the changeset viewer.