TABLE OF CONTENTS


ABINIT/m_ListCdagC [ Modules ]

[ Top ] [ Modules ]

NAME

  m_ListCdagC

FUNCTION

  Manage a 2D vector to store couple of c+c

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_ListCdagC
24 USE m_Global
25 
26 IMPLICIT NONE

ABINIT/m_ListCdagC/listCdagC_assign [ Functions ]

[ Top ] [ Functions ]

NAME

  listCdagC_assign

FUNCTION

  assign routine

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

  list_1=ListCdagC
  list_2=ListCdagC

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

276 SUBROUTINE listCdagC_assign(this, list_2)
277 
278 !Arguments ------------------------------------
279   TYPE(ListCdagC), INTENT(INOUT) :: this
280   TYPE(ListCdagC), INTENT(IN   ) :: list_2
281 !Local variables ------------------------------
282   INTEGER                        :: tail
283 
284   tail = list_2%tail
285   CALL ListCdagC_setSize(this, tail)
286   this%list(0:tail,1:2) = list_2%list(0:tail,1:2)
287   !this%ind (0:tail,1:2) = list_2%ind (0:tail,1:2)
288 
289 END SUBROUTINE ListCdagC_assign

ABINIT/m_ListCdagC/ListCdagC_clear [ Functions ]

[ Top ] [ Functions ]

NAME

  ListCdagC_clear

FUNCTION

  Clear the list

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

  list_1=ListCdagC

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

763 SUBROUTINE ListCdagC_clear(this)
764 
765 !Arguments ------------------------------------
766   TYPE(ListCdagC), INTENT(INOUT) :: this
767   this%tail = 0 
768 END SUBROUTINE ListCdagC_clear

ABINIT/m_ListCdagC/ListCdagC_destroy [ Functions ]

[ Top ] [ Functions ]

NAME

  ListCdagC_destroy

FUNCTION

  destroy the list

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

  list_1=ListCdagC

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

795 SUBROUTINE ListCdagC_destroy(this)
796 
797 !Arguments ------------------------------------
798   TYPE(ListCdagC), INTENT(INOUT) :: this
799 
800   FREEIF(this%list)
801   !FAKEFREEIF(this%ind )
802 
803   this%tail     = 0
804   this%size     = 0
805   !this%inv_dt   = 0.d0
806 END SUBROUTINE ListCdagC_destroy

ABINIT/m_ListCdagC/ListCdagC_enlarge [ Functions ]

[ Top ] [ Functions ]

NAME

  ListCdagC_enlarge

FUNCTION

  Enlarge memory space of the list

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

  list_1=ListCdagC
  size=new memory size

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

213 SUBROUTINE ListCdagC_enlarge(this, size)
214 
215 !Arguments ------------------------------------
216   TYPE(ListCdagC),   INTENT(INOUT)       :: this
217   INTEGER, OPTIONAL, INTENT(IN   )       :: size
218 !Local variables ------------------------------
219   INTEGER                                :: width
220   INTEGER                                :: tail
221   INTEGER                                :: size_val
222   !INTEGER         , ALLOCATABLE, DIMENSION(:,:) :: ind_temp 
223   DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:) :: list_temp 
224 
225   IF ( ALLOCATED(this%list) ) THEN
226     FREEIF(list_temp)
227     !FAKEFREEIF(ind_temp )
228     width = this%size
229     tail  = this%tail
230     size_val = width
231     IF ( PRESENT(size) ) size_val = size 
232     MALLOC(list_temp,(0:tail,1:2))
233     !MALLOC( ind_temp,(0:width,1:2))
234     list_temp(0:tail,:) = this%list(0:tail,:)
235     !ind_temp  = this%ind
236     FREE(this%list)
237     !FREE(this%ind )
238     this%size = width + size_val
239     MALLOC(this%list,(0:this%size,1:2))
240     !MALLOC(this%ind ,(0:this%size,1:2))
241     this%list(0:tail,1:2) = list_temp(0:tail,1:2)
242     !this%ind (0:width,1:2) = ind_temp (0:width,1:2)
243     FREE(list_temp)
244   ELSE
245     !CALL ListCdagC_init(this, this%inv_dt, Global_SIZE)
246     CALL ListCdagC_init(this, Global_SIZE)
247   END IF
248 END SUBROUTINE ListCdagC_enlarge

