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.
florst.F90 in branches/2011/dev_r2802_MERCATOR9_floats/NEMOGCM/NEMO/OPA_SRC/FLO – NEMO

source: branches/2011/dev_r2802_MERCATOR9_floats/NEMOGCM/NEMO/OPA_SRC/FLO/florst.F90 @ 2844

Last change on this file since 2844 was 2844, checked in by cbricaud, 13 years ago

minor corrections

File size: 4.7 KB
Line 
1MODULE florst
2   !!======================================================================
3   !!                       ***  MODULE  florst  ***
4   !! blablabla: floteur....
5   !!======================================================================
6   !!  History :
7   !!    8.0  !  99-09  (Y. Drillet)    : Original code
8   !!         !  00-06  (J.-M. Molines) : Profiling floats for CLS
9   !!    8.5  !  02-10  (A. Bozec)  F90 : Free form and module
10   !!    3.2  !  10-08  (slaw, cbricaud): netcdf outputs and others
11   !!----------------------------------------------------------------------
12#if   defined key_floats   ||   defined key_esopa
13   !!----------------------------------------------------------------------
14   !!   'key_floats'                                     float trajectories
15   !!----------------------------------------------------------------------
16
17   !! * Modules used
18   USE flo_oce         ! ocean drifting floats
19   USE dom_oce         ! ocean space and time domain
20   USE lib_mpp         ! distribued memory computing library
21   USE in_out_manager  ! I/O manager
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC flo_rst      ! routine called by floats.F90
27
28   !! * Substitutions
29#  include "domzgr_substitute.h90"
30   !!----------------------------------------------------------------------
31   !! NEMO/OPA 3.2 , LODYC-IPSL  (2009)
32   !! $Header:
33   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
34   !!----------------------------------------------------------------------
35
36CONTAINS
37
38   SUBROUTINE flo_rst( kt )
39      !!---------------------------------------------------------------------
40      !!                  ***  ROUTINE flo_rst ***
41      !!             
42      !! ** Purpose : 
43      !!             
44      !!   
45      !!     
46      !! ** Method  :   The frequency of  ??? is nwritefl
47      !!     
48      !!----------------------------------------------------------------------
49      !! * Arguments
50      INTEGER  :: kt                            ! time step
51
52      !! * Local declarations
53      CHARACTER (len=80)       :: clname             ! restart filename
54      INTEGER                  :: ic , jc , jpn ,jfl ! temporary integer
55      INTEGER                  :: inum               ! temporary logical unit for restart file
56      INTEGER,DIMENSION(jpnij) :: iproc              ! temporary logical
57      !!----------------------------------------------------------------------
58
59      IF(  ( MOD(kt,nn_stockfl) == 0 ) .OR. ( kt == nitend )  )THEN     
60
61         IF(lwp) THEN
62            WRITE(numout,*)
63            WRITE(numout,*) 'flo_rst : write in  restart_float file '
64            WRITE(numout,*) '~~~~~~~    '
65         ENDIF
66
67         ! file is opened and closed every time it is used.
68
69         clname = 'restart.float.'
70         ic = 1
71         DO jc = 1, 16
72            IF( cexper(jc:jc) /= ' ' ) ic = jc
73         END DO
74         clname = clname(1:14)//cexper(1:ic)
75         ic = 1
76         DO jc = 1, 48
77            IF( clname(jc:jc) /= ' ' ) ic = jc
78         END DO
79
80         inum=0
81         IF( lwp )THEN
82            CALL ctl_opn( inum, clname, 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
83            REWIND inum
84         ENDIF
85         !
86         DO jpn = 1, jpnij
87            iproc(jpn) = 0
88         END DO
89         !
90         IF(lwp) THEN
91            REWIND(inum)
92            WRITE (inum,*) tpifl,tpjfl,tpkfl,nisobfl,ngrpfl
93            CLOSE (inum)
94         ENDIF
95         !
96         ! Compute the number of trajectories for each processor
97         !
98         IF( lk_mpp ) THEN
99            DO jfl = 1, jpnfl
100               IF( (INT(tpifl(jfl)) >= (mig(nldi)-jpizoom+1)) .AND.   &
101                  &(INT(tpifl(jfl)) <= (mig(nlei)-jpizoom+1)) .AND.   &
102                  &(INT(tpjfl(jfl)) >= (mjg(nldj)-jpjzoom+1)) .AND.   &
103                  &(INT(tpjfl(jfl)) <= (mjg(nlej)-jpjzoom+1)) ) THEN
104                  iproc(narea) = iproc(narea)+1
105               ENDIF
106            END DO
107            CALL mpp_sum( iproc, jpnij )
108            !
109            IF(lwp) THEN
110               WRITE(numout,*) 'DATE',adatrj
111               DO jpn = 1, jpnij
112                  IF( iproc(jpn) /= 0 ) THEN
113                     WRITE(numout,*)'PROCESSOR',jpn-1,'compute',iproc(jpn), 'trajectories.'
114                  ENDIF
115               END DO
116            ENDIF
117         ENDIF
118
119      ENDIF
120
121   END SUBROUTINE flo_rst
122
123
124#  else
125   !!----------------------------------------------------------------------
126   !!   Default option                                         Empty module
127   !!----------------------------------------------------------------------
128CONTAINS
129   SUBROUTINE flo_rst                 ! Empty routine
130   END SUBROUTINE flo_rst
131#endif
132
133   !!=======================================================================
134END MODULE florst
Note: See TracBrowser for help on using the repository browser.