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

Last change on this file since 5099 was 5099, checked in by abarral, 4 months ago

Replace most uses of CPP_DUST by the corresponding logical defined in lmdz_cppkeys_wrapper.F90
Convert several files from .F to .f90 to allow Dust to compile w/o rrtm/ecrad
Create lmdz_yoerad.f90
(lint) Remove "!" on otherwise empty line

File size: 3.3 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  IMPLICIT none
8
9  ! Lire les conditions aux limites du modele pour la chimie.
10  ! --------------------------------------------------------
11
12  INCLUDE "dimensions.h"
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 = nf90_open ("limitcarbon.nc", nf90_nowrite, nid1)
37  if (ierr/=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  ierr = nf90_get_var(nid1, nvarid, lmt_bcff, debut, epais)
52  ! print *,'IERR = ',ierr
53  ! print *,'nf90_noerr = ',nf90_noerr
54  ! print *,'debut = ',debut
55  ! print *,'epais = ',epais
56  IF (ierr /= nf90_noerr) THEN
57    PRINT*, 'Pb de lecture pour les sources BC'
58    CALL exit(1)
59  ENDIF
60
61
62  ierr = nf90_inq_varid (nid1, "BCBB", nvarid)
63  ierr = nf90_get_var(nid1, nvarid, lmt_bcbb, debut, epais)
64  IF (ierr /= nf90_noerr) THEN
65    PRINT*, 'Pb de lecture pour les sources BC-biomass'
66    CALL exit(1)
67  ENDIF
68
69
70  ierr = nf90_inq_varid (nid1, "BCBL", nvarid)
71  ierr = nf90_get_var(nid1, nvarid, lmt_bcbbl, debut, epais)
72  IF (ierr /= nf90_noerr) THEN
73    PRINT*, 'Pb de lecture pour les sources BC low'
74    CALL exit(1)
75  ENDIF
76
77
78  ierr = nf90_inq_varid (nid1, "BCBH", nvarid)
79  ierr = nf90_get_var (nid1, nvarid, lmt_bcbbh, debut, epais)
80  IF (ierr /= nf90_noerr) THEN
81    PRINT*, 'Pb de lecture pour les sources BC high'
82    CALL exit(1)
83  ENDIF
84
85  ierr = nf90_inq_varid (nid1, "TERP", nvarid)
86  ierr = nf90_get_var (nid1, nvarid, lmt_terp, debut, epais)
87  IF (ierr /= nf90_noerr) THEN
88    PRINT*, 'Pb de lecture pour les sources Terpene'
89    CALL exit(1)
90  ENDIF
91
92
93  ierr = nf90_inq_varid (nid1, "BC_penner", nvarid)
94  ierr = nf90_get_var (nid1, nvarid, lmt_bc_penner, debut, epais)
95  IF (ierr /= nf90_noerr) THEN
96    PRINT*, 'Pb de lecture pour les sources BC Penner'
97    CALL exit(1)
98  ENDIF
99
100
101  ierr = nf90_inq_varid (nid1, "OMFF", nvarid)
102  ierr = nf90_get_var (nid1, nvarid, lmt_omff, debut, epais)
103  IF (ierr /= nf90_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 = nf90_close(nid1)
117  PRINT*, 'Carbon sources lues pour jour: ', jour
118
119  RETURN
120END SUBROUTINE condsurfc
Note: See TracBrowser for help on using the repository browser.