{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Clash.Primitives.GHC.Int (intTF) where
import Clash.Core.Literal
(Literal(IntegerLiteral, IntLiteral, Int64Literal))
import Clash.Core.Term (Term(Literal))
import Clash.Core.Type (Type)
import Clash.Primitives.GHC.Literal
(literalTF, signed, signedLiteral, assign)
import Clash.Netlist.Types (BlackBox(BBTemplate))
import Clash.Netlist.BlackBox.Types
(BlackBoxFunction, Element(Arg, Result), emptyBlackBoxMeta
,BlackBoxMeta, bbKind, TemplateKind(TDecl))
getIntLit
:: Literal
-> Maybe Integer
getIntLit =
\case
IntegerLiteral i -> Just i
IntLiteral i -> Just i
Int64Literal i -> Just i
_ -> Nothing
intTF :: BlackBoxFunction
intTF = literalTF "GHC.Int.I" intTF'
intTF'
:: Bool
-> [Either Term Type]
-> Int
-> (BlackBoxMeta, BlackBox)
intTF' False [Left (Literal (getIntLit -> Just n))] intSize =
( emptyBlackBoxMeta
, BBTemplate [signedLiteral intSize n])
intTF' True [Left (Literal (getIntLit -> Just n))] intSize =
( emptyBlackBoxMeta
, BBTemplate (assign (Result False) [signedLiteral intSize n]))
intTF' _isDecl _args _intSize =
( emptyBlackBoxMeta {bbKind = TDecl }
, BBTemplate (assign (Result False) (signed (Arg False 0))))