fortran-lang / webpage

New Fortran webpage
https://fortran-lang.org/en
MIT License
47 stars 39 forks source link

Should fortran-lang.org have a Fortran code snippet on the landing page? #108

Open milancurcic opened 3 years ago

milancurcic commented 3 years ago

What prompted me to open this: https://twitter.com/asmeurer/status/1334423581837561856

When putting together the first version of the website back in April, I wanted and tried to include an example Fortran code snippet. However, at the time, I struggled with my HTML and CSS to make it look pretty so in interest of time I dropped it and moved on. Then I forgot about it.

First question is, should the landing page have an example code syntax, nicely styled, syntax-colored, some minimal but real-world example? The purpose is to show what Fortran looks and feels like, on a first impression to a newcomer to the language.

Second, if the answer is yes (and I think so), can you please think of and propose some example snippets that you think would be good for this? Then we can all discuss them and choose our favorite.

Third, are you interested in making this happen? It should be a relatively low-hanging fruit, with I think a high ROI. It would probably require basic-to-intermediate HTML+CSS skills and a basic sense of good design.

Here are examples for inspiration, some pretty, some not so pretty:

milancurcic commented 3 years ago

Tagging @asmeurer: What do you think would be a good example and design? Thank you!

smeskos commented 3 years ago

Nice idea, for me, a proper Hello Word example-code for Fortran would be a demonstration of a common and simplified version of a numerical method, eg. Newton-Raphson, or central-difference or something similar that could be written in 5-10 lines.

certik commented 3 years ago

I was going to say what @smeskos suggested: some actual numerical method, that fits into a few lines. About 10 years ago, Travis Oliphant compared a simple vectorized Poisson solver in Python:

http://technicaldiscovery.blogspot.com/2011/06/speeding-up-python-numpy-cython-and.html

and I wrote a version in Fortran:

https://github.com/certik/laplace_test

that was a lot faster: https://github.com/certik/laplace_test/blob/9f0f0c0377642a5d02a386fdda39d51808f75068/laplace_for.f90

So a simplified version could look something like this:

program laplace_example
implicit none
integer, parameter :: dp=kind(0.d0), N = 100
real(dp) :: u(N,N), t1, t2
call cpu_time(t1)
u = laplace(N, 8000, 0.1_dp, 0.1_dp)
call cpu_time(t2)
print *, "Time:", t2 - t1
print *, sum(u), sum(u**2)

contains

    function laplace(N, Niter, dx, dy) result(u)
    integer, intent(in) :: N, Niter
    real(dp), intent(in) :: dx, dy
    real(dp) :: u(N,N)
    integer :: i
    u(1,:) = 1
    u(2:,:) = 0
    do i = 1, Niter
        u(2:N-1,2:N-1) = ((u(3:,2:N-1) + u(:N-2,2:N-1))*dy**2 + &
            (u(2:N-1,3:) + u(2:N-1,:N-2))*dx**2) / (2*(dx**2 + dy**2))
    end do
    end function

end program

Update: I further simplified the code (it still returns the same answer):

program laplace        
implicit none
integer, parameter :: dp=kind(0.d0), N = 100, Niter = 8000
real(dp) :: dx = 0.1_dp, u(N,N), t1, t2
integer :: i
call cpu_time(t1)
u(1,:) = 1
u(2:,:) = 0
do i = 1, Niter
    u(2:N-1,2:N-1) = ((u(3:,2:N-1) + u(:N-2,2:N-1)) + &
        (u(2:N-1,3:) + u(2:N-1,:N-2))) / 4
end do
call cpu_time(t2)
print *, "Time:", t2 - t1
print *, sum(u), sum(u**2)
end program

Or to condense it even further to better fit at the front page:

program laplace
implicit none
integer, parameter :: dp=kind(0.d0), N=100, Niter=8000
real(dp) :: dx=0.1_dp, u(N,N)
integer :: i
u(1,:) = 1; u(2:,:) = 0
do i = 1, Niter
    u(2:N-1,2:N-1) = ((u(3:,2:N-1) + u(:N-2,2:N-1)) + &
        (u(2:N-1,3:) + u(2:N-1,:N-2))) / 4
end do
print *, sum(u), sum(u**2)
end program

Only 12 lines and it is the full program that compiles and runs.

arjenmarkus commented 3 years ago

A Newton-Raphson like example could be written in FORTRAN 77 as well. How about a/my simple qsort example? That would demonstrate array operations as well as non-trivial memory management.

