SUBROUTINE condsurfc(jour, lmt_bcff, lmt_bcbb, & lmt_bcbbl, lmt_bcbbh, lmt_bc_penner, & lmt_omff, lmt_ombb, lmt_ombbl, lmt_ombbh, & lmt_omnat) USE dimphy USE netcdf, ONLY: nf90_close, nf90_noerr, nf90_inq_varid, nf90_open, nf90_nowrite, nf90_get_var IMPLICIT none ! Lire les conditions aux limites du modele pour la chimie. ! -------------------------------------------------------- INCLUDE "dimensions.h" REAL :: lmt_bcff(klon), lmt_bcbb(klon), lmt_bc_penner(klon) REAL :: lmt_omff(klon), lmt_ombb(klon) REAL :: lmt_bcbbl(klon), lmt_bcbbh(klon) REAL :: lmt_ombbl(klon), lmt_ombbh(klon) REAL :: lmt_omnat(klon) REAL :: lmt_terp(klon) INTEGER :: jour, i INTEGER :: ierr INTEGER :: nid1, nvarid INTEGER :: debut(2), epais(2) IF (jour<0 .OR. jour>(360 - 1)) THEN IF (jour>(360 - 1).AND.jour<=367) THEN jour = 360 - 1 print *, 'JE: jour changed to jour= ', jour ELSE PRINT*, 'Le jour demande n est pas correcte:', jour CALL ABORT ENDIF ENDIF ierr = nf90_open ("limitcarbon.nc", nf90_nowrite, nid1) if (ierr/=nf90_noerr) then write(6, *)' Pb d''ouverture du fichier limitbc.nc' write(6, *)' ierr = ', ierr CALL exit(1) endif ! Tranche a lire: debut(1) = 1 debut(2) = jour + 1 epais(1) = klon epais(2) = 1 ierr = nf90_inq_varid (nid1, "BCFF", nvarid) ierr = nf90_get_var(nid1, nvarid, lmt_bcff, debut, epais) ! print *,'IERR = ',ierr ! print *,'nf90_noerr = ',nf90_noerr ! print *,'debut = ',debut ! print *,'epais = ',epais IF (ierr /= nf90_noerr) THEN PRINT*, 'Pb de lecture pour les sources BC' CALL exit(1) ENDIF ierr = nf90_inq_varid (nid1, "BCBB", nvarid) ierr = nf90_get_var(nid1, nvarid, lmt_bcbb, debut, epais) IF (ierr /= nf90_noerr) THEN PRINT*, 'Pb de lecture pour les sources BC-biomass' CALL exit(1) ENDIF ierr = nf90_inq_varid (nid1, "BCBL", nvarid) ierr = nf90_get_var(nid1, nvarid, lmt_bcbbl, debut, epais) IF (ierr /= nf90_noerr) THEN PRINT*, 'Pb de lecture pour les sources BC low' CALL exit(1) ENDIF ierr = nf90_inq_varid (nid1, "BCBH", nvarid) ierr = nf90_get_var (nid1, nvarid, lmt_bcbbh, debut, epais) IF (ierr /= nf90_noerr) THEN PRINT*, 'Pb de lecture pour les sources BC high' CALL exit(1) ENDIF ierr = nf90_inq_varid (nid1, "TERP", nvarid) ierr = nf90_get_var (nid1, nvarid, lmt_terp, debut, epais) IF (ierr /= nf90_noerr) THEN PRINT*, 'Pb de lecture pour les sources Terpene' CALL exit(1) ENDIF ierr = nf90_inq_varid (nid1, "BC_penner", nvarid) ierr = nf90_get_var (nid1, nvarid, lmt_bc_penner, debut, epais) IF (ierr /= nf90_noerr) THEN PRINT*, 'Pb de lecture pour les sources BC Penner' CALL exit(1) ENDIF ierr = nf90_inq_varid (nid1, "OMFF", nvarid) ierr = nf90_get_var (nid1, nvarid, lmt_omff, debut, epais) IF (ierr /= nf90_noerr) THEN PRINT*, 'Pb de lecture pour les sources om-ifossil' CALL exit(1) ENDIF DO i = 1, klon lmt_ombb(i) = lmt_bcbb(i) * 7.0 * 1.6 !OC/BC=7.0;OM/OC=1.6 lmt_ombbl(i) = lmt_bcbbl(i) * 7.0 * 1.6 lmt_ombbh(i) = lmt_bcbbh(i) * 7.0 * 1.6 lmt_omff(i) = lmt_omff(i) * 1.4 !--OM/OC=1.4 lmt_omnat(i) = lmt_terp(i) * 0.11 * 1.4 !-- 11% Terpene is OC ENDDO ierr = nf90_close(nid1) PRINT*, 'Carbon sources lues pour jour: ', jour END SUBROUTINE condsurfc