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

Last change on this file since 5151 was 5144, checked in by abarral, 7 weeks ago

Put YOMCST.h into modules

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