Op do 3 dec. 2020 15:50 schreef smeskos notifications@github.com:

Nice idea, for me, a proper Hello Word example-code for Fortran would be a demonstration of a common and simplified version of a numerical method, eg. Newton-Raphson, or central-difference or something similar that could be written in 5-10 lines.

— You are receiving this because you are subscribed to this thread. Reply to this email directly, view it on GitHub https://github.com/fortran-lang/webpage/issues/108, or unsubscribe https://github.com/notifications/unsubscribe-auth/AAN6YR4UDRARF6KHUFDZJVLSS6QUBANCNFSM4UMBJH2Q .

certik commented 3 years ago

@arjenmarkus, can you post an example that compiles? Let's compare code snippets, then we can effectively select the best one to represent Fortran.

asmeurer commented 3 years ago

Thanks for opening this issue. To me, the most important thing is just to show what the basic syntax looks like. Believe it or not, quite a few people have never actually seen a Fortran program before.

arjenmarkus commented 3 years ago

@Ondřej Čertík ondrej@certik.us , well, here is an example:

! qsort_reals.f90 -- ! ! Example belonging to "Modern Fortran in Practice" by Arjen Markus ! ! This work is licensed under the Creative Commons Attribution 3.0 Unported License. ! To view a copy of this license, visit http://creativecommons.org/licenses/by/3.0/ ! or send a letter to: ! Creative Commons, 444 Castro Street, Suite 900, Mountain View, California, 94041, USA. ! ! Compact implementation of the QuickSort algorithm ! ! Note: ! Because the function uses Fortran 90 features, its interface should be made ! explicit when using it in an actual program. This is easiest via a module. ! module qsort_functions implicit none contains recursive function qsort_reals( data ) result( sorted ) real, dimension(:), intent(in) :: data real, dimension(1:size(data)) :: sorted

if ( size(data) > 1 ) then
    sorted = &
        (/ qsort_reals( pack( data(2:), data(2:) > data(1) ) ), &
           data(1),                                             &
           qsort_reals( pack( data(2:), data(2:) <= data(1) ) ) /)
else
    sorted = data
endif

end function qsort_reals end module qsort_functions

! test -- ! Straightforward test ... ! program test_qsort_reals use qsort_functions

implicit none

real, dimension(200) :: r

call random_number( r )

write(*,'(f12.5)') qsort_reals( r )

end program test_qsort_reals

Other examples I was thinking about: read a list of numbers, store them in a growing array and then determine basic statistical parameters.

Op do 3 dec. 2020 om 18:03 schreef Ondřej Čertík notifications@github.com:

@arjenmarkus https://github.com/arjenmarkus, can you post an example that compiles? Let's compare code snippets, then we can effectively select the best one to represent Fortran.

— You are receiving this because you were mentioned. Reply to this email directly, view it on GitHub https://github.com/fortran-lang/webpage/issues/108, or unsubscribe https://github.com/notifications/unsubscribe-auth/AAN6YRY6ZWQIMUVCTRQ2P43SS7AEHANCNFSM4UMBJH2Q .

certik commented 3 years ago

@asmeurer wrote:

Believe it or not, quite a few people have never actually seen a Fortran program before.

Oh, we believe it. That is why where are all here trying to fix it. :) Thank you again for your feedback.

vmagnin commented 3 years ago

Personally, I was very impressed by the Mandelbrot snippet on the Julia page: https://julialang.org/learning/code-examples/ In 14 lines, they compute and draw a Mandelbrot set in the terminal, like in Mandelbrot days (late 70's)...

But probably concerning Fortran, a short code computing something with array syntax would be better. The @certik Laplace example is interesting, but the loop is difficult to read for someone not familiar with the method. Could be more readable if we put an image of the mathematical writing on the left, and the Fortran algorithm on the right? Fortran is the IBM Mathematical Formula Translating System, isn't it?

ivan-pi commented 3 years ago

Could be more readable if we put an image of the mathematical writing on the left, and the Fortran algorithm on the right? Fortran is the IBM Mathematical Formula Translating System, isn't it?

This is similar to what @rouson and others from the Sourcery Institute have, see here: http://www.sourceryinstitute.org/

I'm not really sure custom unary and binary operators operating on derived types are the most representative element of Fortran though. A more "low level" example using array slicing might be more suitable.

Perhaps an example including co-arrays is another good selling point. Visitors should realize from first sight, that Fortran is a parallel language.

