Statistiques
| Révision :

root / src / Expand.f90

Historique | Voir | Annoter | Télécharger (2,45 ko)

1
SUBROUTINE Expand(List,Idx,Dim)
2

    
3
  ! This subroutine expands a list entered in a compacted form
4
  ! ie 1 -10 => 1 2 3  4 5 6 7 8 9 10
5

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

    
37
  use VarTypes
38

    
39
  INTEGER(KINT), INTENT(IN) :: Dim
40
  INTEGER(KINT), INTENT(INOUT) :: List(Dim)
41
  INTEGER(KINT), INTENT(INOUT) :: Idx
42

    
43
  LOGICAL, ALLOCATABLE :: FTmp(:) ! Dim
44
  LOGICAL :: Debug
45
  INTEGER(KINT) :: i
46

    
47
  INTERFACE
48
     function valid(string) result (isValid)
49
       CHARACTER(*), intent(in) :: string
50
       logical                  :: isValid
51
     END function VALID
52

    
53
  END INTERFACE
54

    
55
  Debug=valid('Expand')
56

    
57
  Allocate(FTmp(Dim))
58
  FTmp=.FALSE.
59

    
60
  Idx=1
61

    
62
  DO WHILE (List(Idx).NE.0)
63
     If (List(Idx).LT.0) THEN
64
        DO I=List(Idx-1),abs(List(Idx))
65
           IF (.NOT.FTmp(I)) THEN
66
              FTmp(I)=.TRUE.
67
           END IF
68
        END DO
69
     ELSEIF (.NOT.FTmp(List(Idx))) THEN
70
        FTmp(List(Idx))=.TRUE.
71
     END IF
72
     Idx=Idx+1
73
  END DO
74

    
75
  if (debug) WRITE(*,*) "DBG Expand,  List",List
76

    
77
  ! We convert List into non compacted form
78
  Idx=1
79
  DO I=1,Dim
80
     If(Ftmp(I)) THEN
81
        List(Idx)=I
82
        Idx=Idx+1
83
     END IF
84
  END DO
85
  List(Idx)=0
86
  Idx=Idx-1
87

    
88
 DEALLOCATE(Ftmp)
89

    
90
END SUBROUTINE Expand