never executed always true always false
    1 {-# LANGUAGE DuplicateRecordFields #-}
    2 {-# LANGUAGE OverloadedStrings #-}
    3 {-# LANGUAGE QuasiQuotes #-}
    4 {-# LANGUAGE RecordWildCards #-}
    5 {-# LANGUAGE TypeFamilies #-}
    6 
    7 {- |
    8 Module      : NITTA.Model.ProcessorUnits.IO.SPI
    9 Description :
   10 Copyright   : (c) Aleksandr Penskoi, 2019
   11 License     : BSD3
   12 Maintainer  : aleksandr.penskoi@gmail.com
   13 Stability   : experimental
   14 -}
   15 module NITTA.Model.ProcessorUnits.IO.SPI (
   16     SPI,
   17     anySPI,
   18     Ports (..),
   19     IOPorts (..),
   20     spiMasterPorts,
   21     spiSlavePorts,
   22 ) where
   23 
   24 import Data.Aeson
   25 import Data.Default
   26 import Data.HashMap.Strict qualified as HM
   27 import Data.Map.Strict qualified as M
   28 import Data.Maybe (fromMaybe, mapMaybe)
   29 import Data.Set qualified as S
   30 import Data.String.Interpolate
   31 import NITTA.Intermediate.Functions
   32 import NITTA.Intermediate.Types
   33 import NITTA.Model.Problems
   34 import NITTA.Model.ProcessorUnits.IO.SimpleIO
   35 import NITTA.Model.ProcessorUnits.Types
   36 import NITTA.Model.Time
   37 import NITTA.Project
   38 import NITTA.Utils
   39 import Prettyprinter
   40 
   41 data SPIinterface
   42 
   43 instance SimpleIOInterface SPIinterface
   44 
   45 type SPI v x t = SimpleIO SPIinterface v x t
   46 
   47 anySPI :: Time t => Int -> Maybe Int -> SPI v x t
   48 anySPI bounceFilter bufferSize =
   49     SimpleIO
   50         { bounceFilter
   51         , bufferSize
   52         , receiveQueue = []
   53         , receiveN = 0
   54         , isReceiveOver = False
   55         , sendQueue = []
   56         , sendN = 0
   57         , process_ = def
   58         }
   59 
   60 instance IOConnected (SPI v x t) where
   61     data IOPorts (SPI v x t)
   62         = SPIMaster
   63             { master_mosi :: OutputPortTag
   64             , master_miso :: InputPortTag
   65             , master_sclk :: OutputPortTag
   66             , master_cs :: OutputPortTag
   67             }
   68         | SPISlave
   69             { slave_mosi :: InputPortTag
   70             , slave_miso :: OutputPortTag
   71             , slave_sclk :: InputPortTag
   72             , slave_cs :: InputPortTag
   73             }
   74         deriving (Show)
   75 
   76     inputPorts SPISlave{..} = S.fromList [slave_mosi, slave_sclk, slave_cs]
   77     inputPorts SPIMaster{..} = S.fromList [master_miso]
   78 
   79     outputPorts SPISlave{..} = S.fromList [slave_miso]
   80     outputPorts SPIMaster{..} = S.fromList [master_mosi, master_sclk, master_cs]
   81 
   82 spiMasterPorts tag =
   83     SPIMaster
   84         { master_mosi = OutputPortTag $ tag <> "_mosi"
   85         , master_miso = InputPortTag $ tag <> "_miso"
   86         , master_sclk = OutputPortTag $ tag <> "_sclk"
   87         , master_cs = OutputPortTag $ tag <> "_cs"
   88         }
   89 
   90 spiSlavePorts tag =
   91     SPISlave
   92         { slave_mosi = InputPortTag $ tag <> "_mosi"
   93         , slave_miso = OutputPortTag $ tag <> "_miso"
   94         , slave_sclk = InputPortTag $ tag <> "_sclk"
   95         , slave_cs = InputPortTag $ tag <> "_cs"
   96         }
   97 
   98 instance Time t => Default (SPI v x t) where
   99     def = anySPI 0 $ Just 6
  100 
  101 instance (ToJSON v, VarValTime v x t) => TargetSystemComponent (SPI v x t) where
  102     moduleName _ _ = "pu_spi"
  103     hardware _tag _pu =
  104         Aggregate
  105             Nothing
  106             [ FromLibrary "spi/pu_slave_spi_driver.v"
  107             , FromLibrary "spi/spi_slave_driver.v"
  108             , FromLibrary "spi/i2n_splitter.v"
  109             , FromLibrary "spi/buffer.v"
  110             , FromLibrary "spi/bounce_filter.v"
  111             , FromLibrary "spi/spi_master_driver.v"
  112             , FromLibrary "spi/n2i_splitter.v"
  113             , FromLibrary "spi/pu_slave_spi.v"
  114             , FromLibrary "spi/pu_master_spi.v"
  115             ]
  116 
  117     software tag pu = protocolDescription tag pu "SPI Processor Unit"
  118 
  119     hardwareInstance
  120         tag
  121         SimpleIO{bounceFilter, sendN, receiveN}
  122         UnitEnv
  123             { sigClk
  124             , sigRst
  125             , sigCycleBegin
  126             , sigInCycle
  127             , sigCycleEnd
  128             , valueIn = Just (dataIn, attrIn)
  129             , valueOut = Just (dataOut, attrOut)
  130             , ctrlPorts = Just SimpleIOPorts{..}
  131             , ioPorts = Just ioPorts
  132             } =
  133             [__i|
  134                 #{ module_ ioPorts } \#
  135                         ( .DATA_WIDTH( #{ dataWidth (def :: x) } )
  136                         , .ATTR_WIDTH( #{ attrWidth (def :: x) } )
  137                         , .BOUNCE_FILTER( #{ show bounceFilter } )
  138                         , .DISABLED( #{ if sendN == 0 && receiveN == 0 then (1 :: Int) else 0 } )
  139                         ) #{ tag }
  140                     ( .clk( #{ sigClk } )
  141                     , .rst( #{ sigRst } )
  142                     , .flag_stop( #{ stop } )
  143                     , .signal_cycle_begin( #{ sigCycleBegin } )
  144                     , .signal_in_cycle( #{ sigInCycle  } )
  145                     , .signal_cycle_end( #{ sigCycleEnd } )
  146                     , .signal_oe( #{ oe } )
  147                     , .signal_wr( #{ wr } )
  148                     , .data_in( #{ dataIn } ), .attr_in( #{ attrIn } )
  149                     , .data_out( #{ dataOut } ), .attr_out( #{ attrOut } )
  150                     #{ nest 4 $ extIO ioPorts  }
  151                     );
  152             |]
  153             where
  154                 module_ SPISlave{} = "pu_slave_spi" :: Verilog
  155                 module_ SPIMaster{} = "pu_master_spi"
  156                 extIO SPISlave{..} =
  157                     [__i|
  158                         , .mosi( #{ slave_mosi } )
  159                         , .miso( #{ slave_miso } )
  160                         , .sclk( #{ slave_sclk } )
  161                         , .cs( #{ slave_cs } )
  162                     |] ::
  163                         Verilog
  164                 extIO SPIMaster{..} =
  165                     [__i|
  166                         , .mosi( #{ master_mosi } )
  167                         , .miso( #{ master_miso } )
  168                         , .sclk( #{ master_sclk } )
  169                         , .cs( #{ master_cs } )
  170                     |]
  171     hardwareInstance _title _pu _env = error "internal error"
  172 
  173 instance VarValTime v x t => IOTestBench (SPI v x t) v x where
  174     testEnvironmentInitFlag tag _pu = Just $ tag <> "_env_init_flag"
  175 
  176     testEnvironment
  177         tag
  178         sio@SimpleIO{process_, bounceFilter}
  179         UnitEnv
  180             { sigClk
  181             , sigRst
  182             , ctrlPorts = Just SimpleIOPorts{}
  183             , ioPorts = Just ioPorts
  184             }
  185         TestEnvironment{teCntx = cntx@Cntx{cntxCycleNumber, cntxProcess}, teComputationDuration} =
  186             let receivedVariablesSeq =
  187                     mapMaybe
  188                         ( \f -> case castF f of
  189                             Just Receive{} -> Just $ oneOf $ variables f
  190                             _ -> Nothing
  191                         )
  192                         $ functions process_
  193                 receivedVarsValues = take cntxCycleNumber $ cntxReceivedBySlice cntx
  194                 sendedVariableSeq =
  195                     mapMaybe
  196                         ( \case
  197                             (Target v) -> Just v
  198                             _ -> Nothing
  199                         )
  200                         $ getEndpoints process_
  201                 sendedVarsValues = take cntxCycleNumber $ map cycleCntx cntxProcess
  202                 wordWidth = dataWidth (def :: x)
  203                 frameWordCount = max (length receivedVariablesSeq) $ length sendedVariableSeq
  204                 frameWidth = frameWordCount * wordWidth
  205                 timeLag = 10 :: Int
  206                 sendingDuration =
  207                     max
  208                         (teComputationDuration + 2)
  209                         (frameWidth * 2 + bounceFilter + 2)
  210 
  211                 toVerilogLiteral xs =
  212                     let xs' = map toVerilogLiteral' xs
  213                         placeholder = replicate (frameWordCount - length xs) [i|#{ wordWidth }'d00|]
  214                      in hsep $ punctuate ", " (xs' <> placeholder)
  215                 toVerilogLiteral' x
  216                     | abs x /= x = [i|-#{ wordWidth }'sd#{ dataLiteral (-x) }|]
  217                     | otherwise = [i|#{ wordWidth }'sd#{ dataLiteral x }|]
  218 
  219                 disable =
  220                     [__i|
  221                         initial begin
  222                             @(negedge #{ sigRst });
  223                             #{ envInitFlagName } <= 1;
  224                         end
  225                     |]
  226 
  227                 envInitFlagName =
  228                     fromMaybe (error "SPI: testEnvironment: internal error") $
  229                         testEnvironmentInitFlag tag sio
  230              in case ioPorts of
  231                     SPISlave{..} ->
  232                         let receiveCycle transmit =
  233                                 let xs = map (\v -> fromMaybe def $ transmit M.!? v) receivedVariablesSeq
  234                                  in [__i|
  235                                         $display( "set data for sending #{ viaShow xs } by #{ tag }_io_test_input" );
  236                                         #{ tag }_io_test_input = { #{ toVerilogLiteral xs } }; // #{ viaShow xs }
  237                                         #{ tag }_io_test_start_transaction = 1;                           @(posedge #{ sigClk });
  238                                         #{ tag }_io_test_start_transaction = 0;                           @(posedge #{ sigClk });
  239                                         repeat( #{ sendingDuration } ) @(posedge #{ sigClk });
  240 
  241                                     |]
  242 
  243                             sendingAssert transmit =
  244                                 let xs = map (\v -> fromMaybe def $ HM.lookup v transmit) sendedVariableSeq
  245                                  in [__i|
  246                                         @(posedge #{ tag }_io_test_start_transaction);
  247                                             $write( "#{ tag }_io_test_output actual: %H except: %H ({ #{ toVerilogLiteral xs } })",
  248                                                 #{ tag }_io_test_output, { #{ toVerilogLiteral xs } } );
  249                                             if ( #{ tag }_io_test_output != { #{ toVerilogLiteral xs } } ) $display("\t\tFAIL");
  250                                             else $display();
  251 
  252                                     |]
  253 
  254                             endDeviceInstance =
  255                                 [__i|
  256                                     /*
  257                                     #{ pretty sio }
  258                                     */
  259                                     reg #{ tag }_io_test_start_transaction;
  260                                     reg  [#{ frameWidth }-1:0] #{ tag }_io_test_input;
  261                                     wire #{ tag }_io_test_ready;
  262                                     wire [#{ frameWidth }-1:0] #{ tag }_io_test_output;
  263                                     initial #{ envInitFlagName } <= 0; // should be defined on the testbench level.
  264                                     spi_master_driver \#
  265                                             ( .DATA_WIDTH( #{ frameWidth } )
  266                                             , .SCLK_HALFPERIOD( 1 )
  267                                             ) #{ tag }_io_test
  268                                         ( .clk( #{ sigClk } )
  269                                         , .rst( #{ sigRst } )
  270                                         , .start_transaction( #{ tag }_io_test_start_transaction )
  271                                         , .data_in( #{ tag }_io_test_input )
  272                                         , .data_out( #{ tag }_io_test_output )
  273                                         , .ready( #{ tag }_io_test_ready )
  274                                         , .mosi( #{ slave_mosi } )
  275                                         , .miso( #{ slave_miso } )
  276                                         , .sclk( #{ slave_sclk } )
  277                                         , .cs( #{ slave_cs } )
  278                                         );
  279                                     initial #{ tag }_io_test.inner.shiftreg <= 0;
  280                                 |]
  281 
  282                             envDeviceControl =
  283                                 [__i|
  284                                     initial begin
  285                                         #{ tag }_io_test_start_transaction <= 0;
  286                                         #{ tag }_io_test_input <= 0;
  287                                         @(negedge #{ sigRst });
  288                                         repeat(#{ timeLag }) @(posedge #{ sigClk });
  289 
  290                                         #{ nest 4 $ vsep $ map receiveCycle receivedVarsValues }
  291                                         repeat ( 5 ) begin
  292                                             #{ nest 8 $ receiveCycle def }
  293                                         end
  294 
  295                                         // $finish; // DON'T DO THAT (with this line test can pass without data checking)
  296                                     end
  297                                 |]
  298                             envDeviceCheck =
  299                                 [__i|
  300                                     initial begin
  301                                         @(negedge #{ sigRst });
  302                                         repeat ( OUTPUT_LATENCY ) @(posedge #{ tag }_io_test_start_transaction); // latency
  303 
  304                                         #{ nest 4 $ vsep $ map sendingAssert sendedVarsValues }
  305                                         forever begin
  306                                             @(posedge spi_io_test_start_transaction);
  307                                             $display( "#{ tag }_io_test_output actual: %H", #{ tag }_io_test_output );
  308                                         end
  309                                     end
  310                                 |]
  311                          in -- FIXME: do not check output signals when we drop data
  312                             Just
  313                                 [__i|
  314                                     ////////////////////////////////////////
  315                                     // SPI test environment
  316                                     localparam NITTA_LATENCY = 1;
  317                                     localparam OUTPUT_LATENCY = 3;
  318 
  319                                     // SPI device in test environment
  320                                     #{ endDeviceInstance :: Verilog }
  321 
  322                                     // SPI device in test environment control
  323                                     #{ if frameWordCount == 0 then disable else envDeviceControl }
  324 
  325                                     // SPI device in test environment check
  326                                     #{ if frameWordCount == 0 then disable else envDeviceCheck }
  327 
  328                                     // SPI environment initialization flag set
  329                                     initial begin
  330                                         repeat ( NITTA_LATENCY ) @(posedge spi_io_test_start_transaction);
  331                                         spi_env_init_flag <= 1;
  332                                     end
  333                                 |]
  334                     SPIMaster{..} ->
  335                         let receiveCycle transmit =
  336                                 let xs = map (\v -> fromMaybe def $ transmit M.!? v) receivedVariablesSeq
  337                                  in [__i|
  338                                         #{ tag }_io_test_input = { #{ toVerilogLiteral xs } }; // #{ xs }
  339                                         @(posedge #{ tag }_io_test_ready);
  340                                     |]
  341 
  342                             sendingAssert transmit =
  343                                 let xs = map (\v -> fromMaybe def $ HM.lookup v transmit) sendedVariableSeq
  344                                  in [__i|
  345                                         @(posedge #{ tag }_io_test_ready);
  346                                             $display( "#{ tag }_io_test_output except: %H ({ #{ toVerilogLiteral xs } })", { #{ toVerilogLiteral xs } } );
  347                                             $display( "#{ tag }_io_test_output actual: %H", #{ tag }_io_test_output );
  348                                             if ( #{ tag }_io_test_output !=  { #{ toVerilogLiteral xs } } )
  349                                                 $display("                       FAIL");
  350                                             $display();
  351                                     |]
  352 
  353                             envInstance =
  354                                 [__i|
  355                                     /*
  356                                     #{ pretty sio }
  357                                     */
  358                                     reg #{ tag }_io_test_start_transaction;
  359                                     reg  [#{ frameWidth }-1:0] #{ tag }_io_test_input;
  360                                     wire #{ tag }_io_test_ready;
  361                                     wire [#{ frameWidth }-1:0] #{ tag }_io_test_output;
  362                                     initial #{ envInitFlagName } <= 0; // should be defined on the testbench level.
  363                                     spi_slave_driver \#
  364                                             ( .DATA_WIDTH( #{ frameWidth } )
  365                                             ) #{ tag }_io_test_slave
  366                                         ( .clk( #{ sigClk } )
  367                                         , .rst( #{ sigRst } )
  368                                         , .data_in( #{ tag }_io_test_input )
  369                                         , .data_out( #{ tag }_io_test_output )
  370                                         , .ready( #{ tag }_io_test_ready )
  371                                         , .mosi( #{ master_mosi } )
  372                                         , .miso( #{ master_miso } )
  373                                         , .sclk( #{ master_sclk } )
  374                                         , .cs( #{ master_cs } )
  375                                         );
  376                                 |]
  377 
  378                             interactions =
  379                                 [__i|
  380                                     // SPI Input signal generation
  381                                     initial begin
  382                                         @(negedge #{ sigRst });
  383                                         #{ nest 4 $ receiveCycle $ head receivedVarsValues }
  384                                         #{ envInitFlagName } <= 1;
  385 
  386                                         #{ nest 4 $ vsep $ map receiveCycle $ tail receivedVarsValues }
  387                                         repeat(70) @(posedge #{ sigClk });
  388                                         // $finish; // DON'T DO THAT (with this line test can pass without data checking)
  389                                     end
  390 
  391                                     // SPI Output signal checking
  392                                     initial begin
  393                                         @(negedge #{ sigRst });
  394                                         repeat(2) @(posedge #{ tag }_io_test_ready);
  395                                         #{ nest 4 $ vsep $ map sendingAssert sendedVarsValues }
  396                                     end
  397                                 |]
  398                          in Just (envInstance <> line <> line <> if frameWordCount == 0 then disable else interactions)
  399     testEnvironment _title _pu _env _tEnv = error "internal error"