never executed always true always false
    1 {-# LANGUAGE AllowAmbiguousTypes #-}
    2 {-# LANGUAGE OverloadedStrings #-}
    3 
    4 {-# OPTIONS -fno-warn-orphans #-}
    5 
    6 {- |
    7 Module      : NITTA.Project.Types
    8 Description : Types for a target project description and generation
    9 Copyright   : (c) Aleksandr Penskoi, 2019
   10 License     : BSD3
   11 Maintainer  : aleksandr.penskoi@gmail.com
   12 Stability   : experimental
   13 -}
   14 module NITTA.Project.Types (
   15     Project (..),
   16     defProjectTemplates,
   17     TargetSystemComponent (..),
   18     Implementation (..),
   19     UnitEnv (..),
   20     envInputPorts,
   21     envOutputPorts,
   22     envInOutPorts,
   23 ) where
   24 
   25 import Data.Default
   26 import Data.Set qualified as S
   27 import Data.Text qualified as T
   28 import NITTA.Intermediate.Types
   29 import NITTA.Intermediate.Value ()
   30 import NITTA.Model.ProcessorUnits.Types
   31 import NITTA.Utils
   32 
   33 {- | Target project for different purpose (testing, target system, etc). Should
   34 be writable to disk.
   35 -}
   36 
   37 -- FIXME: collision between target project name and output directory. Maybe
   38 -- pName or pTargetProjectPath should be maybe? Or both?
   39 data Project m v x = Project
   40     { pName :: T.Text
   41     -- ^ target project name
   42     , pLibPath :: FilePath
   43     -- ^ IP-core library path
   44     , pTargetProjectPath :: FilePath
   45     -- ^ output path for target project
   46     , pAbsTargetProjectPath :: FilePath
   47     -- ^ absolute output path for target project
   48     , pInProjectNittaPath :: FilePath
   49     -- ^ relative to the project path output path for NITTA processor inside target project
   50     , pAbsNittaPath :: FilePath
   51     -- ^ absolute output path for NITTA processor inside target project
   52     , pUnit :: m
   53     -- ^ 'mUnit' model (a mUnit unit for testbench or network for complete NITTA mUnit)
   54     , pUnitEnv :: UnitEnv m
   55     , pTestCntx :: Cntx v x
   56     -- ^ testbench context with input values
   57     , pTemplates :: [FilePath]
   58     -- ^ Target platform templates
   59     }
   60 
   61 defProjectTemplates :: [FilePath]
   62 defProjectTemplates =
   63     [ "templates/Icarus"
   64     , "templates/DE0-Nano"
   65     ]
   66 
   67 instance Default x => DefaultX (Project m v x) x
   68 
   69 -- | Type class for target components. Target -- a target system project or a testbench.
   70 class TargetSystemComponent pu where
   71     -- | Name of the structural hardware module or Verilog module name (network or process unit)
   72     moduleName :: T.Text -> pu -> T.Text
   73 
   74     -- | Software and other specification which depends on application algorithm
   75     software :: T.Text -> pu -> Implementation
   76 
   77     -- | Hardware which depends on microarchitecture description and requires synthesis.
   78     hardware :: T.Text -> pu -> Implementation
   79 
   80     -- | Generate code for making an instance of the hardware module
   81     hardwareInstance :: T.Text -> pu -> UnitEnv pu -> Verilog
   82 
   83 -- | Element of target system implementation
   84 data Implementation
   85     = -- | Immediate implementation in the from of Ginger template (@nitta.paths.nest@ + 'projectContext')
   86       Immediate {impFileName :: FilePath, impText :: T.Text}
   87     | -- | Fetch implementation from library
   88       FromLibrary {impFileName :: FilePath}
   89     | -- | Aggregation of many implementation parts in separate paths
   90       Aggregate {impPath :: Maybe FilePath, subComponents :: [Implementation]}
   91     | -- | Nothing
   92       Empty
   93 
   94 {- | Resolve uEnv element to verilog source code. E.g. `dataIn` into
   95 `data_bus`, `dataOut` into `accum_data_out`.
   96 -}
   97 data UnitEnv m = UnitEnv
   98     { sigClk :: T.Text
   99     -- ^ clock signal
  100     , sigRst :: T.Text
  101     -- ^ reset signal
  102     , sigCycleBegin :: T.Text
  103     -- ^ posedge on computation cycle begin
  104     , sigInCycle :: T.Text
  105     -- ^ positive on computation cycle
  106     , sigCycleEnd :: T.Text
  107     -- ^ posedge on computation cycle end
  108     , ctrlPorts :: Maybe (Ports m)
  109     , ioPorts :: Maybe (IOPorts m)
  110     , valueIn, valueOut :: Maybe (T.Text, T.Text)
  111     }
  112 
  113 instance Default (UnitEnv m) where
  114     def =
  115         UnitEnv
  116             { sigClk = "clk"
  117             , sigRst = "rst"
  118             , sigCycleBegin = "flag_cycle_begin"
  119             , sigInCycle = "flag_in_cycle"
  120             , sigCycleEnd = "flag_cycle_end"
  121             , ctrlPorts = Nothing
  122             , ioPorts = Nothing
  123             , valueIn = Nothing
  124             , valueOut = Nothing
  125             }
  126 
  127 envInputPorts UnitEnv{ioPorts = Just ports} = inputPorts ports
  128 envInputPorts UnitEnv{ioPorts = Nothing} = S.empty
  129 
  130 envOutputPorts UnitEnv{ioPorts = Just ports} = outputPorts ports
  131 envOutputPorts UnitEnv{ioPorts = Nothing} = S.empty
  132 
  133 envInOutPorts UnitEnv{ioPorts = Just ports} = inoutPorts ports
  134 envInOutPorts UnitEnv{ioPorts = Nothing} = S.empty