source: LMDZ6/trunk/libf/dynphy_lonlat/phylmd/init_ssrf_m.F90 @ 4283

Last change on this file since 4283 was 4283, checked in by jghattas, 19 months ago

Added landice_opt=2 : Treat continental land ice fractions in ORCHIDEE => pctsrf(:,is_lic) = 0.0 in LMDZ.

For this option, some more variables are needed from ORCHIDEE. Therfor change in the interface LMDZ-ORCHIDEE in surf_land_orchidee_mod is done. Previous interface is moved to surf_land_orchidee_nolic_mod.f90. To compile with previous interface, cpp key ORCHIDEE_NOLIC is added. Previous interface is compiled with argument orchidee2.1 in makelmdz and makelmdz_fcm.

At the same time, when the interface was changed, the variable yrmu0(coszang) was added in the call to intersurf_initialize_gathered. This is needed in ORCHIDEE to better initialize the model.

Modifications done by Etienne Vignon and Josefine Ghattas

File size: 6.2 KB
Line 
1MODULE init_ssrf_m
2!
3!*******************************************************************************
4
5  USE indice_sol_mod,     ONLY: is_ter, is_oce, is_oce, is_lic, epsfra
6  USE dimphy,             ONLY: klon, zmasq
7  USE phys_state_var_mod, ONLY: pctsrf
8  USE geometry_mod,       ONLY : longitude_deg, latitude_deg
9  USE grid_atob_m,        ONLY: grille_m
10  USE ioipsl,             ONLY: flininfo, flinopen, flinget, flinclo
11  USE ioipsl_getin_p_mod, ONLY: getin_p
12  USE comconst_mod,       ONLY: im, pi
13  USE surface_data,       ONLY: landice_opt
14
15  CHARACTER(LEN=256), PARAMETER :: icefname="landiceref.nc", icevar="landice"
16  PRIVATE
17  PUBLIC :: start_init_subsurf
18  include "iniprint.h"
19  include "dimensions.h"
20  include "paramet.h"
21  include "comgeom2.h"
22
23CONTAINS
24
25!-------------------------------------------------------------------------------
26!
27SUBROUTINE start_init_subsurf(known_mask)
28!
29!-------------------------------------------------------------------------------
30! Purpose: Subsurfaces initialization.
31!-------------------------------------------------------------------------------
32! Comment: Called by etat0phys_netcdf ; also called by limit_netcdf in case
33!          no starting states are required (ok_etat0==.FALSE.).
34!-------------------------------------------------------------------------------
35  IMPLICIT NONE
36!-------------------------------------------------------------------------------
37! Arguments:
38  LOGICAL, INTENT(IN) :: known_mask
39!-------------------------------------------------------------------------------
40! Local variables:
41  INTEGER           :: iml_lic, jml_lic
42  INTEGER           :: fid, llm_tmp, ttm_tmp, itaul(1), ji, j
43  REAL, ALLOCATABLE :: dlon_lic(:), lon_lic(:,:), fraclic (:,:)
44  REAL, ALLOCATABLE :: dlat_lic(:), lat_lic(:,:), flic_tmp(:,:), vtmp(:,:)
45  REAL              :: date, lev(1), dt, deg2rad
46  LOGICAL           :: no_ter_antartique   ! If true, no land points are allowed at Antartic
47!-------------------------------------------------------------------------------
48  deg2rad= pi/180.0
49
50!--- Physical grid points coordinates
51  DO j=2,jjm; latitude_deg((j-2)*iim+2:(j-1)*iim+1)=rlatu(j);    END DO
52  DO j=2,jjm; longitude_deg((j-2)*iim+2:(j-1)*iim+1)=rlonv(1:im); END DO
53  latitude_deg(1) = pi/2.; latitude_deg(klon) = - pi/2.
54  latitude_deg(:)=latitude_deg(:)/deg2rad
55  longitude_deg(1) = 0.0;   longitude_deg(klon) = 0.0;
56  longitude_deg(:)=longitude_deg(:)/deg2rad
57
58! Compute ground geopotential, sub-cells quantities and possibly the mask.
59! Sub-surfaces initialization
60!*******************************************************************************
61  IF (landice_opt .LT. 2) THEN
62     ! Continue with reading landice.nc file
63     WRITE(lunout,*)"Read landice.nc file to attribute is_lic fraction"
64
65     !--- Read and interpolate on model T-grid soil fraction and soil ice fraction.
66     CALL flininfo(icefname, iml_lic, jml_lic, llm_tmp, ttm_tmp, fid)
67     ALLOCATE(lat_lic(iml_lic,jml_lic),lon_lic(iml_lic,jml_lic))
68     ALLOCATE(fraclic(iml_lic,jml_lic))
69     CALL flinopen(icefname, .FALSE., iml_lic, jml_lic, llm_tmp,  &
70          &               lon_lic, lat_lic, lev, ttm_tmp, itaul, date, dt, fid)
71     CALL flinget(fid, icevar, iml_lic, jml_lic, llm_tmp, ttm_tmp, 1,1, fraclic)
72     CALL flinclo(fid)
73     WRITE(lunout,*)'landice dimensions: iml_lic, jml_lic : ',iml_lic,jml_lic
74     
75     ALLOCATE(dlon_lic(iml_lic),dlat_lic(jml_lic))
76     dlon_lic(:)=lon_lic(:,1); IF(MAXVAL(dlon_lic)>pi) dlon_lic=dlon_lic*pi/180.
77     dlat_lic(:)=lat_lic(1,:); IF(MAXVAL(dlat_lic)>pi) dlat_lic=dlat_lic*pi/180.
78     DEALLOCATE(lon_lic,lat_lic); ALLOCATE(flic_tmp(iip1,jjp1))
79     CALL grille_m(dlon_lic,dlat_lic,fraclic,rlonv(1:iim),rlatu,flic_tmp(1:iim,:))
80     flic_tmp(iip1,:)=flic_tmp(1,:)
81     
82     !--- To the physical grid
83     pctsrf(:,:) = 0.
84     CALL gr_dyn_fi(1, iip1, jjp1, klon, flic_tmp, pctsrf(:,is_lic))
85     DEALLOCATE(flic_tmp)
86     
87     !--- Adequation with soil/sea mask
88     WHERE(pctsrf(:,is_lic)<EPSFRA) pctsrf(:,is_lic)=0.
89     WHERE(zmasq(:)<EPSFRA)         pctsrf(:,is_lic)=0.
90     pctsrf(:,is_ter)=zmasq(:)
91     DO ji=1,klon
92        IF(zmasq(ji)>EPSFRA) THEN
93           IF(pctsrf(ji,is_lic)>=zmasq(ji)) THEN
94              pctsrf(ji,is_lic)=zmasq(ji)
95              pctsrf(ji,is_ter)=0.
96           ELSE
97              pctsrf(ji,is_ter)=zmasq(ji)-pctsrf(ji,is_lic)
98              IF(pctsrf(ji,is_ter)<EPSFRA) THEN
99                 pctsrf(ji,is_ter)=0.
100                 pctsrf(ji,is_lic)=zmasq(ji)
101              END IF
102           END IF
103        END IF
104     END DO
105     
106     
107     !--- Option no_ter_antartique removes all land fractions souther than 60S.
108     !--- Land ice is set instead of the land fractions on these latitudes.
109     !--- The ocean and sea-ice fractions are not changed.
110     no_ter_antartique=.FALSE.
111     CALL getin_p('no_ter_antartique',no_ter_antartique)
112     WRITE(lunout,*)"no_ter_antartique=",no_ter_antartique
113     IF (no_ter_antartique) THEN
114        ! Remove all land fractions souther than 60S and set land-ice instead
115        WRITE(lunout,*) "Remove land fractions souther than 60deg south by increasing"
116        WRITE(lunout,*) "the continental ice fractions. No land can now be found at Antartic."
117        DO ji=1, klon
118           IF (latitude_deg(ji)<-60.0) THEN
119              pctsrf(ji,is_lic) = pctsrf(ji,is_lic) + pctsrf(ji,is_ter)
120              pctsrf(ji,is_ter) = 0
121           END IF
122        END DO
123     END IF
124     
125  ELSE
126     ! landice_opt=2 and higher
127     WRITE(lunout,*) 'No landice is attributed is_lic sub-surface because landice_opt=2 or higher.'
128     WRITE(lunout,*) 'This means that the land model will handel land ice as well as all other land areas.'
129     pctsrf(:,is_ter) = zmasq(:)
130     pctsrf(:,is_lic) = 0.0
131  END IF
132
133!--- Sub-surface ocean and sea ice (sea ice set to zero for start).
134  pctsrf(:,is_oce)=(1.-zmasq(:))
135  WHERE(pctsrf(:,is_oce)<EPSFRA) pctsrf(:,is_oce)=0.
136  IF(known_mask) pctsrf(:,is_oce)=1-zmasq(:)
137
138!--- It is checked that the sub-surfaces sum is equal to 1.
139  ji=COUNT((ABS(SUM(pctsrf(:,:),dim=2))-1.0)>EPSFRA)
140  IF(ji/=0) WRITE(lunout,*) 'Sub-cell distribution problem for ',ji,' points'
141
142END SUBROUTINE start_init_subsurf
143!
144!-------------------------------------------------------------------------------
145
146END MODULE init_ssrf_m
147!
148!*******************************************************************************
Note: See TracBrowser for help on using the repository browser.