Aschoolar
Aschoolar

Reputation: 355

Dynamically type array in Matlab to Fortran

Matlab has a capability to have a dynamically typed array. For example, the matlab code is

function testing1
clc;
close all;
    chrom_len = 35;


function out = newChromosome(len)
genes_pool = struct(...
    'gene',       {'#', 'U-', 'Rs', '+', '-', '*', '/', '^'}, ...
    'stackDepth', {0,   0,    1,    2,   2,   2,  2,  2},...
    'deltaStack', {1,   1,    0,   -1,  -1,   -1, -1, -1});

function gene = newGene(stackDepth)
    % Select an appropriate gene
    done = false;    
    while ~done
        ind = randi([1 numel(genes_pool)], 1, 1);

        if genes_pool(ind).stackDepth <= stackDepth
            done = true;
        end
    end
    % Generate output

    gene = genes_pool(ind);
        disp('start');
        disp('gene.gene is ');
        disp(gene.gene);
         disp('stop');
    if gene.gene == '#'
        gene.gene = round(randn(1,1) * 5);
        disp('new gene.gene is ');
        disp(gene.gene);
        disp('the gene is ');
        disp(gene);
    end
   end

 genes = {}; stack = [];
 stackDepth = 0;    
 i = 1;
 while i <= len || (i > len && stackDepth ~= 1)
     gene = newGene(stackDepth);
 %    disp('outside gene');
 %    disp(gene);
    class(gene.gene) 
    stackDepth = stackDepth + gene.deltaStack;
 %    disp('stackDepth');
 %    disp(stackDepth);
    genes = [genes, gene.gene];
 %   disp('genes');
 %    disp(genes);
    stack = [stack, stackDepth];
 %    disp('stack')
 %   disp(stack);
    i = i + 1;
    if strcmp(gene.gene, 'X') && rand(1,1) < 0.5
        genes = [genes, randi([2 4], 1)]; stackDepth = stackDepth + 1;
        stack = [stack, stackDepth];
        genes = [genes, '^']; stackDepth = stackDepth - 1;
        stack = [stack, stackDepth];
    end
    return;
 end
 out = struct('genes', {genes}, 'stack', {stack});
 return; 
end

newChromosome(2) 
end

The first run Matlab output (I use GNU Octave which is the same thing) is,

start
gene.gene is
U-
stop
ans = char 

The second run Matlab output is,

start
gene.gene is
#
stop
new gene.gene is
-11
the gene is

scalar structure containing the fields:

gene = -11
stackDepth = 0
deltaStack =  1
ans = double

When I translate Matlab to Fortran I want to duplicate output so that output Fortran is the same type as in Matlab. The gene.gene results can be either character or double. This means, it can have two types. Is it possible to do the same in Fortran? How do I dynamically type the variable in Fortran? I believe it has something to do with type casting. So far, my Fortran solution is,

function newchromosome(clen) result(out1)
implicit none

 type garray
 character*2 :: gene; 
 integer     :: stackdepth; 
 integer     :: deltastack;
 end type 

 type(garray), dimension(8) :: genespool
 type(garray), dimension(1) :: gene2

  integer,intent(in) :: clen;
  integer :: out1;
  integer :: inttest;

  genespool = [garray('#',0,1),garray('X',0,1),garray('U-',1,0), &
         garray('+',2,-1),garray('-',2,-1),garray('*',2,-1), &
         garray('/',2,-1),garray('^',2,-1) ]

  gene2 = [garray('s',0,0) ]  

  out1 = clen;
  inttest = newgene(2); 

  contains

  function newgene(stackdepth) result(out2)
  integer, intent(in) :: stackdepth;
  integer :: out2;
  logical :: done;  
  integer :: ind;
  real    :: rnd1;
  character*2, dimension(:), allocatable:: answer2;
  character*2 :: answer;

 answer = 'ye'
 out2=0;
 allocate(answer2(1)); 
!  gene=0;
!  gene = stackdepth;

  done = .FALSE.

  do while (done .EQV. .FALSE.)
    call random_number(rnd1);
    ind = nint(rnd1*size(genespool));  
    if (genespool(ind)%stackdepth <= stackdepth) then
          done = .True.
    end if         
  end do

  ! Generate output
  print*, "genespool(ind)  ", genespool(ind);    
  print*, "gene 2          ", gene2;
 gene2=genespool(ind)
  print*, "new gene 2      ",gene2;
  print*, "new gene2.gene     ",gene2%gene;
  answer2=gene2%gene;

  print*, "test 2 ", answer;
  if ( gene2(1)%gene == '#' ) then
    call random_number(rnd1);
  !  gene2%gene = nint(rnd1*5);   !<------ problem (convert integer to string integer)
  endif  
  return;      
  end function newgene 
