Statistiques
| Révision :

root / src / PrintAnaList.f90 @ 12

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

1 7 pfleura2
 SUBROUTINE PrintAnaList(FileUnit)
2 7 pfleura2
! This routines prints the list of geometrical variables to monitor
3 7 pfleura2
4 12 pfleura2
!----------------------------------------------------------------------
5 12 pfleura2
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon,
6 12 pfleura2
!  Centre National de la Recherche Scientifique,
7 12 pfleura2
!  Université Claude Bernard Lyon 1. All rights reserved.
8 12 pfleura2
!
9 12 pfleura2
!  This work is registered with the Agency for the Protection of Programs
10 12 pfleura2
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
11 12 pfleura2
!
12 12 pfleura2
!  Authors: P. Fleurat-Lessard, P. Dayal
13 12 pfleura2
!  Contact: optnpath@gmail.com
14 12 pfleura2
!
15 12 pfleura2
! This file is part of "Opt'n Path".
16 12 pfleura2
!
17 12 pfleura2
!  "Opt'n Path" is free software: you can redistribute it and/or modify
18 12 pfleura2
!  it under the terms of the GNU Affero General Public License as
19 12 pfleura2
!  published by the Free Software Foundation, either version 3 of the License,
20 12 pfleura2
!  or (at your option) any later version.
21 12 pfleura2
!
22 12 pfleura2
!  "Opt'n Path" is distributed in the hope that it will be useful,
23 12 pfleura2
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
24 12 pfleura2
!
25 12 pfleura2
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
26 12 pfleura2
!  GNU Affero General Public License for more details.
27 12 pfleura2
!
28 12 pfleura2
!  You should have received a copy of the GNU Affero General Public License
29 12 pfleura2
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
30 12 pfleura2
!
31 12 pfleura2
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
32 12 pfleura2
! for commercial licensing opportunities.
33 12 pfleura2
!----------------------------------------------------------------------
34 7 pfleura2
35 7 pfleura2
  use VarTypes
36 7 pfleura2
  use Path_module
37 7 pfleura2
  use Io_module
38 7 pfleura2
39 7 pfleura2
  IMPLICIT NONE
40 7 pfleura2
41 7 pfleura2
  INTERFACE
42 7 pfleura2
     function valid(string) result (isValid)
43 7 pfleura2
       CHARACTER(*), intent(in) :: string
44 7 pfleura2
       logical                  :: isValid
45 7 pfleura2
     END function VALID
46 7 pfleura2
47 7 pfleura2
     SUBROUTINE die(routine, msg, file, line, unit)
48 7 pfleura2
49 7 pfleura2
       Use VarTypes
50 7 pfleura2
       Use io_module
51 7 pfleura2
52 7 pfleura2
       implicit none
53 7 pfleura2
54 7 pfleura2
       character(len=*), intent(in)           :: routine, msg
55 7 pfleura2
       character(len=*), intent(in), optional :: file
56 7 pfleura2
       integer(KINT), intent(in), optional      :: line, unit
57 7 pfleura2
58 7 pfleura2
     END SUBROUTINE die
59 7 pfleura2
60 7 pfleura2
  END INTERFACE
61 7 pfleura2
! Input
62 7 pfleura2
! Unit to print the description
63 7 pfleura2
  INTEGER(KINT) :: FileUnit
64 7 pfleura2
65 7 pfleura2
! Local
66 7 pfleura2
  LOGICAL :: Debug
67 7 pfleura2
  INTEGER(KINT) :: I,J,At1,At2,At3,At4
68 7 pfleura2
69 7 pfleura2
  Debug=Valid('PrintAnaList')
70 7 pfleura2
71 7 pfleura2
  If (Debug) Call Header("Entering PrintAnaList")
72 7 pfleura2
73 8 pfleura2
  WRITE(FileUnit,'(A)') "# Centers of mass used "
74 8 pfleura2
75 7 pfleura2
  CurBary => Bary
76 7 pfleura2
77 7 pfleura2
  DO I=1,NbCom
78 7 pfleura2
     WRITe(*,*) "Dbg PrintAnalist: I,NbCom",I,NbCom
79 7 pfleura2
     At1=CurBary%ListAtoms(0)
80 7 pfleura2
     if (debug)      WRITE(*,'("# c ",I4,20(A3,I3))') At1, &
81 7 pfleura2
                (AtName(CurBary%ListAtoms(j)),CurBary%ListAtoms(j),j=1,At1)
82 7 pfleura2
83 7 pfleura2
     WRITE(FileUnit,'("# c ",I4,20(A3,I3))') At1, &
84 7 pfleura2
                (AtName(CurBary%ListAtoms(j)),CurBary%ListAtoms(j),j=1,At1)
85 7 pfleura2
     if (associated(CurBary%Next)) CurBary=> CurBary%Next
86 7 pfleura2
  END DO
87 7 pfleura2
88 8 pfleura2
  WRITE(FileUnit,'(A)') "# Variables monitored "
89 8 pfleura2
90 7 pfleura2
  CurVar => GeomList
91 7 pfleura2
  DO I=1,NbVar
92 7 pfleura2
     SELECT CASE (CurVar%Type)
93 7 pfleura2
        CASE ('BOND')
94 7 pfleura2
! this is a bond
95 7 pfleura2
           At1=CurVar%At1
96 7 pfleura2
           AT2=CurVar%At2
97 7 pfleura2
           if (debug) WRITE(*,'("# b ",2(1X,A,I3))') TRIM(AtName(At1)),At1,AtName(At2),At2
98 7 pfleura2
           WRITE(FileUnit,'("# b ",2(1X,A,I3))') TRIM(AtName(At1)),At1,AtName(At2),At2
99 7 pfleura2
        CASE ('ANGLE')
100 7 pfleura2
! this is an angle
101 7 pfleura2
           At1=CurVar%At1
102 7 pfleura2
           AT2=CurVar%At2
103 7 pfleura2
           At3=CurVar%At3
104 7 pfleura2
           if (debug) WRITE(*,'("# a ",4(A3,I3))') AtName(At1),At1,AtName(At2),At2,AtName(At3),At3
105 7 pfleura2
           WRITE(FileUnit,'("# a ",4(A3,I3))') AtName(At1),At1,AtName(At2),At2,AtName(At3),At3
106 7 pfleura2
        CASE ('DIHEDRAL')
107 7 pfleura2
! this is a dihedral
108 7 pfleura2
           At1=CurVar%At1
109 7 pfleura2
           AT2=CurVar%At2
110 7 pfleura2
           At3=CurVar%At3
111 7 pfleura2
           At4=CurVar%At4
112 7 pfleura2
           if (debug) WRITE(*,'("# d ",4(A3,I3))') AtName(At1),At1,AtName(At2),At2,AtName(At3),At3,AtName(At4),At4
113 7 pfleura2
           WRITE(FileUnit,'("# d ",4(A3,I3))') AtName(At1),At1,AtName(At2),At2,AtName(At3),At3,AtName(At4),At4
114 7 pfleura2
     END SELECT
115 7 pfleura2
     If (Associated(CurVar%Next)) CurVar => CurVar%next
116 7 pfleura2
  END DO
117 7 pfleura2
118 7 pfleura2
  If (Debug) Call Header("Exiting PrintAnaList")
119 7 pfleura2
120 7 pfleura2
END SUBROUTINE PrintAnaList