chore: append dev to version number after release (#1509)
[FMS.git] / CODE_STYLE.md
blobf5c949fedc165a888990f17dabf031cbb309a4bb
1 # Coding Style
3 ## General
5 * Trim all trailing whitespace from every line (some editors can do this
6   automatically).
7 * No <Tab> characters.
8 * Supply a header for each file with a description of the file and the author(s)
9   name or GitHub ID.
10 * A copy of the [Gnu Lesser General Public License](https://www.gnu.org/licenses/lgpl-3.0.en.html)
11   must be included at the top of each file.
12 * Documentation should be written so that it can be parsed by [Doxygen](http://www.doxygen.nl/).
13 * All variables should be defined, and include units. Unit-less variables should be marked `unitless`
14 * Provide detailed descriptions of modules, interfaces, functions, and subroutines
15 * Define all function/subroutine arguments, and function results (see below)
16 * Follow coding style of the current file, as much as possible.
18 ## Fortran
20 ### General
22 * Use Fortran 95 standard or newer
23 * Two space indentation
24 * Use `KIND` parameters from platform_mod
25 * Never use implicit variables (i.e., always specify `IMPLICIT NONE`)
26 * Lines must be <= 120 characters long (including comments)
27 * logical, compound logical, and relational if statements may be one line,
28   using “&” for line continuation if necessary:
29   ```Fortran
30   if(file_exists(fileName)) call open_file(fileObj,fileName, is_restart=.false)
31   ```
32 * Avoid the use of `GOTO` statements
33 * Avoid the use of Fortran reserved words as variables (e.g. `DATA`, `NAME`)
34 * Avoid the use of `COMMON` blocks
36 ### Derived types
38 * Type names must be in CapitalWord format.
39 * Variables names must be in underscore_word format.
40 * All member variables must be private.
41 * Doxygen description on the line before the type definition.
42 * Inline doxygen descriptions for all member variables.
44 ## Functions
45 * If a function has a result variable, it should be declared on its own line,
46   and the variable should not be declared with a specific intent.
47 * Inline doxygen descriptions for all arguments, except the result variable.
48 * Doxygen description on the line(s) before the function definition.  This must
49   specify what the function is returning using the `@return` doxygen keyword.
51 ## Blocks
52 * terminate `do` loops with `enddo`
53 * terminate block `if`, `then` statements with `endif`
55 ## OpenMP
57 * Directives should start at the beginning of the line, and be in lowercase.
58 * All openMP directives should specify default(none), and then explicitly list
59   all shared and private variables.
60 * All critical sections must have a unique name.
62 ## Precision
63 * Precision of all real arguments are explicitly defined as `real(kind=r4_kind)`,
64   `real(kind=r8_kind)`, or as any other precision parameters defined in platform_mod.
65 * The precision of real numerical values should be consistent with the precision
66   of the associated variable.  For example, if the variable `a` has been declared
67   as r8_kind, then `a=1.4_r8_kind` is acceptable. The following, a=1.4 and a=(1.4,kind=r8_kind),
68   are not acceptable since the numerical value of 1.4 will be represented in the default precision
69   set by the compiler.
70 * The precision of integers do not need to be explicitly defined and can be determined at compile time.
71 * If the precision of integers are explicitly defined, they are defined with the precision parameters,
72   _e.g._ i4_kind, i8_kind, found in platform_mod.
74 ## Macros
75 * All letters in the macro names are capitalized
76 * All macro names end with an underscore "_"
77 * All precision related macro names start with the letters "FMS"
78 * Macro names should be unique to each module.  For example,
79   `FMS_AU_KIND_` is used in axis_utils_mod.
80   `FMS_HI_KIND_` is used in horiz_interp_mod
82 ## .fh and .inc files
83 * The .fh header files contain macro definitions.
84 * If the .fh files contain mainly precision related macro definitions, the files
85   should be named with `_r4.fh` and `_r8.fh` extensions in the include subdirectory found
86   in the module directory.  These .fh files are `#include`-ed at the end of the .F90 module files.
87 * For precision related .inc files, the .inc files contain the procedure definitions and are
88   `#include`-ed at the end of both *_r4.fh and *_f8.fh files.  These .inc files are located in the
89   same include subdirectory as the .fh files.  See below for details.
90 ## Fortran Example
92 ```Fortran ./example.F90 file
94 !***********************************************************************
95 !*                   GNU Lesser General Public License
97 !* This file is part of the GFDL Flexible Modeling System (FMS).
99 !* FMS is free software: you can redistribute it and/or modify it under
100 !* the terms of the GNU Lesser General Public License as published by
101 !* the Free Software Foundation, either version 3 of the License, or (at
102 !* your option) any later version.
104 !* FMS is distributed in the hope that it will be useful, but WITHOUT
105 !* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
106 !* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
107 !* for more details.
109 !* You should have received a copy of the GNU Lesser General Public
110 !* License along with FMS.  If not, see <http://www.gnu.org/licenses/>.
111 !***********************************************************************
113 !> @file
114 !! @brief Example code
115 !! @author <developer>
116 !! @email gfdl.climate.model.info@noaa.gov
118 module example_mod
119   use platform_mod, only r4_kind, r8_kind, i4_kind, i8_kind
120   use util_mod, only: util_func1
121   implicit none
122   private
124   public :: sub1
125   public :: func1
126   public :: ex_subroutine
128   interface ex_subroutine             !< generic interface block.  When the user
129     module procedure ex_subroutine_r4 !! calls ex_subroutine, the compiler checks
130     module procedure ex_subroutine_r8 !! the input arguments and invokes either
131   end interface ex_subroutine         !! ex_subroutine_r4 or ex_subroutine_r8
132                                       !! ex_subroutine_r4/8 are generated by the preprocessor
133                                       !! which requires example_r4.fh, example_r8.fh, and
134                                       !! example.inc files
136   !> @brief Doxygen description of type.
137   type,public :: CustomType
138     private
139     integer(kind=i4_kind) :: a_var !< Inline doxygen description.
140     real(kind=r8_kind),dimension(:),allocatable :: b_arr !< long description
141                                                          !! continued on
142                                                          !! multiple lines.
143   endtype CustomType
145   contains
147   !> @brief Doxygen description.
148   subroutine sub1(arg1, arg2, &
149     & arg3)
150     real(kind=r4_kind),intent(in) :: arg1 !< Inline doxygen description.
151     integer(kind=i8_kind),intent(inout) :: arg2 !< Inline doxygen description.
152     character(len=*),intent(inout) :: arg3 !< Long inline doxygen
153                                            !! description.
155     arg1=2.456_r4_kind
156   end subroutine sub1
158   !> @brief Doxygen description
159   !! @return Function return value.
160   function func1(arg1, arg2) result(res)
161     integer(kind=i4_kind),intent(in) :: arg1 !< Inline doxygen description
162     integer(kind=i4_kind),intent(in) :: arg2 !< Inline doxygen description
163     integer(kind=r8_kind) :: res
165     res=real(arg1,r8_kind) * 3.14_r8_kind
166   end function func1
168 #include "example_r4.fh" !< These two header file contains the macro definition
169 #include "example_r8.fh" !! and an "#include example.inc" where the procedure
170                          !! is defined.  See below.
171 end module example_mod
173 ```Fortran ./include/example_r4.fh file
174 !***********************************************************************
175 !*                   GNU Lesser General Public License
177 !* This file is part of the GFDL Flexible Modeling System (FMS).
179 !* FMS is free software: you can redistribute it and/or modify it under
180 !* the terms of the GNU Lesser General Public License as published by
181 !* the Free Software Foundation, either version 3 of the License, or (at
182 !* your option) any later version.
184 !* FMS is distributed in the hope that it will be useful, but WITHOUT
185 !* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
186 !* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
187 !* for more details.
189 !* You should have received a copy of the GNU Lesser General Public
190 !* License along with FMS.  If not, see <http://www.gnu.org/licenses/>.
191 !***********************************************************************
193 !> @file
194 !! @brief Example _r4.fh file containing macro definitions
195 !! @author <developer>
196 !! @email gfdl.climate.model.info@noaa.gov
198 #undef   FMS_EX_KIND_
199 #define  FMS_EX_KIND_ r4_kind
201 #undef  EX_SUBROUTINE_
202 #define EX_SUBROUTINE_ ex_subroutine_r4
204 #include "example.inc" !< example.inc file contains the procedure definition
206 ```Fortran ./include/example_r8.fh file
207 !***********************************************************************
208 !*                   GNU Lesser General Public License
210 !* This file is part of the GFDL Flexible Modeling System (FMS).
212 !* FMS is free software: you can redistribute it and/or modify it under
213 !* the terms of the GNU Lesser General Public License as published by
214 !* the Free Software Foundation, either version 3 of the License, or (at
215 !* your option) any later version.
217 !* FMS is distributed in the hope that it will be useful, but WITHOUT
218 !* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
219 !* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
220 !* for more details.
222 !* You should have received a copy of the GNU Lesser General Public
223 !* License along with FMS.  If not, see <http://www.gnu.org/licenses/>.
224 !***********************************************************************
226 !> @file
227 !! @brief Example file _r8.fh file containing macro definitions
228 !! @author <developer>
229 !! @email gfdl.climate.model.info@noaa.gov
231 #undef   FMS_EX_KIND_
232 #define  FMS_EX_KIND_ r8_kind
234 #undef  EX_SUBROUTINE_
235 #define EX_SUBROUTINE_ ex_subroutine_r8
237 #include "example.inc" !< example.inc file contains the procedure definition
239 ``` Fortran ./include/example.inc file
240 !***********************************************************************
241 !*                   GNU Lesser General Public License
243 !* This file is part of the GFDL Flexible Modeling System (FMS).
245 !* FMS is free software: you can redistribute it and/or modify it under
246 !* the terms of the GNU Lesser General Public License as published by
247 !* the Free Software Foundation, either version 3 of the License, or (at
248 !* your option) any later version.
250 !* FMS is distributed in the hope that it will be useful, but WITHOUT
251 !* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
252 !* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
253 !* for more details.
255 !* You should have received a copy of the GNU Lesser General Public
256 !* License along with FMS.  If not, see <http://www.gnu.org/licenses/>.
257 !***********************************************************************
258 !> @file
259 !! @brief Example .inc file containing subroutine definitions/declarations
260 !! @author <developer>
261 !! @email gfdl.climate.model.info@noaa.gov
263 !> The macro EX_SUBROUTINE_ gets replaced by the preprocessor
264 !! as ex_subroutine_r4 (as defined in the example_r4.fh file) and
265 !! as ex_subroutine r8 (as defined in the example_r8.fh file)
267 subroutine EX_SUBROUTINE_(arg1, arg2, arg3)
268   real(FMS_EX_KIND_), intent(in)  :: arg2 !< FMS_EX_KIND_ gets replaced by the preprocessor
269   real(FMS_EX_KIND_), intent(out) :: arg1 !< FMS_EX_KIND_ gets replaced by the preprocessor
270   integer(i4_kind) :: arg3
271   integer, parameter :: lkind=FMS_EX_KIND_ !< kind parameter local to the subroutine
273   arg1 = arg2 / 4.0_lkind !< GCC does not like 4.0_FMS_EX_KIND_.  Thus, the
274                           !! parameter lkind is declared and used.
276 end subroutine EX_SUBROUTINE_
279 ## C/C++
281 ### General
282 * C code is written in GNU style.  Each new level in a program block is indented
283   by 2 spaces. Braces start on a new line, and are also indented by 2 spaces.
284 * See the [Gnome C coding style guide](https://developer.gnome.org/programming-guidelines/stable/c-coding-style.html.en)
285   for more information