atomes 1.1.14
atomes: an atomic scale modeling tool box
Loading...
Searching...
No Matches
chains_ogl.F90
Go to the documentation of this file.
1! This file is part of the 'atomes' software.
2!
3! 'atomes' is free software: you can redistribute it and/or modify it under the terms
4! of the GNU Affero General Public License as published by the Free Software Foundation,
5! either version 3 of the License, or (at your option) any later version.
6!
7! 'atomes' is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY;
8! without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
9! See the GNU General Public License for more details.
10!
11! You should have received a copy of the GNU Affero General Public License along with 'atomes'.
12! If not, see <https://www.gnu.org/licenses/>
13!
14! Copyright (C) 2022-2024 by CNRS and University of Strasbourg
15!
20
21INTEGER FUNCTION chains_to_ogl (STEP, NRI, RSAVED)
22
23USE parameters
24
25IMPLICIT NONE
26
27INTEGER, INTENT(IN) :: step
28INTEGER, DIMENSION(TAILLC, NS), INTENT(IN) :: nri
29INTEGER, DIMENSION(TAILLC,NUMA,TAILLC), INTENT(IN) :: rsaved
30INTEGER, DIMENSION(NUMA) :: chain_list
31INTEGER, DIMENSION(:), ALLOCATABLE :: chain_id
32INTEGER :: raa, rab, rac, rad, rae
33
34rab=0
35do raa=2, taillc
36 if (nri(raa,step) > 0) then
37 rab=rab+1
38 call allocate_all_chains (step-1, raa, nri(raa,step))
39 endif
40enddo
41if (rab.eq.0) write (6, *) "Chains RAB=0"
42
43do raa=1, na
44 do rab=2, taillc
45 rac = 0
46 do rad=1, numa
47 chain_list(rad) = 0
48 enddo
49 do rad=1, nri(rab,step)
50 do rae=1, rab
51 if (rsaved(rab,rad,rae) .eq. raa) then
52 rac=rac+1
53 chain_list(rac) = rad
54 goto 001
55 endif
56 enddo
57 001 continue
58 enddo
59 if (allocated(chain_id)) deallocate(chain_id)
60 allocate(chain_id(rac), stat=err)
61 if (err .ne. 0) then
62 call show_error ("Impossible to allocate memory"//char(0), &
63 "Function: CHAINS_TO_OGL"//char(0), "Table: CHAIN_ID (1)"//char(0))
65 goto 002
66 endif
67 do rad=1, rac
68 chain_id(rad) = chain_list(rad)
69 enddo
70 if (rac > 0) call send_atom_chains_id_opengl (step-1, raa-1, rab, rac, chain_id)
71 enddo
72enddo
73
74do raa=2, taillc
75 if (allocated(chain_id)) deallocate(chain_id)
76 allocate(chain_id(raa), stat=err)
77 if (err .ne. 0) then
78 call show_error ("Impossible to allocate memory"//char(0), &
79 "Function: CHAINS_TO_OGL"//char(0), "Table: CHAIN_ID (2)"//char(0))
81 goto 002
82 endif
83 if (nri(raa,step) > 0) then
84 do rab=1, nri(raa,step)
85 do rac=1, raa
86 chain_id(rac) = rsaved(raa,rab,rac)
87 enddo
88 call send_chains_opengl (step-1, raa, rab-1, chain_id)
89 enddo
90 endif
91enddo
92
94
95if (allocated(chain_id)) deallocate(chain_id)
96
97002 continue
98
99END FUNCTION
100
101INTEGER FUNCTION chains_to_ogl_menu (NRI)
102
103USE parameters
104
105IMPLICIT NONE
106
107INTEGER, DIMENSION(TAILLC, NS), INTENT(IN) :: nri
108INTEGER, DIMENSION(:), ALLOCATABLE :: chain_id, chain_jd, chain_kd
109
110if (allocated(chain_id)) deallocate(chain_id)
111allocate(chain_id(taillc-1), stat=err)
112if (err .ne. 0) then
113 call show_error ("Impossible to allocate memory"//char(0), &
114 "Function: CHAINS_TO_OGL_MENU"//char(0), "Table: CHAIN_ID "//char(0))
116 goto 001
117endif
118
119k = 0
120do i=2, taillc
121 chain_id(i-1) = 0
122 do j=1, ns
123 chain_id(i-1) = chain_id(i-1) + nri(i,j)
124 enddo
125 if (chain_id(i-1) > 0) then
126 k = k + 1
127 endif
128enddo
129
130if (allocated(chain_jd)) deallocate(chain_jd)
131allocate(chain_jd(k), stat=err)
132if (err .ne. 0) then
133 call show_error ("Impossible to allocate memory"//char(0), &
134 "Function: CHAINS_TO_OGL_MENU"//char(0), "Table: CHAIN_JD "//char(0))
136 goto 001
137endif
138if (allocated(chain_kd)) deallocate(chain_kd)
139allocate(chain_kd(k), stat=err)
140if (err .ne. 0) then
141 call show_error ("Impossible to allocate memory"//char(0), &
142 "Function: CHAINS_TO_OGL_MENU"//char(0), "Table: CHAIN_KD "//char(0))
144 goto 001
145endif
146
147k = 0
148do i=2, taillc
149 if (chain_id(i-1) > 0) then
150 k = k + 1
151 chain_jd(k) = i
152 chain_kd(k) = chain_id(i-1)
153 endif
154enddo
155
156if (k > 0) then
157 call send_coord_opengl (9, 1, 0, 0, k, k)
158 call init_menurings (9, 5, k, chain_jd, chain_kd)
159endif
160
161if (allocated(chain_id)) deallocate(chain_id)
162if (allocated(chain_jd)) deallocate(chain_jd)
163if (allocated(chain_kd)) deallocate(chain_kd)
164
166
167001 continue
168
169END FUNCTION
integer function chains_to_ogl_menu(nri)
integer function chains_to_ogl(step, nri, rsaved)
void show_error(char *error, int val, GtkWidget *win)
show error message
Definition interface.c:293
integer taillc
integer numa
integer err