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.
trcini.lobster1.h90 in trunk/NEMO/TOP_SRC/SMS – NEMO

source: trunk/NEMO/TOP_SRC/SMS/trcini.lobster1.h90 @ 933

Last change on this file since 933 was 719, checked in by ctlod, 17 years ago

get back to the nemo_v2_3 version for trunk

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.0 KB
RevLine 
[336]1   !!----------------------------------------------------------------------
2   !!                    ***  trcini.lobster1.h90 ***
3   !!----------------------------------------------------------------------
4#  include "domzgr_substitute.h90"
5#  include "passivetrc_substitute.h90"
6CONTAINS
7
8   SUBROUTINE trc_ini
9      !!---------------------------------------------------------------------
10      !!                    ***  ROUTINE trc_ini  ***
11      !!  purpose :
12      !!  ---------
13      !!     specific initialisation for lobster1 model
14      !!
15      !!   History :
16      !!   --------
17      !!      original    : 99-09 (M. Levy)
18      !!      additions   : 00-12 (0. Aumont, E. Kestenare)
19      !!                           add sediment computations
20      !!    03-05 : O. Aumont and A. El Moussaoui F90 
[341]21      !!----------------------------------------------------------------------
22      !!  TOP 1.0 , LOCEAN-IPSL (2005)
[719]23   !! $Header$
[341]24   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
25      !!----------------------------------------------------------------------
[336]26      !! local declarations
27      !! ==================
28      INTEGER ji,jj,jk,jn
[260]29      REAL zdm0(jpi,jpj,jpk),zrro(jpi,jpj),zfluo,zfluu
30      REAL ztest
31
[336]32      !! 1. initialization of fields for optical model
33      !! --------------------------------------------
[260]34
[336]35      xze(:,:)=5.
36      xpar(:,:,:)=0.
[260]37
[336]38      !! 2. initialization for passive tracer remineralisation-damping  array
39      !! -------------------------------------------------------------------------
40
[260]41      DO jn=1,jptra
[336]42         remdmp(:,jn)=tminr
[260]43      END DO
44
45      IF(lwp) THEN
[336]46         WRITE(numout,*) ' '
47         WRITE(numout,*) ' trcini: compute remineralisation-damping  '
48         WRITE(numout,*) '         arrays for tracers'
[260]49      ENDIF
50
[336]51      !! 3. initialization of biological variables
52      !! ------------------------------------------
[260]53
[336]54      !! Calculate vertical distribution of newly formed biogenic poc
55      !! in the water column in the case of max. possible bottom depth
56      !! ------------------------------------------------------------
[260]57
58      zdm0   = 0.
59      zrro = 1.
60      DO jk = jpkb,jpkm1
[336]61         DO jj =1, jpj
62            DO ji =1, jpi
63               zfluo = (fsdepw(ji,jj,jk)/fsdepw(ji,jj,jpkb))**xhr
64               zfluu = (fsdepw(ji,jj,jk+1)/fsdepw(ji,jj,jpkb))**xhr
65               IF (zfluo.GT.1.) zfluo = 1.
66               zdm0(ji,jj,jk) = zfluo-zfluu
67               IF (jk.LE.jpkb-1) zdm0(ji,jj,jk)=0.
68               zrro(ji,jj) = zrro(ji,jj)-zdm0(ji,jj,jk)
69            ENDDO
70         ENDDO
[260]71      ENDDO
72!!!
73
[336]74      zdm0(:,:,jpk) = zrro(:,:)
[260]75
[336]76      !! Calculate vertical distribution of newly formed biogenic poc
77      !! in the water column with realistic topography (first "dry" layer
78      !! contains total fraction, which has passed to the upper layers)
79      !! ----------------------------------------------------------------------
[260]80
81      dminl = 0.
82      dmin3 = zdm0
83
84      DO jk = 1,jpk
85         DO jj = 1,jpj
[336]86            DO ji = 1,jpi
[260]87
[336]88               IF(tmask(ji,jj,jk) == 0) THEN
89                  dminl(ji,jj) = dminl(ji,jj)+dmin3(ji,jj,jk)
90                  dmin3(ji,jj,jk) = 0.0
91               ENDIF
[260]92
[336]93            ENDDO
94         ENDDO
[260]95      ENDDO
96
97      DO jj = 1,jpj
[336]98         DO ji = 1,jpi
99            IF (tmask(ji,jj,1) == 0) dmin3(ji,jj,1) = 0.
100         ENDDO
[260]101      ENDDO
102
[336]103      !! CALCUL DU MASK DE COTE
104      !! ----------------------   
105      cmask=0.
106      do ji=2,jpi-1
107         do jj=2,jpj-1
[260]108            if (tmask(ji,jj,1) == 1) then
[336]109               ztest=tmask(ji+1,jj,1)*tmask(ji-1,jj,1)*tmask(ji,jj+1,1)*tmask(ji,jj-1,1)
110               IF (ztest == 0) cmask(ji,jj) = 1.
111            endif
112         end do
113      end do
[260]114
[336]115      cmask(1,:)=cmask(jpi-1,:)
116      cmask(jpi,:)=cmask(2,:)
[260]117
118
[336]119      !! CALCUL DE LA SURFACE COTIERE
120      !! ----------------------------
121      areacot=0.
122      do ji=2,jpi-1
123         do jj=2,jpj-1
124            areacot=areacot+e1t(ji,jj)*e2t(ji,jj)*cmask(ji,jj)
[260]125         end do
[336]126      end do
[260]127
[336]128   END SUBROUTINE trc_ini
Note: See TracBrowser for help on using the repository browser.