36 USE ioipsl
, ONLY: flininfo, flinopen, flinget, flinclo
51 include
"dimensions.h"
59 REAL,
SAVE,
ALLOCATABLE ::
tsol(:)
91 REAL,
INTENT(INOUT) :: masque(:,:)
92 REAL,
INTENT(INOUT) :: phis (:,:)
95 CHARACTER(LEN=256) :: modname=
"etat0phys_netcdf", fmt
96 INTEGER :: i, j, l, ji, iml, jml
98 REAL :: phystep, dummy
99 REAL,
DIMENSION(SIZE(masque,1),SIZE(masque,2)) :: masque_tmp
100 REAL,
DIMENSION(klon) :: sn, rugmer, run_off_lic_0, fder
101 REAL,
DIMENSION(klon,nbsrf) :: qsolsrf, snsrf
102 REAL,
DIMENSION(klon,nsoilmx,nbsrf) :: tsoil
105 LOGICAL :: ok_journe, ok_mensuel, ok_instan, ok_hf, ok_LES, callstats
106 REAL :: solarlong0, seuil_inversion, fact_cldcon, facttemps
107 LOGICAL :: ok_newmicro
108 INTEGER :: iflag_radia, iflag_cldcon, iflag_ratqs
109 REAL :: ratqsbas, ratqshaut, tau_ratqs
110 LOGICAL :: ok_ade, ok_aie, ok_cdnc, aerosol_couple
111 INTEGER :: flag_aerosol
112 LOGICAL :: flag_aerosol_strat
114 REAL :: bl95_b0, bl95_b1
115 INTEGER :: read_climoz
119 iml=
assert_eq(
SIZE(masque,1),
SIZE(phis,1),trim(modname)//
" iml")
120 jml=
assert_eq(
SIZE(masque,2),
SIZE(phis,2),trim(modname)//
" jml")
124 CALL conf_phys( ok_journe, ok_mensuel, ok_instan, ok_hf, ok_les, &
126 solarlong0,seuil_inversion, &
127 fact_cldcon, facttemps,ok_newmicro,iflag_radia, &
129 iflag_ratqs,ratqsbas,ratqshaut,tau_ratqs, &
130 ok_ade, ok_aie, ok_cdnc, aerosol_couple, &
131 flag_aerosol, flag_aerosol_strat, new_aod, &
142 read_mask=any(masque/=-99999.); masque_tmp=masque
144 WRITE(fmt,
"(i4,'i1)')")iml ; fmt=
'('//adjustl(fmt)
145 IF(.NOT.read_mask)
THEN
148 WRITE(
lunout,*)
'BUILT MASK :'
149 WRITE(
lunout,fmt) nint(masque)
151 WHERE( masque(:,:)<
epsfra) masque(:,:)=0.
152 WHERE(1.-masque(:,:)<
epsfra) masque(:,:)=1.
182 DO i=1,
nbsrf; snsrf(:,i) = sn;
END DO
188 DO i=1,
nbsrf; qsolsrf(:,i)=150.;
END DO
189 DO i=1,
nbsrf;
DO j=1,nsoilmx; tsoil(:,j,i) =
tsol; end do;
END DO
256 REAL,
INTENT(IN) :: lon_in(:), lat_in(:)
257 REAL,
INTENT(INOUT) :: phis(:,:), masque(:,:)
260 CHARACTER(LEN=256) :: modname
261 INTEGER :: fid, llm_tmp,ttm_tmp, iml,jml, iml_rel,jml_rel, itau(1)
262 REAL :: lev(1), date, dt
263 REAL,
ALLOCATABLE :: lon_rad(:), lon_ini(:), lon_rel(:,:), relief_hi(:,:)
264 REAL,
ALLOCATABLE :: lat_rad(:), lat_ini(:), lat_rel(:,:), tmp_var (:,:)
265 REAL,
ALLOCATABLE :: zmea0(:,:), zstd0(:,:), zsig0(:,:)
266 REAL,
ALLOCATABLE :: zgam0(:,:), zthe0(:,:), zpic0(:,:), zval0(:,:)
268 modname=
"start_init_orog"
269 iml=
assert_eq(
SIZE(lon_in),
SIZE(phis,1),
SIZE(masque,1),trim(modname)//
" iml")
270 jml=
assert_eq(
SIZE(lat_in),
SIZE(phis,2),
SIZE(masque,2),trim(modname)//
" jml")
273 CALL flininfo(
orofname, iml_rel, jml_rel, llm_tmp, ttm_tmp, fid)
275 ALLOCATE(lat_rel(iml_rel,jml_rel),lon_rel(iml_rel,jml_rel))
276 CALL flinopen(
orofname, .
false., iml_rel, jml_rel, llm_tmp, lon_rel, lat_rel,&
277 lev, ttm_tmp, itau, date, dt, fid)
278 ALLOCATE(relief_hi(iml_rel,jml_rel))
279 CALL flinget(fid,
orogvar, iml_rel, jml_rel, llm_tmp, ttm_tmp, 1,1, relief_hi)
283 ALLOCATE(lon_ini(iml_rel),lat_ini(jml_rel))
284 lon_ini(:)=lon_rel(:,1);
IF(maxval(lon_rel)>
pi) lon_ini=lon_ini*
deg2rad
285 lat_ini(:)=lat_rel(1,:);
IF(maxval(lat_rel)>
pi) lat_ini=lat_ini*
deg2rad
288 ALLOCATE(lon_rad(iml_rel),lat_rad(jml_rel))
290 DEALLOCATE(lon_ini,lat_ini)
294 WRITE(
lunout,*)
'*** Compute parameters needed for gravity wave drag code ***'
297 ALLOCATE(zmea0(iml,jml),zstd0(iml,jml))
298 ALLOCATE(zsig0(iml,jml),zgam0(iml,jml))
299 ALLOCATE(zthe0(iml,jml))
300 ALLOCATE(zpic0(iml,jml),zval0(iml,jml))
303 CALL grid_noro(lon_rad,lat_rad,relief_hi,lon_in,lat_in,phis,zmea0,zstd0, &
304 zsig0,zgam0,zthe0,zpic0,zval0,masque)
306 phis(iml,:) = phis(1,:)
307 DEALLOCATE(relief_hi,lon_rad,lat_rad)
334 REAL,
INTENT(IN) :: lon_in(:), lat_in(:)
335 REAL,
INTENT(IN) :: phis(:,:)
338 CHARACTER(LEN=256) :: modname
340 INTEGER :: iml, jml, jml2, itau(1)
341 REAL,
ALLOCATABLE :: lon_rad(:), lon_ini(:), var_ana(:,:)
342 REAL,
ALLOCATABLE :: lat_rad(:), lat_ini(:)
343 REAL,
ALLOCATABLE :: ts(:,:), qs(:,:)
345 modname=
"start_init_phys"
346 iml=
assert_eq(
SIZE(lon_in),
SIZE(phis,1),trim(modname)//
" iml")
347 jml=
SIZE(phis,2); jml2=
SIZE(lat_in)
349 WRITE(
lunout,*)
'Opening the surface analysis'
367 DEALLOCATE(var_ana,lon_rad,lat_rad,lon_ini,lat_ini)
385 CHARACTER(LEN=*),
INTENT(IN) :: title
386 REAL,
ALLOCATABLE,
INTENT(INOUT) :: field(:,:)
395 IF(
ALLOCATED(field))
RETURN
396 ALLOCATE(field(iml,jml)); field(:,:)=0.
398 CALL conf_dat2d(title, lon_ini, lat_ini, lon_rad, lat_rad, var_ana, .
true.)
400 lon_in, lat_in, field)
420 CHARACTER(LEN=*),
INTENT(IN) :: nam
421 LOGICAL,
INTENT(IN) :: ibeg
422 REAL,
INTENT(IN) :: lon(:), lat(:)
423 REAL,
INTENT(IN) :: vari(:,:)
424 REAL,
INTENT(IN) :: lon2(:), lat2(:)
425 REAL,
INTENT(OUT) :: varo(:,:)
428 CHARACTER(LEN=256) :: modname
429 INTEGER :: ii, jj, i1, j1, j2
430 REAL,
ALLOCATABLE :: vtmp(:,:)
432 modname=
"interp_startvar"
433 ii=
assert_eq(
SIZE(lon),
SIZE(vari,1),trim(modname)//
" ii")
434 jj=
assert_eq(
SIZE(lat),
SIZE(vari,2),trim(modname)//
" jj")
435 i1=
assert_eq(
SIZE(lon2),
SIZE(varo,1),trim(modname)//
" i1")
436 j1=
SIZE(varo,2); j2=
SIZE(lat2)
437 ALLOCATE(vtmp(i1-1,j1))
439 WRITE(
lunout,*)
"--------------------------------------------------------"
440 WRITE(
lunout,*)
"$$$ Interpolation barycentrique pour "//trim(nam)//
" $$$"
441 WRITE(
lunout,*)
"--------------------------------------------------------"
443 CALL inter_barxy(lon, lat(:jj-1), vari, lon2(:i1-1), lat2, vtmp)
real, dimension(:,:), allocatable, save q_ancien
real, dimension(:,:), allocatable, save w01
real, dimension(:,:), allocatable, save clwcon
real, dimension(:), allocatable, save levphys_ini
real, dimension(:), allocatable, save tsol
integer, parameter is_ter
character(len=256), parameter orofname
real, dimension(:), allocatable, save f0
real, dimension(:), allocatable, save zval
real, dimension(:), allocatable, save zsig
subroutine, public grid_noro(xd, yd, zd, x, y, zphi, zmea, zstd, zsig, zgam, zthe, zpic, zval, mask)
real, dimension(:), allocatable, save snow_fall
subroutine, public regr_lat_time_climoz(read_climoz)
real, dimension(:,:,:), allocatable, save falb_dir
real, dimension(:,:), allocatable, save wake_deltaq
subroutine conf_phys(ok_journe, ok_mensuel, ok_instan, ok_hf, ok_LES, callstats, solarlong0, seuil_inversion, fact_cldcon, facttemps, ok_newmicro, iflag_radia, iflag_cld_th, iflag_ratqs, ratqsbas, ratqshaut, tau_ratqs, ok_ade, ok_aie, ok_cdnc, aerosol_couple, flag_aerosol, flag_aerosol_strat, new_aod, bl95_b0, bl95_b1, read_climoz, alp_offset)
real, dimension(:,:), allocatable, save lat_phys
real, dimension(:), allocatable, save rain_fall
real, dimension(:,:), allocatable, save sig1
real, dimension(:,:), allocatable, save t_ancien
subroutine gr_int_dyn(champin, champdyn, iim, jp1)
subroutine fonte_neige_init(restart_runoff)
character(len=256), parameter tsrfvar
subroutine, public conf_dat2d(title, xd, yd, xf, yf, champd, interbar)
real, dimension(:), allocatable, save zmea
subroutine phyredem(fichnom)
real, dimension(:,:), allocatable, save pctsrf
real, dimension(:), allocatable, save radsol
real, dimension(:,:), allocatable, save entr_therm
!$Id mode_top_bound COMMON comconstr && pi
!$Header!CDK comgeom COMMON comgeom rlatu
real, dimension(:), allocatable, save qsol
subroutine start_init_phys(lon_in, lat_in, phis)
real, dimension(:,:,:), allocatable, save pbl_tke
real, dimension(:), allocatable, save sollw
real, dimension(:,:), allocatable, save rnebcon
!$Header!c include clesph0 h c COMMON clesph0 nbapp_rad
subroutine start_init_orog(lon_in, lat_in, phis, masque)
real, dimension(:), allocatable, save wake_s
real, dimension(:), allocatable, save wake_cstar
!$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
real, dimension(:,:), allocatable, save z0m
real, dimension(:), allocatable, save rugoro
integer, parameter is_lic
real, dimension(:), allocatable, save zpic
subroutine interp_startvar(nam, ibeg, lon, lat, vari, lon2, lat2, varo)
real, dimension(:), allocatable, save rlon
!$Id ok_orolf LOGICAL ok_limitvrai LOGICAL ok_all_xml INTEGER iflag_ener_conserv REAL co2_ppm
real, dimension(:,:), allocatable, save fm_therm
real, dimension(:), allocatable, save solsw
real, dimension(:), allocatable, save zgam
!FH On elimine toutes les clefs physiques dans la dynamique prt_level
character(len=256), parameter psrfvar
character(len=256), parameter phyfname
real, dimension(:), allocatable, save wake_fip
!$Header!CDK comgeom COMMON comgeom rlonu
!$Header!CDK comgeom COMMON comgeom rlatv
subroutine, public inter_barxy(dlonid, dlatid, champ, rlonimod, rlatimod, champint)
!$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
subroutine gr_dyn_fi(nfield, im, jm, ngrid, pdyn, pfi)
!$Id ok_orolf LOGICAL ok_limitvrai LOGICAL ok_all_xml INTEGER iflag_ener_conserv REAL co2_ppm0
subroutine get_var_phys(title, field)
real, dimension(:), allocatable, save rlat
!$Id mode_top_bound COMMON comconstr dtvr
character(len=256), parameter orogvar
real, dimension(:), allocatable, save wake_pe
character(len=256), parameter qsolvar
real, dimension(:,:), allocatable, save agesno
subroutine phys_state_var_init()
real, dimension(:,:), allocatable, save ratqs
real, dimension(:), allocatable, save zstd
subroutine pbl_surface_init(fder_rst, snow_rst, qsurf_rst, ftsoil_rst)
subroutine, public etat0phys_netcdf(masque, phis)
integer, parameter is_sic
real, dimension(:,:), allocatable, save lon_phys
real, dimension(:,:), allocatable, save fevap
real, dimension(:), allocatable, save zmax0
nrlmd
real, dimension(:,:), allocatable, save z0h
real, dimension(:,:), allocatable, save ftsol
subroutine, public start_init_subsurf(known_mask)
real, dimension(:), allocatable, save zthe
integer, parameter is_oce
real, dimension(:,:), allocatable, save detr_therm
!$Header!gestion des impressions de sorties et de débogage la sortie standard prt_level COMMON comprint lunout
!$Header!CDK comgeom COMMON comgeom rlonv
real, dimension(:,:), allocatable, save wake_deltat