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.
floats.F90 in trunk/NEMO/OPA_SRC/FLO – NEMO

source: trunk/NEMO/OPA_SRC/FLO/floats.F90 @ 2325

Last change on this file since 2325 was 1601, checked in by ctlod, 15 years ago

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

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 5.2 KB
RevLine 
[3]1MODULE floats
2   !!======================================================================
3   !!                       ***  MODULE  floats  ***
4   !! Ocean floats : floats
5   !!======================================================================
[1601]6   !! History :  OPA  !          (CLIPPER)   original Code
7   !!   NEMO     1.0  ! 2002-06  (A. Bozec)  F90, Free form and module
8   !!----------------------------------------------------------------------
[3]9#if   defined key_floats   ||   defined key_esopa
10   !!----------------------------------------------------------------------
11   !!   'key_floats'                                     float trajectories
12   !!----------------------------------------------------------------------
13   !!   flo_stp   : float trajectories computation
14   !!   flo_init  : initialization of float trajectories computation
15   !!----------------------------------------------------------------------
16   USE flo_oce         ! floats variables
17   USE lib_mpp         ! distributed memory computing
18   USE flodom          ! initialisation Module
19   USE flowri          ! float output                     (flo_wri routine)
20   USE flo4rk          ! Trajectories, Runge Kutta scheme (flo_4rk routine)
21   USE floblk          ! Trajectories, Blanke scheme      (flo_blk routine)
22
23   IMPLICIT NONE
24   PRIVATE 
25
[1601]26   PUBLIC   flo_stp    ! routine called by step.F90
27
[3]28   !!----------------------------------------------------------------------
[1601]29   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)
[1152]30   !! $Id$
[1601]31   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
[3]32   !!----------------------------------------------------------------------
33
34CONTAINS
35
36   SUBROUTINE flo_stp( kt )
37      !!----------------------------------------------------------------------
38      !!                   ***  ROUTINE flo_stp  ***
39      !!                   
40      !! ** Purpose :   Compute the geographical position (lat., long., depth)
41      !!      of each float at each time step with one of the algorithm.
42      !!
43      !! ** Method  :   The position of a float is computed with Bruno Blanke
44      !!        algorithm by default and with a 4th order Runge-Kutta scheme
45      !!        if ln_flork4 =T
46      !!----------------------------------------------------------------------
47      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
48      !!----------------------------------------------------------------------
[1601]49      !
[3]50      IF( kt == nit000 ) THEN
51         IF(lwp) WRITE(numout,*)
52         IF(lwp) WRITE(numout,*) 'flo_stp : call floats routine '
53         IF(lwp) WRITE(numout,*) '~~~~~~~'
54
55         CALL flo_init           ! read the namelist of floats             
56
57         CALL flo_dom            ! compute/read initial position of floats
58
[1601]59         wb(:,:,:) = wn(:,:,:)   ! set wb for computation of floats trajectories at the first time step
[3]60      ENDIF
[1601]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
[3]64      ENDIF
[1601]65      !
[16]66      IF( lk_mpp )   CALL mppsync   ! synchronization of all the processor
[1601]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      !
[3]73   END SUBROUTINE flo_stp
74
75
76   SUBROUTINE flo_init
77      !!----------------------------------------------------------------
78      !!                 ***  ROUTINE flo_init  ***
79      !!                   
80      !! ** Purpose :   Read the namelist of floats
81      !!----------------------------------------------------------------------
82      USE ioipsl
[1601]83      !!
84      NAMELIST/namflo/ ln_rstflo, nn_writefl, nn_stockfl, ln_argo, ln_flork4 
[3]85      !!---------------------------------------------------------------------
[1601]86      !
87      REWIND( numnam )              ! Namelist namflo : floats
[3]88      READ  ( numnam, namflo )
[1601]89      !
90      IF(lwp) THEN                  ! control print
91         WRITE(numout,*)
[3]92         WRITE(numout,*) '         Namelist floats :'
[16]93         WRITE(numout,*) '            restart                          ln_rstflo = ', ln_rstflo
[1601]94         WRITE(numout,*) '            frequency of float output file   nn_writefl  = ', nn_writefl
95         WRITE(numout,*) '            frequency of float restart file  nn_stockfl  = ', nn_stockfl
[623]96         WRITE(numout,*) '            Argo type floats                 ln_argo   = ', ln_argo
97         WRITE(numout,*) '            Computation of T trajectories    ln_flork4 = ', ln_flork4
[3]98      ENDIF
[1601]99      !
[3]100   END SUBROUTINE flo_init
101
102#  else
103   !!----------------------------------------------------------------------
104   !!   Default option :                                       Empty module
105   !!----------------------------------------------------------------------
106CONTAINS
107   SUBROUTINE flo_stp( kt )          ! Empty routine
[16]108      WRITE(*,*) 'flo_stp: You should not have seen this print! error?', kt
[3]109   END SUBROUTINE flo_stp
110#endif
111
112   !!======================================================================
113 END MODULE floats
Note: See TracBrowser for help on using the repository browser.