New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
oce.F90 in branches/2013/dev_MERGE_2013/NEMOGCM/NEMO/OPA_SRC – NEMO

source: branches/2013/dev_MERGE_2013/NEMOGCM/NEMO/OPA_SRC/oce.F90 @ 4306

Last change on this file since 4306 was 4292, checked in by cetlod, 11 years ago

dev_MERGE_2013 : 1st step of the merge, see ticket #1185

  • Property svn:keywords set to Id
File size: 6.5 KB
RevLine 
[3]1MODULE oce
2   !!======================================================================
[15]3   !!                      ***  MODULE  oce  ***
[3]4   !! Ocean        :  dynamics and active tracers defined in memory
5   !!======================================================================
[2528]6   !! History :  1.0  !  2002-11  (G. Madec)  F90: Free form and module
[1438]7   !!            3.1  !  2009-02  (G. Madec, M. Leclair)  pure z* coordinate
[2528]8   !!            3.3  !  2010-09  (C. Ethe) TRA-TRC merge: add ts, gtsu, gtsv 4D arrays
[3]9   !!----------------------------------------------------------------------
[2715]10   USE par_oce        ! ocean parameters
11   USE lib_mpp        ! MPP library
[3]12
13   IMPLICIT NONE
[15]14   PRIVATE
[3]15
[2715]16   PUBLIC oce_alloc ! routine called by nemo_init in nemogcm.F90
[3]17
[2715]18   LOGICAL, PUBLIC ::   l_traldf_rot = .FALSE.  !: rotated laplacian operator for lateral diffusion
19
20   !! dynamics and tracer fields                            ! before ! now    ! after  ! the after trends becomes the fields
21   !! --------------------------                            ! fields ! fields ! trends ! only after tra_zdf and dyn_spg
22   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   ub   ,  un    , ua     !: i-horizontal velocity        [m/s]
23   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   vb   ,  vn    , va     !: j-horizontal velocity        [m/s]
[4292]24   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   ua_sv,  va_sv          !: Saved trends (time spliting) [m/s2]
[2715]25   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::           wn             !: vertical velocity            [m/s]
26   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   rotb ,  rotn           !: relative vorticity           [s-1]
27   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   hdivb,  hdivn          !: horizontal divergence        [s-1]
[3294]28   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   tsb  ,  tsn            !: 4D T-S fields        [Celcius,psu]
[2715]29   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   rn2b ,  rn2            !: brunt-vaisala frequency**2   [s-2]
[1438]30   !
[3294]31   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::  tsa             !: 4D T-S trends fields & work array
32   !
[2715]33   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   rhd    !: in situ density anomalie rhd=(rho-rau0)/rau0  [no units]
34   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   rhop   !: potential volumic mass                           [kg/m3]
[3]35
[2715]36   !! free surface                                      !  before  ! now    ! after  !
37   !! ------------                                      !  fields  ! fields ! trends !
[3294]38   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET ::   sshb   , sshn   , ssha   !: sea surface height at t-point [m]
[2528]39   !
[2715]40   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   spgu, spgv               !: horizontal surface pressure gradient
[359]41
[2528]42   !! interpolated gradient (only used in zps case)
43   !! ---------------------
[2715]44   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   gtsu, gtsv   !: horizontal gradient of T, S bottom u-point
45   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   gru , grv    !: horizontal gradient of rd at bottom u-point
[2528]46
[4152]47   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   rke          !: kinetic energy
48
[3625]49   !! arrays relating to embedding ice in the ocean. These arrays need to be declared
50   !! even if no ice model is required. In the no ice model or traditional levitating
51   !! ice cases they contain only zeros
52   !! ---------------------
53   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_mass        !: mass of snow and ice at current  ice time step   [Kg/m2]
54   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_mass_b      !: mass of snow and ice at previous ice time step   [Kg/m2]
55   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_fmass       !: time evolution of mass of snow+ice               [Kg/m2/s]
56
[4205]57   !! arrays related to penetration of solar fluxes to calculate the heat budget for sea ice
58   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   oatte, iatte       !: attenuation coef of the input solar flux [unitless]
59
[3]60   !!----------------------------------------------------------------------
[2715]61   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
[1438]62   !! $Id$
[2715]63   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
64   !!----------------------------------------------------------------------
65CONTAINS
66
67   INTEGER FUNCTION oce_alloc()
68      !!----------------------------------------------------------------------
69      !!                   ***  FUNCTION oce_alloc  ***
70      !!----------------------------------------------------------------------
[4205]71      INTEGER :: ierr(4)
[2715]72      !!----------------------------------------------------------------------
73      !
74      ALLOCATE( ub   (jpi,jpj,jpk)      , un   (jpi,jpj,jpk)      , ua(jpi,jpj,jpk)       ,     &
75         &      vb   (jpi,jpj,jpk)      , vn   (jpi,jpj,jpk)      , va(jpi,jpj,jpk)       ,     &     
[4292]76         &      ua_sv(jpi,jpj,jpk)      , va_sv(jpi,jpj,jpk)      ,                             &     
[2715]77         &      wn   (jpi,jpj,jpk)      ,                                                       &
78         &      rotb (jpi,jpj,jpk)      , rotn (jpi,jpj,jpk)      ,                             &   
79         &      hdivb(jpi,jpj,jpk)      , hdivn(jpi,jpj,jpk)      ,                             &
80         &      tsb  (jpi,jpj,jpk,jpts) , tsn  (jpi,jpj,jpk,jpts) , tsa(jpi,jpj,jpk,jpts) ,     &
81         &      rn2b (jpi,jpj,jpk)      , rn2  (jpi,jpj,jpk)                              , STAT=ierr(1) )
82         !
[4292]83      ALLOCATE(rhd (jpi,jpj,jpk) ,                                         &
84         &     rhop(jpi,jpj,jpk) ,                                         &
85         &     sshb  (jpi,jpj)   , sshn  (jpi,jpj) , ssha  (jpi,jpj) ,     &
86         &     spgu  (jpi,jpj)   , spgv(jpi,jpj)   ,                       &
87         &     gtsu(jpi,jpj,jpts), gtsv(jpi,jpj,jpts),                     &
88         &     gru(jpi,jpj)      , grv(jpi,jpj)                      , STAT=ierr(2) )
[2715]89         !
[4205]90      ALLOCATE( snwice_mass(jpi,jpj) , snwice_mass_b(jpi,jpj), snwice_fmass(jpi,jpj) , STAT=ierr(3) )
[3625]91         !
[4205]92      ALLOCATE( iatte(jpi,jpj) , oatte(jpi,jpj) , STAT=ierr(4) )
93         !
[2715]94      oce_alloc = MAXVAL( ierr )
95      IF( oce_alloc /= 0 )   CALL ctl_warn('oce_alloc: failed to allocate arrays')
96      !
97   END FUNCTION oce_alloc
98
[1438]99   !!======================================================================
[3]100END MODULE oce
Note: See TracBrowser for help on using the repository browser.