{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
module Clash.Primitives.Types
( TemplateSource(..)
, TemplateKind(..)
, TemplateFormat(..)
, BlackBoxFunctionName(..)
, Primitive(..)
, UsedArguments(..)
, GuardedCompiledPrimitive
, GuardedResolvedPrimitive
, PrimMap
, UnresolvedPrimitive
, ResolvedPrimitive
, ResolvedPrimMap
, CompiledPrimitive
, CompiledPrimMap
) where
import {-# SOURCE #-} Clash.Netlist.Types
import Clash.Annotations.Primitive (PrimitiveGuard)
import Clash.Core.Term (WorkInfo (..))
import Clash.Netlist.BlackBox.Types
(BlackBoxFunction, BlackBoxTemplate, TemplateKind (..), RenderVoid(..))
import Control.Applicative ((<|>))
import Control.DeepSeq (NFData)
import Data.Aeson
(FromJSON (..), Value (..), (.:), (.:?), (.!=))
import Data.Binary (Binary)
import Data.Char (isUpper, isLower, isAlphaNum)
import Data.Either (lefts)
import Data.Hashable (Hashable)
import qualified Data.HashMap.Strict as H
import Data.List (intercalate)
import qualified Data.Text as S
import Data.Text.Lazy (Text)
import GHC.Generics (Generic)
import GHC.Stack (HasCallStack)
type UnresolvedPrimitive = Primitive Text ((TemplateFormat,BlackBoxFunctionName),Maybe TemplateSource) (Maybe S.Text) (Maybe TemplateSource)
type ResolvedPrimitive = Primitive Text ((TemplateFormat,BlackBoxFunctionName),Maybe Text) () (Maybe Text)
type GuardedResolvedPrimitive = PrimitiveGuard ResolvedPrimitive
type ResolvedPrimMap = PrimMap GuardedResolvedPrimitive
type CompiledPrimitive = Primitive BlackBoxTemplate BlackBox () (Int, BlackBoxFunction)
type GuardedCompiledPrimitive = PrimitiveGuard CompiledPrimitive
type CompiledPrimMap = PrimMap GuardedCompiledPrimitive
type PrimMap a = H.HashMap S.Text a
data BlackBoxFunctionName =
BlackBoxFunctionName [String] String
deriving (Eq, Generic, NFData, Binary, Hashable)
instance Show BlackBoxFunctionName where
show (BlackBoxFunctionName mods funcName) =
"BBFN<" ++ intercalate "." mods ++ "." ++ funcName ++ ">"
splitOn :: String -> String -> [String]
splitOn (S.pack -> sep) (S.pack -> str) =
map S.unpack $ S.splitOn sep str
parseBBFN
:: HasCallStack
=> String
-> Either String BlackBoxFunctionName
parseBBFN bbfn =
case splitOn "." bbfn of
[] -> Left $ "Empty function name: " ++ bbfn
[_] -> Left $ "No module or function defined: " ++ bbfn
nms ->
let (mods, func) = (init nms, last nms) in
let errs = lefts $ checkFunc func : map checkMod mods in
case errs of
[] -> Right $ BlackBoxFunctionName mods func
_ -> Left $ "Error while parsing " ++ show bbfn ++ ": " ++ head errs
where
checkMod mod'
| isLower (head mod') =
Left $ "Module name cannot start with lowercase: " ++ mod'
| any (not . isAlphaNum) mod' =
Left $ "Module name must be alphanumerical: " ++ mod'
| otherwise =
Right mod'
checkFunc func
| isUpper (head func) =
Left $ "Function name must start with lowercase: " ++ func
| otherwise =
Right func
data TemplateSource
= TFile FilePath
| TInline Text
deriving (Show, Eq, Generic, NFData)
data TemplateFormat
= TTemplate
| THaskell
deriving (Show, Generic, Hashable, NFData)
data UsedArguments
= UsedArguments [Int]
| IgnoredArguments [Int]
deriving (Show, Generic, Hashable, NFData, Binary)
data Primitive a b c d
= BlackBox
{ name :: !S.Text
, workInfo :: WorkInfo
, renderVoid :: RenderVoid
, kind :: TemplateKind
, warning :: c
, outputReg :: Bool
, libraries :: [a]
, imports :: [a]
, functionPlurality :: [(Int, Int)]
, includes :: [((S.Text,S.Text),b)]
, resultName :: Maybe b
, resultInit :: Maybe b
, template :: b
}
| BlackBoxHaskell
{ name :: !S.Text
, workInfo :: WorkInfo
, usedArguments :: UsedArguments
, functionName :: BlackBoxFunctionName
, function :: d
}
| Primitive
{ name :: !S.Text
, workInfo :: WorkInfo
, primSort :: !Text
}
deriving (Show, Generic, NFData, Binary, Hashable, Functor)
instance FromJSON UnresolvedPrimitive where
parseJSON (Object v) =
case H.toList v of
[(conKey,Object conVal)] ->
case conKey of
"BlackBoxHaskell" -> do
usedArguments <- conVal .:? "usedArguments"
ignoredArguments <- conVal .:? "ignoredArguments"
args <-
case (usedArguments, ignoredArguments) of
(Nothing, Nothing) -> pure (IgnoredArguments [])
(Just a, Nothing) -> pure (UsedArguments a)
(Nothing, Just a) -> pure (IgnoredArguments a)
(Just _, Just _) ->
fail "[8] Don't use both 'usedArguments' and 'ignoredArguments'"
name' <- conVal .: "name"
wf <- ((conVal .:? "workInfo" >>= maybe (pure Nothing) parseWorkInfo) .!= WorkVariable)
fName <- conVal .: "templateFunction"
templ <- (Just . TInline <$> conVal .: "template")
<|> (Just . TFile <$> conVal .: "file")
<|> (pure Nothing)
fName' <- either fail return (parseBBFN fName)
return (BlackBoxHaskell name' wf args fName' templ)
"BlackBox" ->
BlackBox <$> conVal .: "name"
<*> (conVal .:? "workInfo" >>= maybe (pure Nothing) parseWorkInfo) .!= WorkVariable
<*> conVal .:? "renderVoid" .!= NoRenderVoid
<*> (conVal .: "kind" >>= parseTemplateKind)
<*> conVal .:? "warning"
<*> conVal .:? "outputReg" .!= False
<*> conVal .:? "libraries" .!= []
<*> conVal .:? "imports" .!= []
<*> pure []
<*> (conVal .:? "includes" .!= [] >>= traverse parseInclude)
<*> (conVal .:? "resultName" >>= maybe (pure Nothing) parseResult) .!= Nothing
<*> (conVal .:? "resultInit" >>= maybe (pure Nothing) parseResult) .!= Nothing
<*> parseTemplate conVal
"Primitive" ->
Primitive <$> conVal .: "name"
<*> (conVal .:? "workInfo" >>= maybe (pure Nothing) parseWorkInfo) .!= WorkVariable
<*> conVal .: "primType"
e -> fail $ "[1] Expected: BlackBox or Primitive object, got: " ++ show e
e -> fail $ "[2] Expected: BlackBox or Primitive object, got: " ++ show e
where
parseTemplate c =
(,) <$> ((,) <$> (c .:? "format" >>= traverse parseTemplateFormat) .!= TTemplate
<*> (c .:? "templateFunction" >>= traverse parseBBFN') .!= defTemplateFunction)
<*> (Just . TInline <$> c .: "template" <|>
Just . TFile <$> c .: "file" <|>
pure Nothing)
parseInclude c =
(,) <$> ((,) <$> c .: "name" <*> c .: "extension")
<*> parseTemplate c
parseTemplateKind (String "Declaration") = pure TDecl
parseTemplateKind (String "Expression") = pure TExpr
parseTemplateKind c = fail ("[4] Expected: Declaration or Expression, got " ++ show c)
parseTemplateFormat (String "Template") = pure TTemplate
parseTemplateFormat (String "Haskell") = pure THaskell
parseTemplateFormat c = fail ("[5] unexpected format: " ++ show c)
parseWorkInfo (String "Constant") = pure (Just WorkConstant)
parseWorkInfo (String "Never") = pure (Just WorkNever)
parseWorkInfo (String "Variable") = pure (Just WorkVariable)
parseWorkInfo (String "Always") = pure (Just WorkAlways)
parseWorkInfo c = fail ("[6] unexpected workInfo: " ++ show c)
parseBBFN' = either fail return . parseBBFN
defTemplateFunction = BlackBoxFunctionName ["Template"] "template"
parseResult (Object c) =
Just . Just <$> parseTemplate c
parseResult e = fail $ "[7] unexpected result: " ++ show e
parseJSON unexpected =
fail $ "[3] Expected: BlackBox or Primitive object, got: " ++ show unexpected