Advises about best data structure for mult-iblock structured grid (meshes, CFD))

Hello Everyone,
I’m trying to develop a multi-block structured mesher. Leaving out details, the important things are:

  • A space domain is divided into quadrilateral blocks

  • Some blocks have obvioulsy neighbours blocks

  • Every block is substantially a matrix, in the sense that it stores points in a structured manner.

  • Points are stored in the matrix-block in a way that preserves their order, but their orientation relative to the matrix indexes is random. For example, considering a line, the points x1=0 and x2=1 can be stored like this [0,1], like this [1,0], like this \begin{bmatrix}1\\ 0 \end{bmatrix}or this\begin{bmatrix}0\\ 1 \end{bmatrix}`.

  • When some routines must operate some inter-blocks operation, it is essential to extract points between two blocks and so knowing how they can be extracted coherently with their position relative to the matrix indexes.
    I’m trying to use Fortran OOP features and this is a prototype of the class block (representing a block of a multi-block structure):

MODULE STRUCT_BLOCK_OF_MULTIBLOCK_CLASS

!-----------------------------------------------------------------------
!#######################################################################
! 
! 
!
!#######################################################################
! THIS MODULE DEFINE THE CLASS STRUC_BLOCK_OF_MULTIBLOCK WHICH MODELS A STRUCTURED
! GRID, BEING PART OF MULTIBLOCK GRID. A STRUCTURED BLOCK IS A 1TO1 CORRESPONDENCE
! BETWEEN POINTS IN SPACE AND A MATRIX AND CAN HAVE NEIGHBOURS BLOCKS.
!-----------------------------------------------------------------------

      IMPLICIT NONE
     
      TYPE, PUBLIC :: STRUCT_BLOCK_OF_MULTIBLOCK

      PRIVATE

      INTEGER :: NI,NJ ! structured grid first and second dimensions

      TYPE(INTEGER), DIMENSION(4) ::   NEIGHBOURS_IDS ! neighbours block's ids

      REAL, ALLOCATABLE, DIMENSION(:,:) :: X_BLOCK, Y_BLOCK ! the actual points stored in the block

      CONTAINS

      PROCEDURE, PUBLIC :: CREATE_TFI_BLOCK_QUADRLT => CREATE_TFI_BLOCK_QUADRLT_FN
      PROCEDURE, PUBLIC :: PLOT_STRUCT_BLOCK     => PLOT_STRUCT_BLOCK_FN
      PROCEDURE, PUBLIC :: WRITE_STRUCT_BLOCK    => WRITE_STRUCT_BLOCK_FN
      PROCEDURE, PUBLIC :: SET_SIDE_AND_DIM      => SET_SIDE_AND_DIM_FN


      END TYPE STRUCT_BLOCK_OF_MULTIBLOCK

      PRIVATE :: CREATE_TFI_BLOCK_QUADRLT_FN , PLOT_STRUCT_BLOCK_FN , WRITE_STRUCT_BLOCK_FN ,SET_SIDE_AND_DIM_FN

      CONTAINS ..

So I’m asking advises on

  • Is this Fortran code any good? Any idea to improve or to write in a different way a class in Fortran?
  • Can someone point me on algorithms, books, papers, code or give me advices for how to handle the block connectivity and points position problem?

Thank you very much in advance for your time and patience

I few advanced resources I can suggest are:

  • AFIVO (check the “Relevant publications” section)
  • octree-mg
  • AMReX (this is a C++ code but has a Fortran interface)

With respect to your code, do you want to store the coordinates of the points in a structured grid block?

In general you can think of a structured mesh as an implicit data structure. If you know the size of the quadrilateral block (in physical coordinates), the number of grid points in each dimension, and the step sizes - you can reconstruct the true (x,y)-coordinates of the vertexes on the fly (e.g. during I/O operations).

If you plan to do something like finite-differences in each block, you only need the step sizes.

Thank you for your reply. My fault, let me explain better.
Every block is representative of a quadrilateral with arbitrarily shaped sides and the entire domain being meshed is arbitrarily shaped, i.e. can have holes.
The complete mesh is generally composed by a big amount of blocks and every block covers a region of the domain.
This is an example of what such a mesh can looks like :
https://imgur.com/mOWdoBN

Thanks for the given links, but the type of meshes they deal with is not related to my problem.

1 Like

I’m no expert on structured multiblock, however I think there is some additional information required for your code structure. In addition to specifying the neighbouring blocks (NEIGHBOURS_IDS) you also need to specify which face of the neighbour you are connecting to (e.g. imin/imax/jmin/jmax planes) and you also need to specify the orientation of the neighbouring face. In 2D there are two possible orientations (e.g. up/down). In 3D there are eight possible orientations. You may find this paper useful.

1 Like

Thanks, you made the problem very clear. I was thinking to add a class variable (array of integers from 1 to 4) for representing which side of a neighbour is shared with that particular side of the block and to create a convention, i.e. 1 stays for [:,1], 2 stays for [1,:] and so on. The tricky question is the orientation, not just representing it with data, but in the specific, how to find if two sides, representing the same points, are stored in reverse order in two different blocks ? Thanks for the link, I read that chapters years ago, maybe its time to read it another time more carefully.
What about Fortran code ? Do you suggest some best practice to write or handle such a data structure?
Thanks

Would a simple dot product test of element normals be sufficient perhaps? e.g. take the dot product between the normal vectors of the first element on each block face and check if the sign is positive or negative?

Apologies I won’t be able to help much with this; it’s hard to make more comments on the code without a better understanding of how it will be used. The proposed data structure looks fine to me in general. The separation of the x and y coordinates into different arrays is probably a good idea IMO for performance since structured grids should be able to exploit vectorization well. Perhaps others here may have more experience with structured grid algorithms and be able to provide guidance.

I have some previous experience with axis-aligned quadtree grids, so my answer was biased.

The Snas3D solver from Jiri Blazek, author of the book Computational Fluid Dynamics: Principles and Applications, utilizes such block-structured grids composed of arbitrarily shaped quadrilaterals. The companion website of the book contains some Fortran codes for grid generation, but I don’t know if the codes are object-oriented or not. Still you might find something useful.

@lkedward
I read the chapter you linked but sadly it gives no information on how to understand if a face need to be reoriented.

Would a simple dot product test of element normals be sufficient perhaps? e.g. take the dot product between the normal vectors of the first element on each block face and check if the sign is positive or negative?

Could you elaborate please ? I was actually implementing a method who tries to match faces rotating them and minimizing distances between their associated vertexes, but there must be some better algorithm that is not concerned with geometry but with data structure, like saving IDs integers of faces vertexes and comparing them. Maybe.
I just don’t want to reinvent the wheel, I’d like to use proved and trusted algorithms.

The proposed data structure looks fine to me in general. The separation of the x and y coordinates into different arrays is probably a good idea IMO for performance since structured grids should be able to exploit vectorization well.

Thanks your comment is appreciated, I’m not experienced with Fortran OOP, so for now it’s enough if there is not any bad practice pattern.
@ivanpribec
Thanks for the links, I was aware of the book and of the software, but there is nothing in them about multi-block structured grids. Only structured or unstructured with triangles. However, again, thanks.

@Rob777 ,

As alluded to by your line of inquiry above, this is a site for discourse on Fortran-related matters and as such, it’s with Fortran you can expect most relevant discussion. And any advice on numerical aspects or the CFD domain-related topics will be added bonus.

But now with your Fortran code, as pointed out to you upthread, the snippet you show appears too short to be able to provide you any meaningful feedback. If you’re keen on advice on the Fortran code, a suggestion will be to put together a minimal working example (MWE) that mimics the code design you’ve in mind and put it up some place online (GitHub?) where interested readers can review.

I personally think a great example of how to put together such an MWE is in section 10.2 Case Study: Solving a Heat Transfer Problem in the book Guide to Fortran 2003 Programming by W. S. Brainerd (2009). Shown below is a partial snip of this section. The author here approaches that problem using a simple array of RANK 2 and with variables of POINTER attribute. That may or may not be applicable to you. But the important aspect though is how the case and the code are described and how the code is short and sweet and can be tried using various compliers. Pursuing a similar approach with an MWE (or perhaps even two MWEs - one with OO approach and one without OO) with your CFD problem and sharing it can help you greatly.

You’re right the main matter of discussion must be Fortran. Unfortunately, I don’t have idea how to provide a MWE of a Multiblock structured mesher, it’s a little complicated code. I’m thinking of uploading (it’s time to learn git) some complete class definitions with explanations. We’ll see later.

Hello,
You can check:

Applied Computational Fluid Dynamics Techniques: An Introduction Based on Finite Element Methods, 2nd Edition

Rainald Löhner

Code snippets are in Fortran.

Regards,
JW

1 Like

Welcome to the Fortran community! I think this book can have only code related to triangles, however, seems a great lecture, thanks!