Coarray Reading file

Hi,

I am trying to read a file in coarray program (opencoarrays), I am using the condition that it be read when image==1. But it seems that CAFRUN automatically runs all the images available. Is there any way that coarray reads only from the image 1 and do rest of the calculations, by not repeating it for other images.

Any advice, help and documentation would be helpful

Attached is the source code and dummy file, I am testing. Can we use coarray to read and write in serial mode and do all the numerical operation in parallel mode (something similar to openmp)

Thanks and Regards

Apurva

Fourth.f90 (568 Bytes)
xy.txt (4 Bytes)

For small files it’s easier for people to read and respond if they are pasted in the message. Below are fourth.f90 and xy.txt.

program t1
        use, intrinsic :: iso_fortran_env
         implicit none
        integer :: n[*],pro,q,me
        !n=0
        !write(*,*)"Called Main Program"
        
        me = this_image()
        pro = num_images()
        write(*,*)"image : ",this_image()
        if ( me == 1) then
                open(unit=input_unit,file="xy.txt",action="read")
                read(input_unit,*)n
                do q = 2,pro
                        n[q]=n[1]
                end do
         end if
       
         write(*,*)"n :",n
         sync all 

end program t1

10

Hi @apoorv01 ,

It’s a bit unclear what you mean with these statements.
Maybe, a clarification would further help readers understanding your problem and possibly provide ad-hoc solutions for them.

In the meantime, I tried your code, and by anticipating that I might have not caught what you actually want to achieve with it, I think there are some tiny logic flaws, specially with the loop

do q = 2,pro
   n[q]=n[1]
end do

Here and here some references where you can read more about coarrays and how they work in practice. For sure, other more experianced members here can guide you towards more insightful places.

In the meantime, I give you a modified version of your code based on what I thought you are trying to attempt:

program test
   use, intrinsic :: iso_fortran_env
   implicit none
   integer :: n[*], nimgs, i_, me, iu = 100
   
   me    = this_image()
   nimgs = num_images()
   
   write(*, *) ' Hello from image  :  ', me, '  of ', nimgs
   sync all

   ! Read file only from image 1
   if (me == 1) then
      write(*, *) ' Image ', me, ' reading file...'
      open(unit=iu, file='xy.txt', form='formatted', action = 'read')
      read(iu, *) n[1]  !<--- NOTE: equivalent "read(iu, *) n"
      close(iu)
      write(*, *) ' Image ', me, ' reading file...  ok.'
   endif
   sync all !<-- in the meantime, the others wait for image 1 to finish its work.

   n[me] = n[1] + me  !<-- Broadcast read value to all other images (1-myself included)

  ! print results
   do i_ = 1, nimgs
      if (me == i_) write(*, *) '  Image ', me, '  :  n[me]  = ', n[me]
      sync all
   enddo
end program

Hope this helps.

Regards.

2 Likes

@mEm, Thank you for your suggestions. This has made me more clear about the input file handling. Let me try the real file I want to read and store data for my program.
Best Regards
Apurva

  1. Refer also to Modern Fortran Explained introducing Fortran 2018 for current facilities including with coarray TEAMS
  2. Also, evaluate standard facilities with more than one Fortran processor to cross-check standard semantics and to be ultra mindful of compiler deficiences,
  3. With a Fortran 2018 and newer Fortran processors, consider coarray intrinsics such as CO_BROADCAST for many common tasks. This can be helpful because an author can allow the processor to do the synchronization, as necessary.
   integer :: n[*], i

   ! Simulate file READ
   if ( this_image() == 1 ) n = 42

   call co_broadcast( n, 1 )

   ! check values
   if ( this_image() == 1 ) then
      print "(g0,t10,g0)", "Image", "n"
      do i = 1, num_images()
         print "(g0,t10,g0)", i, n[i]
      end do
   end if

end
C:\temp>ifort /free /standard-semantics /Qcoarray=shared /Qcoarray-num-images=8 p.f
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.10.0 Build 20230609_000000
Copyright (C) 1985-2023 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.36.32537.0
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\temp>p.exe
Image    n
1        42
2        42
3        42
4        42
5        42
6        42
7        42
8        42

To read a multi record file into a coarray variable with allocatable components you would have to allocate the coarray variable separately on all images, before you can use co_broadcast?

@FortranFan …, Thank you for the reply. I will refer the book mentioned