source: LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/condsurfc.f90

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

Put .h into modules

File size: 3.4 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 lmdz_dimensions, ONLY: iim, jjm, llm, ndm
8  IMPLICIT 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<0 .OR. jour>(360 - 1)) THEN
28    IF (jour>(360 - 1).AND.jour<=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/=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  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  IF (ierr /= nf90_noerr) THEN
58    PRINT*, 'Pb de lecture pour les sources BC'
59    CALL exit(1)
60  ENDIF
61
62
63  ierr = nf90_inq_varid (nid1, "BCBB", nvarid)
64  ierr = nf90_get_var(nid1, nvarid, lmt_bcbb, debut, epais)
65  IF (ierr /= nf90_noerr) THEN
66    PRINT*, 'Pb de lecture pour les sources BC-biomass'
67    CALL exit(1)
68  ENDIF
69
70
71  ierr = nf90_inq_varid (nid1, "BCBL", nvarid)
72  ierr = nf90_get_var(nid1, nvarid, lmt_bcbbl, debut, epais)
73  IF (ierr /= nf90_noerr) THEN
74    PRINT*, 'Pb de lecture pour les sources BC low'
75    CALL exit(1)
76  ENDIF
77
78
79  ierr = nf90_inq_varid (nid1, "BCBH", nvarid)
80  ierr = nf90_get_var (nid1, nvarid, lmt_bcbbh, debut, epais)
81  IF (ierr /= nf90_noerr) THEN
82    PRINT*, 'Pb de lecture pour les sources BC high'
83    CALL exit(1)
84  ENDIF
85
86  ierr = nf90_inq_varid (nid1, "TERP", nvarid)
87  ierr = nf90_get_var (nid1, nvarid, lmt_terp, debut, epais)
88  IF (ierr /= nf90_noerr) THEN
89    PRINT*, 'Pb de lecture pour les sources Terpene'
90    CALL exit(1)
91  ENDIF
92
93
94  ierr = nf90_inq_varid (nid1, "BC_penner", nvarid)
95  ierr = nf90_get_var (nid1, nvarid, lmt_bc_penner, debut, epais)
96  IF (ierr /= nf90_noerr) THEN
97    PRINT*, 'Pb de lecture pour les sources BC Penner'
98    CALL exit(1)
99  ENDIF
100
101
102  ierr = nf90_inq_varid (nid1, "OMFF", nvarid)
103  ierr = nf90_get_var (nid1, nvarid, lmt_omff, debut, epais)
104  IF (ierr /= nf90_noerr) THEN
105    PRINT*, 'Pb de lecture pour les sources om-ifossil'
106    CALL exit(1)
107  ENDIF
108
109  DO i = 1, klon
110    lmt_ombb(i) = lmt_bcbb(i) * 7.0 * 1.6      !OC/BC=7.0;OM/OC=1.6
111    lmt_ombbl(i) = lmt_bcbbl(i) * 7.0 * 1.6
112    lmt_ombbh(i) = lmt_bcbbh(i) * 7.0 * 1.6
113    lmt_omff(i) = lmt_omff(i) * 1.4          !--OM/OC=1.4
114    lmt_omnat(i) = lmt_terp(i) * 0.11 * 1.4 !-- 11% Terpene is OC
115  ENDDO
116
117  ierr = nf90_close(nid1)
118  PRINT*, 'Carbon sources lues pour jour: ', jour
119
120
121END SUBROUTINE condsurfc
Note: See TracBrowser for help on using the repository browser.