source: LMDZ6/trunk/libf/phylmd/condsurf.f90 @ 5308

Last change on this file since 5308 was 5282, checked in by abarral, 4 days ago

Turn iniprint.h clesphys.h into modules
Remove unused description.h

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 3.3 KB
RevLine 
[1992]1! $Header$
[644]2
[1992]3SUBROUTINE condsurf(jour, jourvrai, lmt_bils)
[5282]4  USE clesphys_mod_h
[1992]5  USE dimphy
6  USE mod_grid_phy_lmdz
7  USE mod_phys_lmdz_para
8  USE indice_sol_mod
[2344]9  USE time_phylmdz_mod, ONLY: annee_ref
[5270]10  USE netcdf, ONLY: nf90_get_var,nf90_open,nf90_inq_varid,nf90_noerr,nf90_close,nf90_nowrite
[1992]11  IMPLICIT NONE
12
13  ! I. Musat 05.2005
14
15  ! Lire chaque jour le bilan de chaleur au sol issu
16  ! d'un run atmospherique afin de l'utiliser dans
17  ! dans un run "slab" ocean
18  ! -----------------------------------------
19  ! jour     : input  , numero du jour a lire
20  ! jourvrai : input  , vrai jour de la simulation
21
22  ! lmt_bils: bilan chaleur au sol (a utiliser pour "slab-ocean")
23  INTEGER nid, nvarid
24  INTEGER debut(2)
25  INTEGER epais(2)
26
27
28  INTEGER nannemax
29  PARAMETER (nannemax=60)
30
31  INTEGER jour, jourvrai
32  REAL lmt_bils(klon) !bilan chaleur au sol
33
34  ! Variables locales:
35  INTEGER ig, i, kt, ierr
36  LOGICAL ok
37  INTEGER anneelim, anneemax
38  CHARACTER *20 fich
39
40  REAL :: lmt_bils_glo(klon_glo)
41
42  ! c
43  ! c   .....................................................................
44  ! c
45  ! c    Pour lire le fichier limit correspondant vraiment  a l'annee de la
46  ! c     simulation en cours , il suffit de mettre  ok_limitvrai = .TRUE.
47  ! c
48  ! c
49  ! ......................................................................
50
51
52
53  IF (jour<0 .OR. jour>(360-1)) THEN
54    PRINT *, 'Le jour demande n est pas correct: ', jour
[2311]55    CALL abort_physic('condsurf', '', 1)
[1992]56  END IF
57
58  anneelim = annee_ref
59  anneemax = annee_ref + nannemax
60
61
62  IF (ok_limitvrai) THEN
63    DO kt = 1, nannemax
64      IF (jourvrai<=(kt-1)*360+359) THEN
65        WRITE (fich, '("limit",i4,".nc")') anneelim
66        ! PRINT *,' Fichier  Limite ',fich
67        GO TO 100
68      END IF
69      anneelim = anneelim + 1
70    END DO
71
72    PRINT *, ' PBS ! Le jour a lire sur le fichier limit ne se '
73    PRINT *, ' trouve pas sur les ', nannemax, ' annees a partir de '
74    PRINT *, ' l annee de debut', annee_ref
[2311]75    CALL abort_physic('condsurf', '', 1)
[1992]76
77100 CONTINUE
78
79  ELSE
80
81    WRITE (fich, '("limitNEW.nc")')
82    ! PRINT *,' Fichier  Limite ',fich
83  END IF
84
85  ! Ouvrir le fichier en format NetCDF:
86
87  !$OMP MASTER
88  IF (is_mpi_root) THEN
[5270]89    ierr = nf90_open(fich, nf90_nowrite, nid)
90    IF (ierr/=nf90_noerr) THEN
[1992]91      WRITE (6, *) ' Pb d''ouverture du fichier ', fich
92      WRITE (6, *) ' Le fichier limit ', fich, ' (avec 4 chiffres , pour'
93      WRITE (6, *) '       l an 2000 )  ,  n existe  pas !  '
94      WRITE (6, *) ' ierr = ', ierr
[2311]95      CALL abort_physic('condsurf', '', 1)
[1992]96    END IF
97    ! DO k = 1, jour
98    ! La tranche de donnees a lire:
99
100    debut(1) = 1
101    debut(2) = jourvrai
102    epais(1) = klon_glo
103    epais(2) = 1
104    ! Bilan flux de chaleur au sol:
105
[5270]106    ierr = nf90_inq_varid(nid, 'BILS', nvarid)
107    IF (ierr/=nf90_noerr) THEN
[2311]108      CALL abort_physic('cond_surf', 'Le champ <BILS> est absent', 1)
[1992]109    END IF
110    PRINT *, 'debut,epais', debut, epais, 'jour,jourvrai', jour, jourvrai
[5249]111    ierr = nf90_get_var(nid, nvarid,  lmt_bils_glo, debut, epais)
[5270]112    IF (ierr/=nf90_noerr) THEN
[2311]113      CALL abort_physic('condsurf', 'Lecture echouee pour <BILS>', 1)
[1992]114    END IF
115    ! ENDDO !k = 1, jour
[766]116
[1992]117    ! Fermer le fichier:
118
[5270]119    ierr = nf90_close(nid)
[1992]120
121  END IF ! is_mpi_root==0
122
123  !$OMP END MASTER
124  CALL scatter(lmt_bils_glo, lmt_bils)
125
126
127
128  ! PRINT*, 'lmt_bils est lu pour jour: ', jour
129
130  RETURN
131END SUBROUTINE condsurf
Note: See TracBrowser for help on using the repository browser.