Statistiques
| Révision :

root / src / Expand.f90 @ 12

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

1 1 pfleura2
SUBROUTINE Expand(List,Idx,Dim)
2 1 pfleura2
3 1 pfleura2
  ! This subroutine expands a list entered in a compacted form
4 1 pfleura2
  ! ie 1 -10 => 1 2 3  4 5 6 7 8 9 10
5 1 pfleura2
6 12 pfleura2
!----------------------------------------------------------------------
7 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
8 12 pfleura2
!  Centre National de la Recherche Scientifique,
9 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
10 12 pfleura2
!
11 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
12 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
13 12 pfleura2
!
14 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
15 12 pfleura2
!  Contact: optnpath@gmail.com
16 12 pfleura2
!
17 12 pfleura2
! This file is part of "Opt'n Path".
18 12 pfleura2
!
19 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
20 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
21 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
22 12 pfleura2
!  or (at your option) any later version.
23 12 pfleura2
!
24 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
25 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
26 12 pfleura2
!
27 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
28 12 pfleura2
!  GNU Affero General Public License for more details.
29 12 pfleura2
!
30 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
31 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
32 12 pfleura2
!
33 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
34 12 pfleura2
! for commercial licensing opportunities.
35 12 pfleura2
!----------------------------------------------------------------------
36 12 pfleura2
37 1 pfleura2
  use VarTypes
38 1 pfleura2
39 1 pfleura2
  INTEGER(KINT), INTENT(IN) :: Dim
40 1 pfleura2
  INTEGER(KINT), INTENT(INOUT) :: List(Dim)
41 1 pfleura2
  INTEGER(KINT), INTENT(INOUT) :: Idx
42 1 pfleura2
43 1 pfleura2
  LOGICAL, ALLOCATABLE :: FTmp(:) ! Dim
44 1 pfleura2
  LOGICAL :: Debug
45 1 pfleura2
  INTEGER(KINT) :: i
46 1 pfleura2
47 1 pfleura2
  INTERFACE
48 1 pfleura2
     function valid(string) result (isValid)
49 1 pfleura2
       CHARACTER(*), intent(in) :: string
50 1 pfleura2
       logical                  :: isValid
51 1 pfleura2
     END function VALID
52 1 pfleura2
53 1 pfleura2
  END INTERFACE
54 1 pfleura2
55 1 pfleura2
  Debug=valid('Expand')
56 1 pfleura2
57 1 pfleura2
  Allocate(FTmp(Dim))
58 1 pfleura2
  FTmp=.FALSE.
59 1 pfleura2
60 1 pfleura2
  Idx=1
61 1 pfleura2
62 1 pfleura2
  DO WHILE (List(Idx).NE.0)
63 1 pfleura2
     If (List(Idx).LT.0) THEN
64 1 pfleura2
        DO I=List(Idx-1),abs(List(Idx))
65 1 pfleura2
           IF (.NOT.FTmp(I)) THEN
66 1 pfleura2
              FTmp(I)=.TRUE.
67 1 pfleura2
           END IF
68 1 pfleura2
        END DO
69 1 pfleura2
     ELSEIF (.NOT.FTmp(List(Idx))) THEN
70 1 pfleura2
        FTmp(List(Idx))=.TRUE.
71 1 pfleura2
     END IF
72 1 pfleura2
     Idx=Idx+1
73 1 pfleura2
  END DO
74 1 pfleura2
75 1 pfleura2
  if (debug) WRITE(*,*) "DBG Expand,  List",List
76 1 pfleura2
77 1 pfleura2
  ! We convert List into non compacted form
78 1 pfleura2
  Idx=1
79 1 pfleura2
  DO I=1,Dim
80 1 pfleura2
     If(Ftmp(I)) THEN
81 1 pfleura2
        List(Idx)=I
82 1 pfleura2
        Idx=Idx+1
83 1 pfleura2
     END IF
84 1 pfleura2
  END DO
85 1 pfleura2
  List(Idx)=0
86 1 pfleura2
  Idx=Idx-1
87 1 pfleura2
88 1 pfleura2
 DEALLOCATE(Ftmp)
89 1 pfleura2
90 1 pfleura2
END SUBROUTINE Expand