source: LMDZ6/trunk/libf/phylmdiso/change_srf_frac_mod.F90 @ 5898

Last change on this file since 5898 was 5894, checked in by Sebastien Nguyen, 3 weeks ago

rephase LMDZISO with 5864 version of phylmd + bug fixes in physiq_mod + other bugs in isoverif sections. Code now compiles and runs with -debug -isotopes true -isoverif. There are still isoverif error messages for Dexcess getting greater than 1000 on some points at some moments.

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