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

Last change on this file since 3435 was 3435, checked in by Laurent Fairhead, 6 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: 4.5 KB
Line 
1MODULE readaerosolstrato_m
2
3
4CONTAINS
5
6  SUBROUTINE init_readaerosolstrato(flag_aerosol_strat)
7  USE mod_grid_phy_lmdz, ONLY: grid_type, unstructured
8  IMPLICIT NONE
9  INTEGER,INTENT(IN) :: flag_aerosol_strat
10   
11    IF (grid_type==unstructured)  THEN
12   
13      IF (flag_aerosol_strat == 1) THEN
14        CALL init_readaerosolstrato1
15      ELSE IF (flag_aerosol_strat == 2) THEN
16        CALL init_readaerosolstrato2
17      ENDIF
18 
19    ENDIF
20 
21  END SUBROUTINE init_readaerosolstrato
22 
23
24
25  SUBROUTINE init_readaerosolstrato1
26  USE netcdf
27  USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, &
28                      nf95_inq_varid, nf95_open
29  USE mod_phys_lmdz_para
30  USE xios
31  USE YOERAD, ONLY : NLW
32  IMPLICIT NONE
33  REAL, POINTER:: latitude(:)
34  REAL, POINTER:: longitude(:)
35  INTEGER :: nlat, nlon
36  REAL    :: null_array(0)
37  INTEGER :: ncid_in, varid
38 
39    IF (is_omp_master) THEN 
40      IF (is_mpi_root) THEN
41        CALL nf95_open("taustrat.nc", nf90_nowrite, ncid_in)
42        CALL nf95_inq_varid(ncid_in, "LAT", varid)
43        CALL nf95_gw_var(ncid_in, varid, latitude)
44        CALL nf95_inq_varid(ncid_in, "LON", varid)
45        CALL nf95_gw_var(ncid_in, varid, longitude)
46        CALL nf95_close(ncid_in)
47        nlat=size(latitude)
48        nlon=size(longitude)
49      ENDIF
50      CALL bcast_mpi(nlat)
51      CALL bcast_mpi(nlon)
52
53      IF (is_mpi_root) THEN
54        CALL xios_set_domain_attr("domain_taustrat",nj_glo=nlat, nj=nlat, jbegin=0, latvalue_1d=latitude)
55        CALL xios_set_domain_attr("domain_taustrat",ni_glo=nlon, ni=nlon, ibegin=0, lonvalue_1d = longitude)
56       ELSE
57        CALL xios_set_domain_attr("domain_taustrat",nj_glo=nlat, nj=0, jbegin=0, latvalue_1d=null_array )
58        CALL xios_set_domain_attr("domain_taustrat",ni_glo=nlon, ni=0, ibegin=0, lonvalue_1d=null_array)
59      ENDIF   
60 
61      CALL xios_set_fieldgroup_attr("aerosol_strato1",enabled=.TRUE.)
62    ENDIF
63   
64  END SUBROUTINE init_readaerosolstrato1
65 
66  SUBROUTINE init_readaerosolstrato2
67  USE netcdf
68  USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, &
69                      nf95_inq_varid, nf95_open
70  USE mod_phys_lmdz_para
71  USE xios
72  USE YOERAD, ONLY : NLW
73  IMPLICIT NONE
74  REAL, POINTER:: latitude(:)
75  REAL, POINTER:: wav(:)
76  INTEGER :: nlat,n_wav
77  REAL    :: null_array(0)
78  INTEGER :: ncid_in, varid
79
80    IF (is_omp_master) THEN   
81      IF (is_mpi_root) THEN
82        CALL nf95_open("tauswstrat.2D.nc", nf90_nowrite, ncid_in)
83        CALL nf95_inq_varid(ncid_in, "LAT", varid)
84        CALL nf95_gw_var(ncid_in, varid, latitude)
85        CALL nf95_inq_varid(ncid_in, "WAV", varid)
86        CALL nf95_gw_var(ncid_in, varid, wav)
87        CALL nf95_close(ncid_in)
88        nlat=size(latitude)
89        n_wav = size(wav)
90      ENDIF
91      CALL bcast_mpi(nlat)
92      CALL bcast_mpi(n_wav)
93
94      IF (is_mpi_root) THEN
95        CALL xios_set_domain_attr("domain_tauswstrat",nj_glo=nlat, nj=nlat, jbegin=0, latvalue_1d=latitude)
96        CALL xios_set_domain_attr("domain_tauswstrat",ni_glo=8, ni=8, ibegin=0, lonvalue_1d = (/ 0.,45.,90.,135.,180.,225.,270., 315. /))
97        DEALLOCATE(latitude)
98      ELSE
99        CALL xios_set_domain_attr("domain_tauswstrat",nj_glo=nlat, nj=0, jbegin=0, latvalue_1d=null_array )
100        CALL xios_set_domain_attr("domain_tauswstrat",ni_glo=8, ni=0, ibegin=0, lonvalue_1d=null_array)
101      ENDIF   
102      CALL  xios_set_axis_attr("nsw", n_glo=n_wav)
103   
104      IF (is_mpi_root) THEN
105        CALL nf95_open("taulwstrat.2D.nc", nf90_nowrite, ncid_in)
106        CALL nf95_inq_varid(ncid_in, "LAT", varid)
107        CALL nf95_gw_var(ncid_in, varid, latitude)
108        CALL nf95_inq_varid(ncid_in, "WAV", varid)
109        CALL nf95_gw_var(ncid_in, varid, wav)
110        CALL nf95_close(ncid_in)
111        nlat=size(latitude)
112        n_wav = size(wav)
113      ENDIF
114      CALL bcast_mpi(nlat)
115      CALL bcast_mpi(n_wav)
116
117      IF (is_mpi_root) THEN
118        CALL xios_set_domain_attr("domain_taulwstrat",nj_glo=nlat, nj=nlat, jbegin=0, latvalue_1d=latitude)
119        CALL xios_set_domain_attr("domain_taulwstrat",ni_glo=8, ni=8, ibegin=0, lonvalue_1d = (/ 0.,45.,90.,135.,180.,225.,270., 315. /))
120        DEALLOCATE(latitude)
121      ELSE
122        CALL xios_set_domain_attr("domain_taulwstrat",nj_glo=nlat, nj=0, jbegin=0, latvalue_1d=null_array )
123        CALL xios_set_domain_attr("domain_taulwstrat",ni_glo=8, ni=0, ibegin=0, lonvalue_1d=null_array)
124      ENDIF   
125   
126      CALL  xios_set_axis_attr("nlw", n_glo=n_wav)
127      CALL xios_set_fieldgroup_attr("aerosol_strato2",enabled=.TRUE.)
128
129    ENDIF
130   
131  END SUBROUTINE init_readaerosolstrato2
132 
133
134END MODULE readaerosolstrato_m
135
Note: See TracBrowser for help on using the repository browser.