SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
tridiag_ground_rm_soln.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 tridiag_ground_rm_soln(PSOLN,PA_COEF,PB_COEF)
7 !
8 !
9 !!**** *TRIDIAG_GROUND_RM_SOLN*
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 ! Back substitution ("downward sweep") for solution of a tri-diagnoal matrix using
15 ! the method of Richtmeyer and Morton (1967), given coefficients A and B.
16 !
17 !!** METHOD
18 !! ------
19 !
20 !! EXTERNAL
21 !! --------
22 !!
23 !! none
24 !!
25 !! IMPLICIT ARGUMENTS
26 !! ------------------
27 !!
28 !!
29 !! REFERENCE
30 !! ---------
31 !
32 ! Richtmeyer, R. and K. Morton, 1967: Difference method for initial values problems,
33 ! Interscience Publishers, 2.
34 !
35 !! AUTHOR
36 !! ------
37 !!
38 !! A. Boone * Meteo-France *
39 !!
40 !! MODIFICATIONS
41 !! -------------
42 !! Original 21/03/11
43 !! Modif 23/02/12 A. Boone: Optimization
44 !! Modif 03/2013 A. Boone: MEB
45 !
46 !-------------------------------------------------------------------------------
47 !
48 !* 0. DECLARATIONS
49 ! ------------
50 !
51 USE yomhook ,ONLY : lhook, dr_hook
52 USE parkind1 ,ONLY : jprb
53 !
54 IMPLICIT NONE
55 !
56 !
57 !* 0.1 declarations of arguments
58 !
59 REAL, DIMENSION(:,:), INTENT(IN) :: pa_coef ! RM67 A-soil coefficient (-)
60 REAL, DIMENSION(:,:), INTENT(IN) :: pb_coef ! RM67 B-soil coefficient (K)
61 !
62 REAL, DIMENSION(:,:), INTENT(INOUT) :: psoln ! solution vector
63 ! ! of the input variable (*)
64 !
65 !* 0.2 declarations of local variables
66 !
67 INTEGER :: jj, ji
68 !
69 REAL(KIND=JPRB) :: zhook_handle
70 !------------------------------------------------------------------------
71 !
72 IF (lhook) CALL dr_hook('TRIDIAG_GROUND_RM_SOLN',0,zhook_handle)
73 !
74 ! Get the solution vector.
75 ! NOTE: surface value obtained in energy budget routine, so
76 ! this is the *sub-surface* profile solution.
77 !
78 DO jj=2,SIZE(psoln,2)
79  DO ji=1,SIZE(psoln,1)
80  psoln(ji,jj) = pa_coef(ji,jj)*psoln(ji,jj-1) + pb_coef(ji,jj)
81  ENDDO
82 ENDDO
83 !
84 IF (lhook) CALL dr_hook('TRIDIAG_GROUND_RM_SOLN',1,zhook_handle)
85 !------------------------------------------------------------------------
86 END SUBROUTINE tridiag_ground_rm_soln
subroutine tridiag_ground_rm_soln(PSOLN, PA_COEF, PB_COEF)