source: LMDZ6/trunk/libf/phylmd/create_etat0_unstruct.F90 @ 3435

Last change on this file since 3435 was 3435, checked in by Laurent Fairhead, 5 years ago

"Historic" :-) commit merging the physics branch used for DYNAMICO with the LMDZ trunk.
The same physics branch can now be used seamlessly with the traditional lon-lat LMDZ
dynamical core and DYNAMICO.
Testing consisted in running a lon-lat LMDZ bucket simulation with the NPv6.1 physics package
with the original trunk sources and the merged sources. Tests were succesful in the sense that
numeric continuity was preserved in the restart files from both simulation. Further tests
included running both versions of the physics codes for one year in a LMDZOR setting in which
the restart files also came out identical.

Caution:

  • as the physics package now manages unstructured grids, grid information needs to be transmitted

to the surface scheme ORCHIDEE. This means that the interface defined in surf_land_orchidee_mod.F90
is only compatible with ORCHIDEE version orchidee2.1 and later versions. If previous versions of
ORCHIDEE need to be used, the CPP key ORCHIDEE_NOUNSTRUCT needs to be set at compilation time.
This is done automatically if makelmdz/makelmdz_fcm are called with the veget orchidee2.0 switch

  • due to a limitation in XIOS, the time at which limit conditions will be read in by DYNAMICO will be

delayed by one physic timestep with respect to the time it is read in by the lon-lat model. This is caused
by the line

IF (MOD(itime-1, lmt_pas) == 0 .OR. (jour_lu /= jour .AND. grid_type /= unstructured)) THEN ! time to read

in limit_read_mod.F90

Work still needed on COSP integration and XML files for DYNAMICO

EM, YM, LF

