source: LMDZ5/trunk/libf/phylmd/condsurf.F @ 1907

Last change on this file since 1907 was 1907, checked in by lguez, 10 years ago

Added a copyright property to every file of the distribution, except
for the fcm files (which have their own copyright). Use svn propget on
a file to see the copyright. For instance:

$ svn propget copyright libf/phylmd/physiq.F90
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

Also added the files defining the CeCILL version 2 license, in French
and English, at the top of the LMDZ tree.

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