source: LMDZ4/trunk/libf/phylmd/condsurf.F @ 675

Last change on this file since 675 was 675, checked in by Laurent Fairhead, 19 years ago

Pour compatibilite avec g95
LF

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 3.2 KB
Line 
1c $Header$
2c
3      SUBROUTINE condsurf( jour, jourvrai, lmt_bils )
4      IMPLICIT none
5c
6c I. Musat 05.2005
7c
8c Lire chaque jour le bilan de chaleur au sol issu
9c d'un run atmospherique afin de l'utiliser dans
10c dans un run "slab" ocean
11c -----------------------------------------
12c jour     : input  , numero du jour a lire
13c jourvrai : input  , vrai jour de la simulation 
14c
15c lmt_bils: bilan chaleur au sol (a utiliser pour "slab-ocean")
16c
17#include "netcdf.inc"
18      INTEGER nid, nvarid
19      INTEGER debut(2)
20      INTEGER epais(2)
21c
22#include "dimensions.h"
23#include "dimphy.h"
24#include "indicesol.h"
25#include "temps.h"
26#include "clesphys.h"
27c
28      INTEGER     nannemax
29      PARAMETER ( nannemax = 60 )
30c
31      INTEGER jour
32      INTEGER jourvrai
33      REAL lmt_bils(klon) !bilan chaleur au sol
34c
35c Variables locales:
36      INTEGER ig, i, kt, ierr
37      LOGICAL ok
38      INTEGER anneelim,anneemax
39      CHARACTER*20 fich
40cc
41cc   .....................................................................
42cc
43cc    Pour lire le fichier limit correspondant vraiment  a l'annee de la
44cc     simulation en cours , il suffit de mettre  ok_limitvrai = .TRUE.
45cc
46cc   ......................................................................
47c
48c
49      IF (jour.LT.0 .OR. jour.GT.(360-1)) THEN
50         PRINT*,'Le jour demande n est pas correct: ', jour
51         CALL ABORT
52      ENDIF
53c
54       anneelim  = annee_ref
55       anneemax  = annee_ref + nannemax
56c
57c
58       IF( ok_limitvrai )       THEN
59          DO  kt = 1, nannemax
60           IF(jourvrai.LE. (kt-1)*360 + 359  )  THEN
61              WRITE(fich,'("limit",i4,".nc")') anneelim
62c             PRINT *,' Fichier  Limite ',fich
63              GO TO 100
64             ENDIF
65           anneelim = anneelim + 1
66          ENDDO
67
68         PRINT *,' PBS ! Le jour a lire sur le fichier limit ne se '
69         PRINT *,' trouve pas sur les ',nannemax,' annees a partir de '
70         PRINT *,' l annee de debut', annee_ref
71         CALL EXIT(1)
72c
73100     CONTINUE
74c
75       ELSE
76     
77            WRITE(fich,'("limitNEW.nc")')
78c           PRINT *,' Fichier  Limite ',fich
79       ENDIF
80c
81c Ouvrir le fichier en format NetCDF:
82c
83      ierr = NF_OPEN (fich, NF_NOWRITE,nid)
84      IF (ierr.NE.NF_NOERR) THEN
85        WRITE(6,*)' Pb d''ouverture du fichier ', fich
86        WRITE(6,*)' Le fichier limit ',fich,' (avec 4 chiffres , pour'
87        WRITE(6,*)'       l an 2000 )  ,  n existe  pas !  '
88        WRITE(6,*)' ierr = ', ierr
89        CALL EXIT(1)
90      ENDIF
91c     DO k = 1, jour
92c La tranche de donnees a lire:
93c
94      debut(1) = 1
95      debut(2) = jour
96      epais(1) = klon
97      epais(2) = 1
98c
99c Bilan flux de chaleur au sol:
100c
101      ierr = NF_INQ_VARID (nid, "BILS", nvarid)
102      IF (ierr .NE. NF_NOERR) THEN
103         PRINT*, "condsurf: Le champ <BILS> est absent"
104         CALL abort
105      ENDIF
106c     PRINT*,'debut,epais',debut,epais
107#ifdef NC_DOUBLE
108      ierr = NF_GET_VARA_DOUBLE(nid, nvarid,debut,epais,lmt_bils)
109#else
110      ierr = NF_GET_VARA_REAL(nid, nvarid,debut,epais,lmt_bils)
111#endif
112      IF (ierr .NE. NF_NOERR) THEN
113         PRINT*, "condsurf: Lecture echouee pour <BILS>"
114         CALL abort
115      ENDIF
116c     ENDDO !k = 1, jour
117c
118c Fermer le fichier:
119c
120      ierr = NF_CLOSE(nid)
121c
122c
123c     PRINT*, 'lmt_bils est lu pour jour: ', jour
124c
125      RETURN
126      END
Note: See TracBrowser for help on using the repository browser.