Changeset 8426
- Timestamp:
- 2017-08-08T17:53:09+02:00 (7 years ago)
- Location:
- branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3
- Files:
-
- 4 added
- 6 deleted
- 12 edited
Legend:
- Unmodified
- Added
- Removed
-
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/ice.F90
r8424 r8426 177 177 178 178 ! !!** ice-init namelist (namiceini) ** 179 ! -- iceist ate-- !179 ! -- iceist -- ! 180 180 LOGICAL , PUBLIC :: ln_limini ! initialization or not 181 181 LOGICAL , PUBLIC :: ln_limini_file ! Ice initialization state from 2D netcdf file -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceadv.F90
r8424 r8426 29 29 USE lib_fortran ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 30 30 USE timing ! Timing 31 USE icecons ! conservation tests32 31 USE icectl ! control prints 33 32 -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icectl.F90
r8420 r8426 32 32 PRIVATE 33 33 34 PUBLIC ice_cons_hsm 35 PUBLIC ice_cons_final 34 36 PUBLIC ice_ctl 35 37 PUBLIC ice_prt … … 46 48 CONTAINS 47 49 50 SUBROUTINE ice_cons_hsm( icount, cd_routine, zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b ) 51 !!-------------------------------------------------------------------------------------------------------- 52 !! *** ROUTINE ice_cons_hsm *** 53 !! 54 !! ** Purpose : Test the conservation of heat, salt and mass for each ice routine 55 !! + test if ice concentration and volume are > 0 56 !! 57 !! ** Method : This is an online diagnostics which can be activated with ln_limdiachk=true 58 !! It prints in ocean.output if there is a violation of conservation at each time-step 59 !! The thresholds (zv_sill, zs_sill, zh_sill) which determine violations are set to 60 !! a minimum of 1 mm of ice (over the ice area) that is lost/gained spuriously during 100 years. 61 !! For salt and heat thresholds, ice is considered to have a salinity of 10 62 !! and a heat content of 3e5 J/kg (=latent heat of fusion) 63 !!-------------------------------------------------------------------------------------------------------- 64 INTEGER , INTENT(in) :: icount ! determine wether this is the beggining of the routine (0) or the end (1) 65 CHARACTER(len=*), INTENT(in) :: cd_routine ! name of the routine 66 REAL(wp) , INTENT(inout) :: zvi_b, zsmv_b, zei_b, zfs_b, zfw_b, zft_b 67 REAL(wp) :: zvi, zsmv, zei, zfs, zfw, zft 68 REAL(wp) :: zvmin, zamin, zamax 69 REAL(wp) :: zvtrp, zetrp 70 REAL(wp) :: zarea, zv_sill, zs_sill, zh_sill 71 REAL(wp), PARAMETER :: zconv = 1.e-9 ! convert W to GW and kg to Mt 72 73 IF( icount == 0 ) THEN 74 75 ! salt flux 76 zfs_b = glob_sum( ( sfx_bri(:,:) + sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) + & 77 & sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:) + sfx_sub(:,:) + sfx_lam(:,:) & 78 & ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) 79 80 ! water flux 81 zfw_b = glob_sum( -( wfx_bog(:,:) + wfx_bom(:,:) + wfx_sum(:,:) + wfx_sni(:,:) + & 82 & wfx_opw(:,:) + wfx_res(:,:) + wfx_dyn(:,:) + wfx_lam(:,:) + wfx_ice_sub(:,:) + & 83 & wfx_snw_sni(:,:) + wfx_snw_sum(:,:) + wfx_snw_dyn(:,:) + wfx_snw_sub(:,:) + wfx_spr(:,:) & 84 & ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) 85 86 ! heat flux 87 zft_b = glob_sum( ( hfx_sum(:,:) + hfx_bom(:,:) + hfx_bog(:,:) + hfx_dif(:,:) + hfx_opw(:,:) + hfx_snw(:,:) & 88 & - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:) & 89 & ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) 90 91 zvi_b = glob_sum( SUM( v_i * rhoic + v_s * rhosn, dim=3 ) * e1e2t * tmask(:,:,1) * zconv ) 92 93 zsmv_b = glob_sum( SUM( smv_i * rhoic , dim=3 ) * e1e2t * tmask(:,:,1) * zconv ) 94 95 zei_b = glob_sum( ( SUM( SUM( e_i(:,:,1:nlay_i,:), dim=4 ), dim=3 ) + & 96 & SUM( SUM( e_s(:,:,1:nlay_s,:), dim=4 ), dim=3 ) & 97 ) * e1e2t * tmask(:,:,1) * zconv ) 98 99 ELSEIF( icount == 1 ) THEN 100 101 ! salt flux 102 zfs = glob_sum( ( sfx_bri(:,:) + sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) + & 103 & sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:) + sfx_sub(:,:) + sfx_lam(:,:) & 104 & ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) - zfs_b 105 106 ! water flux 107 zfw = glob_sum( -( wfx_bog(:,:) + wfx_bom(:,:) + wfx_sum(:,:) + wfx_sni(:,:) + & 108 & wfx_opw(:,:) + wfx_res(:,:) + wfx_dyn(:,:) + wfx_lam(:,:) + wfx_ice_sub(:,:) + & 109 & wfx_snw_sni(:,:) + wfx_snw_sum(:,:) + wfx_snw_dyn(:,:) + wfx_snw_sub(:,:) + wfx_spr(:,:) & 110 & ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) - zfw_b 111 112 ! heat flux 113 zft = glob_sum( ( hfx_sum(:,:) + hfx_bom(:,:) + hfx_bog(:,:) + hfx_dif(:,:) + hfx_opw(:,:) + hfx_snw(:,:) & 114 & - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:) & 115 & ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) - zft_b 116 117 ! outputs 118 zvi = ( ( glob_sum( SUM( v_i * rhoic + v_s * rhosn, dim=3 ) & 119 & * e1e2t * tmask(:,:,1) * zconv ) - zvi_b ) * r1_rdtice - zfw ) * rday 120 121 zsmv = ( ( glob_sum( SUM( smv_i * rhoic , dim=3 ) & 122 & * e1e2t * tmask(:,:,1) * zconv ) - zsmv_b ) * r1_rdtice + zfs ) * rday 123 124 zei = ( glob_sum( ( SUM( SUM( e_i(:,:,1:nlay_i,:), dim=4 ), dim=3 ) + & 125 & SUM( SUM( e_s(:,:,1:nlay_s,:), dim=4 ), dim=3 ) & 126 & ) * e1e2t * tmask(:,:,1) * zconv ) - zei_b ) * r1_rdtice + zft 127 128 ! zvtrp and zetrp must be close to 0 if the advection scheme is conservative 129 zvtrp = glob_sum( ( diag_trp_vi * rhoic + diag_trp_vs * rhosn ) * e1e2t * tmask(:,:,1) * zconv ) * rday 130 zetrp = glob_sum( ( diag_trp_ei + diag_trp_es ) * e1e2t * tmask(:,:,1) * zconv ) 131 132 zvmin = glob_min( v_i ) 133 zamax = glob_max( SUM( a_i, dim=3 ) ) 134 zamin = glob_min( a_i ) 135 136 ! set threshold values and calculate the ice area (+epsi10 to set a threshold > 0 when there is no ice) 137 zarea = glob_sum( SUM( a_i + epsi10, dim=3 ) * e1e2t * zconv ) ! in 1.e9 m2 138 zv_sill = zarea * 2.5e-5 139 zs_sill = zarea * 25.e-5 140 zh_sill = zarea * 10.e-5 141 142 IF(lwp) THEN 143 IF ( ABS( zvi ) > zv_sill ) WRITE(numout,*) 'violation volume [Mt/day] (',cd_routine,') = ',zvi 144 IF ( ABS( zsmv ) > zs_sill ) WRITE(numout,*) 'violation saline [psu*Mt/day] (',cd_routine,') = ',zsmv 145 IF ( ABS( zei ) > zh_sill ) WRITE(numout,*) 'violation enthalpy [GW] (',cd_routine,') = ',zei 146 IF ( ABS(zvtrp ) > zv_sill .AND. cd_routine == 'iceadv' ) THEN 147 WRITE(numout,*) 'violation vtrp [Mt/day] (',cd_routine,') = ',zvtrp 148 WRITE(numout,*) 'violation etrp [GW] (',cd_routine,') = ',zetrp 149 ENDIF 150 IF ( zvmin < -epsi10 ) WRITE(numout,*) 'violation v_i<0 [m] (',cd_routine,') = ',zvmin 151 IF ( zamax > MAX( rn_amax_n, rn_amax_s ) + epsi10 .AND. & 152 & cd_routine /= 'iceadv' .AND. cd_routine /= 'icerdgrft' ) THEN 153 WRITE(numout,*) 'violation a_i>amax (',cd_routine,') = ',zamax 154 IF ( zamax > 1._wp ) WRITE(numout,*) 'violation a_i>1 (',cd_routine,') = ',zamax 155 ENDIF 156 IF ( zamin < -epsi10 ) WRITE(numout,*) 'violation a_i<0 (',cd_routine,') = ',zamin 157 ENDIF 158 159 ENDIF 160 161 END SUBROUTINE ice_cons_hsm 162 163 164 SUBROUTINE ice_cons_final( cd_routine ) 165 !!--------------------------------------------------------------------------------------------------------- 166 !! *** ROUTINE ice_cons_final *** 167 !! 168 !! ** Purpose : Test the conservation of heat, salt and mass at the end of each ice time-step 169 !! 170 !! ** Method : This is an online diagnostics which can be activated with ln_limdiachk=true 171 !! It prints in ocean.output if there is a violation of conservation at each time-step 172 !! The thresholds (zv_sill, zs_sill, zh_sill) which determine the violation are set to 173 !! a minimum of 1 mm of ice (over the ice area) that is lost/gained spuriously during 100 years. 174 !! For salt and heat thresholds, ice is considered to have a salinity of 10 175 !! and a heat content of 3e5 J/kg (=latent heat of fusion) 176 !!-------------------------------------------------------------------------------------------------------- 177 CHARACTER(len=*), INTENT(in) :: cd_routine ! name of the routine 178 REAL(wp) :: zhfx, zsfx, zvfx 179 REAL(wp) :: zarea, zv_sill, zs_sill, zh_sill 180 REAL(wp), PARAMETER :: zconv = 1.e-9 ! convert W to GW and kg to Mt 181 182 ! heat flux 183 zhfx = glob_sum( ( hfx_in - hfx_out - diag_heat - diag_trp_ei - diag_trp_es & 184 ! & - SUM( qevap_ice * a_i_b, dim=3 ) & !!clem: I think this line must be commented (but need check) 185 & ) * e1e2t * tmask(:,:,1) * zconv ) 186 ! salt flux 187 zsfx = glob_sum( ( sfx + diag_smvi ) * e1e2t * tmask(:,:,1) * zconv ) * rday 188 ! water flux 189 zvfx = glob_sum( ( wfx_ice + wfx_snw + wfx_spr + wfx_sub + diag_vice + diag_vsnw ) * e1e2t * tmask(:,:,1) * zconv ) * rday 190 191 ! set threshold values and calculate the ice area (+epsi10 to set a threshold > 0 when there is no ice) 192 zarea = glob_sum( SUM( a_i + epsi10, dim=3 ) * e1e2t * zconv ) ! in 1.e9 m2 193 zv_sill = zarea * 2.5e-5 194 zs_sill = zarea * 25.e-5 195 zh_sill = zarea * 10.e-5 196 197 IF( ABS( zvfx ) > zv_sill ) WRITE(numout,*) 'violation vfx [Mt/day] (',cd_routine,') = ',(zvfx) 198 IF( ABS( zsfx ) > zs_sill ) WRITE(numout,*) 'violation sfx [psu*Mt/day] (',cd_routine,') = ',(zsfx) 199 IF( ABS( zhfx ) > zh_sill ) WRITE(numout,*) 'violation hfx [GW] (',cd_routine,') = ',(zhfx) 200 201 END SUBROUTINE ice_cons_final 202 203 48 204 SUBROUTINE ice_ctl( kt ) 49 205 !!----------------------------------------------------------------------- -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceforcing.F90
r8414 r8426 19 19 USE sbcblk ! Surface boundary condition: bulk 20 20 USE sbccpl ! Surface boundary condition: coupled interface 21 USE icealb edo! ice albedo21 USE icealb ! ice albedo 22 22 ! 23 23 USE iom ! I/O manager library … … 64 64 IF( nn_timing == 1 ) CALL timing_start('ice_forcing_tau') 65 65 66 IF( kt == nit000 .AND. lwp ) THEN 67 WRITE(numout,*) 68 WRITE(numout,*)'ice_forcing_tau' 69 WRITE(numout,*)'~~~~~~~~~~~~~~~' 70 ENDIF 71 66 72 SELECT CASE( ksbc ) 67 73 CASE( jp_usr ) ; CALL usrdef_sbc_ice_tau( kt ) ! user defined formulation … … 78 84 END DO 79 85 END DO 80 CALL lbc_lnk( utau_ice, 'U', -1. ) 81 CALL lbc_lnk( vtau_ice, 'V', -1. ) 86 CALL lbc_lnk_multi( utau_ice, 'U', -1., vtau_ice, 'V', -1. ) 82 87 ENDIF 83 88 … … 119 124 IF( nn_timing == 1 ) CALL timing_start('ice_forcing_flx') 120 125 126 IF( kt == nit000 .AND. lwp ) THEN 127 WRITE(numout,*) 128 WRITE(numout,*)'ice_forcing_flx' 129 WRITE(numout,*)'~~~~~~~~~~~~~~~' 130 ENDIF 131 121 132 ! --- cloud-sky and overcast-sky ice albedos --- ! 122 CALL ice_alb edo( t_su, ht_i, ht_s, a_ip_frac, h_ip, ln_pnd_rad, zalb_cs, zalb_os )133 CALL ice_alb( t_su, ht_i, ht_s, a_ip_frac, h_ip, ln_pnd_rad, zalb_cs, zalb_os ) 123 134 124 135 ! albedo depends on cloud fraction because of non-linear spectral effects … … 140 151 CALL blk_ice_flx( t_su, alb_ice ) 141 152 IF( ln_mixcpl ) CALL sbc_cpl_ice_flx( picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su ) 142 IF( nn_limflx /= 2 ) CALL ice_ lim_flx( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_limflx )153 IF( nn_limflx /= 2 ) CALL ice_flx_dist( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_limflx ) 143 154 144 155 CASE ( jp_purecpl ) ! coupled formulation 145 156 CALL sbc_cpl_ice_flx( picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su ) 146 IF( nn_limflx == 2 ) CALL ice_ lim_flx( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_limflx )157 IF( nn_limflx == 2 ) CALL ice_flx_dist( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_limflx ) 147 158 END SELECT 148 159 … … 162 173 163 174 164 SUBROUTINE ice_ lim_flx( ptn_ice, palb_ice, pqns_ice, pqsr_ice, pdqn_ice, pevap_ice, pdevap_ice, k_limflx )165 !!--------------------------------------------------------------------- 166 !! *** ROUTINE ice_ lim_flx***175 SUBROUTINE ice_flx_dist( ptn_ice, palb_ice, pqns_ice, pqsr_ice, pdqn_ice, pevap_ice, pdevap_ice, k_limflx ) 176 !!--------------------------------------------------------------------- 177 !! *** ROUTINE ice_flx_dist *** 167 178 !! 168 179 !! ** Purpose : update the ice surface boundary condition by averaging and / or … … 195 206 !!---------------------------------------------------------------------- 196 207 ! 197 IF( nn_timing == 1 ) CALL timing_start('ice_ lim_flx')208 IF( nn_timing == 1 ) CALL timing_start('ice_flx_dist') 198 209 ! 199 210 SELECT CASE( k_limflx ) !== averaged on all ice categories ==! … … 231 242 END SELECT 232 243 ! 233 IF( nn_timing == 1 ) CALL timing_stop('ice_ lim_flx')234 ! 235 END SUBROUTINE ice_ lim_flx244 IF( nn_timing == 1 ) CALL timing_stop('ice_flx_dist') 245 ! 246 END SUBROUTINE ice_flx_dist 236 247 237 248 -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceitd.F90
r8424 r8426 23 23 USE ice1D ! LIM-3 thermodynamic variables 24 24 USE ice ! LIM-3 variables 25 USE icec ons! conservation tests25 USE icectl ! conservation tests 26 26 USE icetab 27 27 ! -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icerdgrft.F90
r8424 r8426 19 19 USE ice ! LIM variables 20 20 USE icevar ! LIM 21 USE icecons ! conservation tests22 21 USE icectl ! control prints 23 22 ! … … 78 77 79 78 80 SUBROUTINE ice_rdgrft 79 SUBROUTINE ice_rdgrft( kt ) 81 80 !!---------------------------------------------------------------------! 82 81 !! *** ROUTINE ice_rdgrft *** … … 104 103 !! and Elizabeth C. Hunke, LANL are gratefully acknowledged 105 104 !!--------------------------------------------------------------------! 105 INTEGER, INTENT(in) :: kt ! number of iteration 106 !! 106 107 INTEGER :: ji, jj, jk, jl ! dummy loop index 107 108 INTEGER :: niter ! local integer … … 120 121 !!----------------------------------------------------------------------------- 121 122 IF( nn_timing == 1 ) CALL timing_start('icerdgrft') 123 124 IF( kt == nit000 .AND. lwp ) THEN 125 WRITE(numout,*) 126 WRITE(numout,*)'icerdgrft' 127 WRITE(numout,*)'~~~~~~~~~' 128 ENDIF 122 129 123 130 ! conservation test -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icerhg.F90
r8424 r8426 19 19 USE ice ! LIM-3 variables 20 20 USE icerhg_evp ! EVP rheology 21 USE icecons ! conservation tests22 21 USE icectl ! control prints 23 22 USE icevar … … 61 60 62 61 IF( nn_timing == 1 ) CALL timing_start('icerhg') 62 63 IF( kt == nit000 .AND. lwp ) THEN 64 WRITE(numout,*) 65 WRITE(numout,*)'icerhg' 66 WRITE(numout,*)'~~~~~~' 67 ENDIF 63 68 64 69 CALL ice_var_agg(1) ! aggregate ice categories -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icestp.F90
r8424 r8426 11 11 !! 3.3 ! 2010-11 (G. Madec) ice-ocean stress always computed at each ocean time-step 12 12 !! 3.4 ! 2011-01 (A Porter) dynamical allocation 13 !! - ! 2012-10 (C. Rousset) add ice_dia hsb13 !! - ! 2012-10 (C. Rousset) add ice_dia 14 14 !! 3.6 ! 2014-07 (M. Vancoppenolle, G. Madec, O. Marti) revise coupled interface 15 15 !! 4.0 ! 2016-06 (L. Brodeau) new unified bulk routine (based on AeroBulk) … … 37 37 USE icerdgrft ! Ice ridging/rafting 38 38 USE iceupdate ! sea surface boundary condition 39 USE icedia hsb! Ice budget diagnostics39 USE icedia ! Ice budget diagnostics 40 40 USE icewri ! Ice outputs 41 41 USE icerst ! Ice restarts 42 USE iceerr1 ! Ice corrections after dynamics 43 USE iceerr2 ! Ice corrections after thermo 42 USE icecor ! Ice corrections 44 43 USE icevar ! Ice variables switch 45 44 USE icectl ! … … 47 46 USE limmp 48 47 ! END MV MP 2016 49 USE iceist ate! LIM initial state48 USE iceist ! LIM initial state 50 49 USE icethd_sal ! LIM ice thermodynamics: salinity 51 50 ! … … 130 129 CALL eos_fzp( sss_m(:,:) , t_bo(:,:) ) 131 130 t_bo(:,:) = ( t_bo(:,:) + rt0 ) * tmask(:,:,1) + rt0 * ( 1._wp - tmask(:,:,1) ) 132 133 ! Mask sea ice surface temperature (set to rt0 over land)134 DO jl = 1, jpl135 t_su(:,:,jl) = t_su(:,:,jl) * tmask(:,:,1) + rt0 * ( 1._wp - tmask(:,:,1) )136 END DO137 131 ! 138 132 CALL ice_bef ! Store previous ice values … … 156 150 CALL ice_adv( kt ) ! -- advection 157 151 IF( nn_limdyn == 2 .AND. nn_monocat /= 2 ) & ! -- ridging/rafting 158 & CALL ice_rdgrft 159 IF( nn_limdyn == 2 ) CALL ice_ err1( kt )! -- Corrections152 & CALL ice_rdgrft( kt ) 153 IF( nn_limdyn == 2 ) CALL ice_cor( kt , 1 ) ! -- Corrections 160 154 ! 161 155 ENDIF 162 163 156 ! --- 157 164 158 #if defined key_agrif 165 159 IF( .NOT. Agrif_Root() ) CALL agrif_interp_lim3('T') … … 196 190 ! END MV MP 2016 197 191 198 IF( ln_limthd ) CALL ice_ err2( kt )! -- Corrections192 IF( ln_limthd ) CALL ice_cor( kt , 2 ) ! -- Corrections 199 193 ! --- 200 194 # if defined key_agrif … … 213 207 !! IF( .NOT. Agrif_Root() ) CALL Agrif_ParentGrid_To_ChildGrid() 214 208 !!# endif 215 IF( ln_limdiahsb ) CALL ice_dia hsb( kt ) ! -- Diagnostics and outputs209 IF( ln_limdiahsb ) CALL ice_dia( kt ) ! -- Diagnostics and outputs 216 210 ! 217 211 CALL ice_wri( 1 ) ! -- Ice outputs … … 282 276 ! ! Initial sea-ice state 283 277 IF( .NOT. ln_rstart ) THEN ! start from rest: sea-ice deduced from sst 284 CALL ice_ist ate278 CALL ice_ist 285 279 ELSE ! start from a restart file 286 280 CALL ice_rst_read … … 291 285 CALL ice_update_init ! ice surface boundary condition 292 286 ! 293 IF( ln_limdiahsb) CALL ice_dia hsb_init ! initialization for diags287 IF( ln_limdiahsb) CALL ice_dia_init ! initialization for diags 294 288 ! 295 289 fr_i(:,:) = at_i(:,:) ! initialisation of sea-ice fraction -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd.F90
r8424 r8426 36 36 USE icetab ! 1D <==> 2D transformation 37 37 USE icevar ! 38 USE icecons ! conservation tests39 38 USE icectl ! control print 40 39 ! … … 93 92 94 93 IF( kt == nit000 .AND. lwp ) THEN 95 WRITE(numout,*) ''96 WRITE(numout,*)' ice _thd '97 WRITE(numout,*)' ~~~~~~~ ~'94 WRITE(numout,*) 95 WRITE(numout,*)' icethd ' 96 WRITE(numout,*)' ~~~~~~~' 98 97 ENDIF 99 98 -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_lac.F90
r8424 r8426 23 23 USE ice ! LIM variables 24 24 USE icetab ! LIM 2D <==> 1D 25 USE icec ons! LIM conservation25 USE icectl ! LIM conservation 26 26 USE icethd_ent 27 27 USE icevar -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceupdate.F90
r8414 r8426 32 32 USE sbc_oce , ONLY : nn_fsbc, ln_ice_embd, sfx, fr_i, qsr_tot, qns, qsr, fmmflx, emp, taum, utau, vtau 33 33 USE sbccpl ! Surface boundary condition: coupled interface 34 USE icealb edo! albedo parameters34 USE icealb ! albedo parameters 35 35 USE traqsr ! add penetration of solar flux in the calculation of heat budget 36 36 USE domvvl ! Variable volume 37 37 USE icectl ! 38 USE icecons !39 38 USE bdy_oce , ONLY: ln_bdy 40 39 ! … … 44 43 USE lib_mpp ! MPP library 45 44 USE lib_fortran ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 45 USE timing ! Timing 46 46 47 47 IMPLICIT NONE … … 108 108 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zalb_cs, zalb_os ! 3D workspace 109 109 !!--------------------------------------------------------------------- 110 IF( nn_timing == 1 ) CALL timing_start('ice_update_flx') 111 112 IF( kt == nit000 .AND. lwp ) THEN 113 WRITE(numout,*) 114 WRITE(numout,*)'ice_update_flx' 115 WRITE(numout,*)'~~~~~~~~~~~~~~' 116 ENDIF 110 117 111 118 ! --- case we bypass ice thermodynamics --- ! … … 201 208 ! Snow/ice albedo (only if sent to coupler, useless in forced mode) ! 202 209 !------------------------------------------------------------------------! 203 CALL ice_alb edo( t_su, ht_i, ht_s, a_ip_frac, h_ip, ln_pnd_rad, zalb_cs, zalb_os ) ! cloud-sky and overcast-sky ice albedos210 CALL ice_alb( t_su, ht_i, ht_s, a_ip_frac, h_ip, ln_pnd_rad, zalb_cs, zalb_os ) ! cloud-sky and overcast-sky ice albedos 204 211 205 212 alb_ice(:,:,:) = ( 1. - cldf_ice ) * zalb_cs(:,:,:) + cldf_ice * zalb_os(:,:,:) … … 211 218 IF( ln_limctl ) CALL ice_prt( kt, iiceprt, jiceprt, 3, ' - Final state ice_update - ' ) 212 219 IF( ln_ctl ) CALL ice_prt3D( 'iceupdate' ) 220 221 IF( nn_timing == 1 ) CALL timing_stop('ice_update_flx') 213 222 214 223 END SUBROUTINE ice_update_flx … … 247 256 REAL(wp) :: zat_v, zvtau_ice, zv_t, zrhoco ! - - 248 257 !!--------------------------------------------------------------------- 258 259 IF( nn_timing == 1 ) CALL timing_start('ice_update_tau') 260 261 IF( kt == nit000 .AND. lwp ) THEN 262 WRITE(numout,*) 263 WRITE(numout,*)'ice_update_tau' 264 WRITE(numout,*)'~~~~~~~~~~~~~~' 265 ENDIF 266 249 267 zrhoco = rau0 * rn_cio 250 268 ! … … 285 303 CALL lbc_lnk_multi( utau, 'U', -1., vtau, 'V', -1. ) ! lateral boundary condition 286 304 ! 305 IF( nn_timing == 1 ) CALL timing_stop('ice_update_tau') 287 306 ! 288 307 END SUBROUTINE ice_update_tau … … 304 323 IF(lwp) WRITE(numout,*) 305 324 IF(lwp) WRITE(numout,*) 'ice_update_init : LIM-3 sea-ice - surface boundary condition' 306 IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~ '325 IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~~ ' 307 326 308 327 ! ! allocate ice_update array … … 368 387 END SUBROUTINE ice_update_init 369 388 370 #else371 !!----------------------------------------------------------------------372 !! Default option : Dummy module NO LIM 3.0 sea-ice model373 !!----------------------------------------------------------------------374 CONTAINS375 SUBROUTINE ice_update ! Dummy routine376 END SUBROUTINE ice_update377 389 #endif 378 390 -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icevar.F90
r8424 r8426 612 612 !! ice thickness distribution follows a gaussian law 613 613 !! around the concentration of the most likely ice thickness 614 !! (similar as iceist ate.F90)614 !! (similar as iceist.F90) 615 615 !! 616 616 !! ** Method: Iterative procedure
Note: See TracChangeset
for help on using the changeset viewer.