summary refs log tree commit diff
path: root/src/Main.hs
diff options
context:
space:
mode:
authortzlil <tzlils@protonmail.com>2024-02-23 16:28:14 +0200
committertzlil <tzlils@protonmail.com>2024-02-23 16:28:14 +0200
commit2d3e55c69d8ff08af0bc0363dd70879b8b6dc873 (patch)
treeb28fec165e5681a5b239e24c12d61872f79ccb77 /src/Main.hs
parentd06c0fa5a036ea068487b260e004dc5da8f92fb9 (diff)
rename stuff, add SSAM2603 ADC/DAC chip docs
Diffstat (limited to 'src/Main.hs')
-rw-r--r--src/Main.hs71
1 files changed, 71 insertions, 0 deletions
diff --git a/src/Main.hs b/src/Main.hs
new file mode 100644
index 0000000..43f4746
--- /dev/null
+++ b/src/Main.hs
@@ -0,0 +1,71 @@
+{-# LANGUAGE ImplicitParams #-}
+{-# LANGUAGE NumericUnderscores #-}
+{-# LANGUAGE AllowAmbiguousTypes #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE LambdaCase #-}
+{-# OPTIONS_GHC -option #-}
+module Main where
+
+import Clash.Prelude
+import Clash.Annotations.SynthesisAttributes
+import Clash.Cores.UART
+import Data.Char (ord)
+import Control.Monad.Trans.State.Strict
+
+-- 50 MHz
+createDomain vSystem{vName="Input", vPeriod=20_000}
+
+{-# ANN topEntity
+  (Synthesize
+    { t_name   = "Main"
+    , t_inputs = [
+      PortName "CLK0",
+      PortName "UART_RX"
+       ]
+    , t_output = PortName "UART_TX"
+    }) #-}
+topEntity ::
+  "CLK" ::: Clock Input
+    `Annotate` 'StringAttr "chip_pin" "R20"
+    `Annotate` 'StringAttr
+                "altera_attribute" "-name IO_STANDARD \"3.3-V LVTTL\""
+  -> "RX" ::: Signal Input Bit
+    `Annotate` 'StringAttr
+                "chip_pin" "M9"
+    `Annotate` 'StringAttr
+                "altera_attribute" "-name IO_STANDARD \"2.5V\""
+  -> "KEY0" ::: Signal Input Bit
+    `Annotate` 'StringAttr
+                "chip_pin" "P11"
+    `Annotate` 'StringAttr
+                "altera_attribute" "-name IO_STANDARD \"1.2V\""
+  -> Signal Input Bit
+    `Annotate` 'StringAttr
+                "chip_pin" "L9"
+    `Annotate` 'StringAttr
+                "altera_attribute" "-name IO_STANDARD \"2.5V\""
+topEntity clk rx key0 = txBit
+  where
+    baud = SNat @115200
+    uart' = exposeClockResetEnable (uart baud) clk resetGen enableGen
+    (rxWord, txBit, ack) = uart' rx txM
+    txM = (exposeClockResetEnable mealyS clk resetGen enableGen) cpu Listening (CPUIn <$> key0 <*> ack <*> rxWord)
+
+
+data CPUIn = CPUIn {
+  key0 :: Bit,
+  ack :: Bool,
+  rx :: Maybe (BitVector 8)
+}
+
+data CPUState = Transmitting (BitVector 8) | Listening deriving (Generic, NFDataX)
+cpu :: CPUIn -> State CPUState (Maybe (BitVector 8))
+cpu CPUIn{rx=Just rx} = do
+  put $ Transmitting $ rx
+  return Nothing
+
+cpu CPUIn{ack=True} = put Listening >> return Nothing
+
+cpu CPUIn{ack=False,rx=Nothing} = get >>= \case 
+  Transmitting s -> return $ Just s
+  Listening -> return Nothing
\ No newline at end of file