TABLE OF CONTENTS


ABINIT/flib_pwscf [ Modules ]

[ Top ] [ Modules ]

NAME

  flib_pwscf

FUNCTION

  the following is a partial import of the flib directory of espresso
  provides small routines for other pwscf-imported subroutines

COPYRIGHT

  Copyright (C) 2008-2024 ABINIT group (MVer)
  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

18 #if defined HAVE_CONFIG_H
19 #include "config.h"
20 #endif
21 
22 module flib_pwscf
23 
24   implicit none
25 
26   contains 

flib_pwscf/capital [ Functions ]

[ Top ] [ flib_pwscf ] [ Functions ]

NAME

 capital

FUNCTION

 converts character to capital if lowercase
 copy character to output in all other cases

INPUTS

OUTPUT

SOURCE

 88 !-----------------------------------------------------------------------
 89 FUNCTION capital( in_char )
 90 !-----------------------------------------------------------------------
 91   IMPLICIT NONE
 92   !
 93   CHARACTER(LEN=1), INTENT(IN) :: in_char
 94   CHARACTER(LEN=1)             :: capital
 95   CHARACTER(LEN=26), PARAMETER :: lower = 'abcdefghijklmnopqrstuvwxyz', &
 96                                   upper = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
 97   INTEGER                      :: i
 98   !
 99   !
100   DO i=1, 26
101      !
102      IF ( in_char == lower(i:i) ) THEN
103         !
104         capital = upper(i:i)
105         !
106         RETURN
107         !
108      END IF
109      !
110   END DO
111   !
112   capital = in_char
113   !
114   RETURN
115   !
116 END FUNCTION capital

flib_pwscf/errore [ Functions ]

[ Top ] [ flib_pwscf ] [ Functions ]

NAME

 errore

FUNCTION

INPUTS

OUTPUT

SOURCE

178 subroutine errore (routine, error, code)
179 
180   use defs_basis, only: std_out,std_out_default
181   implicit none
182 
183   !args
184   character(*), intent(in) :: routine
185   character(*), intent(in) :: error
186   integer, intent(in) :: code
187 
188   if (code == 0) return
189 
190   write(std_out,*) ' in subroutine : ', trim(routine)
191   write(std_out,*) error
192   write(std_out,*) 'error code ', code
193   stop
194 end subroutine errore
195 
196 end module flib_pwscf

flib_pwscf/lowercase [ Functions ]

[ Top ] [ flib_pwscf ] [ Functions ]

NAME

 lowercase

FUNCTION

 converts character to lowercase if capital
 copy character to output in all other cases

INPUTS

OUTPUT

SOURCE

133 !
134 !-----------------------------------------------------------------------
135 FUNCTION lowercase( in_char )
136 !-----------------------------------------------------------------------
137   IMPLICIT NONE
138   !
139   CHARACTER(LEN=1), INTENT(IN) :: in_char
140   CHARACTER(LEN=1)             :: lowercase
141   CHARACTER(LEN=26), PARAMETER :: lower = 'abcdefghijklmnopqrstuvwxyz', &
142                                   upper = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
143   INTEGER                      :: i
144   !
145   !
146   DO i=1, 26
147      !
148      IF ( in_char == upper(i:i) ) THEN
149         !
150         lowercase = lower(i:i)
151         !
152         RETURN
153         !
154      END IF
155      !
156   END DO
157   !
158   lowercase = in_char
159   !
160   RETURN
161   !
162 END FUNCTION lowercase

flib_pwscf/matches [ Functions ]

[ Top ] [ flib_pwscf ] [ Functions ]

NAME

 matches

FUNCTION

 .TRUE. if string1 is contained in string2, .FALSE. otherwise

INPUTS

OUTPUT

SOURCE

42 !-----------------------------------------------------------------------
43 FUNCTION matches( string1, string2 )
44 !-----------------------------------------------------------------------
45   IMPLICIT NONE
46   !
47   CHARACTER (LEN=*), INTENT(IN) :: string1, string2
48   LOGICAL                       :: matches
49   INTEGER                       :: len1, len2, l
50   !
51   !
52   len1 = LEN_TRIM( string1 )
53   len2 = LEN_TRIM( string2 )
54   !
55   DO l = 1, ( len2 - len1 + 1 )
56      !   
57      IF ( string1(1:len1) == string2(l:(l+len1-1)) ) THEN
58         !
59         matches = .TRUE.
60         !
61         RETURN
62         !
63      END IF
64      !
65   END DO
66   !
67   matches = .FALSE.
68   ! 
69   RETURN
70   !
71 END FUNCTION matches