SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
prep_seaflux_buffer.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_seaflux_buffer(HPROGRAM,HSURF,KLUOUT,PFIELD)
7 ! #################################################################################
8 !
9 !!**** *PREP_SEAFLUX_BUFFER* - prepares SEAFLUX fields from BUFFER
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!** METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !!
21 !! AUTHOR
22 !! ------
23 !! S. Malardel
24 !!
25 !! MODIFICATIONS
26 !! -------------
27 !! Original 01/2004
28 !!------------------------------------------------------------------
29 !
30 
31 !
33 !
35 !
36 USE modi_prep_buffer_grid
37 !
38 USE modd_prep, ONLY : cinterp_type
39 USE modd_grid_buffer, ONLY : nni
40 !
41 !
42 USE yomhook ,ONLY : lhook, dr_hook
43 USE parkind1 ,ONLY : jprb
44 !
45 IMPLICIT NONE
46 !
47 !* 0.1 declarations of arguments
48 !
49  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling surf. schemes
50  CHARACTER(LEN=7), INTENT(IN) :: hsurf ! type of field
51 INTEGER, INTENT(IN) :: kluout ! logical unit of output listing
52 REAL,DIMENSION(:,:), POINTER :: pfield ! field to prepare
53 !
54 !* 0.2 declarations of local variables
55 !
56 TYPE (date_time) :: tztime_buf ! current date and time
57  CHARACTER(LEN=6) :: yinmodel ! model from which BUFFER data originate
58 REAL, DIMENSION(:), POINTER :: zfield ! field read
59 REAL(KIND=JPRB) :: zhook_handle
60 !
61 !-------------------------------------------------------------------------------------
62 !
63 !* 1. Reading of grid
64 ! ---------------
65 !
66 IF (lhook) CALL dr_hook('PREP_SEAFLUX_BUFFER',0,zhook_handle)
67  CALL prep_buffer_grid(kluout,yinmodel,tztime_buf)
68 
69 !
70 !* 2. Reading of field
71 ! ----------------
72 !-----------------
73 SELECT CASE(hsurf)
74 !-----------------
75 !
76 !* 1. Orography
77 ! ---------
78 !
79  CASE('ZS ')
80  ALLOCATE(pfield(nni,1))
81  pfield = 0.0
82  SELECT CASE (yinmodel)
83  CASE ('ALADIN')
84  CALL read_buffer_zs(kluout,yinmodel,zfield)
85  pfield(:,1) = zfield(:)
86  DEALLOCATE(zfield)
87  END SELECT
88 
89 !
90 !* 3. Temperature profiles
91 ! --------------------
92 !
93  CASE('SST ')
94  ALLOCATE(pfield(nni,1))
95  pfield = 0.0
96  SELECT CASE (yinmodel)
97  CASE ('ALADIN')
98  CALL read_buffer_sst(kluout,yinmodel,zfield)
99  pfield(:,1) = zfield(:)
100  DEALLOCATE(zfield)
101  END SELECT
102 !
103 !* 5. Sea surface salinity and ice fraction
104 ! -------------------------------------
105 !
106  CASE('SSS ', 'SIC ')
107  ALLOCATE(pfield(nni,1))
108  pfield = 0.0
109 !
110 END SELECT
111 
112 !
113 !* 4. Interpolation method
114 ! --------------------
115 !
116  cinterp_type='BUFFER'
117 IF (lhook) CALL dr_hook('PREP_SEAFLUX_BUFFER',1,zhook_handle)
118 !
119 !
120 !-------------------------------------------------------------------------------------
121 END SUBROUTINE prep_seaflux_buffer
subroutine read_buffer_sst(KLUOUT, HINMODEL, PFIELD)
subroutine prep_buffer_grid(KLUOUT, HINMODEL, TPTIME_BUF)
subroutine prep_seaflux_buffer(HPROGRAM, HSURF, KLUOUT, PFIELD)
subroutine read_buffer_zs(KLUOUT, HINMODEL, PFIELD)