vmagnin commented 3 years ago

Perhaps an example including co-arrays is another good selling point. Visitors should realize from first sight, that Fortran is a parallel language.

Yes, I was also thinking it may be interesting (I am now reading the co-array article). Something with a very modern syntax, with the mathematical formula alongside...

milancurcic commented 3 years ago

If you need the math alongside, I think the example is not simple enough. @certik's Laplace example is too complex IMO.

interkosmos commented 3 years ago

I’m throwing in a Mandelbrot implementation in modern Fortran:

! mandelbrot.f90
program main
    implicit none
    integer, parameter :: NCOLS = 80, NROWS = 40, MAX_ITER = 10
    real,    parameter :: THRESHOLD = 2.0

    character(len=1) :: buffer(NCOLS, NROWS)
    integer          :: x, y
    real             :: re, im
    real             :: t1, t2

    buffer(:, :) = ' '

    call cpu_time(t1)

    do concurrent (y = 1:NROWS)
        im = -1.5 + (y - 1) * 3.0 / NROWS

        do concurrent (x = 1:NCOLS)
            re = -2.0 + (x - 1) * 3.0 / NCOLS

            if (mandelbrot(cmplx(re, im), MAX_ITER, THRESHOLD) >= MAX_ITER) &
                buffer(x, y) = '*'
        end do
    end do

    do y = 1, NROWS
        print '(*(a1))', buffer(:, y)
    end do

    call cpu_time(t2)
    print '("Time: ", f8.6, " sec")', t2 - t1
contains
    pure integer function mandelbrot(c, max_iter, threshold)
        complex, intent(in) :: c
        integer, intent(in) :: max_iter
        real,    intent(in) :: threshold
        complex             :: z

        z = (0.0, 0.0)

        do mandelbrot = 0, max_iter
            z = z**2 + c
            if (abs(z) > threshold) exit
        end do
    end function mandelbrot
end program main

Should work with all compilers and on all platforms, for example:

$ gfortran -o mandelbrot mandelbrot.f90
$ ./mandelbrot

                                                 *                              
                                                  ***                           
                                                 ***                            
                                              *********                         
                                              ********                          
                                     * *   ************  *     *                
                                      ********************* *****               
                                      **************************                
                                   ****************************                 
                    *     *        *******************************              
                     *********    *******************************               
                     *********************************************              
                *   *********************************************               
                 ***********************************************                
**************************************************************                  
                 ***********************************************                
                *   *********************************************               
                     *********************************************              
                     *********    *******************************               
                    *     *        *******************************              
                                   ****************************                 
                                      **************************                
                                      ********************* *****               
                                     * *   ************  *     *                
                                              ********                          
                                              *********                         
                                                 ***                            
                                                  ***                           
                                                 *                              

Time: 0.006165 sec

Edit: Added @arjenmarkus’s hints.

arjenmarkus commented 3 years ago

Nice, just picking a few nits:

Perhaps you can use the unlimited format:

write(,'((a))') buffer(:,iy)

And if you check for a number of iterations larger than 10, there is no need for MAX_ITER to be largerthan that, is there?

Also, the arguments max_iter and threshold could be taken from the host.

Op ma 15 feb. 2021 om 17:19 schreef Philipp notifications@github.com:

I’m throwing in a Mandelbrot implementation in modern Fortran:

! mandelbrot.f90 program main

implicit none

integer, parameter :: NCOLS = 80, NROWS = 40, MAX_ITER = 100

real,    parameter :: THRESHOLD = 2.0

character(len=1) :: buffer(NCOLS, NROWS)

character(len=8) :: fmt

integer          :: x, y

real             :: re, im

real             :: t1, t2

buffer(:, :) = ' '

call cpu_time(t1)

do concurrent (y = 0:NROWS)

    im = -1.5 + y * 3.0 / NROWS

    do concurrent(x = 0:NCOLS)

        re = -2.0 + x * 3.0 / NCOLS

        if (mandelbrot(cmplx(re, im), MAX_ITER, THRESHOLD) > 10) &

            buffer(x + 1, y + 1) = '*'

    end do

end do

write (fmt, '(a, i0, a)') '(', NCOLS, '(a1))'

do y = 1, NROWS

    print fmt, buffer(:, y)

end do

call cpu_time(t2)

print '("Time: ", f8.6, " sec")', t2 - t1

contains

