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.
trcctl.F90 in branches/dev_001_GM/NEMO/TOP_SRC – NEMO

source: branches/dev_001_GM/NEMO/TOP_SRC/trcctl.F90 @ 2793

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

dev_001_GM - small changes : compilation OK

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.3 KB
RevLine 
[268]1MODULE trcctl
[763]2   !!======================================================================
3   !!                         ***  MODULE trcctl  ***
4   !! TOP :   control the cpp options, files and namelist values of a run
5   !!======================================================================
6   !! History :   1.0  !  2005-03 (O. Aumont, A. El Moussaoui) original code
[274]7   !!----------------------------------------------------------------------
[772]8#if defined key_top
[335]9   !!----------------------------------------------------------------------
[772]10   !!   'key_top'                                                TOP models
[763]11   !!----------------------------------------------------------------------
12   !!   trc_ctl    : control the cpp options, files and namelist values
13   !!----------------------------------------------------------------------
[335]14   USE oce_trc
15   USE trc
16   USE sms
17   USE trctrp_ctl
[268]18
[335]19   IMPLICIT NONE
20   PRIVATE
[268]21
[763]22   PUBLIC trc_ctl      ! called by ???
[268]23
[763]24   !!----------------------------------------------------------------------
25   !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)
26   !! $Header:$
27   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
28   !!----------------------------------------------------------------------
29
[268]30CONTAINS
31
[335]32   SUBROUTINE trc_ctl
[763]33      !!----------------------------------------------------------------------
34      !!                     ***  ROUTINE trc_ctl  ***
[335]35      !!
[763]36      !! ** Purpose :   control the cpp options, namelist and files
37      !!              we use IF/ENDIF inside #IF defined option-cpp
38      !!              FILE name must not exceed 21 characters
[335]39      !!----------------------------------------------------------------------
[763]40      INTEGER ::   istop, jn
41      !!----------------------------------------------------------------------
[268]42
[763]43      IF(lwp) WRITE(numout,*)
44      IF(lwp) WRITE(numout,*) ' trc_ctl :   passive tracer option'
45      IF(lwp) WRITE(numout,*) ' ~~~~~~~'
[268]46
[763]47      istop = 0      ! initialise to zero
[268]48
[763]49      ! restart for passive tracer (input)
50      IF( lrsttr ) THEN
51         IF(lwp) WRITE(numout,*) '       READ a restart FILE for passive tracer'
[335]52         IF(lwp) WRITE(numout,*) ' '
[268]53      ELSE
[763]54         IF(lwp) WRITE(numout,*) '       no restart FILE'
55         IF(lwp) WRITE(numout,*)
56         DO jn = 1, jptra
57            IF( lutini(jn) ) THEN      ! OPEN input FILE only IF lutini(jn) is true
[335]58               IF(lwp) WRITE(numout,*)  &
[763]59                  '       READ an initial FILE  for passive tracer number :', jn, ' traceur : ', ctrcnm(jn) 
[335]60            END IF
61         END DO
[268]62      ENDIF
63
[763]64      ! Don't USE non penetrative convective mixing option
65      ! it's not implemented for passive tracer
66      IF( ln_zdfnpc ) THEN
[335]67         IF(lwp) WRITE (numout,*) ' ===>>>> : w a r n i n g '
68         IF(lwp) WRITE (numout,*) ' =======   ============= '
69         IF(lwp) WRITE (numout,*) ' STOP, this sheme is not implemented'
70         IF(lwp) WRITE (numout,*) ' in passive tracer model:'
71         IF(lwp) WRITE (numout,*) ' non penetrative convect. mixing scheme'
72         istop = istop + 1
[268]73      ENDIF
74
[763]75      ! transport scheme option
[268]76      CALL trc_trp_ctl
77
[763]78      ! SMS model
[268]79      IF(lwp) WRITE(numout,*) '  '
[763]80      IF(lwp) WRITE(numout,*) '       Source/Sink model option'
[268]81      IF(lwp) WRITE(numout,*) '  '
82
[772]83# if defined key_lobster
[335]84#   include "trcctl.lobster1.h90"
[773]85
[772]86# elif defined key_pisces
[335]87#   include "trcctl.pisces.h90"
[773]88
[763]89# elif defined key_cfc
[335]90#   include "trcctl.cfc.h90"
[773]91
[763]92# else
93      IF(lwp) WRITE (numout,*) '       No Source/Sink '
94      IF(lwp) WRITE (numout,*)
[268]95#endif
96
[335]97      ! E r r o r  control
98      ! ------------------
[763]99      IF( istop > 0  ) THEN
[335]100         IF(lwp)WRITE(numout,*)
101         IF(lwp)WRITE(numout,*) istop,' E R R O R found : we stop'
[763]102         IF(lwp)WRITE(numout,*) '  **************************'
[335]103         IF(lwp)WRITE(numout,*)
104         STOP 'trcctl'
[268]105      ENDIF
[763]106      !
[335]107   END SUBROUTINE trc_ctl
[268]108
109#else
[763]110   !!----------------------------------------------------------------------
111   !!  Empty module :                                     No passive tracer
112   !!----------------------------------------------------------------------
[335]113CONTAINS
[763]114   SUBROUTINE trc_ctl                      ! Dummy routine
[335]115   END SUBROUTINE trc_ctl
[268]116#endif
117
[763]118   !!======================================================================
[268]119END MODULE trcctl
Note: See TracBrowser for help on using the repository browser.