SURFEX v8.1
General documentation of Surfex
modd_ocean_reln.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 ! Author : P. Peyrille
10 !! Date: 01/2012
11 !!
12 !! declaration of relaxation field, flag for ocean model
13 !
14 USE yomhook ,ONLY : lhook, dr_hook
15 USE parkind1 ,ONLY : jprb
16 !
17 IMPLICIT NONE
18 !
20 !
21  REAL :: xtau_rel ! Time of relaxation (s)
22 !
23  REAL :: xqcorr ! correction coefficient for surface fluxes (BArnier et al. 1998) typcial val: 100.
24 !
25  LOGICAL :: lrel_cur ! flag for relxation on current
26  LOGICAL :: lrel_ts ! flag for relaxation on ocean temperature
27  LOGICAL :: lflux_null ! Flag for testing zero incoming flux at the surface
28 !
29  LOGICAL :: lflx_corr ! Flag for flux correction
30  LOGICAL :: ldiapycnal ! Flag for diapycnal mixing activation
31 !
32  REAL, POINTER, DIMENSION(:,:) :: xseau_rel ! ref. U current profile (C)
33  REAL, POINTER, DIMENSION(:,:) :: xseav_rel ! ref. V current profile (C)
34  REAL, POINTER, DIMENSION(:,:) :: xseat_rel ! ref. temperature profile (C)
35  REAL, POINTER, DIMENSION(:,:) :: xseas_rel ! ---- salinity ---------- (%)
36 !
37 END TYPE ocean_rel_t
38 !
39 
40 
41 CONTAINS
42 !
43 !
44 
45 
46 !
47 !
48 SUBROUTINE ocean_rel_init(YOCEAN_REL)
49 TYPE(ocean_rel_t), INTENT(INOUT) :: YOCEAN_REL
50 REAL(KIND=JPRB) :: ZHOOK_HANDLE
51 IF (lhook) CALL dr_hook("MODD_OCEAN_REL_N:OCEAN_REL_INIT",0,zhook_handle)
52  NULLIFY(yocean_rel%XSEAT_REL)
53  NULLIFY(yocean_rel%XSEAS_REL)
54  NULLIFY(yocean_rel%XSEAU_REL)
55  NULLIFY(yocean_rel%XSEAV_REL)
56 yocean_rel%XTAU_REL=0.
57 yocean_rel%XQCORR=0.
58 yocean_rel%LREL_CUR=.false.
59 yocean_rel%LREL_TS=.false.
60 yocean_rel%LFLUX_NULL=.false.
61 yocean_rel%LFLX_CORR=.false.
62 yocean_rel%LDIAPYCNAL=.false.
63 !
64 IF (lhook) CALL dr_hook("MODD_OCEAN_REL_N:OCEAN_REL_INIT",1,zhook_handle)
65 END SUBROUTINE ocean_rel_init
66 !
67 !
68 END MODULE modd_ocean_rel_n
integer, parameter jprb
Definition: parkind1.F90:32
subroutine ocean_rel_init(YOCEAN_REL)
logical lhook
Definition: yomhook.F90:15