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 11995 for NEMO/branches/2019/dev_r11643_ENHANCE-11_CEthe_Shaconemo_diags/src/OCE/SBC/sbcrnf.F90 – NEMO

Ignore:
Timestamp:
2019-11-28T11:35:08+01:00 (4 years ago)
Author:
cetlod
Message:

Finalisation of CMIP6 diags implementation, src directory

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11643_ENHANCE-11_CEthe_Shaconemo_diags/src/OCE/SBC/sbcrnf.F90

    r11536 r11995  
    4343   REAL(wp)                   ::      rn_dep_max        !: depth over which runoffs is spread       (ln_rnf_depth_ini =T) 
    4444   INTEGER                    ::      nn_rnf_depth_file !: create (=1) a runoff depth file or not (=0) 
     45   LOGICAL                    ::   ln_rnf_icb        !: iceberg flux is specified in a file 
    4546   LOGICAL                    ::   ln_rnf_tem        !: temperature river runoffs attribute specified in a file 
    4647   LOGICAL           , PUBLIC ::   ln_rnf_sal        !: salinity    river runoffs attribute specified in a file 
    4748   TYPE(FLD_N)       , PUBLIC ::   sn_rnf            !: information about the runoff file to be read 
    4849   TYPE(FLD_N)                ::   sn_cnf            !: information about the runoff mouth file to be read 
     50   TYPE(FLD_N)                ::   sn_i_rnf        !: information about the iceberg flux file to be read 
    4951   TYPE(FLD_N)                ::   sn_s_rnf          !: information about the salinities of runoff file to be read 
    5052   TYPE(FLD_N)                ::   sn_t_rnf          !: information about the temperatures of runoff file to be read 
     
    6567 
    6668   TYPE(FLD),        ALLOCATABLE, DIMENSION(:) ::   sf_rnf       ! structure: river runoff (file information, fields read) 
     69   TYPE(FLD),        ALLOCATABLE, DIMENSION(:) ::   sf_i_rnf     ! structure: iceberg flux (file information, fields read) 
    6770   TYPE(FLD),        ALLOCATABLE, DIMENSION(:) ::   sf_s_rnf     ! structure: river runoff salinity (file information, fields read)   
    6871   TYPE(FLD),        ALLOCATABLE, DIMENSION(:) ::   sf_t_rnf     ! structure: river runoff temperature (file information, fields read)   
     
    112115      !                                            !-------------------! 
    113116      ! 
    114       IF( .NOT. l_rnfcpl )   CALL fld_read ( kt, nn_fsbc, sf_rnf   )    ! Read Runoffs data and provide it at kt 
     117      ! 
     118      IF( .NOT. l_rnfcpl )  THEN 
     119                            CALL fld_read ( kt, nn_fsbc, sf_rnf   )    ! Read Runoffs data and provide it at kt ( runoffs + iceberg ) 
     120         IF( ln_rnf_icb )   CALL fld_read ( kt, nn_fsbc, sf_i_rnf )    ! idem for iceberg flux if required 
     121      ENDIF 
    115122      IF(   ln_rnf_tem   )   CALL fld_read ( kt, nn_fsbc, sf_t_rnf )    ! idem for runoffs temperature if required 
    116123      IF(   ln_rnf_sal   )   CALL fld_read ( kt, nn_fsbc, sf_s_rnf )    ! idem for runoffs salinity    if required 
     
    118125      IF( MOD( kt - 1, nn_fsbc ) == 0 ) THEN 
    119126         ! 
    120          IF( .NOT. l_rnfcpl )   rnf(:,:) = rn_rfact * ( sf_rnf(1)%fnow(:,:,1) ) * tmask(:,:,1)       ! updated runoff value at time step kt 
     127         IF( .NOT. l_rnfcpl ) THEN 
     128             rnf(:,:) = rn_rfact * ( sf_rnf(1)%fnow(:,:,1) ) * tmask(:,:,1)  ! updated runoff value at time step kt 
     129             IF( ln_rnf_icb ) THEN 
     130                fwficb(:,:) = rn_rfact * ( sf_i_rnf(1)%fnow(:,:,1) ) * tmask(:,:,1)  ! updated runoff value at time step kt 
     131                CALL iom_put( 'iceberg_cea'  , fwficb(:,:)  )         ! output iceberg flux 
     132                CALL iom_put( 'hflx_icb_cea' , fwficb(:,:) * rLfus )   ! output Heat Flux into Sea Water due to Iceberg Thermodynamics --> 
     133             ENDIF 
     134         ENDIF 
    121135         ! 
    122136         !                                                           ! set temperature & salinity content of runoffs 
     
    132146         ELSE                                                        ! use SST as runoffs temperature 
    133147            !CEOD River is fresh water so must at least be 0 unless we consider ice 
    134             rnf_tsc(:,:,jp_tem) = MAX(sst_m(:,:),0.0_wp) * rnf(:,:) * r1_rau0 
     148            rnf_tsc(:,:,jp_tem) = MAX( sst_m(:,:), 0.0_wp ) * rnf(:,:) * r1_rau0 
    135149         ENDIF 
    136150         !                                                           ! use runoffs salinity data 
    137151         IF( ln_rnf_sal )   rnf_tsc(:,:,jp_sal) = ( sf_s_rnf(1)%fnow(:,:,1) ) * rnf(:,:) * r1_rau0 
    138152         !                                                           ! else use S=0 for runoffs (done one for all in the init) 
    139          IF( iom_use('runoffs') )        CALL iom_put( 'runoffs'     , rnf(:,:)                         )   ! output runoff mass flux 
     153                                         CALL iom_put( 'runoffs'     , rnf(:,:)                         )   ! output runoff mass flux 
    140154         IF( iom_use('hflx_rnf_cea') )   CALL iom_put( 'hflx_rnf_cea', rnf_tsc(:,:,jp_tem) * rau0 * rcp )   ! output runoff sensible heat (W/m2) 
    141155      ENDIF 
     
    242256      REAL(wp), DIMENSION(jpi,jpj,2) :: zrnfcl     
    243257      !! 
    244       NAMELIST/namsbc_rnf/ cn_dir            , ln_rnf_depth, ln_rnf_tem, ln_rnf_sal,   & 
    245          &                 sn_rnf, sn_cnf    , sn_s_rnf    , sn_t_rnf  , sn_dep_rnf,   & 
     258      NAMELIST/namsbc_rnf/ cn_dir            , ln_rnf_depth, ln_rnf_tem, ln_rnf_sal, ln_rnf_icb,   & 
     259         &                 sn_rnf, sn_cnf    , sn_i_rnf, sn_s_rnf    , sn_t_rnf  , sn_dep_rnf,   & 
    246260         &                 ln_rnf_mouth      , rn_hrnf     , rn_avt_rnf, rn_rfact,     & 
    247261         &                 ln_rnf_depth_ini  , rn_dep_max  , rn_rnf_max, nn_rnf_depth_file 
     
    299313         IF( sn_rnf%ln_tint ) ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,1,2) ) 
    300314         CALL fld_fill( sf_rnf, (/ sn_rnf /), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf', no_print ) 
     315         ! 
     316         IF( ln_rnf_icb ) THEN                      ! Create (if required) sf_i_rnf structure 
     317            IF(lwp) WRITE(numout,*) 
     318            IF(lwp) WRITE(numout,*) '          iceberg flux read in a file' 
     319            ALLOCATE( sf_i_rnf(1), STAT=ierror  ) 
     320            IF( ierror > 0 ) THEN 
     321               CALL ctl_stop( 'sbc_rnf_init: unable to allocate sf_i_rnf structure' )   ;   RETURN 
     322            ENDIF 
     323            ALLOCATE( sf_i_rnf(1)%fnow(jpi,jpj,1)   ) 
     324            IF( sn_i_rnf%ln_tint ) ALLOCATE( sf_i_rnf(1)%fdta(jpi,jpj,1,2) ) 
     325            CALL fld_fill (sf_i_rnf, (/ sn_i_rnf /), cn_dir, 'sbc_rnf_init', 'read iceberg flux data', 'namsbc_rnf' ) 
     326         ELSE 
     327            fwficb(:,:) = 0._wp 
     328         ENDIF 
     329 
    301330      ENDIF 
    302331      ! 
Note: See TracChangeset for help on using the changeset viewer.