Ignore:
Timestamp:
Oct 7, 2015 11:56:08 PM (9 years ago)
Author:
knoop
Message:

Code annotations made doxygen readable

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/fft_xy.f90

    r1601 r1682  
    1  MODULE fft_xy
    2 
     1!> @file fft_xy.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    111110! Description:
    112111! ------------
    113 ! Fast Fourier transformation along x and y for 1d domain decomposition along x.
    114 ! Original version: Klaus Ketelsen (May 2002)
     112!> Fast Fourier transformation along x and y for 1d domain decomposition along x.
     113!> Original version: Klaus Ketelsen (May 2002)
    115114!------------------------------------------------------------------------------!
     115 MODULE fft_xy
     116 
    116117
    117118    USE control_parameters,                                                    &
     
    142143    PUBLIC fft_x, fft_x_1d, fft_y, fft_y_1d, fft_init, fft_x_m, fft_y_m
    143144
    144     INTEGER(iwp), DIMENSION(:), ALLOCATABLE, SAVE ::  ifax_x  !:
    145     INTEGER(iwp), DIMENSION(:), ALLOCATABLE, SAVE ::  ifax_y  !:
    146 
    147     LOGICAL, SAVE ::  init_fft = .FALSE.  !:
    148 
    149     REAL(wp), SAVE ::  dnx      !:
    150     REAL(wp), SAVE ::  dny      !:
    151     REAL(wp), SAVE ::  sqr_dnx  !:
    152     REAL(wp), SAVE ::  sqr_dny  !:
     145    INTEGER(iwp), DIMENSION(:), ALLOCATABLE, SAVE ::  ifax_x  !<
     146    INTEGER(iwp), DIMENSION(:), ALLOCATABLE, SAVE ::  ifax_y  !<
     147
     148    LOGICAL, SAVE ::  init_fft = .FALSE.  !<
     149
     150    REAL(wp), SAVE ::  dnx      !<
     151    REAL(wp), SAVE ::  dny      !<
     152    REAL(wp), SAVE ::  sqr_dnx  !<
     153    REAL(wp), SAVE ::  sqr_dny  !<
    153154   
    154     REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trigs_x  !:
    155     REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trigs_y  !:
     155    REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trigs_x  !<
     156    REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trigs_y  !<
    156157
    157158#if defined( __ibm )
    158     INTEGER(iwp), PARAMETER ::  nau1 = 20000  !:
    159     INTEGER(iwp), PARAMETER ::  nau2 = 22000  !:
     159    INTEGER(iwp), PARAMETER ::  nau1 = 20000  !<
     160    INTEGER(iwp), PARAMETER ::  nau2 = 22000  !<
    160161!
    161162!-- The following working arrays contain tables and have to be "save" and
    162163!-- shared in OpenMP sense
    163     REAL(wp), DIMENSION(nau1), SAVE ::  aux1  !:
    164     REAL(wp), DIMENSION(nau1), SAVE ::  auy1  !:
    165     REAL(wp), DIMENSION(nau1), SAVE ::  aux3  !:
    166     REAL(wp), DIMENSION(nau1), SAVE ::  auy3  !:
     164    REAL(wp), DIMENSION(nau1), SAVE ::  aux1  !<
     165    REAL(wp), DIMENSION(nau1), SAVE ::  auy1  !<
     166    REAL(wp), DIMENSION(nau1), SAVE ::  aux3  !<
     167    REAL(wp), DIMENSION(nau1), SAVE ::  auy3  !<
    167168   
    168169#elif defined( __nec )
    169     INTEGER(iwp), SAVE ::  nz1  !:
     170    INTEGER(iwp), SAVE ::  nz1  !<
    170171   
    171     REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trig_xb  !:
    172     REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trig_xf  !:
    173     REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trig_yb  !:
    174     REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trig_yf  !:
     172    REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trig_xb  !<
     173    REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trig_xf  !<
     174    REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trig_yb  !<
     175    REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trig_yf  !<
    175176   
    176177#elif defined( __cuda_fft )
    177     INTEGER(C_INT), SAVE ::  plan_xf  !:
    178     INTEGER(C_INT), SAVE ::  plan_xi  !:
    179     INTEGER(C_INT), SAVE ::  plan_yf  !:
    180     INTEGER(C_INT), SAVE ::  plan_yi  !:
     178    INTEGER(C_INT), SAVE ::  plan_xf  !<
     179    INTEGER(C_INT), SAVE ::  plan_xi  !<
     180    INTEGER(C_INT), SAVE ::  plan_yf  !<
     181    INTEGER(C_INT), SAVE ::  plan_yi  !<
    181182   
    182     INTEGER(iwp), SAVE   ::  total_points_x_transpo  !:
    183     INTEGER(iwp), SAVE   ::  total_points_y_transpo  !:
     183    INTEGER(iwp), SAVE   ::  total_points_x_transpo  !<
     184    INTEGER(iwp), SAVE   ::  total_points_y_transpo  !<
    184185#endif
    185186
    186187#if defined( __fftw )
    187188    INCLUDE  'fftw3.f03'
    188     INTEGER(KIND=C_INT) ::  nx_c  !:
    189     INTEGER(KIND=C_INT) ::  ny_c  !:
     189    INTEGER(KIND=C_INT) ::  nx_c  !<
     190    INTEGER(KIND=C_INT) ::  ny_c  !<
    190191   
    191     COMPLEX(KIND=C_DOUBLE_COMPLEX), DIMENSION(:), ALLOCATABLE, SAVE ::  x_out  !:
     192    COMPLEX(KIND=C_DOUBLE_COMPLEX), DIMENSION(:), ALLOCATABLE, SAVE ::  x_out  !<
    192193    COMPLEX(KIND=C_DOUBLE_COMPLEX), DIMENSION(:), ALLOCATABLE, SAVE ::         &
    193        y_out  !:
     194       y_out  !<
    194195   
    195196    REAL(KIND=C_DOUBLE), DIMENSION(:), ALLOCATABLE, SAVE ::                    &
    196        x_in   !:
     197       x_in   !<
    197198    REAL(KIND=C_DOUBLE), DIMENSION(:), ALLOCATABLE, SAVE ::                    &
    198        y_in   !:
     199       y_in   !<
    199200    !$OMP THREADPRIVATE( x_out, y_out, x_in, y_in )
    200201   
     
    236237
    237238
     239!------------------------------------------------------------------------------!
     240! Description:
     241! ------------
     242!> @todo Missing subroutine description.
     243!------------------------------------------------------------------------------!
    238244    SUBROUTINE fft_init
    239245
     
    246252!--    in OpenMP sense
    247253#if defined( __ibm )
    248        REAL(wp), DIMENSION(0:nx+2) ::  workx  !:
    249        REAL(wp), DIMENSION(0:ny+2) ::  worky  !:
    250        REAL(wp), DIMENSION(nau2)   ::  aux2   !:
    251        REAL(wp), DIMENSION(nau2)   ::  auy2   !:
    252        REAL(wp), DIMENSION(nau2)   ::  aux4   !:
    253        REAL(wp), DIMENSION(nau2)   ::  auy4   !:
     254       REAL(wp), DIMENSION(0:nx+2) ::  workx  !<
     255       REAL(wp), DIMENSION(0:ny+2) ::  worky  !<
     256       REAL(wp), DIMENSION(nau2)   ::  aux2   !<
     257       REAL(wp), DIMENSION(nau2)   ::  auy2   !<
     258       REAL(wp), DIMENSION(nau2)   ::  aux4   !<
     259       REAL(wp), DIMENSION(nau2)   ::  auy4   !<
    254260#elif defined( __nec )
    255        REAL(wp), DIMENSION(0:nx+3,nz+1)   ::  work_x  !:
    256        REAL(wp), DIMENSION(0:ny+3,nz+1)   ::  work_y  !:
    257        REAL(wp), DIMENSION(6*(nx+3),nz+1) ::  workx   !:
    258        REAL(wp), DIMENSION(6*(ny+3),nz+1) ::  worky   !:
     261       REAL(wp), DIMENSION(0:nx+3,nz+1)   ::  work_x  !<
     262       REAL(wp), DIMENSION(0:ny+3,nz+1)   ::  work_y  !<
     263       REAL(wp), DIMENSION(6*(nx+3),nz+1) ::  workx   !<
     264       REAL(wp), DIMENSION(6*(ny+3),nz+1) ::  worky   !<
    259265#endif
    260266
     
    368374
    369375
     376!------------------------------------------------------------------------------!
     377! Description:
     378! ------------
     379!> Fourier-transformation along x-direction.                 
     380!> Version for 2D-decomposition.
     381!> It uses internal algorithms (Singleton or Temperton) or     
     382!> system-specific routines, if they are available           
     383!------------------------------------------------------------------------------!
     384 
    370385    SUBROUTINE fft_x( ar, direction, ar_2d )
    371386
    372 !----------------------------------------------------------------------!
    373 !                                 fft_x                                !
    374 !                                                                      !
    375 !               Fourier-transformation along x-direction               !
    376 !                     Version for 2D-decomposition                     !
    377 !                                                                      !
    378 !      fft_x uses internal algorithms (Singleton or Temperton) or      !
    379 !           system-specific routines, if they are available            !
    380 !----------------------------------------------------------------------!
    381387
    382388       USE cuda_fft_interfaces
     
    387393       IMPLICIT NONE
    388394
    389        CHARACTER (LEN=*) ::  direction  !:
     395       CHARACTER (LEN=*) ::  direction  !<
    390396       
    391        COMPLEX(wp), DIMENSION(:), ALLOCATABLE ::  cwork  !:
    392 
    393        INTEGER(iwp) ::  i          !:
    394        INTEGER(iwp) ::  ishape(1)  !:
    395        INTEGER(iwp) ::  j          !:
    396        INTEGER(iwp) ::  k          !:
    397 
    398        LOGICAL ::  forward_fft !:
     397       COMPLEX(wp), DIMENSION(:), ALLOCATABLE ::  cwork  !<
     398
     399       INTEGER(iwp) ::  i          !<
     400       INTEGER(iwp) ::  ishape(1)  !<
     401       INTEGER(iwp) ::  j          !<
     402       INTEGER(iwp) ::  k          !<
     403
     404       LOGICAL ::  forward_fft !<
    399405       
    400        REAL(wp), DIMENSION(0:nx+2) ::  work   !:
    401        REAL(wp), DIMENSION(nx+2)   ::  work1  !:
     406       REAL(wp), DIMENSION(0:nx+2) ::  work   !<
     407       REAL(wp), DIMENSION(nx+2)   ::  work1  !<
    402408       
    403409#if defined( __ibm )
    404        REAL(wp), DIMENSION(nau2) ::  aux2  !:
    405        REAL(wp), DIMENSION(nau2) ::  aux4  !:
     410       REAL(wp), DIMENSION(nau2) ::  aux2  !<
     411       REAL(wp), DIMENSION(nau2) ::  aux4  !<
    406412#elif defined( __nec )
    407        REAL(wp), DIMENSION(6*(nx+1)) ::  work2  !:
     413       REAL(wp), DIMENSION(6*(nx+1)) ::  work2  !<
    408414#elif defined( __cuda_fft )
    409415       COMPLEX(dp), DIMENSION(0:(nx+1)/2,nys_x:nyn_x,nzb_x:nzt_x) ::           &
    410           ar_tmp  !:
     416          ar_tmp  !<
    411417       ! following does not work for PGI 14.1 -> to be removed later
    412418       ! !$acc declare create( ar_tmp )
     
    414420
    415421       REAL(wp), DIMENSION(0:nx,nys_x:nyn_x), OPTIONAL   ::                    &
    416           ar_2d   !:
     422          ar_2d   !<
    417423       REAL(wp), DIMENSION(0:nx,nys_x:nyn_x,nzb_x:nzt_x) ::                    &
    418           ar      !:
     424          ar      !<
    419425
    420426       IF ( direction == 'forward' )  THEN
     
    781787    END SUBROUTINE fft_x
    782788
     789!------------------------------------------------------------------------------!
     790! Description:
     791! ------------
     792!> Fourier-transformation along x-direction.
     793!> Version for 1D-decomposition.
     794!> It uses internal algorithms (Singleton or Temperton) or
     795!> system-specific routines, if they are available
     796!------------------------------------------------------------------------------!
     797 
    783798    SUBROUTINE fft_x_1d( ar, direction )
    784799
    785 !----------------------------------------------------------------------!
    786 !                               fft_x_1d                               !
    787 !                                                                      !
    788 !               Fourier-transformation along x-direction               !
    789 !                     Version for 1D-decomposition                     !
    790 !                                                                      !
    791 !      fft_x uses internal algorithms (Singleton or Temperton) or      !
    792 !           system-specific routines, if they are available            !
    793 !----------------------------------------------------------------------!
    794800
    795801       IMPLICIT NONE
    796802
    797        CHARACTER (LEN=*) ::  direction  !:
     803       CHARACTER (LEN=*) ::  direction  !<
    798804       
    799        INTEGER(iwp) ::  i               !:
    800        INTEGER(iwp) ::  ishape(1)       !:
    801 
    802        LOGICAL ::  forward_fft          !:
    803 
    804        REAL(wp), DIMENSION(0:nx)   ::  ar     !:
    805        REAL(wp), DIMENSION(0:nx+2) ::  work   !:
    806        REAL(wp), DIMENSION(nx+2)   ::  work1  !:
     805       INTEGER(iwp) ::  i               !<
     806       INTEGER(iwp) ::  ishape(1)       !<
     807
     808       LOGICAL ::  forward_fft          !<
     809
     810       REAL(wp), DIMENSION(0:nx)   ::  ar     !<
     811       REAL(wp), DIMENSION(0:nx+2) ::  work   !<
     812       REAL(wp), DIMENSION(nx+2)   ::  work1  !<
    807813       
    808        COMPLEX(wp), DIMENSION(:), ALLOCATABLE ::  cwork  !:
     814       COMPLEX(wp), DIMENSION(:), ALLOCATABLE ::  cwork  !<
    809815       
    810816#if defined( __ibm )
    811        REAL(wp), DIMENSION(nau2) ::  aux2       !:
    812        REAL(wp), DIMENSION(nau2) ::  aux4       !:
     817       REAL(wp), DIMENSION(nau2) ::  aux2       !<
     818       REAL(wp), DIMENSION(nau2) ::  aux4       !<
    813819#elif defined( __nec )
    814        REAL(wp), DIMENSION(6*(nx+1)) ::  work2  !:
     820       REAL(wp), DIMENSION(6*(nx+1)) ::  work2  !<
    815821#endif
    816822
     
    10011007    END SUBROUTINE fft_x_1d
    10021008
     1009!------------------------------------------------------------------------------!
     1010! Description:
     1011! ------------
     1012!> Fourier-transformation along y-direction.
     1013!> Version for 2D-decomposition.
     1014!> It uses internal algorithms (Singleton or Temperton) or
     1015!> system-specific routines, if they are available.
     1016!>
     1017!> direction:  'forward' or 'backward'
     1018!> ar, ar_tr:  3D data arrays
     1019!>             forward:   ar: before  ar_tr: after transformation
     1020!>             backward:  ar_tr: before  ar: after transfosition
     1021!>
     1022!> In case of non-overlapping transposition/transformation:
     1023!> nxl_y_bound = nxl_y_l = nxl_y
     1024!> nxr_y_bound = nxr_y_l = nxr_y
     1025!>
     1026!> In case of overlapping transposition/transformation
     1027!> - nxl_y_bound  and  nxr_y_bound have the original values of
     1028!>   nxl_y, nxr_y.  ar_tr is dimensioned using these values.
     1029!> - nxl_y_l = nxr_y_r.  ar is dimensioned with these values, so that
     1030!>   transformation is carried out for a 2D-plane only.
     1031!------------------------------------------------------------------------------!
     1032 
    10031033    SUBROUTINE fft_y( ar, direction, ar_tr, nxl_y_bound, nxr_y_bound, nxl_y_l, &
    10041034                      nxr_y_l )
    10051035
    1006 !----------------------------------------------------------------------!
    1007 !                                 fft_y                                !
    1008 !                                                                      !
    1009 !               Fourier-transformation along y-direction               !
    1010 !                     Version for 2D-decomposition                     !
    1011 !                                                                      !
    1012 !      fft_y uses internal algorithms (Singleton or Temperton) or      !
    1013 !           system-specific routines, if they are available            !
    1014 !                                                                      !
    1015 ! direction:  'forward' or 'backward'                                  !
    1016 ! ar, ar_tr:  3D data arrays                                           !
    1017 !             forward:   ar: before  ar_tr: after transformation       !
    1018 !             backward:  ar_tr: before  ar: after transfosition        !
    1019 !                                                                      !
    1020 ! In case of non-overlapping transposition/transformation:             !
    1021 ! nxl_y_bound = nxl_y_l = nxl_y                                        !
    1022 ! nxr_y_bound = nxr_y_l = nxr_y                                        !
    1023 !                                                                      !
    1024 ! In case of overlapping transposition/transformation                  !
    1025 ! - nxl_y_bound  and  nxr_y_bound have the original values of          !
    1026 !   nxl_y, nxr_y.  ar_tr is dimensioned using these values.            !
    1027 ! - nxl_y_l = nxr_y_r.  ar is dimensioned with these values, so that   !
    1028 !   transformation is carried out for a 2D-plane only.                 !
    1029 !----------------------------------------------------------------------!
    10301036
    10311037       USE cuda_fft_interfaces
     
    10361042       IMPLICIT NONE
    10371043
    1038        CHARACTER (LEN=*) ::  direction  !:
     1044       CHARACTER (LEN=*) ::  direction  !<
    10391045       
    1040        INTEGER(iwp) ::  i            !:
    1041        INTEGER(iwp) ::  j            !:
    1042        INTEGER(iwp) ::  jshape(1)    !:
    1043        INTEGER(iwp) ::  k            !:
    1044        INTEGER(iwp) ::  nxl_y_bound  !:
    1045        INTEGER(iwp) ::  nxl_y_l      !:
    1046        INTEGER(iwp) ::  nxr_y_bound  !:
    1047        INTEGER(iwp) ::  nxr_y_l      !:
    1048 
    1049        LOGICAL ::  forward_fft  !:
    1050 
    1051        REAL(wp), DIMENSION(0:ny+2) ::  work   !:
    1052        REAL(wp), DIMENSION(ny+2)   ::  work1  !:
     1046       INTEGER(iwp) ::  i            !<
     1047       INTEGER(iwp) ::  j            !<
     1048       INTEGER(iwp) ::  jshape(1)    !<
     1049       INTEGER(iwp) ::  k            !<
     1050       INTEGER(iwp) ::  nxl_y_bound  !<
     1051       INTEGER(iwp) ::  nxl_y_l      !<
     1052       INTEGER(iwp) ::  nxr_y_bound  !<
     1053       INTEGER(iwp) ::  nxr_y_l      !<
     1054
     1055       LOGICAL ::  forward_fft  !<
     1056
     1057       REAL(wp), DIMENSION(0:ny+2) ::  work   !<
     1058       REAL(wp), DIMENSION(ny+2)   ::  work1  !<
    10531059       
    1054        COMPLEX(wp), DIMENSION(:), ALLOCATABLE ::  cwork  !:
     1060       COMPLEX(wp), DIMENSION(:), ALLOCATABLE ::  cwork  !<
    10551061       
    10561062#if defined( __ibm )
    1057        REAL(wp), DIMENSION(nau2) ::  auy2  !:
    1058        REAL(wp), DIMENSION(nau2) ::  auy4  !:
     1063       REAL(wp), DIMENSION(nau2) ::  auy2  !<
     1064       REAL(wp), DIMENSION(nau2) ::  auy4  !<
    10591065#elif defined( __nec )
    1060        REAL(wp), DIMENSION(6*(ny+1)) ::  work2  !:
     1066       REAL(wp), DIMENSION(6*(ny+1)) ::  work2  !<
    10611067#elif defined( __cuda_fft )
    10621068       COMPLEX(dp), DIMENSION(0:(ny+1)/2,nxl_y:nxr_y,nzb_y:nzt_y) ::           &
    1063           ar_tmp  !:
     1069          ar_tmp  !<
    10641070       ! following does not work for PGI 14.1 -> to be removed later
    10651071       !$acc declare create( ar_tmp )
     
    10671073
    10681074       REAL(wp), DIMENSION(0:ny,nxl_y_l:nxr_y_l,nzb_y:nzt_y)         ::        &
    1069           ar     !:
     1075          ar     !<
    10701076       REAL(wp), DIMENSION(0:ny,nxl_y_bound:nxr_y_bound,nzb_y:nzt_y) ::        &
    1071           ar_tr  !:
     1077          ar_tr  !<
    10721078
    10731079       IF ( direction == 'forward' )  THEN
     
    14071413    END SUBROUTINE fft_y
    14081414
     1415!------------------------------------------------------------------------------!
     1416! Description:
     1417! ------------
     1418!> Fourier-transformation along y-direction.
     1419!> Version for 1D-decomposition.
     1420!> It uses internal algorithms (Singleton or Temperton) or
     1421!> system-specific routines, if they are available.
     1422!------------------------------------------------------------------------------!
     1423 
    14091424    SUBROUTINE fft_y_1d( ar, direction )
    14101425
    1411 !----------------------------------------------------------------------!
    1412 !                               fft_y_1d                               !
    1413 !                                                                      !
    1414 !               Fourier-transformation along y-direction               !
    1415 !                     Version for 1D-decomposition                     !
    1416 !                                                                      !
    1417 !      fft_y uses internal algorithms (Singleton or Temperton) or      !
    1418 !           system-specific routines, if they are available            !
    1419 !----------------------------------------------------------------------!
    14201426
    14211427       IMPLICIT NONE
     
    14231429       CHARACTER (LEN=*) ::  direction
    14241430       
    1425        INTEGER(iwp) ::  j          !:
    1426        INTEGER(iwp) ::  jshape(1)  !:
    1427 
    1428        LOGICAL ::  forward_fft  !:
    1429 
    1430        REAL(wp), DIMENSION(0:ny)    ::  ar     !:
    1431        REAL(wp), DIMENSION(0:ny+2)  ::  work   !:
    1432        REAL(wp), DIMENSION(ny+2)    ::  work1  !:
     1431       INTEGER(iwp) ::  j          !<
     1432       INTEGER(iwp) ::  jshape(1)  !<
     1433
     1434       LOGICAL ::  forward_fft  !<
     1435
     1436       REAL(wp), DIMENSION(0:ny)    ::  ar     !<
     1437       REAL(wp), DIMENSION(0:ny+2)  ::  work   !<
     1438       REAL(wp), DIMENSION(ny+2)    ::  work1  !<
    14331439       
    1434        COMPLEX(wp), DIMENSION(:), ALLOCATABLE ::  cwork  !:
     1440       COMPLEX(wp), DIMENSION(:), ALLOCATABLE ::  cwork  !<
    14351441       
    14361442#if defined( __ibm )
    1437        REAL(wp), DIMENSION(nau2) ::  auy2  !:
    1438        REAL(wp), DIMENSION(nau2) ::  auy4  !:
     1443       REAL(wp), DIMENSION(nau2) ::  auy2  !<
     1444       REAL(wp), DIMENSION(nau2) ::  auy4  !<
    14391445#elif defined( __nec )
    1440        REAL(wp), DIMENSION(6*(ny+1)) ::  work2  !:
     1446       REAL(wp), DIMENSION(6*(ny+1)) ::  work2  !<
    14411447#endif
    14421448
     
    16321638    END SUBROUTINE fft_y_1d
    16331639
     1640!------------------------------------------------------------------------------!
     1641! Description:
     1642! ------------
     1643!> Fourier-transformation along x-direction.
     1644!> Version for 1d domain decomposition
     1645!> using multiple 1D FFT from Math Keisan on NEC or Temperton-algorithm
     1646!> (no singleton-algorithm on NEC because it does not vectorize)
     1647!------------------------------------------------------------------------------!
     1648 
    16341649    SUBROUTINE fft_x_m( ar, direction )
    16351650
    1636 !----------------------------------------------------------------------!
    1637 !                               fft_x_m                                !
    1638 !                                                                      !
    1639 !               Fourier-transformation along x-direction               !
    1640 !                 Version for 1d domain decomposition                  !
    1641 !             using multiple 1D FFT from Math Keisan on NEC            !
    1642 !                       or Temperton-algorithm                         !
    1643 !       (no singleton-algorithm on NEC because it does not vectorize)  !
    1644 !                                                                      !
    1645 !----------------------------------------------------------------------!
    16461651
    16471652       IMPLICIT NONE
    16481653
    1649        CHARACTER (LEN=*) ::  direction  !:
     1654       CHARACTER (LEN=*) ::  direction  !<
    16501655       
    1651        INTEGER(iwp) ::  i     !:
    1652        INTEGER(iwp) ::  k     !:
    1653        INTEGER(iwp) ::  siza  !:
    1654 
    1655        REAL(wp), DIMENSION(0:nx,nz)       ::  ar     !:
    1656        REAL(wp), DIMENSION(0:nx+3,nz+1)   ::  ai     !:
    1657        REAL(wp), DIMENSION(6*(nx+4),nz+1) ::  work1  !:
     1656       INTEGER(iwp) ::  i     !<
     1657       INTEGER(iwp) ::  k     !<
     1658       INTEGER(iwp) ::  siza  !<
     1659
     1660       REAL(wp), DIMENSION(0:nx,nz)       ::  ar     !<
     1661       REAL(wp), DIMENSION(0:nx+3,nz+1)   ::  ai     !<
     1662       REAL(wp), DIMENSION(6*(nx+4),nz+1) ::  work1  !<
    16581663       
    16591664#if defined( __nec )
    1660        INTEGER(iwp) ::  sizw  !:
     1665       INTEGER(iwp) ::  sizw  !<
    16611666       
    1662        COMPLEX(wp), DIMENSION((nx+4)/2+1,nz+1) ::  work  !:
     1667       COMPLEX(wp), DIMENSION((nx+4)/2+1,nz+1) ::  work  !<
    16631668#endif
    16641669
     
    17741779    END SUBROUTINE fft_x_m
    17751780
     1781!------------------------------------------------------------------------------!
     1782! Description:
     1783! ------------
     1784!> Fourier-transformation along y-direction.
     1785!> Version for 1d domain decomposition
     1786!> using multiple 1D FFT from Math Keisan on NEC or Temperton-algorithm
     1787!> (no singleton-algorithm on NEC because it does not vectorize)
     1788!------------------------------------------------------------------------------!
     1789 
    17761790    SUBROUTINE fft_y_m( ar, ny1, direction )
    17771791
    1778 !----------------------------------------------------------------------!
    1779 !                               fft_y_m                                !
    1780 !                                                                      !
    1781 !               Fourier-transformation along y-direction               !
    1782 !                 Version for 1d domain decomposition                  !
    1783 !             using multiple 1D FFT from Math Keisan on NEC            !
    1784 !                       or Temperton-algorithm                         !
    1785 !       (no singleton-algorithm on NEC because it does not vectorize)  !
    1786 !                                                                      !
    1787 !----------------------------------------------------------------------!
    17881792
    17891793       IMPLICIT NONE
    17901794
    1791        CHARACTER (LEN=*) ::  direction  !:
     1795       CHARACTER (LEN=*) ::  direction  !<
    17921796       
    1793        INTEGER(iwp) ::  j     !:
    1794        INTEGER(iwp) ::  k     !:
    1795        INTEGER(iwp) ::  ny1   !:
    1796        INTEGER(iwp) ::  siza  !:
    1797 
    1798        REAL(wp), DIMENSION(0:ny1,nz)      ::  ar     !:
    1799        REAL(wp), DIMENSION(0:ny+3,nz+1)   ::  ai     !:
    1800        REAL(wp), DIMENSION(6*(ny+4),nz+1) ::  work1  !:
     1797       INTEGER(iwp) ::  j     !<
     1798       INTEGER(iwp) ::  k     !<
     1799       INTEGER(iwp) ::  ny1   !<
     1800       INTEGER(iwp) ::  siza  !<
     1801
     1802       REAL(wp), DIMENSION(0:ny1,nz)      ::  ar     !<
     1803       REAL(wp), DIMENSION(0:ny+3,nz+1)   ::  ai     !<
     1804       REAL(wp), DIMENSION(6*(ny+4),nz+1) ::  work1  !<
    18011805       
    18021806#if defined( __nec )
    1803        INTEGER(iwp) ::  sizw  !:
     1807       INTEGER(iwp) ::  sizw  !<
    18041808       
    1805        COMPLEX(wp), DIMENSION((ny+4)/2+1,nz+1) ::  work !:
     1809       COMPLEX(wp), DIMENSION((ny+4)/2+1,nz+1) ::  work !<
    18061810#endif
    18071811
Note: See TracChangeset for help on using the changeset viewer.