Changeset 11541
- Timestamp:
- 2019-09-12T18:41:17+02:00 (4 years ago)
- Location:
- NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE
- Files:
-
- 18 edited
Legend:
- Unmodified
- Added
- Removed
-
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/DYN/divhor.F90
r11529 r11541 64 64 INTEGER :: ji, jj, jk ! dummy loop indices 65 65 REAL(wp) :: zraur, zdep ! local scalars 66 REAL(wp), DIMENSION(jpi,jpj) :: ztmp 66 67 !!---------------------------------------------------------------------- 67 68 ! … … 85 86 END DO 86 87 END DO 88 89 ztmp = 0.0 90 DO jk = jpkm1,1,-1 91 ztmp(:,:) = ztmp(:,:) + hdivn(:,:,jk) * e3t_n(:,:,jk) 92 END DO 93 CALL debug('divhor 1',ztmp) 94 87 95 #if defined key_agrif 88 96 IF( .NOT. Agrif_Root() ) THEN … … 105 113 CALL lbc_lnk( 'divhor', hdivn, 'T', 1. ) ! (no sign change) 106 114 ! 115 ztmp = 0.0 116 DO jk = jpkm1,1,-1 117 ztmp(:,:) = ztmp(:,:) + hdivn(:,:,jk) * e3t_n(:,:,jk) 118 END DO 119 CALL debug('divhor 2',ztmp) 120 ! 107 121 IF( ln_timing ) CALL timing_stop('div_hor') 108 122 ! -
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/DYN/dynnxt.F90
r11521 r11541 244 244 ! 245 245 ! ice shelf melting 246 IF ( ln_isf ) CALL isf_dynnxt( zcoef)246 IF ( ln_isf ) CALL isf_dynnxt( kt, atfp * rdt ) 247 247 ! 248 248 IF( ln_dynadv_vec ) THEN ! Asselin filter applied on velocity -
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/DYN/dynspg_ts.F90
r11529 r11541 382 382 !!gm Is it correct to do so ? I think so... 383 383 384 384 ! 385 385 ! !* barotropic Coriolis trends (vorticity scheme dependent) 386 386 ! ! -------------------------------------------------------- … … 631 631 ! !* Right-Hand-Side of the barotropic ssh equation 632 632 ! ! ----------------------------------------------- 633 ! ! Surface net water flux and rivers633 ! ! Surface net water flux, rivers and ice shelves 634 634 IF (ln_bt_fw) THEN 635 635 zssh_frc(:,:) = r1_rau0 * ( emp(:,:) - rnf(:,:) + fwfisf_cav(:,:) + fwfisf_par(:,:) ) 636 636 ELSE 637 637 zztmp = r1_rau0 * r1_2 638 zssh_frc(:,:) = zztmp * ( emp(:,:) + emp_b(:,:) - rnf(:,:) - rnf_b(:,:) & 638 zssh_frc(:,:) = zztmp * ( emp(:,:) + emp_b(:,:) & 639 & - rnf(:,:) - rnf_b(:,:) & 639 640 & + fwfisf_cav(:,:) + fwfisf_cav_b(:,:) & 640 641 & + fwfisf_par(:,:) + fwfisf_par_b(:,:) ) … … 645 646 ENDIF 646 647 ! 647 IF( ll_isfcpl_cons ) THEN 648 zssh_frc(:,:) = zssh_frc(:,:) + risfcpl_cons_ssh(:,:) 649 END IF 650 ! 651 IF( ln_isfcpl .AND. ln_rstart .AND. kt == nit000 ) THEN 652 zssh_frc(:,:) = zssh_frc(:,:) + risfcpl_ssh(:,:) 648 ! ! ice sheet coupling 649 IF ( ln_isf .AND. ln_isfcpl ) THEN 650 ! 651 ! ice sheet coupling 652 IF( ln_rstart .AND. kt == nit000 ) THEN 653 zssh_frc(:,:) = zssh_frc(:,:) + risfcpl_ssh(:,:) 654 END IF 655 ! 656 ! conservation option 657 IF( ln_isfcpl_cons ) THEN 658 zssh_frc(:,:) = zssh_frc(:,:) + risfcpl_cons_ssh(:,:) 659 END IF 660 ! 653 661 END IF 654 662 ! -
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/DYN/sshwzv.F90
r11521 r11541 261 261 & + fwfisf_par_b(:,:) - fwfisf_par(:,:) ) * ssmask(:,:) 262 262 ENDIF 263 264 ! ice sheet coupling 265 IF ( ln_isf .AND. ln_isfcpl .AND. kt == nit000+1) sshb(:,:) = sshb(:,:) - atfp * rdt * ( risfcpl_ssh(:,:) - 0.0 ) * ssmask(:,:) 266 263 267 sshn(:,:) = ssha(:,:) ! now <-- after 264 268 ENDIF -
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isf.F90
r11529 r11541 71 71 ! 0.1 -------- ice shelf cavity parameter -------------- 72 72 LOGICAL , PUBLIC :: l_isfoasis 73 REAL(wp), PUBLIC :: r1_Lfusisf !: 1/rLfusisf74 73 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: risfload !: ice shelf load 75 74 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fwfisf_oasis … … 97 96 ! 98 97 ! 0.4 -------- coupling namelist parameter ------------- 99 LOGICAL , PUBLIC :: ll_isfcpl !:100 LOGICAL , PUBLIC :: ll_isfcpl_cons !:101 98 INTEGER , PUBLIC :: nstp_iscpl !: 102 99 REAL(wp), PUBLIC :: rdt_iscpl !: -
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfcav.F90
r11521 r11541 1 1 MODULE isfcav 2 2 !!====================================================================== 3 !! *** MODULE sbcisf***4 !! Surface module : update surface ocean boundary conditionunder ice5 !! shelf3 !! *** MODULE isfcav *** 4 !! Ice shelf cavity module : update ice shelf melting under ice 5 !! shelf 6 6 !!====================================================================== 7 7 !! History : 3.2 ! 2011-02 (C.Harris ) Original code isf cav 8 !! X.X ! 2006-02 (C. Wang ) Original code bg039 8 !! 3.4 ! 2013-03 (P. Mathiot) Merging + parametrization 9 !! 4.1 ! 2019-09 (P. Mathiot) Split ice shelf cavity and ice shelf parametrisation 10 10 !!---------------------------------------------------------------------- 11 11 12 12 !!---------------------------------------------------------------------- 13 !! sbc_isf : update sbcunder ice shelf13 !! isf_cav : update ice shelf melting under ice shelf 14 14 !!---------------------------------------------------------------------- 15 15 USE oce ! ocean dynamics and tracers 16 USE isf ! 17 USE isftbl ! 18 USE isfcavmlt 19 USE isfcavgam 20 USE isfdiags 16 USE isf ! ice shelf public variables 17 USE isftbl ! ice shelf top boundary layer properties 18 USE isfcavmlt ! ice shelf melt formulation 19 USE isfcavgam ! ice shelf melt exchange coeficient 20 USE isfdiags ! ice shelf diags 21 21 USE dom_oce ! ocean space and time domain 22 22 USE phycst ! physical constants … … 26 26 USE iom ! I/O library 27 27 USE fldread ! read input field at current time step 28 USE lbclnk ! 28 USE lbclnk ! lbclnk 29 29 30 30 IMPLICIT NONE … … 43 43 SUBROUTINE isf_cav( kt, ptsc, pqfwf ) 44 44 !!--------------------------------------------------------------------- 45 !! *** ROUTINE sbc_isf_cav ***45 !! *** ROUTINE isf_cav *** 46 46 !! 47 47 !! ** Purpose : handle surface boundary condition under ice shelf 48 48 !! 49 !! ** Method : -49 !! ** Method : based on Mathiot et al. (2017) 50 50 !! 51 !! ** Action : utau, vtau : remain unchanged 52 !! taum, wndm : remain unchanged 53 !! qns : update heat flux below ice shelf 54 !! emp, emps : update freshwater flux below ice shelf 51 !! ** Action : - compute geometry of the Losch top bournary layer (see Losch et al. 2008) 52 !! - depending on the chooses option 53 !! - compute temperature/salt in the tbl 54 !! - compute exchange coeficient 55 !! - compute heat and fwf fluxes 56 !! - output 55 57 !!--------------------------------------------------------------------- 56 58 !!-------------------------- OUT -------------------------------------- … … 68 70 REAL(wp), DIMENSION(jpi,jpj) :: zttbl, zstbl 69 71 !!--------------------------------------------------------------------- 70 !71 ! compute misfkb_par, rhisf_tbl72 rhisf_tbl_cav(:,:) = rn_htbl * mskisf_cav(:,:)73 CALL isf_tbl_lvl( ht_n, e3t_n, misfkt_cav, misfkb_cav, rhisf_tbl_cav, rfrac_tbl_cav )74 72 ! 75 73 ! compute T/S/U/V for the top boundary layer … … 118 116 END IF 119 117 END SELECT 120 118 ! 121 119 END DO 122 120 ! … … 145 143 SUBROUTINE isf_cav_init 146 144 !!--------------------------------------------------------------------- 147 !! *** ROUTINE isf_ diags_2dto3d***145 !! *** ROUTINE isf_cav_init *** 148 146 !! 149 !! ** Purpose : 147 !! ** Purpose : initialisation of variable needed to compute melt under an ice shelf 150 148 !! 151 149 !!---------------------------------------------------------------------- -
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfcavgam.F90
r11521 r11541 2 2 !!====================================================================== 3 3 !! *** MODULE isfgammats *** 4 !! Ice shelf module : compute exchange coeficient at the ice/ocean interface4 !! Ice shelf gamma module : compute exchange coeficient at the ice/ocean interface 5 5 !!====================================================================== 6 6 !! History : 4.1 ! (P. Mathiot) original … … 8 8 9 9 !!---------------------------------------------------------------------- 10 !! isf _gammats : compute exchange coeficient gamma10 !! isfcav_gammats : compute exchange coeficient gamma 11 11 !!---------------------------------------------------------------------- 12 12 USE oce ! ocean dynamics and tracers -
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfcavmlt.F90
r11495 r11541 1 1 MODULE isfcavmlt 2 2 !!====================================================================== 3 !! *** MODULE isfcav _mlt ***3 !! *** MODULE isfcavmlt *** 4 4 !! ice shelf module : update surface ocean boundary condition under ice 5 5 !! shelf … … 9 9 10 10 !!---------------------------------------------------------------------- 11 !! isfcav_mlt : 11 !! isfcav_mlt : update surface ocean boundary condition under ice shelf 12 12 !!---------------------------------------------------------------------- 13 13 USE oce ! ocean dynamics and tracers 14 14 USE isf ! ice shelf public variables 15 USE isfutils16 15 USE dom_oce ! ocean space and time domain 17 16 USE phycst ! physical constants … … 42 41 & pqhc, pqoce, pqfwf ) 43 42 !!---------------------------------------------------------------------- 43 !! 44 !! *** ROUTINE isfcav_mlt *** 44 45 !! 45 46 !! ** Purpose : compute or read ice shelf fwf/heat fluxes in the ice shelf cavity … … 79 80 ! ------------------------------------------------------------------------------------------------------- 80 81 81 SUBROUTINE isfcav_mlt_spe(kt, pstbl, 82 SUBROUTINE isfcav_mlt_spe(kt, pstbl, & ! <<== in 82 83 & pqhc , pqoce, pqfwf ) ! ==>> out 83 84 !!---------------------------------------------------------------------- 85 !! 86 !! *** ROUTINE isfcav_mlt_spe *** 87 !! 84 88 !! ** Purpose : - read ice shelf melt from forcing file 85 89 !! - compute ocea-ice heat flux (assuming it is equal to latent heat) … … 109 113 END SUBROUTINE isfcav_mlt_spe 110 114 111 SUBROUTINE isfcav_mlt_2eq(pgt, pttbl, pstbl, & ! <<== in 112 & pqhc , pqoce, pqfwf ) ! ==>> out 113 !!---------------------------------------------------------------------- 115 SUBROUTINE isfcav_mlt_2eq(pgt , pttbl, pstbl, & ! <<== in 116 & pqhc, pqoce, pqfwf ) ! ==>> out 117 !!---------------------------------------------------------------------- 118 !! 119 !! *** ROUTINE isfcav_mlt_spe *** 120 !! 114 121 !! ** Purpose : Compute ice shelf fwf/heqt fluxes using ISOMIP formulation (Hunter et al., 2006) 115 122 !! … … 141 148 ! 142 149 ! compute ocean-ice heat flux and then derive fwf assuming that ocean heat flux equal latent heat 143 pqfwf(:,:) = - pgt(:,:) * rau0_rcp * zthd(:,:) * r1_Lfusisf! fresh water flux ( > 0 out )150 pqfwf(:,:) = - pgt(:,:) * rau0_rcp * zthd(:,:) / rLfusisf ! fresh water flux ( > 0 out ) 144 151 pqoce(:,:) = - pqfwf(:,:) * rLfusisf ! ocea-ice flux ( > 0 out ) 145 152 pqhc (:,:) = pqfwf(:,:) * ztfrz(:,:) * rcp ! heat content flux ( > 0 out ) … … 150 157 END SUBROUTINE isfcav_mlt_2eq 151 158 152 SUBROUTINE isfcav_mlt_3eq(pgt, pgs , pttbl, pstbl, & 153 & pqhc, pqoce, pqfwf ) 154 !!---------------------------------------------------------------------- 159 SUBROUTINE isfcav_mlt_3eq(pgt, pgs , pttbl, pstbl, & ! <<== in 160 & pqhc, pqoce, pqfwf ) ! ==>> out 161 !!---------------------------------------------------------------------- 162 !! 163 !! *** ROUTINE isfcav_mlt_3eq *** 164 !! 155 165 !! ** Purpose : Compute ice shelf fwf/heqt fluxes using the 3 equation formulation 156 166 !! … … 232 242 END SUBROUTINE isfcav_mlt_3eq 233 243 234 SUBROUTINE isfcav_mlt_oasis(kt, pstbl, 244 SUBROUTINE isfcav_mlt_oasis(kt, pstbl, & ! <<== in 235 245 & pqhc , pqoce, pqfwf ) ! ==>> out 236 246 !!---------------------------------------------------------------------- 247 !! *** ROUTINE isfcav_mlt_oasis *** 237 248 !! 238 249 !! ** Purpose : scale the fwf read from input file by the total amount received by the sbccpl interface … … 282 293 END SUBROUTINE isfcav_mlt_oasis 283 294 284 !SUBROUTINE isfmlt_3eq_frz_ktm1285 ! compute tfrz based on sfrz value at kt-1 (need to be SAVED local array)286 ! => should reduce error due to linarisation287 ! compute qfwf (eq 24)288 ! compute zqoce, zqlat, zqcon, zqhc289 ! compute sfrz (eq 26)290 !END SUBROUTINE isfmlt_3eq_frz_ktm1291 292 295 END MODULE isfcavmlt -
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfhdiv.F90
r11529 r11541 20 20 !! *** SUBROUTINE isf_hdiv *** 21 21 !! 22 !! ** Purpose : 22 !! ** Purpose : update the horizontal divergence with the ice shelf contribution 23 !! (parametrisation, explicit, ice sheet coupling conservation 24 !! increment) 23 25 !! 24 !! ** Method :25 !!26 !! ** Action : phdiv decreased by the fwf inflow (isf melt in this case)27 26 !!---------------------------------------------------------------------- 28 27 REAL(wp), DIMENSION(:,:,:), INTENT( inout ) :: phdiv ! horizontal divergence … … 38 37 IF ( ln_isfpar_mlt ) CALL isf_hdiv_mlt(misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par, fwfisf_par, fwfisf_par_b, phdiv) 39 38 ! 40 END IF41 !42 ! ice sheet coupling contribution (if conservation needed)43 IF ( ll_isfcpl ) THEN44 39 ! 45 ! correct divergence only for the first time step 46 IF ( kt == nit000 ) CALL isf_hdiv_cpl(risfcpl_vol, phdiv) 47 ! 48 ! correct divergence every time step to remove any trend due to coupling 49 IF ( ll_isfcpl_cons ) CALL isf_hdiv_cpl(risfcpl_cons_vol, phdiv) 40 ! ice sheet coupling contribution 41 IF ( ln_isfcpl ) THEN 42 ! 43 ! correct divergence only for the first time step 44 IF ( kt == nit000 ) CALL isf_hdiv_cpl(risfcpl_vol , phdiv) 45 IF ( kt == nit000+1 ) CALL isf_hdiv_cpl(risfcpl_vol*0.5_wp, phdiv) 46 ! 47 ! correct divergence every time step to remove any trend due to coupling 48 ! conservation option 49 IF ( ln_isfcpl_cons ) CALL isf_hdiv_cpl(risfcpl_cons_vol, phdiv) 50 ! 51 END IF 50 52 ! 51 53 END IF … … 57 59 !! *** SUBROUTINE sbc_isf_div *** 58 60 !! 59 !! ** Purpose : update the horizontal divergence with the runoff inflow61 !! ** Purpose : update the horizontal divergence with the ice shelf inflow 60 62 !! 61 !! ** Method : 62 !! CAUTION : risf_tsc(:,:,jp_sal) is negative (outflow) increase the 63 !! divergence and expressed in m/s 63 !! ** Method : pfwf is positive (outflow) and expressed as kg/m2/s 64 !! increase the divergence 64 65 !! 65 !! ** Action : phdivn decreased by the runoff inflow66 !! ** Action : phdivn increased by the ice shelf outflow 66 67 !!---------------------------------------------------------------------- 67 68 REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) :: phdiv … … 73 74 INTEGER :: ji, jj, jk ! dummy loop indices 74 75 INTEGER :: ikt, ikb 75 REAL(wp), DIMENSION(jpi,jpj) :: z qvol,ztmp76 REAL(wp), DIMENSION(jpi,jpj) :: zhdiv 76 77 !!---------------------------------------------------------------------- 77 78 ! … … 79 80 ! 80 81 ! compute integrated divergence correction 81 z qvol(:,:) = 0.5_wp * ( pfwf(:,:) + pfwf_b(:,:) ) * r1_rau0 / phtbl(:,:)82 zhdiv(:,:) = 0.5_wp * ( pfwf(:,:) + pfwf_b(:,:) ) * r1_rau0 / phtbl(:,:) 82 83 ! 83 84 ! update divergence at each level affected by ice shelf top boundary layer … … 88 89 ! level fully include in the ice shelf boundary layer 89 90 DO jk = ikt, ikb - 1 90 phdiv(ji,jj,jk) = phdiv(ji,jj,jk) + z qvol(ji,jj)91 phdiv(ji,jj,jk) = phdiv(ji,jj,jk) + zhdiv(ji,jj) 91 92 END DO 92 93 ! level partially include in ice shelf boundary layer 93 phdiv(ji,jj,ikb) = phdiv(ji,jj,ikb) + z qvol(ji,jj) * pfrac(ji,jj)94 phdiv(ji,jj,ikb) = phdiv(ji,jj,ikb) + zhdiv(ji,jj) * pfrac(ji,jj) 94 95 END DO 95 96 END DO … … 101 102 !! *** SUBROUTINE isf_hdiv_cpl *** 102 103 !! 103 !! ** Purpose : 104 !! ** Purpose : update the horizontal divergence with the ice shelf 105 !! coupling conservation increment 104 106 !! 105 !! ** Method : 107 !! ** Method : pqvol is positive (outflow) and expressed as m3/s 108 !! increase the divergence 106 109 !! 107 !! ** Action : 110 !! ** Action : phdivn increased by the ice shelf outflow 111 !! 108 112 !!---------------------------------------------------------------------- 109 113 REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) :: phdiv -
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfload.F90
r11423 r11541 80 80 ! 81 81 ! !- assume water displaced by the ice shelf is at T=-1.9 and S=34.4 (rude) 82 zts_top(:,:,jp_tem) = -1.9_wp ; zts_top(:,:,jp_sal) = 3 4.4_wp82 zts_top(:,:,jp_tem) = -1.9_wp ; zts_top(:,:,jp_sal) = 35.4_wp 83 83 ! 84 84 DO jk = 1, jpk !- compute density of the water displaced by the ice shelf -
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfnxt.F90
r11521 r11541 8 8 9 9 !!------------------------------------------------------------------------- 10 !! dyn_nxt : obtain the next (after) horizontal velocity10 !! isfnxt : aplly correction need for the ice shelf 11 11 !!------------------------------------------------------------------------- 12 12 13 13 USE isf 14 USE phycst 14 15 USE dom_oce 15 16 USE in_out_manager … … 23 24 CONTAINS 24 25 25 SUBROUTINE isf_dynnxt ( pcoef )26 SUBROUTINE isf_dynnxt ( kt, pcoef ) 26 27 !!-------------------------------------------------------------------- 27 28 !! *** ROUTINE isf_dynnxt *** … … 31 32 !!-------------------------------------------------------------------- 32 33 !!-------------------------- OUT ------------------------------------- 33 REAL(wp), INTENT(in ) :: pcoef ! atfp * rdt * r1_rau0 34 INTEGER , INTENT(in ) :: kt 35 ! 36 REAL(wp), INTENT(in ) :: pcoef ! atfp * rdt 34 37 !!-------------------------- IN ------------------------------------- 35 38 !!-------------------------------------------------------------------- 39 INTEGER :: jk ! loop index 36 40 !!-------------------------------------------------------------------- 37 41 ! … … 41 45 ! ice shelf parametrised 42 46 IF ( ln_isfpar_mlt ) CALL isf_dynnxt_mlt(misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par, fwfisf_par, fwfisf_par_b, pcoef) 47 ! 48 IF ( ln_isfcpl .AND. ln_rstart .AND. kt == nit000+1 ) THEN 49 DO jk = 1, jpkm1 50 e3t_b(:,:,jk) = e3t_b(:,:,jk) - pcoef * risfcpl_vol(:,:,jk) * r1_e1e2t(:,:) 51 END DO 52 END IF 43 53 ! 44 54 END SUBROUTINE isf_dynnxt … … 63 73 ! 64 74 ! compute fwf conservation correction 65 zfwfinc(:,:) = pcoef * ( pfwf_b(:,:) - pfwf(:,:) ) / phtbl(:,:) 75 zfwfinc(:,:) = pcoef * ( pfwf_b(:,:) - pfwf(:,:) ) / phtbl(:,:) * r1_rau0 66 76 ! 67 77 ! add the increment in the tbl -
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfpar.F90
r11494 r11541 8 8 !! X.X ! 2006-02 (C. Wang ) Original code bg03 9 9 !! 3.4 ! 2013-03 (P. Mathiot) Merging + parametrization 10 !! 4. 0! 2019-09 (P. Mathiot) Restructuration10 !! 4.1 ! 2019-09 (P. Mathiot) Restructuration 11 11 !!---------------------------------------------------------------------- 12 12 13 13 !!---------------------------------------------------------------------- 14 !! isf _par : compute ice shelf melt using a prametrisation of ice shelf cavities14 !! isfpar : compute ice shelf melt using a prametrisation of ice shelf cavities 15 15 !!---------------------------------------------------------------------- 16 16 USE oce ! ocean dynamics and tracers 17 USE isf 18 USE isf parmlt19 USE isf tbl20 USE isf diags21 USE isf utils17 USE isf ! ice shelf 18 USE isfutils ! 19 USE isfparmlt ! ice shelf parametrisation 20 USE isftbl ! ice shelf depth average 21 USE isfdiags ! ice shelf diagnostics 22 22 USE dom_oce ! ocean space and time domain 23 23 USE phycst ! physical constants … … 45 45 !! *** ROUTINE isf_par *** 46 46 !! 47 !! ** Purpose : 47 !! ** Purpose : compute the heat and fresh water due to ice shelf melting/freezing using a parametrisation 48 48 !! 49 !! ** Method :50 !!51 !! ** Action :52 !!53 49 !!--------------------------------------------------------------------- 54 50 !!-------------------------- OUT -------------------------------------- … … 60 56 REAL(wp), DIMENSION(jpi,jpj) :: zqoce, zqhc, zqlat, zqh 61 57 !!--------------------------------------------------------------------- 62 !63 ! compute misfkb_par, rhisf_tbl64 rhisf_tbl_par(:,:) = rhisf0_tbl_par(:,:)65 CALL isf_tbl_lvl( ht_n, e3t_n, misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par )66 58 ! 67 59 ! compute heat content, latent heat and melt fluxes (2d) … … 94 86 !! *** ROUTINE isf_par_init *** 95 87 !! 96 !! ** Purpose : 88 !! ** Purpose : initialisation of the variable needed for the parametrisation of ice shelf melt 97 89 !! 98 !! ** Method :99 90 !!---------------------------------------------------------------------- 100 91 INTEGER :: ierr … … 125 116 ! 126 117 ! compute ktop 127 CALL isf tbl_ktop(ztblmin, misfkt_par)118 CALL isf_tbl_ktop(ztblmin, misfkt_par) 128 119 ! 129 120 ! initial tbl thickness -
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfparmlt.F90
r11521 r11541 2 2 !!====================================================================== 3 3 !! *** MODULE isfparmlt *** 4 !! Surfacemodule : update surface ocean boundary condition under ice5 !! shelf 4 !! Ice shelf parametrisation module : update surface ocean boundary condition under ice 5 !! shelf using an ice shelf melt parametrisation 6 6 !!====================================================================== 7 7 !! History : 4.0 ! original code … … 9 9 10 10 USE oce ! ocean dynamics and tracers 11 USE isf 12 USE isftbl 11 USE isf ! ice shelf 12 USE isftbl ! ice shelf depth average 13 13 USE dom_oce ! ocean space and time domain 14 14 USE phycst ! physical constants … … 17 17 USE in_out_manager ! I/O manager 18 18 USE iom ! I/O library 19 USE fldread 20 USE lib_fortran 19 USE fldread ! 20 USE lib_fortran ! 21 21 22 22 IMPLICIT NONE … … 143 143 ! 2. ------------Net heat flux and fresh water flux due to the ice shelf 144 144 pqoce(:,:) = rau0 * rcp * rn_gammat0 * risfLeff(:,:) * e1t(:,:) * ( ztavg(:,:) - ztfrz(:,:) ) * r1_e1e2t(:,:) 145 pqfwf(:,:) = - pqoce(:,:) * r1_Lfusisf! derived from the latent heat flux145 pqfwf(:,:) = - pqoce(:,:) / rLfusisf ! derived from the latent heat flux 146 146 pqhc (:,:) = pqfwf(:,:) * ztfrz(:,:) * rcp ! heat content flux 147 147 ! … … 158 158 SUBROUTINE isfpar_mlt_oasis(kt, pqhc , pqoce, pqfwf ) 159 159 !!---------------------------------------------------------------------- 160 !! *** ROUTINE isfpar_ oasis ***160 !! *** ROUTINE isfpar_mlt_oasis *** 161 161 !! 162 162 !! ** Purpose : scale the fwf read from input file by the total amount received by the sbccpl interface … … 173 173 !!-------------------------------------------------------------------- 174 174 INTEGER :: jk ! loop index 175 REAL(wp) :: zfwf_fld, zfwf_oasis 175 REAL(wp) :: zfwf_fld, zfwf_oasis ! total fwf in the forcing fields (pattern) and from the cpl interface (amount) 176 176 REAL(wp), DIMENSION(jpi,jpj) :: ztfrz ! tbl freezing temperature 177 177 REAL(wp), DIMENSION(jpi,jpj) :: zfwf ! 2d fwf map after scaling … … 182 182 CALL fld_read ( kt, nn_fsbc, sf_isfpar_fwf ) 183 183 ! 184 ! compute ptfrz 185 ! 1. ------------Mean freezing point 184 ! 1. ------------Mean freezing point (needed for heat content flux) 186 185 DO jk = 1,jpk 187 186 CALL eos_fzp(tsn(:,:,jk,jp_sal), ztfrz3d(:,:,jk), gdept_n(:,:,jk)) … … 189 188 CALL isf_tbl(ztfrz3d, ztfrz, 'T', misfkt_par, rhisf_tbl_par, misfkb_par, rfrac_tbl_par ) 190 189 ! 190 ! 2. ------------Scale isf melt pattern with total amount from oasis 191 191 ! ice shelf 2d map 192 192 zfwf(:,:) = - sf_isfpar_fwf(1)%fnow(:,:,1) … … 203 203 zfwf(:,:) = zfwf(:,:) * zfwf_oasis / zfwf_fld 204 204 ! 205 ! define fwf and qoce205 ! i3. -----------Define fwf and qoce 206 206 ! ocean heat flux is assume to be equal to the latent heat 207 207 pqfwf(:,:) = zfwf(:,:) ! fwf ( >0 out ) -
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfstp.F90
r11529 r11541 75 75 ! 76 76 ! compute tbl lvl/h 77 rhisf_tbl_cav(:,:) = rn_htbl * mskisf_cav(:,:) 77 78 CALL isf_tbl_lvl(ht_n, e3t_n, misfkt_cav, misfkb_cav, rhisf_tbl_cav, rfrac_tbl_cav) 78 79 ! … … 94 95 ! 95 96 ! compute misfkb, rhisf_tbl, rfrac (deepest level, thickness, fraction of deepest cell affected by tbl) 97 rhisf_tbl_par(:,:) = rhisf0_tbl_par(:,:) 96 98 CALL isf_tbl_lvl(ht_n, e3t_n, misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par) 97 99 ! … … 140 142 CALL isf_alloc() 141 143 ! 144 ! initalisation of fwf and tsc array to 0 142 145 riceload(:,:) = 0.0_wp 143 146 fwfisf_oasis(:,:) = 0.0_wp … … 166 169 IF ( ln_isf ) THEN 167 170 WRITE(numout,*) ' melt inside the cavity ln_isfcav_mlt = ', ln_isfcav_mlt 168 IF ( ln_isfcav 171 IF ( ln_isfcav_mlt) THEN 169 172 WRITE(numout,*) ' melt formulation cn_isfcav_mlt = ', TRIM(cn_isfcav_mlt) 170 173 WRITE(numout,*) ' thickness of the top boundary layer rn_htbl = ', rn_htbl … … 184 187 WRITE(numout,*) '' 185 188 ! 189 WRITE(numout,*) ' Coupling to an ice sheet model ln_isfcpl = ', ln_isfcpl 190 IF ( ln_isfcpl ) THEN 191 WRITE(numout,*) ' conservation activated ln_isfcpl_cons = ', ln_isfcpl_cons 192 WRITE(numout,*) ' number of call of the extrapolation loop = ', nn_drown 193 ENDIF 194 WRITE(numout,*) '' 195 ! 186 196 ELSE 197 187 198 IF ( ln_isfcav ) THEN 188 199 WRITE(numout,*) '' … … 192 203 END IF 193 204 194 WRITE(numout,*) ' Coupling to an ice sheet model ln_isfcpl = ', ln_isfcpl195 IF ( ln_isfcpl ) THEN196 WRITE(numout,*) ' conservation activated ln_isfcpl_cons = ', ln_isfcpl_cons197 WRITE(numout,*) ' number of call of the extrapolation loop = ', nn_drown198 ENDIF199 !200 205 IF (ln_isfcav) WRITE(numout,*) ' Ice shelf load method cn_isfload = ', TRIM(cn_isfload) 201 206 WRITE(numout,*) '' … … 251 256 IF ( ln_isf ) THEN 252 257 ! 253 ! initialisation useful variable 254 r1_Lfusisf = 1._wp / rLfusisf 255 ! 258 !--------------------------------------------------------------------------------------------------------------------- 256 259 ! initialisation melt in the cavity 257 260 IF ( ln_isfcav_mlt ) THEN … … 276 279 ! 277 280 END IF 278 END IF 279 ! 280 !--------------------------------------------------------------------------------------------------------------------- 281 ! initialisation ice sheet coupling 282 ! 283 ll_isfcpl = .FALSE. 284 ll_isfcpl_cons= .FALSE. 285 ! 286 IF( ln_isfcpl ) THEN 287 288 ! prepare writing restart 289 IF( lwxios ) CALL iom_set_rstw_var_active('ssmask') 290 IF( lwxios ) CALL iom_set_rstw_var_active('tmask') 291 !IF( lwxios ) CALL iom_set_rstw_var_active('wmask') 292 !IF( lwxios ) CALL iom_set_rstw_var_active('gdepw_n') 293 IF( lwxios ) CALL iom_set_rstw_var_active('e3t_n') 294 IF( lwxios ) CALL iom_set_rstw_var_active('e3u_n') 295 IF( lwxios ) CALL iom_set_rstw_var_active('e3v_n') 296 297 IF( ln_rstart ) THEN 298 ! 299 ll_isfcpl = .TRUE. 300 ! 301 CALL isf_alloc_cpl() 302 ! 303 ! extrapolation tracer properties 304 CALL isfcpl_tra() 305 ! 306 ! correction of the horizontal divergence and associated temp. and salt content flux 307 CALL isfcpl_vol() 308 ! 309 ! apply the 'conservation' method 310 IF ( ln_isfcpl_cons ) THEN 311 ll_isfcpl_cons = .TRUE. 312 CALL isfcpl_cons() 281 ! 282 !--------------------------------------------------------------------------------------------------------------------- 283 ! initialisation ice sheet coupling 284 IF( ln_isfcpl ) THEN 285 ! 286 ! prepare writing restart 287 IF( lwxios ) CALL iom_set_rstw_var_active('ssmask') 288 IF( lwxios ) CALL iom_set_rstw_var_active('tmask') 289 IF( lwxios ) CALL iom_set_rstw_var_active('e3t_n') 290 IF( lwxios ) CALL iom_set_rstw_var_active('e3u_n') 291 IF( lwxios ) CALL iom_set_rstw_var_active('e3v_n') 292 ! 293 IF( ln_rstart ) THEN 294 ! 295 CALL isf_alloc_cpl() 296 ! 297 ! extrapolation tracer properties 298 CALL isfcpl_tra() 299 ! 300 ! correction of the horizontal divergence and associated temp. and salt content flux 301 CALL isfcpl_vol() 302 ! 303 ! apply the 'conservation' method 304 IF ( ln_isfcpl_cons ) CALL isfcpl_cons() 305 ! 306 ! Need to : - include in the cpl cons the risfcpl_vol/tsc contribution 307 ! - decide how to manage thickness level change in conservation 308 ! 309 tsb (:,:,:,:) = tsn (:,:,:,:) 310 sshb (:,:) = sshn(:,:) 311 ub (:,:,:) = un(:,:,:) 312 vb (:,:,:) = vn(:,:,:) 313 ! 313 314 END IF 314 315 ! 315 ! Need to include in the cpl cons the isfrst_cpl_div contribution 316 ! decide how to manage thickness level change in conservation 317 ! 318 tsb (:,:,:,:) = tsn (:,:,:,:) 319 sshb (:,:) = sshn(:,:) 320 ! 321 END IF 316 END IF 317 ! 322 318 END IF 323 319 -
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isftbl.F90
r11521 r11541 21 21 PRIVATE 22 22 23 PUBLIC isf_tbl, isf_tbl_avg, isf_tbl_lvl, isf tbl_ktop, isftbl_kbot23 PUBLIC isf_tbl, isf_tbl_avg, isf_tbl_lvl, isf_tbl_ktop, isf_tbl_kbot 24 24 25 25 CONTAINS … … 30 30 !! 31 31 !! ** Purpose : compute mean T/S/U/V in the boundary layer at T- point 32 !! 33 !! ** Method : Average properties over a specific thickness 34 !! 35 !! ** Reference : inspired from : Losch, Modeling ice shelf cavities in a z coordinate ocean general circulation model 36 !! https://doi.org/10.1029/2007JC004368 , 2008 32 37 !! 33 38 !!-------------------------------------------------------------------- … … 103 108 SUBROUTINE isf_tbl_avg( ktop, kbot, phtbl, pfrac, pe3, pvarin, pvarout ) 104 109 !!-------------------------------------------------------------------- 105 !! *** ROUTINE isf_tbl_ lvl***110 !! *** ROUTINE isf_tbl_avg *** 106 111 !! 107 112 !! ** Purpose : compute mean property in the boundary layer … … 145 150 !! *** ROUTINE isf_tbl_lvl *** 146 151 !! 147 !! ** Purpose : - compute bottom level fully included inthe top boundary layer152 !! ** Purpose : - compute bottom level off the top boundary layer 148 153 !! - thickness of the top boundary layer 154 !! - fraction of the bottom level affected by the tbl 149 155 !! 150 156 !!--------------------------------------------------------------------- … … 180 186 ! 181 187 ! get ktbl 182 CALL isf tbl_kbot(ktop, phtbl, pe3, kbot)188 CALL isf_tbl_kbot(ktop, phtbl, pe3, kbot) 183 189 ! 184 190 ! get pfrac … … 197 203 END SUBROUTINE isf_tbl_lvl 198 204 ! 199 SUBROUTINE isf tbl_kbot(ktop, phtbl, pe3, kbot)200 !!-------------------------------------------------------------------- 201 !! *** ROUTINE isf_tbl_ lvl***205 SUBROUTINE isf_tbl_kbot(ktop, phtbl, pe3, kbot) 206 !!-------------------------------------------------------------------- 207 !! *** ROUTINE isf_tbl_bot *** 202 208 !! 203 209 !! ** Purpose : compute bottom level of the isf top boundary layer … … 232 238 END DO 233 239 ! 234 END SUBROUTINE isf tbl_kbot235 ! 236 SUBROUTINE isf tbl_ktop(pdep, ktop)237 !!-------------------------------------------------------------------- 238 !! *** ROUTINE isf_tbl_ lvl***240 END SUBROUTINE isf_tbl_kbot 241 ! 242 SUBROUTINE isf_tbl_ktop(pdep, ktop) 243 !!-------------------------------------------------------------------- 244 !! *** ROUTINE isf_tbl_top *** 239 245 !! 240 246 !! ** Purpose : compute top level of the isf top boundary layer in case of an ice shelf parametrisation … … 263 269 END DO 264 270 ! 265 END SUBROUTINE isf tbl_ktop271 END SUBROUTINE isf_tbl_ktop 266 272 267 273 END MODULE isftbl -
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/TRA/traisf.F90
r11529 r11541 48 48 IF( ln_timing ) CALL timing_start('tra_isf') 49 49 ! 50 IF (ln_isf) THEN 51 ! 52 ! cavity case 53 IF ( ln_isfcav_mlt ) CALL tra_isf_mlt(misfkt_cav, misfkb_cav, rhisf_tbl_cav, rfrac_tbl_cav, risf_cav_tsc, risf_cav_tsc_b, tsa) 54 ! 55 ! parametrisation case 56 IF ( ln_isfpar_mlt ) CALL tra_isf_mlt(misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par, risf_par_tsc, risf_par_tsc_b, tsa) 57 ! 58 END IF 50 ! cavity case 51 IF ( ln_isfcav_mlt ) CALL tra_isf_mlt(misfkt_cav, misfkb_cav, rhisf_tbl_cav, rfrac_tbl_cav, risf_cav_tsc, risf_cav_tsc_b, tsa) 52 ! 53 ! parametrisation case 54 IF ( ln_isfpar_mlt ) CALL tra_isf_mlt(misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par, risf_par_tsc, risf_par_tsc_b, tsa) 59 55 ! 60 56 ! ice sheet coupling case 61 IF ( l l_isfcpl ) THEN57 IF ( ln_isfcpl ) THEN 62 58 ! 63 IF ( kt == nit000 ) CALL tra_isf_cpl(risfcpl_tsc, tsa) 59 IF ( kt == nit000 ) CALL tra_isf_cpl(risfcpl_tsc , tsa) 60 IF ( kt == nit000+1) CALL tra_isf_cpl(risfcpl_tsc*0.5_wp, tsa) 64 61 ! 65 62 ! ensure 0 trend due to unconservation of the ice shelf coupling 66 IF ( l l_isfcpl_cons ) CALL tra_isf_cpl(risfcpl_cons_tsc, tsa)63 IF ( ln_isfcpl_cons ) CALL tra_isf_cpl(risfcpl_cons_tsc, tsa) 67 64 ! 68 65 END IF -
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/TRA/tranxt.F90
r11403 r11541 340 340 ! ice shelf 341 341 IF( ll_isf ) THEN 342 ! 342 343 IF ( ln_isfcav_mlt ) THEN 343 344 ! level fully include in the Losch_2008 ice shelf boundary layer … … 372 373 END IF 373 374 END IF 375 ! 376 IF (ln_isfcpl .AND. ln_rstart .AND. kt == nit000+1 ) THEN ! risfcpl_vol_n = 0 and risfcpl_vol_b = risfcpl_vol 377 ztc_f = ztc_f + zfact1 * risfcpl_tsc(ji,jj,jk,jn) * r1_e1e2t(ji,jj) 378 ze3t_f = ze3t_f - zfact1 * risfcpl_vol(ji,jj,jk ) * r1_e1e2t(ji,jj) 379 END IF 380 ! 374 381 END IF 375 382 ! -
NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/step.F90
r11529 r11541 114 114 IF( ln_apr_dyn ) CALL sbc_apr ( kstp ) ! atmospheric pressure (NB: call before bdy_dta which needs ssh_ib) 115 115 IF( ln_bdy ) CALL bdy_dta ( kstp, time_offset=+1 ) ! update dynamic & tracer data at open boundaries 116 IF( ln_isf .OR. ln_isfcpl) CALL isf_stp ( kstp )116 IF( ln_isf ) CALL isf_stp ( kstp ) 117 117 CALL sbc ( kstp ) ! Sea Boundary Condition (including sea-ice) 118 118 … … 242 242 CALL tra_sbc ( kstp ) ! surface boundary condition 243 243 IF( ln_traqsr ) CALL tra_qsr ( kstp ) ! penetrative solar radiation qsr 244 IF( ln_isf .OR. ln_isfcpl) CALL tra_isf ( kstp ) ! ice shelf heat flux244 IF( ln_isf ) CALL tra_isf ( kstp ) ! ice shelf heat flux 245 245 IF( ln_trabbc ) CALL tra_bbc ( kstp ) ! bottom heat flux 246 246 IF( ln_trabbl ) CALL tra_bbl ( kstp ) ! advective (and/or diffusive) bottom boundary layer scheme
Note: See TracChangeset
for help on using the changeset viewer.