source: CPL/oasis3-mct/branches/OASIS3-MCT_2.0_branch/lib/scrip/src/iounits.f @ 4775

Last change on this file since 4775 was 4775, checked in by aclsce, 5 years ago
  • Imported oasis3-mct from Cerfacs svn server (not suppotred anymore).

The version has been extracted from https://oasis3mct.cerfacs.fr/svn/branches/OASIS3-MCT_2.0_branch/oasis3-mct@1818

File size: 6.0 KB
Line 
1!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2!
3!     This module is a dynamic I/O unit manager.  It keeps track of
4!     which units are in use and reserves units for stdin, stdout, and
5!     stderr.
6!
7!-----------------------------------------------------------------------
8!
9!     CVS:$Id: iounits.f 2826 2010-12-10 11:14:21Z valcke $
10!
11!     Copyright (c) 1997, 1998 the Regents of the University of
12!       California.
13!
14!     This software and ancillary information (herein called software)
15!     called SCRIP is made available under the terms described here. 
16!     The software has been approved for release with associated
17!     LA-CC Number 98-45.
18!
19!     Unless otherwise indicated, this software has been authored
20!     by an employee or employees of the University of California,
21!     operator of the Los Alamos National Laboratory under Contract
22!     No. W-7405-ENG-36 with the U.S. Department of Energy.  The U.S.
23!     Government has rights to use, reproduce, and distribute this
24!     software.  The public may copy and use this software without
25!     charge, provided that this Notice and any statement of authorship
26!     are reproduced on all copies.  Neither the Government nor the
27!     University makes any warranty, express or implied, or assumes
28!     any liability or responsibility for the use of this software.
29!
30!     If software is modified to produce derivative works, such modified
31!     software should be clearly marked, so as not to confuse it with
32!     the version available from Los Alamos National Laboratory.
33!
34!***********************************************************************
35
36      module iounits
37
38!-----------------------------------------------------------------------
39
40      use kinds_mod   ! defines data types
41      USE mod_oasis_flush
42
43      implicit none
44
45!-----------------------------------------------------------------------
46
47      logical (kind=log_kind), dimension(99), save ::
48     &    unit_free   ! flags to determine whether unit is free for use
49
50      integer (kind=int_kind), parameter ::
51     &    stdin  = 5, ! reserves unit for standard input
52     &    stdout = 6, ! reserves unit for standard output
53     &    stderr = 6  ! reserves unit for standard error
54
55!***********************************************************************
56
57      contains
58
59!***********************************************************************
60
61      subroutine get_unit(iunit)
62
63!-----------------------------------------------------------------------
64!
65!     This routine returns the next available I/O unit number.
66!
67!-----------------------------------------------------------------------
68
69!-----------------------------------------------------------------------
70!
71!     output variables
72!
73!-----------------------------------------------------------------------
74
75      integer (kind=int_kind), intent(out) ::
76     &     iunit   ! next free I/O unit
77
78!-----------------------------------------------------------------------
79!
80!     local variables
81!
82!-----------------------------------------------------------------------
83
84      integer (kind=int_kind) :: n
85
86      logical (kind=log_kind), save :: first_call = .true.
87
88!-----------------------------------------------------------------------
89!
90!     if this is the first call, reserve stdout, stdin and stderr
91!
92!-----------------------------------------------------------------------
93!
94      IF (nlogprt .GE. 2) THEN
95         WRITE (UNIT = nulou,FMT = *)' '
96         WRITE (UNIT = nulou,FMT = *)'Entering routine get_unit'
97         WRITE (UNIT = nulou,FMT = *)' '
98         CALL OASIS_FLUSH_SCRIP(nulou)
99      ENDIF
100!
101      if (first_call) then
102        unit_free = .true.
103        unit_free(stdin)  = .false.
104        unit_free(stdout) = .false.
105        unit_free(stderr) = .false.
106        first_call = .false.
107      endif
108
109!-----------------------------------------------------------------------
110!
111!     search for next available unit
112!
113!-----------------------------------------------------------------------
114
115      srch_unit: do n=1,99
116        if (unit_free(n)) then
117          iunit = n
118          unit_free(n) = .false.
119          exit srch_unit
120        endif
121      end do srch_unit
122!
123      IF (nlogprt .GE. 2) THEN
124         WRITE (UNIT = nulou,FMT = *)' '
125         WRITE (UNIT = nulou,FMT = *)'Leaving routine get_unit'
126         WRITE (UNIT = nulou,FMT = *)' '
127         CALL OASIS_FLUSH_SCRIP(nulou)
128      ENDIF
129!
130!-----------------------------------------------------------------------
131
132      end subroutine get_unit
133
134!***********************************************************************
135
136      subroutine release_unit(iunit)
137
138!-----------------------------------------------------------------------
139!
140!     This routine releases the specified unit and closes the file.
141!
142!-----------------------------------------------------------------------
143!-----------------------------------------------------------------------
144!
145!     input variables
146!
147!-----------------------------------------------------------------------
148
149      integer (kind=int_kind), intent(in) ::
150     &     iunit   ! I/O unit to release
151
152!-----------------------------------------------------------------------
153!
154!     closes I/O unit and declares it free
155!
156!-----------------------------------------------------------------------
157!
158      IF (nlogprt .GE. 2) THEN
159         WRITE (UNIT = nulou,FMT = *)' '
160         WRITE (UNIT = nulou,FMT = *)'Entering routine release_unit'
161         WRITE (UNIT = nulou,FMT = *)' '
162         CALL OASIS_FLUSH_SCRIP(nulou)
163      ENDIF
164!
165      unit_free(iunit) = .true.
166      close(iunit)
167
168!-----------------------------------------------------------------------
169!
170      IF (nlogprt .GE. 2) THEN
171         WRITE (UNIT = nulou,FMT = *)' '
172         WRITE (UNIT = nulou,FMT = *)'Leaving routine release_unit'
173         WRITE (UNIT = nulou,FMT = *)' '
174         CALL OASIS_FLUSH_SCRIP(nulou)
175      ENDIF
176!
177      end subroutine release_unit
178
179!***********************************************************************
180
181      end module iounits
182
183!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Note: See TracBrowser for help on using the repository browser.