pure integer function mandelbrot(c, max_iter, threshold)

    complex, intent(in) :: c

    integer, intent(in) :: max_iter

    real,    intent(in) :: threshold

    complex             :: z

    z = (0.0, 0.0)

    do mandelbrot = 0, max_iter

        z = z**2 + c

        if (abs(z) > threshold) exit

    end do

end function mandelbrot

end program main

Should work with all compilers and on all platforms, for example:

$ gfortran -o mandelbrot mandelbrot.f90

$ ./mandelbrot

                                             *

                                              ***

                                             ***

                                          *********

                                          ********

                                 * *   ************  *     *

                                  ********************* *****

                                  **************************

                               ****************************

                *     *        *******************************

                 *********    *******************************

                 *********************************************

            *   *********************************************

             ***********************************************

             ***********************************************

            *   *********************************************

                 *********************************************

                 *********    *******************************

                *     *        *******************************

                               ****************************

                                  **************************

                                  ********************* *****

                                 * *   ************  *     *

                                          ********

                                          *********

                                             ***

                                              ***

                                             *

Time: 0.006165 sec

— You are receiving this because you were mentioned. Reply to this email directly, view it on GitHub https://github.com/fortran-lang/webpage/issues/108, or unsubscribe https://github.com/notifications/unsubscribe-auth/AAN6YR5XPXUCBMWZBCH4QS3S7FCP7ANCNFSM4UMBJH2Q .

awvwgk commented 3 years ago

I tried to come up with a shorter version of Philipp's mandelbrot implementation (33 lines, 30 LOC):

! mandelbrot.f90
program main
  implicit none
  integer, parameter :: NCOLS = 80, NROWS = 40, MAX_ITER = 10
  real,    parameter :: THRESHOLD = 1.7
  character :: buffer(NCOLS, NROWS)
  integer   :: x, y, it
  real      :: re, im, t1, t2

  call cpu_time(t1)
  do concurrent (y = 1:NROWS, x = 1:NCOLS)
    im = -1.5 + (y - 1) * 3.0 / NROWS
    re = -2.0 + (x - 1) * 3.0 / NCOLS
    it = mandelbrot(cmplx(re, im), MAX_ITER, THRESHOLD)
    buffer(x, y) = merge('*', ' ', it >= MAX_ITER)
  end do
  call cpu_time(t2)
  print '(*(a1))', [(buffer(:, y), new_line('a'), y = 1, NROWS)]
  print '("Time: ", f8.6, " sec")', t2 - t1
contains
  pure integer function mandelbrot(c, max_iter, threshold)
    complex, intent(in) :: c
    integer, intent(in) :: max_iter
    real,    intent(in) :: threshold
    complex             :: z

    z = (0.0, 0.0)
    do mandelbrot = 0, max_iter
        z = z**2 + c
        if (abs(z) > threshold) exit
    end do
  end function mandelbrot
end program main

I just checked it with Nvidia's, NAG's, Intel's and GCC's Fortran compiler, just to make sure we are not using anything that is prone to break with those. Also tried to reduce the line length (column 63) to make it nicely visible in small code containers.

I think it is a nice example to start with as a code snippet.

vmagnin commented 3 years ago

For computing Mandelbrot, abs(z) is not a good choice, it's faster to compute:

if (real(z)**2 + aimag(z)**2 > threshold**2) exit

Of course it does not matter here with the low resolution: with MAX_ITER = 100000, the time difference is really sensible, but brings nothing graphically here...

certik commented 3 years ago

Regarding abs(z) I want compilers to generate as fast code as real(z)**2 + aimag(z)**2, I can't see why they couldn't. I am aware that sometimes they don't, but I consider that a bug.

certik commented 3 years ago

I think it's still too long for a front page. Here is a shorter version, closer to the Julia example:

program main
  implicit none
  integer, parameter :: NCOLS = 80, NROWS = 40
  character :: buffer(NCOLS, NROWS)
  integer   :: x, y
  real      :: re, im
  do concurrent (y = 1:NROWS, x = 1:NCOLS)
    im = -1.5 + (y - 1) * 3.0 / NROWS
    re = -2.0 + (x - 1) * 3.0 / NCOLS
    buffer(x, y) = merge('*', ' ', abs(mandelbrot(cmplx(re, im))) < 2)
  end do
  print '(*(a1))', [(buffer(:, y), new_line('a'), y = 1, NROWS)]
