source: LMDZ5/trunk/libf/phylmd/ocean_slab_mod.F90 @ 1907

Last change on this file since 1907 was 1907, checked in by lguez, 11 years ago

Added a copyright property to every file of the distribution, except
for the fcm files (which have their own copyright). Use svn propget on
a file to see the copyright. For instance:

$ svn propget copyright libf/phylmd/physiq.F90
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

Also added the files defining the CeCILL version 2 license, in French
and English, at the top of the LMDZ tree.

  • 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:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 6.4 KB
RevLine 
[781]1!
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  IMPLICIT NONE
[996]8  PRIVATE
9  PUBLIC :: ocean_slab_frac, ocean_slab_noice
[781]10
11CONTAINS
12!
13!****************************************************************************************
14!
[996]15  SUBROUTINE ocean_slab_frac(itime, dtime, jour, pctsrf, is_modified)
[781]16
[1067]17    USE dimphy
[996]18    USE limit_read_mod
[1067]19    USE surface_data
[1785]20    USE indice_sol_mod
21
[996]22!    INCLUDE "clesphys.h"
[781]23
[996]24! Arguments
[781]25!****************************************************************************************
[996]26    INTEGER, INTENT(IN)                        :: itime   ! numero du pas de temps courant
27    INTEGER, INTENT(IN)                        :: jour    ! jour a lire dans l'annee
28    REAL   , INTENT(IN)                        :: dtime   ! pas de temps de la physique (en s)
29    REAL, DIMENSION(klon,nbsrf), INTENT(INOUT) :: pctsrf  ! sub-surface fraction
30    LOGICAL, INTENT(OUT)                       :: is_modified ! true if pctsrf is modified at this time step
[781]31
32! Local variables
33!****************************************************************************************
34    CHARACTER (len = 80)   :: abort_message
[996]35    CHARACTER (len = 20)   :: modname = 'ocean_slab_frac'
[781]36
37
[1067]38    IF (version_ocean == 'sicOBS') THEN   
[996]39       CALL limit_read_frac(itime, dtime, jour, pctsrf, is_modified)
40    ELSE
41       abort_message='Ocean slab model without forced sea-ice fractions has to be rewritten!!!'
[781]42       CALL abort_gcm(modname,abort_message,1)
[996]43! Here should sea-ice/ocean fraction either be calculated or returned if saved as a module varaiable
44! (in the case the new fractions are calculated in ocean_slab_ice or ocean_slab_noice subroutines). 
45    END IF
[781]46
[996]47  END SUBROUTINE ocean_slab_frac
[781]48!
49!****************************************************************************************
50!
51  SUBROUTINE ocean_slab_noice( &
[996]52       itime, dtime, jour, knon, knindex, &
[1067]53       p1lay, cdragh, cdragm, precip_rain, precip_snow, temp_air, spechum, &
54       AcoefH, AcoefQ, BcoefH, BcoefQ, &
55       AcoefU, AcoefV, BcoefU, BcoefV, &
56       ps, u1, v1, tsurf_in, &
[888]57       radsol, snow, agesno, &
[1067]58       qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
[996]59       tsurf_new, dflux_s, dflux_l, lmt_bils)
[1067]60   
61    USE dimphy
62    USE calcul_fluxs_mod
[1785]63    USE indice_sol_mod
64
[781]65    INCLUDE "iniprint.h"
66
67! Input arguments
68!****************************************************************************************
[996]69    INTEGER, INTENT(IN)                  :: itime
70    INTEGER, INTENT(IN)                  :: jour
[781]71    INTEGER, INTENT(IN)                  :: knon
72    INTEGER, DIMENSION(klon), INTENT(IN) :: knindex
73    REAL, INTENT(IN)                     :: dtime
74    REAL, DIMENSION(klon), INTENT(IN)    :: p1lay
[1067]75    REAL, DIMENSION(klon), INTENT(IN)    :: cdragh, cdragm
[781]76    REAL, DIMENSION(klon), INTENT(IN)    :: precip_rain, precip_snow
77    REAL, DIMENSION(klon), INTENT(IN)    :: temp_air, spechum
[1067]78    REAL, DIMENSION(klon), INTENT(IN)    :: AcoefH, AcoefQ, BcoefH, BcoefQ
79    REAL, DIMENSION(klon), INTENT(IN)    :: AcoefU, AcoefV, BcoefU, BcoefV
[781]80    REAL, DIMENSION(klon), INTENT(IN)    :: ps
[1067]81    REAL, DIMENSION(klon), INTENT(IN)    :: u1, v1
[996]82    REAL, DIMENSION(klon), INTENT(IN)    :: tsurf_in
[781]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
[1067]94    REAL, DIMENSION(klon), INTENT(OUT)   :: flux_u1, flux_v1
[781]95    REAL, DIMENSION(klon), INTENT(OUT)   :: tsurf_new
96    REAL, DIMENSION(klon), INTENT(OUT)   :: dflux_s, dflux_l     
[996]97    REAL, DIMENSION(klon), INTENT(OUT)   :: lmt_bils
[781]98
99! Local variables
100!****************************************************************************************
[996]101    INTEGER               :: i
102    REAL, DIMENSION(klon) :: cal, beta, dif_grnd
103    REAL, DIMENSION(klon) :: lmt_bils_oce, lmt_foce, diff_sst
[1067]104    REAL, DIMENSION(klon) :: u0, v0
105    REAL, DIMENSION(klon) :: u1_lay, v1_lay
[996]106    REAL                  :: calc_bils_oce, deltat
107    REAL, PARAMETER       :: cyang=50.0 * 4.228e+06 ! capacite calorifique volumetrique de l'eau J/(m2 K)
[781]108
109!****************************************************************************************
[996]110! 1) Flux calculation
111!
112!****************************************************************************************
113    cal(:)      = 0.
114    beta(:)     = 1.
115    dif_grnd(:) = 0.
116    agesno(:)   = 0.
[781]117   
[1067]118! Suppose zero surface speed
119    u0(:)=0.0
120    v0(:)=0.0
121    u1_lay(:) = u1(:) - u0(:)
122    v1_lay(:) = v1(:) - v0(:)
123
[781]124    CALL calcul_fluxs(knon, is_oce, dtime, &
[1067]125         tsurf_in, p1lay, cal, beta, cdragh, ps, &
[781]126         precip_rain, precip_snow, snow, qsurf,  &
127         radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
[1067]128         AcoefH, AcoefQ, BcoefH, BcoefQ, &
[781]129         tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
130
[1067]131! - Flux calculation at first modele level for U and V
132    CALL calcul_flux_wind(knon, dtime, &
133         u0, v0, u1, v1, cdragm, &
134         AcoefU, AcoefV, BcoefU, BcoefV, &
135         p1lay, temp_air, &
136         flux_u1, flux_v1) 
137
[781]138!****************************************************************************************
[996]139! 2) Get global variables lmt_bils and lmt_foce from file limit_slab.nc
[781]140!
141!****************************************************************************************
[996]142    CALL limit_slab(itime, dtime, jour, lmt_bils, lmt_foce, diff_sst)  ! global pour un processus
[781]143
[996]144    lmt_bils_oce(:) = 0.
145    WHERE (lmt_foce > 0.)
146       lmt_bils_oce = lmt_bils / lmt_foce ! global
147    END WHERE
[781]148
149!****************************************************************************************
[996]150! 3) Recalculate new temperature
[781]151!
152!****************************************************************************************
153    DO i = 1, knon
[996]154       calc_bils_oce = radsol(i) + fluxsens(i) + fluxlat(i)
155       deltat        = (calc_bils_oce - lmt_bils_oce(knindex(i)))*dtime/cyang +diff_sst(knindex(i))
156       tsurf_new(i)  = tsurf_in(i) + deltat
157    END DO
[781]158
[996]159  END SUBROUTINE ocean_slab_noice
[781]160!
161!****************************************************************************************
162!
163END MODULE ocean_slab_mod
Note: See TracBrowser for help on using the repository browser.