source: LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phylmd/ce0l.F90 @ 5186

Last change on this file since 5186 was 5186, checked in by abarral, 2 months ago

Encapsulate files in modules

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 9.6 KB
Line 
1PROGRAM ce0l
2
3  !-------------------------------------------------------------------------------
4  ! Purpose: Initial states and boundary conditions files creation:
5  !     * start.nc    for dynamics    (using etat0dyn     routine)
6  !     * startphy.nc for physics     (using etat0phys    routine)
7  !     * limit.nc    for forced runs (using limit_netcdf routine)
8  !-------------------------------------------------------------------------------
9  ! Notes:
10  !     * extrap=.T. (default) for data extrapolation, like for the SSTs when file
11  !                   does contain ocean points only.
12  !     * "masque" can be:
13  !       - read from file "o2a.nc"          (for coupled runs).
14  !       - read from file "startphy0.nc"    (from a previous run).
15  !       - created in etat0phys or etat0dyn (for forced  runs).
16  !     It is then passed to limit_netcdf to ensure consistancy.
17  !-------------------------------------------------------------------------------
18  USE ioipsl, ONLY: ioconf_calendar, getin, flininfo, flinopen, flinget, flinclo
19  USE control_mod, ONLY: day_step, dayref, nsplit_phys
20  USE etat0dyn, ONLY: etat0dyn_netcdf
21  USE etat0phys, ONLY: etat0phys_netcdf
22  USE limit, ONLY: limit_netcdf
23  USE netcdf, ONLY: nf90_open, nf90_nowrite, nf90_close, nf90_noerr, &
24          nf90_inquire_dimension, nf90_inq_dimid, nf90_inq_varid, nf90_get_var
25  USE lmdz_infotrac, ONLY: init_infotrac
26  USE dimphy, ONLY: klon
27  USE test_disvert_m, ONLY: test_disvert
28  USE lmdz_filtreg, ONLY: inifilr
29  USE iniphysiq_mod, ONLY: iniphysiq
30  USE mod_const_mpi, ONLY: comm_lmdz
31
32#ifdef CPP_PARA
33  USE mod_const_mpi,  ONLY: init_const_mpi
34  USE parallel_lmdz,  ONLY: init_parallel, mpi_rank, omp_rank, using_mpi
35  USE bands,          ONLY: read_distrib, distrib_phys
36  USE mod_hallo,      ONLY: init_mod_hallo
37  USE mod_interface_dyn_phys, ONLY: init_interface_dyn_phys
38  USE lmdz_xios, ONLY: using_xios, xios_finalize
39#endif
40
41  USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, kappa, omeg, r, rad, &
42          pi, jmp1
43  USE logic_mod, ONLY: iflag_phys, ok_etat0, ok_limit
44  USE comvert_mod, ONLY: pa, preff, pressure_exner
45  USE temps_mod, ONLY: calend, day_ini, dt
46  USE lmdz_mpi
47  USE lmdz_iniprint, ONLY: lunout, prt_level
48  USE lmdz_comgeom2
49
50  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
51  USE lmdz_paramet
52  USE lmdz_conf_gcm, ONLY: conf_gcm
53
54  IMPLICIT NONE
55
56  !-------------------------------------------------------------------------------
57  ! Local variables:
58
59  REAL :: masque(iip1, jjp1)             !--- CONTINENTAL MASK
60  REAL :: phis  (iip1, jjp1)             !--- GROUND GEOPOTENTIAL
61  CHARACTER(LEN = 256) :: modname, fmt, calnd           !--- CALENDAR TYPE
62  LOGICAL :: use_filtre_fft
63  LOGICAL, PARAMETER :: extrap = .FALSE.
64
65  !--- Local variables for ocean mask reading:
66  INTEGER :: nid_o2a, iml_omask, jml_omask, j
67  INTEGER :: fid, iret, llm_tmp, ttm_tmp, itaul(1)
68  REAL, ALLOCATABLE :: lon_omask(:, :), dlon_omask(:), ocemask(:, :)
69  REAL, ALLOCATABLE :: lat_omask(:, :), dlat_omask(:), ocetmp (:, :)
70  REAL :: date, lev(1)
71
72  !--- Local variables for land mask from startphy0 file reading
73  INTEGER :: nid_sta, nid_nph, nid_msk, nphys
74  REAL, ALLOCATABLE :: masktmp(:)
75
76#ifdef CPP_PARA
77  INTEGER ierr
78#else
79  ! for iniphysiq in serial mode
80  INTEGER, PARAMETER :: mpi_rank = 0
81  INTEGER :: distrib_phys(mpi_rank:mpi_rank) = (jjm - 1) * iim + 2
82#endif
83  !-------------------------------------------------------------------------------
84  modname = "ce0l"
85
86  !--- Constants
87  pi = 4. * ATAN(1.)
88  rad = 6371229.
89  daysec = 86400.
90  omeg = 2. * pi / daysec
91  g = 9.8
92  kappa = 0.2857143
93  cpp = 1004.70885
94  jmp1 = jjm + 1
95  preff = 101325.
96  pa = 50000.
97
98  CALL conf_gcm(99, .TRUE.)
99  dtvr = daysec / REAL(day_step)
100  WRITE(lunout, *)'dtvr', dtvr
101  CALL iniconst()
102  CALL inigeom()
103
104  !--- Calendar choice
105  calnd = 'gregorian'
106  SELECT CASE(calend)
107  CASE('earth_360d');CALL ioconf_calendar('360_day');   calnd = 'with 360 days/year'
108  CASE('earth_365d');CALL ioconf_calendar('noleap'); calnd = 'with no leap year'
109  CASE('earth_366d');CALL ioconf_calendar('366d');   calnd = 'with leap years only'
110  CASE('gregorian'); CALL ioconf_calendar('gregorian')
111  CASE('standard');  CALL ioconf_calendar('gregorian')
112  CASE('julian');    CALL ioconf_calendar('julian'); calnd = 'julian'
113  CASE('proleptic_gregorian'); CALL ioconf_calendar('gregorian')
114  !--- DC Bof...  => IOIPSL a mettre a jour: proleptic_gregorian /= gregorian
115  CASE DEFAULT
116    CALL abort_gcm('ce0l', 'Bad choice for calendar', 1)
117  END SELECT
118  WRITE(lunout, *)'CHOSEN CALENDAR: Earth ' // TRIM(calnd)
119
120#ifdef CPP_PARA
121!--- Physical grid + parallel initializations
122  CALL init_const_mpi()
123  CALL init_parallel()
124  CALL read_distrib()
125  CALL init_mod_hallo()
126#endif
127  WRITE(lunout, *)'---> klon=', klon
128
129  !--- Tracers initializations
130  CALL init_infotrac()
131
132  CALL inifilr()
133  CALL iniphysiq(iim, jjm, llm, &
134          distrib_phys(mpi_rank), comm_lmdz, &
135          daysec, day_ini, dtphys / nsplit_phys, &
136          rlatu, rlatv, rlonu, rlonv, aire, cu, cv, rad, g, r, cpp, iflag_phys)
137  IF(pressure_exner) CALL test_disvert
138
139#ifdef CPP_PARA
140  IF (mpi_rank==0.AND.omp_rank==0) THEN
141#endif
142  use_filtre_fft = .FALSE.
143  CALL getin('use_filtre_fft', use_filtre_fft)
144  IF(use_filtre_fft) THEN
145    WRITE(lunout, *)"FFT filter not available for sequential dynamics."
146    WRITE(lunout, *)"Your setting of variable use_filtre_fft is not used."
147  ENDIF
148
149  !--- LAND MASK. THREE CASES:
150  !   1) read from ocean model    file "o2a.nc"    (coupled runs)
151  !   2) read from previous run   file="startphy0.nc"
152  !   3) computed from topography file "Relief.nc" (masque(:,:)=-99999.)
153  ! In the first case, the mask from the ocean model is used compute the
154  ! weights to ensure ocean fractions are the same for atmosphere and ocean.
155  !*******************************************************************************
156  IF(nf90_open("o2a.nc", nf90_nowrite, nid_o2a)==nf90_noerr) THEN
157    iret = nf90_close(nid_o2a)
158    WRITE(lunout, *)'BEWARE !! Ocean mask "o2a.nc" file found'
159    WRITE(lunout, *)'Coupled run.'
160    CALL flininfo("o2a.nc", iml_omask, jml_omask, llm_tmp, ttm_tmp, nid_o2a)
161    IF(iml_omask/=iim .OR.jml_omask/=jjp1) THEN
162      WRITE(lunout, *)'Mismatching dimensions for ocean mask'
163      WRITE(lunout, *)'iim  = ', iim, ' iml_omask = ', iml_omask
164      WRITE(lunout, *)'jjp1 = ', jjp1, ' jml_omask = ', jml_omask
165      CALL abort_gcm(modname, '', 1)
166    END IF
167    ALLOCATE(ocemask(iim, jjp1), lon_omask(iim, jjp1), dlon_omask(iim))
168    ALLOCATE(ocetmp (iim, jjp1), lat_omask(iim, jjp1), dlat_omask(jjp1))
169    CALL flinopen("o2a.nc", .FALSE., iml_omask, jml_omask, llm_tmp, &
170            lon_omask, lat_omask, lev, ttm_tmp, itaul, date, dt, fid)
171    CALL flinget(fid, "OceMask", iim, jjp1, llm_tmp, ttm_tmp, 1, 1, ocetmp)
172    CALL flinclo(fid)
173    dlon_omask(1:iim) = lon_omask(1:iim, 1)
174    dlat_omask(1:jjp1) = lat_omask(1, 1:jjp1)
175    ocemask = ocetmp
176    IF(dlat_omask(1)<dlat_omask(jml_omask)) THEN
177      DO j = 1, jjp1
178        ocemask(:, j) = ocetmp(:, jjp1 - j + 1)
179      END DO
180    END IF
181    DEALLOCATE(ocetmp, lon_omask, lat_omask, dlon_omask, dlat_omask)
182    IF(prt_level>=1) THEN
183      WRITE(fmt, "(i4,'i1)')")iim ; fmt = '(' // ADJUSTL(fmt)
184      WRITE(lunout, *)'OCEAN MASK :'
185      WRITE(lunout, fmt) NINT(ocemask)
186    END IF
187    masque(1:iim, :) = 1. - ocemask(:, :)
188    masque(iip1, :) = masque(1, :)
189    DEALLOCATE(ocemask)
190  ELSE IF(nf90_open("startphy0.nc", nf90_nowrite, nid_sta)==nf90_noerr) THEN
191    WRITE(lunout, *)'BEWARE !! File "startphy0.nc" found.'
192    WRITE(lunout, *)'Getting the land mask from a previous run.'
193    iret = nf90_inq_dimid(nid_sta, 'points_physiques', nid_nph)
194    iret = nf90_inquire_dimension(nid_sta, nid_nph, len = nphys)
195    IF(nphys/=klon) THEN
196      WRITE(lunout, *)'Mismatching dimensions for land mask'
197      WRITE(lunout, *)'nphys  = ', nphys, ' klon = ', klon
198      iret = nf90_close(nid_sta)
199      CALL abort_gcm(modname, '', 1)
200    END IF
201    ALLOCATE(masktmp(klon))
202    iret = nf90_inq_varid(nid_sta, 'masque', nid_msk)
203    iret = nf90_get_var(nid_sta, nid_msk, masktmp)
204    iret = nf90_close(nid_sta)
205    CALL gr_fi_dyn(1, klon, iip1, jjp1, masktmp, masque)
206    IF(prt_level>=1) THEN
207      WRITE(fmt, "(i4,'i1)')")iip1 ; fmt = '(' // ADJUSTL(fmt)
208      WRITE(lunout, *)'LAND MASK :'
209      WRITE(lunout, fmt) NINT(masque)
210    END IF
211    DEALLOCATE(masktmp)
212  ELSE
213    WRITE(lunout, *)'BEWARE !! No ocean mask "o2a.nc" file or "startphy0.nc" file found'
214    WRITE(lunout, *)'Land mask will be built from the topography file.'
215    masque(:, :) = -99999.
216  END IF
217  phis(:, :) = -99999.
218
219  IF(ok_etat0) THEN
220    WRITE(lunout, '(//)')
221    WRITE(lunout, *) '  ************************  '
222    WRITE(lunout, *) '  ***  etat0phy_netcdf ***  '
223    WRITE(lunout, *) '  ************************  '
224    CALL etat0phys_netcdf(masque, phis)
225    WRITE(lunout, '(//)')
226    WRITE(lunout, *) '  ************************  '
227    WRITE(lunout, *) '  ***  etat0dyn_netcdf ***  '
228    WRITE(lunout, *) '  ************************  '
229    CALL etat0dyn_netcdf(masque, phis)
230  END IF
231
232  IF(ok_limit) THEN
233    WRITE(lunout, '(//)')
234    WRITE(lunout, *) '  *********************  '
235    WRITE(lunout, *) '  ***  Limit_netcdf ***  '
236    WRITE(lunout, *) '  *********************  '
237    WRITE(lunout, '(//)')
238    CALL limit_netcdf(masque, phis, extrap)
239  END IF
240
241  WRITE(lunout, '(//)')
242  WRITE(lunout, *) '  ***************************  '
243  WRITE(lunout, *) '  ***  grilles_gcm_netcdf ***  '
244  WRITE(lunout, *) '  ***************************  '
245  WRITE(lunout, '(//)')
246  CALL grilles_gcm_netcdf_sub(masque, phis)
247
248#ifdef CPP_PARA
249  END IF
250  IF (using_xios) CALL xios_finalize
251  IF (using_mpi) CALL MPI_FINALIZE(ierr)
252#endif
253
254END PROGRAM ce0l
255
256!-------------------------------------------------------------------------------
Note: See TracBrowser for help on using the repository browser.