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

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

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/Sources/phylmd/Interface_surf/interfsur_lim.f revision 150 by guez, Thu Jun 18 13:49:26 2015 UTC trunk/phylmd/Interface_surf/interfsur_lim.f revision 282 by guez, Fri Jul 20 16:46:48 2018 UTC
# Line 4  module interfsur_lim_m Line 4  module interfsur_lim_m
4    
5  contains  contains
6    
7    SUBROUTINE interfsur_lim(itime, dtime, jour, knindex, debut, alb_new, z0_new)    SUBROUTINE interfsur_lim(dtime, jour, knindex, debut, albedo, z0_new)
8    
9      ! Cette routine sert d'interface entre le mod\`ele atmosph\'erique et      ! Cette routine sert d'interface entre le mod\`ele atmosph\'erique et
10      ! un fichier de conditions aux limites.      ! un fichier de conditions aux limites.
11    
12      ! Laurent FAIRHEAD, February 2000      ! Laurent FAIRHEAD, February 2000
13    
     use abort_gcm_m, only: abort_gcm  
14      USE dimphy, ONLY: klon      USE dimphy, ONLY: klon
15      use netcdf, only: NF90_NOWRITE      use netcdf, only: NF90_NOWRITE
16      use netcdf95, only: NF95_close, NF95_GET_VAR, NF95_INQ_VARID, NF95_OPEN      use netcdf95, only: NF95_close, NF95_GET_VAR, NF95_INQ_VARID, NF95_OPEN
17        use time_phylmdz, only: itap
18    
     integer, intent(IN):: itime ! numero du pas de temps courant  
19      real, intent(IN):: dtime ! pas de temps de la physique (en s)      real, intent(IN):: dtime ! pas de temps de la physique (en s)
20      integer, intent(IN):: jour ! jour a lire dans l'annee      integer, intent(IN):: jour ! jour a lire dans l'annee
21    
# Line 24  contains Line 23  contains
23      ! index des points de la surface \`a traiter      ! index des points de la surface \`a traiter
24    
25      logical, intent(IN):: debut ! premier appel \`a la physique (initialisation)      logical, intent(IN):: debut ! premier appel \`a la physique (initialisation)
26      real, intent(out):: alb_new(:) ! (klon) albedo lu      real, intent(out):: albedo(:) ! (knon) albedo lu
27      real, intent(out):: z0_new(:) ! (klon) longueur de rugosit\'e lue      real, intent(out):: z0_new(:) ! (knon) longueur de rugosit\'e lue
28    
29      ! Local:      ! Local:
30    
# Line 49  contains Line 48  contains
48      knon = size(knindex)      knon = size(knindex)
49    
50      if (debut) then      if (debut) then
51         lmt_pas = nint(86400./dtime * 1.0) ! pour une lecture une fois par jour         lmt_pas = nint(86400. / dtime) ! pour une lecture une fois par jour
52         jour_lu_sur = jour - 1         jour_lu_sur = jour - 1
53         allocate(alb_lu(klon))         allocate(alb_lu(klon))
54         allocate(rug_lu(klon))         allocate(rug_lu(klon))
# Line 58  contains Line 57  contains
57      if (jour - jour_lu_sur /= 0) deja_lu_sur = .false.      if (jour - jour_lu_sur /= 0) deja_lu_sur = .false.
58    
59      ! Tester d'abord si c'est le moment de lire le fichier      ! 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      if (mod(itap - 1, lmt_pas) == 0 .and. .not. deja_lu_sur) then
61         call NF95_OPEN('limit.nc', NF90_NOWRITE, ncid)         call NF95_OPEN('limit.nc', NF90_NOWRITE, ncid)
62    
63         ! Lecture Albedo         ! Lecture Albedo
# Line 75  contains Line 74  contains
74      endif      endif
75    
76      ! Recopie des variables dans les champs de sortie      ! Recopie des variables dans les champs de sortie
77      alb_new(:knon) = alb_lu(knindex(:knon))      albedo = alb_lu(knindex)
78      z0_new(:knon) = rug_lu(knindex(:knon))      z0_new = rug_lu(knindex)
     alb_new(knon + 1:) = 999999.  
     z0_new(knon + 1:) = 999999.  
79    
80    END SUBROUTINE interfsur_lim    END SUBROUTINE interfsur_lim
81    

Legend:
Removed from v.150  
changed lines
  Added in v.282

  ViewVC Help
Powered by ViewVC 1.1.21