Skip to content

Commit

Permalink
Randomizer implemented. Need to start testing FFT with convolution.
Browse files Browse the repository at this point in the history
  • Loading branch information
Grant Rotskoff committed May 30, 2012
1 parent 5f5e5be commit 0a82d80
Show file tree
Hide file tree
Showing 2 changed files with 19 additions and 2 deletions.
12 changes: 10 additions & 2 deletions Functions.hs
Original file line number Original file line Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ module Functions where
import Sn import Sn
import Group import Group
import Data.Complex import Data.Complex
import Data.List (unfoldr)
import System.Random import System.Random
import qualified Data.Map as Map import qualified Data.Map as Map


Expand Down Expand Up @@ -31,8 +32,15 @@ add (F f) (F g)
| otherwise = F $ Map.fromList $ zip (k f) vs where | otherwise = F $ Map.fromList $ zip (k f) vs where
vs = zipWith (+) (v f) (v g) vs = zipWith (+) (v f) (v g)


randomF :: Int -> SnMap randomls :: Int -> StdGen -> [Double]
randomF n = undefined randomls n = take n . unfoldr (Just . randomR (0,1))

randomF :: Int -> IO SnMap
randomF n = do
seed <- newStdGen
let ks = s n
let vs = randomls (length ks) seed
return $ F $ Map.fromList $ zip ks vs


-- A key step to the recursion of the Fourier Transform is the adaptation of -- A key step to the recursion of the Fourier Transform is the adaptation of
-- SnMaps to the subgroups of Sn. Essentially, this is a precise way of -- SnMaps to the subgroups of Sn. Essentially, this is a precise way of
Expand Down
9 changes: 9 additions & 0 deletions fft.hs
Original file line number Original file line Diff line number Diff line change
Expand Up @@ -30,6 +30,15 @@ fft (F f) l
n = factInv $ fDim (F f) n = factInv $ fDim (F f)




randomFFT :: Partition -> (IO [[Double]])
randomFFT (Part l) = (randomF n) >>= (\s -> return (fft s (Part l))) where
n = sum l





-- Temp. / Inelegant
factInv :: Int -> Int factInv :: Int -> Int
factInv x = case x of factInv x = case x of
1 -> 1 1 -> 1
Expand Down

0 comments on commit 0a82d80

Please sign in to comment.