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 branches/dev_001_GM/NEMO/TOP_SRC/LOBSTER – NEMO

source: branches/dev_001_GM/NEMO/TOP_SRC/LOBSTER/trcini.lobster1.h90 @ 764

Last change on this file since 764 was 764, checked in by gm, 16 years ago

dev_001_GM - create new directory and move files only

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.4 KB
Line 
1   !!======================================================================
2   !!                         ***  trcini.lobster1.h90  ***
3   !! TOP :   Initialisation of LOBSTER 1 biological model
4   !!======================================================================
5   !! History :    -   !  1999-09  (M. Levy) Original code
6   !!              -   !  2000-12  (0. Aumont, E. Kestenare) add sediment
7   !!             1.0  !  2004-03  (C. Ethe) Modularity
8   !!              -   !  2005-03  (O. Aumont, A. El Moussaoui) F90
9   !!----------------------------------------------------------------------
10
11#  include "domzgr_substitute.h90"
12#  include "passivetrc_substitute.h90"
13   !!----------------------------------------------------------------------
14   !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)
15   !! $Id$
16   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
17   !!----------------------------------------------------------------------
18
19CONTAINS
20
21   SUBROUTINE trc_ini
22      !!----------------------------------------------------------------------
23      !!                    ***  ROUTINE trc_ini  ***
24      !! ** purpose :   specific initialisation for lobster1 model
25      !!----------------------------------------------------------------------
26      INTEGER  ::   ji, jj, jk, jn
27      REAL(wp) ::   zdm0(jpi,jpj,jpk), zrro(jpi,jpj), zfluo, zfluu
28      REAL(wp) ::   ztest, zfluo, zfluu
29      REAL(wp), DIMENSION(jpi,jpj) ::   zrro
30      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zdm0
31      !!----------------------------------------------------------------------
32
33      ! initialization of fields for optical model
34      ! --------------------------------------------
35      xze (:,:)   = 5.e0
36      xpar(:,:,:) = 0.e0
37
38      ! initialization for passive tracer remineralisation-damping  array
39      ! -----------------------------------------------------------------
40
41      DO jn = 1, jptra
42         remdmp(:,jn) = tminr
43      END DO
44
45      IF(lwp) THEN
46         WRITE(numout,*) ' '
47         WRITE(numout,*) ' trcini: compute remineralisation-damping  '
48         WRITE(numout,*) '         arrays for tracers'
49      ENDIF
50
51      ! initialization of biological variables
52      ! ------------------------------------------
53
54      ! Calculate vertical distribution of newly formed biogenic poc
55      ! in the water column in the case of max. possible bottom depth
56      ! ------------------------------------------------------------
57
58      zdm0   = 0.e0
59      zrro = 1.e0
60      DO jk = jpkb,jpkm1
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.e0
66               zdm0(ji,jj,jk) = zfluo - zfluu
67               IF( jk <= jpkb-1 )   zdm0(ji,jj,jk) = 0.e0
68               zrro(ji,jj) = zrro(ji,jj) - zdm0(ji,jj,jk)
69            END DO
70         END DO
71      END DO
72
73      zdm0(:,:,jpk) = zrro(:,:)
74
75      ! Calculate vertical distribution of newly formed biogenic poc
76      ! in the water column with realistic topography (first "dry" layer
77      ! contains total fraction, which has passed to the upper layers)
78      ! ----------------------------------------------------------------------
79      dminl = 0.
80      dmin3 = zdm0
81      DO jk = 1, jpk
82         DO jj = 1, jpj
83            DO ji = 1, jpi
84               IF( tmask(ji,jj,jk) == 0. ) THEN
85                  dminl(ji,jj) = dminl(ji,jj) + dmin3(ji,jj,jk)
86                  dmin3(ji,jj,jk) = 0.e0
87               ENDIF
88            END DO
89         END DO
90      END DO
91
92      DO jj = 1, jpj
93         DO ji = 1, jpi
94            IF( tmask(ji,jj,1) == 0 )   dmin3(ji,jj,1) = 0.e0
95         END DO
96      END DO
97
98      ! Coastal mask
99      ! ------------   
100      cmask = 0.e0
101      DO ji = 2, jpi-1
102         DO jj = 2, jpj-1
103            if (tmask(ji,jj,1) == 1) then
104               ztest=tmask(ji+1,jj,1)*tmask(ji-1,jj,1)*tmask(ji,jj+1,1)*tmask(ji,jj-1,1)
105               IF (ztest == 0) cmask(ji,jj) = 1.
106            endif
107         END DO
108      END DO
109
110      cmask( 1 ,:) = cmask(jpi-1,:)
111      cmask(jpi,:) = cmask( 2   ,:)
112
113      !!gm BUG !!!!!   not valid in mpp and also not valid for north fold   !!!!!
114
115      ! Coastal surface
116      ! ---------------
117      areacot = 0.e0
118      DO ji = 2, jpi-1
119         DO jj = 2, jpj-1
120            areacot = areacot + e1t(ji,jj) * e2t(ji,jj) * cmask(ji,jj)
121         END DO
122      END DO
123      !
124   END SUBROUTINE trc_ini
Note: See TracBrowser for help on using the repository browser.