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 13662 for NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/OCE/SBC/sbcrnf.F90 – NEMO

Ignore:
Timestamp:
2020-10-22T20:49:56+02:00 (4 years ago)
Author:
clem
Message:

update to almost r4.0.4

Location:
NEMO/branches/2019/dev_r11842_SI3-10_EAP
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP

    • Property svn:externals
      •  

        old new  
        1 ^/utils/build/arch@HEAD       arch 
        2 ^/utils/build/makenemo@HEAD   makenemo 
        3 ^/utils/build/mk@HEAD         mk 
        4 ^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
        6 ^/vendors/FCM@HEAD            ext/FCM 
        7 ^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         1^/utils/build/arch@12130      arch 
         2^/utils/build/makenemo@12191  makenemo 
         3^/utils/build/mk@11662        mk 
         4^/utils/tools_r4.0-HEAD@12672 tools 
         5^/vendors/AGRIF/dev@10586     ext/AGRIF 
         6^/vendors/FCM@10134           ext/FCM 
         7^/vendors/IOIPSL@9655         ext/IOIPSL 
         8 
         9# SETTE mapping (inactive) 
         10#^/utils/CI/sette@12135        sette 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/OCE/SBC/sbcrnf.F90

    r11536 r13662  
    1919   USE phycst         ! physical constants 
    2020   USE sbc_oce        ! surface boundary condition variables 
    21    USE sbcisf         ! PM we could remove it I think 
    2221   USE eosbn2         ! Equation Of State 
    23    USE closea        ! closed seas 
     22   USE closea, ONLY: l_clo_rnf, clo_rnf ! closed seas 
    2423   ! 
    2524   USE in_out_manager ! I/O manager 
     
    4342   REAL(wp)                   ::      rn_dep_max        !: depth over which runoffs is spread       (ln_rnf_depth_ini =T) 
    4443   INTEGER                    ::      nn_rnf_depth_file !: create (=1) a runoff depth file or not (=0) 
     44   LOGICAL                    ::   ln_rnf_icb        !: iceberg flux is specified in a file 
    4545   LOGICAL                    ::   ln_rnf_tem        !: temperature river runoffs attribute specified in a file 
    4646   LOGICAL           , PUBLIC ::   ln_rnf_sal        !: salinity    river runoffs attribute specified in a file 
    4747   TYPE(FLD_N)       , PUBLIC ::   sn_rnf            !: information about the runoff file to be read 
    4848   TYPE(FLD_N)                ::   sn_cnf            !: information about the runoff mouth file to be read 
     49   TYPE(FLD_N)                ::   sn_i_rnf          !: information about the iceberg flux file to be read 
    4950   TYPE(FLD_N)                ::   sn_s_rnf          !: information about the salinities of runoff file to be read 
    5051   TYPE(FLD_N)                ::   sn_t_rnf          !: information about the temperatures of runoff file to be read 
     
    6566 
    6667   TYPE(FLD),        ALLOCATABLE, DIMENSION(:) ::   sf_rnf       ! structure: river runoff (file information, fields read) 
     68   TYPE(FLD),        ALLOCATABLE, DIMENSION(:) ::   sf_i_rnf     ! structure: iceberg flux (file information, fields read) 
    6769   TYPE(FLD),        ALLOCATABLE, DIMENSION(:) ::   sf_s_rnf     ! structure: river runoff salinity (file information, fields read)   
    6870   TYPE(FLD),        ALLOCATABLE, DIMENSION(:) ::   sf_t_rnf     ! structure: river runoff temperature (file information, fields read)   
     
    112114      !                                            !-------------------! 
    113115      ! 
    114       IF( .NOT. l_rnfcpl )   CALL fld_read ( kt, nn_fsbc, sf_rnf   )    ! Read Runoffs data and provide it at kt 
     116      ! 
     117      IF( .NOT. l_rnfcpl )  THEN 
     118                            CALL fld_read ( kt, nn_fsbc, sf_rnf   )    ! Read Runoffs data and provide it at kt ( runoffs + iceberg ) 
     119         IF( ln_rnf_icb )   CALL fld_read ( kt, nn_fsbc, sf_i_rnf )    ! idem for iceberg flux if required 
     120      ENDIF 
    115121      IF(   ln_rnf_tem   )   CALL fld_read ( kt, nn_fsbc, sf_t_rnf )    ! idem for runoffs temperature if required 
    116122      IF(   ln_rnf_sal   )   CALL fld_read ( kt, nn_fsbc, sf_s_rnf )    ! idem for runoffs salinity    if required 
     
    118124      IF( MOD( kt - 1, nn_fsbc ) == 0 ) THEN 
    119125         ! 
    120          IF( .NOT. l_rnfcpl )   rnf(:,:) = rn_rfact * ( sf_rnf(1)%fnow(:,:,1) ) * tmask(:,:,1)       ! updated runoff value at time step kt 
     126         IF( .NOT. l_rnfcpl ) THEN 
     127             rnf(:,:) = rn_rfact * ( sf_rnf(1)%fnow(:,:,1) ) * tmask(:,:,1)  ! updated runoff value at time step kt 
     128             IF( ln_rnf_icb ) THEN 
     129                fwficb(:,:) = rn_rfact * ( sf_i_rnf(1)%fnow(:,:,1) ) * tmask(:,:,1)  ! updated runoff value at time step kt 
     130                CALL iom_put( 'iceberg_cea'  , fwficb(:,:)  )         ! output iceberg flux 
     131                CALL iom_put( 'hflx_icb_cea' , fwficb(:,:) * rLfus )   ! output Heat Flux into Sea Water due to Iceberg Thermodynamics --> 
     132             ENDIF 
     133         ENDIF 
    121134         ! 
    122135         !                                                           ! set temperature & salinity content of runoffs 
     
    127140               rnf_tsc(:,:,jp_tem) = sst_m(:,:) * rnf(:,:) * r1_rau0 
    128141            END WHERE 
    129             WHERE( sf_t_rnf(1)%fnow(:,:,1) == -222._wp )             ! where fwf comes from melting of ice shelves or iceberg 
    130                rnf_tsc(:,:,jp_tem) = ztfrz(:,:) * rnf(:,:) * r1_rau0 - rnf(:,:) * rLfusisf * r1_rau0_rcp 
    131             END WHERE 
    132142         ELSE                                                        ! use SST as runoffs temperature 
    133143            !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 
     144            rnf_tsc(:,:,jp_tem) = MAX( sst_m(:,:), 0.0_wp ) * rnf(:,:) * r1_rau0 
    135145         ENDIF 
    136146         !                                                           ! use runoffs salinity data 
    137147         IF( ln_rnf_sal )   rnf_tsc(:,:,jp_sal) = ( sf_s_rnf(1)%fnow(:,:,1) ) * rnf(:,:) * r1_rau0 
    138148         !                                                           ! 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 
     149                                         CALL iom_put( 'runoffs'     , rnf(:,:)                         )   ! output runoff mass flux 
    140150         IF( iom_use('hflx_rnf_cea') )   CALL iom_put( 'hflx_rnf_cea', rnf_tsc(:,:,jp_tem) * rau0 * rcp )   ! output runoff sensible heat (W/m2) 
    141151      ENDIF 
     
    242252      REAL(wp), DIMENSION(jpi,jpj,2) :: zrnfcl     
    243253      !! 
    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,   & 
     254      NAMELIST/namsbc_rnf/ cn_dir            , ln_rnf_depth, ln_rnf_tem, ln_rnf_sal, ln_rnf_icb,   & 
     255         &                 sn_rnf, sn_cnf    , sn_i_rnf, sn_s_rnf    , sn_t_rnf  , sn_dep_rnf,   & 
    246256         &                 ln_rnf_mouth      , rn_hrnf     , rn_avt_rnf, rn_rfact,     & 
    247257         &                 ln_rnf_depth_ini  , rn_dep_max  , rn_rnf_max, nn_rnf_depth_file 
     
    265275      !                                   ! ============ 
    266276      ! 
    267       REWIND( numnam_ref )              ! Namelist namsbc_rnf in reference namelist : Runoffs  
     277      REWIND( numnam_ref ) 
    268278      READ  ( numnam_ref, namsbc_rnf, IOSTAT = ios, ERR = 901) 
    269279901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc_rnf in reference namelist' ) 
    270280 
    271       REWIND( numnam_cfg )              ! Namelist namsbc_rnf in configuration namelist : Runoffs 
     281      REWIND( numnam_cfg ) 
    272282      READ  ( numnam_cfg, namsbc_rnf, IOSTAT = ios, ERR = 902 ) 
    273283902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namsbc_rnf in configuration namelist' ) 
     
    299309         IF( sn_rnf%ln_tint ) ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,1,2) ) 
    300310         CALL fld_fill( sf_rnf, (/ sn_rnf /), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf', no_print ) 
     311         ! 
     312         IF( ln_rnf_icb ) THEN                      ! Create (if required) sf_i_rnf structure 
     313            IF(lwp) WRITE(numout,*) 
     314            IF(lwp) WRITE(numout,*) '          iceberg flux read in a file' 
     315            ALLOCATE( sf_i_rnf(1), STAT=ierror  ) 
     316            IF( ierror > 0 ) THEN 
     317               CALL ctl_stop( 'sbc_rnf_init: unable to allocate sf_i_rnf structure' )   ;   RETURN 
     318            ENDIF 
     319            ALLOCATE( sf_i_rnf(1)%fnow(jpi,jpj,1)   ) 
     320            IF( sn_i_rnf%ln_tint ) ALLOCATE( sf_i_rnf(1)%fdta(jpi,jpj,1,2) ) 
     321            CALL fld_fill (sf_i_rnf, (/ sn_i_rnf /), cn_dir, 'sbc_rnf_init', 'read iceberg flux data', 'namsbc_rnf' ) 
     322         ELSE 
     323            fwficb(:,:) = 0._wp 
     324         ENDIF 
     325 
    301326      ENDIF 
    302327      ! 
     
    341366               IF( h_rnf(ji,jj) > 0._wp ) THEN 
    342367                  jk = 2 
    343                   DO WHILE ( jk /= mbkt(ji,jj) .AND. gdept_0(ji,jj,jk) < h_rnf(ji,jj) ) ;  jk = jk + 1 
     368                  DO WHILE ( jk < mbkt(ji,jj) .AND. gdept_0(ji,jj,jk) < h_rnf(ji,jj) ) ;  jk = jk + 1 
    344369                  END DO 
    345370                  nk_rnf(ji,jj) = jk 
     
    398423               IF( zrnfcl(ji,jj,1) > 0._wp ) THEN 
    399424                  jk = 2 
    400                   DO WHILE ( jk /= mbkt(ji,jj) .AND. gdept_0(ji,jj,jk) < h_rnf(ji,jj) ) ;  jk = jk + 1 
     425                  DO WHILE ( jk < mbkt(ji,jj) .AND. gdept_0(ji,jj,jk) < h_rnf(ji,jj) ) ;  jk = jk + 1 
    401426                  END DO 
    402427                  nk_rnf(ji,jj) = jk 
     
    439464         !                                      !    - mixed upstream-centered (ln_traadv_cen2=T) 
    440465         ! 
    441          IF ( ln_rnf_depth )   CALL ctl_warn( 'sbc_rnf_init: increased mixing turned on but effects may already',   & 
     466         IF( ln_rnf_depth )   CALL ctl_warn( 'sbc_rnf_init: increased mixing turned on but effects may already',   & 
    442467            &                                              'be spread through depth by ln_rnf_depth'               ) 
    443468         ! 
Note: See TracChangeset for help on using the changeset viewer.