{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Clash.Primitives.Types where
import Control.Applicative ((<|>))
import Data.Aeson (FromJSON (..), Value (..), (.:), (.:?), (.!=))
import Data.HashMap.Lazy (HashMap)
import qualified Data.HashMap.Strict as H
import qualified Data.Text as S
import Data.Text.Lazy (Text)
type PrimMap a = HashMap S.Text (Primitive a)
data Primitive a
= BlackBox
{ name :: !S.Text
, outputReg :: Bool
, library :: [a]
, imports :: [a]
, include :: Maybe ((S.Text,S.Text),a)
, template :: !(Either a a)
}
| Primitive
{ name :: !S.Text
, primType :: !Text
}
deriving Show
instance FromJSON (Primitive Text) where
parseJSON (Object v) = case H.toList v of
[(conKey,Object conVal)] -> case conKey of
"BlackBox" -> BlackBox <$> conVal .: "name"
<*> conVal .:? "outputReg" .!= False
<*> conVal .:? "libraries" .!= []
<*> conVal .:? "imports" .!= []
<*> (conVal .:? "include" >>= parseInclude)
<*> ((Left <$> conVal .: "templateD") <|> (Right <$> conVal .: "templateE"))
"Primitive" -> Primitive <$> conVal .: "name" <*> conVal .: "primType"
_ -> error "Expected: BlackBox or Primitive object"
_ -> error "Expected: BlackBox or Primitive object"
where
parseInclude Nothing = pure Nothing
parseInclude (Just c) =
Just <$> ((,) <$> ((,) <$> c .: "name" <*> c .: "extension") <*> c .: "content")
parseJSON _ = error "Expected: BlackBox or Primitive object"