genOperator1' :: (AST.Expr -> AST.Expr) -> dst -> CoreSyn.CoreBndr -> [AST.Expr] -> VHDLSession AST.Expr
genOperator1' op _ f [arg] = return $ op arg
+-- | Generate a unary operator application
+genNegation :: BuiltinBuilder
+genNegation = genVarArgs $ genExprRes genNegation'
+genNegation' :: dst -> CoreSyn.CoreBndr -> [Var.Var] -> VHDLSession AST.Expr
+genNegation' _ f [arg] = return $ op (varToVHDLExpr arg)
+ where
+ ty = Var.varType arg
+ (tycon, args) = Type.splitTyConApp ty
+ name = Name.getOccString (TyCon.tyConName tycon)
+ op = case name of
+ "SizedInt" -> AST.Neg
+ otherwise -> error $ "\nGenerate.genNegation': Negation allowed for type: " ++ show name
+
-- | Generate a function call from the destination binder, function name and a
-- list of expressions (its arguments)
genFCall :: Bool -> BuiltinBuilder
, (hwnotId , (1, genOperator1 AST.Not ) )
, (plusId , (2, genOperator2 (AST.:+:) ) )
, (timesId , (2, genOperator2 (AST.:*:) ) )
- , (negateId , (1, genOperator1 AST.Neg ) )
+ , (negateId , (1, genNegation ) )
, (minusId , (2, genOperator2 (AST.:-:) ) )
, (fromSizedWordId , (1, genFromSizedWord ) )
, (fromIntegerId , (1, genFromInteger ) )
import qualified UniqSupply
import qualified CoreUtils
import qualified Type
+import qualified TcType
import qualified Id
import qualified Var
import qualified VarSet
+import qualified NameSet
import qualified CoreFVs
import qualified CoreUtils
import qualified MkCore
let used_funcs = VarSet.varSetElems used_funcs_set
-- Process each of the used functions recursively
mapM normalizeBind used_funcs
+ -- FIXME: Can't we inline these 'implicit' function calls or something?
+ -- TODO: Add an extra let expression to the current finding, so the VHDL
+ -- Will make a signa assignment for this 'implicit' function call
+ --
+ -- Find all the other free variables used that are used. This applies to
+ -- variables that are actually a reference to a Class function. Example:
+ --
+ -- functiontest :: SizedInt D8 -> SizedInt D8
+ -- functiontest = \a -> let r = a + 1 in r
+ --
+ -- The literal(Lit) '1' will be turned into a variable (Var)
+ -- As it will call the 'fromInteger' class function that belongs
+ -- to the Num class. So we need to translate the refenced function
+ -- let used_vars_set = CoreFVs.exprSomeFreeVars (\v -> (Type.isAlgType . snd . Type.splitForAllTys . Id.idType) v) expr'
+ -- let used_vars = VarSet.varSetElems used_vars_set
+ -- -- Filter for dictionary args, they should not be translated
+ -- -- FIXME: check for other non-translatable stuff as well
+ -- let trans_vars = filter (\v -> (not . TcType.isDictTy . Id.idType) v) used_vars
+ -- mapM normalizeBind trans_vars
return ()
-- We don't have a value for this binder. This really shouldn't
-- happen for local id's...
maintainer: christiaan.baaij@gmail.com & matthijs@stdin.nl
build-depends: base > 4, syb, ghc, ghc-paths, transformers, haskell98,
ForSyDe > 3.0, regex-posix ,data-accessor-template, pretty,
- data-accessor, containers, prettyclass, tfp > 0.3,
+ data-accessor, containers, prettyclass, tfp > 0.3.1,
tfvec > 0.1.2, QuickCheck, template-haskell, filepath
executable: clash