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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 328 - (show annotations)
Thu Jun 13 14:40:06 2019 UTC (4 years, 11 months ago) by guez
File size: 1696 byte(s)
Change all `.f` suffixes to `.f90`. (The opposite was done in revision
82.)  Because of change of philosopy in GNUmakefile: we already had a
rewritten rule for `.f`, so it does not make the makefile longer to
replace it by a rule for `.f90`. And it spares us options of
makedepf90 and of the compiler. Also we prepare the way for a simpler
`CMakeLists.txt`.

1 module interfsur_lim_m
2
3 implicit none
4
5 contains
6
7 SUBROUTINE interfsur_lim(jour, knindex, 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 conf_gcm_m, only: lmt_pas
15 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 use time_phylmdz, only: itap
19
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 real, intent(out):: albedo(:) ! (knon) albedo lu
26 real, intent(out):: z0_new(:) ! (knon) longueur de rugosit\'e lue
27
28 ! Local:
29
30 integer:: jour_lu_sur = - 1
31
32 ! Champs lus dans le fichier de conditions aux limites :
33 real, save:: alb_lu(klon), rug_lu(klon)
34
35 integer ncid, varid
36
37 !------------------------------------------------------------
38
39 ! Tester d'abord si c'est le moment de lire le fichier
40 if (mod(itap - 1, lmt_pas) == 0 .and. jour /= jour_lu_sur) then
41 call NF95_OPEN('limit.nc', NF90_NOWRITE, ncid)
42
43 ! Lecture Albedo
44 call NF95_INQ_VARID(ncid, 'ALB', varid)
45 call NF95_GET_VAR(ncid, varid, alb_lu, start=(/1, jour/))
46
47 ! Lecture rugosit\'e
48 call NF95_INQ_VARID(ncid, 'RUG', varid)
49 call NF95_GET_VAR(ncid, varid, rug_lu, start=(/1, jour/))
50
51 call NF95_CLOSE(ncid)
52 jour_lu_sur = jour
53 endif
54
55 ! Recopie des variables dans les champs de sortie
56 albedo = alb_lu(knindex)
57 z0_new = rug_lu(knindex)
58
59 END SUBROUTINE interfsur_lim
60
61 end module interfsur_lim_m

  ViewVC Help
Powered by ViewVC 1.1.21