File: fox_init_module.f90

package info (click to toggle)
espresso 6.7-4
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid
  • size: 311,068 kB
  • sloc: f90: 447,429; ansic: 52,566; sh: 40,631; xml: 37,561; tcl: 20,077; lisp: 5,923; makefile: 4,503; python: 4,379; perl: 1,219; cpp: 761; fortran: 618; java: 568; awk: 128
file content (24 lines) | stat: -rw-r--r-- 728 bytes parent folder | download | duplicates (4)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
MODULE fox_init_module
USE mp,   ONLY: mp_bcast, mp_barrier 
USE io_global, ONLY: ionode, ionode_id
USE mp_images, ONLY: intra_image_comm
USE m_common_io, ONLY: setup_io, io_err, io_eor, io_eof
IMPLICIT NONE 
PRIVATE
PUBLIC     :: fox_init 

CONTAINS 
   SUBROUTINE fox_init() 
      IMPLICIT NONE
      INTEGER   :: errcodes(3)
      IF (ionode) THEN
         call setup_io() 
         errcodes(1) = io_err
         errcodes(2) = io_eor
         errcodes(3) = io_eof
      END IF
      CALL mp_barrier(intra_image_comm) 
      CALL mp_bcast(errcodes, ionode_id, intra_image_comm) 
      CALL setup_io(ERR_CODE = errcodes(1), EOR_CODE = errcodes(2), EOF_CODE = errcodes(3))
   END SUBROUTINE fox_init
END MODULE fox_init_module