SURFEX v8.1
General documentation of Surfex
init_townn.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_town_n (DTCO, OREAD_BUDGETC, UG, U, GCP, TM, GDM, GRM, DGO, DL, DLC, &
7  HPROGRAM,HINIT,KI,KSV,KSW, HSV,PCO2,PRHOA, &
8  PZENITH,PAZIM,PSW_BANDS,PDIR_ALB,PSCA_ALB, &
9  PEMIS,PTSRAD,PTSURF,KYEAR,KMONTH,KDAY,PTIME, &
10  HATMFILE,HATMFILETYPE,HTEST )
11 ! #############################################################
12 !
13 !!**** *INIT_TOWN_n* - chooses initialization routine for towns
14 !!
15 !! PURPOSE
16 !! -------
17 !!
18 !!** METHOD
19 !! ------
20 !!
21 !! EXTERNAL
22 !! --------
23 !!
24 !!
25 !! IMPLICIT ARGUMENTS
26 !! ------------------
27 !!
28 !! REFERENCE
29 !! ---------
30 !!
31 !!
32 !! AUTHOR
33 !! ------
34 !! V. Masson *Meteo France*
35 !!
36 !! MODIFICATIONS
37 !! -------------
38 !! Original 27/09/96
39 !! V.Masson 18/08/97 call to fmread directly with dates and strings
40 !! V.Masson 15/03/99 new PGD treatment with COVER types
41 ! F.Solmon 06/00 adaptation for patch approach
42 !! B.Decharme 04/2013 new coupling variables
43 !-------------------------------------------------------------------------------
44 !
45 !* 0. DECLARATIONS
46 ! ------------
47 !
48 !
51 USE modd_surf_atm_n, ONLY : surf_atm_t
53 USE modd_surfex_n, ONLY : teb_model_t
57 !
58 USE modd_csts, ONLY : xtt
59 !
60 USE yomhook ,ONLY : lhook, dr_hook
61 USE parkind1 ,ONLY : jprb
62 !
63 USE modi_init_ideal_flux
64 !
65 USE modi_init_teb_n
66 !
67 IMPLICIT NONE
68 !
69 !* 0.1 Declarations of arguments
70 ! -------------------------
71 !
72 LOGICAL, INTENT(IN) :: OREAD_BUDGETC
73 !
74 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
75 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
76 TYPE(surf_atm_t), INTENT(INOUT) :: U
77 TYPE(grid_conf_proj_t),INTENT(INOUT) :: GCP
78 TYPE(teb_model_t), INTENT(INOUT) :: TM
79 TYPE(teb_garden_model_t), INTENT(INOUT) :: GDM
80 TYPE(teb_greenroof_model_t), INTENT(INOUT) :: GRM
81 TYPE(diag_options_t), INTENT(INOUT) :: DGO
82 TYPE(diag_t), INTENT(INOUT) :: DL
83 TYPE(diag_t), INTENT(INOUT) :: DLC
84 !
85 !
86  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
87  CHARACTER(LEN=3), INTENT(IN) :: HINIT ! choice of fields to initialize
88 INTEGER, INTENT(IN) :: KI ! number of points
89 INTEGER, INTENT(IN) :: KSV ! number of scalars
90 INTEGER, INTENT(IN) :: KSW ! number of short-wave spectral bands
91  CHARACTER(LEN=6), DIMENSION(KSV), INTENT(IN) :: HSV ! name of all scalar variables
92 REAL, DIMENSION(KI), INTENT(IN) :: PCO2 ! CO2 concentration (kg/m3)
93 REAL, DIMENSION(KI), INTENT(IN) :: PRHOA ! air density
94 REAL, DIMENSION(KI), INTENT(IN) :: PZENITH ! solar zenithal angle
95 REAL, DIMENSION(KI), INTENT(IN) :: PAZIM ! solar azimuthal angle (rad from N, clock)
96 REAL, DIMENSION(KSW), INTENT(IN) :: PSW_BANDS ! middle wavelength of each band
97 REAL, DIMENSION(KI,KSW),INTENT(OUT) :: PDIR_ALB ! direct albedo for each band
98 REAL, DIMENSION(KI,KSW),INTENT(OUT) :: PSCA_ALB ! diffuse albedo for each band
99 REAL, DIMENSION(KI), INTENT(OUT) :: PEMIS ! emissivity
100 REAL, DIMENSION(KI), INTENT(OUT) :: PTSRAD ! radiative temperature
101 REAL, DIMENSION(KI), INTENT(OUT) :: PTSURF ! surface effective temperature (K)
102 INTEGER, INTENT(IN) :: KYEAR ! current year (UTC)
103 INTEGER, INTENT(IN) :: KMONTH ! current month (UTC)
104 INTEGER, INTENT(IN) :: KDAY ! current day (UTC)
105 REAL, INTENT(IN) :: PTIME ! current time since
106  ! midnight (UTC, s)
107 !
108  CHARACTER(LEN=28), INTENT(IN) :: HATMFILE ! atmospheric file name
109  CHARACTER(LEN=6), INTENT(IN) :: HATMFILETYPE! atmospheric file type
110  CHARACTER(LEN=2), INTENT(IN) :: HTEST ! must be equal to 'OK'
111 REAL(KIND=JPRB) :: ZHOOK_HANDLE
112 !
113 !
114 !
115 !* 0.2 Declarations of local variables
116 ! -------------------------------
117 !
118 !-------------------------------------------------------------------------------
119 !
120 !* 2. Selection of surface scheme
121 ! ---------------------------
122 !
123 IF (lhook) CALL dr_hook('INIT_TOWN_N',0,zhook_handle)
124 IF (u%CTOWN=='NONE ') THEN
125  pdir_alb=0.
126  psca_alb=0.
127  pemis =1.
128  ptsrad =xtt
129  ptsurf =xtt
130 ELSE IF (u%CTOWN=='FLUX ') THEN
131  CALL init_ideal_flux(dgo, dl, dlc, oread_budgetc, &
132  hprogram,hinit,ki,ksv,ksw,hsv,pdir_alb,psca_alb, &
133  pemis,ptsrad,ptsurf,'OK' )
134 ELSE IF (u%CTOWN=='TEB ') THEN
135  CALL init_teb_n(dtco, ug, u, gcp, tm%CHT, tm%DTT, tm%SB, tm%G, tm%TOP, &
136  tm%TPN, tm%TIR, tm%NT, tm%TD, tm%BDD, tm%BOP, tm%DTB, tm%NB, &
137  gdm, grm, hprogram, hinit, ki, ksv, ksw, hsv, pco2, &
138  prhoa, pzenith, pazim, psw_bands, pdir_alb, &
139  psca_alb, pemis, ptsrad, ptsurf, kyear, kmonth, &
140  kday, ptime, hatmfile, hatmfiletype, 'OK' )
141 END IF
142 IF (lhook) CALL dr_hook('INIT_TOWN_N',1,zhook_handle)
143 !
144 !-------------------------------------------------------------------------------
145 END SUBROUTINE init_town_n
subroutine init_teb_n(DTCO, UG, U, GCP, CHT, DTT, SB, TG, TOP, TP
Definition: init_tebn.F90:7
subroutine init_ideal_flux(DGO, D, DC, OREAD_BUDGETC, HPROGRAM, HINIT, KI, KSV, KSW, HSV, PDIR_ALB, PSCA_ALB, PEMIS, PTSRAD, PTSURF, HTEST)
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
real, save xtt
Definition: modd_csts.F90:66
subroutine init_town_n(DTCO, OREAD_BUDGETC, UG, U, GCP, TM, GDM,
Definition: init_townn.F90:7