16 REAL,
ALLOCATABLE,
DIMENSION(:,:),
SAVE,
PRIVATE ::
pctsrf
18 REAL,
ALLOCATABLE,
DIMENSION(:),
SAVE,
PRIVATE ::
rugos
20 REAL,
ALLOCATABLE,
DIMENSION(:),
SAVE,
PRIVATE ::
albedo
22 REAL,
ALLOCATABLE,
DIMENSION(:),
SAVE,
PRIVATE ::
sst
44 INTEGER,
INTENT(IN) :: itime
45 INTEGER,
INTENT(IN) :: jour
46 REAL ,
INTENT(IN) :: dtime
50 REAL,
DIMENSION(klon,nbsrf),
INTENT(OUT) :: pctsrf_new
51 LOGICAL,
INTENT(OUT) :: is_modified
60 pctsrf_new(:,:) =
pctsrf(:,:)
79 INTEGER,
INTENT(IN) :: itime
80 INTEGER,
INTENT(IN) :: jour
81 REAL ,
INTENT(IN) :: dtime
82 INTEGER,
INTENT(IN) :: knon
83 INTEGER,
DIMENSION(klon),
INTENT(IN) :: knindex
86 REAL,
DIMENSION(klon),
INTENT(OUT) :: rugos_out
87 REAL,
DIMENSION(klon),
INTENT(OUT) :: alb_out
92 LOGICAL :: is_modified
102 rugos_out(i) =
rugos(knindex(i))
103 alb_out(i) =
albedo(knindex(i))
116 INTEGER,
INTENT(IN) :: knon
117 INTEGER,
DIMENSION(klon),
INTENT(IN) :: knindex
118 REAL,
DIMENSION(klon),
INTENT(OUT) :: sst_out
123 sst_out(i) =
sst(knindex(i))
155 INTEGER,
INTENT(IN) :: itime
156 INTEGER,
INTENT(IN) :: jour
157 REAL ,
INTENT(IN) :: dtime
159 LOGICAL,
INTENT(OUT) :: is_modified
164 INTEGER,
SAVE :: lmt_pas
166 LOGICAL,
SAVE :: first_call=.
true.
168 INTEGER,
SAVE :: jour_lu = -1
172 INTEGER :: nid, nvarid
174 INTEGER,
DIMENSION(2) :: start, epais
175 REAL,
DIMENSION(klon_glo,nbsrf) :: pct_glo
176 REAL,
DIMENSION(klon_glo) :: sst_glo
177 REAL,
DIMENSION(klon_glo) :: rug_glo
178 REAL,
DIMENSION(klon_glo) :: alb_glo
179 CHARACTER(len=20) :: modname=
'limit_read_mod'
190 lmt_pas = nint(86400./dtime * 1.0)
195 IF (ierr /= 0)
CALL abort_physic(modname,
'PB in allocating pctsrf and sst',1)
200 IF (ierr /= 0)
CALL abort_physic(modname,
'PB in allocating rugos and albedo',1)
212 is_modified = .
false.
213 IF (mod(itime-1, lmt_pas) == 0 .OR. jour_lu /= jour )
THEN
217 IF (is_mpi_root)
THEN
219 ierr = nf90_open(
'limit.nc', nf90_nowrite, nid)
221 'Pb d''ouverture du fichier de conditions aux limites',1)
238 ierr = nf90_inq_varid(nid,
'FOCE', nvarid)
239 IF (ierr /= nf90_noerr)
CALL abort_physic(modname,
'Le champ <FOCE> est absent',1)
241 ierr = nf90_get_var(nid,nvarid,pct_glo(:,
is_oce),start,epais)
242 IF (ierr /= nf90_noerr)
CALL abort_physic(modname,
'Lecture echouee pour <FOCE>' ,1)
245 ierr = nf90_inq_varid(nid,
'FSIC', nvarid)
246 IF (ierr /= nf90_noerr)
CALL abort_physic(modname,
'Le champ <FSIC> est absent',1)
248 ierr = nf90_get_var(nid,nvarid,pct_glo(:,
is_sic),start,epais)
249 IF (ierr /= nf90_noerr)
CALL abort_physic(modname,
'Lecture echouee pour <FSIC>' ,1)
256 ierr = nf90_inq_varid(nid,
'FTER', nvarid)
257 IF (ierr /= nf90_noerr)
CALL abort_physic(modname,
'Le champ <FTER> est absent',1)
259 ierr = nf90_get_var(nid,nvarid,pct_glo(:,
is_ter),start,epais)
260 IF (ierr /= nf90_noerr)
CALL abort_physic(modname,
'Lecture echouee pour <FTER>',1)
263 ierr = nf90_inq_varid(nid,
'FLIC', nvarid)
264 IF (ierr /= nf90_noerr)
CALL abort_physic(modname,
'Le champ <FLIC> est absent',1)
266 ierr = nf90_get_var(nid,nvarid,pct_glo(:,
is_lic),start,epais)
267 IF (ierr /= nf90_noerr)
CALL abort_physic(modname,
'Lecture echouee pour <FLIC>',1)
278 ierr = nf90_inq_varid(nid,
'SST', nvarid)
279 IF (ierr /= nf90_noerr)
CALL abort_physic(modname,
'Le champ <SST> est absent',1)
281 ierr = nf90_get_var(nid,nvarid,sst_glo,start,epais)
282 IF (ierr /= nf90_noerr)
CALL abort_physic(modname,
'Lecture echouee pour <SST>',1)
294 ierr = nf90_inq_varid(nid,
'ALB', nvarid)
295 IF (ierr /= nf90_noerr)
CALL abort_physic(modname,
'Le champ <ALB> est absent',1)
297 ierr = nf90_get_var(nid,nvarid,alb_glo,start,epais)
298 IF (ierr /= nf90_noerr)
CALL abort_physic(modname,
'Lecture echouee pour <ALB>',1)
301 ierr = nf90_inq_varid(nid,
'RUG', nvarid)
302 IF (ierr /= nf90_noerr)
CALL abort_physic(modname,
'Le champ <RUG> est absent',1)
304 ierr = nf90_get_var(nid,nvarid,rug_glo,start,epais)
305 IF (ierr /= nf90_noerr)
CALL abort_physic(modname,
'Lecture echouee pour <RUG>',1)
313 ierr = nf90_close(nid)
314 IF (ierr /= nf90_noerr)
CALL abort_physic(modname,
'Pb when closing file', 1)
321 CALL scatter(sst_glo,
sst)
331 CALL scatter(alb_glo,
albedo)
332 CALL scatter(rug_glo,
rugos)
subroutine limit_read_frac(itime, dtime, jour, pctsrf_new, is_modified)
integer, parameter is_ter
logical, save read_continents
character(len=6), save version_ocean
!$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
subroutine limit_read_sst(knon, knindex, sst_out)
integer, parameter is_lic
subroutine limit_read_tot(itime, dtime, jour, is_modified)
!$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
real, dimension(:), allocatable, save, private rugos
character(len=6), save type_ocean
real, dimension(:,:), allocatable, save, private pctsrf
integer, parameter is_sic
subroutine abort_physic(modname, message, ierr)
integer, parameter is_oce
real, dimension(:), allocatable, save, private sst
subroutine limit_read_rug_alb(itime, dtime, jour, knon, knindex, rugos_out, alb_out)