17 USE ioipsl
, ONLY: ioconf_calendar, getin, flininfo, flinopen, flinget, flinclo
22 USE netcdf
, ONLY: nf90_open, nf90_nowrite, nf90_close, nf90_noerr
44 include
"dimensions.h"
52 REAL :: masque(iip1,
jjp1)
53 REAL :: phis (iip1,
jjp1)
54 CHARACTER(LEN=256) :: modname, fmt, calnd
55 LOGICAL :: use_filtre_fft
56 LOGICAL,
PARAMETER :: extrap=.
false.
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 (:,:)
66 INTEGER,
PARAMETER :: mpi_rank=0
67 INTEGER :: distrib_phys(mpi_rank:mpi_rank)=(jjm-1)*
iim+2
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')
103 CALL abort_gcm(
'ce0l',
'Bad choice for calendar',1)
105 WRITE(
lunout,*)
'CHOSEN CALENDAR: Earth '//trim(calnd)
124 WRITE(
lunout,*)
'nbtr =' , nbtr
131 distrib_phys(mpi_rank),comm_lmdz, &
133 rlatu,
rlatv,
rlonu,
rlonv,
aire,
cu,
cv,
rad,
g,
r,
cpp,
iflag_phys)
137 IF (mpi_rank==0.AND.
omp_rank==0)
THEN
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."
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.'
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
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)
173 dlon_omask(1:
iim ) = lon_omask(1:
iim,1)
174 dlat_omask(1:
jjp1) = lat_omask(1,1:
jjp1)
176 IF(dlat_omask(1)<dlat_omask(jml_omask))
THEN
177 DO j=1,
jjp1; ocemask(:,j) = ocetmp(:,
jjp1-j+1);
END DO
179 DEALLOCATE(ocetmp,lon_omask,lat_omask,dlon_omask,dlat_omask)
181 WRITE(fmt,
"(i4,'i1)')")
iim ; fmt=
'('//adjustl(fmt)
182 WRITE(
lunout,*)
'OCEAN MASK :'
183 WRITE(
lunout,fmt) nint(ocemask)
185 masque(1:
iim,:)=1.-ocemask(:,:)
186 masque(iip1 ,:)=masque(1,:)
193 WRITE(
lunout,*)
' ************************ '
194 WRITE(
lunout,*)
' *** etat0phy_netcdf *** '
195 WRITE(
lunout,*)
' ************************ '
198 WRITE(
lunout,*)
' ************************ '
199 WRITE(
lunout,*)
' *** etat0dyn_netcdf *** '
200 WRITE(
lunout,*)
' ************************ '
206 WRITE(
lunout,*)
' ********************* '
207 WRITE(
lunout,*)
' *** Limit_netcdf *** '
208 WRITE(
lunout,*)
' ********************* '
214 WRITE(
lunout,*)
' *************************** '
215 WRITE(
lunout,*)
' *** grilles_gcm_netcdf *** '
216 WRITE(
lunout,*)
' *************************** '
integer, dimension(:), allocatable distrib_phys
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
!$Id mode_top_bound COMMON comconstr g
subroutine grilles_gcm_netcdf_sub(masque, phis)
!$Id mode_top_bound COMMON comconstr kappa
subroutine init_interface_dyn_phys
!$Id ysinus ok_gradsfile ok_limit
subroutine limit_netcdf(masque, phis, extrap)
!$Id calend INTEGER itaufin INTEGER itau_phy INTEGER day_ref REAL dt
subroutine abort_gcm(modname, message, ierr)
!$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
!$Id mode_top_bound COMMON comconstr && pi
!$Header!CDK comgeom COMMON comgeom aire
!$Header!CDK comgeom COMMON comgeom rlatu
!$Id ysinus ok_gradsfile hybrid COMMON logici iflag_phys
subroutine init_mod_hallo
subroutine init_const_mpi
!$Id mode_top_bound COMMON comconstr dtphys
!$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
!$Id ysinus ok_gradsfile ok_etat0
!$Id mode_top_bound COMMON comconstr rad
!$Id mode_top_bound COMMON comconstr cpp
integer, parameter is_lic
!FH On elimine toutes les clefs physiques dans la dynamique prt_level
!$Id mode_top_bound COMMON comconstr daysec
subroutine conf_gcm(tapedef, etatinit)
!$Header!CDK comgeom COMMON comgeom rlonu
!$Header!CDK comgeom COMMON comgeom rlatv
!$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
!$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
!$Id mode_top_bound COMMON comconstr dtvr
integer, save nsplit_phys
c c zjulian c cym CALL iim cym klev iim
subroutine, public etat0phys_netcdf(masque, phis)
integer, parameter is_sic
!$Header!CDK comgeom COMMON comgeom cv
subroutine, public etat0dyn_netcdf(masque, phis)
integer, parameter is_oce
!$Header!gestion des impressions de sorties et de débogage la sortie standard prt_level COMMON comprint lunout
!$Header!CDK comgeom COMMON comgeom rlonv