This discussion got me the idea to see how much you can compute at compile time. For example this program computes \int_a^b \sin(x) dx at compile time:
program compile_time
implicit none
integer, parameter :: N = 65535
integer, parameter :: sp = kind(1.0)
integer, parameter :: dp = kind(1.d0)
real(dp), parameter :: pi = 2*asin(1._dp)
real(dp), parameter :: a = 0, b = pi
real(dp), parameter :: dx = (b-a)/N
integer :: i
real(dp), parameter :: X(*) = [(sin(a+(b-a)*i/N), i = 1, N)]
real(dp), parameter :: S = sum(X)*dx
logical, parameter :: l = S < 2
real(kind=merge(sp, dp, l)) :: y
if (kind(y) == sp) then
print *, "true"
else
print *, "false"
end if
print *, S
end program
It prints:
true
1.9999999996170159
The value in S must be known at compile time, because it is used to determine the kind of the variable y, which must be known at compile time.
It looks like one can already do loops, if statements, etc.
If I remember correctly the last slide was an analogy with vortexes in a flowing fluid, similar to how the fluid is stretched and folded, we can use packing/unpacking, or generating/reshaping to evaluate the desired expression.
Edit: Iād be extremely impressed if someone could write a compile time prime-sieve.
Is doing 65,535 calculations of sin, so that would make sense. Iād guess the equivalent program would take a similar amount of time in many interpreted languages.
Gfortran only takes 2 seconds to compile it, though, so the speed of compile time calculations across compilers seems to vary more than run-time speed.
Well, I could not resist the challenge, and I must confess it is not a true prime sieve, more a brute force approach, but here is one solution to computing a list of primes at compile-time:
! primesieve.f90 --
! Is it possible t obuild a prime sieve using compile-time computation?
!
program primesieve
implicit none
integer, parameter :: N = 100
integer :: i, j
integer, parameter :: candidates(*) = [(i, i=2,N)]
integer, parameter :: multiples(*) = [(( i*j, i=2,N), j=2,N)]
integer, parameter :: primes(*) = pack( candidates, [(all(candidates(i) /= multiples), i = 1,size(candidates))] )
write(*,*) primes
end program primesieve
I first tried with N = 1000, but then gfortran choked, gaspng that I should use -fmax-array-constructor. When I tried that, my patience was exhausted. May try again later on.
The program in this state does get compiled by both gfortran and Intel Fortran, even in a reasonable time, though Intel Fortran is slower and compiling takes, eh, a bit longer than you would expect from so tiny a program. But they both give executables that do their job.
Update: with N=1000 both gfortran and Intel Fortran have now taken more than 15 minutes to compile the program and there is no indication that they are about to complete the task.
Conclusion: if you want a list of primes, you are probably better off computing it in run-time.
Me neither, I intend to let them run in the background, until I turn off the laptop. Just curious to see what the result is (not the list of primes, the compile time)
That sounds right: quadratic to fill the array of multiples and then the loop over all the candidates to see if any occur within that list of multiples.
That is several orders of magnitude more memory than I would as a naĆÆve programmer expect!
(The Intel compiler is still considering my program and it takes 1 GB of memory. I have no idea how much it usually takes, as compilation is usually quick and so I would not even bother to find out)
I have a teaching example which uses a 375,000+ word dictionary. The overall best way to get the āwordsā into a data structure is reading the file. In Fortran I read into an array and use a binary search algorithm. In C# and C++ I use sets and set membership, but with both of these too I read the data in. Worst case scenario is 375,000+ lines of source code. Not worth trying to ācomputeā at compile time in my opinion.
I hereby nominate Arjen as Leader of the PACK Intrinsic (is groepsleider better?).
Here is a slight modification of his program, with two speed-ups:
Avoid even numbers in candidates, except for 2.
Avoid putting numbers larger than N in the multiples array.
! primesieve.f90 --
! Is it possible to build a prime sieve using compile-time computation?
!
program primesieve
implicit none
integer, parameter :: N = 1000
integer, parameter :: rtN = 31 ! isqrt(N)
integer :: i, j
integer, parameter :: candidates(*) = [2,(i, i=3,N-1,2)]
integer, parameter :: multiples(*) = [(( i*j, i=j,N/j,2), j=3,rtN,2)]
integer, parameter :: primes(*) = pack( candidates, [(all(candidates(i) /= multiples), i = 1,size(candidates))] )
write(*,'(10I8)') primes
end program primesieve
This version should work with more compilers, while retaining the attribute of āall calculations done at compile timeā.
This version, with N equal to 1000, compiled with GFortran 12 (Windows Cygwin64) in less than 3 s (i7-10710U CPU). Intelās Ifort and Ifx compilers took less than 1 second to compile and run. For this value of N, the size of the multiples array in this version is 563, whereas Arjenās original version had it at nearly one million!