OpenMP parallelization

I have a subroutine as below. How can I use OpenMP to parallelize all the loops inside it?

subroutine call_price(n, s, sigma, t, r, k, res)
  integer(4) :: n, i1, i2 
  real(8) :: s, sigma, t, r, k, res, delta_t, u, d, q, stock_tree(n + 1, n + 1), option_tree(n + 1, n + 1)
  delta_t = t/n
  u = exp(sigma*sqrt(delta_t))
  d = exp(-sigma*sqrt(delta_t))
  q = (exp(r*delta_t) - d)/(u - d)
  !$omp parallel do collapse(2)
  do i2 = 1, n + 1
    do i1 = 1, n + 1
      stock_tree(i1, i2) = 0d0
      option_tree(i1, i2) = 0d0
    end do
  end do
  do i2 = 1, n + 1
    do i1 = 1, i2
      stock_tree(i1, i2) = s*u**(i1 - 1)*d**((i2 - 1) - (i1 - 1))
    end do
  end do
  !$omp parallel do
  do i1 = 1, n + 1
    option_tree(i1, n + 1) = max(stock_tree(i1, n + 1) - k, 0d0)
  end do
  do i2 = n, 1, -1
    do i1 = 1, i2
      option_tree(i1, i2) = ((1d0 - q)*option_tree(i1, i2 + 1) + q*option_tree(i1 + 1, i2 + 1))/exp(r*delta_t)
    end do
  end do
  res = option_tree(1, 1)
end subroutine

You could parallelise the first two DO groups, for “do i2 = 1, n + 1”, but don’t use collapse.

The last group “do i2 = n+1, 1, -1” is not easy to use !$omp, as each I2 depends on I2+1.

I am not sure of your sample, but when mapping the relationship for the last DO group:
as only stock_tree(:,n+1) is used, and
options_tree(:,i2) depends on options_tree(:,i2+1),
so vectors stock_list(n+1) and option_list(n+1) can be used.
Unless I am mistaken, this results in the following, which is unlikely to benefit from !$OMP.
It may not be what you want, but I see no way of applying !$OMP to the last DO group.
(apologies if I have missed something!)

subroutine call_price (n, s, sigma, t, r, k, res)
  integer*4 :: n
  real*8    :: s, sigma, t, r, k, res

  integer*4 :: i1, i2
  real*8    :: delta_t, u, d, q, stock_list(n + 1), option_list(n+1)
  real*8    :: alpha, beta, op,op1

  delta_t = t/n
  u = exp(sigma*sqrt(delta_t))
  d = exp(-sigma*sqrt(delta_t))

    i2 = n + 1
    do i1 = 1, i2
      stock_list(i1) = s*u**(i1 - 1)*d**((i2 - 1) - (i1 - 1))
    end do

! Note : only stock_tree(:,n+1) is used > stock_list(:)

  q     = (exp(r*delta_t) - d)/(u - d)
  alpha = (1d0 - q)/exp(r*delta_t)
  beta  = q/exp(r*delta_t)

  do i2 = n+1, 1, -1
    if ( i2==n+1 ) then
       do i1 = 1, n + 1
         option_list(i1) = max (stock_list(i1) - k, 0d0)
       end do
    else
      op1 = option_list(i2 + 1)
      do i1 = i2,1,-1
        op = option_list(i1)
        option_list(i1) = alpha*op + beta*op1
        op1 = op
      end do
    end if
  end do
  res = option_list(1)
end subroutine call_price