{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
module Clash.Annotations.BitRepresentation.Internal
( buildCustomReprs
, dataReprAnnToDataRepr'
, constrReprToConstrRepr'
, getConstrRepr
, uncheckedGetConstrRepr
, getDataRepr
, thTypeToType'
, ConstrRepr'(..)
, DataRepr'(..)
, Type'(..)
, CustomReprs
) where
import Clash.Annotations.BitRepresentation
(BitMask, Value, Size, FieldAnn, DataReprAnn(..), ConstrRepr(..))
import Control.DeepSeq (NFData)
import Data.Coerce (coerce)
import Data.Hashable (Hashable)
import qualified Data.Map as Map
import Data.Maybe (fromMaybe)
import qualified Data.Text as Text
import Data.Typeable (Typeable)
import qualified Language.Haskell.TH.Syntax as TH
import GHC.Generics (Generic)
import GHC.Stack (HasCallStack)
import qualified TextShow as TS
import qualified TextShow.Generic as TS
data Type'
= AppTy' Type' Type'
| ConstTy' Text.Text
| LitTy' Integer
deriving (Generic, NFData, Eq, Typeable, Hashable, Ord, Show)
instance TS.TextShow Type' where
showt = TS.showt . coerce @_ @(TS.FromGeneric (Type'))
showb = TS.showb . coerce @_ @(TS.FromGeneric (Type'))
data DataRepr' = DataRepr'
{ drType :: Type'
, drSize :: Size
, drConstrs :: [ConstrRepr']
}
deriving (Show, Generic, NFData, Eq, Typeable, Hashable, Ord)
data ConstrRepr' = ConstrRepr'
{ crName :: Text.Text
, crPosition :: Int
, crMask :: BitMask
, crValue :: Value
, crFieldAnns :: [FieldAnn]
}
deriving (Show, Generic, NFData, Eq, Typeable, Ord, Hashable)
constrReprToConstrRepr' :: Int -> ConstrRepr -> ConstrRepr'
constrReprToConstrRepr' n (ConstrRepr name mask value fieldanns) =
ConstrRepr' (thToText name) n mask value (map fromIntegral fieldanns)
dataReprAnnToDataRepr' :: DataReprAnn -> DataRepr'
dataReprAnnToDataRepr' (DataReprAnn typ size constrs) =
DataRepr' (thTypeToType' typ) size (zipWith constrReprToConstrRepr' [0..] constrs)
thToText :: TH.Name -> Text.Text
thToText (TH.Name (TH.OccName name') (TH.NameG _namespace _pkgName (TH.ModName modName))) =
Text.pack $ modName ++ "." ++ name'
thToText name' = error $ "Unexpected pattern: " ++ show name'
thTypeToType' :: TH.Type -> Type'
thTypeToType' ty = go ty
where
go (TH.ConT name') = ConstTy' (thToText name')
go (TH.AppT ty1 ty2) = AppTy' (go ty1) (go ty2)
go (TH.LitT (TH.NumTyLit n)) = LitTy' n
go _ = error $ "Unsupported type: " ++ show ty
type CustomReprs =
( Map.Map Type' DataRepr'
, Map.Map Text.Text ConstrRepr'
)
getDataRepr :: Type' -> CustomReprs -> Maybe DataRepr'
getDataRepr name (reprs, _) = Map.lookup name reprs
getConstrRepr :: Text.Text -> CustomReprs -> Maybe ConstrRepr'
getConstrRepr name (_, reprs) = Map.lookup name reprs
uncheckedGetConstrRepr
:: HasCallStack
=> Text.Text
-> CustomReprs
-> ConstrRepr'
uncheckedGetConstrRepr name (_, reprs) =
fromMaybe
(error ("Could not find custom representation for" ++ Text.unpack name))
(Map.lookup name reprs)
addCustomRepr :: CustomReprs -> DataRepr' -> CustomReprs
addCustomRepr (dMap, cMap) d@(DataRepr' name _size constrReprs) =
let insertConstr c@(ConstrRepr' name' _ _ _ _) cMap' = Map.insert name' c cMap' in
(Map.insert name d dMap, foldr insertConstr cMap constrReprs)
buildCustomReprs :: [DataRepr'] -> CustomReprs
buildCustomReprs = foldl addCustomRepr (Map.empty, Map.empty)