source: LMDZ6/trunk/libf/phylmd/Dust/condsurfc.F @ 5073

Last change on this file since 5073 was 5073, checked in by abarral, 7 weeks ago

Remove all NC_DOUBLE uses outside of lmdz_netcdf.F90 (except in obsolete/, which I hope we'll ditch soon...)
Note: make sure to check convergence at some point, it's possible that we've messed up some when replacing nf_* by nf90_* calls
(lint) replace obsolete logical operators along the way

File size: 3.6 KB
Line 
1      SUBROUTINE condsurfc(jour,lmt_bcff,lmt_bcbb,
2     .                     lmt_bcbbl,lmt_bcbbh,lmt_bc_penner,
3     .                     lmt_omff,lmt_ombb,lmt_ombbl,lmt_ombbh,
4     .                     lmt_omnat)
5      USE dimphy
6      IMPLICIT none
7!
8! Lire les conditions aux limites du modele pour la chimie.
9! --------------------------------------------------------
10!
11      INCLUDE "dimensions.h"
12      INCLUDE "netcdf.inc"
13     
14      REAL lmt_bcff(klon), lmt_bcbb(klon),lmt_bc_penner(klon)
15      REAL lmt_omff(klon), lmt_ombb(klon)
16      REAL lmt_bcbbl(klon), lmt_bcbbh(klon)
17      REAL lmt_ombbl(klon), lmt_ombbh(klon)
18      REAL lmt_omnat(klon)
19      REAL lmt_terp(klon)
20!
21      INTEGER jour, i
22      INTEGER ierr
23      INTEGER nid1,nvarid
24      INTEGER debut(2),epais(2)
25!
26      IF (jour<0 .OR. jour>(360-1)) THEN
27         IF (jour>(360-1).AND.jour<=367) THEN
28           jour=360-1
29           print *,'JE: jour changed to jour= ',jour
30         ELSE
31           PRINT*,'Le jour demande n est pas correcte:', jour
32           CALL ABORT
33         ENDIF
34      ENDIF
35!
36      ierr = NF_OPEN ("limitcarbon.nc", NF_NOWRITE, nid1)
37      if (ierr/=NF_NOERR) then
38        write(6,*)' Pb d''ouverture du fichier limitbc.nc'
39        write(6,*)' ierr = ', ierr
40        call exit(1)
41      endif
42!
43! Tranche a lire:
44      debut(1) = 1
45      debut(2) = jour+1
46      epais(1) = klon
47      epais(2) = 1
48!
49!
50      ierr = NF_INQ_VARID (nid1, "BCFF", nvarid)
51      ierr = nf90_get_var(nid1, nvarid, lmt_bcff, debut, epais)
52!      print *,'IERR = ',ierr
53!      print *,'NF_NOERR = ',NF_NOERR
54!      print *,'debut = ',debut
55!      print *,'epais = ',epais
56      IF (ierr /= NF_NOERR) THEN
57         PRINT*, 'Pb de lecture pour les sources BC'
58         CALL exit(1)
59      ENDIF
60!
61!
62      ierr = NF_INQ_VARID (nid1, "BCBB", nvarid)
63      ierr = nf90_get_var(nid1, nvarid, lmt_bcbb, debut, epais)
64      IF (ierr /= NF_NOERR) THEN
65         PRINT*, 'Pb de lecture pour les sources BC-biomass'
66         CALL exit(1)
67      ENDIF
68!
69!
70      ierr = NF_INQ_VARID (nid1, "BCBL", nvarid)
71      ierr = nf90_get_var(nid1, nvarid, lmt_bcbbl, debut, epais)
72      IF (ierr /= NF_NOERR) THEN
73         PRINT*, 'Pb de lecture pour les sources BC low'
74         CALL exit(1)
75      ENDIF
76!
77!
78      ierr = NF_INQ_VARID (nid1, "BCBH", nvarid)
79      ierr = nf90_get_var (nid1, nvarid, lmt_bcbbh, debut, epais)
80      IF (ierr /= NF_NOERR) THEN
81         PRINT*, 'Pb de lecture pour les sources BC high'
82         CALL exit(1)
83      ENDIF
84!
85      ierr = NF_INQ_VARID (nid1, "TERP", nvarid)
86      ierr = nf90_get_var (nid1, nvarid, lmt_terp, debut, epais)
87      IF (ierr /= NF_NOERR) THEN
88         PRINT*, 'Pb de lecture pour les sources Terpene'
89         CALL exit(1)
90      ENDIF
91!
92!
93      ierr = NF_INQ_VARID (nid1, "BC_penner", nvarid)
94      ierr = nf90_get_var (nid1, nvarid, lmt_bc_penner, debut,  epais)
95      IF (ierr /= NF_NOERR) THEN
96         PRINT*, 'Pb de lecture pour les sources BC Penner'
97         CALL exit(1)
98      ENDIF
99!
100!
101      ierr = NF_INQ_VARID (nid1, "OMFF", nvarid)
102      ierr = nf90_get_var (nid1, nvarid, lmt_omff, debut, epais)
103      IF (ierr /= NF_NOERR) THEN
104         PRINT*, 'Pb de lecture pour les sources om-ifossil'
105         CALL exit(1)
106      ENDIF
107!
108      DO i=1,klon
109        lmt_ombb(i)  = lmt_bcbb(i)*7.0*1.6      !OC/BC=7.0;OM/OC=1.6
110        lmt_ombbl(i) = lmt_bcbbl(i)*7.0*1.6
111        lmt_ombbh(i) = lmt_bcbbh(i)*7.0*1.6
112        lmt_omff(i)  = lmt_omff(i)*1.4          !--OM/OC=1.4
113        lmt_omnat(i)  = lmt_terp(i)*0.11*1.4 !-- 11% Terpene is OC
114      ENDDO
115!
116      ierr = NF_CLOSE(nid1)
117      PRINT*, 'Carbon sources lues pour jour: ', jour
118!
119      RETURN
120      END
Note: See TracBrowser for help on using the repository browser.