source: lmdz_wrf/WRFV3/lmdz/change_srf_frac_mod.F90 @ 1

Last change on this file since 1 was 1, checked in by lfita, 10 years ago
  • -- --- Opening of the WRF+LMDZ coupling repository --- -- -

WRF: version v3.3
LMDZ: version v1818

More details in:

File size: 6.1 KB
Line 
1!
2! $Header$
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, alb1, alb2, 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
24    USE dimphy
25    USE surface_data, ONLY : type_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 : ocean_slab_frac
30    USE indice_sol_mod
31
32    INCLUDE "iniprint.h"
33    INCLUDE "YOMCST.h"
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) :: alb1   ! albedo first interval in SW spektrum
46    REAL, DIMENSION(klon,nbsrf), INTENT(INOUT) :: alb2   ! albedo second interval in SW spektrum
47    REAL, DIMENSION(klon,nbsrf), INTENT(INOUT) :: tsurf
48    REAL, DIMENSION(klon,nbsrf), INTENT(INOUT) :: ustar
49    REAL, DIMENSION(klon,nbsrf), INTENT(INOUT) :: u10m
50    REAL, DIMENSION(klon,nbsrf), INTENT(INOUT) :: v10m
51    REAL, DIMENSION(klon,klev+1,nbsrf), INTENT(INOUT) :: pbl_tke
52
53! Loccal variables
54!****************************************************************************************
55    INTEGER                        :: i, nsrf
56    LOGICAL                        :: is_modified   ! true if pctsrf is modified at this time step
57    LOGICAL                        :: test_sum=.FALSE.
58    LOGICAL, DIMENSION(klon,nbsrf) :: new_surf
59    REAL, DIMENSION(klon,nbsrf)    :: pctsrf_old    ! fraction from previous time-step
60    REAL                           :: tmpsum
61
62    pctsrf_old(:,:) = pctsrf(:,:)
63!****************************************************************************************
64! 1)
65! For each type of ocean (force, slab, couple) receive new fractions only if it's time 
66! to modify (is_modified=true). Otherwise nothing is done (is_modified=false).   
67!****************************************************************************************
68    SELECT CASE (type_ocean)
69    CASE ('force')
70       ! Read fraction from limit.nc
71! L. Fita, LMD. Ovember 2013. Removing reading from 'limit.nc'
72!!       CALL limit_read_frac(itime, dtime, jour, pctsrf, is_modified)
73       PRINT *,'  L. Fita. LMDZ+WRF: Already loaded, no limit.nc !'
74    CASE ('slab')
75       ! Get fraction from slab module
76       CALL ocean_slab_frac(itime, dtime, jour, pctsrf, is_modified)
77    CASE ('couple')
78       ! Get fraction from the coupler
79       CALL cpl_receive_frac(itime, dtime, pctsrf, is_modified)
80    END SELECT
81
82
83!****************************************************************************************
84! 2)
85! Tests and ajustements on the new fractions :
86! - Put to zero fractions that are too small
87! - Test total fraction sum is one for each grid point
88!
89!****************************************************************************************
90    IF (is_modified) THEN
91 
92! Test and exit if a fraction is negative
93       IF (MINVAL(pctsrf(:,:)) < 0.) THEN
94          WRITE(lunout,*)'Warning! One or several fractions are negative, itime=',itime
95          WRITE(lunout,*)'at point = ',MINLOC(pctsrf(:,:))
96          WRITE(lunout,*)'value = ',MINVAL(pctsrf(:,:))
97          CALL abort_gcm('change_srf_frac','Negative fraction',1)
98       END IF
99
100! Optional test on the incoming fraction
101       IF (test_sum) THEN
102          DO i= 1, klon
103             tmpsum = SUM(pctsrf(i,:))
104             IF (ABS(1. - tmpsum) > 0.05) CALL abort_gcm('change_srf_frac','Total fraction not equal 1.',1)
105          END DO
106       END IF
107
108! Test for too small fractions of the sum land+landice and ocean+sea-ice
109       WHERE ((pctsrf(:,is_ter) + pctsrf(:,is_lic)) < 2*EPSFRA)
110          pctsrf(:,is_ter) = 0.
111          pctsrf(:,is_lic) = 0.
112       END WHERE
113
114       WHERE ((pctsrf(:,is_oce) + pctsrf(:,is_sic)) < 2*EPSFRA)
115          pctsrf(:,is_oce) = 0.
116          pctsrf(:,is_sic) = 0.
117       END WHERE
118
119! Normalize to force total fraction to be equal one
120       DO i= 1, klon
121          tmpsum = SUM(pctsrf(i,:))
122          DO nsrf = 1, nbsrf
123             pctsrf(i,nsrf) = pctsrf(i,nsrf) / tmpsum
124          END DO
125       END DO
126
127! Test for too small fractions at each sub-surface
128       WHERE (pctsrf(:,is_ter) < EPSFRA)
129          pctsrf(:,is_lic) = pctsrf(:,is_ter) + pctsrf(:,is_lic)
130          pctsrf(:,is_ter) = 0.
131       END WHERE
132
133       WHERE (pctsrf(:,is_lic) < EPSFRA)
134          pctsrf(:,is_ter) = pctsrf(:,is_ter) + pctsrf(:,is_lic)
135          pctsrf(:,is_lic) = 0.
136       END WHERE
137
138       WHERE (pctsrf(:,is_oce) < EPSFRA)
139          pctsrf(:,is_sic) = pctsrf(:,is_oce) + pctsrf(:,is_sic)
140          pctsrf(:,is_oce) = 0.
141       END WHERE
142
143       WHERE (pctsrf(:,is_sic) < EPSFRA)
144          pctsrf(:,is_oce) = pctsrf(:,is_oce) + pctsrf(:,is_sic)
145          pctsrf(:,is_sic) = 0.
146       END WHERE
147
148!****************************************************************************************
149! 3)
150! Initialize variables where a new fraction has appered,
151! i.e. where new sea ice has been formed
152! or where ice free ocean has appread in a grid cell
153!
154!****************************************************************************************
155       CALL pbl_surface_newfrac(itime, pctsrf, pctsrf_old, tsurf, alb1, alb2, ustar, u10m, v10m, pbl_tke)
156
157    ELSE
158       ! No modifcation should be done
159       pctsrf(:,:) = pctsrf_old(:,:)
160
161    END IF ! is_modified
162
163  END SUBROUTINE change_srf_frac
164
165
166END MODULE change_srf_frac_mod
Note: See TracBrowser for help on using the repository browser.