Ignore:
Timestamp:
Aug 25, 2020 12:11:17 PM (4 years ago)
Author:
raasch
Message:

files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/posix_calls_from_fortran.f90

    r4360 r4649  
    11!> @posix_calls_from_fortran.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    5 ! PALM is free software: you can redistribute it and/or modify it under the
    6 ! terms of the GNU General Public License as published by the Free Software
    7 ! Foundation, either version 3 of the License, or (at your option) any later
    8 ! version.
     5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
     6! Public License as published by the Free Software Foundation, either version 3 of the License, or
     7! (at your option) any later version.
    98!
    10 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    11 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    12 ! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
     9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
     10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
     11! Public License for more details.
    1312!
    14 ! You should have received a copy of the GNU General Public License along with
    15 ! PALM. If not, see <http://www.gnu.org/licenses/>.
     13! You should have received a copy of the GNU General Public License along with PALM. If not, see
     14! <http://www.gnu.org/licenses/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
     18!
    1919!
    2020! Current revisions:
    2121! -----------------
    22 ! 
    23 ! 
     22!
     23!
    2424! Former revisions:
    2525! -----------------
    2626! $Id: posix_calls_from_fortran.f90 2696 2017-12-14 17:12:51Z kanani $
     27! File re-formatted to follow the PALM coding standard
     28!
     29!
     30! 2696 2017-12-14 17:12:51Z kanani
    2731! Corrected "Former revisions" section
    28 ! 
     32!
    2933! 2696 2017-12-14 17:12:51Z kanani
    30 ! add variable description
    31 ! 
     34! Add variable description
     35!
    3236! 1986 2016-08-10 14:07:17Z gronemeier
    3337! Initial revision
    34 !
     38!
     39!--------------------------------------------------------------------------------------------------!
    3540! Description:
    3641! ------------
    3742!> Collection of POSIX-command calls for Fortran
    38 !------------------------------------------------------------------------------!
     43!--------------------------------------------------------------------------------------------------!
    3944 MODULE posix_calls_from_fortran
    4045
    41     USE, INTRINSIC ::  iso_c_binding, ONLY: c_int
     46    USE, INTRINSIC ::  iso_c_binding,                                                              &
     47        ONLY: c_int
    4248
    4349    IMPLICIT none
     
    4955!
    5056!--    Sleep function from C library
    51        FUNCTION fsleep( seconds )  BIND( C, NAME='sleep' )
     57       FUNCTION fsleep( seconds )  BIND( C, NAME = 'sleep' )
    5258          IMPORT
    53           INTEGER(c_int) ::  fsleep
    54           INTEGER(c_int), INTENT(IN), VALUE ::  seconds
     59          INTEGER(c_int)                    ::  fsleep   !<
     60          INTEGER(c_int), INTENT(IN), VALUE ::  seconds  !<
    5561       END FUNCTION fsleep
    5662
     
    6672 CONTAINS
    6773
    68 !------------------------------------------------------------------------------!
     74!--------------------------------------------------------------------------------------------------!
    6975! Description:
    7076! ------------
    7177!> Wait a specified amount of seconds
    72 !------------------------------------------------------------------------------!
     78!--------------------------------------------------------------------------------------------------!
    7379 SUBROUTINE fortran_sleep( seconds )
    7480
Note: See TracChangeset for help on using the changeset viewer.