/[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

revision 282 by guez, Fri Jul 20 16:46:48 2018 UTC revision 312 by guez, Fri Dec 7 14:17:11 2018 UTC
# Line 4  module interfsur_lim_m Line 4  module interfsur_lim_m
4    
5  contains  contains
6    
7    SUBROUTINE interfsur_lim(dtime, jour, knindex, debut, albedo, z0_new)    SUBROUTINE interfsur_lim(jour, knindex, 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    
14        use conf_gcm_m, only: lmt_pas
15      USE dimphy, ONLY: klon      USE dimphy, ONLY: klon
16      use netcdf, only: NF90_NOWRITE      use netcdf, only: NF90_NOWRITE
17      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
18      use time_phylmdz, only: itap      use time_phylmdz, only: itap
19    
     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    
22      integer, intent(in):: knindex(:) ! (knon)      integer, intent(in):: knindex(:) ! (knon)
23      ! index des points de la surface \`a traiter      ! index des points de la surface \`a traiter
24    
     logical, intent(IN):: debut ! premier appel \`a la physique (initialisation)  
25      real, intent(out):: albedo(:) ! (knon) albedo lu      real, intent(out):: albedo(:) ! (knon) albedo lu
26      real, intent(out):: z0_new(:) ! (knon) longueur de rugosit\'e lue      real, intent(out):: z0_new(:) ! (knon) longueur de rugosit\'e lue
27    
28      ! Local:      ! Local:
29    
30      integer knon ! nombre de points dans le domaine a traiter      integer:: jour_lu_sur = - 1
   
     integer, save:: lmt_pas ! frequence de lecture des conditions limites  
     ! (en pas de physique)  
   
     logical, save:: deja_lu_sur  
     ! jour \`a lire d\'ej\`a lu pour une surface pr\'ec\'edente  
   
     integer, save:: jour_lu_sur  
31    
32      ! Champs lus dans le fichier de conditions aux limites :      ! Champs lus dans le fichier de conditions aux limites :
33      real, allocatable, save:: alb_lu(:), rug_lu(:)      real, save:: alb_lu(klon), rug_lu(klon)
34    
35      integer ncid, varid      integer ncid, varid
36    
37      !------------------------------------------------------------      !------------------------------------------------------------
38    
     knon = size(knindex)  
   
     if (debut) then  
        lmt_pas = nint(86400. / dtime) ! pour une lecture une fois par jour  
        jour_lu_sur = jour - 1  
        allocate(alb_lu(klon))  
        allocate(rug_lu(klon))  
     endif  
   
     if (jour - jour_lu_sur /= 0) deja_lu_sur = .false.  
   
39      ! Tester d'abord si c'est le moment de lire le fichier      ! Tester d'abord si c'est le moment de lire le fichier
40      if (mod(itap - 1, lmt_pas) == 0 .and. .not. deja_lu_sur) then      if (mod(itap - 1, lmt_pas) == 0 .and. jour /= jour_lu_sur) then
41         call NF95_OPEN('limit.nc', NF90_NOWRITE, ncid)         call NF95_OPEN('limit.nc', NF90_NOWRITE, ncid)
42    
43         ! Lecture Albedo         ! Lecture Albedo
# Line 69  contains Line 49  contains
49         call NF95_GET_VAR(ncid, varid, rug_lu, start=(/1, jour/))         call NF95_GET_VAR(ncid, varid, rug_lu, start=(/1, jour/))
50    
51         call NF95_CLOSE(ncid)         call NF95_CLOSE(ncid)
        deja_lu_sur = .true.  
52         jour_lu_sur = jour         jour_lu_sur = jour
53      endif      endif
54    

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

  ViewVC Help
Powered by ViewVC 1.1.21