SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
carbon_spinup.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6  SUBROUTINE carbon_spinup(KMONTH,KDAY,PTIME, &
7  ospinupcarbs, ospinupcarbw, pspinmaxs, pspinmaxw, &
8  knbyearspins, knbyearspinw, knbyearsold, hphoto, &
9  hrespsl, kspins, kspinw )
10 
11 ! #######################################################################
12 !
13 !
14 !!**** *CARBON_SPINUP*
15 !!
16 !! PURPOSE
17 !! -------
18 ! Number of times the accelerated subroutine is called
19 ! for each time step
20 !!** METHOD
21 !! ------
22 !
23 !! EXTERNAL
24 !! --------
25 !!
26 !! IMPLICIT ARGUMENTS
27 !! ------------------
28 !!
29 !!
30 !! REFERENCE
31 !! ---------
32 !!
33 !! AUTHOR
34 !! ------
35 !! R. Alkama * Meteo-France *
36 !!
37 !! MODIFICATIONS
38 !! -------------
39 !! Original 03/26/2012
40 !!
41 !-------------------------------------------------------------------------------
42 !
43 !* 0. DECLARATIONS
44 ! ------------
45 !
46 !
47 USE modi_spinup_max
48 !
49 USE yomhook ,ONLY : lhook, dr_hook
50 USE parkind1 ,ONLY : jprb
51 !
52 IMPLICIT NONE
53 !
54  CHARACTER(LEN=3), INTENT(IN) :: hrespsl ! Soil Respiration
55 ! ! 'DEF' = Norman 1992
56 ! ! 'PRM' = Rivalland PhD Thesis (2003)
57 ! ! 'CNT' = CENTURY model (Gibelin 2008)
58  CHARACTER(LEN=3), INTENT(IN) :: hphoto ! type of photosynthesis
59 !
60 INTEGER, INTENT(IN) :: kmonth ! Current month
61 INTEGER, INTENT(IN) :: kday ! Current day
62 REAL, INTENT(IN) :: ptime ! Current time
63 LOGICAL, INTENT(IN) :: ospinupcarbs ! T: do the soil carb spinup, F: no
64 LOGICAL, INTENT(IN) :: ospinupcarbw ! T: do the wood carb spinup, F: no
65 REAL, INTENT(IN) :: pspinmaxs ! max number of times CARBON_SOIL subroutine
66 REAL, INTENT(IN) :: pspinmaxw ! max number of times the wood is accelerated
67 INTEGER, INTENT(IN) :: knbyearspins ! nbr years needed to reaches soil equilibrium
68 INTEGER, INTENT(IN) :: knbyearspinw ! nbr years needed to reaches wood equilibrium
69 !
70 INTEGER, INTENT(INOUT) :: knbyearsold ! nbr years executed at curent time step
71 INTEGER, INTENT(OUT) :: kspins ! number of times the soil is accelerated
72 INTEGER, INTENT(OUT) :: kspinw ! number of times the wood is accelerated
73 !
74 !* 0. declarations of local variables
75 !
76 REAL(KIND=JPRB) :: zhook_handle
77 !
78 !-------------------------------------------------------------------------------
79 !
80 IF (lhook) CALL dr_hook('CARBON_SPINUP',0,zhook_handle)
81 !
82 ! 1. Initializations
83 ! ---------------
84 !
85 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
86 ! number of times CARBON_SOIL subroutine is called for each time step
87 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
88 kspins =1
89 IF ( ospinupcarbs .AND. hphoto/='NON' .AND. hrespsl=='CNT' ) THEN
90  CALL spinup_max(pspinmaxs,knbyearspins,knbyearsold,kspins)
91 ENDIF
92 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
93 ! number of times WOOD carbon subroutine is called for each time step
94 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
95 kspinw=1
96 IF ( ospinupcarbw .AND. hphoto=='NCB' ) THEN
97  CALL spinup_max(pspinmaxw,knbyearspinw,knbyearsold,kspinw)
98 ENDIF
99 !
100 IF (kmonth == 1 .AND. kday==1 .AND. ptime == 0.0 )THEN
101  knbyearsold = knbyearsold + 1
102 ENDIF
103 !
104 IF (lhook) CALL dr_hook('CARBON_SPINUP',1,zhook_handle)
105 !
106 !
107 !-------------------------------------------------------------------------------
108 !
109 END SUBROUTINE
subroutine carbon_spinup(KMONTH, KDAY, PTIME, OSPINUPCARBS, OSPINUPCARBW, PSPINMAXS, PSPINMAXW, KNBYEARSPINS, KNBYEARSPINW, KNBYEARSOLD, HPHOTO, HRESPSL, KSPINS, KSPINW)
subroutine spinup_max(PSPINMAX, KNBYEARSPIN, KNBYEARSOLD, KSPIN)
Definition: spinup_max.F90:6