source: LMDZ6/trunk/libf/phylmd/Dust/condsurfc.f90 @ 5277

Last change on this file since 5277 was 5271, checked in by abarral, 32 hours ago

Move dimensions.h into a module
Nb: doesn't compile yet

File size: 4.1 KB
Line 
1SUBROUTINE 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  USE netcdf, ONLY: nf90_close, nf90_noerr, nf90_inq_varid, nf90_open, nf90_nowrite, nf90_get_var
7  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
8IMPLICIT none
9  !
10  ! Lire les conditions aux limites du modele pour la chimie.
11  ! --------------------------------------------------------
12  !
13
14
15  REAL :: lmt_bcff(klon), lmt_bcbb(klon),lmt_bc_penner(klon)
16  REAL :: lmt_omff(klon), lmt_ombb(klon)
17  REAL :: lmt_bcbbl(klon), lmt_bcbbh(klon)
18  REAL :: lmt_ombbl(klon), lmt_ombbh(klon)
19  REAL :: lmt_omnat(klon)
20  REAL :: lmt_terp(klon)
21  !
22  INTEGER :: jour, i
23  INTEGER :: ierr
24  INTEGER :: nid1,nvarid
25  INTEGER :: debut(2),epais(2)
26  !
27  IF (jour.LT.0 .OR. jour.GT.(360-1)) THEN
28     IF (jour.GT.(360-1).AND.jour.LE.367) THEN
29       jour=360-1
30       print *,'JE: jour changed to jour= ',jour
31     ELSE
32       PRINT*,'Le jour demande n est pas correcte:', jour
33       CALL ABORT
34     ENDIF
35  ENDIF
36  !
37  ierr = nf90_open ("limitcarbon.nc", nf90_nowrite, nid1)
38  if (ierr.ne.nf90_noerr) then
39    write(6,*)' Pb d''ouverture du fichier limitbc.nc'
40    write(6,*)' ierr = ', ierr
41    call exit(1)
42  endif
43  !
44  ! Tranche a lire:
45  debut(1) = 1
46  debut(2) = jour+1
47  epais(1) = klon
48  epais(2) = 1
49  !
50  !
51  ierr = nf90_inq_varid(nid1, "BCFF", nvarid)
52  !nhl #ifdef NC_DOUBLE
53  ierr = nf90_get_var(nid1, nvarid, lmt_bcff, debut, epais)
54   ! print *,'IERR = ',ierr
55   ! print *,'nf90_noerr = ',nf90_noerr
56   ! print *,'debut = ',debut
57   ! print *,'epais = ',epais
58  !nhl #else
59  !nhl       ierr = nf90_get_var(nid1, nvarid, lmt_bcff, debut, epais)
60  !nhl #endif
61  IF (ierr .NE. nf90_noerr) THEN
62     PRINT*, 'Pb de lecture pour les sources BC'
63     CALL exit(1)
64  ENDIF
65  !
66  !
67  ierr = nf90_inq_varid(nid1, "BCBB", nvarid)
68  !nhl #ifdef NC_DOUBLE
69  ierr = nf90_get_var(nid1, nvarid, lmt_bcbb, debut, epais)
70  !nhl #else
71  !nhl       ierr = nf90_get_var(nid1, nvarid, lmt_bcbb, debut, epais)
72  !nhl #endif
73  IF (ierr .NE. nf90_noerr) THEN
74     PRINT*, 'Pb de lecture pour les sources BC-biomass'
75     CALL exit(1)
76  ENDIF
77  !
78  !
79  ierr = nf90_inq_varid(nid1, "BCBL", nvarid)
80  !nhl #ifdef NC_DOUBLE
81  ierr = nf90_get_var(nid1, nvarid, lmt_bcbbl, debut, epais)
82  !nhl #else
83  !nhl       ierr = nf90_get_var(nid1, nvarid, lmt_bcbbl, debut, epais)
84  !nhl #endif
85  IF (ierr .NE. nf90_noerr) THEN
86     PRINT*, 'Pb de lecture pour les sources BC low'
87     CALL exit(1)
88  ENDIF
89  !
90  !
91  ierr = nf90_inq_varid(nid1, "BCBH", nvarid)
92  !nhl #ifdef NC_DOUBLE
93  ierr = nf90_get_var(nid1, nvarid, lmt_bcbbh, debut, epais)
94  !nhl #else
95  !nhl       ierr = nf90_get_var(nid1, nvarid, lmt_bcbbh, debut, epais)
96  !nhl #endif
97  IF (ierr .NE. nf90_noerr) THEN
98     PRINT*, 'Pb de lecture pour les sources BC high'
99     CALL exit(1)
100  ENDIF
101  !
102  ierr = nf90_inq_varid(nid1, "TERP", nvarid)
103  !nhl #ifdef NC_DOUBLE
104  ierr = nf90_get_var(nid1, nvarid, lmt_terp, debut, epais)
105  !nhl #else
106  !nhl       ierr = nf90_get_var(nid1, nvarid, lmt_terp, debut, epais)
107  !nhl #endif
108  IF (ierr .NE. nf90_noerr) THEN
109     PRINT*, 'Pb de lecture pour les sources Terpene'
110     CALL exit(1)
111  ENDIF
112  !
113  !
114  ierr = nf90_inq_varid(nid1, "BC_penner", nvarid)
115  ierr = nf90_get_var(nid1, nvarid, lmt_bc_penner, debut, &
116        epais)
117  IF (ierr .NE. nf90_noerr) THEN
118     PRINT*, 'Pb de lecture pour les sources BC Penner'
119     CALL exit(1)
120  ENDIF
121  !
122  !
123  ierr = nf90_inq_varid(nid1, "OMFF", nvarid)
124  !nhl #ifdef NC_DOUBLE
125  ierr = nf90_get_var(nid1, nvarid, lmt_omff, debut, epais)
126  !nhl #else
127  !nhl       ierr = nf90_get_var(nid1, nvarid, lmt_omff, debut, epais)
128  !nhl #endif
129  IF (ierr .NE. nf90_noerr) THEN
130     PRINT*, 'Pb de lecture pour les sources om-ifossil'
131     CALL exit(1)
132  ENDIF
133  !
134  DO i=1,klon
135    lmt_ombb(i)  = lmt_bcbb(i)*7.0*1.6      !OC/BC=7.0;OM/OC=1.6
136    lmt_ombbl(i) = lmt_bcbbl(i)*7.0*1.6
137    lmt_ombbh(i) = lmt_bcbbh(i)*7.0*1.6
138    lmt_omff(i)  = lmt_omff(i)*1.4          !--OM/OC=1.4
139    lmt_omnat(i)  = lmt_terp(i)*0.11*1.4 !-- 11% Terpene is OC
140  ENDDO
141  !
142  ierr = nf90_close(nid1)
143  PRINT*, 'Carbon sources lues pour jour: ', jour
144  !
145  RETURN
146END SUBROUTINE condsurfc
Note: See TracBrowser for help on using the repository browser.