/[lmdze]/trunk/phylmd/Interface_surf/interfsur_lim.f
ViewVC logotype

Contents of /trunk/phylmd/Interface_surf/interfsur_lim.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 98 - (show annotations)
Tue May 13 17:23:16 2014 UTC (10 years, 1 month ago) by guez
File size: 2642 byte(s)
Split inter_barxy.f : one procedure per module, one module per
file. Grouped the files into a directory.

Split orbite.f.

Value of raz_date read from the namelist is taken into account
(resetting the step counter) even if annee_ref == anneeref and day_ref
== dayref. raz_date is no longer modified by gcm main unit. (Following
LMDZ.)

Removed argument klon of interfsur_lim. Renamed arguments lmt_alb,
lmt_rug to alb_new, z0_new (same name as corresponding actual
arguments in interfsurf_hq).

Removed argument klon of interfsurf_hq.

Removed arguments qs and d_qs of diagetpq. Were always
zero. Downgraded arguments d_qw, d_ql of diagetpq to local variables,
they were not used in physiq. Removed all computations for solid water
in diagetpq, was just zero.


Downgraded arguments fs_bound, fq_bound of diagphy to local variables,
they were not used in physiq. Encapsulated in a test on iprt all
computations in diagphy.

Removed parameter nbtr of module dimphy. Replaced it everywhere in the
program by nqmx - 2.

Removed parameter rnpb of procedure physiq. Kept the true case in
physiq and phytrac. Could not work with false case anyway.

Removed arguments klon, llm, airephy of qcheck. Removed argument ftsol
of initrrnpb, was not used.

1 module interfsur_lim_m
2
3 implicit none
4
5 contains
6
7 SUBROUTINE interfsur_lim(itime, dtime, jour, nisurf, knon, knindex, debut, &
8 alb_new, z0_new)
9
10 ! Cette routine sert d'interface entre le modèle atmosphérique et
11 ! un fichier de conditions aux limites.
12
13 ! L. Fairhead 02/2000
14
15 use abort_gcm_m, only: abort_gcm
16 USE dimphy, ONLY: klon
17 use netcdf, only: NF90_NOWRITE
18 use netcdf95, only: NF95_close, NF95_GET_VAR, NF95_INQ_VARID, NF95_OPEN
19
20 integer, intent(IN):: itime ! numero du pas de temps courant
21 real, intent(IN):: dtime ! pas de temps de la physique (en s)
22 integer, intent(IN):: jour ! jour a lire dans l'annee
23
24 integer, intent(IN):: nisurf
25 ! index de la surface à traiter (1 = sol continental)
26
27 integer, intent(IN):: knon ! nombre de points dans le domaine a traiter
28
29 integer, intent(in):: knindex(:) ! (klon)
30 ! index des points de la surface à traiter
31
32 logical, intent(IN):: debut ! premier appel à la physique (initialisation)
33 real, intent(out):: alb_new(:) ! (klon) albedo lu
34 real, intent(out):: z0_new(:) ! (klon) longueur de rugosité lue
35
36 ! Local:
37
38 integer, save:: lmt_pas ! frequence de lecture des conditions limites
39 ! (en pas de physique)
40
41 logical, save:: deja_lu_sur
42 ! jour à lire déjà lu pour une surface précédente
43
44 integer, save:: jour_lu_sur
45
46 ! Champs lus dans le fichier de conditions aux limites :
47 real, allocatable, save:: alb_lu(:), rug_lu(:)
48
49 integer ncid, varid
50
51 !------------------------------------------------------------
52
53 if (debut) then
54 lmt_pas = nint(86400./dtime * 1.0) ! pour une lecture une fois par jour
55 jour_lu_sur = jour - 1
56 allocate(alb_lu(klon))
57 allocate(rug_lu(klon))
58 endif
59
60 if (jour - jour_lu_sur /= 0) deja_lu_sur = .false.
61
62 ! Tester d'abord si c'est le moment de lire le fichier
63 if (mod(itime - 1, lmt_pas) == 0 .and. .not. deja_lu_sur) then
64 call NF95_OPEN('limit.nc', NF90_NOWRITE, ncid)
65
66 ! Lecture Albedo
67 call NF95_INQ_VARID(ncid, 'ALB', varid)
68 call NF95_GET_VAR(ncid, varid, alb_lu, start=(/1, jour/))
69
70 ! Lecture rugosité
71 call NF95_INQ_VARID(ncid, 'RUG', varid)
72 call NF95_GET_VAR(ncid, varid, rug_lu, start=(/1, jour/))
73
74 call NF95_CLOSE(ncid)
75 deja_lu_sur = .true.
76 jour_lu_sur = jour
77 endif
78
79 ! Recopie des variables dans les champs de sortie
80 alb_new(:knon) = alb_lu(knindex(:knon))
81 z0_new(:knon) = rug_lu(knindex(:knon))
82 alb_new(knon + 1:) = 999999.
83 z0_new(knon + 1:) = 999999.
84
85 END SUBROUTINE interfsur_lim
86
87 end module interfsur_lim_m

  ViewVC Help
Powered by ViewVC 1.1.21