Statistiques
| Révision :

root / src / Header.f90

Historique | Voir | Annoter | Télécharger (3,22 ko)

1
      subroutine Header(String)
2
! This short subroutine print a header in a nice way
3

    
4
!----------------------------------------------------------------------
5
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
6
!  Centre National de la Recherche Scientifique,
7
!  Université Claude Bernard Lyon 1. All rights reserved.
8
!
9
!  This work is registered with the Agency for the Protection of Programs 
10
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
11
!
12
!  Authors: P. Fleurat-Lessard, P. Dayal
13
!  Contact: optnpath@gmail.com
14
!
15
! This file is part of "Opt'n Path".
16
!
17
!  "Opt'n Path" is free software: you can redistribute it and/or modify
18
!  it under the terms of the GNU Affero General Public License as
19
!  published by the Free Software Foundation, either version 3 of the License,
20
!  or (at your option) any later version.
21
!
22
!  "Opt'n Path" is distributed in the hope that it will be useful,
23
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
24
!
25
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
26
!  GNU Affero General Public License for more details.
27
!
28
!  You should have received a copy of the GNU Affero General Public License
29
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
30
!
31
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
32
! for commercial licensing opportunities.
33
!----------------------------------------------------------------------
34

    
35
         IMPLICIT NONE
36

    
37

    
38
         CHARACTER(*) :: String
39

    
40
         INTERFACE
41
            function valid(string) result (isValid)
42
              CHARACTER(*), intent(in) :: string
43
              logical                  :: isValid
44
            END function VALID
45
         END INTERFACE
46

    
47

    
48
         CHARACTER(70) :: Head1,Sep
49
         CHARACTER(70) :: String2
50
         INTEGER :: LenS,Len1,Pos1
51
         INTEGER :: Idx,PosE
52
         LOGICAL :: Debug
53

    
54

    
55
         Debug=Valid("Header")
56

    
57
         Head1="====================================================================="
58
           Sep="                                                                     "
59

    
60
           If (debug) THEN
61
              WRITe(*,'(A)') Head1
62
              WRITE(*,'(A)') "=     Entering Header.... "
63
              WRITe(*,'(A)') Head1
64
           END IF
65

    
66
         WRITe(*,'(A)') Head1
67

    
68
         LenS=len_Trim(String)
69
         DO WHILE (LenS>65)
70
            Idx=Index(String(1:65)," ",BACK=.TRUE.)
71
            If (Idx>0) THEN
72
               PosE=Idx-1
73
            ELSE 
74
               PosE=65
75
            END IF
76
            
77
            String2=AdjustL(Trim(String(1:PosE)))
78
            LenS=Len_Trim(String2)
79
 !        WRITE(*,*) "DBG Head:",LenS, String
80
            Pos1=33-Int(LenS/2)
81
            Len1=67-LenS-Pos1
82

    
83
            WRITE(*,'(A)') "=" // Sep(1:Pos1) // TRIM(String2) // Sep(1:Len1) // "="
84
            String2=String(PosE+1:)
85
            String=AdjustL(String2)
86
            LenS=Len_Trim(String)
87
      END DO
88

    
89
         Pos1=34-Int(LenS/2)
90
         Len1=67-LenS-Pos1
91
         
92
         WRITE(*,'(A)') "=" // Sep(1:Pos1) // TRIM(String) // Sep(1:Len1) // "="
93

    
94
         WRITe(*,'(A)') Head1
95

    
96
           If (debug) THEN
97
              WRITe(*,'(A)') Head1
98
              WRITE(*,'(A)') "=     Exiting Header.... "
99
              WRITe(*,'(A)') Head1
100
           END IF
101

    
102

    
103
       END subroutine Header