/[lmdze]/trunk/phylmd/Interface_surf/interfoce_lim.f
ViewVC logotype

Diff of /trunk/phylmd/Interface_surf/interfoce_lim.f

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

revision 191 by guez, Mon May 9 19:56:28 2016 UTC revision 202 by guez, Wed Jun 8 12:23:41 2016 UTC
# Line 4  module interfoce_lim_m Line 4  module interfoce_lim_m
4    
5  contains  contains
6    
7    SUBROUTINE interfoce_lim(dtime, jour, knindex, debut, lmt_sst, pctsrf_new)    SUBROUTINE interfoce_lim(jour, pctsrf_new_oce, pctsrf_new_sic)
8    
9      ! lecture conditions limites      ! lecture conditions limites
10      ! Cette routine sert d'interface entre le modèle atmosphérique et      ! Cette routine sert d'interface entre le modèle atmosphérique et
# Line 12  contains Line 12  contains
12    
13      ! Laurent FAIRHEAD, February 2000      ! Laurent FAIRHEAD, February 2000
14    
     USE dimphy, ONLY: klon  
     USE indicesol, ONLY: is_lic, is_oce, is_sic, is_ter, nbsrf  
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
     use nr_util, only: assert  
     use time_phylmdz, only: itap  
17    
     real, intent(IN):: dtime ! pas de temps de la physique (en s)  
18      integer, intent(IN):: jour ! jour a lire dans l'annee      integer, intent(IN):: jour ! jour a lire dans l'annee
19    
20      integer, intent(in):: knindex(:) ! (knon)      real, intent(out):: pctsrf_new_oce(:), pctsrf_new_sic(:) ! (klon)
     ! index des points de la surface a traiter  
   
     logical, intent(IN):: debut ! 1er appel a la physique (initialisation)  
   
     real, intent(out):: lmt_sst(:) ! (knon)  
     ! SST lues dans le fichier de conditions aux limites  
   
     real, intent(out):: pctsrf_new(:, :) ! (klon, nbsrf)  
21      ! sous-maille fractionnelle      ! sous-maille fractionnelle
22    
23      ! Local:      ! Local:
   
     INTEGER, save:: lmt_pas ! frequence de lecture des conditions limites  
     ! (en pas de physique)  
   
     logical, save:: deja_lu  
     ! pour indiquer que le jour à lire a déjà été lu pour une surface  
     ! précédente  
   
     integer, save:: jour_lu  
   
     ! Champs lus dans le fichier de conditions aux limites :  
     real, allocatable, save:: sst_lu(:)  
     real, allocatable, save:: pct_tmp(:, :)  
   
24      integer ncid, varid ! pour NetCDF      integer ncid, varid ! pour NetCDF
25    
26      ! --------------------------------------------------      ! --------------------------------------------------
27    
28      call assert(size(knindex) == size(lmt_sst), "interfoce_lim knon")      call NF95_OPEN ('limit.nc', NF90_NOWRITE, ncid)
29    
30        ! Fraction "ocean"
31        call NF95_INQ_VARID(ncid, 'FOCE', varid)
32        call NF95_GET_VAR(ncid, varid, pctsrf_new_oce, start = (/1, jour/))
33    
34        ! Fraction "glace de mer"
35        call NF95_INQ_VARID(ncid, 'FSIC', varid)
36        call NF95_GET_VAR(ncid, varid, pctsrf_new_sic, start = (/1, jour/))
37    
38      if (debut .and. .not. allocated(sst_lu)) then      call NF95_CLOSE(ncid)
        lmt_pas = nint(86400. / dtime) ! pour une lecture une fois par jour  
        jour_lu = jour - 1  
        allocate(sst_lu(klon))  
        allocate(pct_tmp(klon, nbsrf))  
     endif  
   
     if ((jour - jour_lu) /= 0) deja_lu = .false.  
   
     ! Tester d'abord si c'est le moment de lire le fichier  
     if (mod(itap - 1, lmt_pas) == 0 .and. .not. deja_lu) then  
        call NF95_OPEN ('limit.nc', NF90_NOWRITE, ncid)  
   
        ! Fraction "ocean"  
        call NF95_INQ_VARID(ncid, 'FOCE', varid)  
        call NF95_GET_VAR(ncid, varid, pct_tmp(:, is_oce), start = (/1, jour/))  
   
        ! Fraction "glace de mer"  
        call NF95_INQ_VARID(ncid, 'FSIC', varid)  
        call NF95_GET_VAR(ncid, varid, pct_tmp(:, is_sic), start = (/1, jour/))  
   
        ! Fraction "terre"  
        call NF95_INQ_VARID(ncid, 'FTER', varid)  
        call NF95_GET_VAR(ncid, varid, pct_tmp(:, is_ter), start = (/1, jour/))  
   
        ! Fraction "glacier terre"  
        call NF95_INQ_VARID(ncid, 'FLIC', varid)  
        call NF95_GET_VAR(ncid, varid, pct_tmp(:, is_lic), start = (/1, jour/))  
   
        call NF95_INQ_VARID(ncid, 'SST', varid)  
        call NF95_GET_VAR(ncid, varid, sst_lu, start = (/1, jour/))  
   
        call NF95_CLOSE(ncid)  
        deja_lu = .true.  
        jour_lu = jour  
     endif  
   
     ! Recopie des variables dans les champs de sortie  
     lmt_sst = sst_lu(knindex)  
     pctsrf_new(:, is_oce) = pct_tmp(:, is_oce)  
     pctsrf_new(:, is_sic) = pct_tmp(:, is_sic)  
39    
40    END SUBROUTINE interfoce_lim    END SUBROUTINE interfoce_lim
41    

Legend:
Removed from v.191  
changed lines
  Added in v.202

  ViewVC Help
Powered by ViewVC 1.1.21