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 @ 896

Last change on this file since 896 was 719, checked in by ctlod, 17 years ago

get back to the nemo_v2_3 version for trunk

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.4 KB
Line 
1MODULE floats
2   !!======================================================================
3   !!                       ***  MODULE  floats  ***
4   !! Ocean floats : floats
5   !!======================================================================
6#if   defined key_floats   ||   defined key_esopa
7   !!----------------------------------------------------------------------
8   !!   'key_floats'                                     float trajectories
9   !!----------------------------------------------------------------------
10   !!   flo_stp   : float trajectories computation
11   !!   flo_init  : initialization of float trajectories computation
12   !!----------------------------------------------------------------------
13   !! * Modules used
14   USE flo_oce         ! floats variables
15   USE lib_mpp         ! distributed memory computing
16   USE flodom          ! initialisation Module
17   USE flowri          ! float output                     (flo_wri routine)
18   USE flo4rk          ! Trajectories, Runge Kutta scheme (flo_4rk routine)
19   USE floblk          ! Trajectories, Blanke scheme      (flo_blk routine)
20
21   IMPLICIT NONE
22   PRIVATE 
23
24   !! * Routine accessibility
25   PUBLIC flo_stp    ! routine called by step.F90
26   !!----------------------------------------------------------------------
27   !!   OPA 9.0 , LOCEAN-IPSL (2005)
28   !! $Header$
29   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
30   !!----------------------------------------------------------------------
31
32CONTAINS
33
34   SUBROUTINE flo_stp( kt )
35      !!----------------------------------------------------------------------
36      !!                   ***  ROUTINE flo_stp  ***
37      !!                   
38      !! ** Purpose :   Compute the geographical position (lat., long., depth)
39      !!      of each float at each time step with one of the algorithm.
40      !!
41      !! ** Method  :   The position of a float is computed with Bruno Blanke
42      !!        algorithm by default and with a 4th order Runge-Kutta scheme
43      !!        if ln_flork4 =T
44      !!     
45      !! History :
46      !!   8.5  !  02-06  (A. Bozec, G. Madec )  F90: Free form and module
47      !!----------------------------------------------------------------------
48      !! * arguments
49      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
50      !!----------------------------------------------------------------------
51
52      IF( kt == nit000 ) THEN
53         IF(lwp) WRITE(numout,*)
54         IF(lwp) WRITE(numout,*) 'flo_stp : call floats routine '
55         IF(lwp) WRITE(numout,*) '~~~~~~~'
56
57         CALL flo_init           ! read the namelist of floats             
58
59         CALL flo_dom            ! compute/read initial position of floats
60
61         ! Initialisation of wb for computation of floats trajectories at the first time step
62         wb(:,:,:) = wn(:,:,:)
63      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
69      ENDIF
70
71      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
84   END SUBROUTINE flo_stp
85
86
87   SUBROUTINE flo_init
88      !!----------------------------------------------------------------
89      !!                 ***  ROUTINE flo_init  ***
90      !!                   
91      !! ** 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
96      !!----------------------------------------------------------------------
97      !! * Modules used
98      USE ioipsl
99
100      !! * Local declarations
101      NAMELIST/namflo/ ln_rstflo, nwritefl, nstockfl, ln_argo, ln_flork4 
102      !!---------------------------------------------------------------------
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 )
112      READ  ( numnam, namflo )
113
114      IF(lwp) THEN
115         WRITE(numout,*) ' '
116         WRITE(numout,*) '         Namelist floats :'
117         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
120         WRITE(numout,*) '            Argo type floats                 ln_argo   = ', ln_argo
121         WRITE(numout,*) '            Computation of T trajectories    ln_flork4 = ', ln_flork4
122         WRITE(numout,*) ' '
123      ENDIF
124
125   END SUBROUTINE flo_init
126
127#  else
128   !!----------------------------------------------------------------------
129   !!   Default option :                                       Empty module
130   !!----------------------------------------------------------------------
131CONTAINS
132   SUBROUTINE flo_stp( kt )          ! Empty routine
133      WRITE(*,*) 'flo_stp: You should not have seen this print! error?', kt
134   END SUBROUTINE flo_stp
135#endif
136
137   !!======================================================================
138 END MODULE floats
Note: See TracBrowser for help on using the repository browser.