Back to OASIS3 home
Modules used for the scrip
library (in oasis3/lib/scrip/src) : 
iounits : keeps track of which units are in
use and reserves
units for stdin, stdout, and stderr
used in grids.f,
      use
kinds_mod   ! defines
data types
      USE mod_unit                                
------------------> defined in oasis3/src
      USE mod_printing                          
------------------> defined in oasis3/src
      implicit none
!-----------------------------------------------------------------------
      logical (kind=log_kind), dimension(99),
save ::
     &    unit_free  
! flags to determine whether unit is free for use
      integer (kind=int_kind), parameter ::
     &    stdin  = 5, !
reserves unit for standard input
     &    stdout = 6, ! reserves
unit for standard output
     &    stderr = 6  !
reserves unit for standard error
!***********************************************************************
      contains
!***********************************************************************
      subroutine get_unit(iunit)
!-----------------------------------------------------------------------
!
!     This routine returns the next available I/O
unit number.
!
!-----------------------------------------------------------------------
!-----------------------------------------------------------------------
!
!     output variables
!
!-----------------------------------------------------------------------
      integer (kind=int_kind), intent(out) ::
     &    
iunit   ! next free I/O unit
!-----------------------------------------------------------------------
!
!     local variables
!
!-----------------------------------------------------------------------
      integer (kind=int_kind) :: n
      logical (kind=log_kind), save ::
first_call = .true.
!-----------------------------------------------------------------------
!
!     if this is the first call, reserve stdout,
stdin and stderr
!
!-----------------------------------------------------------------------
!
      IF (nlogprt .GE. 2) THEN
         WRITE (UNIT =
nulou,FMT = *)' '
         WRITE (UNIT =
nulou,FMT = *)'Entering routine get_unit'
         WRITE (UNIT =
nulou,FMT = *)' '
         CALL FLUSH(nulou)
      ENDIF
!
      if (first_call) then
        unit_free = .true.
        unit_free(stdin)  =
.false.
        unit_free(stdout) = .false.
        unit_free(stderr) = .false.
        first_call = .false.
      endif
!-----------------------------------------------------------------------
!
!     search for next available unit
!
!-----------------------------------------------------------------------
      srch_unit: do n=1,99
        if (unit_free(n)) then
          iunit = n
          unit_free(n) =
.false.
          exit srch_unit
        endif
      end do srch_unit
!
      IF (nlogprt .GE. 2) THEN
         WRITE (UNIT =
nulou,FMT = *)' '
         WRITE (UNIT =
nulou,FMT = *)'Leaving routine get_unit'
         WRITE (UNIT =
nulou,FMT = *)' '
         CALL FLUSH(nulou)
      ENDIF
!
!-----------------------------------------------------------------------
      end subroutine get_unit
!***********************************************************************
      subroutine release_unit(iunit)
!-----------------------------------------------------------------------
!
!     This routine releases the specified unit and
closes the file.
!
!-----------------------------------------------------------------------
!-----------------------------------------------------------------------
!
!     input variables
!
!-----------------------------------------------------------------------
      integer (kind=int_kind), intent(in) ::
     &    
iunit   ! I/O unit to release
!-----------------------------------------------------------------------
!
!     closes I/O unit and declares it free
!
!-----------------------------------------------------------------------
!
      IF (nlogprt .GE. 2) THEN
         WRITE (UNIT =
nulou,FMT = *)' '
         WRITE (UNIT =
nulou,FMT = *)'Entering routine release_unit'
         WRITE (UNIT =
nulou,FMT = *)' '
         CALL FLUSH(nulou)
      ENDIF
!
      unit_free(iunit) = .true.
      close(iunit)
!-----------------------------------------------------------------------
!
      IF (nlogprt .GE. 2) THEN
         WRITE (UNIT =
nulou,FMT = *)' '
         WRITE (UNIT =
nulou,FMT = *)'Leaving routine release_unit'
         WRITE (UNIT =
nulou,FMT = *)' '
         CALL FLUSH(nulou)
      ENDIF
!
      end subroutine release_unit