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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 150 - (hide annotations)
Thu Jun 18 13:49:26 2015 UTC (9 years ago) by guez
File size: 2573 byte(s)
Removed unused arguments of groupe, cv3_undilute2, cv_undilute2,
interfsur_lim, drag_noro, orodrag, gwprofil

Chickened out of revision 148: back to double precision in
invert_zoom_x (and overloaded rtsafe).

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

  ViewVC Help
Powered by ViewVC 1.1.21