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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 178 - (show annotations)
Fri Mar 11 18:47:26 2016 UTC (8 years, 3 months ago) by guez
File size: 2479 byte(s)
Moved variables date0, deltat, datasz_max, ncvar_ids, point, buff_pos,
buffer, regular from module histcom_var to modules where they are
defined.

Removed procedure ioipslmpp, useless for a sequential program.

Added argument datasz_max to histwrite_real (to avoid circular
dependency with histwrite).

Removed useless variables and computations everywhere.

Changed real litteral constants from default kind to double precision
in lwb, lwu, lwvn, sw1s, swtt, swtt1, swu.

Removed unused arguments: paer of sw, sw1s, sw2s, swclr; pcldsw of
sw1s, sw2s; pdsig, prayl of swr; co2_ppm of clmain, clqh; tsol of
transp_lay; nsrf of screenp; kcrit and kknu of gwstress; pstd of
orosetup.

Added output of relative humidity.

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

  ViewVC Help
Powered by ViewVC 1.1.21