summary refs log tree commit diff
path: root/src
diff options
context:
space:
mode:
authortzlil <tzlils@protonmail.com>2024-01-26 21:09:09 +0200
committertzlil <tzlils@protonmail.com>2024-01-26 21:09:09 +0200
commit5c6635052b6983d2149b936762298200f6419275 (patch)
treed6cde34d61df3aa7be7e63bbb42da157207a93a9 /src
parent3b5936958c72d7f4db1b5d0deb00cdb43a2f5e66 (diff)
UART ECHO SERVER!!!!!!!!
Diffstat (limited to 'src')
-rw-r--r--src/Blinker.hs62
1 files changed, 40 insertions, 22 deletions
diff --git a/src/Blinker.hs b/src/Blinker.hs
index 8980763..7ee5ff8 100644
--- a/src/Blinker.hs
+++ b/src/Blinker.hs
@@ -1,47 +1,65 @@
-{-# OPTIONS_GHC -fno-warn-orphans #-}
 {-# LANGUAGE ImplicitParams #-}
-{-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE NumericUnderscores #-}
 {-# LANGUAGE AllowAmbiguousTypes #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# OPTIONS_GHC -option #-}
 module Blinker where
 
 import Clash.Prelude
 import Clash.Annotations.SynthesisAttributes
+import Clash.Cores.UART
+import Data.Char (ord)
+import Control.Monad.Trans.State.Strict
 
-createDomain vSystem{vName="Input", vPeriod=20000}
-
--- createDomain vSystem{vName="Dom20MHz", vPeriod=50000}
+-- 50 MHz
+createDomain vSystem{vName="Input", vPeriod=20_000}
 
 {-# ANN topEntity
   (Synthesize
     { t_name   = "Blinker"
     , t_inputs = [
       PortName "CLK0",
-      PortName "KEY0"
+      PortName "UART_RX"
        ]
-    , t_output = PortName "LED"
+    , t_output = PortName "UART_TX"
     }) #-}
 topEntity ::
-  HiddenClockResetEnable Input =>
-  Clock Input
+  "CLK" ::: Clock Input
     `Annotate` 'StringAttr "chip_pin" "R20"
     `Annotate` 'StringAttr
-                "altera_attribute" "-name IO_STANDARD \"3.3-V LVTTL\"" ->
-  Signal Input Bit
-    `Annotate` 'StringAttr "chip_pin" "AC9"
+                "altera_attribute" "-name IO_STANDARD \"3.3-V LVTTL\""
+  -> "RX" ::: Signal Input Bit
     `Annotate` 'StringAttr
-                "altera_attribute" "-name IO_STANDARD \"3.3-V LVTTL\"" ->
-
-  Signal Input Bit
+                "chip_pin" "M9"
     `Annotate` 'StringAttr
-                "chip_pin" "F7"
+                "altera_attribute" "-name IO_STANDARD \"2.5V\""
+  -> "KEY0" ::: Signal Input Bit
     `Annotate` 'StringAttr
-                "altera_attribute" "-name IO_STANDARD \"3.3-V LVTTL\""
-topEntity clk sw = msb <$> r
+                "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
-    r :: Signal Input (Unsigned 24)
-    r = withClockResetEnable clk resetGen enableGen $ register 0 (r + 1)
+    baud = SNat @115200
+    uart' = exposeClockResetEnable (uart baud) clk resetGen enableGen
+    (rxWord, txBit, ack) = uart' rx txM
+    txM = (exposeClockResetEnable mealySB clk resetGen enableGen) (uncurry cpu) Nothing (ack,rxWord)
+
+type CpuState = Maybe (BitVector 8)
+cpu :: Bool -> Maybe (BitVector 8) -> State CpuState (Maybe (BitVector 8))
+cpu _ (Just rx) = do
+  put (Just rx)
+  return Nothing
 
+cpu True Nothing = do
+  put Nothing
+  return Nothing
 
--- graph :: Signal Dom20MHz (Unsigned 8) -> Signal Dom20MHz (Maybe ((Unsigned 8), Term)) -> Signal Dom20MHz Term
--- graph = asyncRam d32
\ No newline at end of file
+cpu False Nothing = do
+  s <- get
+  return s
\ No newline at end of file