TABLE OF CONTENTS


ABINIT/m_MapHyb [ Modules ]

[ Top ] [ Modules ]

NAME

  m_MapHyb

FUNCTION

  map template integer/double

COPYRIGHT

  Copyright (C) 2013-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

NOTES

SOURCE

22 #include "defs.h"
23 MODULE m_MapHyb
24 USE m_Global
25 IMPLICIT NONE

ABINIT/m_MapHyb/MapHyb_assign [ Functions ]

[ Top ] [ Functions ]

NAME

  MapHyb_assign

FUNCTION

  assign this=map

COPYRIGHT

  Copyright (C) 2013-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

INPUTS

  this=this
  this=Map

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

252 SUBROUTINE MapHyb_assign(this, map)
253 
254 !Arguments ------------------------------------
255   TYPE(MapHyb), INTENT(INOUT) :: this
256   TYPE(MapHyb), INTENT(IN   ) :: map
257 !Local variables ------------------------------
258   INTEGER                     :: tail
259 
260   tail = map%tail
261   CALL MapHyb_setSize(this, tail)
262   this%listINT(1:tail)  = map%listINT(1:tail)
263   this%listDBLE(1:tail) = map%listDBLE(1:tail)
264 
265 END SUBROUTINE MapHyb_assign

ABINIT/m_MapHyb/MapHyb_clear [ Functions ]

[ Top ] [ Functions ]

NAME

  MapHyb_clear

FUNCTION

  Clear the this

COPYRIGHT

  Copyright (C) 2013-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

INPUTS

  this=Map

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

441 SUBROUTINE MapHyb_clear(this)
442 
443 !Arguments ------------------------------------
444   TYPE(MapHyb), INTENT(INOUT) :: this
445   this%tail = 0 
446 END SUBROUTINE MapHyb_clear

ABINIT/m_MapHyb/MapHyb_destroy [ Functions ]

[ Top ] [ Functions ]

NAME

  MapHyb_destroy

FUNCTION

  destroy and deallocate the this

COPYRIGHT

  Copyright (C) 2013-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

INPUTS

  this=Map

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

473 SUBROUTINE MapHyb_destroy(this)
474 
475 !Arguments ------------------------------------
476   TYPE(MapHyb), INTENT(INOUT) :: this
477 
478   FREEIF(this%listINT)
479   FREEIF(this%listDBLE)
480 
481   this%tail     = 0
482   this%size     = 0
483 END SUBROUTINE MapHyb_destroy

ABINIT/m_MapHyb/MapHyb_enlarge [ Functions ]

[ Top ] [ Functions ]

NAME

  MapHyb_enlarge

FUNCTION

  enlarge memory space

COPYRIGHT

  Copyright (C) 2013-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

INPUTS

  this=Map
  size=new memory size

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

188 SUBROUTINE MapHyb_enlarge(this, size)
189 
190 !Arguments ------------------------------------
191   TYPE(MapHyb)     , INTENT(INOUT)       :: this
192   INTEGER, OPTIONAL, INTENT(IN   )       :: size
193 !Local variables ------------------------------
194   INTEGER                                :: width
195   INTEGER                                :: tail
196   INTEGER                                :: size_val
197   INTEGER         , ALLOCATABLE, DIMENSION(:) :: listINT_temp 
198   DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:) :: listDBLE_temp 
199 
200   IF ( ALLOCATED(this%listINT) ) THEN
201     FREEIF(listINT_temp)
202     width = this%size
203     tail  = this%tail
204     size_val = width
205     IF ( PRESENT(size) ) size_val = size 
206     ! listINT enlarge
207     MALLOC(listINT_temp,(1:tail))
208     listINT_temp(1:tail) = this%listINT(1:tail)
209     FREE(this%listINT)
210     this%size = width + size_val
211     MALLOC(this%listINT,(1:this%size))
212     this%listINT(1:tail) = listINT_temp(1:tail)
213     FREE(listINT_temp)
214     ! listDBLE enlarge
215     MALLOC(listDBLE_temp,(1:tail))
216     listDBLE_temp(1:tail) = this%listDBLE(1:tail)
217     FREE(this%listDBLE)
218     MALLOC(this%listDBLE,(1:this%size))
219     this%listDBLE(1:tail) = listDBLE_temp(1:tail)
220     FREE(listDBLE_temp)
221   ELSE
222     CALL MapHyb_init(this, Global_SIZE)
223   END IF
224 END SUBROUTINE MapHyb_enlarge

ABINIT/m_MapHyb/MapHyb_init [ Functions ]

[ Top ] [ Functions ]

NAME

  MapHyb_init

FUNCTION

  initialize

COPYRIGHT

  Copyright (C) 2013-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

INPUTS

  this=Map
  size=memory size for initialization

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

100 SUBROUTINE MapHyb_init(this, size)
101 
102 !Arguments ------------------------------------
103   TYPE(MapHyb)     , INTENT(INOUT) :: this
104   INTEGER, OPTIONAL, INTENT(IN   ) :: size
105 !Local variables ------------------------------
106   INTEGER                          :: size_val
107 
108   size_val = Global_SIZE
109   IF ( PRESENT(size) ) size_val = size
110   this%size = size_val
111   FREEIF(this%listINT)
112   MALLOC(this%listINT,(1:size_val))
113   FREEIF(this%listDBLE)
114   MALLOC(this%listDBLE,(1:size_val))
115   this%tail     = 0
116 END SUBROUTINE MapHyb_init

