LMDZ
condsurf.F90
Go to the documentation of this file.
1 ! $Id: condsurf.F90 2344 2015-08-21 07:23:13Z emillour $
2 
3 SUBROUTINE condsurf(jour, jourvrai, lmt_bils)
4  USE dimphy
8  USE time_phylmdz_mod, ONLY: annee_ref
9  IMPLICIT NONE
10 
11  ! I. Musat 05.2005
12 
13  ! Lire chaque jour le bilan de chaleur au sol issu
14  ! d'un run atmospherique afin de l'utiliser dans
15  ! dans un run "slab" ocean
16  ! -----------------------------------------
17  ! jour : input , numero du jour a lire
18  ! jourvrai : input , vrai jour de la simulation
19 
20  ! lmt_bils: bilan chaleur au sol (a utiliser pour "slab-ocean")
21 
22  include "netcdf.inc"
23  INTEGER nid, nvarid
24  INTEGER debut(2)
25  INTEGER epais(2)
26 
27  include "clesphys.h"
28 
29  INTEGER nannemax
30  parameter(nannemax=60)
31 
32  INTEGER jour, jourvrai
33  REAL lmt_bils(klon) !bilan chaleur au sol
34 
35  ! Variables locales:
36  INTEGER ig, i, kt, ierr
37  LOGICAL ok
38  INTEGER anneelim, anneemax
39  CHARACTER *20 fich
40 
41  REAL :: lmt_bils_glo(klon_glo)
42 
43  ! c
44  ! c .....................................................................
45  ! c
46  ! c Pour lire le fichier limit correspondant vraiment a l'annee de la
47  ! c simulation en cours , il suffit de mettre ok_limitvrai = .TRUE.
48  ! c
49  ! c
50  ! ......................................................................
51 
52 
53 
54  IF (jour<0 .OR. jour>(360-1)) THEN
55  print *, 'Le jour demande n est pas correct: ', jour
56  CALL abort_physic('condsurf', '', 1)
57  END IF
58 
59  anneelim = annee_ref
60  anneemax = annee_ref + nannemax
61 
62 
63  IF (ok_limitvrai) THEN
64  DO kt = 1, nannemax
65  IF (jourvrai<=(kt-1)*360+359) THEN
66  WRITE (fich, '("limit",i4,".nc")') anneelim
67  ! PRINT *,' Fichier Limite ',fich
68  GO TO 100
69  END IF
70  anneelim = anneelim + 1
71  END DO
72 
73  print *, ' PBS ! Le jour a lire sur le fichier limit ne se '
74  print *, ' trouve pas sur les ', nannemax, ' annees a partir de '
75  print *, ' l annee de debut', annee_ref
76  CALL abort_physic('condsurf', '', 1)
77 
78 100 CONTINUE
79 
80  ELSE
81 
82  WRITE (fich, '("limitNEW.nc")')
83  ! PRINT *,' Fichier Limite ',fich
84  END IF
85 
86  ! Ouvrir le fichier en format NetCDF:
87 
88  !$OMP MASTER
89  IF (is_mpi_root) THEN
90  ierr = nf_open(fich, nf_nowrite, nid)
91  IF (ierr/=nf_noerr) THEN
92  WRITE (6, *) ' Pb d''ouverture du fichier ', fich
93  WRITE (6, *) ' Le fichier limit ', fich, ' (avec 4 chiffres , pour'
94  WRITE (6, *) ' l an 2000 ) , n existe pas ! '
95  WRITE (6, *) ' ierr = ', ierr
96  CALL abort_physic('condsurf', '', 1)
97  END IF
98  ! DO k = 1, jour
99  ! La tranche de donnees a lire:
100 
101  debut(1) = 1
102  debut(2) = jourvrai
103  epais(1) = klon_glo
104  epais(2) = 1
105  ! Bilan flux de chaleur au sol:
106 
107  ierr = nf_inq_varid(nid, 'BILS', nvarid)
108  IF (ierr/=nf_noerr) THEN
109  CALL abort_physic('cond_surf', 'Le champ <BILS> est absent', 1)
110  END IF
111  print *, 'debut,epais', debut, epais, 'jour,jourvrai', jour, jourvrai
112 #ifdef NC_DOUBLE
113  ierr = nf_get_vara_double(nid, nvarid, debut, epais, lmt_bils_glo)
114 #else
115  ierr = nf_get_vara_real(nid, nvarid, debut, epais, lmt_bils_glo)
116 #endif
117  IF (ierr/=nf_noerr) THEN
118  CALL abort_physic('condsurf', 'Lecture echouee pour <BILS>', 1)
119  END IF
120  ! ENDDO !k = 1, jour
121 
122  ! Fermer le fichier:
123 
124  ierr = nf_close(nid)
125 
126  END IF ! is_mpi_root==0
127 
128  !$OMP END MASTER
129  CALL scatter(lmt_bils_glo, lmt_bils)
130 
131 
132 
133  ! PRINT*, 'lmt_bils est lu pour jour: ', jour
134 
135  RETURN
136 END SUBROUTINE condsurf
!$Header!c include clesph0 h c COMMON clesph0 ok_limitvrai
Definition: clesph0.h:6
integer, save klon
Definition: dimphy.F90:3
integer, save klon_glo
!$Header!integer nvarmx parameter(nfmx=10, imx=200, jmx=150, lmx=200, nvarmx=1000) real xd(imx
subroutine condsurf(jour, jourvrai, lmt_bils)
Definition: condsurf.F90:4
subroutine abort_physic(modname, message, ierr)
Definition: abort_physic.F90:3
Definition: dimphy.F90:1
!$Id annee_ref
Definition: temps.h:15