contains
  pure complex function mandelbrot(a) result(z)
    complex, intent(in) :: a
    integer :: i
    z = 0
    do i = 1, 50
      z = z**2 + a
    end do
  end function
end program

Ours is better, because it's in parallel.

awvwgk commented 3 years ago

Ours is better, because it's in parallel.

Parallel yes, but I'm not sure about the better

❯ nvfortran main.f90 -stdpar=multicore  && ./a.out
/usr/bin/ld: warning: /opt/nvidia/Linux_x86_64/21.5/compilers/lib/nvhpc.ld contains output sections; did you forget -T?

        *
*
 *                                                                              

                   *                             ****          *                
         *  *     

                                       *** ***************                      

                                    ***************************                 

                      **********   ******************************               
                *        

 ************************************************************                   

                      *********    ******************************               
               *               

                      *             **************************                  

                                                *****                           
                                               ******                           
                                                 ****                           

Intel Fortran gets it right even in parallel. So no worries.

vmagnin commented 3 years ago

Regarding abs(z) I want compilers to generate as fast code as real(z)**2 + aimag(z)**2, I can't see why they couldn't.

@certik No, don't forget that abs(z) = sqrt(real(z)**2 + aimag(z)**2) By replacing abs() by real(z)**2 + aimag(z)**2, you are removing the useless computation of the square root, that's just why it's faster.

certik commented 3 years ago

You are right, if forgot about that.

certik commented 3 years ago

I still like the Laplace example the most. It's one of the simplest possible numerical methods. I agree the vectorized loop is not the simplest to read. But we can rewrite it in explicit loops, then it is clear that it is just the stencil. Here is the original:

program laplace
implicit none
integer, parameter :: dp=kind(0.d0), N=100, Niter=80000
real(dp) :: u(N,N)
integer :: i
u(1,:) = 1; u(2:,:) = 0
do i = 1, Niter
    u(2:N-1,2:N-1) = ((u(3:,2:N-1) + u(:N-2,2:N-1)) + &
        (u(2:N-1,3:) + u(2:N-1,:N-2))) / 4
end do
print *, sum(u), sum(u**2)
end program

And here is the explicit stencil version:

program laplace
implicit none
integer, parameter :: dp=kind(0.d0), N=100, Niter=80000
real(dp) :: u(N,N)
integer :: i, j, m
u(1,:) = 1; u(2:,:) = 0
do m = 1, Niter
    do j = 2, N-1
    do i = 2, N-1
        u(i,j) = (u(i+1,j) + u(i-1,j) + u(i,j+1) + u(i,j-1)) / 4
    end do
    end do
end do
print *, sum(u), sum(u**2)
end program

The first and second version produce the following numbers, respectively:

   2500.9999999998840        1356.5191481174465     
   2500.9999999998754        1356.5191481174404     

For smaller iteration numbers (Niter) they differ slightly because the first version updates the whole array at once, while the second version is reusing the new value in the next stencil, but as iterations progress, both versions converge towards the same result.

arjenmarkus commented 3 years ago

How about using j = 2,size(N,2)-1 and similar for i? Just to illustrate an IMO important aspect of Fortran: that you do not need to rely explicitly on the declaration of arrays, but have (a limited form of) introspection.

Also: I prefer 4.0 over 4

One last remark: as this determines the stationary solution, it is not a particular problem to use the new value of u(i,j), but it would be if you were to extend it to a time-dependent diffusion problem.

Op za 19 jun. 2021 om 23:46 schreef Ondřej Čertík @.***

:

I still like the Laplace example the most. It's one of the simplest possible numerical methods. I agree the vectorized loop is not the simplest to read. But we can rewrite it in loops, then it is clear that it is just the stencil. Here is the original:

program laplaceimplicit noneinteger, parameter :: dp=kind(0.d0), N=100, Niter=80000real(dp) :: u(N,N)integer :: i u(1,:) = 1; u(2:,:) = 0do i = 1, Niter u(2:N-1,2:N-1) = ((u(3:,2:N-1) + u(:N-2,2:N-1)) + & (u(2:N-1,3:) + u(2:N-1,:N-2))) / 4end doprint *, sum(u), sum(u**2)end program

And here is the explicit stencil version:

program laplaceimplicit noneinteger, parameter :: dp=kind(0.d0), N=100, Niter=80000real(dp) :: u(N,N)integer :: i, j, m u(1,:) = 1; u(2:,:) = 0do m = 1, Niter do j = 2, N-1 do i = 2, N-1 u(i,j) = (u(i+1,j) + u(i-1,j) + u(i,j+1) + u(i,j-1)) / 4 end do end doend doprint *, sum(u), sum(u**2)end program

