123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189 |
- MODULE dom_oce
- !!======================================================================
- !! *** MODULE dom_oce ***
- !!
- !! ** Purpose : Define in memory all the ocean space domain variables
- !!======================================================================
- !! History : 1.0 ! 2005-10 (A. Beckmann, G. Madec) reactivate s-coordinate
- !!----------------------------------------------------------------------
- !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)
- !! $Id: dom_oce.F90 1886 2010-05-27 10:13:51Z rblod $
- !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
- !!----------------------------------------------------------------------
- use par_kind
- ! USE par_oce ! ocean parameters
- IMPLICIT NONE
- PUBLIC ! allows the acces to par_oce when dom_oce is used
- ! ! exception to coding rules... to be suppressed ???
- !!----------------------------------------------------------------------
- !! time & space domain namelist
- !! ----------------------------
- ! !!* Namelist namdom : time & space domain
- INTEGER , PUBLIC :: nn_bathy = 0 !: = 0/1 ,compute/read the bathymetry file
- REAL(wp), PUBLIC :: rn_e3zps_min = 5.0_wp !: miminum thickness for partial steps (meters)
- REAL(wp), PUBLIC :: rn_e3zps_rat = 0.1_wp !: minimum thickness ration for partial steps
- INTEGER , PUBLIC :: nn_msh = 0 !: = 1 create a mesh-mask file
- INTEGER , PUBLIC :: nn_acc = 0 !: = 0/1 use of the acceleration of convergence technique
- REAL(wp), PUBLIC :: rn_atfp = 0.1_wp !: asselin time filter parameter
- REAL(wp), PUBLIC :: rn_rdt = 3600._wp !: time step for the dynamics (and tracer if nacc=0)
- REAL(wp), PUBLIC :: rn_rdtmin = 3600._wp !: minimum time step on tracers
- REAL(wp), PUBLIC :: rn_rdtmax = 3600._wp !: maximum time step on tracers
- REAL(wp), PUBLIC :: rn_rdth = 800._wp !: depth variation of tracer step
- INTEGER , PUBLIC :: nn_baro = 64 !: number of barotropic time steps (key_dynspg_ts)
- INTEGER , PUBLIC :: nn_closea = 0 !: =0 suppress closed sea/lake from the ORCA domain or not (=1)
- ! ! old non-DOCTOR names still used in the model
- INTEGER , PUBLIC :: ntopo !: = 0/1 ,compute/read the bathymetry file
- REAL(wp), PUBLIC :: e3zps_min !: miminum thickness for partial steps (meters)
- REAL(wp), PUBLIC :: e3zps_rat !: minimum thickness ration for partial steps
- INTEGER , PUBLIC :: nmsh !: = 1 create a mesh-mask file
- INTEGER , PUBLIC :: nacc !: = 0/1 use of the acceleration of convergence technique
- REAL(wp), PUBLIC :: atfp !: asselin time filter parameter
- REAL(wp), PUBLIC :: rdt !: time step for the dynamics (and tracer if nacc=0)
- REAL(wp), PUBLIC :: rdtmin !: minimum time step on tracers
- REAL(wp), PUBLIC :: rdtmax !: maximum time step on tracers
- REAL(wp), PUBLIC :: rdth !: depth variation of tracer step
- INTEGER , PUBLIC :: nclosea !: =0 suppress closed sea/lake from the ORCA domain or not (=1)
- ! !!! associated variables
- INTEGER , PUBLIC :: neuler = 0 !: restart euler forward option (0=Euler)
- REAL(wp), PUBLIC :: atfp1 !: asselin time filter coeff. (atfp1= 1-2*atfp)
- REAL(wp), PUBLIC, DIMENSION(jpk) :: rdttra !: vertical profile of tracer time step
- ! !!* Namelist namcla : cross land advection
- INTEGER, PUBLIC :: nn_cla = 0 !: =1 cross land advection for exchanges through some straits (ORCA2)
- ! ! old non-DOCTOR names still used in the model
- INTEGER, PUBLIC :: n_cla = 0 !: =1 cross land advection for exchanges through some straits (ORCA2)
- !!----------------------------------------------------------------------
- !! space domain parameters
- !!----------------------------------------------------------------------
- LOGICAL, PUBLIC :: lzoom = .FALSE. !: zoom flag
- LOGICAL, PUBLIC :: lzoom_e = .FALSE. !: East zoom type flag
- LOGICAL, PUBLIC :: lzoom_w = .FALSE. !: West zoom type flag
- LOGICAL, PUBLIC :: lzoom_s = .FALSE. !: South zoom type flag
- LOGICAL, PUBLIC :: lzoom_n = .FALSE. !: North zoom type flag
- LOGICAL, PUBLIC :: lzoom_arct = .FALSE. !: ORCA arctic zoom flag
- LOGICAL, PUBLIC :: lzoom_anta = .FALSE. !: ORCA antarctic zoom flag
- ! !!! domain parameters linked to mpp
- INTEGER, PUBLIC :: nperio = 4 !: type of lateral boundary condition
- INTEGER, PUBLIC :: nimpp, njmpp !: i- & j-indexes for mpp-subdomain left bottom
- INTEGER, PUBLIC :: nreci, nrecj !: overlap region in i and j
- INTEGER, PUBLIC :: nproc !: number for local processor
- INTEGER, PUBLIC :: narea !: number for local area
- INTEGER, PUBLIC :: nbondi, nbondj !: mark of i- and j-direction local boundaries
- INTEGER, PUBLIC :: npolj !: north fold mark (0, 3 or 4)
- INTEGER, PUBLIC :: nlci, nldi, nlei !: i-dimensions of the local subdomain and its first and last indoor indices
- INTEGER, PUBLIC :: nlcj, nldj, nlej !: i-dimensions of the local subdomain and its first and last indoor indices
- INTEGER, PUBLIC :: noea, nowe !: index of the local neighboring processors in
- INTEGER, PUBLIC :: noso, nono !: east, west, south and north directions
- INTEGER, PUBLIC :: npne, npnw !: index of north east and north west processor
- INTEGER, PUBLIC :: npse, npsw !: index of south east and south west processor
- INTEGER, PUBLIC :: nbne, nbnw !: logical of north east & north west processor
- INTEGER, PUBLIC :: nbse, nbsw !: logical of south east & south west processor
- INTEGER, PUBLIC :: nidom !: ???
- INTEGER, PUBLIC, DIMENSION(jpi) :: mig !: local ==> global domain i-index
- INTEGER, PUBLIC, DIMENSION(jpj) :: mjg !: local ==> global domain j-index
- ! ! (mi0=1 and mi1=0 if the global index is not in the local domain)
- !!----------------------------------------------------------------------
- !! horizontal curvilinear coordinate and scale factors
- !! ---------------------------------------------------------------------
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: glamt, glamu !: longitude of t-, u-, v- and f-points (degre)
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: glamv, glamf !:
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: gphit, gphiu !: latitude of t-, u-, v- and f-points (degre)
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: gphiv, gphif !:
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: e1t, e2t !: horizontal scale factors at t-point (m)
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: e1u, e2u !: horizontal scale factors at u-point (m)
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: e1v, e2v !: horizontal scale factors at v-point (m)
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: e1f, e2f !: horizontal scale factors at f-point (m)
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: ff !: coriolis factor (2.*omega*sin(yphi) ) (s-1)
- !!----------------------------------------------------------------------
- !! vertical coordinate and scale factors
- !! ---------------------------------------------------------------------
- ! !!* Namelist namzgr : vertical coordinate *
- LOGICAL, PUBLIC :: ln_zco = .TRUE. !: z-coordinate - full step
- LOGICAL, PUBLIC :: ln_zps = .FALSE. !: z-coordinate - partial step
- LOGICAL, PUBLIC :: ln_sco = .FALSE. !: s-coordinate or hybrid z-s coordinate
- !! All coordinates
- !! ---------------
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) :: gdep3w !: depth of T-points (sum of e3w) (m)
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) :: gdept , gdepw !: analytical depth at T-W points (m)
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) :: e3v , e3f !: analytical vertical scale factors at V--F
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) :: e3t , e3u !: T--U points (m)
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) :: e3vw !: analytical vertical scale factors at VW--
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) :: e3w , e3uw !: W--UW points (m)
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: hur , hvr !: inverse of u and v-points ocean depth (1/m)
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: hu , hv !: depth at u- and v-points (meters)
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: hu_0 , hv_0 !: refernce depth at u- and v-points (meters)
- INTEGER, PUBLIC :: nla10 !: deepest W level Above ~10m (nlb10 - 1)
- INTEGER, PUBLIC :: nlb10 !: shallowest W level Bellow ~10m (nla10 + 1)
- !! z-coordinate with full steps (also used in the other cases as reference z-coordinate)
- !! =-----------------====------
- REAL(wp), PUBLIC, DIMENSION(jpk) :: gdept_0, gdepw_0 !: reference depth of t- and w-points (m)
- REAL(wp), PUBLIC, DIMENSION(jpk) :: e3t_0 , e3w_0 !: reference vertical scale factors at T- and W-pts (m)
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: hdept , hdepw !: ocean bottom depth at T and W points
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: e3tp , e3wp !: ocean bottom level thickness at T and W points
- !! s-coordinate and hybrid z-s-coordinate
- !! =----------------======---------------
- REAL(wp), PUBLIC, DIMENSION(jpk) :: gsigt, gsigw !: model level depth coefficient at t-, w-levels (analytic)
- REAL(wp), PUBLIC, DIMENSION(jpk) :: gsi3w !: model level depth coefficient at w-level (sum of gsigw)
- REAL(wp), PUBLIC, DIMENSION(jpk) :: esigt, esigw !: vertical scale factor coef. at t-, w-levels
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: hbatv , hbatf !: ocean depth at the vertical of V--F
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: hbatt , hbatu !: T--U points (m)
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: scosrf, scobot !: ocean surface and bottom topographies
- ! ! (if deviating from coordinate surfaces in HYBRID)
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: hifv , hiff !: interface depth between stretching at V--F
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: hift , hifu !: and quasi-uniform spacing T--U points (m)
- !!----------------------------------------------------------------------
- !! masks, bathymetry
- !! ---------------------------------------------------------------------
- INTEGER , PUBLIC, DIMENSION(jpi,jpj) :: mbathy !: number of ocean level (=0, 1, ... , jpk-1)
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: bathy !: ocean depth (meters)
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: tmask_i !: interior domain T-point mask
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: bmask !: land/ocean mask of barotropic stream function
- REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) :: tmask, umask, vmask, fmask !: land/ocean mask at T-, U-, V- and F-points
- !!----------------------------------------------------------------------
- !! calendar variables
- !! ---------------------------------------------------------------------
- INTEGER , PUBLIC :: nyear !: current year
- INTEGER , PUBLIC :: nmonth !: current month
- INTEGER , PUBLIC :: nday !: current day of the month
- INTEGER , PUBLIC :: ndastp !: time step date in yyyymmdd format
- INTEGER , PUBLIC :: nday_year !: current day counted from jan 1st of the current year
- INTEGER , PUBLIC :: nsec_year !: current time step counted in second since 00h jan 1st of the current year
- INTEGER , PUBLIC :: nsec_month !: current time step counted in second since 00h 1st day of the current month
- INTEGER , PUBLIC :: nsec_day !: current time step counted in second since 00h of the current day
- REAL(wp), PUBLIC :: fjulday !: julian day
- REAL(wp), PUBLIC :: adatrj !: number of elapsed days since the begining of the whole simulation
- ! !: (cumulative duration of previous runs that may have used different time-step size)
- INTEGER , PUBLIC, DIMENSION(0: 1) :: nyear_len !: length in days of the previous/current year
- INTEGER , PUBLIC, DIMENSION(0:13) :: nmonth_len !: length in days of the months of the current year
- INTEGER , PUBLIC, DIMENSION(0:13) :: nmonth_half !: second since Jan 1st 0h of the current year and the half of the months
- INTEGER , PUBLIC, DIMENSION(0:13) :: nmonth_end !: second since Jan 1st 0h of the current year and the end of the months
- INTEGER , PUBLIC :: nsec1jan000 !: second since Jan 1st 0h of nit000 year and Jan 1st 0h the current year
- !!----------------------------------------------------------------------
- !! agrif domain
- !!----------------------------------------------------------------------
- LOGICAL, PUBLIC, PARAMETER :: lk_agrif = .FALSE. !: agrif flag
- !!======================================================================
- END MODULE dom_oce
|