SURFEX v7.3
General documentation of Surfex
 All Classes Files Functions Variables Typedefs
/home/dasprezs/EXPORT_v7_3/src/SURFEX/soil_temp_arp.F90
Go to the documentation of this file.
00001 !     #########
00002       SUBROUTINE SOIL_TEMP_ARP(PTSTEP,PA,PB,PC,PGAMMAT,PTDEEP,PSODELX,PTG)
00003 !     ############################################################
00004 !
00005 !!****  *SOIL_TEMP_ARP*  
00006 !
00007 !!    PURPOSE
00008 !!    -------
00009 !     This subroutine solves the ARPEGE 1-d surface and deep force-restore 
00010 !     'PTG' using the backward-difference scheme (implicit) as in soil_heatdiff. 
00011 !     The eqs are solved rapidly by taking advantage of the
00012 !     fact that the matrix is tridiagonal. Soln to the eqs:
00013 !
00014 !                   dTi       S1   
00015 !                   --- =  Ct --  (Gi - Gi+1)
00016 !                   dt        Si
00017 !
00018 !     with        |  G1 = Rn-H-LE
00019 !                 |
00020 !                 |         2Pi         1
00021 !                 |  Gi = ------  -------------- (Ti-1 - Ti) 
00022 !                 |       Ct*Day  S1 (Si-1 + Si)
00023 !                 
00024 !
00025 !     where Si = pulsation depth, i=1 is the surface
00026 !     
00027 !!**  METHOD
00028 !!    ------
00029 !
00030 !     Direct calculation
00031 !
00032 !!    EXTERNAL
00033 !!    --------
00034 !
00035 !     None
00036 !!
00037 !!    IMPLICIT ARGUMENTS
00038 !!    ------------------
00039 !!
00040 !!    USE MODD_SURF_PAR
00041 !!    USE MODI_TRIDIAG_GROUND
00042 !!      
00043 !!    REFERENCE
00044 !!    ---------
00045 !!      
00046 !!    AUTHOR
00047 !!    ------
00048 !!      B. Decharme          * Meteo-France *
00049 !!
00050 !!    MODIFICATIONS
00051 !!    -------------
00052 !!      Original    21/01/09   B. Decharme
00053 !
00054 !-------------------------------------------------------------------------------
00055 !
00056 !*       0.     DECLARATIONS
00057 !               ------------
00058 !
00059 USE MODD_CSTS,       ONLY : XPI, XDAY
00060 !
00061 USE MODD_SURF_PAR,   ONLY : XUNDEF
00062 !
00063 USE MODI_TRIDIAG_GROUND
00064 !
00065 !
00066 USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
00067 USE PARKIND1  ,ONLY : JPRB
00068 !
00069 IMPLICIT NONE
00070 !
00071 !
00072 REAL, INTENT(IN)                   :: PTSTEP ! Model time step (s)
00073 !
00074 REAL, DIMENSION(:), INTENT(IN)     :: PA,PB,PC ! terms for the linearization of Ts(t)
00075 !
00076 REAL, DIMENSION(:), INTENT(IN)     :: PTDEEP, PGAMMAT
00077 !                                     PTDEEP   = Deep soil temperature (prescribed)
00078 !                                                which models heating/cooling from
00079 !                                                below the diurnal wave penetration
00080 !                                               (surface temperature) depth.
00081 !                                      PGAMMAT  = Deep soil heat transfer coefficient:
00082 !                                                assuming homogeneous soil so that
00083 !                                                this can be prescribed in units of 
00084 !                                                (1/days): associated time scale with
00085 !                                                PTDEEP.
00086 REAL, DIMENSION(:), INTENT (IN)     ::  PSODELX   ! Pulsation for each layer (Only used if LTEMP_ARP=True)
00087 !
00088 REAL, DIMENSION(:,:), INTENT(INOUT) :: PTG
00089 !                                      PTG    = soil temperature (K)
00090 !
00091 !
00092 !*      0.2    declarations of local variables
00093 !
00094 INTEGER                             :: JJ ! Loop counter
00095 !
00096 INTEGER                             :: INLVLD ! Number of points and grid layers
00097 !
00098 REAL, DIMENSION(SIZE(PTG,1),SIZE(PTG,2))  :: ZTGM, ZFRCV, ZAMTRX, ZBMTRX,     
00099                                              ZCMTRX, ZLAMBDA, ZALPHA  
00100 REAL(KIND=JPRB) :: ZHOOK_HANDLE
00101 !
00102 !-------------------------------------------------------------------------------
00103 !
00104 ! Initialize local variables:
00105 !
00106 IF (LHOOK) CALL DR_HOOK('SOIL_TEMP_ARP',0,ZHOOK_HANDLE)
00107 INLVLD = SIZE(PTG(:,:),2)
00108 !
00109 ZTGM(:,:)      = PTG(:,:)
00110 !
00111 ZFRCV  (:,:)   = 0.0
00112 ZAMTRX (:,:)   = 0.0
00113 ZBMTRX (:,:)   = 0.0
00114 ZCMTRX (:,:)   = 0.0
00115 ZALPHA (:,:)   = 0.0
00116 ZLAMBDA(:,:)   = 0.0
00117 !
00118 !-------------------------------------------------------------------------------
00119 !
00120 ! Calculate tri-diagonal matrix coefficients:
00121 !
00122 !
00123 DO JJ=1,INLVLD-1
00124    ZALPHA (:,JJ) = PSODELX(JJ)*XDAY/(PTSTEP*PSODELX(1)*2.0*XPI)
00125    ZLAMBDA(:,JJ) = 1.0/(PSODELX(1)*(PSODELX(JJ)+PSODELX(JJ+1)))
00126 ENDDO
00127 ZALPHA(:,INLVLD) = PSODELX(INLVLD)*XDAY/(PTSTEP*PSODELX(1)*2.0*XPI)
00128 !
00129 !-------------------------------------------------------------------------------
00130 !
00131 ! Upper BC
00132 !
00133 ZAMTRX(:,1) =  0.0
00134 ZBMTRX(:,1) =  PA(:)+(2.0*XPI/XDAY)*(1.0/(PSODELX(1)*(PSODELX(1)+PSODELX(2)))-1.0)
00135 ZCMTRX(:,1) = -2.0*XPI/(XDAY*PSODELX(1)*(PSODELX(1)+PSODELX(2)))
00136 ZFRCV (:,1) =  PB(:)*ZTGM(:,1)+PC(:)-2.0*XPI*ZTGM(:,2)/XDAY
00137 !
00138 !
00139 ! Interior Grid
00140 !
00141 DO JJ=2,INLVLD-1
00142    ZAMTRX(:,JJ) = -ZLAMBDA(:,JJ-1) 
00143    ZBMTRX(:,JJ) =  ZALPHA(:,JJ) + ZLAMBDA(:,JJ-1) + ZLAMBDA(:,JJ)
00144    ZCMTRX(:,JJ) = -ZLAMBDA(:,JJ)
00145    ZFRCV(:,JJ)  =  ZALPHA(:,JJ)*ZTGM(:,JJ) 
00146 ENDDO
00147 !
00148 ! Lower BC: 2 currently accounted for, Either zero flux
00149 ! or a fixed temperature 'TDEEP' 
00150 !
00151 ZAMTRX(:,INLVLD) = -ZLAMBDA(:,INLVLD-1) 
00152 ZCMTRX(:,INLVLD) =  0.0                
00153 !
00154 WHERE(PTDEEP(:) /= XUNDEF .AND. PGAMMAT(:) /= XUNDEF)
00155    ZBMTRX(:,INLVLD) =  ZALPHA(:,INLVLD) + ZLAMBDA(:,INLVLD-1) + PTSTEP*PGAMMAT(:)/XDAY
00156    ZFRCV (:,INLVLD) =  ZALPHA(:,INLVLD)*ZTGM(:,INLVLD) + PTSTEP*PGAMMAT(:)*PTDEEP(:)/XDAY
00157 ELSEWHERE
00158    ZBMTRX(:,INLVLD) =  ZALPHA(:,INLVLD) + ZLAMBDA(:,INLVLD-1) 
00159    ZFRCV (:,INLVLD) =  ZALPHA(:,INLVLD)*ZTGM(:,INLVLD) 
00160 END WHERE
00161 !
00162 !-------------------------------------------------------------------------------
00163 !
00164 ! Compute ZTGM (solution vector) 
00165 ! used for systems of equations involving tridiagonal 
00166 ! matricies.
00167 !
00168  CALL TRIDIAG_GROUND(ZAMTRX,ZBMTRX,ZCMTRX,ZFRCV,ZTGM)
00169 !
00170 ! Update values in time:
00171 !
00172 PTG(:,:) = ZTGM(:,:)
00173 !
00174 IF (LHOOK) CALL DR_HOOK('SOIL_TEMP_ARP',1,ZHOOK_HANDLE)
00175 !
00176 !-------------------------------------------------------------------------------
00177 !
00178 END SUBROUTINE SOIL_TEMP_ARP