views:

1605

answers:

2

Hi, All.

I'm really having trouble with Allocatable array.

I have to copy all information from a file into allocatable array. The file is like this:

3 
3 5 
2 1 
4 0

3 is the number of points other six numbers shows points on the graph in (x, y) form. So (3,5), (2, 1), (4,0) are the points. But I have problem to make these number as a pair.

I tried to code, and here is my coding:

PROGRAM practice

IMPLICIT NONE

INTEGER :: astat, ioStatus
INTEGER :: x, y
INTEGER :: num, code1, code2, code3, code4, code5, code6
! num shows number of location. in this case 3
! code 1 to 6 shows x and y variable. and code1 and 2 have to be paired. 
! as well as this, code 3 and 4, code 5 and 6 have to be paired

! Declare TYPE
! set 1 to 3 show pair of (x, y)
TYPE Location
  INTEGER :: set1, set2, set3
  INTEGER :: num_locations
END TYPE

! Array ()
! for number of locations to visit
TYPE(Location), DIMENSION(:) :: numLocationArray(1000)

! allocatable array
! For locations
TYPE(Location), DIMENSION(:, :) :: LocationArray
ALLOCATABLE :: LocationArray

! allocate LocationArray
ALLOCATE(LocationArray(x, y), STAT = astat)
  IF (astat < 0) STOP "allocate failed"

! open input file to copy info into array
OPEN (UNIT = 10, File ="input.txt", STATUS = "OLD", ACTION = "READ", &
IOSTAT = ioStatus)
IF (ioStatus < 0) STOP "open failed"
! format of the file  
100 FORMAT (I1, /, 2I2, /, 2I2, / 2I2)

! Do loop to set table
DO x = 0, size(LocationArray), 1
   READ (UNIT = 10, FMT = 100, IOSTAT = ioStatus) num, code1, code2, &
   code3, code4, code5, code6
   ! check whether program read file correctly  (option) 
        PRINT *, num, code1, code2, code3, code4, code5, code6

   IF (x == code1) THEN
       DO y = 0, size(LocationArray), 1
          IF (y == code2) THEN
             LocationArray%set1 = LocationArray(x, y)
              ! check whether copied correctly
            PRINT *, LocationArray(x, y)
     PRINT *, LocationArray%set1
      END IF
   END DO
   END IF
 END DO

! ==============
! execution part
! ==============

! instructions:
! use pointer to do excecution

! read allocatable array above
! do excecution (distance) ** do not forget to go back to the original place (0,0)
!                          ** do not forget to try every single possible way
! when get total distance, do distance times 2 and figure out cost
! print all info (cost, distance, and steps)
! (example of output)
!  The minimum cost is    36
!  The distance travelled is    18
!  Step  1: Start at (  0,   0)
!  Step  2: Goes to (  2,   1)
!  Step  3: Goes to (  3,   5)
!  Step  4: Goes to (  4,   0)
!  Step  5: Ends at (  0,   0)

END PROGRAM

This program does not work...I have an error:

LocationArray%set1 = LocationArray(x, y)
Error: Can't convert TYPE(location) to INTEGER(4) at (1)

I tired to figure out this error, but I couldn't Does anyone any advice or suggestion about my coding?

Forgive my English, I'm Japanese.

If anyone has questions about my question (I mean need more explanation), please let me know.

Thank you. Uka

A: 

Looks like you are trying to give an integer the value of two integeres. It's something like you try to do = (or var = 5,5).

yeah that's what i was trying to do. but I figured out the part! thank you for your comment.
Uka
+1  A: 

In the definition of the type Location, you've said that set1, set2, and set3 are integer variables, then you attempt to assign an array to it. I think what you want, since these are pairs, is to have set1, set2, and set3 be an integer array of size 2.

What if you change the Location type to be:

TYPE Location
  INTEGER, DIMENSION(2) :: set1, set2, set3
  INTEGER :: num_locations
END TYPE

Also the loop to read the data makes no sense to me. I think I'd write it as (note that arrays in Fortran are 1-based by default, not zero-based as in C):

DO x = 1, size(numLocationArray), 1
   READ (UNIT = 10, FMT = 100, IOSTAT = ioStatus) num, code1, code2, &
   code3, code4, code5, code6
   ! check whether program read file correctly  (option) 
        PRINT *, num, code1, code2, code3, code4, code5, code6

   numLocationArray(x)%num_locations = num
   numLocationArray(x)%set1(0) = code1
   numLocationArray(x)%set1(1) = code2
   numLocationArray(x)%set2(0) = code3
   numLocationArray(x)%set2(1) = code4
   numLocationArray(x)%set3(0) = code5
   numLocationArray(x)%set3(1) = code6
END DO

You'll obviously need to do something to detect and handle the end of file condition as well.

If the number of locations is truly varaible, then you'd need to do something like:

TYPE Coordinate
   INTEGER :: x
   INTEGER :: y
END TYPE

TYPE Locations
   TYPE(Coordinate), DIMENSION(:), ALLOCATABLE :: location
   INTEGER :: num_locations
END TYPE

TYPE(Location), DIMENSION(:) :: numLocationArray(1000)

! open input file to copy info into array
OPEN (UNIT = 10, File ="input.txt", STATUS = "OLD", ACTION = "READ", &
IOSTAT = ioStatus)
IF (ioStatus < 0) STOP "open failed"
! format of the file  
100 FORMAT (I1 )
200 FORMAT (2I2)

DO n = 1, size(numLocationArray), 1
   READ (UNIT = 10, FMT = 100, IOSTAT = iostatus) num

   numLocationArray(n)%num_locations = num

   ALLOCATE (numLocationArray(n)%locations(num), STAT = astat)
   if (astat < 0) STOP 'allocate failed'

   DO l = 1, num, 1
      READ (UNIT = 10, FMT = 200, IOSTAT = iostatus) x, y
      numLocationArray(n)%locations(l)%x = x
      numLocationArray(n)%locations(l)%y = y
   END DO
END DO
tvanfosson
Thank you for your help! I figured out :)
Uka