[QE-developers] Fwd: q-e | Syntax rules in QE (#143)
Andrea Ferretti
andrea.ferretti at nano.cnr.it
Tue Oct 1 11:22:00 CEST 2019
Hi All,
a few points from my side (not sure I am the most entitled here):
* shall we really keep fortran keywords capitalized ?
I have the impression that with syntax highlighting it may no longer be
needed
* concerning variable delclaration, I would tend to keep things short
real(DP) instead of real(KIND = DP)
(just a matter of taste)
* very good to have a code beautification tool
take care
Andrea
> Any opinions? Paolo
>
> ---------- Forwarded message ---------
> From: Samuel Poncé <gitlab at mg.gitlab.com>
> Date: Mon, Sep 23, 2019 at 5:22 PM
> Subject: q-e | Syntax rules in QE (#143)
> To: <p.giannozzi at gmail.com>
>
>
> Samuel Poncé created an issue:
>
> Dear QE developers,
>
> After carefully thinking about a general syntax rules for the code, trying to make them as consistent with each other as possible, I propose
> the following rules:
>
> Pre-processing
>
> * Preprocessing options should be capitalized and start with two underscores. Examples:__MPI, __LINUX, ...
> * Use preprocessing syntax#if defined (XXX), not #if defined XXX or #ifdef XXX
>
> Common style
>
> * Fortran commands should be capitalized: CALL something(XXX)
> * Variable names should be lowercase: foo = bar/2
> * Use (KIND = DP) (defined in module kinds) to define the type of real and complex variables
>
> Order of declaration
>
> * The recommanded order is as follow:
>
> CHARACTER(LEN = 256) :: var
>
> LOGICAL :: var
>
> LOGICAL, ALLOCATED :: var(:)
>
> INTEGER :: var
>
> INTEGER, ALLOCATED :: var(:)
>
> REAL(KIND = DP) :: var
>
> REAL(KIND = DP), ALLOCATED :: var(:)
>
> COMPLEX(KIND = DP) :: var
>
> COMPLEX(KIND = DP), ALLOCATED :: var(:)
> * First all INTENT variables are declared (in that order) and then all the local variables are declared (in that order).
> * Note: Do not use DIMENSION(:)
>
> Typical header of subroutines
>
> !------------------------------------------------------------------------
>
> SUBROUTINE name(arg1, arg2)
>
> !------------------------------------------------------------------------
>
> !!
>
> !! Description of subroutine
>
> !!
>
> !------------------------------------------------------------------------
>
> USE kinds, ONLY : DP
>
> USE cell_base, ONLY : at, bg, alat
>
> !
>
> IMPLICIT NONE
>
> !
>
> ! input variables
>
> !
>
> INTEGER, INTENT(in) :: arg1
>
> !! Description
>
> REAL(KIND = DP), INTENT(in) :: arg2(3, 5)
>
> !! Description
>
> !
>
> ! Local variables
>
> !
>
> INTEGER :: ik
>
> !! Description
>
>
>
> !------------------------------------------------------------------------
>
> END SUBROUTINE name
>
> !------------------------------------------------------------------------
>
> Indentation
>
> * Use two spaces for indentation
>
> DO ik = 1, nkf
>
> DO imode = 1, nmodes
>
> code
>
> ENDDO
>
> ENDDO
>
> Spaces
>
> * Leave one space after a comma "," and between "multiple conditions" in a IF statement
>
> IF (cond) THEN
>
> CALL name(arg1, arg2, arg3)
>
> ENDIF
>
> ALLOCATE(var1(dim1, dim2), STAT = ierr)
>
> IF (ierr /= 0) CALL io_error('Error allocating var1 in subroutine_name')
>
>
>
> DO ik = 1, nkf
>
> ikk = 2 * ik - 1
>
> ikq = 2 * ik
>
> IF ((MINVAL(ABS(var1(:, ikk) - ef)) < fsthick) .AND. (MINVAL(ABS(var1(:, ikq) - ef)) < fsthick)) THEN
>
> ENDDO
>
>
>
> DEALLOCATE(var1, STAT = ierr)
>
> IF (ierr /= 0) CALL io_error('Error deallocating var1 in subroutine_name')
>
> Allocating and deallocating arrays
>
> * Check the status once an array is allocated or deallocated
>
> ALLOCATE(var1(dim1, dim2), STAT = ierr)
>
> IF (ierr /= 0) CALL errore('subroutine_name', 'Error allocating var1', 1)
>
>
>
> DEALLOCATE(var1, STAT = ierr)
>
> IF (ierr /= 0) CALL errore('subroutine_name', 'Error deallocating var1', 1)
>
> Reading and writing files
>
> * Leave one space after a comma "," and after a statement
>
> OPEN(UNIT = file_unit, FILE = 'file_name', STATUS = 'old', FORMAT = 'formatted', IOSTAT = ios)
>
> IF (ios /= 0) CALL errore('subroutine', 'error opening file_name', iunit_name)
>
> READ(file_unit) index
>
> CLOSE(file_unit)
>
>
>
> OPEN(UNIT = file_unit, FILE = 'file_name', STATUS = 'old', FORMAT = 'formatted', IOSTAT = ios)
>
> IF (ios /= 0) CALL errore('subroutine', 'error opening file_name', iunit_name)
>
> WRITE(file_unit, '(i7)') index
>
> CLOSE(file_unit)
>
> Intrinsic functions
>
> * Use capital letters when calling an intrinsic function or logical:
>
> a = MATMUL(c, d)
>
> c = TRANSPOSE(DBLE(e))
>
> f = .TRUE.
>
> Relational operator
>
> * Use modern relational operators:
>
> > instead of .gt.
>
> < instead of .lt.
>
> == instead of .eq.
>
> /= instead of .neq.
>
> Mathematical operator
>
> * Use one space between mathematical operators
>
> a = b + i
>
> c = c / SQRT(s)
>
> Spaces in the code
>
> * Avoid white space in the code. When a space is need, add a comment (!) that follows the indentation:
>
> !
>
> a = b
>
> !
>
> DO i = 1, n
>
> !
>
> y = a + c
>
> ENDDO
>
> Conditional allocation
>
> * Do NOT use: IF (.NOT. ALLOCATED(var)) ALLOCATE(var(dim1))
> * Do use:
>
> ALLOCATE(var1(dim1, dim2), STAT = ierr)
>
> IF (ierr /= 0) CALL errore('subroutine_name', 'Error allocating var1', 1)
>
> Indeed conditional allocations create potential memory leaks and can always be avoided.
>
> Good practice
>
> * Conversions should be explicitly indicated. For conversions to real, use DBLE, or else REAL(..., KIND = DP). For conversions to complex,
> use CMPLX(...,...,KIND = DP). For complex conjugate, use CONJG. For imaginary part, use AIMAG.
> * Do not use REAL or CMPLX without KIND = DP, or else you will lose precision (except when you take the real part of a double precision
> complex number).
> * Do not use automatic arrays (e.g. REAL(KIND = DP) :: A(N) with N defined at run time) unless you are sure that the array is small in all
> cases: large arrays may easily exceed the stack size, or the memory size.
> * Do not use pointers unless you have a good reason to: pointers may hinder optimization. Allocatable arrays should be used instead.
> * If you use pointers, nullify them before performing tests on their status.
> * Be careful with F90 array syntax and in particular with array sections. Passing an array section to a routine may look elegant but it may
> turn out to be inefficient: a copy will be silently done if the section is not contiguous in memory (or if the compiler decides it is the
> right thing to do), increasing the memory footprint.
> * Do not pass unallocated arrays as arguments, even in those cases where they are not actually used inside the subroutine: some compilers
> don't like it.
> * Always use IMPLICIT NONE and declare all local variables. All variables passed as arguments to a routine should be declared as
> INTENT(in), (out) , or (inout). All variables from modules should be explicitly specified via USE module, ONLY : variable. Variables used
> in an array declaration must be declared first, as in the following example:
>
> INTEGER, INTENT(in) :: N
>
> REAL(KIND = DP), INTENT(out) :: A(N)
>
> in this order (some compilers complain if you put the second line before the first).
>
> —
> Reply to this email directly or view it on GitLab.
> You're receiving this email because of your account on gitlab.com. If you'd like to receive fewer emails, you can unsubscribe from this
> thread or adjust your notification settings.
>
>
>
> --
> Paolo Giannozzi, Dip. Scienze Matematiche Informatiche e Fisiche,
> Univ. Udine, via delle Scienze 208, 33100 Udine, Italy
> Phone +39-0432-558216, fax +39-0432-558222
>
>
>
--
Andrea Ferretti, PhD
S3 Center, Istituto Nanoscienze, CNR
via Campi 213/A, 41125, Modena, Italy
Tel: +39 059 2055322; Skype: andrea_ferretti
URL: http://www.nano.cnr.it
More information about the developers
mailing list