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 NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/FLO – NEMO

source: NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/FLO/floats.F90 @ 10970

Last change on this file since 10970 was 10970, checked in by davestorkey, 5 years ago

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : CRS and FLO. Only tested compilation. Note that base code doesn't compile with key_floats (#2279), so changes to FLO not really tested at all.

  • Property svn:keywords set to Id
File size: 7.5 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   !!----------------------------------------------------------------------
[9124]9#if   defined   key_floats
[3]10   !!----------------------------------------------------------------------
11   !!   'key_floats'                                     float trajectories
12   !!----------------------------------------------------------------------
13   !!   flo_stp   : float trajectories computation
14   !!   flo_init  : initialization of float trajectories computation
15   !!----------------------------------------------------------------------
[2528]16   USE oce             ! ocean variables
[3]17   USE flo_oce         ! floats variables
18   USE lib_mpp         ! distributed memory computing
19   USE flodom          ! initialisation Module
20   USE flowri          ! float output                     (flo_wri routine)
[3294]21   USE florst          ! float restart                    (flo_rst routine)
[3]22   USE flo4rk          ! Trajectories, Runge Kutta scheme (flo_4rk routine)
23   USE floblk          ! Trajectories, Blanke scheme      (flo_blk routine)
[9124]24   !
[2528]25   USE in_out_manager  ! I/O manager
[3294]26   USE timing          ! preformance summary
[3]27
28   IMPLICIT NONE
29   PRIVATE 
30
[1601]31   PUBLIC   flo_stp    ! routine called by step.F90
[2528]32   PUBLIC   flo_init   ! routine called by opa.F90
[1601]33
[3]34   !!----------------------------------------------------------------------
[9598]35   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[1152]36   !! $Id$
[10068]37   !! Software governed by the CeCILL license (see ./LICENSE)
[3]38   !!----------------------------------------------------------------------
39CONTAINS
40
[10970]41   SUBROUTINE flo_stp( kt, Kbb, Kmm )
[3]42      !!----------------------------------------------------------------------
43      !!                   ***  ROUTINE flo_stp  ***
44      !!                   
45      !! ** Purpose :   Compute the geographical position (lat., long., depth)
46      !!      of each float at each time step with one of the algorithm.
47      !!
48      !! ** Method  :   The position of a float is computed with Bruno Blanke
49      !!        algorithm by default and with a 4th order Runge-Kutta scheme
50      !!        if ln_flork4 =T
51      !!----------------------------------------------------------------------
[10970]52      INTEGER, INTENT( in  ) ::   kt        ! ocean time step
53      INTEGER, INTENT( in  ) ::   Kbb, Kmm  ! ocean time level indices
[3]54      !!----------------------------------------------------------------------
[1601]55      !
[9124]56      IF( ln_timing )   CALL timing_start('flo_stp')
[3294]57      !
[10970]58      IF( ln_flork4 ) THEN   ;   CALL flo_4rk( kt, Kbb, Kmm )  ! Trajectories using a 4th order Runge Kutta scheme
59      ELSE                   ;   CALL flo_blk( kt, Kbb, Kmm )  ! Trajectories using Blanke' algorithme
[3]60      ENDIF
[1601]61      !
[16]62      IF( lk_mpp )   CALL mppsync   ! synchronization of all the processor
[1601]63      !
[10970]64      CALL flo_wri( kt, Kmm ) ! trajectories ouput
[1601]65      !
[3294]66      CALL flo_rst( kt )      ! trajectories restart
67      !
[10970]68      wb(:,:,:) = ww(:,:,:)         ! Save the old vertical velocity field
[1601]69      !
[9124]70      IF( ln_timing )   CALL timing_stop('flo_stp')
[3294]71      !
[3]72   END SUBROUTINE flo_stp
73
74
[10970]75   SUBROUTINE flo_init( Kmm )
[3]76      !!----------------------------------------------------------------
77      !!                 ***  ROUTINE flo_init  ***
78      !!                   
79      !! ** Purpose :   Read the namelist of floats
80      !!----------------------------------------------------------------------
[10970]81      INTEGER, INTENT(in) :: Kmm       ! ocean time level index
82      !
[9124]83      INTEGER ::   jfl
84      INTEGER ::   ios                 ! Local integer output status for namelist read
[3294]85      !
86      NAMELIST/namflo/ jpnfl, jpnnewflo, ln_rstflo, nn_writefl, nn_stockfl, ln_argo, ln_flork4, ln_ariane, ln_flo_ascii
[3]87      !!---------------------------------------------------------------------
[1601]88      !
[2715]89      IF(lwp) WRITE(numout,*)
90      IF(lwp) WRITE(numout,*) 'flo_stp : call floats routine '
91      IF(lwp) WRITE(numout,*) '~~~~~~~'
92
[4147]93      REWIND( numnam_ref )              ! Namelist namflo in reference namelist : Floats
94      READ  ( numnam_ref, namflo, IOSTAT = ios, ERR = 901)
[9168]95901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namflo in reference namelist', lwp )
[4147]96
97      REWIND( numnam_cfg )              ! Namelist namflo in configuration namelist : Floats
98      READ  ( numnam_cfg, namflo, IOSTAT = ios, ERR = 902 )
[9168]99902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namflo in configuration namelist', lwp )
[4624]100      IF(lwm) WRITE ( numond, namflo )
[1601]101      !
102      IF(lwp) THEN                  ! control print
103         WRITE(numout,*)
[3]104         WRITE(numout,*) '         Namelist floats :'
[3294]105         WRITE(numout,*) '            number of floats                      jpnfl        = ', jpnfl
106         WRITE(numout,*) '            number of new floats                  jpnflnewflo  = ', jpnnewflo
107         WRITE(numout,*) '            restart                               ln_rstflo    = ', ln_rstflo
108         WRITE(numout,*) '            frequency of float output file        nn_writefl   = ', nn_writefl
109         WRITE(numout,*) '            frequency of float restart file       nn_stockfl   = ', nn_stockfl
110         WRITE(numout,*) '            Argo type floats                      ln_argo      = ', ln_argo
111         WRITE(numout,*) '            Computation of T trajectories         ln_flork4    = ', ln_flork4
112         WRITE(numout,*) '            Use of ariane convention              ln_ariane    = ', ln_ariane
113         WRITE(numout,*) '            ascii output (T) or netcdf output (F) ln_flo_ascii = ', ln_flo_ascii
114
[3]115      ENDIF
[1601]116      !
[2715]117      !                             ! allocate floats arrays
118      IF( flo_oce_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'flo_init : unable to allocate arrays' )
119      !
[3294]120      !                             ! allocate flodom arrays
121      IF( flo_dom_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'flo_dom : unable to allocate arrays' )
122      !
[2715]123      !                             ! allocate flowri arrays
124      IF( flo_wri_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'flo_wri : unable to allocate arrays' )
125      !
[3294]126      !                             ! allocate florst arrays
127      IF( flo_rst_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'flo_rst : unable to allocate arrays' )
128      !
[9124]129      jpnrstflo = jpnfl-jpnnewflo   ! memory allocation
[3294]130      !
[9124]131      DO jfl = 1, jpnfl             ! vertical axe for netcdf IOM ouput
132         nfloat(jfl) = jfl 
133      END DO
134      !
[10970]135      CALL flo_dom( Kmm )           ! compute/read initial position of floats
[9124]136      !
[10970]137      wb(:,:,:) = ww(:,:,:)         ! set wb for computation of floats trajectories at the first time step
[2715]138      !
[3]139   END SUBROUTINE flo_init
140
141#  else
142   !!----------------------------------------------------------------------
143   !!   Default option :                                       Empty module
144   !!----------------------------------------------------------------------
145CONTAINS
[10970]146   SUBROUTINE flo_stp( kt, Kbb, Kmm )  ! Empty routine
[9927]147      IMPLICIT NONE
148      INTEGER, INTENT( in ) :: kt
[10970]149      INTEGER, INTENT( in ) :: Kbb, Kmm
[16]150      WRITE(*,*) 'flo_stp: You should not have seen this print! error?', kt
[3]151   END SUBROUTINE flo_stp
[10970]152   SUBROUTINE flo_init( Kmm )          ! Empty routine
[9927]153      IMPLICIT NONE
[10970]154      INTEGER, INTENT( in ) :: Kmm
[2528]155   END SUBROUTINE flo_init
[3]156#endif
157
158   !!======================================================================
159 END MODULE floats
Note: See TracBrowser for help on using the repository browser.