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 15574 for NEMO/branches/2021/dev_r14318_RK3_stage1/src/OCE/ISF/isfpar.F90 – NEMO

Ignore:
Timestamp:
2021-12-03T20:32:50+01:00 (3 years ago)
Author:
techene
Message:

#2605 #2715 trunk merged into dev_r14318_RK3_stage1

Location:
NEMO/branches/2021/dev_r14318_RK3_stage1
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14318_RK3_stage1

    • Property svn:externals
      •  

        old new  
        99 
        1010# SETTE 
        11 ^/utils/CI/sette@14244        sette 
         11^/utils/CI/sette@HEAD        sette 
         12 
  • NEMO/branches/2021/dev_r14318_RK3_stage1/src/OCE/ISF/isfpar.F90

    r13226 r15574  
    99   !!            3.4  !  2013-03  (P. Mathiot) Merging + parametrization 
    1010   !!            4.1  !  2019-09  (P. Mathiot) Restructuration 
     11   !!            4.2  !  2021-05  (C. Ethe   ) Test and fix oasis case 
    1112   !!---------------------------------------------------------------------- 
    1213 
     
    2930   USE iom            ! I/O library 
    3031   USE fldread        ! read input field at current time step 
    31    USE lbclnk         ! lbc_lnk 
    3232 
    3333   IMPLICIT NONE 
     
    3636   PUBLIC   isf_par, isf_par_init 
    3737 
     38   !! * Substitutions    
     39#  include "do_loop_substitute.h90" 
    3840   !!---------------------------------------------------------------------- 
    3941   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    5658      !!              the name tbl was kept. 
    5759      !! 
     60      !! ** Convention : all fluxes are from isf to oce 
     61      !! 
    5862      !!--------------------------------------------------------------------- 
    5963      !!-------------------------- OUT -------------------------------------- 
     
    6468      INTEGER, INTENT(in) ::   Kmm                                    ! ocean time level index 
    6569      !!--------------------------------------------------------------------- 
     70      INTEGER ::   ji, jj 
    6671      REAL(wp), DIMENSION(jpi,jpj) :: zqoce, zqhc, zqlat, zqh 
    6772      !!--------------------------------------------------------------------- 
     
    7075      CALL isfpar_mlt( kt, Kmm, zqhc, zqoce, pqfwf  ) 
    7176      ! 
    72       ! compute heat and water flux ( > 0 out ) 
    73       pqfwf(:,:) = pqfwf(:,:) * mskisf_par(:,:) 
    74       zqoce(:,:) = zqoce(:,:) * mskisf_par(:,:) 
    75       zqhc (:,:) = zqhc(:,:)  * mskisf_par(:,:) 
    76       ! 
    77       ! compute heat content flux ( > 0 out ) 
    78       zqlat(:,:) = pqfwf(:,:) * rLfusisf    ! 2d latent heat flux (W/m2) 
    79       ! 
    80       ! total heat flux ( > 0 out ) 
    81       zqh(:,:) = ( zqhc (:,:) + zqoce(:,:) ) 
    82       ! 
    83       ! lbclnk on melt and heat fluxes 
    84       CALL lbc_lnk_multi( 'isfmlt', zqh, 'T', 1.0_wp, pqfwf, 'T', 1.0_wp) 
     77      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
     78         ! compute heat and water flux (from isf to oce) 
     79         pqfwf(ji,jj) = pqfwf(ji,jj) * mskisf_par(ji,jj) 
     80         zqoce(ji,jj) = zqoce(ji,jj) * mskisf_par(ji,jj) 
     81         zqhc (ji,jj) = zqhc(ji,jj)  * mskisf_par(ji,jj) 
     82         ! 
     83         ! compute latent heat flux (from isf to oce) 
     84         zqlat(ji,jj) = - pqfwf(ji,jj) * rLfusisf    ! 2d latent heat flux (W/m2) 
     85         ! 
     86         ! total heat flux (from isf to oce) 
     87         zqh(ji,jj) = ( zqhc (ji,jj) + zqoce(ji,jj) ) 
     88         ! 
     89         ! set temperature content 
     90         ptsc(ji,jj,jp_tem) = zqh(ji,jj) * r1_rho0_rcp 
     91      END_2D 
    8592      ! 
    8693      ! output fluxes 
    8794      CALL isf_diags_flx( Kmm, misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par, 'par', pqfwf, zqoce, zqlat, zqhc) 
    88       ! 
    89       ! set temperature content 
    90       ptsc(:,:,jp_tem) = zqh(:,:) * r1_rho0_rcp 
    9195      ! 
    9296      ! write restart variables (qoceisf, qhcisf, fwfisf for now and before) 
     
    9498      ! 
    9599      IF ( ln_isfdebug ) THEN 
     100         IF(lwp) WRITE(numout,*) 
    96101         CALL debug('isf_par: ptsc T',ptsc(:,:,1)) 
    97102         CALL debug('isf_par: ptsc S',ptsc(:,:,2)) 
    98103         CALL debug('isf_par: pqfwf fwf',pqfwf(:,:)) 
     104         IF(lwp) WRITE(numout,*) 
    99105      END IF 
    100106      ! 
     
    175181      CASE ( 'oasis' ) 
    176182         ! 
     183         ALLOCATE( sf_isfpar_fwf(1), STAT=ierr ) 
     184         ALLOCATE( sf_isfpar_fwf(1)%fnow(jpi,jpj,1), sf_isfpar_fwf(1)%fdta(jpi,jpj,1,2) ) 
     185         CALL fld_fill( sf_isfpar_fwf, (/ sn_isfpar_fwf /), cn_isfdir, 'isf_par_init', 'read fresh water flux isf data', 'namisf' ) 
     186         ! 
    177187         IF(lwp) WRITE(numout,*) 
    178188         IF(lwp) WRITE(numout,*) '      ==>>>    isf melt provided by OASIS (cn_isfmlt_par = oasis)' 
Note: See TracChangeset for help on using the changeset viewer.