SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
modd_dummy_surf_fieldsn.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 ! ####################
7 ! ####################
8 !
9 !!**** *MODD_DUMMY_SURF_FIELDS* - declaration of dummy physiographic data arrays
10 !!
11 !! PURPOSE
12 !! -------
13 ! The purpose of this declarative module is to specify the
14 ! dummy physiographic data arrays.
15 !
16 !!
17 !! AUTHOR
18 !! ------
19 !! V. Masson *Meteo France*
20 !!
21 !! MODIFICATIONS
22 !! -------------
23 !! Original 03/2004
24 !-------------------------------------------------------------------------------
25 !
26 !* 0. DECLARATIONS
27 ! ------------
28 !
29 !
30 USE yomhook ,ONLY : lhook, dr_hook
31 USE parkind1 ,ONLY : jprb
32 !
33 IMPLICIT NONE
34 
36 !
37  INTEGER :: NDUMMY_NBR
38 ! ! number of dummy pgd fields chosen by user
39  CHARACTER(LEN=3) , DIMENSION(:), POINTER :: CDUMMY_AREA
40 ! ! areas where dummy pgd fields are defined
41 ! ! 'ALL' : everywhere
42 ! ! 'SEA' : where sea exists
43 ! ! 'LAN' : where land exists
44 ! ! 'WAT' : where inland water exists
45 ! ! 'NAT' : where natural or agricultural areas exist
46 ! ! 'TWN' : where town areas exist
47 ! ! 'STR' : where streets are present
48 ! ! 'BLD' : where buildings are present
49 ! !
50  CHARACTER(LEN=20), DIMENSION(:), POINTER :: CDUMMY_NAME
51 ! ! name of the dummy pgd fields (for information)
52  REAL, DIMENSION(:,:), POINTER :: XDUMMY_FIELDS
53 ! ! dummy pgd fields themselves
54 !
55 !-------------------------------------------------------------------------------
56 !
57 END TYPE dummy_surf_fields_t
58 
59  CONTAINS
60 !
61 !
62 SUBROUTINE dummy_surf_fields_init(YDUMMY_SURF_FIELDS)
63 TYPE(dummy_surf_fields_t), INTENT(INOUT) :: ydummy_surf_fields
64 REAL(KIND=JPRB) :: zhook_handle
65 IF (lhook) CALL dr_hook("MODD_DUMMY_SURF_FIELDS_N:DUMMY_SURF_FIELDS_INIT",0,zhook_handle)
66  nullify(ydummy_surf_fields%CDUMMY_NAME)
67  nullify(ydummy_surf_fields%CDUMMY_AREA)
68  nullify(ydummy_surf_fields%XDUMMY_FIELDS)
69 ydummy_surf_fields%NDUMMY_NBR=0
70 IF (lhook) CALL dr_hook("MODD_DUMMY_SURF_FIELDS_N:DUMMY_SURF_FIELDS_INIT",1,zhook_handle)
71 END SUBROUTINE dummy_surf_fields_init
72 
73 
74 END MODULE modd_dummy_surf_fields_n
subroutine dummy_surf_fields_init(YDUMMY_SURF_FIELDS)