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 NEMO/branches/2020/dev_r12563_ASINTER-06_ABL_improvement/src/OCE/FLO – NEMO

source: NEMO/branches/2020/dev_r12563_ASINTER-06_ABL_improvement/src/OCE/FLO/florst.F90 @ 13159

Last change on this file since 13159 was 11536, checked in by smasson, 5 years ago

trunk: merge dev_r10984_HPC-13 into the trunk

  • Property svn:keywords set to Id
File size: 4.5 KB
Line 
1MODULE florst
2   !!======================================================================
3   !!                       ***  MODULE  florst  ***
4   !! Ocean floats : write floats restart files
5   !!======================================================================
6   !!  History :  OPA  !  1999-09  (Y. Drillet)    : Original code
7   !!              -   !  2000-06  (J.-M. Molines) : Profiling floats for CLS
8   !!   NEMO      1.0  !  2002-10  (A. Bozec)  F90 : Free form and module
9   !!             3.2  !  2010-08  (slaw, cbricaud): netcdf outputs and others
10   !!----------------------------------------------------------------------
11   USE flo_oce         ! ocean drifting floats
12   USE dom_oce         ! ocean space and time domain
13   USE lib_mpp         ! distribued memory computing library
14   USE in_out_manager  ! I/O manager
15
16   IMPLICIT NONE
17   PRIVATE
18
19   PUBLIC flo_rst         ! routine called by floats.F90
20   PUBLIC flo_rst_alloc   ! routine called by floats.F90
21
22   INTEGER, ALLOCATABLE, DIMENSION(:) :: iperproc   ! 1D workspace
23
24   !!----------------------------------------------------------------------
25   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
26   !! $Id$
27   !! Software governed by the CeCILL license (see ./LICENSE)
28   !!----------------------------------------------------------------------
29CONTAINS
30
31   INTEGER FUNCTION flo_rst_alloc()
32      !!-------------------------------------------------------------------
33      !!                ***  FUNCTION flo_rst_alloc  ***
34      !!-------------------------------------------------------------------
35      ALLOCATE( iperproc(jpnij), STAT=flo_rst_alloc )
36     
37      CALL mpp_sum ( 'florst', flo_rst_alloc )
38      IF( flo_rst_alloc /= 0 )   CALL ctl_stop( 'STOP', 'flo_rst_alloc: failed to allocate arrays.' )
39   END FUNCTION flo_rst_alloc
40
41
42   SUBROUTINE flo_rst( kt )
43      !!---------------------------------------------------------------------
44      !!                  ***  ROUTINE flo_rst ***
45      !!             
46      !! ** Purpose : 
47      !!             
48      !!     
49      !! ** Method  :   The frequency of  ??? is nwritefl
50      !!     
51      !!----------------------------------------------------------------------
52      INTEGER  :: kt                            ! time step
53      !
54      CHARACTER (len=80)       :: clname             ! restart filename
55      INTEGER                  :: ic , jc , jpn ,jfl ! temporary integer
56      INTEGER                  :: inum               ! temporary logical unit for restart file
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            iperproc(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)) .AND.   &
101                  &(INT(tpifl(jfl)) <= mig(nlei)) .AND.   &
102                  &(INT(tpjfl(jfl)) >= mjg(nldj)) .AND.   &
103                  &(INT(tpjfl(jfl)) <= mjg(nlej)) ) THEN
104                  iperproc(narea) = iperproc(narea)+1
105               ENDIF
106            END DO
107            CALL mpp_sum( 'florst', iperproc, jpnij )
108            !
109            IF(lwp) THEN
110               WRITE(numout,*) 'DATE',adatrj
111               DO jpn = 1, jpnij
112                  IF( iperproc(jpn) /= 0 ) THEN
113                     WRITE(numout,*)'PROCESSOR',jpn-1,'compute',iperproc(jpn), 'trajectories.'
114                  ENDIF
115               END DO
116            ENDIF
117         ENDIF
118         !
119      ENDIF
120      !
121   END SUBROUTINE flo_rst
122
123   !!=======================================================================
124END MODULE florst
Note: See TracBrowser for help on using the repository browser.