File: FReader.f90

package info (click to toggle)
adios2 2.10.2%2Bdfsg1-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 33,764 kB
  • sloc: cpp: 175,964; ansic: 160,510; f90: 14,630; yacc: 12,668; python: 7,275; perl: 7,126; sh: 2,825; lisp: 1,106; xml: 1,049; makefile: 579; lex: 557
file content (70 lines) | stat: -rw-r--r-- 2,006 bytes parent folder | download
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
program FReader
    use mpi
    use adios2
    implicit none

    integer(kind=8), dimension(2) :: sel_start, sel_count
    real, dimension(:,:), allocatable :: data
    integer(kind=8) :: i, j
    integer :: irank, isize, ierr

    ! adios2 handlers
    type(adios2_adios):: adios
    type(adios2_io):: io
    type(adios2_variable):: var
    type(adios2_engine):: engine

    ! Launch MPI
    call MPI_Init(ierr)
    call MPI_Comm_rank(MPI_COMM_WORLD, irank, ierr)
    call MPI_Comm_size(MPI_COMM_WORLD, isize, ierr)

    if( irank == 0 ) then
        ! Create adios handler passing the communicator and error flag
        call adios2_init(adios, MPI_COMM_SELF, ierr)

        ! Declare an IO process configuration inside adios
        call adios2_declare_io(io, adios, "FReader", ierr)

        ! Open in write mode, this launches an engine
        call adios2_open(engine, io, "CppWriter.bp", adios2_mode_read, ierr)

        call adios2_begin_step(engine, ierr)

        call adios2_inquire_variable(var, io, 'data2D', ierr)

        if( ierr == adios2_found ) then

            sel_start = (/ 0, 2 /)
            sel_count = (/ 3, 2 /)
            allocate( data( sel_count(1), sel_count(2) ) )

            call adios2_set_selection( var, 2, sel_start, sel_count, ierr )

            call adios2_get(engine, var, data, adios2_mode_sync, ierr)

            write(*,'(A,2(I2,A),A,2(I2,A),A)') 'Selection  &
                      & [ start = (', (sel_start(i),',',i=1,2) , ') &
                      &  count =  (', (sel_count(i),',',i=1,2) , ') ]'

            do j=1,sel_count(2)
              do i=1,sel_count(1)
                write(6,'(F3.0,A)', advance="no") data(i,j), ' '
              end do
              write(*,*)
            end do

            if( allocated(data) ) deallocate(data)

        end if

        call adios2_end_step(engine, ierr)

        call adios2_close(engine, ierr)
        call adios2_finalize(adios, ierr)

    end if

    call MPI_Finalize(ierr)

end program FReader