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

Last change on this file since 1990 was 1931, checked in by lguez, 11 years ago

abort and exit are not in the Fortran standard. Replaced them by abort_gcm.

  • 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
RevLine 
[644]1c $Header$
2c
3      SUBROUTINE condsurf( jour, jourvrai, lmt_bils )
[766]4      USE dimphy
[776]5      USE mod_grid_phy_lmdz
6      USE mod_phys_lmdz_para
[1785]7      USE indice_sol_mod
[644]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
[766]26cym#include "dimensions.h"
27cym#include "dimphy.h"
[644]28#include "temps.h"
29#include "clesphys.h"
30c
31      INTEGER     nannemax
32      PARAMETER ( nannemax = 60 )
33c
[688]34      INTEGER jour, jourvrai
[644]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
[766]42     
[776]43      REAL :: lmt_bils_glo(klon_glo)
[766]44     
[644]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
[766]54     
[644]55      IF (jour.LT.0 .OR. jour.GT.(360-1)) THEN
56         PRINT*,'Le jour demande n est pas correct: ', jour
[1931]57         CALL ABORT_gcm("condsurf", "", 1)
[644]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
[1931]77         CALL abort_gcm("condsurf", "", 1)
[644]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
[766]89c$OMP MASTER
[776]90      IF (is_mpi_root) THEN
[644]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
[1931]97        CALL abort_gcm("condsurf", "", 1)
[644]98      ENDIF
99c     DO k = 1, jour
100c La tranche de donnees a lire:
101c
102      debut(1) = 1
[688]103      debut(2) = jourvrai
[776]104      epais(1) = klon_glo
[644]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
[1931]110         CALL abort_gcm("cond_surf", "Le champ <BILS> est absent", 1)
[644]111      ENDIF
[688]112      PRINT*,'debut,epais',debut,epais,'jour,jourvrai',jour,jourvrai
[644]113#ifdef NC_DOUBLE
[766]114      ierr = NF_GET_VARA_DOUBLE(nid, nvarid,debut,epais,lmt_bils_glo)
[644]115#else
[766]116      ierr = NF_GET_VARA_REAL(nid, nvarid,debut,epais,lmt_bils_glo)
[644]117#endif
118      IF (ierr .NE. NF_NOERR) THEN
[1931]119         CALL abort_gcm("condsurf", "Lecture echouee pour <BILS>", 1)
[644]120      ENDIF
121c     ENDDO !k = 1, jour
122c
123c Fermer le fichier:
124c
125      ierr = NF_CLOSE(nid)
[766]126     
[776]127      ENDIF ! is_mpi_root==0
[766]128
129c$OMP END MASTER
[776]130      CALL scatter(lmt_bils_glo,lmt_bils)
[766]131           
[644]132c
133c
134c     PRINT*, 'lmt_bils est lu pour jour: ', jour
135c
136      RETURN
137      END
Note: See TracBrowser for help on using the repository browser.