SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
spinup_max.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 spinup_max(PSPINMAX,KNBYEARSPIN,KNBYEARSOLD,KSPIN)
7 
8 ! #######################################################################
9 !
10 !
11 !!**** *SPINUP_MAX*
12 !!
13 !! PURPOSE
14 !! -------
15 !! Number of times the accelerated subroutine is called
16 !!
17 !!** METHOD
18 !! ------
19 !!
20 !! EXTERNAL
21 !! --------
22 !!
23 !! IMPLICIT ARGUMENTS
24 !! ------------------
25 !!
26 !!
27 !! REFERENCE
28 !! ---------
29 !!
30 !! AUTHOR
31 !! ------
32 !! R. Alkama * Meteo-France *
33 !!
34 !! MODIFICATIONS
35 !! -------------
36 !! Original 03/26/2012
37 !-------------------------------------------------------------------------------
38 !
39 !* 0. DECLARATIONS
40 ! ------------
41 !
42 USE modd_co2v_par, ONLY : xspin_co2
43 !
44 USE yomhook ,ONLY : lhook, dr_hook
45 USE parkind1 ,ONLY : jprb
46 !
47 IMPLICIT NONE
48 !
49 !* 0.1 declarations of arguments
50 !
51 !
52 REAL, INTENT(IN) :: pspinmax ! max number of times the accelerated subroutine
53  ! is called for each time step in simulation
54  ! during the acceleration procedure
55 
56 INTEGER, INTENT(IN) :: knbyearspin ! spinup duration in years
57  ! nbr of years needed to reach the equilibrium
58 INTEGER, INTENT(IN) :: knbyearsold
59 INTEGER, INTENT(OUT) :: kspin
60 !
61 !
62 !* 0.2 declarations of local variables
63 !
64 !We assume that 10% of the spinup period is for ramping up CO2 concentration
65 !from XCO2_START to XCO2_END
66 !
67 REAL, PARAMETER :: zspin_max = 0.6 ! spin up soil at its maximum PSPINMAX
68 REAL :: zspin_decrease ! fraction of KNBYEARSPIN period used to
69 !
70 REAL :: zslope
71 REAL :: zmax
72 REAL :: zdecrease
73 !
74 INTEGER :: imax
75 INTEGER :: idecrease
76 !
77 REAL(KIND=JPRB) :: zhook_handle
78 !
79 !-------------------------------------------------------------------------------
80 !
81 ! 1. Initializations
82 ! ---------------
83 !
84 IF (lhook) CALL dr_hook('SPINUP_MAX',0,zhook_handle)
85 !
86 zspin_decrease=1.0-zspin_max-xspin_co2
87 !
88 zmax = zspin_max*REAL(knbyearspin)
89 imax = nint(zmax)
90 !
91 zdecrease = zmax+zspin_decrease*REAL(knbyearspin)
92 idecrease = nint(zdecrease)
93 !
94 IF ( knbyearsold <= imax)THEN
95  !
96  kspin = nint(pspinmax)
97  !
98 ELSE IF (knbyearsold > imax .AND. knbyearsold <= idecrease)THEN
99  !
100  zslope = (pspinmax-1.0) / (zdecrease - zmax)
101  !
102  kspin = nint(pspinmax - zslope * (REAL(KNBYEARSOLD) - zmax))
103  !
104  kspin = max(kspin,1)
105  !
106 ELSE
107  !
108  kspin = 1
109  !
110 ENDIF
111 !
112 IF (lhook) CALL dr_hook('SPINUP_MAX',1,zhook_handle)
113 !
114 !
115 !-------------------------------------------------------------------------------
116 !
117 END SUBROUTINE
subroutine spinup_max(PSPINMAX, KNBYEARSPIN, KNBYEARSOLD, KSPIN)
Definition: spinup_max.F90:6