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.
trcsms_pisces.F90 in trunk/NEMO/TOP_SRC/PISCES – NEMO

source: trunk/NEMO/TOP_SRC/PISCES/trcsms_pisces.F90 @ 1255

Last change on this file since 1255 was 1255, checked in by cetlod, 15 years ago

minor modifications in all top models, see ticket:299

  • Property svn:executable set to *
  • Property svn:keywords set to Id
File size: 4.1 KB
Line 
1MODULE trcsms_pisces
2   !!======================================================================
3   !!                         ***  MODULE trcsms_pisces  ***
4   !! TOP :   PISCES Source Minus Sink manager
5   !!======================================================================
6   !! History :   1.0  !  2004-03 (O. Aumont) Original code
7   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90
8   !!----------------------------------------------------------------------
9#if defined key_pisces
10   !!----------------------------------------------------------------------
11   !!   'key_pisces'                                       PISCES bio-model
12   !!----------------------------------------------------------------------
13   !!   trcsms_pisces        :  Time loop of passive tracers sms
14   !!----------------------------------------------------------------------
15   USE oce_trc         !
16   USE trc
17   USE sms_pisces
18   USE lbclnk
19   USE lib_mpp
20   
21   USE p4zint          !
22   USE p4zche          !
23   USE p4zbio          !
24   USE p4zsed          !
25   USE p4zlys          !
26   USE p4zflx          !
27
28   USE trdmld_trc_oce
29   USE trdmld_trc
30
31   USE sedmodel
32
33   IMPLICIT NONE
34   PRIVATE
35
36   PUBLIC   trc_sms_pisces    ! called in trcsms.F90
37
38   !!----------------------------------------------------------------------
39   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
40   !! $Id$
41   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
42   !!----------------------------------------------------------------------
43
44CONTAINS
45
46   SUBROUTINE trc_sms_pisces( kt )
47      !!---------------------------------------------------------------------
48      !!                     ***  ROUTINE trc_sms_pisces  ***
49      !!
50      !! ** Purpose :   Managment of the call to Biological sources and sinks
51      !!              routines of PISCES bio-model
52      !!
53      !! ** Method  : - at each new day ...
54      !!              - several calls of bio and sed ???
55      !!              - ...
56      !!---------------------------------------------------------------------
57      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index     
58      !!
59      INTEGER ::   jnt, jn
60      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   ztrpis   ! used for pisces sms trends
61      !!---------------------------------------------------------------------
62
63      IF( ndayflxtr /= nday ) THEN      ! New days
64         !
65         ndayflxtr = nday
66
67         CALL p4z_che          ! computation of chemical constants
68         CALL p4z_int          ! computation of various rates for biogeochemistry
69         !
70      ENDIF
71
72
73      DO jnt = 1, nrdttrc          ! Potential time splitting if requested
74         !
75         CALL p4z_bio (kt, jnt)    ! Compute soft tissue production (POC)
76         CALL p4z_sed (kt, jnt)    ! compute soft tissue remineralisation
77         !
78         trb(:,:,:,:) = trn(:,:,:,:)
79         !
80      END DO
81
82      CALL p4z_lys( kt )             ! Compute CaCO3 saturation
83      CALL p4z_flx( kt )             ! Compute surface fluxes
84
85
86      DO jn = jp_pcs0, jp_pcs1
87        CALL lbc_lnk( trn(:,:,:,jn), 'T', 1. )
88        CALL lbc_lnk( trb(:,:,:,jn), 'T', 1. )
89        CALL lbc_lnk( tra(:,:,:,jn), 'T', 1. )
90      END DO
91
92      IF( l_trdtrc ) THEN
93          DO jn = jp_pcs0, jp_pcs1
94            ztrpis(:,:,:) = tra(:,:,:,jn)
95            CALL trd_mod_trc( ztrpis, jn, jptrc_trd_sms, kt )   ! save trends
96          END DO
97      END IF
98
99#if defined key_sed
100
101      CALL sed_model( kt )     !  Main program of Sediment model
102
103      DO jn = jp_pcs0, jp_pcs1
104        CALL lbc_lnk( trn(:,:,:,jn), 'T', 1. )
105      END DO
106
107#endif
108
109      !
110   END SUBROUTINE trc_sms_pisces
111
112#else
113   !!======================================================================
114   !!  Dummy module :                                   No PISCES bio-model
115   !!======================================================================
116CONTAINS
117   SUBROUTINE trc_sms_pisces( kt )                   ! Empty routine
118      INTEGER, INTENT( in ) ::   kt
119      WRITE(*,*) 'trc_sms_pisces: You should not have seen this print! error?', kt
120   END SUBROUTINE trc_sms_pisces
121#endif 
122
123   !!======================================================================
124END MODULE trcsms_pisces 
Note: See TracBrowser for help on using the repository browser.