source: LMDZ4/branches/pre_V3/libf/phylmd/condsurf.F @ 1957

Last change on this file since 1957 was 688, checked in by lmdzadmin, 18 years ago

Modif. jour -> jourvrai si slab ocean
IM

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 3.3 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, jourvrai
32      REAL lmt_bils(klon) !bilan chaleur au sol
33c
34c Variables locales:
35      INTEGER ig, i, kt, ierr
36      LOGICAL ok
37      INTEGER anneelim,anneemax
38      CHARACTER*20 fich
39cc
40cc   .....................................................................
41cc
42cc    Pour lire le fichier limit correspondant vraiment  a l'annee de la
43cc     simulation en cours , il suffit de mettre  ok_limitvrai = .TRUE.
44cc
45cc   ......................................................................
46c
47c
48      IF (jour.LT.0 .OR. jour.GT.(360-1)) THEN
49         PRINT*,'Le jour demande n est pas correct: ', jour
50         CALL ABORT
51      ENDIF
52c
53       anneelim  = annee_ref
54       anneemax  = annee_ref + nannemax
55c
56c
57       IF( ok_limitvrai )       THEN
58          DO  kt = 1, nannemax
59           IF(jourvrai.LE. (kt-1)*360 + 359  )  THEN
60              WRITE(fich,'("limit",i4,".nc")') anneelim
61c             PRINT *,' Fichier  Limite ',fich
62              GO TO 100
63             ENDIF
64           anneelim = anneelim + 1
65          ENDDO
66
67         PRINT *,' PBS ! Le jour a lire sur le fichier limit ne se '
68         PRINT *,' trouve pas sur les ',nannemax,' annees a partir de '
69         PRINT *,' l annee de debut', annee_ref
70         CALL EXIT(1)
71c
72100     CONTINUE
73c
74       ELSE
75     
76            WRITE(fich,'("limitNEW.nc")')
77c           PRINT *,' Fichier  Limite ',fich
78       ENDIF
79c
80c Ouvrir le fichier en format NetCDF:
81c
82      ierr = NF_OPEN (fich, NF_NOWRITE,nid)
83      IF (ierr.NE.NF_NOERR) THEN
84        WRITE(6,*)' Pb d''ouverture du fichier ', fich
85        WRITE(6,*)' Le fichier limit ',fich,' (avec 4 chiffres , pour'
86        WRITE(6,*)'       l an 2000 )  ,  n existe  pas !  '
87        WRITE(6,*)' ierr = ', ierr
88        CALL EXIT(1)
89      ENDIF
90c     DO k = 1, jour
91c La tranche de donnees a lire:
92c
93      debut(1) = 1
94      debut(2) = jourvrai
95      epais(1) = klon
96      epais(2) = 1
97c
98c Bilan flux de chaleur au sol:
99c
100      ierr = NF_INQ_VARID (nid, "BILS", nvarid)
101      IF (ierr .NE. NF_NOERR) THEN
102         PRINT*, "condsurf: Le champ <BILS> est absent"
103         CALL abort
104      ENDIF
105      PRINT*,'debut,epais',debut,epais,'jour,jourvrai',jour,jourvrai
106#ifdef NC_DOUBLE
107      ierr = NF_GET_VARA_DOUBLE(nid, nvarid,debut,epais,lmt_bils)
108#else
109      ierr = NF_GET_VARA_REAL(nid, nvarid,debut,epais,lmt_bils)
110#endif
111      IF (ierr .NE. NF_NOERR) THEN
112         PRINT*, "condsurf: Lecture echouee pour <BILS>"
113         CALL abort
114      ENDIF
115c     ENDDO !k = 1, jour
116c
117c Fermer le fichier:
118c
119      ierr = NF_CLOSE(nid)
120c
121c
122c     PRINT*, 'lmt_bils est lu pour jour: ', jour
123c
124      RETURN
125      END
Note: See TracBrowser for help on using the repository browser.