source: LMDZ6/branches/Amaury_dev/libf/phylmd/change_srf_frac_mod.F90 @ 5101

Last change on this file since 5101 was 5101, checked in by abarral, 4 months ago

Handle DEBUG_IO in lmdz_cppkeys_wrapper.F90
Transform some files .F -> .[fF]90
[ne compile pas à cause de writefield_u non défini - en attente de réponse Laurent]

  • 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: 6.8 KB
Line 
1
2! $Id: change_srf_frac_mod.F90 5101 2024-07-23 06:22:55Z abarral $
3
4MODULE change_srf_frac_mod
5
6  IMPLICIT NONE
7
8CONTAINS
9
10! Change Surface Fractions
11! Author J Ghattas 2008
12
13  SUBROUTINE change_srf_frac(itime, dtime, jour, &
14        pctsrf, evap, z0m, z0h, agesno,              &
15        alb_dir, alb_dif, tsurf, ustar, u10m, v10m, pbl_tke)
16
17! This subroutine is called from physiq.F at each timestep.
18! 1- For each type of ocean (force, slab, couple) receive new fractions only if
19!    it's time to modify (is_modified=true). Otherwise nothing is done (is_modified=false).   
20! If received new fraction :
21! 2- Tests and ajustements are done on the fractions
22! 3- Initialize variables where a new fraction(new or melted ice) has appered,
23
24    USE dimphy
25    USE surface_data, ONLY: type_ocean,version_ocean
26    USE limit_read_mod
27    USE pbl_surface_mod, ONLY: pbl_surface_newfrac
28    USE cpl_mod, ONLY: cpl_receive_frac
29    USE ocean_slab_mod, ONLY: fsic, ocean_slab_frac
30    USE indice_sol_mod
31    USE print_control_mod, ONLY: lunout
32   
33    INCLUDE "YOMCST.h"
34!albedo SB >>>
35    include "clesphys.h"
36!albedo SB <<<
37
38
39
40! Input arguments
41!****************************************************************************************
42    INTEGER, INTENT(IN)                     :: itime   ! current time step
43    INTEGER, INTENT(IN)                     :: jour    ! day of the year
44    REAL,    INTENT(IN)                     :: dtime   ! length of time step (s)
45 
46! In-Output arguments
47!****************************************************************************************
48   
49    REAL, DIMENSION(klon,nbsrf), INTENT(INOUT) :: pctsrf ! sub-surface fraction
50    REAL, DIMENSION(klon,nbsrf), INTENT(INOUT) :: evap, agesno ! sub-surface fraction
51    REAL, DIMENSION(klon,nbsrf+1), INTENT(INOUT) :: z0m,z0h ! sub-surface fraction
52!albedo SB >>>
53    REAL, DIMENSION(klon,nsw,nbsrf), INTENT(INOUT) :: alb_dir,alb_dif
54!albedo SB <<<
55
56    REAL, DIMENSION(klon,nbsrf), INTENT(INOUT) :: tsurf
57    REAL, DIMENSION(klon,nbsrf), INTENT(INOUT) :: ustar
58    REAL, DIMENSION(klon,nbsrf), INTENT(INOUT) :: u10m
59    REAL, DIMENSION(klon,nbsrf), INTENT(INOUT) :: v10m
60!jyg<
61!!    REAL, DIMENSION(klon,klev+1,nbsrf), INTENT(INOUT) :: pbl_tke
62    REAL, DIMENSION(klon,klev+1,nbsrf+1), INTENT(INOUT) :: pbl_tke
63!>jyg
64
65! Loccal variables
66!****************************************************************************************
67    INTEGER                        :: i, nsrf
68    LOGICAL                        :: is_modified   ! true if pctsrf is modified at this time step
69    LOGICAL                        :: test_sum=.FALSE.
70    LOGICAL, DIMENSION(klon,nbsrf) :: new_surf
71    REAL, DIMENSION(klon,nbsrf)    :: pctsrf_old    ! fraction from previous time-step
72    REAL                           :: tmpsum
73
74    pctsrf_old(:,:) = pctsrf(:,:)
75!****************************************************************************************
76! 1)
77! For each type of ocean (force, slab, couple) receive new fractions only if it's time 
78! to modify (is_modified=true). Otherwise nothing is done (is_modified=false).   
79!****************************************************************************************
80    SELECT CASE (type_ocean)
81    CASE ('force')
82       ! Read fraction from limit.nc
83       CALL limit_read_frac(itime, dtime, jour, pctsrf, is_modified)
84    CASE ('slab')
85       IF (version_ocean == 'sicOBS'.OR. version_ocean == 'sicNO') THEN
86       ! Read fraction from limit.nc
87           CALL limit_read_frac(itime, dtime, jour, pctsrf, is_modified)
88       ELSE
89       ! Get fraction from slab module
90           CALL ocean_slab_frac(itime, dtime, jour, pctsrf, is_modified)
91       ENDIF
92    CASE ('couple')
93       ! Get fraction from the coupler
94       CALL cpl_receive_frac(itime, dtime, pctsrf, is_modified)
95    END SELECT
96
97
98!****************************************************************************************
99! 2)
100! Tests and ajustements on the new fractions :
101! - Put to zero fractions that are too small
102! - Test total fraction sum is one for each grid point
103
104!****************************************************************************************
105    IF (is_modified) THEN
106 
107! Test and exit if a fraction is negative
108       IF (MINVAL(pctsrf(:,:)) < 0.) THEN
109          WRITE(lunout,*)'Warning! One or several fractions are negative, itime=',itime
110          WRITE(lunout,*)'at point = ',MINLOC(pctsrf(:,:))
111          WRITE(lunout,*)'value = ',MINVAL(pctsrf(:,:))
112          CALL abort_physic('change_srf_frac','Negative fraction',1)
113       END IF
114
115! Optional test on the incoming fraction
116       IF (test_sum) THEN
117          DO i= 1, klon
118             tmpsum = SUM(pctsrf(i,:))
119             IF (ABS(1. - tmpsum) > 0.05) CALL abort_physic('change_srf_frac','Total fraction not equal 1.',1)
120          END DO
121       END IF
122
123! Test for too small fractions of the sum land+landice and ocean+sea-ice
124       WHERE ((pctsrf(:,is_ter) + pctsrf(:,is_lic)) < 2*EPSFRA)
125          pctsrf(:,is_ter) = 0.
126          pctsrf(:,is_lic) = 0.
127       END WHERE
128
129       WHERE ((pctsrf(:,is_oce) + pctsrf(:,is_sic)) < 2*EPSFRA)
130          pctsrf(:,is_oce) = 0.
131          pctsrf(:,is_sic) = 0.
132       END WHERE
133
134! Normalize to force total fraction to be equal one
135       DO i= 1, klon
136          tmpsum = SUM(pctsrf(i,:))
137          DO nsrf = 1, nbsrf
138             pctsrf(i,nsrf) = pctsrf(i,nsrf) / tmpsum
139          END DO
140       END DO
141
142! Test for too small fractions at each sub-surface
143       WHERE (pctsrf(:,is_ter) < EPSFRA)
144          pctsrf(:,is_lic) = pctsrf(:,is_ter) + pctsrf(:,is_lic)
145          pctsrf(:,is_ter) = 0.
146       END WHERE
147
148       WHERE (pctsrf(:,is_lic) < EPSFRA)
149          pctsrf(:,is_ter) = pctsrf(:,is_ter) + pctsrf(:,is_lic)
150          pctsrf(:,is_lic) = 0.
151       END WHERE
152
153       WHERE (pctsrf(:,is_oce) < EPSFRA)
154          pctsrf(:,is_sic) = pctsrf(:,is_oce) + pctsrf(:,is_sic)
155          pctsrf(:,is_oce) = 0.
156       END WHERE
157
158       WHERE (pctsrf(:,is_sic) < EPSFRA)
159          pctsrf(:,is_oce) = pctsrf(:,is_oce) + pctsrf(:,is_sic)
160          pctsrf(:,is_sic) = 0.
161       END WHERE
162! Send fractions back to slab ocean if needed
163       IF (type_ocean == 'slab'.AND. version_ocean/='sicINT') THEN
164           WHERE (1.-zmasq(:)>EPSFRA)
165               fsic(:)=pctsrf(:,is_sic)/(1.-zmasq(:))
166           END WHERE
167       END IF
168
169!****************************************************************************************
170! 3)
171! Initialize variables where a new fraction has appered,
172! i.e. where new sea ice has been formed
173! or where ice free ocean has appread in a grid cell
174
175!****************************************************************************************
176
177       CALL pbl_surface_newfrac(itime, pctsrf, pctsrf_old,        &
178           evap, z0m, z0h, agesno,                                &
179           tsurf, alb_dir,alb_dif, ustar, u10m, v10m, pbl_tke)
180
181    ELSE
182       ! No modifcation should be done
183       pctsrf(:,:) = pctsrf_old(:,:)
184
185    END IF ! is_modified
186
187  END SUBROUTINE change_srf_frac
188
189
190END MODULE change_srf_frac_mod
Note: See TracBrowser for help on using the repository browser.