ABINIT/m_ListCdagC/ListCdagC_erase [ Functions ]

[ Top ] [ Functions ]

NAME

  ListCdagC_erase

FUNCTION

  Erase a couple at a given position

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

  list_1=ListCdagC
  position=position of the element to remove

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

524 SUBROUTINE ListCdagC_erase(this,position)
525 
526 !Arguments ------------------------------------
527   TYPE(ListCdagC), INTENT(INOUT) :: this
528   INTEGER,         INTENT(IN   ) :: position
529 !Local variables ------------------------------
530   INTEGER                        :: tail
531   INTEGER                        :: new_tail
532   INTEGER                        :: continueing
533   
534   tail = this%tail
535   IF ( position .GT. tail ) &
536     CALL ERROR("ListCdagC_erase : position > tail                 ")
537   new_tail    = tail - 1
538   continueing = position + 1
539   this%list(new_tail:position:-1,1:2) = this%list(tail:continueing:-1,1:2)
540   this%tail = new_tail
541 END SUBROUTINE ListCdagC_erase

ABINIT/m_ListCdagC/ListCdagC_firstHigherThanReal [ Functions ]

[ Top ] [ Functions ]

NAME

  ListCdagC_firstHigherThanReal

FUNCTION

  search for the first element higher than the real time
  assume the list is already sorted

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

  list_1=ListCdagC
  time=reference

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

570 INTEGER FUNCTION ListCdagC_firstHigherThanReal(this, time)
571 
572 !Arguments ------------------------------------
573   TYPE(ListCdagC),  INTENT(IN) :: this
574   DOUBLE PRECISION, INTENT(IN) :: time
575 #include "ListCdagC_firstHigher.h"
576   ! Dichotomic research
577 #define list_1 this
578 #include "ListCdagC_firstHigher"
579 #undef list_1
580 !  unefficient function for long list  
581 !  it = 1
582 !  DO WHILE ( it .LE. this%tail .AND. this%list(it) .LE. value )
583 !    it = it + 1
584 !  END DO
585 !  IF ( it .GT. this%tail ) it = -1
586 !  ListCdagC_firstHigherThanReal = it
587   ListCdagC_firstHigherThanReal = firstHigher
588 END FUNCTION ListCdagC_firstHigherThanReal

ABINIT/m_ListCdagC/ListCdagC_init [ Functions ]

[ Top ] [ Functions ]

NAME

  ListCdagC_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

  list_1=ListCdagC
  size=size of initialization

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

120 SUBROUTINE ListCdagC_init(this, size)
121 
122 !Arguments ------------------------------------
123   TYPE(ListCdagC)  , INTENT(INOUT) :: this
124   !DOUBLE PRECISION , INTENT(IN   ) :: inv_dt
125   INTEGER, OPTIONAL, INTENT(IN   ) :: size
126 !Local variables ------------------------------
127   INTEGER                          :: size_val
128 
129   size_val = Global_SIZE
130   !this%inv_dt = inv_dt
131   IF ( PRESENT(size) ) size_val = size
132   this%size = size_val
133   FREEIF(this%list)
134   MALLOC(this%list,(0:size_val,1:2))
135   !FAKEFREEIF(this%ind)
136   !FAKEMALLOC(this%ind,(0:size_val,1:2))
137   this%tail     = 0
138 END SUBROUTINE ListCdagC_init

ABINIT/m_ListCdagC/ListCdagC_insert [ Functions ]

