source: LMDZ4/trunk/libf/phylmd/ocean_slab_mod.F90 @ 996

Last change on this file since 996 was 996, checked in by lsce, 16 years ago
  • Modifications liées au calcul des nouveau sous-fractions
  • Nettoyage de ocean slab : il reste uniquement la version avec glace de mer forcé
  • Nouveaux variables pour distiguer la version et type d'ocean : type_ocean=force/slab/couple, version_ocean=opa8/nemo pour couplé ou version_ocean=sicOBS pour slab

JG

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 5.9 KB
Line 
1!
2! $Header$
3!
4MODULE ocean_slab_mod
5!
6! This module is used for both surface ocean and sea-ice when using the slab ocean,
7! "ocean=slab".
8!
9  USE surface_data
10  USE fonte_neige_mod,  ONLY : fonte_neige
11  USE calcul_fluxs_mod, ONLY : calcul_fluxs
12  USE dimphy
13 
14  IMPLICIT NONE
15  PRIVATE
16  PUBLIC :: ocean_slab_frac, ocean_slab_noice
17
18CONTAINS
19!
20!****************************************************************************************
21!
22  SUBROUTINE ocean_slab_frac(itime, dtime, jour, pctsrf, is_modified)
23
24    USE limit_read_mod
25    INCLUDE "indicesol.h"
26!    INCLUDE "clesphys.h"
27
28! Arguments
29!****************************************************************************************
30    INTEGER, INTENT(IN)                        :: itime   ! numero du pas de temps courant
31    INTEGER, INTENT(IN)                        :: jour    ! jour a lire dans l'annee
32    REAL   , INTENT(IN)                        :: dtime   ! pas de temps de la physique (en s)
33    REAL, DIMENSION(klon,nbsrf), INTENT(INOUT) :: pctsrf  ! sub-surface fraction
34    LOGICAL, INTENT(OUT)                       :: is_modified ! true if pctsrf is modified at this time step
35
36! Local variables
37!****************************************************************************************
38    CHARACTER (len = 80)   :: abort_message
39    CHARACTER (len = 20)   :: modname = 'ocean_slab_frac'
40
41
42    IF (version_ocean=='sicOBS') THEN   
43       CALL limit_read_frac(itime, dtime, jour, pctsrf, is_modified)
44    ELSE
45       abort_message='Ocean slab model without forced sea-ice fractions has to be rewritten!!!'
46       CALL abort_gcm(modname,abort_message,1)
47! Here should sea-ice/ocean fraction either be calculated or returned if saved as a module varaiable
48! (in the case the new fractions are calculated in ocean_slab_ice or ocean_slab_noice subroutines). 
49    END IF
50
51  END SUBROUTINE ocean_slab_frac
52!
53!****************************************************************************************
54!
55  SUBROUTINE ocean_slab_noice( &
56       itime, dtime, jour, knon, knindex, &
57       p1lay, tq_cdrag, precip_rain, precip_snow, temp_air, spechum, &
58       petAcoef, peqAcoef, petBcoef, peqBcoef, &
59       ps, u1_lay, v1_lay, tsurf_in, &
60       radsol, snow, agesno, &
61       qsurf, evap, fluxsens, fluxlat, &
62       tsurf_new, dflux_s, dflux_l, lmt_bils)
63
64    INCLUDE "indicesol.h"
65    INCLUDE "iniprint.h"
66
67! Input arguments
68!****************************************************************************************
69    INTEGER, INTENT(IN)                  :: itime
70    INTEGER, INTENT(IN)                  :: jour
71    INTEGER, INTENT(IN)                  :: knon
72    INTEGER, DIMENSION(klon), INTENT(IN) :: knindex
73    REAL, INTENT(IN)                     :: dtime
74    REAL, DIMENSION(klon), INTENT(IN)    :: p1lay
75    REAL, DIMENSION(klon), INTENT(IN)    :: tq_cdrag
76    REAL, DIMENSION(klon), INTENT(IN)    :: precip_rain, precip_snow
77    REAL, DIMENSION(klon), INTENT(IN)    :: temp_air, spechum
78    REAL, DIMENSION(klon), INTENT(IN)    :: petAcoef, peqAcoef
79    REAL, DIMENSION(klon), INTENT(IN)    :: petBcoef, peqBcoef
80    REAL, DIMENSION(klon), INTENT(IN)    :: ps
81    REAL, DIMENSION(klon), INTENT(IN)    :: u1_lay, v1_lay
82    REAL, DIMENSION(klon), INTENT(IN)    :: tsurf_in
83
84! In/Output arguments
85!****************************************************************************************
86    REAL, DIMENSION(klon), INTENT(INOUT) :: radsol
87    REAL, DIMENSION(klon), INTENT(INOUT) :: snow
88    REAL, DIMENSION(klon), INTENT(INOUT) :: agesno
89   
90! Output arguments
91!****************************************************************************************
92    REAL, DIMENSION(klon), INTENT(OUT)   :: qsurf
93    REAL, DIMENSION(klon), INTENT(OUT)   :: evap, fluxsens, fluxlat
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                  :: calc_bils_oce, deltat
104    REAL, PARAMETER       :: cyang=50.0 * 4.228e+06 ! capacite calorifique volumetrique de l'eau J/(m2 K)
105
106!****************************************************************************************
107! 1) Flux calculation
108!
109!****************************************************************************************
110    cal(:)      = 0.
111    beta(:)     = 1.
112    dif_grnd(:) = 0.
113    agesno(:)   = 0.
114   
115    CALL calcul_fluxs(knon, is_oce, dtime, &
116         tsurf_in, p1lay, cal, beta, tq_cdrag, ps, &
117         precip_rain, precip_snow, snow, qsurf,  &
118         radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
119         petAcoef, peqAcoef, petBcoef, peqBcoef, &
120         tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
121
122!****************************************************************************************
123! 2) Get global variables lmt_bils and lmt_foce from file limit_slab.nc
124!
125!****************************************************************************************
126    CALL limit_slab(itime, dtime, jour, lmt_bils, lmt_foce, diff_sst)  ! global pour un processus
127
128    lmt_bils_oce(:) = 0.
129    WHERE (lmt_foce > 0.)
130       lmt_bils_oce = lmt_bils / lmt_foce ! global
131    END WHERE
132
133!****************************************************************************************
134! 3) Recalculate new temperature
135!
136!****************************************************************************************
137    DO i = 1, knon
138       calc_bils_oce = radsol(i) + fluxsens(i) + fluxlat(i)
139       deltat        = (calc_bils_oce - lmt_bils_oce(knindex(i)))*dtime/cyang +diff_sst(knindex(i))
140       tsurf_new(i)  = tsurf_in(i) + deltat
141    END DO
142
143  END SUBROUTINE ocean_slab_noice
144!
145!****************************************************************************************
146!
147END MODULE ocean_slab_mod
Note: See TracBrowser for help on using the repository browser.