File: plugin_arguments.f90

package info (click to toggle)
espresso 6.7-2
  • links: PTS, VCS
  • area: main
  • in suites: bookworm, bullseye
  • size: 311,040 kB
  • sloc: f90: 447,429; ansic: 52,566; sh: 40,631; xml: 37,561; tcl: 20,077; lisp: 5,923; makefile: 4,502; python: 4,379; perl: 1,219; cpp: 761; fortran: 618; java: 568; awk: 128
file content (87 lines) | stat: -rw-r--r-- 2,397 bytes parent folder | download | duplicates (5)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
!
! Copyright (C) 2010-2013 Quantum ESPRESSO group
! This file is distributed under the terms of the
! GNU General Public License. See the file `License'
! in the root directory of the present distribution,
! or http://www.gnu.org/copyleft/gpl.txt .
!
!----------------------------------------------------------------------------
SUBROUTINE plugin_arguments()
  !-----------------------------------------------------------------------------
  !
  ! check for presence of command-line option "-plugin_name" or "--plugin_name"
  ! where "plugin_name" has to be set here. If such option is found, variable
  ! "use_plugin_name" is set and usage of "plugin_name" is thus enabled.
  ! Currently implemented: "plumed", "pw2casino" (both case-sensitive)
  !
  USE kinds,         ONLY : DP
  !
  USE io_global,     ONLY : stdout
  !
  USE plugin_flags
  !
  IMPLICIT NONE
  !
  INTEGER  :: iiarg, nargs, i, i0
  CHARACTER (len=1), EXTERNAL ::  lowercase
  CHARACTER (len=256) :: arg
  !
  nargs = command_argument_count()
  ! add here more plugins
  use_plumed = .false.
  use_pw2casino = .false.
  use_environ = .false.
  !
  DO iiarg = 1, nargs 
    CALL get_command_argument( iiarg, plugin_name)
    IF ( plugin_name(1:1) == '-') THEN
       i0 = 1
       IF ( plugin_name(2:2) == '-') i0 = 2
       arg = ' '
       DO i=i0+1, LEN_TRIM (plugin_name)
          arg(i-i0:i-i0) = lowercase (plugin_name(i:i))
       END DO
!       write(0,*) "plugin_name: ", trim(arg)
       ! add here more plugins
       IF ( TRIM(arg)=='plumed' ) THEN
          use_plumed = .true.
       END IF
       IF ( TRIM(arg)=='pw2casino' ) THEN
          use_pw2casino = .true.
       ENDIF
       IF ( TRIM(arg)=='environ' ) THEN
          use_environ = .true.
       ENDIF
    ENDIF
  ENDDO
  !
  RETURN
  !
END SUBROUTINE plugin_arguments
!
!----------------------------------------------------------------------------
  SUBROUTINE plugin_arguments_bcast(root,comm)
  !----------------------------------------------------------------------------
  !
  ! broadcast plugin arguments
  !
  USE mp, ONLY : mp_bcast
  USE plugin_flags
  !
  IMPLICIT NONE
  !
  integer :: root
  integer :: comm
  !
  CALL mp_bcast(use_plumed,root,comm)
  !
  CALL mp_bcast(use_pw2casino,root,comm)
  !
  CALL mp_bcast(use_environ,root,comm)
  !
!  write(0,*) "use_plumed: ", use_plumed
  !
  RETURN
  !
END SUBROUTINE plugin_arguments_bcast