source: LMDZ6/branches/LMDZ_ECRad/libf/phylmd/readaerosolstrato_m.F90 @ 4390

Last change on this file since 4390 was 4179, checked in by lguez, 2 years ago

Use an external updated NetCDF95 library

Remove NetCDF95 from source files. We want to use an up-to-date
NetCDF95 library to read a NetCDF file containing groups, for aerosol
optical properties. It seems complicated to keep the NetCDF95 library
inside LMDZ because:

  • NetCDF95 now also needs a C compiler. I do not know how to make this work with FCM.


  • NetCDF95 cannot be compiled with the -r8 option: some specific procedures in a generic interface become identical.


  • Secondarily, we would have to change the names of files to adhere to the LMDZ standard. We are not glad to do that every time we update.


For now, we can compile using the options -include and -link of
makelmdz_fcm.

As we use an updated NetCDF95 library, we have to update some of the
calls in LMDZ. Those are the calls to nf95_inquire_variable and
nf95_gw_var which used to take a pointer argument and now take an
allocatable argument.

File size: 4.6 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#ifdef CPP_XIOS
27  USE netcdf
28  USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, &
29                      nf95_inq_varid, nf95_open
30  USE mod_phys_lmdz_para
31  USE xios
32!  USE YOERAD, ONLY : NLW
33  IMPLICIT NONE
34  REAL, allocatable:: latitude(:)
35  REAL, allocatable:: longitude(:)
36  INTEGER :: nlat, nlon
37  REAL    :: null_array(0)
38  INTEGER :: ncid_in, varid
39 
40    IF (is_omp_master) THEN 
41      IF (is_mpi_root) THEN
42        CALL nf95_open("taustrat.nc", nf90_nowrite, ncid_in)
43        CALL nf95_inq_varid(ncid_in, "LAT", varid)
44        CALL nf95_gw_var(ncid_in, varid, latitude)
45        CALL nf95_inq_varid(ncid_in, "LON", varid)
46        CALL nf95_gw_var(ncid_in, varid, longitude)
47        CALL nf95_close(ncid_in)
48        nlat=size(latitude)
49        nlon=size(longitude)
50      ENDIF
51      CALL bcast_mpi(nlat)
52      CALL bcast_mpi(nlon)
53
54      IF (is_mpi_root) THEN
55        CALL xios_set_domain_attr("domain_taustrat",nj_glo=nlat, nj=nlat, jbegin=0, latvalue_1d=latitude)
56        CALL xios_set_domain_attr("domain_taustrat",ni_glo=nlon, ni=nlon, ibegin=0, lonvalue_1d = longitude)
57       ELSE
58        CALL xios_set_domain_attr("domain_taustrat",nj_glo=nlat, nj=0, jbegin=0, latvalue_1d=null_array )
59        CALL xios_set_domain_attr("domain_taustrat",ni_glo=nlon, ni=0, ibegin=0, lonvalue_1d=null_array)
60      ENDIF   
61 
62      CALL xios_set_fieldgroup_attr("aerosol_strato1",enabled=.TRUE.)
63    ENDIF
64   
65#endif
66  END SUBROUTINE init_readaerosolstrato1
67 
68  SUBROUTINE init_readaerosolstrato2
69#ifdef CPP_XIOS
70  USE netcdf
71  USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, &
72                      nf95_inq_varid, nf95_open
73  USE mod_phys_lmdz_para
74  USE xios
75!  USE YOERAD, ONLY : NLW
76  IMPLICIT NONE
77  REAL, allocatable:: latitude(:)
78  REAL, allocatable:: wav(:)
79  INTEGER :: nlat,n_wav
80  REAL    :: null_array(0)
81  INTEGER :: ncid_in, varid
82
83    IF (is_omp_master) THEN   
84      IF (is_mpi_root) THEN
85        CALL nf95_open("tauswstrat.2D.nc", nf90_nowrite, ncid_in)
86        CALL nf95_inq_varid(ncid_in, "LAT", varid)
87        CALL nf95_gw_var(ncid_in, varid, latitude)
88        CALL nf95_inq_varid(ncid_in, "WAV", varid)
89        CALL nf95_gw_var(ncid_in, varid, wav)
90        CALL nf95_close(ncid_in)
91        nlat=size(latitude)
92        n_wav = size(wav)
93      ENDIF
94      CALL bcast_mpi(nlat)
95      CALL bcast_mpi(n_wav)
96
97      IF (is_mpi_root) THEN
98        CALL xios_set_domain_attr("domain_tauswstrat",nj_glo=nlat, nj=nlat, jbegin=0, latvalue_1d=latitude)
99        CALL xios_set_domain_attr("domain_tauswstrat",ni_glo=8, ni=8, ibegin=0, lonvalue_1d = (/ 0.,45.,90.,135.,180.,225.,270., 315. /))
100        DEALLOCATE(latitude)
101      ELSE
102        CALL xios_set_domain_attr("domain_tauswstrat",nj_glo=nlat, nj=0, jbegin=0, latvalue_1d=null_array )
103        CALL xios_set_domain_attr("domain_tauswstrat",ni_glo=8, ni=0, ibegin=0, lonvalue_1d=null_array)
104      ENDIF   
105      CALL  xios_set_axis_attr("nsw", n_glo=n_wav)
106   
107      IF (is_mpi_root) THEN
108        CALL nf95_open("taulwstrat.2D.nc", nf90_nowrite, ncid_in)
109        CALL nf95_inq_varid(ncid_in, "LAT", varid)
110        CALL nf95_gw_var(ncid_in, varid, latitude)
111        CALL nf95_inq_varid(ncid_in, "WAV", varid)
112        CALL nf95_gw_var(ncid_in, varid, wav)
113        CALL nf95_close(ncid_in)
114        nlat=size(latitude)
115        n_wav = size(wav)
116      ENDIF
117      CALL bcast_mpi(nlat)
118      CALL bcast_mpi(n_wav)
119
120      IF (is_mpi_root) THEN
121        CALL xios_set_domain_attr("domain_taulwstrat",nj_glo=nlat, nj=nlat, jbegin=0, latvalue_1d=latitude)
122        CALL xios_set_domain_attr("domain_taulwstrat",ni_glo=8, ni=8, ibegin=0, lonvalue_1d = (/ 0.,45.,90.,135.,180.,225.,270., 315. /))
123        DEALLOCATE(latitude)
124      ELSE
125        CALL xios_set_domain_attr("domain_taulwstrat",nj_glo=nlat, nj=0, jbegin=0, latvalue_1d=null_array )
126        CALL xios_set_domain_attr("domain_taulwstrat",ni_glo=8, ni=0, ibegin=0, lonvalue_1d=null_array)
127      ENDIF   
128   
129      CALL  xios_set_axis_attr("nlw", n_glo=n_wav)
130      CALL xios_set_fieldgroup_attr("aerosol_strato2",enabled=.TRUE.)
131
132    ENDIF
133#endif   
134  END SUBROUTINE init_readaerosolstrato2
135 
136
137END MODULE readaerosolstrato_m
138
Note: See TracBrowser for help on using the repository browser.