source: LMDZ6/branches/Amaury_dev/libf/filtrez/lmdz_fft_wrapper.f90

Last change on this file was 5160, checked in by abarral, 7 weeks ago

Put .h into modules

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 1.2 KB
RevLine 
[5107]1MODULE lmdz_fft_wrapper
[5120]2  IMPLICIT NONE; PRIVATE
3  PUBLIC vsize, inc, init_fft, fft_forward, fft_backward
[986]4
5  INTEGER,SAVE             :: vsize
6  INTEGER,PARAMETER        :: inc=1
7
8CONTAINS
9 
[5120]10  SUBROUTINE init_fft(iim,nb)
[986]11  IMPLICIT NONE
12    INTEGER :: iim
13    INTEGER :: nb
14   
[5160]15    PRINT *, "wrapper fft : une FFT doit etre specifiee a l'aide d'une clee CPP, sinon utiliser le filtre classique"
[4456]16    stop 1
[5120]17  END SUBROUTINE init_fft
[986]18 
19 
20  SUBROUTINE fft_forward(vect,TF_vect,nb_vect)
21    IMPLICIT NONE
22    INTEGER,INTENT(IN)  :: nb_vect
23    REAL,INTENT(IN)     :: vect(vsize+inc,nb_vect)
[1403]24    COMPLEX,INTENT(INOUT) :: TF_vect(vsize/2+1,nb_vect)
[986]25   
[5160]26    PRINT *, "wrapper fft : une FFT doit etre specifiee a l'aide d'une clee CPP, sinon utiliser le filtre classique"
[4456]27    stop 1
[986]28   
29  END SUBROUTINE fft_forward
30 
31  SUBROUTINE fft_backward(TF_vect,vect,nb_vect)
32    IMPLICIT NONE
33    INTEGER,INTENT(IN)  :: nb_vect
34    REAL,INTENT(INOUT)    :: vect(vsize+inc,nb_vect)
[1403]35    COMPLEX,INTENT(IN ) :: TF_vect(vsize/2+1,nb_vect)
[986]36 
[5160]37    PRINT *, "wrapper fft : une FFT doit etre specifiee a l'aide d'une clee CPP, sinon utiliser le filtre classique"
[4456]38    stop 1
[986]39   
40  END SUBROUTINE fft_backward
41 
[5107]42END MODULE lmdz_fft_wrapper
Note: See TracBrowser for help on using the repository browser.