SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
prep_flake_ascllv.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 prep_flake_ascllv (DTCO, UG, U, USS, &
7  hprogram,hsurf,kluout,pfield)
8 ! #################################################################################
9 !
10 !!**** *PREP_FLAKE_ASCLLV* - prepares FLAKE field from prescribed values
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 !!** METHOD
16 !! ------
17 !!
18 !! REFERENCE
19 !! ---------
20 !!
21 !!
22 !! AUTHOR
23 !! ------
24 !! P. Le Moigne
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 03/2007
29 !!------------------------------------------------------------------
30 !
31 !
32 !
33 !
34 !
35 !
38 USE modd_surf_atm_n, ONLY : surf_atm_t
40 !
41 USE modd_prep, ONLY : cinterp_type
42 USE modd_pgd_grid, ONLY : nl,llatlonmask,cgrid,xgrid_par,ngrid_par
43 USE modd_pgdwork, ONLY : catype
44 USE modd_surf_par, ONLY : xundef
45 USE modd_prep_flake, ONLY : ctype, cfile_flake
46 USE modi_pgd_field
47 USE modi_get_latlonmask_n
48 !
49 !
50 USE yomhook ,ONLY : lhook, dr_hook
51 USE parkind1 ,ONLY : jprb
52 !
53 USE modi_get_type_dim_n
54 !
55 IMPLICIT NONE
56 !
57 !* 0.1 declarations of arguments
58 !
59 !
60 TYPE(data_cover_t), INTENT(INOUT) :: dtco
61 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
62 TYPE(surf_atm_t), INTENT(INOUT) :: u
63 TYPE(surf_atm_sso_t), INTENT(INOUT) :: uss
64 !
65  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling surf. schemes
66  CHARACTER(LEN=7), INTENT(IN) :: hsurf ! type of field
67 INTEGER, INTENT(IN) :: kluout ! logical unit of output listing
68 REAL, POINTER, DIMENSION(:,:) :: pfield ! field to interpolate horizontally
69 !
70 !* 0.2 declarations of local variables
71 !
72 INTEGER :: il
73 !
74 REAL, ALLOCATABLE, DIMENSION(:) :: zfield
75 REAL(KIND=JPRB) :: zhook_handle
76 !
77 !-------------------------------------------------------------------------------------
78 !
79 IF (lhook) CALL dr_hook('PREP_FLAKE_ASCLLV',0,zhook_handle)
80  catype = 'ARI'
81 !
82 !* 1. get full dimension of grid
83 !
84  CALL get_type_dim_n(dtco, u, &
85  'FULL ',nl)
86 !
87 !* 2. get water dimension
88 !
89  CALL get_type_dim_n(dtco, u, &
90  'WATER ',il)
91 !
92 ALLOCATE(zfield(il))
93 !
94 !* 3. get grid informations known over full grid
95 !
96  CALL get_latlonmask_n(ug, &
97  llatlonmask,cgrid,xgrid_par,ngrid_par)
98 !
99 !
100 SELECT CASE(hsurf)
101 !
102 !
103 !* 5. surface temperature
104 
105  CASE('TS ')
106 
107  CALL pgd_field(dtco, ug, u, uss, &
108  hprogram,'TS_WATER: temperature','WAT',cfile_flake, &
109  ctype,xundef,zfield(:))
110 
111  ALLOCATE(pfield(il,1))
112  pfield(:,1) = zfield(:)
113 
114 END SELECT
115 !
116 !* 6. Interpolation method
117 ! --------------------
118 !
119  cinterp_type='NONE '
120 DEALLOCATE(zfield)
121 IF (lhook) CALL dr_hook('PREP_FLAKE_ASCLLV',1,zhook_handle)
122 !
123 !-------------------------------------------------------------------------------------
124 END SUBROUTINE prep_flake_ascllv
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
subroutine pgd_field(DTCO, UG, U, USS, HPROGRAM, HFIELD, HAREA, HFILE, HFILETYPE, PUNIF, PFIELD, OPRESENT)
Definition: pgd_field.F90:6
subroutine get_latlonmask_n(UG, OLATLONMASK, HGRID, PGRID_PAR, KGRID_PAR)
subroutine prep_flake_ascllv(DTCO, UG, U, USS, HPROGRAM, HSURF, KLUOUT, PFIELD)