`block` syntax and my confusion

In the Fortran2008 standard, the block grammar is introduced, which allows a special block to be constructed locally. What is the meaning of its existence?

```fortran
label: blcok
    type :: variable
    command

end block label
```

In some Fortran codes with poor experience, subroutines with more business may need to set many variables in the Fortran subroutines. This will cause “variable disasters”, difficult to read. And it may appear that the location where the variable is declared is far away from the location where it is used, resulting in a poor experience.

So I sometimes deliberately avoid this problem ( “variable disasters”), and occasionally use the block syntax to “digest” some temporary variables.

As far as I know, go language and python language often declare and use variables nearby, which is a better experience.
Moreover, the c language seems to support the writing of nearby variables in the new standard.
Will Fortran also support this feature in the future:

It is not mandatory to declare variables at the head of the subroutine, and variables can be declared anywhere in the subroutine.

Thank you. :smiling_face_with_three_hearts:

1 Like

To be honest, I really got used to all the variables being at the top of a routine.
In this way there are no “surprise” variable declarations hidden in hundreds of lines of code.

However, I never used the block construct, because I am more familiar with subroutines, which are another way to get your “declarations” closer to the part where you are using them.

So maybe, if you think your declaration is too far away, you should consider breaking down your code into smaller subroutines/functions.

1 Like

Yes, I would also consider subdividing complex business into small subroutines, but sometimes I often have to consider passing parameters to subroutines, which can also cause cumbersomeness.
There are indeed some code subroutines that are very verbose, especially from beginners, causing many variables to be at the head of the subroutine and difficult to read.

Moreover, there are indeed some local variables that only need to be used once, but when you want to declare them, you need to jump to the first part of the subroutine to write, and then come back to write the code logic, which is weird.
Even if it is ok, not too bad.

Hi @zoziha, welcome to the Discourse!
You may find this previous answer of mine relevant:

See also this particular use case where block was uniquely helpful for scoping:

and this answer about local scope in do concurrent:

7 Likes

@zoziha ,

Welcome to the forum.

Re: “Will Fortran also support this feature in the future,” chances are low to zero the future Fortran revisions will allow type declarations interspersed among executable statements the way they are supported by those other languages on your list.

Please see the feedback by @lkedward .

You may know of the classic text by Kernighan and Plauger, it’s always worth reviewing it again whenever you start looking at new features such as BLOCK construct that then makes you wonder about using it in new code or refactoring existing code:

And this one too on modern Fortran style and usage:
https://www.cambridge.org/us/academic/subjects/computer-science/scientific-computing-scientific-software/modern-fortran-style-and-usage?format=PB

These texts can help you analyze and develop style(s) that suit your business needs.

3 Likes

My take is that relaxing the rules for positioning of declarations adds no functionality and complicates implementations. I also would consider scattered declarations to be poor programming practice, and I would think poorly of any programmer who wrote code that way.

2 Likes

I thought that a major rationale for BLOCK was that code generators can shield their own temporary variables from the surrounding context. Perhaps I am misunderstanding the question.

1 Like

Think of BLOCK as like { in C and END BLOCK like }. The main purpose it to allow declaration of local variables in the block. BLOCKS are effectively like textually inlined subroutines with no arguments.

DO CONCURRENT already has a way to specify that a variable is localized to the block - the LOCAL( ) specifier in the DO CONCURRENT statement. It is roughly like “private” in OpenMP.

4 Likes

BLOCK construct with EXIT clause is also quite useful for simplifying rather convoluted program logic flow with highly nested IF.. THEN.. ELSE blocks, often with GO TO statements, in existing codes.

5 Likes

This is how it’s done in almost any other non-Fortran language. Everyone else are poor programmers?

I think a lot of the legacy Fortran I work on would’ve been cleaner if the original programmers had been able to quickly declare and use some local variables. Just a simple…

integer,parameter :: TIME_CHAN = 27
integer,parameter :: SPEED_CHAN = 7

… above a block of code would mean a lot more to me than wondering what the code is doing with DAT(27) and DAT(7). I understand why the original programmers didn’t scroll hundreds of lines away just to declare a named variable to only use for a small block of code in the middle of the file, but it makes my life harder now.

