Hi Matthew,
Although it doesn't "really" answer you question, you could take the
same approach as I did with CLaSH (http://clash-lang.org/) which
translates Haskell to VHDL/(System)Verilog.
Although I didn't want to "expose" VHDL/(System)Verilog terms and types
per sé, I guess you could see it like that in a way.
Let's take a look at the BitVector type
(http://hackage.haskell.org/package/clash-prelude-0.10.13/docs/CLaSH-Sized-Internal-BitVector.html)
for example.
= Exposing data types =
You could, in a way, say that the BitVector type, and its operations,
are the "exposed" std_logic_vector/bitvector types and operations of
VHDL/(System)Verilog.
So, I "exposed" the bitvector/std_logic_vector type as:
> import GHC.TypeLits
>
> newtype BitVector (n :: Nat) = BV {unsafeToInteger :: Integer}
Now, there are, using newtypes can be a bit "dangerous" as GHC will have
the tendency to coerce between newtypes and it's underlying representation.
That, and if you use
https://downloads.haskell.org/~ghc/8.0.1/docs/html/libraries/ghc-8.0.1/Type.html#v:coreView,
you might accidentally look through the newtype.
So, perhaps a safer way is to just do:
> data BitVector (n :: Nat) = BV {unsafeToInteger :: Integer}
Also, I use 'Integer' as the underlying representation because I want to
"simulate" my circuits in Haskell.
However, if you dont't care about this, you might as well use '()'.
= Exposing functions =
You mentioned that GHC does name mangling, but I must say I've never
seen GHC do this.
What GHC does do is inlining and specialisation, which might optimise
away your carefully constructed "primitive".
What I do in this case, is simply mark my "primitive" function, your
"exposed" BlueSpec functions, as NOINLINE.
For example, I define equality on BitVector as:
> instance Eq (BitVector n) where
> (==) = eq#
> (/=) = neq#
>
> {-# NOINLINE eq# #-}
> eq# :: BitVector n -> BitVector n -> Bool
> eq# (BV v1) (BV v2) = v1 == v2
>
> {-# NOINLINE neq# #-}
> neq# :: BitVector n -> BitVector n -> Bool
> neq# (BV v1) (BV v2) = v1 /= v2
Again, I want to "simulate" my circuits, so I've given actual
definitions for my operations.
But if you don't care for this, you can simply leave them as 'undefined'.
= Wrapping up =
So I hope it's clear how to "expose" target terms and types through
simple data type wrapping and the use of NOINLINE.
You'll have to do the above for all the BlueSpec data types and
functions you want to expose and then package it up.
Perhaps also, if you have the time, using BlueSpec's FFI and Haskell's
FFI, you could hook up the "exposed" operations to BlueSim, and have
"co-simulation" between Haskell and BlueSpec.
Anyhow, I hope this helps. Let me know if you have any more questions.
Regards,
Christiaan
On 08/24/2016 02:05 AM, Matthew Farkas-Dyck via Glasgow-haskell-users wrote:
A colleague and i are writing, as an unofficial side project, a
Haskell→Bluespec compiler, using GHC as our Haskell front-end. The
source language of the part we are writing is GHC Core. We need to
somehow expose some Bluespec terms and types to the Haskell source
program. We had a few ideas:
1. Some "NO_MANGLE" pragma which would tell GHC to not mangle the
emitted name, e.g. `x = {-# NO_MANGLE #-} x` to expose `x`
2. `foreign import prim`, not quite sure how yet
3. "CORE" pragmas, e.g. `x = {-# CORE "foo" #-} x` to expose `x`
4. "ANN" pragmas, e.g. `{-# ANN x "no_mangle" #-} x = x` to expose `x`
1 and 2 would mean modifying GHC which we'd rather not do. For 3,
we're not sure how to find the "CORE"-pragmatic annotations in a
`Core` AST. 4 seems it would work but be a little cumbersome, as the
annotation is not on the `Core` AST.
Anyone know a good way to do this?
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users