[ Top ] [ Functions ]

NAME

  ListCdagC_insert

FUNCTION

  insert somewhere a couple

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

  list_1=ListCdagC
  CdagC_1=couple
  position=where to insert

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

431 SUBROUTINE ListCdagC_insert(this, CdagC_1, position)
432 
433 !Arguments ------------------------------------
434   TYPE(ListCdagC), INTENT(INOUT) :: this
435   DOUBLE PRECISION, DIMENSION(1:2), INTENT(IN   ) :: CdagC_1 
436   INTEGER        , INTENT(IN   ) :: position
437 !Local variables ------------------------------
438   INTEGER                        :: new_position
439   INTEGER                        :: tail
440   
441   tail         = this%tail + 1
442   new_position = position 
443   IF ( tail .GT. this%size ) THEN
444     CALL ListCdagC_enlarge(this)
445   END IF
446   IF ( position .EQ. -1 ) THEN
447     new_position = tail
448   ELSE IF ( position .LE. tail ) THEN
449   ! new_position = position 
450     this%list(tail:position+1:-1,1:2) = this%list(this%tail:position:-1,1:2)
451   ELSE 
452     CALL ERROR("ListCdagC_insert : position > tail                ")
453   END IF
454   
455   this%list(new_position,1:2) = CdagC_1
456   !this%ind (new_position,Cdag_) = INT(CdagC_1(Cdag_) * this%inv_dt + 0.5d0)
457   !this%ind (new_position,C_   ) = INT(CdagC_1(C_   ) * this%inv_dt + 0.5d0)
458   this%tail = tail
459 END SUBROUTINE ListCdagC_insert

ABINIT/m_ListCdagC/ListCdagC_popBack [ Functions ]

[ Top ] [ Functions ]

NAME

  ListCdagC_popBack

FUNCTION

  Remove the last element

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

  list_1=ListCdagC

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

486 SUBROUTINE ListCdagC_popBack(this)
487 
488 !Arguments ------------------------------------
489   TYPE(ListCdagC), INTENT(INOUT) :: this
490 !Local variables ------------------------------
491   INTEGER                        :: tail
492 
493   tail = this%tail
494   IF ( tail .EQ. 0 ) RETURN
495   this%tail = tail - 1
496 END SUBROUTINE ListCdagC_popBack

ABINIT/m_ListCdagC/ListCdagC_print [ Functions ]

[ Top ] [ Functions ]

NAME

  ListCdagC_print

FUNCTION

  print the list

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

  list_1=ListCdagC
  ostrean=file stream

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

721 SUBROUTINE ListCdagC_print(this,ostream)
722 
723 !Arguments ------------------------------------
724   TYPE(ListCdagC)  , INTENT(IN) :: this
725   INTEGER, OPTIONAL, INTENT(IN) :: ostream
726 !Local variables ------------------------------
727   INTEGER                       :: ostream_val
728   INTEGER                       :: it
729 
730   ostream_val = 6
731   IF ( PRESENT(ostream) ) ostream_val = ostream
732   WRITE(ostream_val,'(A,2x,A4,22x,A)') "#","Cdag", "C"
733   DO it = 1, this%tail
734     WRITE(ostream_val,*) this%list(it,Cdag_), this%list(it,C_) 
735   END DO
736 END SUBROUTINE ListCdagC_print

ABINIT/m_ListCdagC/ListCdagC_pushBack [ Functions ]

[ Top ] [ Functions ]

NAME

  ListCdagC_pushBack

FUNCTION

  push at the end of the list a couple

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

  list_1=ListCdagC
  CdagC_1=couple

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