ABINIT/m_MapHyb/MapHyb_print [ Functions ]

[ Top ] [ Functions ]

NAME

  MapHyb_print

FUNCTION

  print the this

COPYRIGHT

  Copyright (C) 2013-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

INPUTS

  this=Map
  ostream=file stream

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

399 SUBROUTINE MapHyb_print(this,ostream)
400 
401 !Arguments ------------------------------------
402   TYPE(MapHyb)     , INTENT(IN) :: this
403   INTEGER, OPTIONAL, INTENT(IN) :: ostream
404 !Local variables ------------------------------
405   INTEGER                       :: ostream_val
406   INTEGER                       :: it
407 
408   ostream_val = 6
409   IF ( PRESENT(ostream) ) ostream_val = ostream
410   WRITE(ostream_val,'(A,2x,A5,2x,A5)') "#","Index", "Value"
411   DO it = 1, this%tail
412     WRITE(ostream_val,'(3x,I5,2x,ES22.14)') this%listINT(it), this%listDBLE(it) 
413   END DO
414 END SUBROUTINE MapHyb_print

ABINIT/m_MapHyb/MapHyb_quickSort [ Functions ]

[ Top ] [ Functions ]

NAME

  MapHyb_quickSort

FUNCTION

  sort the this with respect to the integer array
  with the quickSort algo

COPYRIGHT

  Copyright (C) 2013-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

INPUTS

  this=Map
  begin=first element to consider
  end=last element to consider

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

329 RECURSIVE SUBROUTINE MapHyb_quickSort(this, begin, end)
330 
331 !Arguments ------------------------------------
332   TYPE(MapHyb), INTENT(INOUT) :: this
333   INTEGER     , INTENT(IN   ) :: begin
334   INTEGER     , INTENT(IN   ) :: end
335 !Local variables ------------------------------
336   INTEGER                     :: it1
337   INTEGER                     :: it2
338   INTEGER                     :: pivot
339   INTEGER                     :: Iswap
340   DOUBLE PRECISION            :: Dswap
341 
342   pivot = this%listINT((end-begin)/2 + begin) ! not the betterchoice.... FIXME
343   it1 = begin
344   it2 = end
345   DO WHILE (it1 .LE. it2)
346     DO WHILE ( this%listINT(it1) .LT. pivot )
347       it1 = it1 + 1
348     END DO
349     DO WHILE ( this%listINT(it2) .GT. pivot )
350       it2 = it2 - 1
351     END DO
352     IF ( it1 .LE. it2) THEN
353       Iswap = this%listINT(it1)
354       Dswap = this%listDBLE(it1)
355       this%listINT(it1)  = this%listINT(it2)
356       this%listDBLE(it1) = this%listDBLE(it2)
357       this%listINT(it2)  = Iswap
358       this%listDBLE(it2) = Dswap
359       it1 = it1 + 1
360       it2 = it2 - 1
361     END IF
362   END DO
363   IF ( begin < it2 ) THEN
364     CALL MapHyb_quickSort(this,begin,it2)
365   END IF
366   !!it2= it1+1
367   IF ( it1 < end ) THEN
368     CALL MapHyb_quickSort(this,it1,end)
369   END IF
370 
371 END SUBROUTINE MapHyb_quickSort

ABINIT/m_MapHyb/MapHyb_setSize [ Functions ]

[ Top ] [ Functions ]

NAME

  MapHyb_setSize

FUNCTION

  impose size of the this

COPYRIGHT

  Copyright (C) 2013-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

INPUTS

  this=Map
  new_tail=new size

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

144 SUBROUTINE MapHyb_setSize(this,new_tail)
145 
146 !Arguments ------------------------------------
147   TYPE(MapHyb), INTENT(INOUT) :: this
148   INTEGER     , INTENT(IN   ) :: new_tail
149 !Local variables ------------------------------
150   INTEGER                     :: size
151 
152   IF ( .NOT. ALLOCATED(this%listINT) ) THEN
153     CALL MapHyb_init(this)
154   END IF
155   size = this%size
156   IF( new_tail .GT. size ) THEN
157     CALL MapHyb_enlarge(this, MAX(new_tail-size,Global_SIZE))
158   END IF
159   this%tail = new_tail
160 END SUBROUTINE MapHyb_setSize  

ABINIT/m_MapHyb/MapHyb_sort [ Functions ]

[ Top ] [ Functions ]

NAME

  MapHyb_sort

FUNCTION

  sort the this with respect to the integer array

COPYRIGHT

  Copyright (C) 2013-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

INPUTS

  this=Map

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

292 SUBROUTINE MapHyb_sort(this)
293 
294 !Arguments ------------------------------------
295   TYPE(MapHyb), INTENT(INOUT) :: this
296  
297   IF ( this%tail .EQ. 1 ) RETURN
298   CALL MapHyb_quickSort(this, 1, this%tail)
299 END SUBROUTINE MapHyb_sort

m_MapHyb/MapHyb [ Types ]

[ Top ] [ m_MapHyb ] [ Types ]

NAME

  MapHyb

FUNCTION

  This structured datatype contains the necessary data

COPYRIGHT

  Copyright (C) 2013-2024 ABINIT group (J. Bieder)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

SOURCE

46 TYPE, PUBLIC :: MapHyb
47   INTEGER _PRIVATE :: size
48   INTEGER          :: tail
49   INTEGER         , ALLOCATABLE, DIMENSION(:) :: listINT
50   DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:) :: listDBLE
51 END TYPE MapHyb