SURFEX v8.1
General documentation of Surfex
diag_sean.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 diag_sea_n (DLO, DL, DLC, SD, HSEA, HPROGRAM, DUP, DUPC, KMASK )
7 ! #####################################################################
8 !
9 !!**** *DIAG_SEA_n * - Chooses the surface schemes for sea diagnostics
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!** METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !!
21 !! AUTHOR
22 !! ------
23 !! V. Masson
24 !!
25 !! MODIFICATIONS
26 !! -------------
27 !! Original 01/2004
28 !! Modified 01/2006 : sea flux parameterization.
29 !! Modified 08/2009 : new diag
30 ! B. decharme 04/2013 : Add EVAP and SUBL diag
31 !!------------------------------------------------------------------
32 !
33 USE mode_diag
34 !
36 USE modd_surfex_n, ONLY : seaflux_diag_t
37 !
38 USE modd_surf_par, ONLY : xundef
39 !
40 USE yomhook ,ONLY : lhook, dr_hook
41 USE parkind1 ,ONLY : jprb
42 !
43 IMPLICIT NONE
44 !
45 !* 0.1 declarations of arguments
46 !
47 TYPE(diag_options_t), INTENT(INOUT) :: DLO
48 TYPE(diag_t), INTENT(INOUT) :: DL
49 TYPE(diag_t), INTENT(INOUT) :: DLC
50 TYPE(seaflux_diag_t), INTENT(INOUT) :: SD
51 !
52  CHARACTER(LEN=*), INTENT(IN) :: HSEA
53  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
54 !
55 TYPE(diag_t), INTENT(INOUT) :: DUP
56 TYPE(diag_t), INTENT(INOUT) :: DUPC
57 !
58 INTEGER, DIMENSION(:), INTENT(IN) :: KMASK
59 !
60 REAL(KIND=JPRB) :: ZHOOK_HANDLE
61 !
62 !
63 !* 0.2 declarations of local variables
64 !
65 !-------------------------------------------------------------------------------------
66 !
67 IF (lhook) CALL dr_hook('DIAG_SEA_N',0,zhook_handle)
68 IF (hsea=='SEAFLX') THEN
69  CALL diag_evap(sd%O, sd%D, sd%DC, hprogram, dup, dupc, kmask)
70 ELSEIF (hsea=='FLUX') THEN
71  CALL diag_evap(dlo, dl, dlc, hprogram, dup, dupc, kmask)
72 ELSE IF (hsea=='NONE ') THEN
73  CALL init_bud(sd%O, dup, dupc, xundef)
74 END IF
75 IF (lhook) CALL dr_hook('DIAG_SEA_N',1,zhook_handle)
76 !
77 !-------------------------------------------------------------------------------------
78 !
79 END SUBROUTINE diag_sea_n
subroutine init_bud(DGO, DA, DAC, PVAL)
Definition: mode_diag.F90:185
subroutine diag_sea_n(DLO, DL, DLC, SD, HSEA, HPROGRAM, DUP, DUPC, KMASK)
Definition: diag_sean.F90:7
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
subroutine diag_evap(DGO, DA, DAC, HPROGRAM, DAUP, DAUPC, KMASK)
Definition: mode_diag.F90:288
logical lhook
Definition: yomhook.F90:15