379 SUBROUTINE ListCdagC_pushBack(this, CdagC_1)
380 
381 !Arguments ------------------------------------
382   TYPE(ListCdagC), INTENT(INOUT)       :: this
383   DOUBLE PRECISION, DIMENSION(1:2), INTENT(IN   ) :: CdagC_1
384 !Local variables ------------------------------
385   INTEGER                              :: tail
386 
387   !IF ( this%size .EQ. 0 ) THEN
388   !  CALL ListCdagC_init(this, this%inv_dt, Global_SIZE)
389   !ENDIF
390   IF ( this%size .EQ. 0 ) THEN
391     CALL ListCdagC_init(this, Global_SIZE)
392   END IF
393   tail = this%tail
394   tail = tail + 1
395   IF ( tail .GT. this%size ) THEN
396     CALL ListCdagC_enlarge(this)
397   END IF
398   this%list(tail,1:2) = CdagC_1
399   !this%ind (tail,Cdag_) = INT(CdagC_1(Cdag_) * this%inv_dt + 0.5d0)
400   !this%ind (tail,C_   ) = INT(CdagC_1(C_   ) * this%inv_dt + 0.5d0)
401   this%tail       = tail
402 END SUBROUTINE ListCdagC_pushBack

ABINIT/m_ListCdagC/ListCdagC_quickSort [ Functions ]

[ Top ] [ Functions ]

NAME

  ListCdagC_quickSort

FUNCTION

  sort the list by c+ increasing with the quick sort 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

  list_1=ListCdagC
  begin=from element to consider
  end=last element to consider

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

651 RECURSIVE SUBROUTINE ListCdagC_quickSort(this, begin, end)
652 
653 !Arguments ------------------------------------
654   TYPE(ListCdagC), INTENT(INOUT) :: this
655   INTEGER,         INTENT(IN   ) :: begin
656   INTEGER,         INTENT(IN   ) :: end
657 !Local variables k-----------------------------
658   INTEGER                        :: it1
659   INTEGER                        :: it2
660   DOUBLE PRECISION               :: pivot
661   DOUBLE PRECISION, DIMENSION(1:2):: CdagC_swap
662   !DOUBLE PRECISION, DIMENSION(1:2):: ind_swap
663 
664   pivot = this%list((end-begin)/2 + begin,Cdag_) ! not the betterchoice.... FIXME
665   it1 = begin
666   it2 = end
667   DO WHILE (it1 .LE. it2)
668     DO WHILE ( this%list(it1,Cdag_) .LT. pivot )
669       it1 = it1 + 1
670     END DO
671     DO WHILE ( this%list(it2,Cdag_) .GT. pivot )
672       it2 = it2 - 1
673     END DO
674     IF ( it1 .LE. it2) THEN
675       CdagC_swap = this%list(it1,1:2)
676       !ind_swap   = this%ind (it1,1:2)
677       this%list(it1,1:2) = this%list(it2,1:2)
678       !this%ind (it1,1:2) = this%ind (it2,1:2)
679       this%list(it2,1:2) = CdagC_swap
680       !this%ind (it2,1:2) = ind_swap
681       it1 = it1 + 1
682       it2 = it2 - 1
683     END IF
684   END DO
685   IF ( begin < it2 ) THEN
686     CALL ListCdagC_quickSort(this,begin,it2)
687   END IF
688   !!it2= it1+1
689   IF ( it1 < end ) THEN
690     CALL ListCdagC_quickSort(this,it1,end)
691   END IF
692 
693 END SUBROUTINE ListCdagC_quickSort

ABINIT/m_ListCdagC/ListCdagC_setSize [ Functions ]

[ Top ] [ Functions ]

NAME

  ListCdagC_setSize

FUNCTION

  Impose size of the list

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

  list_1=ListCdagC
  new_tail=new_size

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

