SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
get_cpl_gcmn.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 get_cpl_gcm_n (U, &
7  hprogram,ki,prain,psnow,pz0,pz0h,pqsurf)
8 ! ######################################################
9 !
10 !!**** *GET_CPL_GCM_n* - routine to get physical fields
11 !! for initialise ARPEGE/ALADIN run
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !!
17 !!** METHOD
18 !! ------
19 !!
20 !! EXTERNAL
21 !! --------
22 !!
23 !!
24 !!
25 !! IMPLICIT ARGUMENTS
26 !! ------------------
27 !!
28 !! REFERENCE
29 !! ---------
30 !!
31 !!
32 !! AUTHOR
33 !! ------
34 !! B. Decharme *Meteo France*
35 !!
36 !! MODIFICATIONS
37 !! -------------
38 !! Original 04/2013
39 !-------------------------------------------------------------------------------
40 !
41 !* 0. DECLARATIONS
42 ! ------------
43 !
44 !
45 USE modd_surf_atm_n, ONLY : surf_atm_t
46 !
47 USE modd_surf_atm, ONLY : lcpl_gcm
48 !
49 USE yomhook ,ONLY : lhook, dr_hook
50 USE parkind1 ,ONLY : jprb
51 !
52 USE modi_get_luout
53 USE modi_abor1_sfx
54 !
55 IMPLICIT NONE
56 !
57 !* 0.1 Declarations of arguments
58 ! -------------------------
59 !
60 !
61 TYPE(surf_atm_t), INTENT(INOUT) :: u
62 !
63  CHARACTER(LEN=6), INTENT(IN) :: hprogram
64 INTEGER, INTENT(IN) :: ki ! number of points
65 !
66 REAL, DIMENSION(KI), INTENT(OUT) :: prain ! total rainfall rate (kg/m2/s)
67 REAL, DIMENSION(KI), INTENT(OUT) :: psnow ! total snowfall rate (kg/m2/s)
68 REAL, DIMENSION(KI), INTENT(OUT) :: pz0 ! roughness length for momentum (m)
69 REAL, DIMENSION(KI), INTENT(OUT) :: pz0h ! roughness length for heat (m)
70 REAL, DIMENSION(KI), INTENT(OUT) :: pqsurf ! specific humidity at surface (kg/kg)
71 !
72 !* 0.2 Declarations of local variables
73 ! -------------------------------
74 !
75 INTEGER :: iluout
76 !
77 REAL(KIND=JPRB) :: zhook_handle
78 !
79 !-------------------------------------------------------------------------------
80 IF (lhook) CALL dr_hook('GET_CPL_GCM_N',0,zhook_handle)
81 !
82  CALL get_luout(hprogram,iluout)
83 !
84 IF(lcpl_gcm) THEN
85 !
86  IF(SIZE(pz0)/=SIZE(u%XZ0H))THEN
87  WRITE(iluout,*)'try to get Z0 field from atmospheric model, but size is not correct'
88  WRITE(iluout,*)'size of field expected by the atmospheric model (PZ0) :', SIZE(pz0)
89  WRITE(iluout,*)'size of field in SURFEX (XZ0) :', SIZE(u%XZ0)
90  CALL abor1_sfx('GET_CPL_GCMN: PZ0 ARGUMENT SIZE /= XZ0 MODULE SIZE')
91  ENDIF
92 !
93  prain(:) = u%XRAIN
94  psnow(:) = u%XSNOW
95  pz0(:) = u%XZ0
96  pz0h(:) = u%XZ0H
97  pqsurf(:) = u%XQSURF
98 !
99 ELSE
100 !
101  WRITE(iluout,*)'LCPL_GCM must be TRUE when you use atmospheric model'
102  CALL abor1_sfx('GET_CPL_GCMN: LCPL_GCM must be TRUE')
103 !
104 ENDIF
105 
106 !
107 IF (lhook) CALL dr_hook('GET_CPL_GCM_N',1,zhook_handle)
108 !-------------------------------------------------------------------------------
109 !
110 END SUBROUTINE get_cpl_gcm_n
subroutine get_cpl_gcm_n(U, HPROGRAM, KI, PRAIN, PSNOW, PZ0, PZ0H, PQSURF)
Definition: get_cpl_gcmn.F90:6
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6