source: LMDZ5/trunk/libf/dynphy_lonlat/phylmd/ce0l.F90 @ 2798

Last change on this file since 2798 was 2665, checked in by dcugnet, 8 years ago
  • A (re)startphy.nc file (standard name: "startphy0.nc") can be read by ce0l to get land mask, so mask can be defined (in decreasing priority order) from: 1) "o2a.nc file" if this file is found 2) "startphy0.nc" if this file is found 3) "Relief.nc" otherwise
  • Sub-cell scales parameters for orographic gravity waves can be read from file "oro_params.nc" if the configuration key "read_orop" is TRUE. The effect is to bypass the "grid_noro" routine in ce0l, so that any pre-defined mask (from o2a.nc or startphy0.nc) is then overwritten.
  • The gcm stops if the "limit.nc" records number differs from the current year number of days. A warning is issued in case the gcm calendar does not match the time axis attribute "calendar" (if available) from the "limit.nc" file. This attribute is now added to the "limit.nc" time axis.
  • Few simplifications in grid_noro
  • Few parameters changes in acama_gwd and flott_gwd.
  • Variable d_u can be saved in the outputs.
  • 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.4 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 infotrac,       ONLY: type_trac, infotrac_init
26  USE dimphy,         ONLY: klon
27  USE test_disvert_m, ONLY: test_disvert
28  USE filtreg_mod,    ONLY: inifilr
29  USE iniphysiq_mod,  ONLY: iniphysiq
30  USE mod_const_mpi,  ONLY: comm_lmdz
31#ifdef CPP_PARA
32  USE mod_const_mpi,  ONLY: init_const_mpi
33  USE parallel_lmdz,  ONLY: init_parallel, mpi_rank, omp_rank
34  USE bands,          ONLY: read_distrib, distrib_phys
35  USE mod_hallo,      ONLY: init_mod_hallo
36  USE mod_interface_dyn_phys, ONLY: init_interface_dyn_phys
37#endif
38  USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, kappa, omeg, r, rad, &
39                          pi, jmp1
40  USE logic_mod, ONLY: iflag_phys, ok_etat0, ok_limit
41  USE comvert_mod, ONLY: pa, preff, pressure_exner
42  USE temps_mod, ONLY: calend, day_ini, dt
43
44  IMPLICIT NONE
45
46!-------------------------------------------------------------------------------
47! Local variables:
48  include "dimensions.h"
49  include "paramet.h"
50  include "comgeom2.h"
51  include "iniprint.h"
52  REAL               :: masque(iip1,jjp1)             !--- CONTINENTAL MASK
53  REAL               :: phis  (iip1,jjp1)             !--- GROUND GEOPOTENTIAL
54  CHARACTER(LEN=256) :: modname, fmt, calnd           !--- CALENDAR TYPE
55  LOGICAL            :: use_filtre_fft
56  LOGICAL, PARAMETER :: extrap=.FALSE.
57
58!--- Local variables for ocean mask reading:
59  INTEGER            :: nid_o2a, iml_omask, jml_omask, j
60  INTEGER            :: fid, iret, llm_tmp, ttm_tmp, itaul(1)
61  REAL, ALLOCATABLE  :: lon_omask(:,:), dlon_omask(:), ocemask(:,:)
62  REAL, ALLOCATABLE  :: lat_omask(:,:), dlat_omask(:), ocetmp (:,:)
63  REAL               :: date, lev(1)
64
65!--- Local variables for land mask from startphy0 file reading
66  INTEGER            :: nid_sta, nid_nph, nid_msk, nphys
67  REAL, ALLOCATABLE  :: masktmp(:)
68
69#ifndef CPP_PARA
70! for iniphysiq in serial mode
71  INTEGER,PARAMETER :: mpi_rank=0
72  INTEGER :: distrib_phys(mpi_rank:mpi_rank)=(jjm-1)*iim+2
73#endif
74!-------------------------------------------------------------------------------
75  modname="ce0l"
76
77!--- Constants
78  pi     = 4. * ATAN(1.)
79  rad    = 6371229.
80  daysec = 86400.
81  omeg   = 2.*pi/daysec
82  g      = 9.8
83  kappa  = 0.2857143
84  cpp    = 1004.70885
85  jmp1   = jjm + 1
86  preff   = 101325.
87  pa      = 50000.
88
89  CALL conf_gcm( 99, .TRUE. )
90  dtvr = daysec/REAL(day_step)
91  WRITE(lunout,*)'dtvr',dtvr
92  CALL iniconst()
93  CALL inigeom()
94
95!--- Calendar choice
96#ifdef CPP_IOIPSL
97  calnd='gregorian'
98  SELECT CASE(calend)
99    CASE('earth_360d');CALL ioconf_calendar('360d');   calnd='with 360 days/year'
100    CASE('earth_365d');CALL ioconf_calendar('noleap'); calnd='with no leap year'
101    CASE('earth_366d');CALL ioconf_calendar('366d');   calnd='with leap years only'
102    CASE('gregorian'); CALL ioconf_calendar('gregorian')
103    CASE('standard');  CALL ioconf_calendar('gregorian')
104    CASE('julian');    CALL ioconf_calendar('julian'); calnd='julian'
105    CASE('proleptic_gregorian'); CALL ioconf_calendar('gregorian')
106  !--- DC Bof...  => IOIPSL a mettre a jour: proleptic_gregorian /= gregorian
107    CASE DEFAULT
108      CALL abort_gcm('ce0l','Bad choice for calendar',1)
109  END SELECT
110  WRITE(lunout,*)'CHOSEN CALENDAR: Earth '//TRIM(calnd)
111#endif
112
113#ifdef CPP_PARA
114!--- Physical grid + parallel initializations
115  CALL init_const_mpi()
116  CALL init_parallel()
117  CALL read_distrib()
118  CALL init_mod_hallo()
119#endif
120  WRITE(lunout,*)'---> klon=',klon
121
122!--- Tracers initializations
123  CALL infotrac_init()
124
125  CALL inifilr()
126  CALL iniphysiq(iim,jjm,llm, &
127                 distrib_phys(mpi_rank),comm_lmdz, &
128                 daysec,day_ini,dtphys/nsplit_phys, &
129                 rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp,iflag_phys)
130  IF(pressure_exner) CALL test_disvert
131
132#ifdef CPP_PARA
133  IF (mpi_rank==0.AND.omp_rank==0) THEN
134#endif
135  use_filtre_fft=.FALSE.
136  CALL getin('use_filtre_fft',use_filtre_fft)
137  IF(use_filtre_fft) THEN
138     WRITE(lunout,*)"FFT filter not available for sequential dynamics."
139     WRITE(lunout,*)"Your setting of variable use_filtre_fft is not used."
140  ENDIF
141
142!--- LAND MASK. THREE CASES:
143!   1) read from ocean model    file "o2a.nc"    (coupled runs)
144!   2) read from previous run   file="startphy0.nc"
145!   3) computed from topography file "Relief.nc" (masque(:,:)=-99999.)
146! In the first case, the mask from the ocean model is used compute the
147! weights to ensure ocean fractions are the same for atmosphere and ocean.
148!*******************************************************************************
149  IF(NF90_OPEN("o2a.nc", NF90_NOWRITE, nid_o2a)==NF90_NOERR) THEN
150    iret=NF90_CLOSE(nid_o2a)
151    WRITE(lunout,*)'BEWARE !! Ocean mask "o2a.nc" file found'
152    WRITE(lunout,*)'Coupled run.'
153    CALL flininfo("o2a.nc", iml_omask, jml_omask, llm_tmp, ttm_tmp, nid_o2a)
154    IF(iml_omask/=iim .OR.jml_omask/=jjp1) THEN
155      WRITE(lunout,*)'Mismatching dimensions for ocean mask'
156      WRITE(lunout,*)'iim  = ',iim ,' iml_omask = ',iml_omask
157      WRITE(lunout,*)'jjp1 = ',jjp1,' jml_omask = ',jml_omask
158      CALL abort_gcm(modname,'',1)
159    END IF
160    ALLOCATE(ocemask(iim,jjp1),lon_omask(iim,jjp1),dlon_omask(iim ))
161    ALLOCATE(ocetmp (iim,jjp1),lat_omask(iim,jjp1),dlat_omask(jjp1))
162    CALL flinopen("o2a.nc", .FALSE.,iml_omask,jml_omask,llm_tmp,               &
163                  lon_omask,lat_omask,lev,ttm_tmp,itaul,date,dt,fid)
164    CALL flinget(fid, "OceMask",    iim,jjp1,llm_tmp,ttm_tmp,1,1,ocetmp)
165    CALL flinclo(fid)
166    dlon_omask(1:iim ) = lon_omask(1:iim,1)
167    dlat_omask(1:jjp1) = lat_omask(1,1:jjp1)
168    ocemask = ocetmp
169    IF(dlat_omask(1)<dlat_omask(jml_omask)) THEN
170      DO j=1,jjp1; ocemask(:,j) = ocetmp(:,jjp1-j+1); END DO
171    END IF
172    DEALLOCATE(ocetmp,lon_omask,lat_omask,dlon_omask,dlat_omask)
173    IF(prt_level>=1) THEN
174      WRITE(fmt,"(i4,'i1)')")iim ; fmt='('//ADJUSTL(fmt)
175      WRITE(lunout,*)'OCEAN MASK :'
176      WRITE(lunout,fmt) NINT(ocemask)
177    END IF
178    masque(1:iim,:)=1.-ocemask(:,:)
179    masque(iip1 ,:)=masque(1,:)
180    DEALLOCATE(ocemask)
181  ELSE IF(NF90_OPEN("startphy0.nc", NF90_NOWRITE, nid_sta)==NF90_NOERR) THEN
182    WRITE(lunout,*)'BEWARE !! File "startphy0.nc" found.'
183    WRITE(lunout,*)'Getting the land mask from a previous run.'
184    iret=NF90_INQ_DIMID(nid_sta,'points_physiques',nid_nph)
185    iret=NF90_INQUIRE_DIMENSION(nid_sta,nid_nph,len=nphys)
186    IF(nphys/=klon) THEN
187      WRITE(lunout,*)'Mismatching dimensions for land mask'
188      WRITE(lunout,*)'nphys  = ',nphys ,' klon = ',klon
189      iret=NF90_CLOSE(nid_sta)
190      CALL abort_gcm(modname,'',1)
191    END IF
192    ALLOCATE(masktmp(klon))
193    iret=NF90_INQ_VARID(nid_sta,'masque',nid_msk)
194    iret=NF90_GET_VAR(nid_sta,nid_msk,masktmp)
195    iret=NF90_CLOSE(nid_sta)
196    CALL gr_fi_dyn(1,klon,iip1,jjp1,masktmp,masque)
197    IF(prt_level>=1) THEN
198      WRITE(fmt,"(i4,'i1)')")iip1 ; fmt='('//ADJUSTL(fmt)
199      WRITE(lunout,*)'LAND MASK :'
200      WRITE(lunout,fmt) NINT(masque)
201    END IF
202    DEALLOCATE(masktmp)
203  ELSE
204    WRITE(lunout,*)'BEWARE !! No ocean mask "o2a.nc" file or "startphy0.nc" file found'
205    WRITE(lunout,*)'Land mask will be built from the topography file.'
206    masque(:,:)=-99999.
207  END IF
208  phis(:,:)=-99999.
209
210  IF(ok_etat0) THEN
211    WRITE(lunout,'(//)')
212    WRITE(lunout,*) '  ************************  '
213    WRITE(lunout,*) '  ***  etat0phy_netcdf ***  '
214    WRITE(lunout,*) '  ************************  '
215    CALL etat0phys_netcdf(masque,phis)
216    WRITE(lunout,'(//)')
217    WRITE(lunout,*) '  ************************  '
218    WRITE(lunout,*) '  ***  etat0dyn_netcdf ***  '
219    WRITE(lunout,*) '  ************************  '
220    CALL etat0dyn_netcdf(masque,phis)
221  END IF
222
223  IF(ok_limit) THEN
224    WRITE(lunout,'(//)')
225    WRITE(lunout,*) '  *********************  '
226    WRITE(lunout,*) '  ***  Limit_netcdf ***  '
227    WRITE(lunout,*) '  *********************  '
228    WRITE(lunout,'(//)')
229    CALL limit_netcdf(masque,phis,extrap)
230  END IF
231
232  WRITE(lunout,'(//)')
233  WRITE(lunout,*) '  ***************************  '
234  WRITE(lunout,*) '  ***  grilles_gcm_netcdf ***  '
235  WRITE(lunout,*) '  ***************************  '
236  WRITE(lunout,'(//)')
237  CALL grilles_gcm_netcdf_sub(masque,phis)
238
239#ifdef CPP_PARA
240  END IF
241#endif
242
243END PROGRAM ce0l
244!
245!-------------------------------------------------------------------------------
Note: See TracBrowser for help on using the repository browser.