module Hardware.SiClock.Examples where
import Control.Monad
import Control.Monad.IO.Class
import Control.Concurrent (threadDelay)
import Hardware.SiClock
import Hardware.SiClock.FSK as FSK
import Hardware.SiClock.MorseKeyer as MorseKeyer
import Hardware.SiClock.JT65Test (jt65SendHelloWorld)
testSynth :: Frequency -> IO ()
testSynth f = runSynth $ do
liftIO $ putStrLn $ "setting clk0 to " ++ show f
void $ setDividers PLL_A CLK_0 f
pllReset
clk0_On
liftIO $ putStrLn $ "clk0_on "
clkOff :: IO ()
clkOff = runSynth $ setCLKControl CLK_0 [CLK_off]
testI2CReading :: IO ()
testI2CReading = runSynth dumpRegisters
someHopFrequencies :: [Frequency]
someHopFrequencies = [28120000,28120100..28120400]
testHopping :: [Frequency] -> IO ()
testHopping sw = runSynth $ do
maxPLLFreq <- askMaxPLLFrequency
xtalFreq <- askXtalFrequency
setPLLDivider_A $ maxPLLFreq / xtalFreq
forever $ forM_ sw $ \freq -> do
setCLKDivider CLK_0 0 $ maxPLLFreq / freq
pllReset
clk0_On
liftIO $ threadDelay 1500000
testJT65 :: Frequency -> IO ()
testJT65 f = runSynth $ jt65SendHelloWorld f
testMorse :: Frequency -> IO ()
testMorse f
= runSynth $ MorseKeyer.sendMsg f MorseKeyer.someMsg
testRTTY :: Frequency -> IO ()
testRTTY f
= runSynth $ FSK.rtty FSK.symbolTime45 f FSK.someMsgBaudot
testClicks1 :: Frequency -> IO ()
testClicks1 f = runSynth $ do
maxPLLFreq <- askMaxPLLFrequency
xtalFreq <- askXtalFrequency
setPLLDivider_A $ maxPLLFreq / xtalFreq
setPLLDivider_B $ maxPLLFreq / xtalFreq
setCLKDivider CLK_0 0 $ maxPLLFreq / f
pllReset
forever $ do
liftIO $ putStrLn "A"
setCLKControl CLK_0 [CLK_on,CLK_multi,CLK_DRV8,CLK_multiPLLA]
liftIO $ threadDelay $ 2000*1000
liftIO $ putStrLn "B"
setCLKControl CLK_0 [CLK_on,CLK_multi,CLK_DRV8,CLK_multiPLLB]
liftIO $ threadDelay $ 2000*1000
noClicks2 :: Frequency -> IO ()
noClicks2 f = runSynth $ do
maxPLLFreq <- askMaxPLLFrequency
xtalFreq <- askXtalFrequency
setPLLDivider_A $ maxPLLFreq / xtalFreq
setCLKDivider CLK_0 0 $ maxPLLFreq / f
forever $ do
setPLLDivider_A $ maxPLLFreq / xtalFreq
setCLKDivider CLK_0 0 $ maxPLLFreq / f
setCLKControl CLK_0 [CLK_on,CLK_multi,CLK_DRV8,CLK_multiPLLA]
liftIO $ threadDelay $ 500*1000