Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations strongm on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

"Hybrid" multidimensional arrays 1

Status
Not open for further replies.

radzio

Technical User
Aug 10, 2011
7
Hi All,

I have a question concerning the possibility of having some kind of a "hybrid" array which can store, for example, both integer and real numbers. Is possible to construct something like this using derived types? I'm not a professional programmer and looking at the web for this information was unsuccessful... Some working examples would be very much appreciated.

Thanks in advance,

Radek
 
Yes it's possible, look at this example:
In the example above a compound datatype named mineral is defined:
Code:
type mineral !Definicao de mineral com as suas caracterisitcas
    integer:: numero
    character(50) :: nome,cor, brilho
    real :: dureza
end type mineral
You see - it contains one integer. three strings and one real.
Further an array of this datatypes is defined:
Code:
  type (mineral), dimension(1200) :: basededados
Try the example and see how it works...
 
Which version of Fortran are you using? There are different techniques depending on whether it is F77 or F90.
 
Fist of all thanks for interest:)

I'm using mostly Fortran 90.

As far as I understand I can define for example type like this in a module:

Code:
MODULE MOD1

  TYPE TP1
    INTEGER,DIMENSION(5) :: INTMAT
    REAL :: realval
  END TP1

END MODULE MOD1

Then in a program I would like to open some file and read a data in a format like this:

Code:
...
1 2 3 4 5  4.56
6 7 8 9 0  5.78
...

How could I do that with such definition? When I define this type somewhere like:

Code:
TYPE(TP1),DIMENSION(number) :: VALUES

and then try to read it like (from 101 file):

Code:
READ(101,*) VALUES

it tries to read it line by line, not in a row from file. How to do this? And more importantly how to make the "inner" variables allocatable and how to allocate them in the type? For example not to stick to

Code:
INTEGER,DIMENSION(5) :: INTMAT

but have it like:

Code:
INTEGER,DIMENSION(:),ALLOCATABLE :: INTMAT

I'm not sure how does it work...

Thanks,

Radek
 