end function newchromosome

program testing1
! ------ unit declaration ----------------------------------------------
use iso_fortran_env
implicit none
! ----------------------------------------------------------------------
! ------ variable declaration ------------------------------------------
integer                 :: chromlen;
integer                 :: newchromosome;
integer                 :: test;

  chromlen = 35; 
  test = 0;
  test=int(newChromosome(chromlen));
  print*, "newChromosome is ", test;
 flush( output_unit )

 end program testing1

I added some dummy variables such as 'answer2' just for debugging purpose. I marked with arrow where my code in FORTRAN is causing trouble due to Matlab dynamic type declaration. In FORTRAN, it could be impossible to have a variable that is both character and double (real). In FORTRAN, I cannot have U- and -11 like in Matlab because in FORTRAN has declaration of gene2 type as a character. Matlab is flexible, FORTRAN is strict. In FORTRAN, how do I make the gene2.gene accept 'real type' -11 without causing an error? Is there a better way making a type declaration such as %ptr or class(*) for heterogeneous array declaration?

Upvotes: 1

Views: 144

Answers (1)

Rodrigo Rodrigues
Rodrigo Rodrigues

Reputation: 8556

Well, I think I finally understand your code. And, if I do, what you want is to have the component gene%gene to be able to display a character or a number, when needed.

You definitely do not need/want to simulate a dynamic type or anything that hard, though. You can just maintain the component as a character type and if you need to store an integer, you convert it to text. In Fortran, conversion of other types into character is done with the same I/O statements you are used to, but you pass a character variable instead of a unit number. Like this:

write(gene2%gene, '(i0)') int(rnd1 * 5);

This statement will write the integer value of the passed expression into the character component. The format (i0) will use the minimum space needed for the number, in this case. If you need to store a real variable instead of an integer, use the same principle; but you may need to increase the length of the character component and use a different format, maybe (g0).


Even though this technically solves your question, I wrote a port of your Matlab program in, as I consider, a more "Fortran-ish" way. You may used it as a exercise to learn some language concepts and constructs you may not be familiar.

Wrap functionality into a module:

module genetics
  implicit none

  ! use a constant, so it will be easier to refactor when needed
  integer, parameter :: g_charlen = 2

  type gene
    character(g_charlen) :: gene
    integer :: depth
    integer :: delta
  end type

  ! initializing in a data statement looks nicer in this case
  type(gene) :: pool(8)
  data pool%gene  / '#', 'U-', 'Rs',  '+',  '-',  '*',  '/',  '^'/
  data pool%depth /   0,    0,    1,    2,    2,    2,    2,    2/
  data pool%delta /   1,    1,    0,   -1,   -1,   -1,   -1,   -1/

  ! or whatever implementation you may have
  type chromosome
    character(g_charlen) :: gene
    integer :: stack
  end type

contains

  ! there is no need for nested procedures in this case
  function new_gene(depth) result(out)
    integer, intent(in) :: depth
    type(gene) :: out
    real :: rnd

    associate(filtered => pack(pool, pool%depth <= depth))
      if(size(filtered) < 1) error stop 'there is no suitable gene in the pool'
      call random_number(rnd)
      out = filtered(int(rnd * size(filtered)) + 1)
    end associate
    if(out%gene == '#') then
      call random_number(rnd)
      write(out%gene, '(i0)') int(rnd * 5) ! <- here is the line
    end if
  end

  ! or whatever implementation you may have
  function new_chromosome(clen) result(out)
    integer, intent(in) :: clen
    type(chromosome), allocatable :: out(:)
    type(gene) :: g
    integer :: i, depth
    real :: rnd
    character(g_charlen) :: gch

    allocate(out(0))
    depth = 0
    i = 1
    do while(i <= clen .or. depth /= 1)
      g = new_gene(depth)
      depth = depth + g%delta
      out = [out, chromosome(g%gene, depth)]
      i = i + 1
      if(g%gene == 'X') then
        call random_number(rnd)
        if(rnd >= 0.5) cycle
        call random_number(rnd)
        write(gch, '(i0)') int(rnd * 3) + 2;
        out = [out, chromosome(gch, depth + 1), chromosome('^', depth - 1)]
      end if
    end do
  end
end

And you can test the code with:

program test
  use :: genetics
  implicit none

  type(chromosome), allocatable :: c1(:)
  integer :: i

  call random_seed
  c1 = new_chromosome(10)
  do i = 1, size(c1)
    print *, c1(i)
  end do
end

One posible output is:

 1            1
 U-           2
 *            1
 U-           2
 1            3
 2            4
 -            3
 U-           4
 U-           5
 ^            4
 /            3
 Rs           3
 -            2
 0            3
 -            2
 ^            1

Upvotes: 2

Related Questions