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

Last change on this file since 5408 was 5337, checked in by Laurent Fairhead, 4 weeks ago

Getting rid of dependance to dynamics

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
7IMPLICIT none
8  !
9  ! Lire les conditions aux limites du modele pour la chimie.
10  ! --------------------------------------------------------
11  !
12
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.LT.0 .OR. jour.GT.(360-1)) THEN
27     IF (jour.GT.(360-1).AND.jour.LE.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 = nf90_open ("limitcarbon.nc", nf90_nowrite, nid1)
37  if (ierr.ne.nf90_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 = nf90_inq_varid(nid1, "BCFF", nvarid)
51  !nhl #ifdef NC_DOUBLE
52  ierr = nf90_get_var(nid1, nvarid, lmt_bcff, debut, epais)
53   ! print *,'IERR = ',ierr
54   ! print *,'nf90_noerr = ',nf90_noerr
55   ! print *,'debut = ',debut
56   ! print *,'epais = ',epais
57  !nhl #else
58  !nhl       ierr = nf90_get_var(nid1, nvarid, lmt_bcff, debut, epais)
59  !nhl #endif
60  IF (ierr .NE. nf90_noerr) THEN
61     PRINT*, 'Pb de lecture pour les sources BC'
62     CALL exit(1)
63  ENDIF
64  !
65  !
66  ierr = nf90_inq_varid(nid1, "BCBB", nvarid)
67  !nhl #ifdef NC_DOUBLE
68  ierr = nf90_get_var(nid1, nvarid, lmt_bcbb, debut, epais)
69  !nhl #else
70  !nhl       ierr = nf90_get_var(nid1, nvarid, lmt_bcbb, debut, epais)
71  !nhl #endif
72  IF (ierr .NE. nf90_noerr) THEN
73     PRINT*, 'Pb de lecture pour les sources BC-biomass'
74     CALL exit(1)
75  ENDIF
76  !
77  !
78  ierr = nf90_inq_varid(nid1, "BCBL", nvarid)
79  !nhl #ifdef NC_DOUBLE
80  ierr = nf90_get_var(nid1, nvarid, lmt_bcbbl, debut, epais)
81  !nhl #else
82  !nhl       ierr = nf90_get_var(nid1, nvarid, lmt_bcbbl, debut, epais)
83  !nhl #endif
84  IF (ierr .NE. nf90_noerr) THEN
85     PRINT*, 'Pb de lecture pour les sources BC low'
86     CALL exit(1)
87  ENDIF
88  !
89  !
90  ierr = nf90_inq_varid(nid1, "BCBH", nvarid)
91  !nhl #ifdef NC_DOUBLE
92  ierr = nf90_get_var(nid1, nvarid, lmt_bcbbh, debut, epais)
93  !nhl #else
94  !nhl       ierr = nf90_get_var(nid1, nvarid, lmt_bcbbh, debut, epais)
95  !nhl #endif
96  IF (ierr .NE. nf90_noerr) THEN
97     PRINT*, 'Pb de lecture pour les sources BC high'
98     CALL exit(1)
99  ENDIF
100  !
101  ierr = nf90_inq_varid(nid1, "TERP", nvarid)
102  !nhl #ifdef NC_DOUBLE
103  ierr = nf90_get_var(nid1, nvarid, lmt_terp, debut, epais)
104  !nhl #else
105  !nhl       ierr = nf90_get_var(nid1, nvarid, lmt_terp, debut, epais)
106  !nhl #endif
107  IF (ierr .NE. nf90_noerr) THEN
108     PRINT*, 'Pb de lecture pour les sources Terpene'
109     CALL exit(1)
110  ENDIF
111  !
112  !
113  ierr = nf90_inq_varid(nid1, "BC_penner", nvarid)
114  ierr = nf90_get_var(nid1, nvarid, lmt_bc_penner, debut, &
115        epais)
116  IF (ierr .NE. nf90_noerr) THEN
117     PRINT*, 'Pb de lecture pour les sources BC Penner'
118     CALL exit(1)
119  ENDIF
120  !
121  !
122  ierr = nf90_inq_varid(nid1, "OMFF", nvarid)
123  !nhl #ifdef NC_DOUBLE
124  ierr = nf90_get_var(nid1, nvarid, lmt_omff, debut, epais)
125  !nhl #else
126  !nhl       ierr = nf90_get_var(nid1, nvarid, lmt_omff, debut, epais)
127  !nhl #endif
128  IF (ierr .NE. nf90_noerr) THEN
129     PRINT*, 'Pb de lecture pour les sources om-ifossil'
130     CALL exit(1)
131  ENDIF
132  !
133  DO i=1,klon
134    lmt_ombb(i)  = lmt_bcbb(i)*7.0*1.6      !OC/BC=7.0;OM/OC=1.6
135    lmt_ombbl(i) = lmt_bcbbl(i)*7.0*1.6
136    lmt_ombbh(i) = lmt_bcbbh(i)*7.0*1.6
137    lmt_omff(i)  = lmt_omff(i)*1.4          !--OM/OC=1.4
138    lmt_omnat(i)  = lmt_terp(i)*0.11*1.4 !-- 11% Terpene is OC
139  ENDDO
140  !
141  ierr = nf90_close(nid1)
142  PRINT*, 'Carbon sources lues pour jour: ', jour
143  !
144  RETURN
145END SUBROUTINE condsurfc
Note: See TracBrowser for help on using the repository browser.