Ignore:
Timestamp:
Jul 24, 2024, 4:23:34 PM (4 months ago)
Author:
abarral
Message:

rename modules properly lmdz_*
move some unused files to obsolete/
(lint) uppercase fortran keywords

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/misc/lmdz_new_unit.f90

    r5116 r5117  
    1 module new_unit_m
     1module lmdz_new_unit
    22
    33  IMPLICIT NONE
     
    55contains
    66
     7  ! Returns an existing unit id that isn't already opened
    78  SUBROUTINE new_unit(unit)
     9    INTEGER, INTENT(OUT):: unit
    810
    9     integer, intent(out):: unit
    10 
    11     ! Variables local to the procedure:
    12     logical opened, exist
    13 
    14     !------------------------------------------------------
     11    LOGICAL opened, exist
    1512
    1613    unit = 0
    17     do
    18        inquire(unit=unit, opened=opened, exist=exist)
    19        if (exist .and. .not. opened) exit
     14    DO
     15       INQUIRE(unit=unit, opened=opened, exist=exist)
     16       IF (exist .AND. .NOT. opened) RETURN
    2017       unit = unit + 1
    2118    END DO
     
    2320  END SUBROUTINE  new_unit
    2421
    25 end module new_unit_m
     22end module lmdz_new_unit
Note: See TracChangeset for help on using the changeset viewer.