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 5381 for branches/2015/dev_r5218_CNRS17_coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcrnf.F90 – NEMO

Ignore:
Timestamp:
2015-06-09T00:48:54+02:00 (9 years ago)
Author:
smasson
Message:

dev_r5218_CNRS17_coupling: continue...

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5218_CNRS17_coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcrnf.F90

    r4990 r5381  
    5151   REAL(wp)          , PUBLIC ::   rn_rfact        !: multiplicative factor for runoff 
    5252 
     53   LOGICAL           , PUBLIC ::   l_rnfcpl = .false.       ! runoffs recieved from oasis 
     54 
    5355   INTEGER , PUBLIC  ::   nkrnf = 0         !: nb of levels over which Kz is increased at river mouths 
    5456   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rnfmsk              !: river mouth mask (hori.) 
     
    120122         !                                                !-------------------! 
    121123         ! 
    122                              CALL fld_read ( kt, nn_fsbc, sf_rnf   )    ! Read Runoffs data and provide it at kt 
    123          IF( ln_rnf_tem  )   CALL fld_read ( kt, nn_fsbc, sf_t_rnf )    ! idem for runoffs temperature if required 
    124          IF( ln_rnf_sal  )   CALL fld_read ( kt, nn_fsbc, sf_s_rnf )    ! idem for runoffs salinity    if required 
     124         IF( .NOT. l_rnfcpl )   CALL fld_read ( kt, nn_fsbc, sf_rnf   )    ! Read Runoffs data and provide it at kt 
     125         IF(   ln_rnf_tem   )   CALL fld_read ( kt, nn_fsbc, sf_t_rnf )    ! idem for runoffs temperature if required 
     126         IF(   ln_rnf_sal   )   CALL fld_read ( kt, nn_fsbc, sf_s_rnf )    ! idem for runoffs salinity    if required 
    125127         ! 
    126128         ! Runoff reduction only associated to the ORCA2_LIM configuration 
    127129         ! when reading the NetCDF file runoff_1m_nomask.nc 
    128          IF( cp_cfg == 'orca' .AND. jp_cfg == 2 )   THEN 
     130         IF( cp_cfg == 'orca' .AND. jp_cfg == 2 .AND. .NOT. l_rnfcpl )   THEN 
    129131            WHERE( 40._wp < gphit(:,:) .AND. gphit(:,:) < 65._wp ) 
    130132               sf_rnf(1)%fnow(:,:,1) = 0.85 * sf_rnf(1)%fnow(:,:,1) 
     
    134136         IF( MOD( kt - 1, nn_fsbc ) == 0 ) THEN 
    135137            ! 
    136             rnf(:,:) = rn_rfact * ( sf_rnf(1)%fnow(:,:,1) )       ! updated runoff value at time step kt 
     138            IF( .NOT. l_rnfcpl )   rnf(:,:) = rn_rfact * ( sf_rnf(1)%fnow(:,:,1) )       ! updated runoff value at time step kt 
    137139            ! 
    138140            !                                                     ! set temperature & salinity content of runoffs 
     
    152154            IF( ln_rnf_sal )   rnf_tsc(:,:,jp_sal) = ( sf_s_rnf(1)%fnow(:,:,1) ) * rnf(:,:) * r1_rau0 
    153155            !                                                           ! else use S=0 for runoffs (done one for all in the init) 
    154             IF ( ANY( rnf(:,:) < 0._wp ) ) z_err=1 
    155             IF(lk_mpp) CALL mpp_sum(z_err) 
    156             IF( z_err > 0 ) CALL ctl_stop( 'sbc_rnf : negative runnoff values exist' ) 
    157             ! 
    158156            CALL iom_put( "runoffs", rnf )         ! output runoffs arrays 
    159157         ENDIF 
     
    161159      ENDIF 
    162160      ! 
     161      !                                                ! ---------------------------------------- ! 
    163162      IF( kt == nit000 ) THEN                          !   set the forcing field at nit000 - 1    ! 
    164163         !                                             ! ---------------------------------------- ! 
     
    290289      ENDIF 
    291290      ! 
     291      IF( ln_rnf_emp .AND. nn_components == jp_iam_opa ) THEN 
     292         CALL ctl_stop( 'sbc_rnf_init: ln_rnf_emp must be false in case of SAS-OPA coupling' )   ;   RETURN 
     293      ENDIF 
    292294      !                                   ! ================== 
    293295      !                                   !   Type of runoff 
     
    306308      ELSE                                      !==  runoffs read in a file : set sf_rnf structure  ==! 
    307309         ! 
    308          ALLOCATE( sf_rnf(1), STAT=ierror )         ! Create sf_rnf structure (runoff inflow) 
    309          IF(lwp) WRITE(numout,*) 
    310          IF(lwp) WRITE(numout,*) '          runoffs inflow read in a file' 
    311          IF( ierror > 0 ) THEN 
    312             CALL ctl_stop( 'sbc_rnf: unable to allocate sf_rnf structure' )   ;   RETURN 
    313          ENDIF 
    314          ALLOCATE( sf_rnf(1)%fnow(jpi,jpj,1)   ) 
    315          IF( sn_rnf%ln_tint ) ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,1,2) ) 
    316          !                                          ! fill sf_rnf with the namelist (sn_rnf) and control print 
    317          CALL fld_fill( sf_rnf, (/ sn_rnf /), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf' ) 
     310         IF( .NOT. l_rnfcpl ) THEN                     
     311            ALLOCATE( sf_rnf(1), STAT=ierror )      ! Create (if required) sf_rnf structure (runoff inflow) 
     312            IF(lwp) WRITE(numout,*) 
     313            IF(lwp) WRITE(numout,*) '          runoffs inflow read in a file' 
     314            IF( ierror > 0 ) THEN 
     315               CALL ctl_stop( 'sbc_rnf: unable to allocate sf_rnf structure' )   ;   RETURN 
     316            ENDIF 
     317            ALLOCATE( sf_rnf(1)%fnow(jpi,jpj,1)   ) 
     318            IF( sn_rnf%ln_tint ) ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,1,2) ) 
     319            CALL fld_fill( sf_rnf, (/ sn_rnf /), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf' ) 
     320         ENDIF 
    318321         ! 
    319322         IF( ln_rnf_tem ) THEN                      ! Create (if required) sf_t_rnf structure 
Note: See TracChangeset for help on using the changeset viewer.