The first and second version produce the following numbers, respectively:

2500.9999999998840 1356.5191481174465 2500.9999999998754 1356.5191481174404

For smaller iteration numbers they differ slightly because the first version updates the whole array at once, while the second version is reusing the new value in the next stencil, but as iterations progress, both versions converge towards the same result.

— You are receiving this because you were mentioned. Reply to this email directly, view it on GitHub https://github.com/fortran-lang/webpage/issues/108, or unsubscribe https://github.com/notifications/unsubscribe-auth/AAN6YR42IELQKEDJYSFJES3TTUF37ANCNFSM4UMBJH2Q .

certik commented 3 years ago

Btw, using 4.0 would give wrong answers, you want to use 4.0_dp. I prefer 4, because it is shorter, but I am fine with either.

Yes, we can do do i = 2, size(u)-1, although it's longer, so for cases like this, I usually prefer to use the variable N as it is shorter.

Both of these points are minor (from my perspective), so I am fine either way.

Good point about time-dependent diffusion problem.

arjenmarkus commented 3 years ago

Re 4: yes, that is true, it should be 4.0_dp. I prefer to be explicit about the "real" character, so that 4/3 pi radius**3 or the like does not give surprising results.

Re size: I prefer the longer version, because then I do not have to look up what the dimensions were - and to avoid misreading them ;).

But I can live with the short version too. Picking nits is a wonderful pastime, but it is also nice to actually produce things.

Op ma 21 jun. 2021 om 13:43 schreef Ondřej Čertík @.***

:

Btw, using 4.0 would give wrong answers, you want to use 4.0_dp. I prefer 4, because it is shorter, but I am fine with either.

Yes, we can do do i = 2, size(u)-1, although it's longer, so for cases like this, I usually prefer to use the variable N as it is shorter.

— You are receiving this because you were mentioned. Reply to this email directly, view it on GitHub https://github.com/fortran-lang/webpage/issues/108, or unsubscribe https://github.com/notifications/unsubscribe-auth/AAN6YR6PRHZF7GBV5DYWKH3TT4QU5ANCNFSM4UMBJH2Q .

jacobwilliams commented 3 years ago

I really like the https://www.python.org one, where they have a 5 very short examples.

Their "launch interactive shell" is also amazing.... maybe one day with LFortran we could have that too!

ivan-pi commented 2 years ago

The Taichi GitHub landing page also features a Mandelbrot example (both parallelized and executed on GPU). Taichi is a domain-specific language for high-performance parallel computing based on Python syntax.

bhaskar0120 commented 2 years ago

I really like the idea of an interactive shell on the website like @jacobwilliams suggested. But if that is a bit far fetched for now, I feel that a carousel animation of small code snippets (Like simple loops and conditions) would give the user a feel of what the language is syntactically.

hojdan commented 2 years ago

Personally I like Python's approach the best. Haskell also has a sound approach in that they do not even need to write entire programs. Instead of a single program showcasing the capabilities of Fortran, perhaps several simpler programs each showcasing just a few features of the language would be better. It would not be as intimidating and I feel it would be better understood by newcomers. Also so that we don't need to keep seeing implicit none it does not need to be a full program.

KHUSHIJAIN910 commented 9 months ago

Some ideas could include a simple mathematical computation, a loop structure, or an input/output operation. For instance: program HelloWorld implicit none write(*, '(A)') 'Hello, World!' end program HelloWorld

Will be happy if I can contibute to any of the issue here

Om15102003 commented 9 months ago

Including a Fortran code snippet on the landing page of fortran-lang.org can be beneficial for users seeking a quick glimpse of the language's syntax and usage. It could provide a concise example to showcase Fortran's strengths and encourage further exploration.
Will be happy if I can contribute to any of the issue here.

EnigmaShi commented 8 months ago

Here are a few minimal but real-world Fortran code snippets that could be considered for the landing page: ! Example 2: Simple Array Operation PROGRAM ArrayOperation INTEGER, PARAMETER :: N = 5 REAL, DIMENSION(N) :: numbers INTEGER :: i

numbers = (/1.0, 2.0, 3.0, 4.0, 5.0/)

DO i = 1, N numbers(i) = numbers(i) * 2.0 END DO END PROGRAM ArrayOperation