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