source: LMDZ6/branches/Amaury_dev/libf/phylmd/ocean_slab_mod.F90 @ 5159

Last change on this file since 5159 was 5144, checked in by abarral, 8 weeks ago

Put YOMCST.h into modules

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 39.7 KB
Line 
1!Completed
2MODULE ocean_slab_mod
3
4  ! This module is used for both surface ocean and sea-ice when using the slab ocean,
5  ! "ocean=slab".
6
7  USE dimphy
8  USE indice_sol_mod
9  USE surface_data
10  USE lmdz_grid_phy, ONLY: klon_glo
11  USE lmdz_phys_mpi_data, ONLY: is_mpi_root
12  USE lmdz_abort_physic, ONLY: abort_physic
13
14  IMPLICIT NONE; PRIVATE
15  PUBLIC :: ocean_slab_init, ocean_slab_frac, ocean_slab_noice, ocean_slab_ice
16
17  !***********************************************************************************
18  ! Global saved variables
19  !***********************************************************************************
20  ! number of slab vertical layers
21  INTEGER, PUBLIC, SAVE :: nslay
22  !$OMP THREADPRIVATE(nslay)
23  ! timestep for coupling (update slab temperature) in timesteps
24  INTEGER, PRIVATE, SAVE :: cpl_pas
25  !$OMP THREADPRIVATE(cpl_pas)
26  ! cyang = 1/heat capacity of top layer (rho.c.H)
27  REAL, PRIVATE, SAVE :: cyang
28  !$OMP THREADPRIVATE(cyang)
29  ! depth of slab layers (1 or 2)
30  REAL, ALLOCATABLE, DIMENSION(:), PRIVATE, SAVE :: slabh
31  !$OMP THREADPRIVATE(slabh)
32  ! slab temperature
33  REAL, ALLOCATABLE, DIMENSION(:, :), PUBLIC, SAVE :: tslab
34  !$OMP THREADPRIVATE(tslab)
35  ! heat flux convergence due to Ekman
36  REAL, ALLOCATABLE, DIMENSION(:, :), PUBLIC, SAVE :: dt_ekman
37  !$OMP THREADPRIVATE(dt_ekman)
38  ! heat flux convergence due to horiz diffusion
39  REAL, ALLOCATABLE, DIMENSION(:, :), PUBLIC, SAVE :: dt_hdiff
40  !$OMP THREADPRIVATE(dt_hdiff)
41  ! heat flux convergence due to GM eddy advection
42  REAL, ALLOCATABLE, DIMENSION(:, :), PUBLIC, SAVE :: dt_gm
43  !$OMP THREADPRIVATE(dt_gm)
44  ! Heat Flux correction
45  REAL, ALLOCATABLE, DIMENSION(:, :), PUBLIC, SAVE :: dt_qflux
46  !$OMP THREADPRIVATE(dt_qflux)
47  ! fraction of ocean covered by sea ice (sic / (oce+sic))
48  REAL, ALLOCATABLE, DIMENSION(:), PUBLIC, SAVE :: fsic
49  !$OMP THREADPRIVATE(fsic)
50  ! temperature of the sea ice
51  REAL, ALLOCATABLE, DIMENSION(:), PUBLIC, SAVE :: tice
52  !$OMP THREADPRIVATE(tice)
53  ! sea ice thickness, in kg/m2
54  REAL, ALLOCATABLE, DIMENSION(:), PUBLIC, SAVE :: seaice
55  !$OMP THREADPRIVATE(seaice)
56  ! net surface heat flux, weighted by open ocean fraction
57  ! slab_bils accumulated over cpl_pas timesteps
58  REAL, ALLOCATABLE, DIMENSION(:), PRIVATE, SAVE :: bils_cum
59  !$OMP THREADPRIVATE(bils_cum)
60  ! net heat flux into the ocean below the ice : conduction + solar radiation
61  REAL, ALLOCATABLE, DIMENSION(:), PUBLIC, SAVE :: slab_bilg
62  !$OMP THREADPRIVATE(slab_bilg)
63  ! slab_bilg over cpl_pas timesteps
64  REAL, ALLOCATABLE, DIMENSION(:), PRIVATE, SAVE :: bilg_cum
65  !$OMP THREADPRIVATE(bilg_cum)
66  ! wind stress saved over cpl_pas timesteps
67  REAL, ALLOCATABLE, DIMENSION(:), PRIVATE, SAVE :: taux_cum
68  !$OMP THREADPRIVATE(taux_cum)
69  REAL, ALLOCATABLE, DIMENSION(:), PRIVATE, SAVE :: tauy_cum
70  !$OMP THREADPRIVATE(tauy_cum)
71
72  !***********************************************************************************
73  ! Parameters (could be read in def file: move to slab_init)
74  !***********************************************************************************
75  ! snow and ice physical characteristics:
76  REAL, PARAMETER :: t_freeze = 271.35 ! freezing sea water temp
77  REAL, PARAMETER :: t_melt = 273.15   ! melting ice temp
78  REAL, PARAMETER :: sno_den = 300. !mean snow density, kg/m3
79  REAL, PARAMETER :: ice_den = 917. ! ice density
80  REAL, PARAMETER :: sea_den = 1025. ! sea water density
81  REAL, PARAMETER :: ice_cond = 2.17 * ice_den !conductivity of ice
82  REAL, PARAMETER :: sno_cond = 0.31 * sno_den ! conductivity of snow
83  REAL, PARAMETER :: ice_cap = 2067.   ! specific heat capacity, snow and ice
84  REAL, PARAMETER :: sea_cap = 3995.   ! specific heat capacity, snow and ice
85  REAL, PARAMETER :: ice_lat = 334000. ! freeze /melt latent heat snow and ice
86
87  ! control of snow and ice cover & freeze / melt (heights converted to kg/m2)
88  REAL, PARAMETER :: snow_min = 0.05 * sno_den !critical snow height 5 cm
89  REAL, PARAMETER :: snow_wfact = 0.4 ! max fraction of falling snow blown into ocean
90  REAL, PARAMETER :: ice_frac_min = 0.001
91  REAL, PARAMETER :: ice_frac_max = 1. ! less than 1. if min leads fraction
92  REAL, PARAMETER :: h_ice_min = 0.01 * ice_den ! min ice thickness
93  REAL, PARAMETER :: h_ice_thin = 0.15 * ice_den ! thin ice thickness
94  ! below ice_thin, priority is melt lateral / grow height
95  ! ice_thin is also height of new ice
96  REAL, PARAMETER :: h_ice_thick = 2.5 * ice_den ! thin ice thickness
97  ! above ice_thick, priority is melt height / grow lateral
98  REAL, PARAMETER :: h_ice_new = 1. * ice_den ! max height of new open ocean ice
99  REAL, PARAMETER :: h_ice_max = 10. * ice_den ! max ice height
100
101  ! albedo  and radiation parameters
102  REAL, PARAMETER :: alb_sno_min = 0.55 !min snow albedo
103  REAL, PARAMETER :: alb_sno_del = 0.3  !max snow albedo = min + del
104  REAL, PARAMETER :: alb_ice_dry = 0.75 !dry thick ice
105  REAL, PARAMETER :: alb_ice_wet = 0.66 !melting thick ice
106  REAL, PARAMETER :: pen_frac = 0.3 !fraction of shortwave penetrating into the
107  ! ice (no snow)
108  REAL, PARAMETER :: pen_ext = 1.5 !extinction of penetrating shortwave (m-1)
109
110  ! horizontal transport
111  LOGICAL, PUBLIC, SAVE :: slab_hdiff
112  !$OMP THREADPRIVATE(slab_hdiff)
113  LOGICAL, PUBLIC, SAVE :: slab_gm
114  !$OMP THREADPRIVATE(slab_gm)
115  REAL, PRIVATE, SAVE :: coef_hdiff ! coefficient for horizontal diffusion
116  !$OMP THREADPRIVATE(coef_hdiff)
117  INTEGER, PUBLIC, SAVE :: slab_ekman, slab_cadj ! Ekman, conv adjustment
118  !$OMP THREADPRIVATE(slab_ekman)
119  !$OMP THREADPRIVATE(slab_cadj)
120
121  !***********************************************************************************
122
123CONTAINS
124
125  !***********************************************************************************
126
127  SUBROUTINE ocean_slab_init(dtime, pctsrf_rst)
128    !, seaice_rst etc
129
130    USE lmdz_ioipsl_getin_p, ONLY: getin_p
131    USE lmdz_phys_transfert_para, ONLY: gather
132    USE slab_heat_transp_mod, ONLY: ini_slab_transp
133
134    ! Input variables
135    !***********************************************************************************
136    REAL, INTENT(IN) :: dtime
137    ! Variables read from restart file
138    REAL, DIMENSION(klon, nbsrf), INTENT(IN) :: pctsrf_rst
139    ! surface fractions from start file
140
141    ! Local variables
142    !************************************************************************************
143    INTEGER :: error
144    REAL, DIMENSION(klon_glo) :: zmasq_glo
145    CHARACTER (len = 80) :: abort_message
146    CHARACTER (len = 20) :: modname = 'ocean_slab_intit'
147
148    !***********************************************************************************
149    ! Define some parameters
150    !***********************************************************************************
151    ! Number of slab layers
152    nslay = 2
153    CALL getin_p('slab_layers', nslay)
154    print *, 'number of slab layers : ', nslay
155    ! Layer thickness
156    ALLOCATE(slabh(nslay), stat = error)
157    IF (error /= 0) THEN
158      abort_message = 'Pb allocation slabh'
159      CALL abort_physic(modname, abort_message, 1)
160    ENDIF
161    slabh(1) = 50.
162    CALL getin_p('slab_depth', slabh(1))
163    IF (nslay>1) THEN
164      slabh(2) = 150.
165    END IF
166
167    ! cyang = 1/heat capacity of top layer (rho.c.H)
168    cyang = 1 / (slabh(1) * sea_den * sea_cap)
169
170    ! cpl_pas  coupling period (update of tslab and ice fraction)
171    ! pour un calcul a chaque pas de temps, cpl_pas=1
172    cpl_pas = NINT(86400. / dtime * 1.0) ! une fois par jour
173    CALL getin_p('cpl_pas', cpl_pas)
174    print *, 'cpl_pas', cpl_pas
175
176    ! Horizontal diffusion
177    slab_hdiff = .FALSE.
178    CALL getin_p('slab_hdiff', slab_hdiff)
179    coef_hdiff = 25000.
180    CALL getin_p('coef_hdiff', coef_hdiff)
181    ! Ekman transport
182    slab_ekman = 0
183    CALL getin_p('slab_ekman', slab_ekman)
184    ! GM eddy advection (2-layers only)
185    slab_gm = .FALSE.
186    CALL getin_p('slab_gm', slab_gm)
187    IF (slab_ekman<2) THEN
188      slab_gm = .FALSE.
189    ENDIF
190    ! Convective adjustment
191    IF (nslay==1) THEN
192      slab_cadj = 0
193    ELSE
194      slab_cadj = 1
195    END IF
196    CALL getin_p('slab_cadj', slab_cadj)
197
198    !************************************************************************************
199    ! Allocate surface fraction read from restart file
200    !************************************************************************************
201    ALLOCATE(fsic(klon), stat = error)
202    IF (error /= 0) THEN
203      abort_message = 'Pb allocation tmp_pctsrf_slab'
204      CALL abort_physic(modname, abort_message, 1)
205    ENDIF
206    fsic(:) = 0.
207    !zmasq = continent fraction
208    WHERE (1. - zmasq(:)>EPSFRA)
209      fsic(:) = pctsrf_rst(:, is_sic) / (1. - zmasq(:))
210    END WHERE
211
212    !************************************************************************************
213    ! Allocate saved fields
214    !************************************************************************************
215    ALLOCATE(tslab(klon, nslay), stat = error)
216    IF (error /= 0) CALL abort_physic &
217            (modname, 'pb allocation tslab', 1)
218
219    ALLOCATE(bils_cum(klon), stat = error)
220    IF (error /= 0) THEN
221      abort_message = 'Pb allocation slab_bils_cum'
222      CALL abort_physic(modname, abort_message, 1)
223    ENDIF
224    bils_cum(:) = 0.0
225
226    IF (version_ocean=='sicINT') THEN ! interactive sea ice
227      ALLOCATE(slab_bilg(klon), stat = error)
228      IF (error /= 0) THEN
229        abort_message = 'Pb allocation slab_bilg'
230        CALL abort_physic(modname, abort_message, 1)
231      ENDIF
232      slab_bilg(:) = 0.0
233      ALLOCATE(bilg_cum(klon), stat = error)
234      IF (error /= 0) THEN
235        abort_message = 'Pb allocation slab_bilg_cum'
236        CALL abort_physic(modname, abort_message, 1)
237      ENDIF
238      bilg_cum(:) = 0.0
239      ALLOCATE(tice(klon), stat = error)
240      IF (error /= 0) THEN
241        abort_message = 'Pb allocation slab_tice'
242        CALL abort_physic(modname, abort_message, 1)
243      ENDIF
244      ALLOCATE(seaice(klon), stat = error)
245      IF (error /= 0) THEN
246        abort_message = 'Pb allocation slab_seaice'
247        CALL abort_physic(modname, abort_message, 1)
248      ENDIF
249    END IF
250
251    IF (slab_hdiff) THEN !horizontal diffusion
252      ALLOCATE(dt_hdiff(klon, nslay), stat = error)
253      IF (error /= 0) THEN
254        abort_message = 'Pb allocation dt_hdiff'
255        CALL abort_physic(modname, abort_message, 1)
256      ENDIF
257      dt_hdiff(:, :) = 0.0
258    ENDIF
259
260    ALLOCATE(dt_qflux(klon, nslay), stat = error)
261    IF (error /= 0) THEN
262      abort_message = 'Pb allocation dt_qflux'
263      CALL abort_physic(modname, abort_message, 1)
264    ENDIF
265    dt_qflux(:, :) = 0.0
266
267    IF (slab_gm) THEN !GM advection
268      ALLOCATE(dt_gm(klon, nslay), stat = error)
269      IF (error /= 0) THEN
270        abort_message = 'Pb allocation dt_gm'
271        CALL abort_physic(modname, abort_message, 1)
272      ENDIF
273      dt_gm(:, :) = 0.0
274    ENDIF
275
276    IF (slab_ekman>0) THEN ! ekman transport
277      ALLOCATE(dt_ekman(klon, nslay), stat = error)
278      IF (error /= 0) THEN
279        abort_message = 'Pb allocation dt_ekman'
280        CALL abort_physic(modname, abort_message, 1)
281      ENDIF
282      dt_ekman(:, :) = 0.0
283      ALLOCATE(taux_cum(klon), stat = error)
284      IF (error /= 0) THEN
285        abort_message = 'Pb allocation taux_cum'
286        CALL abort_physic(modname, abort_message, 1)
287      ENDIF
288      taux_cum(:) = 0.0
289      ALLOCATE(tauy_cum(klon), stat = error)
290      IF (error /= 0) THEN
291        abort_message = 'Pb allocation tauy_cum'
292        CALL abort_physic(modname, abort_message, 1)
293      ENDIF
294      tauy_cum(:) = 0.0
295    ENDIF
296
297    ! Initialize transport
298    IF (slab_hdiff.OR.(slab_ekman>0)) THEN
299      CALL gather(zmasq, zmasq_glo)
300      ! Master thread/process only
301      !$OMP MASTER
302      IF (is_mpi_root) THEN
303        CALL ini_slab_transp(zmasq_glo)
304      END IF
305      !$OMP END MASTER
306    END IF
307
308  END SUBROUTINE ocean_slab_init
309
310  !***********************************************************************************
311
312  SUBROUTINE ocean_slab_frac(itime, dtime, jour, pctsrf_chg, is_modified)
313
314    ! this routine sends back the sea ice and ocean fraction to the main physics
315    ! routine. Called only with interactive sea ice
316
317    ! Arguments
318    !************************************************************************************
319    INTEGER, INTENT(IN) :: itime   ! current timestep
320    INTEGER, INTENT(IN) :: jour    !  day in year (not
321    REAL, INTENT(IN) :: dtime   ! physics timestep (s)
322    REAL, DIMENSION(klon, nbsrf), INTENT(INOUT) :: pctsrf_chg  ! sub-surface fraction
323    LOGICAL, INTENT(OUT) :: is_modified ! true if pctsrf is
324    ! modified at this time step
325
326    pctsrf_chg(:, is_oce) = (1. - fsic(:)) * (1. - zmasq(:))
327    pctsrf_chg(:, is_sic) = fsic(:) * (1. - zmasq(:))
328    is_modified = .TRUE.
329
330  END SUBROUTINE ocean_slab_frac
331
332  !************************************************************************************
333
334  SUBROUTINE ocean_slab_noice(&
335          itime, dtime, jour, knon, knindex, &
336          p1lay, cdragh, cdragq, cdragm, precip_rain, precip_snow, temp_air, spechum, &
337          AcoefH, AcoefQ, BcoefH, BcoefQ, &
338          AcoefU, AcoefV, BcoefU, BcoefV, &
339          ps, u1, v1, gustiness, tsurf_in, &
340          radsol, snow, &
341          qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
342          tsurf_new, dflux_s, dflux_l, slab_bils)
343
344    USE calcul_fluxs_mod
345    USE slab_heat_transp_mod, ONLY: divgrad_phy, slab_ekman1, slab_ekman2, slab_gmdiff
346    USE lmdz_phys_para
347    USE lmdz_clesphys
348
349    ! This routine
350    ! (1) computes surface turbulent fluxes over points with some open ocean
351    ! (2) reads additional Q-flux (everywhere)
352    ! (3) computes horizontal transport (diffusion & Ekman)
353    ! (4) updates slab temperature every cpl_pas ; creates new ice if needed.
354
355    ! Note :
356    ! klon total number of points
357    ! knon number of points with open ocean (varies with time)
358    ! knindex gives position of the knon points within klon.
359    ! In general, local saved variables have klon values
360    ! variables exchanged with PBL module have knon.
361
362    ! Input arguments
363    !***********************************************************************************
364    INTEGER, INTENT(IN) :: itime ! current timestep INTEGER,
365    INTEGER, INTENT(IN) :: jour  ! day in year (for Q-Flux)
366    INTEGER, INTENT(IN) :: knon  ! number of points
367    INTEGER, DIMENSION(klon), INTENT(IN) :: knindex
368    REAL, INTENT(IN) :: dtime  ! timestep (s)
369    REAL, DIMENSION(klon), INTENT(IN) :: p1lay
370    REAL, DIMENSION(klon), INTENT(IN) :: cdragh, cdragq, cdragm
371    ! drag coefficients
372    REAL, DIMENSION(klon), INTENT(IN) :: precip_rain, precip_snow
373    REAL, DIMENSION(klon), INTENT(IN) :: temp_air, spechum ! near surface T, q
374    REAL, DIMENSION(klon), INTENT(IN) :: AcoefH, AcoefQ, BcoefH, BcoefQ
375    REAL, DIMENSION(klon), INTENT(IN) :: AcoefU, AcoefV, BcoefU, BcoefV
376    ! exchange coefficients for boundary layer scheme
377    REAL, DIMENSION(klon), INTENT(IN) :: ps  ! surface pressure
378    REAL, DIMENSION(klon), INTENT(IN) :: u1, v1, gustiness ! surface wind
379    REAL, DIMENSION(klon), INTENT(IN) :: tsurf_in ! surface temperature
380    REAL, DIMENSION(klon), INTENT(INOUT) :: radsol ! net surface radiative flux
381
382    ! In/Output arguments
383    !************************************************************************************
384    REAL, DIMENSION(klon), INTENT(INOUT) :: snow ! in kg/m2
385
386    ! Output arguments
387    !************************************************************************************
388    REAL, DIMENSION(klon), INTENT(OUT) :: qsurf
389    REAL, DIMENSION(klon), INTENT(OUT) :: evap, fluxsens, fluxlat
390    REAL, DIMENSION(klon), INTENT(OUT) :: flux_u1, flux_v1
391    REAL, DIMENSION(klon), INTENT(OUT) :: tsurf_new ! new surface tempearture
392    REAL, DIMENSION(klon), INTENT(OUT) :: dflux_s, dflux_l
393    REAL, DIMENSION(klon), INTENT(OUT) :: slab_bils
394
395    ! Local variables
396    !************************************************************************************
397    INTEGER :: i, ki, k
398    REAL :: t_cadj
399    !  for surface heat fluxes
400    REAL, DIMENSION(klon) :: cal, beta, dif_grnd
401    ! for Q-Flux computation: d/dt SST, d/dt ice volume (kg/m2), surf fluxes
402    REAL, DIMENSION(klon) :: diff_sst, diff_siv
403    REAL, DIMENSION(klon, nslay) :: lmt_bils
404    ! for surface wind stress
405    REAL, DIMENSION(klon) :: u0, v0
406    REAL, DIMENSION(klon) :: u1_lay, v1_lay
407    ! for new ice creation
408    REAL :: e_freeze, h_new, dfsic
409    ! horizontal diffusion and Ekman local vars
410    ! dimension = global domain (klon_glo) instead of // subdomains
411    REAL, DIMENSION(klon_glo, nslay) :: dt_hdiff_glo, dt_ekman_glo, dt_gm_glo
412    ! dt_ekman_glo saved for diagnostic, dt_ekman_tmp used for time loop
413    REAL, DIMENSION(klon_glo, nslay) :: dt_hdiff_tmp, dt_ekman_tmp
414    REAL, DIMENSION(klon_glo, nslay) :: tslab_glo
415    REAL, DIMENSION(klon_glo) :: taux_glo, tauy_glo
416
417    !****************************************************************************************
418    ! 1) Surface fluxes calculation
419
420    !****************************************************************************************
421    !cal(:)      = 0. ! infinite thermal inertia
422    !beta(:)     = 1. ! wet surface
423    !dif_grnd(:) = 0. ! no diffusion into ground
424    ! EV: use calbeta
425    CALL calbeta(dtime, is_oce, knon, snow, qsurf, beta, cal, dif_grnd)
426
427
428
429    ! Suppose zero surface speed
430    u0(:) = 0.0
431    v0(:) = 0.0
432    u1_lay(:) = u1(:) - u0(:)
433    v1_lay(:) = v1(:) - v0(:)
434
435    ! Compute latent & sensible fluxes
436    CALL calcul_fluxs(knon, is_oce, dtime, &
437            tsurf_in, p1lay, cal, beta, cdragh, cdragq, ps, &
438            precip_rain, precip_snow, snow, qsurf, &
439            radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, gustiness, &
440            f_qsat_oce, AcoefH, AcoefQ, BcoefH, BcoefQ, &
441            tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
442
443    ! save total cumulated heat fluxes locally
444    ! radiative + turbulent + melt of falling snow
445    slab_bils(:) = 0.
446    DO i = 1, knon
447      ki = knindex(i)
448      slab_bils(ki) = (1. - fsic(ki)) * (fluxlat(i) + fluxsens(i) + radsol(i) &
449              - precip_snow(i) * ice_lat * (1. + snow_wfact * fsic(ki)))
450      bils_cum(ki) = bils_cum(ki) + slab_bils(ki)
451    END DO
452
453    !  Compute surface wind stress
454    CALL calcul_flux_wind(knon, dtime, &
455            u0, v0, u1, v1, gustiness, cdragm, &
456            AcoefU, AcoefV, BcoefU, BcoefV, &
457            p1lay, temp_air, &
458            flux_u1, flux_v1)
459
460    ! save cumulated wind stress
461    IF (slab_ekman>0) THEN
462      DO i = 1, knon
463        ki = knindex(i)
464        taux_cum(ki) = taux_cum(ki) + flux_u1(i) * (1. - fsic(ki)) / cpl_pas
465        tauy_cum(ki) = tauy_cum(ki) + flux_v1(i) * (1. - fsic(ki)) / cpl_pas
466      END DO
467    ENDIF
468
469    !****************************************************************************************
470    ! 2) Q-Flux : get global variables lmt_bils, diff_sst and diff_siv from file limit_slab.nc
471
472    !****************************************************************************************
473    CALL limit_slab(itime, dtime, jour, lmt_bils, diff_sst, diff_siv)
474    ! lmt_bils and diff_sst,siv saved by limit_slab
475    ! qflux = total QFlux correction (in W/m2)
476    dt_qflux(:, 1) = lmt_bils(:, 1) + diff_sst(:) / cyang / 86400. - diff_siv(:) * ice_den * ice_lat / 86400.
477    IF (nslay>1) THEN
478      dt_qflux(:, 2:nslay) = lmt_bils(:, 2:nslay)
479    END IF
480
481    !****************************************************************************************
482    ! 3) Recalculate new temperature (add Surf fluxes, Q-Flux, Ocean transport)
483    !    Bring to freezing temp and make sea ice if necessary
484
485    !***********************************************o*****************************************
486    tsurf_new = tsurf_in
487    IF (MOD(itime, cpl_pas)==0) THEN ! time to update tslab & fraction
488      ! ***********************************
489      !  Horizontal transport
490      ! ***********************************
491      IF (slab_ekman>0) THEN
492        ! copy wind stress to global var
493        CALL gather(taux_cum, taux_glo)
494        CALL gather(tauy_cum, tauy_glo)
495      END IF
496
497      IF (slab_hdiff.OR.(slab_ekman>0)) THEN
498        CALL gather(tslab, tslab_glo)
499        ! Compute horiz transport on one process only
500        IF (is_mpi_root .AND. is_omp_root) THEN ! Only master processus         
501          IF (slab_hdiff) THEN
502            dt_hdiff_glo(:, :) = 0.
503          END IF
504          IF (slab_ekman>0) THEN
505            dt_ekman_glo(:, :) = 0.
506          END IF
507          IF (slab_gm) THEN
508            dt_gm_glo(:, :) = 0.
509          END IF
510          DO i = 1, cpl_pas ! time splitting for numerical stability
511            IF (slab_ekman>0) THEN
512              SELECT CASE (slab_ekman)
513              CASE (1)
514                CALL slab_ekman1(taux_glo, tauy_glo, tslab_glo, dt_ekman_tmp)
515              CASE (2)
516                CALL slab_ekman2(taux_glo, tauy_glo, tslab_glo, dt_ekman_tmp, dt_hdiff_tmp, slab_gm)
517              CASE DEFAULT
518                dt_ekman_tmp(:, :) = 0.
519              END SELECT
520              dt_ekman_glo(:, :) = dt_ekman_glo(:, :) + dt_ekman_tmp(:, :)
521              ! convert dt_ekman from K.s-1.(kg.m-2) to K.s-1   
522              DO k = 1, nslay
523                dt_ekman_tmp(:, k) = dt_ekman_tmp(:, k) / (slabh(k) * sea_den)
524              ENDDO
525              tslab_glo = tslab_glo + dt_ekman_tmp * dtime
526              IF (slab_gm) THEN ! Gent-McWilliams eddy advection
527                dt_gm_glo(:, :) = dt_gm_glo(:, :) + dt_hdiff_tmp(:, :)
528                ! convert dt from K.s-1.(kg.m-2) to K.s-1   
529                DO k = 1, nslay
530                  dt_hdiff_tmp(:, k) = dt_hdiff_tmp(:, k) / (slabh(k) * sea_den)
531                END DO
532                tslab_glo = tslab_glo + dt_hdiff_tmp * dtime
533              END IF
534            ENDIF
535            ! GM included in Ekman_2
536            !            IF (slab_gm) THEN ! Gent-McWilliams eddy advection
537            !              CALL slab_gmdiff(tslab_glo,dt_hdiff_tmp)
538            !              ! convert dt_gm from K.m.s-1 to K.s-1
539            !              DO k=1,nslay
540            !                dt_hdiff_tmp(:,k)=dt_hdiff_tmp(:,k)/slabh(k)
541            !              END DO
542            !              tslab_glo=tslab_glo+dt_hdiff_tmp*dtime
543            !              dt_gm_glo(:,:)=dt_gm_glo(:,:)+ dt_hdiff_tmp(:,:)
544            !            END IF
545            IF (slab_hdiff) THEN ! horizontal diffusion
546              ! laplacian of slab T
547              CALL divgrad_phy(nslay, tslab_glo, dt_hdiff_tmp)
548              ! multiply by diff coef and normalize to 50m slab equivalent
549              dt_hdiff_tmp = dt_hdiff_tmp * coef_hdiff * 50. / SUM(slabh)
550              dt_hdiff_glo(:, :) = dt_hdiff_glo(:, :) + dt_hdiff_tmp(:, :)
551              tslab_glo = tslab_glo + dt_hdiff_tmp * dtime
552            END IF
553          END DO ! time splitting
554          IF (slab_hdiff) THEN
555            !dt_hdiff_glo saved in W/m2
556            DO k = 1, nslay
557              dt_hdiff_glo(:, k) = dt_hdiff_glo(:, k) * slabh(k) * sea_den * sea_cap / cpl_pas
558            END DO
559          END IF
560          IF (slab_gm) THEN
561            !dt_hdiff_glo saved in W/m2
562            dt_gm_glo(:, :) = dt_gm_glo(:, :) * sea_cap / cpl_pas
563          END IF
564          IF (slab_ekman>0) THEN
565            ! dt_ekman_glo saved in W/m2
566            dt_ekman_glo(:, :) = dt_ekman_glo(:, :) * sea_cap / cpl_pas
567          END IF
568        END IF ! master process
569        !$OMP BARRIER
570        ! Send new fields back to all processes
571        CALL Scatter(tslab_glo, tslab)
572        IF (slab_hdiff) THEN
573          CALL Scatter(dt_hdiff_glo, dt_hdiff)
574        END IF
575        IF (slab_gm) THEN
576          CALL Scatter(dt_gm_glo, dt_gm)
577        END IF
578        IF (slab_ekman>0) THEN
579          CALL Scatter(dt_ekman_glo, dt_ekman)
580          ! clear wind stress
581          taux_cum(:) = 0.
582          tauy_cum(:) = 0.
583        END IF
584      ENDIF ! transport
585
586      ! ***********************************
587      ! Other heat fluxes
588      ! ***********************************
589      ! Add read QFlux
590      DO k = 1, nslay
591        tslab(:, k) = tslab(:, k) + dt_qflux(:, k) * cyang * dtime * cpl_pas &
592                * slabh(1) / slabh(k)
593      END DO
594      ! Add cumulated surface fluxes
595      tslab(:, 1) = tslab(:, 1) + bils_cum(:) * cyang * dtime
596      ! Convective adjustment if 2 layers
597      IF ((nslay>1).AND.(slab_cadj>0)) THEN
598        DO i = 1, klon
599          IF (tslab(i, 2)>tslab(i, 1)) THEN
600            ! mean (mass-weighted) temperature
601            t_cadj = SUM(tslab(i, :) * slabh(:)) / SUM(slabh(:))
602            tslab(i, 1) = t_cadj
603            tslab(i, 2) = t_cadj
604          END IF
605        END DO
606      END IF
607      ! ***********************************
608      ! Update surface temperature and ice
609      ! ***********************************
610      SELECT CASE(version_ocean)
611      CASE('sicNO') ! no sea ice even below freezing !
612        DO i = 1, knon
613          ki = knindex(i)
614          tsurf_new(i) = tslab(ki, 1)
615        END DO
616      CASE('sicOBS') ! "realistic" case, for prescribed sea ice
617        ! tslab cannot be below freezing, or above it if there is sea ice
618        DO i = 1, knon
619          ki = knindex(i)
620          IF ((tslab(ki, 1)<t_freeze).OR.(fsic(ki)>epsfra)) THEN
621            tslab(ki, 1) = t_freeze
622          END IF
623          tsurf_new(i) = tslab(ki, 1)
624        END DO
625      CASE('sicINT') ! interactive sea ice
626        DO i = 1, knon
627          ki = knindex(i)
628          IF (fsic(ki)<epsfra) THEN ! Free of ice
629            IF (tslab(ki, 1)<t_freeze) THEN ! create new ice
630              ! quantity of new ice formed
631              e_freeze = (t_freeze - tslab(ki, 1)) / cyang / ice_lat
632              ! new ice
633              tice(ki) = t_freeze
634              fsic(ki) = MIN(ice_frac_max, e_freeze / h_ice_thin)
635              IF (fsic(ki)>ice_frac_min) THEN
636                seaice(ki) = MIN(e_freeze / fsic(ki), h_ice_max)
637                tslab(ki, 1) = t_freeze
638              ELSE
639                fsic(ki) = 0.
640              END IF
641              tsurf_new(i) = t_freeze
642            ELSE
643              tsurf_new(i) = tslab(ki, 1)
644            END IF
645          ELSE ! ice present
646            tsurf_new(i) = t_freeze
647            IF (tslab(ki, 1)<t_freeze) THEN ! create new ice
648              ! quantity of new ice formed over open ocean
649              e_freeze = (t_freeze - tslab(ki, 1)) / cyang * (1. - fsic(ki)) &
650                      / (ice_lat + ice_cap / 2. * (t_freeze - tice(ki)))
651              ! new ice height and fraction
652              h_new = MIN(h_ice_new, seaice(ki)) ! max new height ice_new
653              dfsic = MIN(ice_frac_max - fsic(ki), e_freeze / h_new)
654              h_new = MIN(e_freeze / dfsic, h_ice_max)
655              ! update tslab to freezing over open ocean only
656              tslab(ki, 1) = tslab(ki, 1) * fsic(ki) + t_freeze * (1. - fsic(ki))
657              ! update sea ice
658              seaice(ki) = (h_new * dfsic + seaice(ki) * fsic(ki)) &
659                      / (dfsic + fsic(ki))
660              fsic(ki) = fsic(ki) + dfsic
661              ! update snow?
662            END IF ! tslab below freezing
663          END IF ! sea ice present
664        END DO
665      END SELECT
666      bils_cum(:) = 0.0! clear cumulated fluxes
667    END IF ! coupling time
668  END SUBROUTINE ocean_slab_noice
669
670  !****************************************************************************************
671
672  SUBROUTINE ocean_slab_ice(&
673          itime, dtime, jour, knon, knindex, &
674          tsurf_in, p1lay, cdragh, cdragm, precip_rain, precip_snow, temp_air, spechum, &
675          AcoefH, AcoefQ, BcoefH, BcoefQ, &
676          AcoefU, AcoefV, BcoefU, BcoefV, &
677          ps, u1, v1, gustiness, &
678          radsol, snow, qsurf, qsol, agesno, &
679          alb1_new, alb2_new, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
680          tsurf_new, dflux_s, dflux_l, swnet)
681
682    USE calcul_fluxs_mod
683    USE lmdz_clesphys
684    USE lmdz_yomcst
685
686    IMPLICIT NONE
687
688    ! Input arguments
689    !****************************************************************************************
690    INTEGER, INTENT(IN) :: itime, jour, knon
691    INTEGER, DIMENSION(klon), INTENT(IN) :: knindex
692    REAL, INTENT(IN) :: dtime
693    REAL, DIMENSION(klon), INTENT(IN) :: tsurf_in
694    REAL, DIMENSION(klon), INTENT(IN) :: p1lay
695    REAL, DIMENSION(klon), INTENT(IN) :: cdragh, cdragm
696    REAL, DIMENSION(klon), INTENT(IN) :: precip_rain, precip_snow
697    REAL, DIMENSION(klon), INTENT(IN) :: temp_air, spechum
698    REAL, DIMENSION(klon), INTENT(IN) :: AcoefH, AcoefQ, BcoefH, BcoefQ
699    REAL, DIMENSION(klon), INTENT(IN) :: AcoefU, AcoefV, BcoefU, BcoefV
700    REAL, DIMENSION(klon), INTENT(IN) :: ps
701    REAL, DIMENSION(klon), INTENT(IN) :: u1, v1, gustiness
702    REAL, DIMENSION(klon), INTENT(IN) :: swnet
703
704    ! In/Output arguments
705    !****************************************************************************************
706    REAL, DIMENSION(klon), INTENT(INOUT) :: snow, qsol
707    REAL, DIMENSION(klon), INTENT(INOUT) :: agesno
708    REAL, DIMENSION(klon), INTENT(INOUT) :: radsol
709
710    ! Output arguments
711    !****************************************************************************************
712    REAL, DIMENSION(klon), INTENT(OUT) :: qsurf
713    REAL, DIMENSION(klon), INTENT(OUT) :: alb1_new  ! new albedo in visible SW interval
714    REAL, DIMENSION(klon), INTENT(OUT) :: alb2_new  ! new albedo in near IR interval
715    REAL, DIMENSION(klon), INTENT(OUT) :: evap, fluxsens, fluxlat
716    REAL, DIMENSION(klon), INTENT(OUT) :: flux_u1, flux_v1
717    REAL, DIMENSION(klon), INTENT(OUT) :: tsurf_new
718    REAL, DIMENSION(klon), INTENT(OUT) :: dflux_s, dflux_l
719
720    ! Local variables
721    !****************************************************************************************
722    INTEGER :: i, ki
723    REAL, DIMENSION(klon) :: cal, beta, dif_grnd
724    REAL, DIMENSION(klon) :: u0, v0
725    REAL, DIMENSION(klon) :: u1_lay, v1_lay
726    ! intermediate heat fluxes:
727    REAL :: f_cond, f_swpen
728    ! for snow/ice albedo:
729    REAL :: alb_snow, alb_ice, alb_pond
730    REAL :: frac_snow, frac_ice, frac_pond
731    ! for ice melt / freeze
732    REAL :: e_melt, snow_evap, h_test
733    ! dhsic, dfsic change in ice mass, fraction.
734    REAL :: dhsic, dfsic, frac_mf
735
736    !****************************************************************************************
737    ! 1) Flux calculation
738    !****************************************************************************************
739    ! Suppose zero surface speed
740    u0(:) = 0.0
741    v0(:) = 0.0
742    u1_lay(:) = u1(:) - u0(:)
743    v1_lay(:) = v1(:) - v0(:)
744
745    ! set beta, cal, compute conduction fluxes inside ice/snow
746    slab_bilg(:) = 0.
747    !dif_grnd(:)=0.
748    !beta(:) = 1.
749    ! EV: use calbeta to calculate beta and then recalculate properly cal
750    CALL calbeta(dtime, is_sic, knon, snow, qsol, beta, cal, dif_grnd)
751
752    DO i = 1, knon
753      ki = knindex(i)
754      IF (snow(i)>snow_min) THEN
755        ! snow-layer heat capacity
756        cal(i) = 2. * RCPD / (snow(i) * ice_cap)
757        ! snow conductive flux
758        f_cond = sno_cond * (tice(ki) - tsurf_in(i)) / snow(i)
759        ! all shortwave flux absorbed
760        f_swpen = 0.
761        ! bottom flux (ice conduction)
762        slab_bilg(ki) = ice_cond * (tice(ki) - t_freeze) / seaice(ki)
763        ! update ice temperature
764        tice(ki) = tice(ki) - 2. / ice_cap / (snow(i) + seaice(ki)) &
765                * (slab_bilg(ki) + f_cond) * dtime
766      ELSE ! bare ice
767        ! ice-layer heat capacity
768        cal(i) = 2. * RCPD / (seaice(ki) * ice_cap)
769        ! conductive flux
770        f_cond = ice_cond * (t_freeze - tice(ki)) / seaice(ki)
771        ! penetrative shortwave flux...
772        f_swpen = swnet(i) * pen_frac * exp(-pen_ext * seaice(ki) / ice_den)
773        slab_bilg(ki) = f_swpen - f_cond
774      END IF
775      radsol(i) = radsol(i) + f_cond - f_swpen
776    END DO
777    ! weight fluxes to ocean by sea ice fraction
778    slab_bilg(:) = slab_bilg(:) * fsic(:)
779
780    ! calcul_fluxs (sens, lat etc)
781    CALL calcul_fluxs(knon, is_sic, dtime, &
782            tsurf_in, p1lay, cal, beta, cdragh, cdragh, ps, &
783            precip_rain, precip_snow, snow, qsurf, &
784            radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, gustiness, &
785            f_qsat_oce, AcoefH, AcoefQ, BcoefH, BcoefQ, &
786            tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
787    DO i = 1, knon
788      IF (snow(i)<snow_min) tice(knindex(i)) = tsurf_new(i)
789    END DO
790
791    ! calcul_flux_wind
792    CALL calcul_flux_wind(knon, dtime, &
793            u0, v0, u1, v1, gustiness, cdragm, &
794            AcoefU, AcoefV, BcoefU, BcoefV, &
795            p1lay, temp_air, &
796            flux_u1, flux_v1)
797
798    !****************************************************************************************
799    ! 2) Update snow and ice surface
800    !****************************************************************************************
801    ! snow precip
802    DO i = 1, knon
803      ki = knindex(i)
804      IF (precip_snow(i) > 0.) THEN
805        snow(i) = snow(i) + precip_snow(i) * dtime * (1. - snow_wfact * (1. - fsic(ki)))
806      END IF
807      ! snow and ice sublimation
808      IF (evap(i) > 0.) THEN
809        snow_evap = MIN (snow(i) / dtime, evap(i))
810        snow(i) = snow(i) - snow_evap * dtime
811        snow(i) = MAX(0.0, snow(i))
812        seaice(ki) = MAX(0.0, seaice(ki) - (evap(i) - snow_evap) * dtime)
813      ENDIF
814      ! Melt / Freeze snow from above if Tsurf>0
815      IF (tsurf_new(i)>t_melt) THEN
816        ! energy available for melting snow (in kg of melted snow /m2)
817        e_melt = MIN(MAX(snow(i) * (tsurf_new(i) - t_melt) * ice_cap / 2. &
818                / (ice_lat + ice_cap / 2. * (t_melt - tice(ki))), 0.0), snow(i))
819        ! remove snow
820        IF (snow(i)>e_melt) THEN
821          snow(i) = snow(i) - e_melt
822          tsurf_new(i) = t_melt
823        ELSE ! all snow is melted
824          ! add remaining heat flux to ice
825          e_melt = e_melt - snow(i)
826          tice(ki) = tice(ki) + e_melt * ice_lat * 2. / (ice_cap * seaice(ki))
827          tsurf_new(i) = tice(ki)
828        END IF
829      END IF
830      ! melt ice from above if Tice>0
831      IF (tice(ki)>t_melt) THEN
832        ! quantity of ice melted (kg/m2)
833        e_melt = MAX(seaice(ki) * (tice(ki) - t_melt) * ice_cap / 2. &
834                / (ice_lat + ice_cap / 2. * (t_melt - t_freeze)), 0.0)
835        ! melt from above, height only
836        dhsic = MIN(seaice(ki) - h_ice_min, e_melt)
837        e_melt = e_melt - dhsic
838        IF (e_melt>0) THEN
839          ! lateral melt if ice too thin
840          dfsic = MAX(fsic(ki) - ice_frac_min, e_melt / h_ice_min * fsic(ki))
841          ! if all melted add remaining heat to ocean
842          e_melt = MAX(0., e_melt * fsic(ki) - dfsic * h_ice_min)
843          slab_bilg(ki) = slab_bilg(ki) + e_melt * ice_lat / dtime
844          ! update height and fraction
845          fsic(ki) = fsic(ki) - dfsic
846        END IF
847        seaice(ki) = seaice(ki) - dhsic
848        ! surface temperature at melting point
849        tice(ki) = t_melt
850        tsurf_new(i) = t_melt
851      END IF
852      ! convert snow to ice if below floating line
853      h_test = (seaice(ki) + snow(i)) * ice_den - seaice(ki) * sea_den
854      IF (h_test>0.) THEN !snow under water
855        ! extra snow converted to ice (with added frozen sea water)
856        dhsic = h_test / (sea_den - ice_den + sno_den)
857        seaice(ki) = seaice(ki) + dhsic
858        snow(i) = snow(i) - dhsic * sno_den / ice_den
859        ! available energy (freeze sea water + bring to tice)
860        e_melt = dhsic * (1. - sno_den / ice_den) * (ice_lat + &
861                ice_cap / 2. * (t_freeze - tice(ki)))
862        ! update ice temperature
863        tice(ki) = tice(ki) + 2. * e_melt / ice_cap / (snow(i) + seaice(ki))
864      END IF
865    END DO
866
867    ! New albedo
868    DO i = 1, knon
869      ki = knindex(i)
870      ! snow albedo: update snow age
871      IF (snow(i)>0.0001) THEN
872        agesno(i) = (agesno(i) + (1. - agesno(i) / 50.) * dtime / 86400.)&
873                * EXP(-1. * MAX(0.0, precip_snow(i)) * dtime / 5.)
874      ELSE
875        agesno(i) = 0.0
876      END IF
877      ! snow albedo
878      alb_snow = alb_sno_min + alb_sno_del * EXP(-agesno(i) / 50.)
879      ! ice albedo (varies with ice tkickness and temp)
880      alb_ice = MAX(0.0, 0.13 * LOG(100. * seaice(ki) / ice_den) + 0.1)
881      IF (tice(ki)>t_freeze - 0.01) THEN
882        alb_ice = MIN(alb_ice, alb_ice_wet)
883      ELSE
884        alb_ice = MIN(alb_ice, alb_ice_dry)
885      END IF
886      ! pond albedo
887      alb_pond = 0.36 - 0.1 * (2.0 + MIN(0.0, MAX(tice(ki) - t_melt, -2.0)))
888      ! pond fraction
889      frac_pond = 0.2 * (2.0 + MIN(0.0, MAX(tice(ki) - t_melt, -2.0)))
890      ! snow fraction
891      frac_snow = MAX(0.0, MIN(1.0 - frac_pond, snow(i) / snow_min))
892      ! ice fraction
893      frac_ice = MAX(0.0, 1. - frac_pond - frac_snow)
894      ! total albedo
895      alb1_new(i) = alb_snow * frac_snow + alb_ice * frac_ice + alb_pond * frac_pond
896    END DO
897    alb2_new(:) = alb1_new(:)
898
899    !****************************************************************************************
900    ! 3) Recalculate new ocean temperature (add fluxes below ice)
901    !    Melt / freeze from below
902    !***********************************************o*****************************************
903    !cumul fluxes
904    bilg_cum(:) = bilg_cum(:) + slab_bilg(:)
905    IF (MOD(itime, cpl_pas)==0) THEN ! time to update tslab & fraction
906      ! Add cumulated surface fluxes
907      tslab(:, 1) = tslab(:, 1) + bilg_cum(:) * cyang * dtime
908      DO i = 1, knon
909        ki = knindex(i)
910        ! split lateral/top melt-freeze
911        frac_mf = MIN(1., MAX(0., (seaice(ki) - h_ice_thin) / (h_ice_thick - h_ice_thin)))
912        IF (tslab(ki, 1)<=t_freeze) THEN
913          ! ****** Form new ice from below *******
914          ! quantity of new ice
915          e_melt = (t_freeze - tslab(ki, 1)) / cyang &
916                  / (ice_lat + ice_cap / 2. * (t_freeze - tice(ki)))
917          ! first increase height to h_thin
918          dhsic = MAX(0., MIN(h_ice_thin - seaice(ki), e_melt / fsic(ki)))
919          seaice(ki) = dhsic + seaice(ki)
920          e_melt = e_melt - fsic(ki) * dhsic
921          IF (e_melt>0.) THEN
922            ! frac_mf fraction used for lateral increase
923            dfsic = MIN(ice_frac_max - fsic(ki), e_melt * frac_mf / seaice(ki))
924            fsic(ki) = fsic(ki) + dfsic
925            e_melt = e_melt - dfsic * seaice(ki)
926            ! rest used to increase height
927            seaice(ki) = MIN(h_ice_max, seaice(ki) + e_melt / fsic(ki))
928          END IF
929          tslab(ki, 1) = t_freeze
930        ELSE ! slab temperature above freezing
931          ! ****** melt ice from below *******
932          ! quantity of melted ice
933          e_melt = (tslab(ki, 1) - t_freeze) / cyang &
934                  / (ice_lat + ice_cap / 2. * (tice(ki) - t_freeze))
935          ! first decrease height to h_thick
936          dhsic = MAX(0., MIN(seaice(ki) - h_ice_thick, e_melt / fsic(ki)))
937          seaice(ki) = seaice(ki) - dhsic
938          e_melt = e_melt - fsic(ki) * dhsic
939          IF (e_melt>0) THEN
940            ! frac_mf fraction used for height decrease
941            dhsic = MAX(0., MIN(seaice(ki) - h_ice_min, e_melt * frac_mf / fsic(ki)))
942            seaice(ki) = seaice(ki) - dhsic
943            e_melt = e_melt - fsic(ki) * dhsic
944            ! rest used to decrease fraction (up to 0!)
945            dfsic = MIN(fsic(ki), e_melt / seaice(ki))
946            ! keep remaining in ocean
947            e_melt = e_melt - dfsic * seaice(ki)
948          END IF
949          tslab(ki, 1) = t_freeze + e_melt * ice_lat * cyang
950          fsic(ki) = fsic(ki) - dfsic
951        END IF
952      END DO
953      bilg_cum(:) = 0.
954    END IF ! coupling time
955
956    !tests ice fraction
957    WHERE (fsic<ice_frac_min)
958      tslab(:, 1) = tslab(:, 1) - fsic * seaice * ice_lat * cyang
959      tice = t_melt
960      fsic = 0.
961      seaice = 0.
962    END WHERE
963
964  END SUBROUTINE ocean_slab_ice
965
966  !****************************************************************************************
967
968  SUBROUTINE ocean_slab_final
969
970    !****************************************************************************************
971    ! Deallocate module variables
972    !****************************************************************************************
973    IF (ALLOCATED(tslab)) DEALLOCATE(tslab)
974    IF (ALLOCATED(fsic)) DEALLOCATE(fsic)
975    IF (ALLOCATED(tice)) DEALLOCATE(tice)
976    IF (ALLOCATED(seaice)) DEALLOCATE(seaice)
977    IF (ALLOCATED(slab_bilg)) DEALLOCATE(slab_bilg)
978    IF (ALLOCATED(bilg_cum)) DEALLOCATE(bilg_cum)
979    IF (ALLOCATED(bils_cum)) DEALLOCATE(bils_cum)
980    IF (ALLOCATED(taux_cum)) DEALLOCATE(taux_cum)
981    IF (ALLOCATED(tauy_cum)) DEALLOCATE(tauy_cum)
982    IF (ALLOCATED(dt_ekman)) DEALLOCATE(dt_ekman)
983    IF (ALLOCATED(dt_hdiff)) DEALLOCATE(dt_hdiff)
984    IF (ALLOCATED(dt_gm)) DEALLOCATE(dt_gm)
985    IF (ALLOCATED(dt_qflux)) DEALLOCATE(dt_qflux)
986
987  END SUBROUTINE ocean_slab_final
988
989END MODULE ocean_slab_mod
Note: See TracBrowser for help on using the repository browser.