Newbie Question: use OpenMP with derived type?

Dear all:

I am wondering if it is possible to use OpenMP with derived type. The reason I am asking this is that projects like nlopt-f are using nlopt_func to send derived type inside the user-defined objective function. If it is possible then maybe my calculation speed using nlopt can be even faster, yet my primitive online search told me that it is…impossible?

I really hope that it is possible to use parallel computing with derived type!

Thanks!

HJ

Could you post a toy example that illustrates your question? Without code it’s not easy (at least for me) to understand the problem.

In the absence of an example… My understanding of the problem is that in your user-defined objective function you are receiving a derived type object as an argument and you have to perform calculations with/on it. And you would like to use this object inside an OpenMP parallel region.

The general answer is: yes of course this is possible:

  • without any restriction if the object is shared between threads.
  • if the object is private
    – allocatable components are allocated with the same size than in the original object, but are not initialised (I tested with gfortran and I’m not sure if the fact that the component is allocated is guaranteed by the OpenMP standard or if this is specific to gfortran)
    – pointer components have an undefined status
  • if the object is firstprivate
    – allocatable components are allocated with the same size than in the original object, and are initialized with the data contained in the original object
    – pointer components point to the same target than the pointer component of the original object. This means that on entering the parallel region, the target data are somehow shared
1 Like

Thank you so much for your reply! I am now trying to come up with a toy example but somehow OpenMP works with derived type :exploding_head::exploding_head::exploding_head:

Well, if it answered your question, you don’t really need to build a toy example. Unless it helps getting more details.

Somehow my actual code is still not providing the correct answer, so I still don’t understand why it works in the toy example but not in my code

My actual code is in the following code chuck:

and the derived type conf is defined in the following place:

I am using fpm, so if you run fpm run @fast it will run the file, and now I set it so that it only runs the subroutine wvalueiter.

And the result is different from running it sequentially, like running fpm run --flag="-O3".

Here is my toy example that somehow OMP works:

program main

    use iso_Fortran_env, only: rk => real64, ik => int32

    implicit none

    integer(ik) :: i
    real(rk) :: x, fx
    real(rk), dimension(:), allocatable :: fxvec

    type configurations
        real(rk) :: a
        real(rk) :: b
        real(rk) :: c
        real(rk), dimension(:, :), allocatable :: vec
    end type

    type(configurations) :: conf


    allocate(conf%vec(10, 3), source = 0.0_rk)
    allocate(fxvec(10), source = 0.0_rk)

    write(*, *) conf%vec

    !$omp parallel do private(x, conf, fx)
    do i = 1, 10, 1
        x = dble(i-1)
        conf%vec(1, 2) = dble(i - 2)
        conf%vec(1, 3) = dble(i - 1)
        conf%a = dble(i)
        conf%b = dble(i*2)
        conf%c = dble(i*3)

        write(*, *) i, conf%vec(1, 2), conf%vec(1, 3), conf%a, conf%b, conf%c

        fx = f(x, conf)
        fxvec(i) = fx
    enddo
    !$omp end parallel do

    write(*, *) fxvec



contains

    function f(x, conf)
        real(rk), intent(in) :: x
        type(configurations), intent(in) :: conf
        real(rk) :: f

        f = conf%a * x + conf%b + conf%c + conf%vec(1, 2)*conf%vec(1, 3)

    end function f


end program main

Thank you so much @PierU !

You have commented out some !$OMP parallel do directives to leave only the one on the outer loop. By doing so, some variables that were declared as private (such as kval, yval…) are now shared, which is not what you want I think. So you have to append these variables to the private list of the outer loop directive.

1 Like

Thank you so much! Now I understand and thank you again to solve my question!

I have been using OpenMP successfully for a few years, but try to use intrinsic data types and also avoid memory sharing where possible, especially modifying shared arrays, apart from some well tested methods, such as skyline linear equation reduction.
I have not attempted to use derived types in OpenMP regions, so am not familiar with these limitations.

I would expect there could be a difference if the derived type is PRIVATE, rather than SHARED.
It would be easier to work with a shared derived type, whose values are never changed (only referenced).
For a PRIVATE derived type there would be more complexity for defining and initialising these data structures.
Use of FLUSH for shared arrays could also be problematic.
Your use of allocatable components is also more difficult. Could you seperate just these out of the derived type ?

I limit derived types to be used as an in-memory data structure that is referenced, and rarely changed, outside !$OMP regions.

If you can limit derived type usage to only referencing in an !$OMP region, that may work, but private derived type or worse still, a shared derived type that is modified in an !$OMP region, would be very optimistic.

As it is best to have !$OMP encompasing large blocks of computation, it may be a challenge to removed derived types from !$OMP; perhaps trying in a CRITICAL construct.

Your approach may have had limited compiler testing so could be more error prone.

I actually don’t see the problem with SHARED derived types, even to update them. There is no real ambiguity about what it is supposed to do, and this is the responsability of the developer to avoid race conditions, as with any other SHARED variable.

But indeed I would be more cautious with [FIRST]PRIVATE derived types… As already mentionned a FIRSTPRIVATE derived type can be misleading if it contains pointer components. And when playing around with gfortran (v12) I have observed that the components of a PRIVATE derived type are not initialized, even though the definition of the type contains initializations. I am not sure if it’s a bug in gfortran or a pitfall in the OpenMP specification.

Moreover, we generally don’t want the complete derived type to be [FIRST]PRIVATE, and the clause applies to all the components.