File size: 5.0 KB
Line 
1MODULE create_etat0_unstruct_mod
2
3
4
5
6
7
8CONTAINS
9
10  SUBROUTINE create_etat0_unstruct
11  USE dimphy
12#ifdef CPP_XIOS
13  USE xios
14  USE infotrac_phy
15  USE fonte_neige_mod
16  USE pbl_surface_mod
17  USE phys_state_var_mod
18  USE indice_sol_mod
19  USE mod_phys_lmdz_para
20  IMPLICIT NONE
21  INCLUDE 'dimsoil.h'
22
23    REAL,    DIMENSION(klon)                 :: tsol
24    REAL,    DIMENSION(klon)                 :: sn
25    REAL,    DIMENSION(klon)                 :: rugmer
26    REAL,    DIMENSION(klon)                 :: run_off_lic_0
27    REAL,    DIMENSION(klon)                 :: lic
28    REAL,    DIMENSION(klon)                 :: fder
29
30    REAL,    DIMENSION(klon,nbsrf)           :: qsolsrf, snsrf
31    REAL,    DIMENSION(klon,nsoilmx,nbsrf)   :: tsoil
32   
33    REAL,    DIMENSION(klon_mpi)             :: tsol_mpi, qsol_mpi, zmasq_mpi, lic_mpi
34    REAL,    DIMENSION(klon_mpi)             :: zmea_mpi, zstd_mpi, zsig_mpi, zgam_mpi, zthe_mpi
35
36    INTEGER :: ji,j,i
37 
38    IF (is_omp_master) THEN
39      CALL xios_recv_field("ts",tsol_mpi)
40      CALL xios_recv_field("qs",qsol_mpi)
41      CALL xios_recv_field("mask",zmasq_mpi)
42      CALL xios_recv_field("landice",lic_mpi)
43      CALL xios_recv_field("zmea",zmea_mpi)
44      CALL xios_recv_field("zstd",zstd_mpi)
45      CALL xios_recv_field("zsig",zsig_mpi)
46      CALL xios_recv_field("zgam",zgam_mpi)
47      CALL xios_recv_field("zthe",zthe_mpi)
48    ENDIF
49    CALL scatter_omp(tsol_mpi,tsol)
50    CALL scatter_omp(qsol_mpi,qsol)
51    CALL scatter_omp(zmasq_mpi,zmasq)
52    CALL scatter_omp(lic_mpi,lic)
53    CALL scatter_omp(zmea_mpi,zmea)
54    CALL scatter_omp(zstd_mpi,zstd)
55    CALL scatter_omp(zsig_mpi,zsig)
56    CALL scatter_omp(zgam_mpi,zgam)
57    CALL scatter_omp(zthe_mpi,zthe)
58
59    radsol(:)   = 0.0
60    rugmer(:) = 0.001
61    sn(:)     = 0
62
63    WHERE(qsol(:)<0) qsol(:)=0
64       
65    WHERE(   zmasq(:)<EPSFRA) zmasq(:)=0.
66    WHERE(1.-zmasq(:)<EPSFRA) zmasq(:)=1.
67
68    pctsrf(:,:) = 0
69    pctsrf(:,is_lic)=lic
70    WHERE(pctsrf(:,is_lic)<EPSFRA) pctsrf(:,is_lic)=0.
71    WHERE(zmasq(:)<EPSFRA)         pctsrf(:,is_lic)=0.
72
73    pctsrf(:,is_ter)=zmasq(:)
74
75!--- Adequation with soil/sea mask
76    DO ji=1,klon
77      IF(zmasq(ji)>EPSFRA) THEN
78        IF(pctsrf(ji,is_lic)>=zmasq(ji)) THEN
79          pctsrf(ji,is_lic)=zmasq(ji)
80          pctsrf(ji,is_ter)=0.
81        ELSE
82          pctsrf(ji,is_ter)=zmasq(ji)-pctsrf(ji,is_lic)
83          IF(pctsrf(ji,is_ter)<EPSFRA) THEN
84            pctsrf(ji,is_ter)=0.
85            pctsrf(ji,is_lic)=zmasq(ji)
86          END IF
87        END IF
88      END IF
89    END DO
90   
91! sub-surface ocean and sea ice (sea ice set to zero for start)
92!*******************************************************************************
93    pctsrf(:,is_oce)=(1.-zmasq(:))
94    WHERE(pctsrf(:,is_oce)<EPSFRA) pctsrf(:,is_oce)=0.
95   
96    zval(:)=max(0.,zmea-2*zstd(:))
97    zpic(:)=zmea+2*zstd(:)
98   
99!! WARNING    DON'T FORGET FOR LATER
100!!ym  IF(couple) pctsrf(:,is_oce)=ocemask_fi(:)
101!!
102   
103! Init: tsol, qsol, sn, evap, tsoil, rain_fall, snow_fall, solsw, sollw, frugs
104!*******************************************************************************
105    DO i=1,nbsrf
106     ftsol(:,i) = tsol
107    END DO
108 
109    DO i=1,nbsrf
110     snsrf(:,i) = sn
111    END DO
112!albedo SB >>>
113!ym error : the sub surface dimension is the third not second
114!    falb_dir(:,is_ter,:)=0.08; falb_dir(:,is_lic,:)=0.6
115!    falb_dir(:,is_oce,:)=0.5;  falb_dir(:,is_sic,:)=0.6
116    falb_dir(:,:,is_ter)=0.08; falb_dir(:,:,is_lic)=0.6
117    falb_dir(:,:,is_oce)=0.5;  falb_dir(:,:,is_sic)=0.6
118
119!ym falb_dif has been forgotten, initialize with defaukt value found in phyetat0 or 0 ?
120!ym probably the uninitialized value was 0 for standard (regular grid) case
121    falb_dif(:,:,:)=0
122
123!albedo SB <<<
124    fevap(:,:) = 0.
125    DO i=1,nbsrf
126     qsolsrf(:,i)=150.
127    END DO
128 
129    DO i=1,nbsrf
130      DO j=1,nsoilmx
131        tsoil(:,j,i) = tsol
132      END DO
133    END DO
134 
135    rain_fall = 0.; snow_fall = 0.
136    solsw = 165.;   sollw = -53.
137!ym warning missing init for sollwdown => set to 0
138  sollwdown  = 0.
139   
140   
141    t_ancien = 273.15
142    u_ancien=0
143    v_ancien=0
144    q_ancien = 0.
145    agesno = 0.
146
147    z0m(:,is_oce) = rugmer(:)
148
149   z0m(:,is_ter) = MAX(1.0e-05,zstd(:)*zsig(:)/2.0)
150   z0m(:,is_lic) = MAX(1.0e-05,zstd(:)*zsig(:)/2.0)
151
152   z0m(:,is_sic) = 0.001
153   z0h(:,:)=z0m(:,:)
154
155    fder = 0.0
156    clwcon = 0.0
157    rnebcon = 0.0
158    ratqs = 0.0
159    run_off_lic_0 = 0.0
160    rugoro = 0.0
161
162! Before phyredem calling, surface modules and values to be saved in startphy.nc
163! are initialized
164!*******************************************************************************
165    pbl_tke(:,:,:) = 1.e-8
166    zmax0(:) = 40.
167    f0(:) = 1.e-5
168    sig1(:,:) = 0.
169    w01(:,:) = 0.
170    wake_deltat(:,:) = 0.
171    wake_deltaq(:,:) = 0.
172    wake_s(:) = 0.
173    wake_cstar(:) = 0.
174    wake_fip(:) = 0.
175    wake_pe = 0.
176    fm_therm = 0.
177    entr_therm = 0.
178    detr_therm = 0.
179    ale_bl = 0.
180    ale_bl_trig =0.
181    alp_bl =0.
182    CALL fonte_neige_init(run_off_lic_0)
183    CALL pbl_surface_init( fder, snsrf, qsolsrf, tsoil )
184    CALL phyredem( "startphy.nc" )
185
186#endif
187  END SUBROUTINE create_etat0_unstruct
188
189
190END MODULE create_etat0_unstruct_mod
Note: See TracBrowser for help on using the repository browser.