SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
pgd_grid_surf_atm.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 pgd_grid_surf_atm (&
7  ug, u, &
8  hprogram,hfile,hfiletype,ogrid)
9 ! ###########################################################
10 !!
11 !! PURPOSE
12 !! -------
13 !! This program prepares the physiographic data fields.
14 !!
15 !! METHOD
16 !! ------
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !!
26 !! REFERENCE
27 !! ---------
28 !!
29 !! AUTHOR
30 !! ------
31 !!
32 !! V. Masson Meteo-France
33 !!
34 !! MODIFICATION
35 !! ------------
36 !!
37 !! Original 13/10/03
38 !----------------------------------------------------------------------------
39 !
40 !* 0. DECLARATION
41 ! -----------
42 !
43 !
44 !
45 !
46 !
47 !
49 USE modd_surf_atm_n, ONLY : surf_atm_t
50 !
51 USE modd_surf_par, ONLY : nversion, nbugfix
52 USE modd_surf_conf, ONLY : cprogname
53 USE modd_pgd_grid, ONLY : llatlonmask, nl
54 !
55 USE modi_pgd_grid
56 USE modi_ini_csts
57 !
58 USE yomhook ,ONLY : lhook, dr_hook
59 USE parkind1 ,ONLY : jprb
60 !
61 USE modi_pgd_grid_io_init
62 USE modi_surf_version
63 !
64 IMPLICIT NONE
65 !
66 !* 0.1 Declaration of dummy arguments
67 ! ------------------------------
68 !
69 !
70 !
71 !
72 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
73 TYPE(surf_atm_t), INTENT(INOUT) :: u
74 !
75  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
76  CHARACTER(LEN=28), INTENT(IN) :: hfile ! atmospheric file name
77  CHARACTER(LEN=6), INTENT(IN) :: hfiletype! atmospheric file type
78 LOGICAL, INTENT(IN) :: ogrid ! .true. if grid is imposed by atm. model
79 REAL(KIND=JPRB) :: zhook_handle
80 !
81 !
82 !* 0.2 Declaration of local variables
83 ! ------------------------------
84 !
85  CHARACTER(LEN=100) :: ycomment
86 INTEGER :: iresp ! error return code
87 !------------------------------------------------------------------------------
88 IF (lhook) CALL dr_hook('PGD_GRID_SURF_ATM',0,zhook_handle)
89  cprogname=hprogram
90 !
91 !* 1. Set default constant values
92 ! ---------------------------
93 !
94  CALL surf_version
95 !
96  CALL ini_csts
97 !
98 !-------------------------------------------------------------------------------
99 !
100 !* 2. Initialisation of output grid
101 ! -----------------------------
102 !
103  CALL pgd_grid(&
104  ug, u, &
105  hprogram,hfile,hfiletype,ogrid,ug%CGRID,ug%NGRID_PAR,ug%XGRID_PAR)
106 !
107 !
108 !-------------------------------------------------------------------------------
109 !
110 !
111 !* 3. Additional actions for I/O
112 !
113  CALL pgd_grid_io_init(hprogram)
114 !
115 IF (lhook) CALL dr_hook('PGD_GRID_SURF_ATM',1,zhook_handle)
116 !_______________________________________________________________________________
117 !
118 END SUBROUTINE pgd_grid_surf_atm
subroutine pgd_grid_surf_atm(UG, U, HPROGRAM, HFILE, HFILETYPE, OGRID)
subroutine pgd_grid_io_init(HPROGRAM)
subroutine ini_csts
Definition: ini_csts.F90:6
subroutine surf_version
Definition: surf_version.F90:6
subroutine pgd_grid(UG, U, HPROGRAM, HFILE, HFILETYPE, OGRID, HGRID, KGRID_PAR, PGRID_PAR)
Definition: pgd_grid.F90:6