SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
modd_oceann.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  MODULE modd_ocean_n
7 ! #################
8 !
9 !!**** *MODD_OCEAN_n - declaration of ocean varaiables
10 !! for 1D oceanic model
11 !!
12 !! PURPOSE
13 !! -------
14 ! Declaration of ocean varaiables
15 !
16 !!
17 !!** IMPLICIT ARGUMENTS
18 !! ------------------
19 !! None
20 !!
21 !! REFERENCE
22 !! ---------
23 !!
24 !! AUTHOR
25 !! ------
26 !! C. Lebeaupin *Meteo France*
27 !!
28 !! MODIFICATIONS
29 !! -------------
30 !! Original 04/2006
31 !! Modified 07/2012, P. Le Moigne : CMO1D phasing
32 !
33 !* 0. DECLARATIONS
34 ! ------------
35 !
36 !
37 USE yomhook ,ONLY : lhook, dr_hook
38 USE parkind1 ,ONLY : jprb
39 !
40 IMPLICIT NONE
41 !
42 TYPE ocean_t
43 !
44 !
45 ! Switche for interactive coupling with oceanic model
46 LOGICAL:: LMERCATOR !set to .true. to initialize oceanic var. from Mercator
47 LOGICAL:: LCURRENT !set to .true. to make initialize ocean state with current
48 LOGICAL:: LPROGSST !set to .true. to make SST evolve with tendance
49 INTEGER:: NTIME_COUPLING! coupling time frequency
50 INTEGER:: NOCTCOUNT !oceanic model counter
51 REAL :: XOCEAN_TSTEP ! time step of the oceanic 1D model
52 !
53 ! General surface:
54 !
55 REAL, POINTER, DIMENSION(:,:) :: XSEAT ! oceanic temperature profiles
56 REAL, POINTER, DIMENSION(:,:) :: XSEAS ! oceanic salinity profiles
57 REAL, POINTER, DIMENSION(:,:) :: XSEAU ! oceanic zonal current profiles
58 REAL, POINTER, DIMENSION(:,:) :: XSEAV ! oceanic meridian current profiles
59 REAL, POINTER, DIMENSION(:,:) :: XSEAE ! oceanic kinetic turbulent energy profiles (^(1/2))
60 REAL, POINTER, DIMENSION(:,:) :: XSEABATH !bathymetry indice
61  !=1 for free sea water
62  !=0 for sea-bed
63 REAL, POINTER, DIMENSION(:) :: XSEAHMO! oceanic mixing lengths
64 !
65 REAL, POINTER, DIMENSION(:,:) :: XLE,XLK! oceanic mixing lengths
66 REAL, POINTER, DIMENSION(:,:) :: XKMEL,XKMELM ! oceanic mixing coefficients
67 !
68 REAL, POINTER, DIMENSION(:) :: XSEATEND! SST tendance
69 !
70 REAL, POINTER, DIMENSION(:,:) :: XDTFSOL ! Temp tendancy due to solar flux
71 REAL, POINTER, DIMENSION(:) :: XDTFNSOL! -------------------- non solar flux
72 !
73 END TYPE ocean_t
74 !
75 
76 
77  CONTAINS
78 
79 !
80 
81 
82 
83 
84 SUBROUTINE ocean_init(YOCEAN)
85 TYPE(ocean_t), INTENT(INOUT) :: yocean
86 REAL(KIND=JPRB) :: zhook_handle
87 IF (lhook) CALL dr_hook("MODD_OCEAN_N:OCEAN_INIT",0,zhook_handle)
88  nullify(yocean%XSEAT)
89  nullify(yocean%XSEAS)
90  nullify(yocean%XSEAU)
91  nullify(yocean%XSEAV)
92  nullify(yocean%XSEAE)
93  nullify(yocean%XSEABATH)
94  nullify(yocean%XSEAHMO)
95  nullify(yocean%XLE)
96  nullify(yocean%XLK)
97  nullify(yocean%XKMEL)
98  nullify(yocean%XKMELM)
99  nullify(yocean%XSEATEND)
100  nullify(yocean%XDTFNSOL)
101  nullify(yocean%XDTFSOL)
102 yocean%LMERCATOR=.false.
103 yocean%LCURRENT=.false.
104 yocean%LPROGSST=.false.
105 yocean%NTIME_COUPLING=0
106 yocean%NOCTCOUNT=0
107 yocean%XOCEAN_TSTEP=5*60.
108 IF (lhook) CALL dr_hook("MODD_OCEAN_N:OCEAN_INIT",1,zhook_handle)
109 END SUBROUTINE ocean_init
110 
111 
112 END MODULE modd_ocean_n
subroutine ocean_init(YOCEAN)
Definition: modd_oceann.F90:84