source: LMDZ6/trunk/libf/phylmd/change_srf_frac_mod.f90 @ 5353

Last change on this file since 5353 was 5285, checked in by abarral, 7 weeks ago

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