LMDZ
ce0l.F90
Go to the documentation of this file.
1 PROGRAM 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 ! - created in etat0phys or etat0dyn (for forced runs).
15 ! It is then passed to limit_netcdf to ensure consistancy.
16 !-------------------------------------------------------------------------------
17  USE ioipsl, ONLY: ioconf_calendar, getin, flininfo, flinopen, flinget, flinclo
19  USE etat0dyn, ONLY: etat0dyn_netcdf
20  USE etat0phys, ONLY: etat0phys_netcdf
21  USE limit, ONLY: limit_netcdf
22  USE netcdf, ONLY: nf90_open, nf90_nowrite, nf90_close, nf90_noerr
23  USE infotrac, ONLY: type_trac, infotrac_init
24  USE dimphy, ONLY: klon
25  USE test_disvert_m, ONLY: test_disvert
26  USE filtreg_mod, ONLY: inifilr
27  USE iniphysiq_mod, ONLY: iniphysiq
28  USE mod_const_mpi, ONLY: comm_lmdz
29 #ifdef inca
31 #endif
32 #ifdef CPP_PARA
33  USE mod_const_mpi, ONLY: init_const_mpi
35  USE bands, ONLY: read_distrib, distrib_phys
36  USE mod_hallo, ONLY: init_mod_hallo
38 #endif
39 
40  IMPLICIT NONE
41 
42 !-------------------------------------------------------------------------------
43 ! Local variables:
44  include "dimensions.h"
45  include "paramet.h"
46  include "comgeom2.h"
47  include "comconst.h"
48  include "comvert.h"
49  include "iniprint.h"
50  include "temps.h"
51  include "logic.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 #ifndef CPP_PARA
65 ! for iniphysiq in serial mode
66  INTEGER,PARAMETER :: mpi_rank=0
67  INTEGER :: distrib_phys(mpi_rank:mpi_rank)=(jjm-1)*iim+2
68 #endif
69 !-------------------------------------------------------------------------------
70  modname="ce0l"
71 
72 !--- Constants
73  pi = 4. * atan(1.)
74  rad = 6371229.
75  daysec = 86400.
76  omeg = 2.*pi/daysec
77  g = 9.8
78  kappa = 0.2857143
79  cpp = 1004.70885
80  jmp1 = jjm + 1
81  preff = 101325.
82  pa = 50000.
83 
84  CALL conf_gcm( 99, .true. )
85  dtvr = daysec/REAL(day_step)
86  WRITE(lunout,*)'dtvr',dtvr
87  CALL iniconst()
88  CALL inigeom()
89 
90 !--- Calendar choice
91 #ifdef CPP_IOIPSL
92  calnd='gregorian'
93  SELECT CASE(calend)
94  CASE('earth_360d');CALL ioconf_calendar('360d'); calnd='with 360 days/year'
95  CASE('earth_365d');CALL ioconf_calendar('noleap'); calnd='with no leap year'
96  CASE('earth_366d');CALL ioconf_calendar('366d'); calnd='with leap years only'
97  CASE('gregorian'); CALL ioconf_calendar('gregorian')
98  CASE('standard'); CALL ioconf_calendar('gregorian')
99  CASE('julian'); CALL ioconf_calendar('julian'); calnd='julian'
100  CASE('proleptic_gregorian'); CALL ioconf_calendar('gregorian')
101  !--- DC Bof... => IOIPSL a mettre a jour: proleptic_gregorian /= gregorian
102  CASE DEFAULT
103  CALL abort_gcm('ce0l','Bad choice for calendar',1)
104  END SELECT
105  WRITE(lunout,*)'CHOSEN CALENDAR: Earth '//trim(calnd)
106 #endif
107 
108 #ifdef CPP_PARA
109 !--- Physical grid + parallel initializations
110  CALL init_const_mpi()
111  CALL init_parallel()
112  CALL read_distrib()
113  CALL init_mod_hallo()
114 #endif
115  WRITE(lunout,*)'---> klon=',klon
116 
117 !--- Tracers initializations
118  IF (type_trac == 'inca') THEN
119 #ifdef INCA
120  CALL init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday,&
122  CALL init_inca_para(iim,jjp1,llm,klon_glo,mpi_size,distrib_phys,&
123  comm_lmdz)
124  WRITE(lunout,*)'nbtr =' , nbtr
125 #endif
126  END IF
127  CALL infotrac_init()
128 
129  CALL inifilr()
130  CALL iniphysiq(iim,jjm,llm, &
131  distrib_phys(mpi_rank),comm_lmdz, &
134  IF(pressure_exner) CALL test_disvert
135 
136 #ifdef CPP_PARA
137  IF (mpi_rank==0.AND.omp_rank==0) THEN
138 #endif
139  use_filtre_fft=.false.
140  CALL getin('use_filtre_fft',use_filtre_fft)
141  IF(use_filtre_fft) THEN
142  WRITE(lunout,*)"FFT filter not available for sequential dynamics."
143  WRITE(lunout,*)"Your setting of variable use_filtre_fft is not used."
144  ENDIF
145 
146 !--- LAND MASK. TWO CASES:
147 ! 1) read from ocean model file "o2a.nc" (coupled runs)
148 ! 2) computed from topography file "Relief.nc" (masque(:,:)=-99999.)
149 ! Coupled simulations (case 1) use the ocean model mask to compute the
150 ! weights to ensure ocean fractions are the same for atmosphere and ocean.
151 !*******************************************************************************
152  IF(nf90_open("o2a.nc", nf90_nowrite, nid_o2a)/=nf90_noerr) THEN
153  WRITE(lunout,*)'BEWARE !! No ocean mask "o2a.nc" file found'
154  WRITE(lunout,*)'Forced run.'
155  masque(:,:)=-99999.
156  ELSE
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; ocemask(:,j) = ocetmp(:,jjp1-j+1); END DO
178  END IF
179  DEALLOCATE(ocetmp,lon_omask,lat_omask,dlon_omask,dlat_omask)
180  IF(prt_level>=1) THEN
181  WRITE(fmt,"(i4,'i1)')")iim ; fmt='('//adjustl(fmt)
182  WRITE(lunout,*)'OCEAN MASK :'
183  WRITE(lunout,fmt) nint(ocemask)
184  END IF
185  masque(1:iim,:)=1.-ocemask(:,:)
186  masque(iip1 ,:)=masque(1,:)
187  DEALLOCATE(ocemask)
188  END IF
189  phis(:,:)=-99999.
190 
191  IF(ok_etat0) THEN
192  WRITE(lunout,'(//)')
193  WRITE(lunout,*) ' ************************ '
194  WRITE(lunout,*) ' *** etat0phy_netcdf *** '
195  WRITE(lunout,*) ' ************************ '
196  CALL etat0phys_netcdf(masque,phis)
197  WRITE(lunout,'(//)')
198  WRITE(lunout,*) ' ************************ '
199  WRITE(lunout,*) ' *** etat0dyn_netcdf *** '
200  WRITE(lunout,*) ' ************************ '
201  CALL etat0dyn_netcdf(masque,phis)
202  END IF
203 
204  IF(ok_limit) THEN
205  WRITE(lunout,'(//)')
206  WRITE(lunout,*) ' ********************* '
207  WRITE(lunout,*) ' *** Limit_netcdf *** '
208  WRITE(lunout,*) ' ********************* '
209  WRITE(lunout,'(//)')
210  CALL limit_netcdf(masque,phis,extrap)
211  END IF
212 
213  WRITE(lunout,'(//)')
214  WRITE(lunout,*) ' *************************** '
215  WRITE(lunout,*) ' *** grilles_gcm_netcdf *** '
216  WRITE(lunout,*) ' *************************** '
217  WRITE(lunout,'(//)')
218  CALL grilles_gcm_netcdf_sub(masque,phis)
219 
220 #ifdef CPP_PARA
221  END IF
222 #endif
223 
224 END PROGRAM ce0l
225 !
226 !-------------------------------------------------------------------------------
Definition: bands.F90:4
integer, dimension(:), allocatable distrib_phys
Definition: bands.F90:24
subroutine iniphysiq(iim, jjm, nlayer, nbp, communicator, punjours, pdayref, ptimestep, rlatu, rlatv, rlonu, rlonv, aire, cu, cv, prad, pg, pr, pcpp, iflag_phys)
integer, parameter is_ter
!$Id mode_top_bound COMMON comconstr r
Definition: comconst.h:7
!$Id mode_top_bound COMMON comconstr g
Definition: comconst.h:7
subroutine grilles_gcm_netcdf_sub(masque, phis)
!$Id preff
Definition: comvert.h:8
!$Id mode_top_bound COMMON comconstr kappa
Definition: comconst.h:7
integer, save mpi_rank
integer, save dayref
Definition: control_mod.F90:26
integer, save klon
Definition: dimphy.F90:3
!$Id ysinus ok_gradsfile ok_limit
Definition: logic.h:10
integer, save mpi_size
subroutine limit_netcdf(masque, phis, extrap)
!$Id calend INTEGER itaufin INTEGER itau_phy INTEGER day_ref REAL dt
Definition: temps.h:15
subroutine abort_gcm(modname, message, ierr)
Definition: abort_gcm.F:7
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga u_toga vq_toga w_prof vq_prof llm day day1 day day1 *dt_dice endif!time annee_ref dt_dice swup_dice vg_dice omega_dice tg_prof vg_profd w_profd omega_profd!do llm!print llm l llm
subroutine inifilr
Definition: filtreg_mod.F90:12
!$Id mode_top_bound COMMON comconstr && pi
Definition: comconst.h:7
!$Header!CDK comgeom COMMON comgeom aire
Definition: comgeom.h:25
!$Header!CDK comgeom COMMON comgeom rlatu
Definition: comgeom.h:25
!$Id ysinus ok_gradsfile hybrid COMMON logici iflag_phys
Definition: logic.h:10
integer, save day_step
Definition: control_mod.F90:15
subroutine init_mod_hallo
Definition: mod_hallo.F90:66
subroutine init_const_mpi
subroutine inigeom
Definition: inigeom.F:7
!$Id && day_ini
Definition: temps.h:15
!$Id mode_top_bound COMMON comconstr dtphys
Definition: comconst.h:7
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
Definition: calcul_STDlev.h:26
!$Id ysinus ok_gradsfile ok_etat0
Definition: logic.h:10
!$Id mode_top_bound COMMON comconstr rad
Definition: comconst.h:7
!$Header jjp1
Definition: paramet.h:14
!$Id mode_top_bound COMMON comconstr cpp
Definition: comconst.h:7
integer, parameter is_lic
integer comm_lmdz
!FH On elimine toutes les clefs physiques dans la dynamique prt_level
!$Id mode_top_bound COMMON comconstr daysec
Definition: comconst.h:7
integer, save omp_rank
subroutine conf_gcm(tapedef, etatinit)
Definition: conf_gcm.F90:5
!$Header!CDK comgeom COMMON comgeom rlonu
Definition: comgeom.h:25
!$Header!CDK comgeom COMMON comgeom rlatv
Definition: comgeom.h:25
!$Id && pa
Definition: comvert.h:8
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
character(len=4), save type_trac
Definition: infotrac.F90:40
!$Id!Parameters for parameters that control the rate of approach!to quasi equilibrium noff nlm real tlcrit real entp real sigd real coeffs real dtmax real cu real betad real damp real delta COMMON cvparam nlm tlcrit sigd coeffs cu
Definition: cvparam.h:12
subroutine test_disvert
integer, parameter nbsrf
!$Id jmp1
Definition: comconst.h:7
!$Id mode_top_bound COMMON comconstr dtvr
Definition: comconst.h:7
integer, save nsplit_phys
Definition: control_mod.F90:19
subroutine init_parallel
c c zjulian c cym CALL iim cym klev iim
Definition: ini_bilKP_ave.h:24
subroutine, public etat0phys_netcdf(masque, phis)
integer, parameter is_sic
subroutine read_distrib
Definition: bands.F90:43
subroutine infotrac_init
Definition: infotrac.F90:61
!$Header!CDK comgeom COMMON comgeom cv
Definition: comgeom.h:25
Definition: dimphy.F90:1
subroutine, public etat0dyn_netcdf(masque, phis)
integer, parameter is_oce
subroutine iniconst
Definition: iniconst.F90:5
!$Header!gestion des impressions de sorties et de débogage la sortie standard prt_level COMMON comprint lunout
Definition: iniprint.h:7
program ce0l
Definition: ce0l.F90:1
!$Header!CDK comgeom COMMON comgeom rlonv
Definition: comgeom.h:25