New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 6225 for branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/TOOLS/SIREN/src/filter.f90 – NEMO

Ignore:
Timestamp:
2016-01-08T10:35:19+01:00 (8 years ago)
Author:
jamesharle
Message:

Update MPP_BDY_UPDATE branch to be consistent with head of trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/TOOLS/SIREN/src/filter.f90

    r4213 r6225  
    66! 
    77! DESCRIPTION: 
    8 !> @brief filter manager <br/> 
     8!> @brief This module is filter manager. 
    99!> 
    10 !> @details 
     10!> @details Filtering method to be used is specify inside variable strcuture, 
     11!>    as array of string character.<br/> 
     12!>    td_var\%c_filter(1) string character is the filter name choose between:<br/> 
     13!>       - 'hann' 
     14!>          - rad < cutoff : @f$ filter=0.5+0.5*COS(\pi*\frac{rad}{cutoff}) @f$ 
     15!>          - rad > cutoff : @f$ filter=0 @f$ 
     16!>       - 'hamming' 
     17!>          - rad < cutoff : @f$ filter=0.54+0.46*COS(\pi*\frac{rad}{cutoff}) @f$ 
     18!>          - rad > cutoff : @f$ filter=0 @f$                
     19!>       - 'blackman' 
     20!>          - rad < cutoff : @f$ filter=0.42 + 0.5*COS(\pi*\frac{rad}{cutoff}) +  
     21!>                                      0.08*COS(2\pi*\frac{rad}{cutoff}) @f$ 
     22!>          - rad > cutoff : @f$ filter=0 @f$ 
     23!>       - 'gauss' 
     24!>          - @f$filter=exp(-(\alpha * rad^2) / (2*cutoff^2))@f$ 
     25!>       - 'butterworth' 
     26!>          - @f$ filer=1 / (1+(rad^2 / cutoff^2)^{\alpha}) @f$ 
     27!>             . 
     28!> 
     29!>       with @f$ rad= \sqrt{(dist-radius)^2} @f$ 
     30!> 
     31!>    td_var\%c_filter(2) string character is the number of turn to be done<br/> 
     32!>    td_var\%c_filter(3) string character is the cut-off frequency  
     33! >                       (count in number of mesh grid)<br/> 
     34!>    td_var\%c_filter(4) string character is the halo radius  
     35!>                        (count in number of mesh grid)<br/> 
     36!>    td_var\%c_filter(5) string character is the alpha parameter  
     37!>                        (for gauss and butterworth method)<br/> 
     38!>     
     39!>    @note Filter method could be specify for each variable in namelist _namvar_, 
     40!>    defining string character _cn\_varinfo_. None by default.<br/> 
     41!>    Filter method parameters are informed inside bracket. 
     42!>       - @f$\alpha@f$ parameter is added for _gauss_ and _butterworth_ methods 
    1143!>  
     44!>    The number of turn is specify using '*' separator.<br/> 
     45!>    Example: 
     46!>       - cn_varinfo='varname1:flt=2*hamming(@f$cutoff@f$,@f$radius@f$)',  
     47!>                    'varname2:flt=gauss(@f$cutoff@f$,@f$radius@f$,@f$\alpha@f$)' 
     48!> 
     49!>    to filter variable value:<br/> 
     50!> @code 
     51!>    CALL filter_fill_value( td_var ) 
     52!> @endcode 
     53!>       - td_var is variable structure 
     54!> 
    1255!> @author 
    1356!> J.Paul 
    1457! REVISION HISTORY: 
    15 !> @date Nov, 2013 - Initial Version 
     58!> @date November, 2013 - Initial Version 
    1659! 
    1760!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    18 !> @todo 
    1961!---------------------------------------------------------------------- 
    2062MODULE filter 
    2163   USE kind                            ! F90 kind parameter 
    2264   USE phycst                          ! physical constant 
    23    USE logger                             ! log file manager 
     65   USE logger                          ! log file manager 
    2466   USE fct                             ! basic usefull function 
    2567   use att                             ! attribute manager 
     
    2769   USE extrap                          ! extrapolation manager 
    2870   IMPLICIT NONE 
    29    PRIVATE 
    3071   ! NOTE_avoid_public_variables_if_possible 
    3172 
     
    3475 
    3576   ! function and subroutine 
    36    PUBLIC :: filter_fill_value 
    37  
    38    PRIVATE :: filter__fill_value_wrapper 
    39    PRIVATE :: filter__fill_value 
    40    PRIVATE :: filter__3D_fill_value 
    41    PRIVATE :: filter__2D_fill_value 
    42    PRIVATE :: filter__2D 
    43    PRIVATE :: filter__2D_coef 
    44    PRIVATE :: filter__2D_hann 
    45    PRIVATE :: filter__2D_hamming 
    46    PRIVATE :: filter__2D_blackman 
    47    PRIVATE :: filter__2D_gauss 
    48    PRIVATE :: filter__2D_butterworth 
     77   PUBLIC :: filter_fill_value   !< filter variable value 
     78 
     79   PRIVATE :: filter__fill_value_wrapper ! 
     80   PRIVATE :: filter__fill_value         ! 
     81   PRIVATE :: filter__3D_fill_value      !  
     82   PRIVATE :: filter__2D_fill_value      ! 
     83   PRIVATE :: filter__2D                 ! 
     84   PRIVATE :: filter__2D_coef            ! 
     85   PRIVATE :: filter__2D_hann            ! 
     86   PRIVATE :: filter__2D_hamming         ! 
     87   PRIVATE :: filter__2D_blackman        ! 
     88   PRIVATE :: filter__2D_gauss           ! 
     89   PRIVATE :: filter__2D_butterworth     ! 
     90   PRIVATE :: filter__1D_fill_value      ! 
     91   PRIVATE :: filter__1D                 ! 
     92   PRIVATE :: filter__1D_coef            ! 
     93   PRIVATE :: filter__1D_hann            ! 
     94   PRIVATE :: filter__1D_hamming         ! 
     95   PRIVATE :: filter__1D_blackman        ! 
     96   PRIVATE :: filter__1D_gauss           ! 
     97   PRIVATE :: filter__1D_butterworth     ! 
    4998 
    5099   INTERFACE filter_fill_value 
     
    55104   !------------------------------------------------------------------- 
    56105   !> @brief 
    57    !> This subroutine filtering variable value. 
    58    !>  
    59    !> @details  
    60    !> 
    61    !> @author J.Paul 
    62    !> - Nov, 2013- Initial Version 
    63    ! 
    64    !> @param[inout] td_var : variable  
    65    !------------------------------------------------------------------- 
    66    !> @code 
     106   !> This subroutine filter variable value. 
     107   !> 
     108   !> @details 
     109   !> it checks if filtering method is available, 
     110   !>  gets parameter value, and launch filter__fill_value  
     111   !> 
     112   !> @author J.Paul 
     113   !> @date November, 2013 - Initial Version 
     114   ! 
     115   !> @param[inout] td_var variable structure  
     116   !------------------------------------------------------------------- 
    67117   SUBROUTINE filter__fill_value_wrapper( td_var ) 
    68118      IMPLICIT NONE 
     
    85135 
    86136      IF( .NOT. ASSOCIATED(td_var%d_value) )THEN 
    87          CALL logger_error("FILTER FILL VALUE: no table of value "//& 
     137         CALL logger_error("FILTER FILL VALUE: no array of value "//& 
    88138         &  "associted to variable "//TRIM(td_var%c_name) ) 
    89139      ELSE 
     
    93143         CASE DEFAULT 
    94144          
    95             CALL logger_info("FILTER FILL VALUE: no filter selected "//& 
     145            CALL logger_trace("FILTER FILL VALUE: no filter selected "//& 
    96146            &  "for variable "//TRIM(td_var%c_name)) 
    97147 
     
    181231               tl_att=att_init('filter',cl_filter) 
    182232               CALL var_move_att(td_var,tl_att) 
    183                 
     233               ! clean 
     234               CALL att_clean(tl_att) 
     235 
    184236               DO jl=1,il_nturn 
    185237                  CALL filter__fill_value( td_var, TRIM(cl_method),  &  
     
    192244      ENDIF 
    193245   END SUBROUTINE filter__fill_value_wrapper 
    194    !> @endcode 
    195246   !------------------------------------------------------------------- 
    196247   !> @brief 
    197    !> This subroutine filtering variable value. 
     248   !> This subroutine filtering variable value, given cut-off frequency 
     249   !> halo radius and alpha parameter. 
    198250   !>  
    199251   !> @details  
    200    !> 
    201    !> @author J.Paul 
    202    !> - Nov, 2013- Initial Version 
    203    ! 
    204    !> @param[inout] td_var : variable  
    205    !> @param[in] cd_name : filter name 
    206    !> @param[in] dd_cutoff : cuto-off frequency 
    207    !> @param[in] id_radius : filter halo radius 
    208    !> @param[in] dd_alpha : filter parameter 
    209    !------------------------------------------------------------------- 
    210    !> @code 
     252   !>    First extrabands are added to array of variable value. 
     253   !>    Then values are extrapolated, before apply filter. 
     254   !>    Finally extrabands are removed. 
     255   !> 
     256   !> @author J.Paul 
     257   !> @date November, 2013 - Initial Version 
     258   ! 
     259   !> @param[inout] td_var variable  
     260   !> @param[in] cd_name   filter name 
     261   !> @param[in] dd_cutoff cut-off frequency 
     262   !> @param[in] id_radius filter halo radius 
     263   !> @param[in] dd_alpha  filter parameter 
     264   !------------------------------------------------------------------- 
    211265   SUBROUTINE filter__fill_value( td_var, cd_name, & 
    212266   &                              dd_cutoff, id_radius, dd_alpha ) 
     
    247301 
    248302      !3-extrapolate 
    249       CALL extrap_fill_value( td_var, id_iext=id_radius, id_jext=id_radius ) 
     303      CALL extrap_fill_value( td_var ) !, id_iext=id_radius, id_jext=id_radius ) 
    250304 
    251305      !4-filtering 
     
    274328      END WHERE 
    275329 
     330      ! clean 
     331      CALL var_clean(tl_mask) 
     332 
    276333      !6-remove extraband 
    277334      CALL extrap_del_extrabands(td_var, id_radius, id_radius) 
    278335 
    279336   END SUBROUTINE filter__fill_value 
    280    !> @endcode 
    281    !------------------------------------------------------------------- 
    282    !> @brief This subroutine compute filtered value of 3D table.  
    283    !> 
    284    !> @details 
    285    !> 
    286    !> @warning table of value should have been already extrapolated before 
     337   !------------------------------------------------------------------- 
     338   !> @brief This subroutine compute filtered value of 3D array.  
     339   !> 
     340   !> @details 
     341   !>    First compute filter coefficient. 
     342   !>    Then apply it on each level of variable value. 
     343   !> 
     344   !> @warning array of value should have been already extrapolated before 
    287345   !> running this subroutine. 
    288346   ! 
    289347   !> @author J.Paul 
    290    !> - Nov, 2013- Initial Version 
    291    ! 
    292    !> @param[inout] dd_value : table of value to be filtered  
    293    !> @param[in] dd_fill : fill value  
    294    !> @param[in] cd_name : filter name 
    295    !> @param[in] dd_cutoff : cuto-off frequency 
    296    !> @param[in] id_radius : filter halo radius 
    297    !> @param[in] dd_alpha : filter parameter 
    298    !------------------------------------------------------------------- 
    299    !> @code 
     348   !> @date November, 2013 - Initial Version 
     349   ! 
     350   !> @param[inout] dd_value  array of value to be filtered  
     351   !> @param[in] dd_fill      fill value  
     352   !> @param[in] cd_name      filter name 
     353   !> @param[in] dd_cutoff    cut-off frequency 
     354   !> @param[in] id_radius    filter halo radius 
     355   !> @param[in] dd_alpha     filter parameter 
     356   !------------------------------------------------------------------- 
    300357   SUBROUTINE filter__3D_fill_value( dd_value, dd_fill, cd_name, & 
    301358   &                                 dd_cutoff, id_radius, dd_alpha) 
     
    330387 
    331388   END SUBROUTINE filter__3D_fill_value 
    332    !> @endcode 
    333    !------------------------------------------------------------------- 
    334    !> @brief This subroutine compute filtered value of 2D table. 
    335    ! 
    336    !> @details 
    337    ! 
    338    !> @warning table of value should have been already extrapolated before 
     389   !------------------------------------------------------------------- 
     390   !> @brief This subroutine compute filtered value of 2D array. 
     391   ! 
     392   !> @details 
     393   !>    First compute filter coefficient. 
     394   !>    Then apply it on variable value. 
     395   !> 
     396   !> @warning array of value should have been already extrapolated before 
    339397   !> running this subroutine. 
    340398   !> 
    341399   !> @author J.Paul 
    342    !> - Nov, 2013- Initial Version 
    343    ! 
    344    !> @param[inout] dd_value : table of value to be filtered  
    345    !> @param[in] dd_fill : fill value  
    346    !> @param[in] cd_name : filter name 
    347    !> @param[in] dd_cutoff : cuto-off frequency 
    348    !> @param[in] id_radius : filter halo radius 
    349    !> @param[in] dd_alpha : filter parameter 
    350    !------------------------------------------------------------------- 
    351    !> @code 
     400   !> @date November, 2013 - Initial Version 
     401   ! 
     402   !> @param[inout] dd_value  array of value to be filtered  
     403   !> @param[in] dd_fill      fill value  
     404   !> @param[in] cd_name      filter name 
     405   !> @param[in] dd_cutoff    cut-off frequency 
     406   !> @param[in] id_radius    filter halo radius 
     407   !> @param[in] dd_alpha     filter parameter 
     408   !------------------------------------------------------------------- 
    352409   SUBROUTINE filter__2D_fill_value( dd_value, dd_fill, cd_name, & 
    353410   &                                 dd_cutoff, id_radius, dd_alpha) 
     
    376433 
    377434   END SUBROUTINE filter__2D_fill_value 
    378    !> @endcode 
    379    !------------------------------------------------------------------- 
    380    !> @brief This subroutine compute filtered value of 1D table. 
    381    ! 
    382    !> @details 
    383    ! 
    384    !> @warning table of value should have been already extrapolated before 
     435   !------------------------------------------------------------------- 
     436   !> @brief This subroutine compute filtered value of 1D array. 
     437   ! 
     438   !> @details 
     439   !>    First compute filter coefficient. 
     440   !>    Then apply it on variable value. 
     441   !> 
     442   !> @warning array of value should have been already extrapolated before 
    385443   !> running this subroutine. 
    386444   !> 
    387445   !> @author J.Paul 
    388    !> - Nov, 2013- Initial Version 
    389    ! 
    390    !> @param[inout] dd_value : table of value to be filtered  
    391    !> @param[in] dd_fill : fill value  
    392    !> @param[in] cd_name : filter name 
    393    !> @param[in] dd_cutoff : cuto-off frequency 
    394    !> @param[in] id_radius : filter halo radius 
    395    !> @param[in] dd_alpha : filter parameter 
    396    !------------------------------------------------------------------- 
    397    !> @code 
     446   !> @date November, 2013 - Initial Version 
     447   ! 
     448   !> @param[inout] dd_value  array of value to be filtered  
     449   !> @param[in] dd_fill      fill value  
     450   !> @param[in] cd_name      filter name 
     451   !> @param[in] dd_cutoff    cut-off frequency 
     452   !> @param[in] id_radius    filter halo radius 
     453   !> @param[in] dd_alpha     filter parameter 
     454   !------------------------------------------------------------------- 
    398455   SUBROUTINE filter__1D_fill_value( dd_value, dd_fill, cd_name, & 
    399456   &                                 dd_cutoff, id_radius, dd_alpha) 
     
    422479 
    423480   END SUBROUTINE filter__1D_fill_value 
    424    !> @endcode 
    425    !------------------------------------------------------------------- 
    426    !> @brief This subroutine  
    427    ! 
    428    !> @details 
    429    ! 
    430    !> @note  
    431    !> if fill value are detected in the computing area,  
    432    !> no filtering is done. 
    433    !> 
    434    !> @author J.Paul 
    435    !> - Nov, 2013- Initial Version 
    436    ! 
    437    !> @param[inout] dd_value : table of value to be filtered  
    438    !> @param[in] dd_fill : fill value  
    439    !> @param[in] dd_coef :  filter coefficent table 
    440    !> @param[in] id_radius : filter halo radius 
    441    !------------------------------------------------------------------- 
    442    !> @code 
     481   !------------------------------------------------------------------- 
     482   !> @brief This subroutine filtered 2D array of value  
     483   !> 
     484   !> @details 
     485   !>    loop on first and second dimension,  
     486   !>    and apply coefficient 2D array on each point 
     487   !> 
     488   !> @author J.Paul 
     489   !> @date November, 2013 - Initial Version 
     490   ! 
     491   !> @param[inout] dd_value  array of value to be filtered  
     492   !> @param[in] dd_fill      fill value  
     493   !> @param[in] dd_coef      filter coefficent array 
     494   !> @param[in] id_radius    filter halo radius 
     495   !------------------------------------------------------------------- 
    443496   SUBROUTINE filter__2D(dd_value, dd_fill, dd_coef, id_radius) 
    444497      IMPLICIT NONE 
     
    452505      INTEGER(i4), DIMENSION(2)                :: il_shape 
    453506      REAL(dp)   , DIMENSION(:,:), ALLOCATABLE :: dl_value 
    454       REAL(dp)   , DIMENSION(:,:), ALLOCATABLE :: dl_area 
     507      REAL(dp)   , DIMENSION(:,:), ALLOCATABLE :: dl_halo 
    455508 
    456509      ! loop indices 
     
    463516      dl_value(:,:)=dd_value(:,:) 
    464517 
    465       ALLOCATE(dl_area(2*id_radius+1,2*id_radius+1)) 
     518      ALLOCATE(dl_halo(2*id_radius+1,2*id_radius+1)) 
    466519 
    467520      DO jj=1+id_radius,il_shape(2)-id_radius 
    468521         DO ji=1+id_radius,il_shape(1)-id_radius 
    469522 
    470             dl_area(:,:)=dd_fill 
    471             dl_area(:,:)=dl_value(ji-id_radius:ji+id_radius, & 
     523            dl_halo(:,:)=dd_fill 
     524            dl_halo(:,:)=dl_value(ji-id_radius:ji+id_radius, & 
    472525            &                     jj-id_radius:jj+id_radius) 
    473526 
    474             IF( ALL(dl_area(:,:)/=dd_fill) )THEN 
    475                dd_value(ji,jj)=SUM(dl_area(:,:)*dd_coef(:,:)) 
    476             ENDIF 
     527            dd_value(ji,jj)=SUM(dl_halo(:,:)*dd_coef(:,:)) 
    477528 
    478529         ENDDO 
    479530      ENDDO 
    480531 
    481       DEALLOCATE(dl_area) 
     532      DEALLOCATE(dl_halo) 
    482533      DEALLOCATE(dl_value) 
    483534 
    484535   END SUBROUTINE filter__2D 
    485    !> @endcode 
    486    !------------------------------------------------------------------- 
    487    !> @brief This subroutine  
    488    ! 
    489    !> @details 
    490    ! 
    491    !> @author J.Paul 
    492    !> - Nov, 2013- Initial Version 
    493    ! 
    494    !> @param[inout] dd_value : table of value to be filtered  
    495    !> @param[in] dd_fill : fill value  
    496    !> @param[in] dd_coef :  filter coefficent table 
    497    !> @param[in] id_radius : filter halo radius 
    498    !------------------------------------------------------------------- 
    499    !> @code 
     536   !------------------------------------------------------------------- 
     537   !> @brief This subroutine filtered 1D array of value   
     538   ! 
     539   !> @details 
     540   !>    loop on first dimension,  
     541   !>    and apply coefficient 1D array on each point 
     542   !> 
     543   !> @author J.Paul 
     544   !> @date November, 2013 - Initial Version 
     545   ! 
     546   !> @param[inout] dd_value  array of value to be filtered  
     547   !> @param[in] dd_fill      fill value  
     548   !> @param[in] dd_coef      filter coefficent array 
     549   !> @param[in] id_radius    filter halo radius 
     550   !------------------------------------------------------------------- 
    500551   SUBROUTINE filter__1D(dd_value, dd_fill, dd_coef, id_radius) 
    501552      IMPLICIT NONE 
     
    507558 
    508559      ! local variable 
    509       INTEGER(i4), DIMENSION(1)                :: il_shape 
     560      INTEGER(i4), DIMENSION(1)              :: il_shape 
    510561      REAL(dp)   , DIMENSION(:), ALLOCATABLE :: dl_value 
    511562 
     
    519570      DO ji=1+id_radius,il_shape(1)-id_radius 
    520571 
     572         dl_value(:)=dd_fill 
    521573         dl_value(:)=dd_value(ji-id_radius:ji+id_radius) 
    522574 
    523          IF( ANY(dl_value(:)==dd_fill) )THEN 
    524             CALL logger_error("FILTER FILL VALUE: fill value detected. "//& 
    525             &  " can't compute filtered value. "//& 
    526             &  "you should have extrapolate table before running "//& 
    527             &  " filter_fill_value") 
    528          ELSE 
    529             dd_value(ji)=SUM(dl_value(:)*dd_coef(:)) 
    530          ENDIF 
     575         dd_value(ji)=SUM(dl_value(:)*dd_coef(:)) 
    531576 
    532577      ENDDO 
     
    535580 
    536581   END SUBROUTINE filter__1D 
    537    !> @endcode 
    538582   !------------------------------------------------------------------- 
    539583   !> @brief This function compute filter coefficient.  
     
    548592   !> - butterworth 
    549593   !> Cut-off frequency could be specify. 
    550    !> As well as a filter parameter for gauss an butterworth filter 
    551    ! 
    552    !> @author J.Paul 
    553    !> - Nov, 2013- Initial Version 
    554    ! 
    555    !> @param[in] cd_name : filter name 
    556    !> @param[in] dd_cutoff : cut-off frequency 
    557    !> @param[in] id_radius : filter halo radius 
    558    !> @param[in] dd_alpha : filter parameter  
    559    !> @return table of filter coefficient 
    560    !------------------------------------------------------------------- 
    561    !> @code 
     594   !> As well as a filter parameter for gauss and butterworth filter 
     595   ! 
     596   !> @author J.Paul 
     597   !> @date November, 2013 - Initial Version 
     598   ! 
     599   !> @param[in] cd_name   filter name 
     600   !> @param[in] dd_cutoff cut-off frequency 
     601   !> @param[in] id_radius filter halo radius 
     602   !> @param[in] dd_alpha  filter parameter  
     603   !> @return array of filter coefficient 
     604   !------------------------------------------------------------------- 
    562605   FUNCTION filter__2D_coef(cd_name, dd_cutoff, id_radius, dd_alpha) 
    563606      IMPLICIT NONE 
     
    596639 
    597640   END FUNCTION filter__2D_coef 
    598    !> @endcode 
    599641   !------------------------------------------------------------------- 
    600642   !> @brief This function compute filter coefficient.  
     
    612654   ! 
    613655   !> @author J.Paul 
    614    !> - Nov, 2013- Initial Version 
    615    ! 
    616    !> @param[in] cd_name : filter name 
    617    !> @param[in] dd_cutoff : cut-off frequency 
    618    !> @param[in] id_radius : filter halo radius 
    619    !> @param[in] dd_alpha : filter parameter  
    620    !> @return table of filter coefficient 
    621    !------------------------------------------------------------------- 
    622    !> @code 
     656   !> @date November, 2013 - Initial Version 
     657   ! 
     658   !> @param[in] cd_name   filter name 
     659   !> @param[in] dd_cutoff cut-off frequency 
     660   !> @param[in] id_radius filter halo radius 
     661   !> @param[in] dd_alpha  filter parameter  
     662   !> @return array of filter coefficient 
     663   !------------------------------------------------------------------- 
    623664   FUNCTION filter__1D_coef(cd_name, dd_cutoff, id_radius, dd_alpha) 
    624665      IMPLICIT NONE 
     
    653694 
    654695   END FUNCTION filter__1D_coef 
    655    !> @endcode 
    656696   !------------------------------------------------------------------- 
    657697   !> @brief This function compute coefficient for HANN filter. 
     
    660700   ! 
    661701   !> @author J.Paul 
    662    !> - Nov, 2013- Initial Version 
    663    ! 
    664    !> @param[in] dd_cutoff : cuto-off frequency 
    665    !> @param[in] id_radius : filter halo radius 
    666    !> @return table of hann filter coefficient  
    667    !------------------------------------------------------------------- 
    668    !> @code 
     702   !> @date November, 2013 - Initial Version 
     703   ! 
     704   !> @param[in] dd_cutoff cut-off frequency 
     705   !> @param[in] id_radius filter halo radius 
     706   !> @return array of hann filter coefficient  
     707   !------------------------------------------------------------------- 
    669708   FUNCTION filter__1D_hann(dd_cutoff, id_radius) 
    670709      IMPLICIT NONE 
     
    695734             
    696735            IF( dl_rad < dd_cutoff )THEN 
    697                filter__1D_hann(ji)=0.5 + 0.5*COS(dg_pi*dl_rad/dd_cutoff) 
     736               filter__1D_hann(ji)=0.5 + 0.5*COS(dp_pi*dl_rad/dd_cutoff) 
    698737            ELSE 
    699738               filter__1D_hann(ji)=0 
     
    709748 
    710749   END FUNCTION filter__1D_hann 
    711    !> @endcode 
    712750   !------------------------------------------------------------------- 
    713751   !> @brief This function compute coefficient for HANN filter. 
     
    716754   ! 
    717755   !> @author J.Paul 
    718    !> - Nov, 2013- Initial Version 
    719    ! 
    720    !> @param[in] dd_cutoff : cuto-off frequency 
    721    !> @param[in] id_radius : filter halo radius 
    722    !> @return table of hann filter coefficient  
    723    !------------------------------------------------------------------- 
    724    !> @code 
     756   !> @date November, 2013 - Initial Version 
     757   ! 
     758   !> @param[in] dd_cutoff cut-off frequency 
     759   !> @param[in] id_radius filter halo radius 
     760   !> @return array of hann filter coefficient  
     761   !------------------------------------------------------------------- 
    725762   FUNCTION filter__2D_hann(dd_cutoff, id_radius) 
    726763      IMPLICIT NONE 
     
    755792                
    756793               IF( dl_rad < dd_cutoff )THEN 
    757                   filter__2D_hann(ji,jj)=0.5 + 0.5*COS(dg_pi*dl_rad/dd_cutoff) 
     794                  filter__2D_hann(ji,jj)=0.5 + 0.5*COS(dp_pi*dl_rad/dd_cutoff) 
    758795               ELSE 
    759796                  filter__2D_hann(ji,jj)=0 
     
    770807 
    771808   END FUNCTION filter__2D_hann 
    772    !> @endcode 
    773809   !------------------------------------------------------------------- 
    774810   !> @brief This function compute coefficient for HAMMING filter. 
     
    777813   ! 
    778814   !> @author J.Paul 
    779    !> - Nov, 2013- Initial Version 
    780    ! 
    781    !> @param[in] dd_cutoff : cuto-off frequency 
    782    !> @param[in] id_radius : filter halo radius 
    783    !> @return table of hamming filter coefficient  
    784    !------------------------------------------------------------------- 
    785    !> @code 
     815   !> @date November, 2013 - Initial Version 
     816   ! 
     817   !> @param[in] dd_cutoff cut-off frequency 
     818   !> @param[in] id_radius filter halo radius 
     819   !> @return array of hamming filter coefficient  
     820   !------------------------------------------------------------------- 
    786821   FUNCTION filter__1D_hamming(dd_cutoff, id_radius) 
    787822      IMPLICIT NONE 
     
    813848            IF( dl_rad < dd_cutoff )THEN 
    814849               filter__1D_hamming(ji)= 0.54 & 
    815                &                     + 0.46*COS(dg_pi*dl_rad/dd_cutoff) 
     850               &                     + 0.46*COS(dp_pi*dl_rad/dd_cutoff) 
    816851            ELSE 
    817852               filter__1D_hamming(ji)=0 
     
    827862 
    828863   END FUNCTION filter__1D_hamming 
    829    !> @endcode 
    830864   !------------------------------------------------------------------- 
    831865   !> @brief This function compute coefficient for HAMMING filter. 
     
    834868   ! 
    835869   !> @author J.Paul 
    836    !> - Nov, 2013- Initial Version 
    837    ! 
    838    !> @param[in] dd_cutoff : cuto-off frequency 
    839    !> @param[in] id_radius : filter halo radius 
    840    !> @return table of hamming filter coefficient  
    841    !------------------------------------------------------------------- 
    842    !> @code 
     870   !> @date November, 2013 - Initial Version 
     871   ! 
     872   !> @param[in] dd_cutoff cut-off frequency 
     873   !> @param[in] id_radius filter halo radius 
     874   !> @return array of hamming filter coefficient  
     875   !------------------------------------------------------------------- 
    843876   FUNCTION filter__2D_hamming(dd_cutoff, id_radius) 
    844877      IMPLICIT NONE 
     
    873906               IF( dl_rad < dd_cutoff )THEN 
    874907                  filter__2D_hamming(ji,jj)= 0.54 & 
    875                   &                        + 0.46*COS(dg_pi*dl_rad/dd_cutoff) 
     908                  &                        + 0.46*COS(dp_pi*dl_rad/dd_cutoff) 
    876909               ELSE 
    877910                  filter__2D_hamming(ji,jj)=0 
     
    888921 
    889922   END FUNCTION filter__2D_hamming 
    890    !> @endcode 
    891923   !------------------------------------------------------------------- 
    892924   !> @brief This function compute coefficient for BLACKMAN filter. 
     
    895927   ! 
    896928   !> @author J.Paul 
    897    !> - Nov, 2013- Initial Version 
    898    ! 
    899    !> @param[in] dd_cutoff : cuto-off frequency 
    900    !> @param[in] id_radius : filter halo radius 
    901    !> @return table of blackman filter coefficient  
    902    !------------------------------------------------------------------- 
    903    !> @code 
     929   !> @date November, 2013 - Initial Version 
     930   ! 
     931   !> @param[in] dd_cutoff cut-off frequency 
     932   !> @param[in] id_radius filter halo radius 
     933   !> @return array of blackman filter coefficient  
     934   !------------------------------------------------------------------- 
    904935   FUNCTION filter__1D_blackman(dd_cutoff, id_radius) 
    905936      IMPLICIT NONE 
     
    931962            IF( dl_rad < dd_cutoff )THEN 
    932963               filter__1D_blackman(ji)= 0.42 & 
    933                &                      + 0.5 *COS(  dg_pi*dl_rad/dd_cutoff) & 
    934                &                      + 0.08*COS(2*dg_pi*dl_rad/dd_cutoff) 
     964               &                      + 0.5 *COS(  dp_pi*dl_rad/dd_cutoff) & 
     965               &                      + 0.08*COS(2*dp_pi*dl_rad/dd_cutoff) 
    935966            ELSE 
    936967               filter__1D_blackman(ji)=0 
     
    946977 
    947978   END FUNCTION filter__1D_blackman 
    948    !> @endcode 
    949979   !------------------------------------------------------------------- 
    950980   !> @brief This function compute coefficient for BLACKMAN filter. 
    951    ! 
    952    !> @details 
    953    ! 
    954    !> @author J.Paul 
    955    !> - Nov, 2013- Initial Version 
    956    ! 
    957    !> @param[in] dd_cutoff : cuto-off frequency 
    958    !> @param[in] id_radius : filter halo radius 
    959    !> @return table of blackman filter coefficient  
    960    !------------------------------------------------------------------- 
    961    !> @code 
     981   !> 
     982   !> @details 
     983   !> 
     984   !> @author J.Paul 
     985   !> @date November, 2013 - Initial Version 
     986   !> 
     987   !> @param[in] dd_cutoff cut-off frequency 
     988   !> @param[in] id_radius filter halo radius 
     989   !> @return array of blackman filter coefficient  
     990   !------------------------------------------------------------------- 
    962991   FUNCTION filter__2D_blackman(dd_cutoff, id_radius) 
    963992      IMPLICIT NONE 
     
    9921021               IF( dl_rad < dd_cutoff )THEN 
    9931022                  filter__2D_blackman(ji,jj)= 0.42 & 
    994                   &                         + 0.5 *COS(  dg_pi*dl_rad/dd_cutoff) & 
    995                   &                         + 0.08*COS(2*dg_pi*dl_rad/dd_cutoff) 
     1023                  &                         + 0.5 *COS(  dp_pi*dl_rad/dd_cutoff) & 
     1024                  &                         + 0.08*COS(2*dp_pi*dl_rad/dd_cutoff) 
    9961025               ELSE 
    9971026                  filter__2D_blackman(ji,jj)=0 
     
    10081037 
    10091038   END FUNCTION filter__2D_blackman 
    1010    !> @endcode 
    10111039   !------------------------------------------------------------------- 
    10121040   !> @brief This function compute coefficient for GAUSS filter. 
    1013    ! 
    1014    !> @details 
    1015    ! 
    1016    !> @author J.Paul 
    1017    !> - Nov, 2013- Initial Version 
    1018    ! 
    1019    !> @param[in] dd_cutoff : cuto-off frequency 
    1020    !> @param[in] id_radius : filter halo radius 
    1021    !> @param[in] dd_alpha : filter parameter 
    1022    !> @return table of gauss filter coefficient  
    1023    !------------------------------------------------------------------- 
    1024    !> @code 
     1041   !> 
     1042   !> @details 
     1043   !> 
     1044   !> @author J.Paul 
     1045   !> @date November, 2013 - Initial Version 
     1046   !> 
     1047   !> @param[in] dd_cutoff cut-off frequency 
     1048   !> @param[in] id_radius filter halo radius 
     1049   !> @param[in] dd_alpha  filter parameter 
     1050   !> @return array of gauss filter coefficient  
     1051   !------------------------------------------------------------------- 
    10251052   FUNCTION filter__1D_gauss(dd_cutoff, id_radius, dd_alpha) 
    10261053      IMPLICIT NONE 
     
    10621089 
    10631090   END FUNCTION filter__1D_gauss 
    1064    !> @endcode 
    10651091   !------------------------------------------------------------------- 
    10661092   !> @brief This function compute coefficient for GAUSS filter. 
    1067    ! 
    1068    !> @details 
    1069    ! 
    1070    !> @author J.Paul 
    1071    !> - Nov, 2013- Initial Version 
    1072    ! 
    1073    !> @param[in] dd_cutoff : cuto-off frequency 
    1074    !> @param[in] id_radius : filter halo radius 
    1075    !> @param[in] dd_alpha : filter parameter 
    1076    !> @return table of gauss filter coefficient  
    1077    !------------------------------------------------------------------- 
    1078    !> @code 
     1093   !> 
     1094   !> @details 
     1095   !> 
     1096   !> @author J.Paul 
     1097   !> @date November, 2013 - Initial Version 
     1098   !> 
     1099   !> @param[in] dd_cutoff cut-off frequency 
     1100   !> @param[in] id_radius filter halo radius 
     1101   !> @param[in] dd_alpha  filter parameter 
     1102   !> @return array of gauss filter coefficient  
     1103   !------------------------------------------------------------------- 
    10791104   FUNCTION filter__2D_gauss(dd_cutoff, id_radius, dd_alpha) 
    10801105      IMPLICIT NONE 
     
    11201145 
    11211146   END FUNCTION filter__2D_gauss 
    1122    !> @endcode 
    11231147   !------------------------------------------------------------------- 
    11241148   !> @brief This function compute coefficient for BUTTERWORTH filter. 
    1125    ! 
    1126    !> @details 
    1127    ! 
    1128    !> @author J.Paul 
    1129    !> - Nov, 2013- Initial Version 
    1130    ! 
    1131    !> @param[in] dd_cutoff : cuto-off frequency 
    1132    !> @param[in] id_radius : filter halo radius 
    1133    !> @param[in] dd_alpha : filter parameter 
    1134    !> @return table of butterworth filter coefficient  
    1135    !------------------------------------------------------------------- 
    1136    !> @code 
     1149   !> 
     1150   !> @details 
     1151   !> 
     1152   !> @author J.Paul 
     1153   !> @date November, 2013 - Initial Version 
     1154   !> 
     1155   !> @param[in] dd_cutoff cut-off frequency 
     1156   !> @param[in] id_radius filter halo radius 
     1157   !> @param[in] dd_alpha  filter parameter 
     1158   !> @return array of butterworth filter coefficient  
     1159   !------------------------------------------------------------------- 
    11371160   FUNCTION filter__1D_butterworth(dd_cutoff, id_radius, dd_alpha) 
    11381161      IMPLICIT NONE 
     
    11741197 
    11751198   END FUNCTION filter__1D_butterworth 
    1176    !> @endcode 
    11771199   !------------------------------------------------------------------- 
    11781200   !> @brief This function compute coefficient for BUTTERWORTH filter. 
    1179    ! 
    1180    !> @details 
    1181    ! 
    1182    !> @author J.Paul 
    1183    !> - Nov, 2013- Initial Version 
    1184    ! 
    1185    !> @param[in] dd_cutoff : cuto-off frequency 
    1186    !> @param[in] id_radius : filter halo radius 
    1187    !> @param[in] dd_alpha : filter parameter 
    1188    !> @return table of butterworth filter coefficient  
    1189    !------------------------------------------------------------------- 
    1190    !> @code 
     1201   !> 
     1202   !> @details 
     1203   !> 
     1204   !> @author J.Paul 
     1205   !> @date November, 2013 - Initial Version 
     1206   !> 
     1207   !> @param[in] dd_cutoff cut-off frequency 
     1208   !> @param[in] id_radius filter halo radius 
     1209   !> @param[in] dd_alpha  filter parameter 
     1210   !> @return array of butterworth filter coefficient  
     1211   !------------------------------------------------------------------- 
    11911212   FUNCTION filter__2D_butterworth(dd_cutoff,  id_radius, dd_alpha) 
    11921213      IMPLICIT NONE 
     
    12321253 
    12331254   END FUNCTION filter__2D_butterworth 
    1234    !> @endcode 
    1235 !   !------------------------------------------------------------------- 
    1236 !   !> @brief This function  
    1237 !   ! 
    1238 !   !> @details 
    1239 !   ! 
    1240 !   !> @author J.Paul 
    1241 !   !> - Nov, 2013- Initial Version 
    1242 !   ! 
    1243 !   !> @param[in]  
    1244 !   !------------------------------------------------------------------- 
    1245 !   !> @code 
    1246 !   FUNCTION filter_() 
    1247 !      IMPLICIT NONE 
    1248 !      ! Argument       
    1249 !      ! function 
    1250 !      ! local variable 
    1251 !      ! loop indices 
    1252 !      !---------------------------------------------------------------- 
    1253 ! 
    1254 !   END FUNCTION filter_ 
    1255 !   !> @endcode 
    1256 !   !------------------------------------------------------------------- 
    1257 !   !> @brief This subroutine  
    1258 !   ! 
    1259 !   !> @details 
    1260 !   ! 
    1261 !   !> @author J.Paul 
    1262 !   !> - Nov, 2013- Initial Version 
    1263 !   ! 
    1264 !   !> @param[in]  
    1265 !   !------------------------------------------------------------------- 
    1266 !   !> @code 
    1267 !   SUBROUTINE filter_() 
    1268 !      IMPLICIT NONE 
    1269 !      ! Argument       
    1270 !      ! local variable 
    1271 !      ! loop indices 
    1272 !      !---------------------------------------------------------------- 
    1273 ! 
    1274 !   END SUBROUTINE filter_ 
    1275 !   !> @endcode 
    12761255END MODULE filter 
    12771256 
Note: See TracChangeset for help on using the changeset viewer.