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 503 for trunk/NEMO/OPA_SRC/TRD/trdvor.F90 – NEMO

Ignore:
Timestamp:
2006-09-27T10:52:29+02:00 (18 years ago)
Author:
opalod
Message:

nemo_v1_update_064 : CT : general trends update including the addition of mean windows analysis possibility in the mixed layer

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/TRD/trdvor.F90

    r462 r503  
    44   !! Ocean diagnostics:  momentum trends 
    55   !!===================================================================== 
    6     
     6   !! History :  9.0  !  04-06  (L. Brunier, A-M. Treguier) Original code  
     7   !!                 !  04-08  (C. Talandier) New trends organization 
     8   !!---------------------------------------------------------------------- 
    79#if defined key_trdvor   ||   defined key_esopa 
    810   !!---------------------------------------------------------------------- 
    911   !!   'key_trdvor'   : momentum trend diagnostics 
     12   !!---------------------------------------------------------------------- 
    1013   !!---------------------------------------------------------------------- 
    1114   !!   trd_vor      : momentum trends averaged over the depth 
     
    1316   !!   trd_vor_init : initialization step 
    1417   !!---------------------------------------------------------------------- 
    15    !! * Modules used 
    1618   USE oce             ! ocean dynamics and tracers variables 
    1719   USE dom_oce         ! ocean space and time domain variables 
     
    2729   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2830 
    29  
    3031   IMPLICIT NONE 
    3132   PRIVATE 
    3233 
    33    !! * Interfaces 
    3434   INTERFACE trd_vor_zint 
    3535      MODULE PROCEDURE trd_vor_zint_2d, trd_vor_zint_3d 
    3636   END INTERFACE 
    3737 
    38    !! * Accessibility 
    39    PUBLIC trd_vor        ! routine called by step.F90 
    40    PUBLIC trd_vor_zint   ! routine called by dynamics routines 
    41    PUBLIC trd_vor_init   ! routine called by opa.F90 
    42  
    43    !! * Shared module variables 
    44    LOGICAL, PUBLIC ::   lk_trdvor = .TRUE.   ! momentum trend flag 
    45  
    46    !! * Module variables 
     38   PUBLIC   trd_vor        ! routine called by step.F90 
     39   PUBLIC   trd_vor_zint   ! routine called by dynamics routines 
     40   PUBLIC   trd_vor_init   ! routine called by opa.F90 
     41 
    4742   INTEGER ::                & 
    4843      nh_t, nmoydpvor  ,     & 
     
    6156     vor_avrres 
    6257 
    63    REAL(wp), DIMENSION(jpi,jpj,jplvor)::   &  !: curl of trends 
    64       vortrd    
    65  
     58   REAL(wp), DIMENSION(jpi,jpj,jpltot_vor)::   vortrd  !: curl of trends 
     59          
    6660   CHARACTER(len=12) ::   cvort 
    6761 
     
    7064#  include "ldfdyn_substitute.h90" 
    7165#  include "vectopt_loop_substitute.h90" 
    72  
    7366   !!---------------------------------------------------------------------- 
    7467   !!   OPA 9.0 , LOCEAN-IPSL (2005)  
    7568   !! $Header$  
    76    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     69   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    7770   !!---------------------------------------------------------------------- 
    7871   
     
    8073 
    8174   SUBROUTINE trd_vor_zint_2d( putrdvor, pvtrdvor, ktrd ) 
     75      !!---------------------------------------------------------------------------- 
     76      !!                  ***  ROUTINE trd_vor_zint  *** 
     77      !! 
     78      !! ** Purpose :   computation of vertically integrated vorticity budgets 
     79      !!      from ocean surface down to control surface (NetCDF output) 
     80      !! 
     81      !! ** Method/usage : 
     82      !!      integration done over nwrite-1 time steps 
     83      !! 
     84      !! 
     85      !! ** Action : 
     86      !!            /comvor/   : 
     87      !!                         vor_avr          average 
     88      !!                         vor_avrb         vorticity at kt-1 
     89      !!                         vor_avrbb        vorticity at begining of the NWRITE-1 
     90      !!                                          time steps averaging period 
     91      !!                         vor_avrbn         vorticity at time step after the 
     92      !!                                          begining of the NWRITE-1 time 
     93      !!                                          steps averaging period 
     94      !! 
     95      !!                 trends : 
     96      !! 
     97      !!                  vortrd (,, 1) = Pressure Gradient Trend 
     98      !!                  vortrd (,, 2) = KE Gradient Trend 
     99      !!                  vortrd (,, 3) = Relative Vorticity Trend 
     100      !!                  vortrd (,, 4) = Coriolis Term Trend 
     101      !!                  vortrd (,, 5) = Horizontal Diffusion Trend 
     102      !!                  vortrd (,, 6) = Vertical Advection Trend 
     103      !!                  vortrd (,, 7) = Vertical Diffusion Trend 
     104      !!                  vortrd (,, 8) = Surface Pressure Grad. Trend 
     105      !!                  vortrd (,, 9) = Beta V 
     106      !!                  vortrd (,,10) = forcing term 
     107      !!      vortrd (,,11) = bottom friction term 
     108      !!                  rotot(,) : total cumulative trends over nwrite-1 time steps 
     109      !!                  vor_avrtot(,) : first membre of vrticity equation 
     110      !!                  vor_avrres(,) : residual = dh/dt entrainment 
     111      !! 
     112      !!      trends output in netCDF format using ioipsl 
     113      !! 
     114      !!---------------------------------------------------------------------- 
     115      INTEGER, INTENT( in ) ::   ktrd         ! ocean trend index 
     116      REAL(wp), DIMENSION(jpi,jpj), INTENT( inout ) ::   & 
     117         putrdvor,                         &  ! u vorticity trend  
     118         pvtrdvor                             ! v vorticity trend 
     119      !! 
     120      INTEGER ::   ji, jj 
     121      INTEGER ::   ikbu, ikbum1, ikbv, ikbvm1 
     122      REAL(wp), DIMENSION(jpi,jpj) ::   zudpvor, zvdpvor   ! total cmulative trends 
     123      !!---------------------------------------------------------------------- 
     124 
     125      ! Initialization 
     126      zudpvor(:,:) = 0.e0 
     127      zvdpvor(:,:) = 0.e0 
     128 
     129      CALL lbc_lnk( putrdvor,  'U' , -1. ) 
     130      CALL lbc_lnk( pvtrdvor,  'V' , -1. ) 
     131 
     132      !  ===================================== 
     133      !  I vertical integration of 2D trends 
     134      !  ===================================== 
     135 
     136      SELECT CASE (ktrd)  
     137 
     138      CASE (jpvor_bfr)        ! bottom friction 
     139 
     140         DO jj = 2, jpjm1 
     141            DO ji = fs_2, fs_jpim1  
     142               ikbu   = min( mbathy(ji+1,jj), mbathy(ji,jj) ) 
     143               ikbum1 = max( ikbu-1, 1 ) 
     144               ikbv   = min( mbathy(ji,jj+1), mbathy(ji,jj) ) 
     145               ikbvm1 = max( ikbv-1, 1 ) 
     146             
     147               zudpvor(ji,jj) = putrdvor(ji,jj) * fse3u(ji,jj,ikbum1) * e1u(ji,jj) * umask(ji,jj,ikbum1) 
     148               zvdpvor(ji,jj) = pvtrdvor(ji,jj) * fse3v(ji,jj,ikbvm1) * e2v(ji,jj) * vmask(ji,jj,ikbvm1) 
     149            END DO 
     150         END DO 
     151 
     152      CASE (jpvor_swf)        ! wind stress 
     153 
     154         zudpvor(:,:) = putrdvor(:,:) * fse3u(:,:,1) * e1u(:,:) * umask(:,:,1) 
     155         zvdpvor(:,:) = pvtrdvor(:,:) * fse3v(:,:,1) * e2v(:,:) * vmask(:,:,1) 
     156 
     157      END SELECT 
     158 
     159      ! Average except for Beta.V 
     160      zudpvor(:,:) = zudpvor(:,:) * hur(:,:) 
     161      zvdpvor(:,:) = zvdpvor(:,:) * hvr(:,:) 
     162    
     163      ! Curl 
     164      DO ji=1,jpim1 
     165         DO jj=1,jpjm1 
     166            vortrd(ji,jj,ktrd) = ( zvdpvor(ji+1,jj) - zvdpvor(ji,jj)        & 
     167                 &                - ( zudpvor(ji,jj+1) - zudpvor(ji,jj) ) ) & 
     168                 &               / ( e1f(ji,jj) * e2f(ji,jj) ) 
     169         END DO 
     170      END DO 
     171 
     172      ! Surface mask 
     173      vortrd(:,:,ktrd) = vortrd(:,:,ktrd) * fmask(:,:,1) 
     174 
     175      IF( idebug /= 0 ) THEN 
     176         IF(lwp) WRITE(numout,*) ' debuging trd_vor_zint: I done' 
     177         CALL FLUSH(numout) 
     178      ENDIF 
     179      ! 
     180   END SUBROUTINE trd_vor_zint_2d 
     181 
     182 
     183   SUBROUTINE trd_vor_zint_3d( putrdvor, pvtrdvor, ktrd ) 
    82184      !!---------------------------------------------------------------------------- 
    83185      !!                  ***  ROUTINE trd_vor_zint  *** 
     
    119221      !!      trends output in netCDF format using ioipsl 
    120222      !! 
    121       !! History : 
    122       !!   9.0  !  04-06  (L. Brunier, A-M. Treguier) Original code  
    123       !!        !  04-08  (C. Talandier) New trends organization 
    124       !!---------------------------------------------------------------------- 
    125       !! * Arguments 
     223      !!---------------------------------------------------------------------- 
    126224      INTEGER, INTENT( in ) ::   ktrd         ! ocean trend index 
    127  
    128       REAL(wp), DIMENSION(jpi,jpj), INTENT( inout ) ::   & 
    129          putrdvor,                         &  ! u vorticity trend  
    130          pvtrdvor                             ! v vorticity trend 
    131  
    132       !! * Local declarations 
    133       INTEGER ::   ji, jj 
    134       INTEGER ::   ikbu, ikbum1, ikbv, ikbvm1 
    135       REAL(wp), DIMENSION(jpi,jpj) ::   & 
    136          zudpvor,                       &  ! total cmulative trends 
    137          zvdpvor                           !   "      "        " 
    138       !!---------------------------------------------------------------------- 
    139  
    140       ! Initialization 
    141       zudpvor(:,:) = 0.e0 
    142       zvdpvor(:,:) = 0.e0 
    143  
    144       CALL lbc_lnk( putrdvor,  'U' , -1. ) 
    145       CALL lbc_lnk( pvtrdvor,  'V' , -1. ) 
    146  
    147       !  ===================================== 
    148       !  I vertical integration of 2D trends 
    149       !  ===================================== 
    150  
    151       SELECT CASE (ktrd)  
    152  
    153       CASE (jpvorbfr)        ! bottom friction 
    154  
    155          DO jj = 2, jpjm1 
    156             DO ji = fs_2, fs_jpim1  
    157                ikbu   = min( mbathy(ji+1,jj), mbathy(ji,jj) ) 
    158                ikbum1 = max( ikbu-1, 1 ) 
    159                ikbv   = min( mbathy(ji,jj+1), mbathy(ji,jj) ) 
    160                ikbvm1 = max( ikbv-1, 1 ) 
    161              
    162                zudpvor(ji,jj) = putrdvor(ji,jj) * fse3u(ji,jj,ikbum1) * e1u(ji,jj) * umask(ji,jj,ikbum1) 
    163                zvdpvor(ji,jj) = pvtrdvor(ji,jj) * fse3v(ji,jj,ikbvm1) * e2v(ji,jj) * vmask(ji,jj,ikbvm1) 
    164             END DO 
    165          END DO 
    166  
    167       CASE (jpvorswf)        ! wind stress 
    168  
    169          zudpvor(:,:) = putrdvor(:,:) * fse3u(:,:,1) * e1u(:,:) * umask(:,:,1) 
    170          zvdpvor(:,:) = pvtrdvor(:,:) * fse3v(:,:,1) * e2v(:,:) * vmask(:,:,1) 
    171  
    172       END SELECT 
    173  
    174       ! Average except for Beta.V 
    175       zudpvor(:,:) = zudpvor(:,:) * hur(:,:) 
    176       zvdpvor(:,:) = zvdpvor(:,:) * hvr(:,:) 
    177     
    178       ! Curl 
    179       DO ji=1,jpim1 
    180          DO jj=1,jpjm1 
    181             vortrd(ji,jj,ktrd) = ( zvdpvor(ji+1,jj) - zvdpvor(ji,jj)        & 
    182                  &                - ( zudpvor(ji,jj+1) - zudpvor(ji,jj) ) ) & 
    183                  &               / ( e1f(ji,jj) * e2f(ji,jj) ) 
    184          END DO 
    185       END DO 
    186  
    187       ! Surface mask 
    188       vortrd(:,:,ktrd) = vortrd(:,:,ktrd) * fmask(:,:,1) 
    189  
    190       IF( idebug /= 0 ) THEN 
    191          IF(lwp) WRITE(numout,*) ' debuging trd_vor_zint: I done' 
    192          CALL FLUSH(numout) 
    193       ENDIF 
    194  
    195    END SUBROUTINE trd_vor_zint_2d 
    196  
    197  
    198  
    199    SUBROUTINE trd_vor_zint_3d( putrdvor, pvtrdvor, ktrd ) 
    200       !!---------------------------------------------------------------------------- 
    201       !!                  ***  ROUTINE trd_vor_zint  *** 
    202       !! 
    203       !! ** Purpose :   computation of vertically integrated vorticity budgets 
    204       !!      from ocean surface down to control surface (NetCDF output) 
    205       !! 
    206       !! ** Method/usage : 
    207       !!      integration done over nwrite-1 time steps 
    208       !! 
    209       !! 
    210       !! ** Action : 
    211       !!            /comvor/   : 
    212       !!                         vor_avr          average 
    213       !!                         vor_avrb         vorticity at kt-1 
    214       !!                         vor_avrbb        vorticity at begining of the NWRITE-1 
    215       !!                                          time steps averaging period 
    216       !!                         vor_avrbn         vorticity at time step after the 
    217       !!                                          begining of the NWRITE-1 time 
    218       !!                                          steps averaging period 
    219       !! 
    220       !!                 trends : 
    221       !! 
    222       !!                  vortrd (,,1) = Pressure Gradient Trend 
    223       !!                  vortrd (,,2) = KE Gradient Trend 
    224       !!                  vortrd (,,3) = Relative Vorticity Trend 
    225       !!                  vortrd (,,4) = Coriolis Term Trend 
    226       !!                  vortrd (,,5) = Horizontal Diffusion Trend 
    227       !!                  vortrd (,,6) = Vertical Advection Trend 
    228       !!                  vortrd (,,7) = Vertical Diffusion Trend 
    229       !!                  vortrd (,,8) = Surface Pressure Grad. Trend 
    230       !!                  vortrd (,,9) = Beta V 
    231       !!                  vortrd (,,10) = forcing term 
    232       !!      vortrd (,,11) = bottom friction term 
    233       !!                  rotot(,) : total cumulative trends over nwrite-1 time steps 
    234       !!                  vor_avrtot(,) : first membre of vrticity equation 
    235       !!                  vor_avrres(,) : residual = dh/dt entrainment 
    236       !! 
    237       !!      trends output in netCDF format using ioipsl 
    238       !! 
    239       !! History : 
    240       !!   9.0  !  04-06  (L. Brunier, A-M. Treguier) Original code  
    241       !!        !  04-08  (C. Talandier) New trends organization 
    242       !!---------------------------------------------------------------------- 
    243       !! * Arguments 
    244       INTEGER, INTENT( in ) ::   ktrd         ! ocean trend index 
    245  
    246225      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   & 
    247226         putrdvor,                         &  ! u vorticity trend  
    248227         pvtrdvor                             ! v vorticity trend 
    249  
    250       !! * Local declarations 
     228      !! 
    251229      INTEGER ::   ji, jj, jk 
    252  
    253230      REAL(wp), DIMENSION(jpi,jpj) ::   & 
    254231         zubet,                         &  ! u Beta.V case 
     
    279256      ! Save Beta.V term to avoid average before Curl 
    280257      ! Beta.V : intergration, no average 
    281       IF( ktrd == jpvorbev ) THEN  
     258      IF( ktrd == jpvor_bev ) THEN  
    282259         zubet(:,:) = zudpvor(:,:) 
    283260         zvbet(:,:) = zvdpvor(:,:) 
     
    302279      ! Special treatement for the Beta.V term 
    303280      ! Compute the Curl of the Beta.V term which is not averaged 
    304       IF( ktrd == jpvorbev ) THEN 
     281      IF( ktrd == jpvor_bev ) THEN 
    305282         DO ji=1,jpim1 
    306283            DO jj=1,jpjm1 
    307                vortrd(ji,jj,jpvorbev) = (  zvbet(ji+1,jj) - zvbet(ji,jj) -   & 
     284               vortrd(ji,jj,jpvor_bev) = (  zvbet(ji+1,jj) - zvbet(ji,jj) -   & 
    308285                    &                    ( zubet(ji,jj+1) - zubet(ji,jj) ) ) & 
    309286                    &                   / ( e1f(ji,jj) * e2f(ji,jj) ) 
     
    312289 
    313290         ! Average on the Curl 
    314          vortrd(:,:,jpvorbev) = vortrd(:,:,jpvorbev) * hur(:,:) 
     291         vortrd(:,:,jpvor_bev) = vortrd(:,:,jpvor_bev) * hur(:,:) 
    315292 
    316293         ! Surface mask 
    317          vortrd(:,:,jpvorbev) = vortrd(:,:,jpvorbev) * fmask(:,:,1) 
     294         vortrd(:,:,jpvor_bev) = vortrd(:,:,jpvor_bev) * fmask(:,:,1) 
    318295      ENDIF 
    319296    
     
    322299         CALL FLUSH(numout) 
    323300      ENDIF 
    324  
     301      ! 
    325302   END SUBROUTINE trd_vor_zint_3d 
    326  
    327303 
    328304 
     
    333309      !! ** Purpose :  computation of cumulated trends over analysis period 
    334310      !!               and make outputs (NetCDF or DIMG format) 
    335       !! 
    336       !! ** Method/usage : 
    337       !! 
    338       !! History : 
    339       !!   9.0  !  04-06  (L. Brunier, A-M. Treguier) Original code  
    340       !!        !  04-08  (C. Talandier) New trends organization 
    341       !!---------------------------------------------------------------------- 
    342       !! * Arguments 
     311      !!---------------------------------------------------------------------- 
    343312      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
    344  
    345       !! * Local declarations 
    346       INTEGER :: ji, jj, jk, jl, it 
    347  
    348       REAL(wp) :: zmean 
    349  
    350       REAL(wp) ,DIMENSION(jpi,jpj) ::   & 
    351          zun, zvn 
     313      !! 
     314      INTEGER  ::   ji, jj, jk, jl, it 
     315      REAL(wp) ::   zmean 
     316      REAL(wp), DIMENSION(jpi,jpj) ::   zun, zvn 
    352317      !!---------------------------------------------------------------------- 
    353318 
     
    424389      IF( kt >= nit000+2 ) THEN 
    425390         nmoydpvor = nmoydpvor + 1 
    426          DO jl = 1, jplvor 
     391         DO jl = 1, jpltot_vor 
    427392            IF( jl /= 9 ) THEN 
    428393               rotot(:,:) = rotot(:,:) + vortrd(:,:,jl) 
     
    490455         it= kt-nit000+1 
    491456         IF( lwp .AND. MOD( kt, ntrd ) == 0 ) THEN 
    492             WRITE(numout,*) '     trdvor_ncwrite : write NetCDF fields' 
     457            WRITE(numout,*) '' 
     458            WRITE(numout,*) 'trd_vor : write trends in the NetCDF file at kt = ', kt 
     459            WRITE(numout,*) '~~~~~~~  ' 
    493460         ENDIF 
    494461  
    495          CALL histwrite( nidvor,"sovortPh",it,vortrd(:,:,1),ndimvor1,ndexvor1)  ! grad Ph 
    496          CALL histwrite( nidvor,"sovortEk",it,vortrd(:,:,2),ndimvor1,ndexvor1)  ! Energy 
    497          CALL histwrite( nidvor,"sovozeta",it,vortrd(:,:,3),ndimvor1,ndexvor1)  ! rel vorticity 
    498          CALL histwrite( nidvor,"sovortif",it,vortrd(:,:,4),ndimvor1,ndexvor1)  ! coriolis 
    499          CALL histwrite( nidvor,"sovodifl",it,vortrd(:,:,5),ndimvor1,ndexvor1)  ! lat diff 
    500          CALL histwrite( nidvor,"sovoadvv",it,vortrd(:,:,6),ndimvor1,ndexvor1)  ! vert adv 
    501          CALL histwrite( nidvor,"sovodifv",it,vortrd(:,:,7),ndimvor1,ndexvor1)  ! vert diff 
    502          CALL histwrite( nidvor,"sovortPs",it,vortrd(:,:,8),ndimvor1,ndexvor1)  ! grad Ps 
    503          CALL histwrite( nidvor,"sovortbv",it,vortrd(:,:,9),ndimvor1,ndexvor1)  ! beta.V 
    504          CALL histwrite( nidvor,"sovowind",it,vortrd(:,:,10),ndimvor1,ndexvor1) ! wind stress 
    505          CALL histwrite( nidvor,"sovobfri",it,vortrd(:,:,11),ndimvor1,ndexvor1) ! bottom friction 
     462         CALL histwrite( nidvor,"sovortPh",it,vortrd(:,:,jpvor_prg),ndimvor1,ndexvor1)  ! grad Ph 
     463         CALL histwrite( nidvor,"sovortEk",it,vortrd(:,:,jpvor_keg),ndimvor1,ndexvor1)  ! Energy 
     464         CALL histwrite( nidvor,"sovozeta",it,vortrd(:,:,jpvor_rvo),ndimvor1,ndexvor1)  ! rel vorticity 
     465         CALL histwrite( nidvor,"sovortif",it,vortrd(:,:,jpvor_pvo),ndimvor1,ndexvor1)  ! coriolis 
     466         CALL histwrite( nidvor,"sovodifl",it,vortrd(:,:,jpvor_ldf),ndimvor1,ndexvor1)  ! lat diff 
     467         CALL histwrite( nidvor,"sovoadvv",it,vortrd(:,:,jpvor_zad),ndimvor1,ndexvor1)  ! vert adv 
     468         CALL histwrite( nidvor,"sovodifv",it,vortrd(:,:,jpvor_zdf),ndimvor1,ndexvor1)  ! vert diff 
     469         CALL histwrite( nidvor,"sovortPs",it,vortrd(:,:,jpvor_spg),ndimvor1,ndexvor1)  ! grad Ps 
     470         CALL histwrite( nidvor,"sovortbv",it,vortrd(:,:,jpvor_bev),ndimvor1,ndexvor1)  ! beta.V 
     471         CALL histwrite( nidvor,"sovowind",it,vortrd(:,:,jpvor_swf),ndimvor1,ndexvor1) ! wind stress 
     472         CALL histwrite( nidvor,"sovobfri",it,vortrd(:,:,jpvor_bfr),ndimvor1,ndexvor1) ! bottom friction 
    506473         CALL histwrite( nidvor,"1st_mbre",it,vor_avrtot    ,ndimvor1,ndexvor1) ! First membre 
    507474         CALL histwrite( nidvor,"sovorgap",it,vor_avrres    ,ndimvor1,ndexvor1) ! gap between 1st and 2 nd mbre 
    508  
     475         ! 
    509476         IF( idebug /= 0 ) THEN 
    510477            WRITE(numout,*) ' debuging trd_vor: III.4 done' 
    511478            CALL FLUSH(numout) 
    512479         ENDIF 
    513  
    514       ENDIF 
    515  
     480         ! 
     481      ENDIF 
     482      ! 
    516483      IF( MOD( kt - nit000+1, ntrd ) == 0 ) rotot(:,:)=0 
    517  
     484      ! 
    518485      IF( kt == nitend )   CALL histclo( nidvor ) 
    519  
     486      ! 
    520487   END SUBROUTINE trd_vor 
    521  
    522488 
    523489 
     
    528494      !! ** Purpose :   computation of vertically integrated T and S budgets 
    529495      !!      from ocean surface down to control surface (NetCDF output) 
    530       !! 
    531       !! ** Method/usage : 
    532       !! 
    533       !! History : 
    534       !!   9.0  !  04-06  (L. Brunier, A-M. Treguier) Original code  
    535       !!        !  04-08  (C. Talandier) New trends organization 
    536       !!---------------------------------------------------------------------- 
    537       !! * Local declarations 
    538       REAL(wp) :: zjulian, zsto, zout 
    539  
     496      !!---------------------------------------------------------------------- 
     497      REAL(wp) ::   zjulian, zsto, zout 
    540498      CHARACTER (len=40) ::   clhstnam 
    541499      CHARACTER (len=40) ::   clop 
    542  
    543       NAMELIST/namtrd/ ntrd,nctls 
    544500      !!---------------------------------------------------------------------- 
    545501 
     
    553509      idebug = 0      ! set it to 1 in case of problem to have more Print 
    554510 
    555       ! namelist namtrd : trend diagnostic 
    556       REWIND( numnam ) 
    557       READ  ( numnam, namtrd ) 
    558  
    559511      IF(lwp) THEN 
    560512         WRITE(numout,*) ' ' 
    561          WRITE(numout,*) 'trd_vor_init: vorticity trends' 
    562          WRITE(numout,*) '~~~~~~~~~~~~~' 
     513         WRITE(numout,*) ' trd_vor_init: vorticity trends' 
     514         WRITE(numout,*) ' ~~~~~~~~~~~~' 
    563515         WRITE(numout,*) ' ' 
    564          WRITE(numout,*) '          Namelist namtrd : ' 
    565          WRITE(numout,*) '             time step frequency trend       ntrd  = ',ntrd 
    566          WRITE(numout,*) ' ' 
    567          WRITE(numout,*) '##########################################################################' 
    568          WRITE(numout,*) ' CAUTION: The interpretation of the vorticity trends is' 
    569          WRITE(numout,*) ' not obvious, please contact Anne-Marie TREGUIER at: treguier@ifremer.fr ' 
    570          WRITE(numout,*) '##########################################################################' 
     516         WRITE(numout,*) '               ##########################################################################' 
     517         WRITE(numout,*) '                CAUTION: The interpretation of the vorticity trends is' 
     518         WRITE(numout,*) '                not obvious, please contact Anne-Marie TREGUIER at: treguier@ifremer.fr ' 
     519         WRITE(numout,*) '               ##########################################################################' 
    571520         WRITE(numout,*) ' ' 
    572521      ENDIF 
     
    599548      zout = ntrd*rdt 
    600549 
    601       IF(lwp) WRITE (numout,*) ' trdvor_ncinit: netCDF initialization' 
     550      IF(lwp) WRITE(numout,*) '              netCDF initialization' 
    602551 
    603552      ! II.2 Compute julian date from starting date of the run 
    604553      ! ------------------------ 
    605554      CALL ymds2ju( nyear, nmonth, nday, 0.e0, zjulian ) 
    606       IF (lwp) WRITE(numout,*)' '   
    607       IF (lwp) WRITE(numout,*)' Date 0 used :',nit000         & 
    608            ,' YEAR ', nyear,' MONTH ', nmonth,' DAY ', nday   & 
    609            ,'Julian day : ', zjulian 
     555      IF(lwp) WRITE(numout,*)' '   
     556      IF(lwp) WRITE(numout,*)'               Date 0 used :',nit000,    & 
     557         &                   ' YEAR ', nyear,' MONTH '      , nmonth,   & 
     558         &                   ' DAY ' , nday, 'Julian day : ', zjulian 
    610559 
    611560      ! II.3 Define the T grid trend file (nidvor) 
     
    650599         CALL FLUSH(numout) 
    651600      ENDIF 
    652  
     601      ! 
    653602   END SUBROUTINE trd_vor_init 
    654603 
     
    657606   !!   Default option :                                       Empty module 
    658607   !!---------------------------------------------------------------------- 
    659    LOGICAL, PUBLIC ::   lk_trdvor = .FALSE.   ! momentum trend flag 
    660  
    661    !! * Interfaces 
    662608   INTERFACE trd_vor_zint 
    663609      MODULE PROCEDURE trd_vor_zint_2d, trd_vor_zint_3d 
    664610   END INTERFACE 
    665  
    666611CONTAINS 
    667612   SUBROUTINE trd_vor( kt )        ! Empty routine 
     
    669614   END SUBROUTINE trd_vor 
    670615   SUBROUTINE trd_vor_zint_2d( putrdvor, pvtrdvor, ktrd ) 
    671       REAL, DIMENSION(:,:), INTENT( inout ) ::   & 
    672          putrdvor, pvtrdvor                  ! U and V momentum trends 
     616      REAL, DIMENSION(:,:), INTENT( inout ) ::   putrdvor, pvtrdvor 
    673617      INTEGER, INTENT( in ) ::   ktrd         ! ocean trend index 
    674618      WRITE(*,*) 'trd_vor_zint_2d: You should not have seen this print! error?', putrdvor(1,1) 
     
    677621   END SUBROUTINE trd_vor_zint_2d 
    678622   SUBROUTINE trd_vor_zint_3d( putrdvor, pvtrdvor, ktrd ) 
    679       REAL, DIMENSION(:,:,:), INTENT( inout ) ::   & 
    680          putrdvor, pvtrdvor                  ! U and V momentum trends 
     623      REAL, DIMENSION(:,:,:), INTENT( inout ) ::   putrdvor, pvtrdvor 
    681624      INTEGER, INTENT( in ) ::   ktrd         ! ocean trend index 
    682625      WRITE(*,*) 'trd_vor_zint_3d: You should not have seen this print! error?', putrdvor(1,1,1) 
Note: See TracChangeset for help on using the changeset viewer.