There can be a lot of clarity gained by having variables declared close to where they’re used. It can be (1) easier to define and use them, and (2) clearer what exactly they’re used for.

2 Likes

The example you gave contains named constants, not variables. A good place for these is in a module and then “USE constants, Only: TIME_CHAN,SPEED_CHAN”. The problem here seems to be that nobody updated the old code to use the nice, new features. BLOCK construct allows you to declare variables near where they are used (whether the compiler will benefit from this is another matter).

1 Like

It might make sense to declare a constant like that in a module if it’s going to be used all over the place, but other times it’s more clear to have it defined closer to where it’s used.

That was just an example, though I can think of others. It’d be nice to be able to inline-declare, e.g., a string to write to multiple units without duplicating the code to generate the string.

character(len=256) :: errormsg
errormsg = "Error with value: "//string(value1)//" and other value: "//string(value2)
write (*     ,'(a)') errormsg
write (syslog,'(a)') errormsg

In our legacy code, we also have a bunch of rvtemp1, rvtemp2, rvtemp3, etc variables that get reused for different things throughout the code because apparently it wasn’t worth defining permanent variables for them in the header.

1 Like

You can effectively define parameters (variables that cannot be changed) in the middle of a program using ASSOCIATE, for example

associate (TIME_CHAN => 27, SPEED_CHAN => 7)

I have suggested that the requirement for ASSOCIATE to be paired with END ASSOCIATE be removed, to make using ASSOCIATE more convenient.

4 Likes

Works with strings too:

program demo
  use iso_fortran_env, only: error_unit, output_unit
  implicit none
  associate(errmsg => "Error with value: "//string(5))
    write(output_unit,'(A)') errmsg
    write(error_unit,'(A)') errmsg
  end associate
contains
  pure function string(i) result(str)
    integer, intent(in) :: i
    character(len=6) :: str
    write(str,'(I6)') i
  end function
end program
3 Likes

The other option of using block construct is not too bad either, if you really don’t want to scroll to the top of your procedure:

block
  character(len=256) :: errormsg
  errormsg = "Error with value: "//string(value1)//" and other value: "//string(value2)
  write (*     ,'(a)') errormsg
  write (syslog,'(a)') errormsg
end block

The thing I dislike about the associate construct is how visually unappealing it is when your declarations are long and you need to use line breaks, i.e.

associate( &
  rvtemp1 => ..., &
  rvtemp2 => ..., &
  rvtemp3 => ...)

end associate
2 Likes

Interesting uses of associate! I’ve done something a bit like this before but I’ve generally tried to shy away from it under the assumption that it might be bad practice, but I do kind of like it.

I still like to declare variables nearby, which does have its own needs!

Using block with label can also make the code structure clearer, and can “digest” some local disposable variables.
It is true that many people are accustomed to the existing programming style, just like my teacher is still accustomed to office2007, and the computer I bought is only equipped with office2016 by default :crazy_face:. The times are advancing, maybe we can become more flexible :blush:.

I think it is rigid :thinking: and hard-core to use many associate and block syntax to deal with local declaration variables. It is not as good as directly declaring variables nearby.

2 Likes

Does it mean that the use of block in a tight loop would not have any performance penalty? Testing this would likely be the ultimate answer. But I am curious to hear anyone’s comment or experience on this matter. Thanks in advance.

relative to not having a block at all and putting all declarations in the parent scope. My question is, do compilers translate block to an internal subroutine call or something similar, or try to reorganize code to inline block?

My earlier Euler program and one using BLOCK

program main
! simulate Euler's number e
implicit none
integer, parameter :: nsim = 10000000, niter = 10
integer            :: i,iter,nsum(nsim)
call random_seed()
do iter=1,niter
   do i=1,nsim
      block
         real    :: xsum,xran
         integer :: j
         xsum = 0.0
         j = 0
         do
            j = j + 1
            call random_number(xran)
            xsum = xsum + xran
            if (xsum > 1.0) exit
         end do
         nsum(i) = j
      end block
   end do
   print*,sum(nsum)/real(nsim),minval(nsum),maxval(nsum)
end do
print*,exp(1.0)," true"
end program main

take the same time using gfortran -O2.

2 Likes