1!
2! Copyright (C) 2014 Quantum ESPRESSO group
3! This file is distributed under the terms of the
4! GNU General Public License. See the file `License'
5! in the root directory of the present distribution,
6! or http://www.gnu.org/copyleft/gpl.txt .
7!
8!----------------------------------------------------------------------------
9PROGRAM manycp
10  !----------------------------------------------------------------------------
11  !
12  ! ... Poor-man cp.x parallel launcher. Usage (for mpirun):
13  ! ...    mpirun -np Np manycp.x -ni Ni [other options]
14  ! ... or whatever is appropriate for your parallel environment
15  ! ... Starts Ni cp.x instances each running on Np/Ni processors
16  ! ... Each cp.x instances
17  ! ... * reads input data from from cp_N.in, N=0,..,,Ni-1 if no input
18  ! ...   file is specified via the -i option; from "input_file"_N
19  ! ...   if command-line options -i "input_file" is specified
20  ! ... * saves temporary and final data to "outdir"_N/ directory
21  ! ...   (or to tmp_N/ if outdir='./')
22  ! ... * writes output to cp_N.out in the current directory if no input
23  ! ...   file is specified via the -i option; to "input_file"_N.out
24  ! ...   if command-line options -i "input_file" is specified
25  !
26  USE input,             ONLY : iosys_pseudo, iosys
27  USE input_parameters,  ONLY : outdir
28  USE environment,       ONLY : environment_start, environment_end
29  USE io_global,         ONLY : ionode, ionode_id, stdout
30  USE mp_global,         ONLY : mp_startup
31  USE mp_world,          ONLY : world_comm
32  USE mp_images,         ONLY : intra_image_comm, my_image_id
33  USE mp_pools,          ONLY : intra_pool_comm
34  USE mp_bands,          ONLY : intra_bgrp_comm, inter_bgrp_comm
35  USE read_input,        ONLY : read_input_file
36  USE check_stop,        ONLY : check_stop_init
37  USE command_line_options, ONLY: input_file_, ndiag_
38  !
39  IMPLICIT NONE
40  !
41  include 'laxlib.fh'
42  !
43  INTEGER :: i
44  LOGICAL :: opnd, diag_in_band_group = .true.
45  CHARACTER(LEN=256) :: filin, filout
46  CHARACTER(LEN=7) :: image_label
47  CHARACTER(LEN=6), EXTERNAL :: int_to_char
48  !
49  !
50  CALL mp_startup ( start_images=.true. )
51  CALL laxlib_start ( ndiag_, world_comm, intra_bgrp_comm, &
52       do_distr_diag_inside_bgrp_ = diag_in_band_group )
53  CALL set_mpi_comm_4_solvers( intra_pool_comm, intra_bgrp_comm, &
54       inter_bgrp_comm )
55  CALL environment_start ( 'MANYCP' )
56  !
57  ! ... Image-specific input files
58  !
59  image_label = '_' // int_to_char(my_image_id)
60  IF ( TRIM (input_file_) == ' ') THEN
61     filin = 'cp' // TRIM(image_label)  // '.in'
62  ELSE
63     filin = TRIM(input_file_) // TRIM(image_label) // '.in'
64  END IF
65  !
66  ! ... Here open image-specific output files
67  !
68  IF ( ionode ) THEN
69     !
70     INQUIRE ( UNIT = stdout, OPENED = opnd )
71     IF (opnd) CLOSE ( UNIT = stdout )
72     IF ( TRIM (input_file_) == ' ') THEN
73        filout = 'cp' // TRIM(image_label)  // '.out'
74     ELSE
75        filout = TRIM(input_file_) // TRIM(image_label) // '.out'
76     END IF
77     OPEN( UNIT = stdout, FILE = TRIM(filout), STATUS = 'UNKNOWN' )
78     !
79  END IF
80  !
81  CALL start_clock('CP')
82  CALL read_input_file ( prog='CP', input_file_=filin )
83  !
84  ! ... Set image-specific value for "outdir", starting from input value
85  ! ... (read in read_input_file)
86  !
87  DO i=LEN_TRIM(outdir),1,-1
88     IF ( outdir(i:i) /= '/' .AND. outdir(i:i) /= '.' ) EXIT
89  END DO
90  ! ... i = position of last character different from '/' and '.'
91  IF ( i == 0 ) THEN
92     outdir = 'tmp' // trim(image_label) // '/'
93  ELSE
94     outdir = outdir(1:i) // trim(image_label) // '/'
95  END IF
96  !
97  ! ... Perform actual calculation
98  !
99  ! ... read in pseudopotentials files and then
100  ! ... copy pseudopotential parameters into internal variables
101  !
102  CALL iosys_pseudo()
103  !
104  ! ... copy input parameters from input_parameter module
105  !
106  CALL iosys()
107  !
108  CALL check_stop_init()
109  !
110  CALL cpr_loop( 1 )
111  !
112  CALL laxlib_end ()
113  CALL stop_cp_run(  )
114  !
115END PROGRAM manycp
116