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.
Changeset 2528 for trunk/NEMOGCM/NEMO/OPA_SRC/TRD/trdmod.F90 – NEMO

Ignore:
Timestamp:
2010-12-27T18:33:53+01:00 (13 years ago)
Author:
rblod
Message:

Update NEMOGCM from branch nemo_v3_3_beta

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/TRD/trdmod.F90

    • Property svn:eol-style deleted
    r1708 r2528  
    44   !! Ocean diagnostics:  ocean tracers and dynamic trends 
    55   !!===================================================================== 
    6    !! History :  9.0  !  04-08  (C. Talandier) Original code 
    7    !!                 !  05-04  (C. Deltel)    Add Asselin trend in the ML budget 
     6   !! History :  1.0  !  2004-08  (C. Talandier) Original code 
     7   !!             -   !  2005-04  (C. Deltel)    Add Asselin trend in the ML budget 
     8   !!            3.3  ! 2010-10  (C. Ethe, G. Madec) reorganisation of initialisation phase 
    89   !!---------------------------------------------------------------------- 
    910#if  defined key_trdtra || defined key_trddyn || defined key_trdmld || defined key_trdvor || defined key_esopa 
     
    3637#  include "vectopt_loop_substitute.h90" 
    3738   !!---------------------------------------------------------------------- 
    38    !!   OPA 9.0 , LOCEAN-IPSL (2005)  
     39   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    3940   !! $Id$ 
    40    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     41   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    4142   !!---------------------------------------------------------------------- 
    4243 
    4344CONTAINS 
    4445 
    45    SUBROUTINE trd_mod( ptrdx, ptrdy, ktrd, ctype, kt, cnbpas ) 
     46   SUBROUTINE trd_mod( ptrdx, ptrdy, ktrd, ctype, kt ) 
    4647      !!--------------------------------------------------------------------- 
    4748      !!                  ***  ROUTINE trd_mod  *** 
     
    5354      INTEGER, INTENT( in ) ::   ktrd                              ! tracer trend index 
    5455      CHARACTER(len=3), INTENT( in ) ::   ctype                    ! momentum or tracers trends type 'DYN'/'TRA' 
    55       CHARACTER(len=3), INTENT( in ), OPTIONAL ::   cnbpas         ! number of passage 
    5656      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   ptrdx ! Temperature or U trend  
    5757      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   ptrdy ! Salinity    or V trend 
    5858      !! 
    5959      INTEGER ::   ji, jj 
    60       CHARACTER(len=3) ::   ccpas                                  ! number of passage 
    6160      REAL(wp), DIMENSION(jpi,jpj) ::   ztswu, ztswv               ! 2D workspace 
    6261      REAL(wp), DIMENSION(jpi,jpj) ::   ztbfu, ztbfv               ! 2D workspace 
     
    6564 
    6665      z2dx(:,:)   = 0.e0   ;   z2dy(:,:)   = 0.e0                  ! initialization of workspace arrays 
    67  
    68       ! Control of optional arguments 
    69       ccpas = 'fst' 
    70       IF( PRESENT(cnbpas) )  ccpas = cnbpas 
    7166 
    7267      IF( neuler == 0 .AND. kt == nit000    ) THEN   ;   r2dt =      rdt      ! = rdtra (restarting with Euler time stepping) 
     
    9590            CASE ( jptra_trd_yad )   ;   CALL trd_icp( ptrdx, ptrdy, jpicpt_yad, ctype )   ! y- horiz adv 
    9691            CASE ( jptra_trd_zad )                                                         ! z- vertical adv  
    97                CALL trd_icp( ptrdx, ptrdy, jpicpt_zad, ctype, clpas=ccpas )    
     92               CALL trd_icp( ptrdx, ptrdy, jpicpt_zad, ctype )    
    9893               ! compute the surface flux condition wn(:,:,1)*tn(:,:,1) 
    9994               z2dx(:,:) = wn(:,:,1)*tn(:,:,1)/fse3t(:,:,1) 
     
    222217 
    223218      ENDIF 
    224  
     219      ! 
    225220   END SUBROUTINE trd_mod 
    226221 
    227 #   else 
     222#else 
    228223   !!---------------------------------------------------------------------- 
    229224   !!   Default case :                                         Empty module 
     
    235230 
    236231CONTAINS 
    237    SUBROUTINE trd_mod(ptrd3dx, ptrd3dy, ktrd , ctype, kt, cnbpas)   ! Empty routine 
    238       REAL, DIMENSION(:,:,:), INTENT( in ) ::   & 
    239           ptrd3dx,                     &                           ! Temperature or U trend  
    240           ptrd3dy                                                  ! Salinity    or V trend 
    241       INTEGER, INTENT( in ) ::   ktrd                              ! momentum or tracer trend index 
    242       INTEGER, INTENT( in ) ::   kt                                ! Time step 
    243       CHARACTER(len=3), INTENT( in ) ::  ctype                     ! momentum or tracers trends type 
    244       CHARACTER(len=3), INTENT( in ), OPTIONAL ::   cnbpas         ! number of passage 
    245       WRITE(*,*) 'trd_3d: You should not have seen this print! error ?', ptrd3dx(1,1,1) 
    246       WRITE(*,*) ' "   ": You should not have seen this print! error ?', ptrd3dy(1,1,1) 
    247       WRITE(*,*) ' "   ": You should not have seen this print! error ?', ktrd 
    248       WRITE(*,*) ' "   ": You should not have seen this print! error ?', ctype 
    249       WRITE(*,*) ' "   ": You should not have seen this print! error ?', kt 
    250       WRITE(*,*) ' "   ": You should not have seen this print! error ?', cnbpas 
     232   SUBROUTINE trd_mod(ptrd3dx, ptrd3dy, ktrd , ctype, kt )   ! Empty routine 
     233      REAL    ::   ptrd3dx(:,:,:), ptrd3dy(:,:,:) 
     234      INTEGER ::   ktrd, kt                             
     235      CHARACTER(len=3) ::  ctype                   
     236      WRITE(*,*) 'trd_3d: You should not have seen this print! error ?', ptrd3dx(1,1,1), ptrd3dy(1,1,1) 
     237      WRITE(*,*) ' "   ": You should not have seen this print! error ?', ktrd, ctype, kt 
    251238   END SUBROUTINE trd_mod 
    252 #   endif 
     239#endif 
    253240 
    254241   SUBROUTINE trd_mod_init 
     
    259246      !!---------------------------------------------------------------------- 
    260247      USE in_out_manager          ! I/O manager 
    261  
     248      !!     
    262249      NAMELIST/namtrd/ nn_trd, nn_ctls, cn_trdrst_in, cn_trdrst_out, ln_trdmld_restart, rn_ucf, ln_trdmld_instant 
    263250      !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.