166 SUBROUTINE ListCdagC_setSize(this,new_tail)
167 
168 !Arguments ------------------------------------
169   TYPE(ListCdagC), INTENT(INOUT) :: this
170   INTEGER        , INTENT(IN   ) :: new_tail
171 !Local variables ------------------------------
172   INTEGER                        :: size
173 
174   !IF ( .NOT. ALLOCATED(this%list) ) THEN
175   !  CALL ListCdagC_init(this, this%inv_dt)
176   !END IF
177   IF ( .NOT. ALLOCATED(this%list) ) THEN
178     CALL ListCdagC_init(this)
179   END IF
180   size = this%size
181   IF( new_tail .GT. size ) THEN
182     CALL ListCdagC_enlarge(this,MAX(Global_SIZE, new_tail-size))
183   END IF
184   this%tail = new_tail
185 END SUBROUTINE ListCdagC_setSize  

ABINIT/m_ListCdagC/ListCdagC_sort [ Functions ]

[ Top ] [ Functions ]

NAME

  ListCdagC_sort

FUNCTION

  sort the list by c+ increasing

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

  list_1=ListCdagC

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

615 SUBROUTINE ListCdagC_sort(this)
616 
617 !Arguments ------------------------------------
618   TYPE(ListCdagC), INTENT(INOUT) :: this
619  
620   IF ( this%tail .EQ. 1 ) RETURN
621   CALL ListCdagC_quickSort(this, 1, this%tail)
622 END SUBROUTINE ListCdagC_sort

ABINIT/m_ListCdagC/ListCdagC_swap [ Functions ]

[ Top ] [ Functions ]

NAME

  ListCdagC_swap

FUNCTION

  Swap two lists

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

  list_1=ListCdagC
  list_2=ListCdagC

OUTPUT

SIDE EFFECTS

NOTES

SOURCE

317 SUBROUTINE ListCdagC_swap(this,list_2)
318 
319 !Arguments ------------------------------------
320   TYPE(ListCdagC), INTENT(INOUT) :: this
321   TYPE(ListCdagC), INTENT(INOUT) :: list_2
322 !Local variables ------------------------------
323   INTEGER :: tail1
324   INTEGER :: tail2
325   INTEGER :: i
326   INTEGER :: j
327   !INTEGER         , DIMENSION(1:2) :: ind_tmp
328   DOUBLE PRECISION, DIMENSION(1:2) :: CdagC_tmp
329 
330   tail1 = this%tail
331   tail2 = list_2%tail
332 
333   i = MAX(tail1,tail2)
334   IF ( this%size .LT. i ) THEN
335     CALL ListCdagC_enlarge(this,i)
336   END IF
337   IF ( list_2%size .LT. i ) THEN
338     CALL ListCdagC_enlarge(list_2,i)
339   END IF
340 
341   DO j = 0, i
342     CdagC_tmp(1:2) = this%list(j,1:2)
343     !ind_tmp  (1:2) = this%ind (j,1:2)
344     this%list(j,1:2) = list_2%list(j,1:2)
345     !this%ind (j,1:2) = list_2%ind (j,1:2)
346     list_2%list(j,1:2) = CdagC_tmp(1:2)
347     !list_2%ind (j,1:2) = ind_tmp  (1:2)
348   END DO
349   list_2%tail = tail1
350   this%tail = tail2
351 END SUBROUTINE ListCdagC_swap

m_ListCdagC/ListCdagC [ Types ]

[ Top ] [ m_ListCdagC ] [ Types ]

NAME

  ListCdagC

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

47 TYPE, PUBLIC :: ListCdagC
48   INTEGER _PRIVATE :: size = 0
49 !  max size of matrix list
50 
51   INTEGER          :: tail = 0 
52 !  the size of matrix list that contains physical data (ie number of
53 !  segment)
54   !DOUBLE PRECISION :: inv_dt = 0.d0
55 !  TYPE(CdagC), ALLOCATABLE, DIMENSION(:) :: list => NULL()
56   !INTEGER         , ALLOCATABLE, DIMENSION(:,:) :: ind
57   DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:)         :: list
58 !  for all elements i below itail, list(i,1:2) are times for creation
59 !  and destruction of particles.
60 END TYPE ListcdagC