SURFEX v8.1
General documentation of Surfex
init_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 init_cpl_gcm_n (U, HPROGRAM,HINIT)
7 ! ########################################
8 !
9 !!**** *INIT_CPL_GCM_n* - routine to read physical fields into
10 !! the restart file for ARPEGE/ALADIN run
11 !!
12 !! PURPOSE
13 !! -------
14 !! The purpose of this routine is to initialise some
15 !! physical fields. Indeed, when ARPEGE/ALADIN is used,
16 !! these field is not initialize at the begin of a run.
17 !!
18 !!
19 !!** METHOD
20 !! ------
21 !! The data are read in the initial surface file :
22 !! - 2D data fields
23 !!
24 !! It does not read the grid definition. This should have been
25 !! read already.
26 !!
27 !! EXTERNAL
28 !! --------
29 !!
30 !!
31 !!
32 !! IMPLICIT ARGUMENTS
33 !! ------------------
34 !!
35 !! REFERENCE
36 !! ---------
37 !!
38 !!
39 !! AUTHOR
40 !! ------
41 !! B. Decharme *Meteo France*
42 !!
43 !! MODIFICATIONS
44 !! -------------
45 !! Original 04/2013
46 !-------------------------------------------------------------------------------
47 !
48 !* 0. DECLARATIONS
49 ! ------------
50 !
51 !
52 !
53 !
54 !
55 !
56 USE modd_surf_atm_n, ONLY : surf_atm_t
57 !
59 !
60 USE yomhook ,ONLY : lhook, dr_hook
61 USE parkind1 ,ONLY : jprb
62 !
63 IMPLICIT NONE
64 !
65 !* 0.1 Declarations of arguments
66 ! -------------------------
67 !
68 !
69 !
70 !
71 TYPE(surf_atm_t), INTENT(INOUT) :: U
72 !
73  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! calling program
74  CHARACTER(LEN=3), INTENT(IN) :: HINIT ! choice of fields to initialize
75 !
76 !* 0.2 Declarations of local variables
77 ! -------------------------------
78 !
79 INTEGER :: IRESP ! Error code after redding
80 !
81  CHARACTER(LEN=12) :: YRECFM ! Name of the article to be read
82 !
83 INTEGER :: IVERSION ! surface version
84 !
85 LOGICAL :: LREAD ! work key
86 LOGICAL :: GCPL_GCM ! work key
87 !
88 REAL(KIND=JPRB) :: ZHOOK_HANDLE
89 !
90 !-------------------------------------------------------------------------------
91 IF (lhook) CALL dr_hook('INIT_CPL_GCM_N',0,zhook_handle)
92 !
93 gcpl_gcm = .false.
94 !
95 IF (hinit=='PGD') THEN
96 !
97  ALLOCATE(u%XRAIN (0))
98  ALLOCATE(u%XSNOW (0))
99  ALLOCATE(u%XZ0 (0))
100  ALLOCATE(u%XZ0H (0))
101  ALLOCATE(u%XQSURF(0))
102 !
103 ELSE
104 !
105  ALLOCATE(u%XRAIN (u%NSIZE_FULL))
106  ALLOCATE(u%XSNOW (u%NSIZE_FULL))
107  ALLOCATE(u%XZ0 (u%NSIZE_FULL))
108  ALLOCATE(u%XZ0H (u%NSIZE_FULL))
109  ALLOCATE(u%XQSURF(u%NSIZE_FULL))
110 !
111  u%XRAIN (:) = 0.0
112  u%XSNOW (:) = 0.0
113  u%XZ0 (:) = 0.001
114  u%XZ0H (:) = 0.001
115  u%XQSURF(:) = 0.0
116 !
117 ENDIF
118 !
119 yrecfm='VERSION'
120  CALL read_surf(hprogram,yrecfm,iversion,iresp)
121 !
122 lread=(hinit/='PGD'.AND.hinit/='PRE'.AND.iversion>=8)
123 !
124 IF (lread) THEN
125  yrecfm='LCPL_GCM'
126  CALL read_surf(hprogram,yrecfm,gcpl_gcm,iresp)
127 ENDIF
128 !
129 IF (lread.AND.gcpl_gcm) THEN
130 !
131  yrecfm='RAIN_GCM'
132  CALL read_surf(hprogram,yrecfm,u%XRAIN(:),iresp)
133 !
134  yrecfm='SNOW_GCM'
135  CALL read_surf(hprogram,yrecfm,u%XSNOW(:),iresp)
136 !
137  yrecfm='Z0_GCM'
138  CALL read_surf(hprogram,yrecfm,u%XZ0(:),iresp)
139 !
140  yrecfm='Z0H_GCM'
141  CALL read_surf(hprogram,yrecfm,u%XZ0H(:),iresp)
142 !
143  yrecfm='QS_GCM'
144  CALL read_surf(hprogram,yrecfm,u%XQSURF(:),iresp)
145 !
146 ENDIF
147 !
148 IF (lhook) CALL dr_hook('INIT_CPL_GCM_N',1,zhook_handle)
149 !-------------------------------------------------------------------------------
150 !
151 END SUBROUTINE init_cpl_gcm_n
integer, parameter jprb
Definition: parkind1.F90:32
subroutine init_cpl_gcm_n(U, HPROGRAM, HINIT)
logical lhook
Definition: yomhook.F90:15