/[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 134 - (show annotations)
Wed Apr 29 15:47:56 2015 UTC (9 years, 1 month ago) by guez
File size: 2661 byte(s)
Sources inside, compilation outside.
1 module interfsur_lim_m
2
3 implicit none
4
5 contains
6
7 SUBROUTINE interfsur_lim(itime, dtime, jour, nisurf, 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 ! Laurent FAIRHEAD, February 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
28 integer, intent(in):: knindex(:) ! (knon)
29 ! index des points de la surface à traiter
30
31 logical, intent(IN):: debut ! premier appel à la physique (initialisation)
32 real, intent(out):: alb_new(:) ! (klon) albedo lu
33 real, intent(out):: z0_new(:) ! (klon) longueur de rugosité lue
34
35 ! Local:
36
37 integer knon ! nombre de points dans le domaine a traiter
38
39 integer, save:: lmt_pas ! frequence de lecture des conditions limites
40 ! (en pas de physique)
41
42 logical, save:: deja_lu_sur
43 ! jour à lire déjà lu pour une surface précédente
44
45 integer, save:: jour_lu_sur
46
47 ! Champs lus dans le fichier de conditions aux limites :
48 real, allocatable, save:: alb_lu(:), rug_lu(:)
49
50 integer ncid, varid
51
52 !------------------------------------------------------------
53
54 knon = size(knindex)
55
56 if (debut) then
57 lmt_pas = nint(86400./dtime * 1.0) ! pour une lecture une fois par jour
58 jour_lu_sur = jour - 1
59 allocate(alb_lu(klon))
60 allocate(rug_lu(klon))
61 endif
62
63 if (jour - jour_lu_sur /= 0) deja_lu_sur = .false.
64
65 ! Tester d'abord si c'est le moment de lire le fichier
66 if (mod(itime - 1, lmt_pas) == 0 .and. .not. deja_lu_sur) then
67 call NF95_OPEN('limit.nc', NF90_NOWRITE, ncid)
68
69 ! Lecture Albedo
70 call NF95_INQ_VARID(ncid, 'ALB', varid)
71 call NF95_GET_VAR(ncid, varid, alb_lu, start=(/1, jour/))
72
73 ! Lecture rugosité
74 call NF95_INQ_VARID(ncid, 'RUG', varid)
75 call NF95_GET_VAR(ncid, varid, rug_lu, start=(/1, jour/))
76
77 call NF95_CLOSE(ncid)
78 deja_lu_sur = .true.
79 jour_lu_sur = jour
80 endif
81
82 ! Recopie des variables dans les champs de sortie
83 alb_new(:knon) = alb_lu(knindex(:knon))
84 z0_new(:knon) = rug_lu(knindex(:knon))
85 alb_new(knon + 1:) = 999999.
86 z0_new(knon + 1:) = 999999.
87
88 END SUBROUTINE interfsur_lim
89
90 end module interfsur_lim_m

  ViewVC Help
Powered by ViewVC 1.1.21