My Project
 All Classes Files Functions Variables Macros
ocean_slab_mod.F90
Go to the documentation of this file.
1 !
3 !
4 ! This module is used for both surface ocean and sea-ice when using the slab ocean,
5 ! "ocean=slab".
6 !
7  IMPLICIT NONE
8  PRIVATE
10 
11 CONTAINS
12 !
13 !****************************************************************************************
14 !
15  SUBROUTINE ocean_slab_frac(itime, dtime, jour, pctsrf, is_modified)
16 
17  USE dimphy
18  USE limit_read_mod
19  USE surface_data
20  include "indicesol.h"
21 ! INCLUDE "clesphys.h"
22 
23 ! Arguments
24 !****************************************************************************************
25  INTEGER, INTENT(IN) :: itime ! numero du pas de temps courant
26  INTEGER, INTENT(IN) :: jour ! jour a lire dans l'annee
27  REAL , INTENT(IN) :: dtime ! pas de temps de la physique (en s)
28  REAL, DIMENSION(klon,nbsrf), INTENT(INOUT) :: pctsrf ! sub-surface fraction
29  LOGICAL, INTENT(OUT) :: is_modified ! true if pctsrf is modified at this time step
30 
31 ! Local variables
32 !****************************************************************************************
33  CHARACTER (len = 80) :: abort_message
34  CHARACTER (len = 20) :: modname = 'ocean_slab_frac'
35 
36 
37  IF (version_ocean == 'sicOBS') THEN
38  CALL limit_read_frac(itime, dtime, jour, pctsrf, is_modified)
39  ELSE
40  abort_message='Ocean slab model without forced sea-ice fractions has to be rewritten!!!'
41  CALL abort_gcm(modname,abort_message,1)
42 ! Here should sea-ice/ocean fraction either be calculated or returned if saved as a module varaiable
43 ! (in the case the new fractions are calculated in ocean_slab_ice or ocean_slab_noice subroutines).
44  END IF
45 
46  END SUBROUTINE ocean_slab_frac
47 !
48 !****************************************************************************************
49 !
50  SUBROUTINE ocean_slab_noice( &
51  itime, dtime, jour, knon, knindex, &
52  p1lay, cdragh, cdragm, precip_rain, precip_snow, temp_air, spechum, &
53  acoefh, acoefq, bcoefh, bcoefq, &
54  acoefu, acoefv, bcoefu, bcoefv, &
55  ps, u1, v1, tsurf_in, &
56  radsol, snow, agesno, &
57  qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
58  tsurf_new, dflux_s, dflux_l, lmt_bils)
59 
60  USE dimphy
62 
63  include "indicesol.h"
64  include "iniprint.h"
65 
66 ! Input arguments
67 !****************************************************************************************
68  INTEGER, INTENT(IN) :: itime
69  INTEGER, INTENT(IN) :: jour
70  INTEGER, INTENT(IN) :: knon
71  INTEGER, DIMENSION(klon), INTENT(IN) :: knindex
72  REAL, INTENT(IN) :: dtime
73  REAL, DIMENSION(klon), INTENT(IN) :: p1lay
74  REAL, DIMENSION(klon), INTENT(IN) :: cdragh, cdragm
75  REAL, DIMENSION(klon), INTENT(IN) :: precip_rain, precip_snow
76  REAL, DIMENSION(klon), INTENT(IN) :: temp_air, spechum
77  REAL, DIMENSION(klon), INTENT(IN) :: acoefh, acoefq, bcoefh, bcoefq
78  REAL, DIMENSION(klon), INTENT(IN) :: acoefu, acoefv, bcoefu, bcoefv
79  REAL, DIMENSION(klon), INTENT(IN) :: ps
80  REAL, DIMENSION(klon), INTENT(IN) :: u1, v1
81  REAL, DIMENSION(klon), INTENT(IN) :: tsurf_in
82 
83 ! In/Output arguments
84 !****************************************************************************************
85  REAL, DIMENSION(klon), INTENT(INOUT) :: radsol
86  REAL, DIMENSION(klon), INTENT(INOUT) :: snow
87  REAL, DIMENSION(klon), INTENT(INOUT) :: agesno
88 
89 ! Output arguments
90 !****************************************************************************************
91  REAL, DIMENSION(klon), INTENT(OUT) :: qsurf
92  REAL, DIMENSION(klon), INTENT(OUT) :: evap, fluxsens, fluxlat
93  REAL, DIMENSION(klon), INTENT(OUT) :: flux_u1, flux_v1
94  REAL, DIMENSION(klon), INTENT(OUT) :: tsurf_new
95  REAL, DIMENSION(klon), INTENT(OUT) :: dflux_s, dflux_l
96  REAL, DIMENSION(klon), INTENT(OUT) :: lmt_bils
97 
98 ! Local variables
99 !****************************************************************************************
100  INTEGER :: i
101  REAL, DIMENSION(klon) :: cal, beta, dif_grnd
102  REAL, DIMENSION(klon) :: lmt_bils_oce, lmt_foce, diff_sst
103  REAL, DIMENSION(klon) :: u0, v0
104  REAL, DIMENSION(klon) :: u1_lay, v1_lay
105  REAL :: calc_bils_oce, deltat
106  REAL, PARAMETER :: cyang=50.0 * 4.228e+06 ! capacite calorifique volumetrique de l'eau J/(m2 K)
107 
108 !****************************************************************************************
109 ! 1) Flux calculation
110 !
111 !****************************************************************************************
112  cal(:) = 0.
113  beta(:) = 1.
114  dif_grnd(:) = 0.
115  agesno(:) = 0.
116 
117 ! Suppose zero surface speed
118  u0(:)=0.0
119  v0(:)=0.0
120  u1_lay(:) = u1(:) - u0(:)
121  v1_lay(:) = v1(:) - v0(:)
122 
123  CALL calcul_fluxs(knon, is_oce, dtime, &
124  tsurf_in, p1lay, cal, beta, cdragh, ps, &
125  precip_rain, precip_snow, snow, qsurf, &
126  radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
127  acoefh, acoefq, bcoefh, bcoefq, &
128  tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
129 
130 ! - Flux calculation at first modele level for U and V
131  CALL calcul_flux_wind(knon, dtime, &
132  u0, v0, u1, v1, cdragm, &
133  acoefu, acoefv, bcoefu, bcoefv, &
134  p1lay, temp_air, &
135  flux_u1, flux_v1)
136 
137 !****************************************************************************************
138 ! 2) Get global variables lmt_bils and lmt_foce from file limit_slab.nc
139 !
140 !****************************************************************************************
141  CALL limit_slab(itime, dtime, jour, lmt_bils, lmt_foce, diff_sst) ! global pour un processus
142 
143  lmt_bils_oce(:) = 0.
144  WHERE (lmt_foce > 0.)
145  lmt_bils_oce = lmt_bils / lmt_foce ! global
146  END WHERE
147 
148 !****************************************************************************************
149 ! 3) Recalculate new temperature
150 !
151 !****************************************************************************************
152  DO i = 1, knon
153  calc_bils_oce = radsol(i) + fluxsens(i) + fluxlat(i)
154  deltat = (calc_bils_oce - lmt_bils_oce(knindex(i)))*dtime/cyang +diff_sst(knindex(i))
155  tsurf_new(i) = tsurf_in(i) + deltat
156  END DO
157 
158  END SUBROUTINE ocean_slab_noice
159 !
160 !****************************************************************************************
161 !
162 END MODULE ocean_slab_mod