Look at this code
Code:
[COLOR=#a020f0]module[/color] MOD1  
  [COLOR=#2e8b57][b]type[/b][/color] TP1    
    [COLOR=#2e8b57][b]INTEGER[/b][/color],[COLOR=#2e8b57][b]DIMENSION[/b][/color]([COLOR=#ff00ff]5[/color]) :: INTMAT    
[COLOR=#2e8b57][b]    REAL[/b][/color] :: realval  
  [COLOR=#2e8b57][b]end type[/b][/color] TP1 
[COLOR=#a020f0]end module[/color] MOD1

[COLOR=#a020f0]program[/color] radzio
  [COLOR=#a020f0]use[/color] mod1
  [COLOR=#2e8b57][b]integer[/b][/color], [COLOR=#2e8b57][b]parameter[/b][/color] :: [COLOR=#804040][b]number[/b][/color] [COLOR=#804040][b]=[/b][/color] [COLOR=#ff00ff]2[/color]
  [COLOR=#2e8b57][b]integer[/b][/color] :: i, j
  [COLOR=#2e8b57][b]TYPE[/b][/color](TP1),[COLOR=#2e8b57][b]DIMENSION[/b][/color]([COLOR=#804040][b]number[/b][/color]) :: VALUES
  
  [COLOR=#0000ff]! assign data[/color]
  [COLOR=#0000ff]! element #1[/color]
  values([COLOR=#ff00ff]1[/color])%intmat([COLOR=#ff00ff]1[/color]) [COLOR=#804040][b]=[/b][/color] [COLOR=#ff00ff]1[/color]
  values([COLOR=#ff00ff]1[/color])%intmat([COLOR=#ff00ff]2[/color]) [COLOR=#804040][b]=[/b][/color] [COLOR=#ff00ff]2[/color]
  values([COLOR=#ff00ff]1[/color])%intmat([COLOR=#ff00ff]3[/color]) [COLOR=#804040][b]=[/b][/color] [COLOR=#ff00ff]3[/color]
  values([COLOR=#ff00ff]1[/color])%intmat([COLOR=#ff00ff]4[/color]) [COLOR=#804040][b]=[/b][/color] [COLOR=#ff00ff]4[/color]
  values([COLOR=#ff00ff]1[/color])%intmat([COLOR=#ff00ff]5[/color]) [COLOR=#804040][b]=[/b][/color] [COLOR=#ff00ff]5[/color]
  values([COLOR=#ff00ff]1[/color])%realval   [COLOR=#804040][b]=[/b][/color] [COLOR=#ff00ff]4.56[/color]
  [COLOR=#0000ff]! element #2[/color]
  values([COLOR=#ff00ff]2[/color])%intmat([COLOR=#ff00ff]1[/color]) [COLOR=#804040][b]=[/b][/color] [COLOR=#ff00ff]6[/color]
  values([COLOR=#ff00ff]2[/color])%intmat([COLOR=#ff00ff]2[/color]) [COLOR=#804040][b]=[/b][/color] [COLOR=#ff00ff]7[/color]
  values([COLOR=#ff00ff]2[/color])%intmat([COLOR=#ff00ff]3[/color]) [COLOR=#804040][b]=[/b][/color] [COLOR=#ff00ff]8[/color]
  values([COLOR=#ff00ff]2[/color])%intmat([COLOR=#ff00ff]4[/color]) [COLOR=#804040][b]=[/b][/color] [COLOR=#ff00ff]9[/color]
  values([COLOR=#ff00ff]2[/color])%intmat([COLOR=#ff00ff]5[/color]) [COLOR=#804040][b]=[/b][/color] [COLOR=#ff00ff]0[/color]
  values([COLOR=#ff00ff]2[/color])%realval   [COLOR=#804040][b]=[/b][/color] [COLOR=#ff00ff]5.78[/color]

  [COLOR=#0000ff]! print data[/color]
  [COLOR=#804040][b]do[/b][/color] i[COLOR=#804040][b]=[/b][/color][COLOR=#ff00ff]1[/color], [COLOR=#804040][b]number[/b][/color]
    [COLOR=#804040][b]write[/b][/color]([COLOR=#804040][b]*[/b][/color],[COLOR=#804040][b]*[/b][/color]) (values(i)%intmat(j), j[COLOR=#804040][b]=[/b][/color][COLOR=#ff00ff]1[/color],[COLOR=#ff00ff]5[/color]), values(i)%realval 
  [COLOR=#804040][b]end do[/b][/color]

[COLOR=#a020f0]end program[/color] radzio
the output is
Code:
$ g95 radzio.f95 -o radzio

$ radzio
 1 2 3 4 5 4.56
 6 7 8 9 0 5.78
 
If you are looking for an input method, then the best way would be a semi object oriented
Code:
module KnownMod
  type KnownType
    INTEGER,DIMENSION(5) :: INTMAT    
    REAL :: realval  
  end type KnownType
contains
   subroutine KnownRead (var_value, in_channel)
     type (KnownType), intent(inout):: var_value
     integer, intent(in):: in_channel
     
     read (in_channel, *) &
       (var_value%intmat(ii), ii = 1, 5), &
       var_value%realval 
  end subroutine KnownRead
  
  subroutine KnownPrint (in_value)
     type (KnownType), intent(in):: in_value
     
     write (*, '(5I4, F10.4)') &
       (in_value%intmat(ii), ii = 1, 5), &
       in_value%realval
   end subroutine KnownPrint 
end module KnownMod

program main
   use KnownMod
   integer, parameter:: infile = 20
   type (KnownType):: hybrid
   open (unit=infile, file='twotypes.txt', status='old')
   call KnownRead (hybrid, infile)
   call KnownPrint (hybrid)
   
   call KnownRead (hybrid, infile)
   call KnownPrint (hybrid)
   
   close (infile)
  
end program
Taking this a bit further, if you're not too worried about space, then you could have an array of types. In languages like C, this would have been done using a union to save space
Code:
   type UnknownType
      logical:: isInt
      real:: rval
      integer:: ival
   end type UnknownType
You could then base the number type on the input
Code:
module UnknownMod
   type UnknownType
      logical:: isInt
      real:: rval
      integer:: ival
   end type UnknownType
   
contains
   subroutine UnknownRead (var_value, in_count, in_channel)
      type (UnknownType), dimension(*), intent(inout):: var_value
      integer, intent(in):: in_count
      character(len=128):: input
      character:: ch
      integer:: ii, pos
      logical:: isInt

      read (in_channel, '(A)') input
      
      ! Now read everything as real
      read (input, *) (var_value(ii)%rval, ii=1, in_count)
      
      ! Now check and set integers accordingly
      pos = 1
      do ii = 1, in_count
         ! Skip the whitespace
         do while (input(pos:pos) .eq. ' ')
            pos = pos + 1
         end do
         
         ! Look for a float
         isInt = .true.
         ch = input(pos:pos)
         do while (ch .ne. ' ')
            isInt = isInt .and. ch .ne. '.' .and. ch .ne. 'E'
            pos = pos + 1
            ch = input(pos:pos)
         end do
         
         var_value(ii)%isInt = isInt
         if (isInt) var_value(ii)%ival = nint(var_value(ii)%rval)
      end do
   end subroutine UnknownRead
   
   subroutine UnknownPrint (in_value, in_count)
      type (UnknownType), dimension(*), intent(in):: in_value
      integer, intent(in):: in_count
      
      do ii = 1, in_count
         if (in_value(ii)%isInt) then
            write (*, '(I5)', advance='no') in_value(ii)%ival
         else
            write (*, '(F10.4)', advance='no') in_value(ii)%rval
         end if
      end do
      write (*, *)
   end subroutine
end module UnknownMod

program main
   use UnknownMod
   integer, parameter:: hybridmax = 6
   type (UnknownType), dimension(hybridmax):: hybrid
   integer, parameter:: infile = 20
   open (unit=infile, file='twotypes.txt', status='old')
   call UnknownRead (hybrid, hybridmax, infile)
   call UnknownPrint (hybrid, hybridmax)
   
   call UnknownRead (hybrid, hybridmax, infile)
   call UnknownPrint (hybrid, hybridmax)
   
   close (infile)
end program
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top