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 1601 for trunk/NEMO/OPA_SRC/FLO – NEMO

Ignore:
Timestamp:
2009-08-11T12:09:19+02:00 (15 years ago)
Author:
ctlod
Message:

Doctor naming of OPA namelist variables , see ticket: #526

Location:
trunk/NEMO/OPA_SRC/FLO
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/FLO/flo_oce.F90

    r1152 r1601  
    22   !!====================================================================== 
    33   !!                     ***  MODULE flo_oce  *** 
    4    !!                 
    5    !! ** Purpose : - Define in memory all floats parameters and variables 
    6    !! 
    7    !! History : 
    8    !!   8.0  !  99-10  (CLIPPER projet) 
    9    !!   9.0  !  02-11  (G. Madec, A. Bozec)  F90: Free form and module 
     4   !! lagrangian floats :   define in memory all floats parameters and variables 
    105   !!====================================================================== 
    11    !!  OPA 9.0 , LOCEAN-IPSL (2005)  
    12    !! $Id$  
    13    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     6   !! History :   OPA  ! 1999-10  (CLIPPER projet) 
     7   !!   NEMO      1.0  ! 2002-11  (G. Madec, A. Bozec)  F90: Free form and module 
    148   !!---------------------------------------------------------------------- 
    159#if   defined key_floats   ||   defined key_esopa 
     
    1711   !!   'key_floats'                                        drifting floats 
    1812   !!---------------------------------------------------------------------- 
    19    !! * Modules used 
    2013   USE par_oce         ! ocean parameters 
    2114 
    2215   IMPLICIT NONE 
     16   PUBLIC 
    2317 
    2418   LOGICAL, PUBLIC, PARAMETER ::   lk_floats = .TRUE.    !: float flag 
     
    2620   !! float parameters 
    2721   !! ---------------- 
    28    INTEGER, PARAMETER ::   & 
    29       jpnfl     = 23 ,            &  ! total number of floats during the run 
    30       jpnnewflo =  0 ,            &  ! number of floats added in a new run 
    31       jpnrstflo = jpnfl-jpnnewflo    ! number of floats for the restart 
     22   INTEGER, PUBLIC, PARAMETER ::   jpnfl     = 23 ,                !: total number of floats during the run 
     23   INTEGER, PUBLIC, PARAMETER ::   jpnnewflo =  0 ,                !: number of floats added in a new run 
     24   INTEGER, PUBLIC, PARAMETER ::   jpnrstflo = jpnfl - jpnnewflo   !: number of floats for the restart 
    3225 
    3326   !! float variables 
    3427   !! --------------- 
    35    INTEGER, DIMENSION(jpnfl)  ::    & 
    36       nisobfl,    &  ! 0 for a isobar float 
    37       !              ! 1 for a float following the w velocity 
    38       ngrpfl         ! number to identify searcher group 
     28   INTEGER, PUBLIC, DIMENSION(jpnfl)  ::   nisobfl   !: =0 for a isobar float , =1 for a float following the w velocity 
     29   INTEGER, PUBLIC, DIMENSION(jpnfl)  ::   ngrpfl    !: number to identify searcher group 
    3930 
    40    REAL(wp), DIMENSION(jpnfl) ::    & 
    41       flxx,       &  ! longitude of float (decimal degree) 
    42       flyy,       &  ! latitude of float (decimal degree) 
    43       flzz,       &  ! depth of float (m, positive) 
    44       tpifl,      &  ! index of float position on zonal axe 
    45       tpjfl,      &  ! index of float position on meridien axe 
    46       tpkfl          ! index of float position on z axe 
     31   REAL(wp), PUBLIC, DIMENSION(jpnfl) ::   flxx , flyy , flzz    !: longitude, latitude, depth of float (decimal degree, m >0) 
     32   REAL(wp), PUBLIC, DIMENSION(jpnfl) ::   tpifl, tpjfl, tpkfl   !: (i,j,k) indices of float position 
     33 
     34   REAL(wp), PUBLIC, DIMENSION(jpi, jpj, jpk) ::   wb            !: vertical velocity at previous time step (m s-1). 
    4735    
    48    REAL(wp), DIMENSION(jpi, jpj, jpk) ::    &  
    49       wb             ! vertical velocity at previous time step (m s-1). 
    50     
    51    ! floats unit 
    52     
    53    LOGICAL  ::                & !!! * namelist namflo * 
    54       ln_rstflo = .FALSE. ,   &  ! T/F float restart  
    55       ln_argo   = .FALSE. ,   &  ! T/F argo type floats 
    56       ln_flork4 = .FALSE.        ! T/F 4th order Runge-Kutta 
    57    INTEGER  ::               & !!! * namelist namflo * 
    58       nwritefl,              &  ! frequency of float output file  
    59       nstockfl                  ! frequency of float restart file 
     36   !                                  !!! * namelist namflo : langrangian floats * 
     37   LOGICAL, PUBLIC  ::   ln_rstflo  = .FALSE.    !: T/F float restart  
     38   LOGICAL, PUBLIC  ::   ln_argo    = .FALSE.    !: T/F argo type floats 
     39   LOGICAL, PUBLIC  ::   ln_flork4  = .FALSE.    !: T/F 4th order Runge-Kutta 
     40   INTEGER, PUBLIC  ::   nn_writefl = 150       !: frequency of float output file  
     41   INTEGER, PUBLIC  ::   nn_stockfl = 450       !: frequency of float restart file 
    6042 
    6143#else 
     
    6648#endif 
    6749 
     50   !!---------------------------------------------------------------------- 
     51   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)  
     52   !! $Id$  
     53   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    6854   !!====================================================================== 
    6955END MODULE flo_oce 
  • trunk/NEMO/OPA_SRC/FLO/floats.F90

    r1152 r1601  
    44   !! Ocean floats : floats 
    55   !!====================================================================== 
     6   !! History :  OPA  !          (CLIPPER)   original Code 
     7   !!   NEMO     1.0  ! 2002-06  (A. Bozec)  F90, Free form and module 
     8   !!---------------------------------------------------------------------- 
    69#if   defined key_floats   ||   defined key_esopa 
    710   !!---------------------------------------------------------------------- 
     
    1114   !!   flo_init  : initialization of float trajectories computation 
    1215   !!---------------------------------------------------------------------- 
    13    !! * Modules used 
    1416   USE flo_oce         ! floats variables 
    1517   USE lib_mpp         ! distributed memory computing 
     
    2224   PRIVATE   
    2325 
    24    !! * Routine accessibility 
    25    PUBLIC flo_stp    ! routine called by step.F90 
     26   PUBLIC   flo_stp    ! routine called by step.F90 
     27 
    2628   !!---------------------------------------------------------------------- 
    27    !!   OPA 9.0 , LOCEAN-IPSL (2005)  
     29   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)  
    2830   !! $Id$  
    29    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     31   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    3032   !!---------------------------------------------------------------------- 
    3133 
     
    4244      !!        algorithm by default and with a 4th order Runge-Kutta scheme 
    4345      !!        if ln_flork4 =T 
    44       !!       
    45       !! History : 
    46       !!   8.5  !  02-06  (A. Bozec, G. Madec )  F90: Free form and module 
    4746      !!---------------------------------------------------------------------- 
    48       !! * arguments 
    4947      INTEGER, INTENT( in  ) ::   kt   ! ocean time step 
    5048      !!---------------------------------------------------------------------- 
    51  
     49      ! 
    5250      IF( kt == nit000 ) THEN 
    5351         IF(lwp) WRITE(numout,*) 
     
    5957         CALL flo_dom            ! compute/read initial position of floats 
    6058 
    61          ! Initialisation of wb for computation of floats trajectories at the first time step 
    62          wb(:,:,:) = wn(:,:,:) 
     59         wb(:,:,:) = wn(:,:,:)   ! set wb for computation of floats trajectories at the first time step 
    6360      ENDIF 
    64  
    65       IF( ln_flork4 ) THEN 
    66          CALL flo_4rk( kt )        ! Trajectories using a 4th order Runge Kutta scheme 
    67       ELSE 
    68          CALL flo_blk( kt )        ! Trajectories using Blanke' algorithme 
     61      ! 
     62      IF( ln_flork4 ) THEN   ;   CALL flo_4rk( kt )        ! Trajectories using a 4th order Runge Kutta scheme 
     63      ELSE                   ;   CALL flo_blk( kt )        ! Trajectories using Blanke' algorithme 
    6964      ENDIF 
    70  
     65      ! 
    7166      IF( lk_mpp )   CALL mppsync   ! synchronization of all the processor 
    72  
    73  
    74       ! Writing and restart       
    75        
    76       ! trajectories file  
    77       IF( kt == nit000 .OR. MOD( kt, nwritefl ) == 0 )   CALL flo_wri( kt ) 
    78       ! restart file  
    79       IF( kt == nitend .OR. MOD( kt, nstockfl ) == 0 )   CALL flo_wri( kt ) 
    80  
    81       ! Save the old vertical velocity field 
    82       wb(:,:,:) = wn(:,:,:) 
    83  
     67      ! 
     68      IF( kt == nit000 .OR. MOD( kt, nn_writefl ) == 0 )   CALL flo_wri( kt )      ! trajectories file  
     69      IF( kt == nitend .OR. MOD( kt, nn_stockfl ) == 0 )   CALL flo_wri( kt )      ! restart file  
     70      ! 
     71      wb(:,:,:) = wn(:,:,:)         ! Save the old vertical velocity field 
     72      ! 
    8473   END SUBROUTINE flo_stp 
    8574 
     
    9079      !!                    
    9180      !! ** Purpose :   Read the namelist of floats 
    92       !!       
    93       !! History : 
    94       !!   8.0  !         (CLIPPER)   original Code 
    95       !!   8.5  !  02-06  (A. Bozec)  F90, Free form and module 
    9681      !!---------------------------------------------------------------------- 
    97       !! * Modules used 
    9882      USE ioipsl 
    99  
    100       !! * Local declarations 
    101       NAMELIST/namflo/ ln_rstflo, nwritefl, nstockfl, ln_argo, ln_flork4  
     83      !! 
     84      NAMELIST/namflo/ ln_rstflo, nn_writefl, nn_stockfl, ln_argo, ln_flork4  
    10285      !!--------------------------------------------------------------------- 
    103       ! Namelist namflo : floats 
    104        
    105       ! default values 
    106       ln_rstflo  = .FALSE. 
    107       nwritefl  = 150 
    108       nstockfl  = 450 
    109        
    110       ! lecture of namflo 
    111       REWIND( numnam ) 
     86      ! 
     87      REWIND( numnam )              ! Namelist namflo : floats 
    11288      READ  ( numnam, namflo ) 
    113  
    114       IF(lwp) THEN 
    115          WRITE(numout,*) ' ' 
     89      ! 
     90      IF(lwp) THEN                  ! control print 
     91         WRITE(numout,*) 
    11692         WRITE(numout,*) '         Namelist floats :' 
    11793         WRITE(numout,*) '            restart                          ln_rstflo = ', ln_rstflo 
    118          WRITE(numout,*) '            frequency of float output file   nwritefl  = ', nwritefl 
    119          WRITE(numout,*) '            frequency of float restart file  nstockfl  = ', nstockfl 
     94         WRITE(numout,*) '            frequency of float output file   nn_writefl  = ', nn_writefl 
     95         WRITE(numout,*) '            frequency of float restart file  nn_stockfl  = ', nn_stockfl 
    12096         WRITE(numout,*) '            Argo type floats                 ln_argo   = ', ln_argo 
    12197         WRITE(numout,*) '            Computation of T trajectories    ln_flork4 = ', ln_flork4 
    122          WRITE(numout,*) ' ' 
    12398      ENDIF 
    124  
     99      ! 
    125100   END SUBROUTINE flo_init 
    126101 
  • trunk/NEMO/OPA_SRC/FLO/flowri.F90

    r1581 r1601  
    22   !!====================================================================== 
    33   !!                       ***  MODULE  flowri  *** 
    4    !!  
     4   !! lagrangian floats :   outputs 
    55   !!====================================================================== 
     6   !! History :   OPA  ! 1999-09  (Y. Drillet)  Original code 
     7   !!                  ! 2000-06  (J.-M. Molines)  Profiling floats for CLS  
     8   !!   NEMO      1.0  ! 2002-11  (G. Madec, A. Bozec)  F90: Free form and module 
     9   !!---------------------------------------------------------------------- 
     10 
    611#if   defined key_floats   ||   defined key_esopa 
    712   !!---------------------------------------------------------------------- 
     
    1015   !!    flowri     : write trajectories of floats in file  
    1116   !!---------------------------------------------------------------------- 
    12    !! * Modules used 
    1317   USE flo_oce         ! ocean drifting floats 
    1418   USE oce             ! ocean dynamics and tracers 
     
    1923 
    2024   IMPLICIT NONE 
    21  
    22    !! * Accessibility 
    2325   PRIVATE 
    24    PUBLIC flo_wri     ! routine called by floats.F90 
    25  
    26    !! * Module variables 
    27       INTEGER :: jfl              ! number of floats 
     26 
     27   PUBLIC   flo_wri    ! routine called by floats.F90 
     28 
     29   INTEGER ::   jfl    ! number of floats 
    2830 
    2931   !! * Substitutions 
    3032#  include "domzgr_substitute.h90" 
    3133   !!---------------------------------------------------------------------- 
    32    !!   OPA 9.0 , LOCEAN-IPSL (2005)  
     34   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)  
    3335   !! $Id$  
    34    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     36   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    3537   !!---------------------------------------------------------------------- 
    3638 
     
    3840 
    3941   SUBROUTINE flo_wri( kt ) 
    40       !!--------------------------------------------------------------------- 
     42      !!------------------------------------------------------------------- 
    4143      !!                  ***  ROUTINE flo_wri  *** 
    4244      !!              
     
    4446      !!      and the temperature and salinity at this position 
    4547      !!       
    46       !! ** Method  :   The frequency is nwritefl 
    47       !!       
    48       !!  History : 
    49       !!    8.0  !  99-09  (Y. Drillet)  Original code 
    50       !!         !  00-06  (J.-M. Molines)  Profiling floats for CLS  
    51       !!    8.5  !  02-10  (A. Bozec)  F90: Free form and module 
     48      !! ** Method  :   The frequency is nn_writefl 
    5249      !!---------------------------------------------------------------------- 
    53       !! * Arguments 
    54       INTEGER  :: kt                               ! time step 
    55  
    56       !! * Local declarations 
     50      INTEGER ::   kt   ! time step 
     51      !! 
    5752      CHARACTER (len=21) ::  clname 
    58       INTEGER ::   inum            ! temporary logical unit for restart file 
    59       INTEGER  ::   & 
    60          iafl,ibfl,icfl,ia1fl,ib1fl,ic1fl,jfl,irecflo,   & 
    61          iafloc,ibfloc,ia1floc,ib1floc,   & 
    62          iafln, ibfln 
     53      INTEGER ::   inum   ! temporary logical unit for restart file 
     54      INTEGER ::   iafl, ibfl, icfl, ia1fl, ib1fl, ic1fl, jfl, irecflo,   & 
     55      INTEGER ::   iafloc, ibfloc, ia1floc, ib1floc, iafln, ibfln 
    6356      INTEGER  ::    ic, jc , jpn 
    6457      INTEGER, DIMENSION ( jpnij )  :: iproc 
     
    6962      !!--------------------------------------------------------------------- 
    7063       
    71       IF( kt == nit000 .OR. MOD( kt,nwritefl)== 0 ) THEN  
     64      IF( kt == nit000 .OR. MOD( kt,nn_writefl)== 0 ) THEN  
    7265 
    7366         ! header of output floats file 
     
    8477 
    8578         IF( kt == nit000 ) THEN 
    86             irecflo = NINT( (nitend-nit000) / FLOAT(nwritefl) ) 
    87             IF(lwp) WRITE(numflo)cexper,no,irecflo,jpnfl,nwritefl 
     79            irecflo = NINT( (nitend-nit000) / FLOAT(nn_writefl) ) 
     80            IF(lwp) WRITE(numflo)cexper,no,irecflo,jpnfl,nn_writefl 
    8881         ENDIF 
    8982         zdtj = rdt / 86400.      !!bug   use of 86400 instead of the phycst parameter 
     
    246239      ENDIF 
    247240       
    248       IF( (MOD(kt,nstockfl) == 0) .OR. ( kt == nitend ) ) THEN  
     241      IF( (MOD(kt,nn_stockfl) == 0) .OR. ( kt == nitend ) ) THEN  
    249242         ! Writing the restart file  
    250243         IF(lwp) THEN 
Note: See TracChangeset for help on using the changeset viewer.