<div dir="ltr">Hi Aura,<div><br></div><div>I recently added a typed module for exactly this data in clang-pure: <a href="https://hackage.haskell.org/package/clang-pure-0.2.0.2/docs/Language-C-Clang-Cursor-Typed.html">https://hackage.haskell.org/package/clang-pure-0.2.0.2/docs/Language-C-Clang-Cursor-Typed.html</a></div><div><br></div><div>As in libclang, the AST is represented as a tree of Cursors, which have a CursorKind such as StructDecl, CallExpr etc.</div><div>In Haskell it's possible to lift this CursorKind to the type level, so you know at compile-time what kind of Cursor you're dealing with.</div><div>This is useful because only certain kinds of Cursors have certain types of properties, for example source extent, spelling etc.</div><div><br></div><div>You can use</div><div><br></div><div>matchKind :: forall kind. SingI kind => Cursor -> Maybe (CursorK kind)</div><div><br></div><div>to convert an untyped Cursor into a Cursor with a particular known kind. Then, if you search the AST and only look at cursors where this function returns Just,</div><div>you know that the given cursor has certain properties you expect.</div><div><br></div><div>Patrick</div></div><div class="gmail_extra"><br><div class="gmail_quote">On Thu, Dec 8, 2016 at 1:19 PM, Aura Kelloniemi <span dir="ltr"><<a href="mailto:kaura.dev@sange.fi" target="_blank">kaura.dev@sange.fi</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Hello<br>
<br>
This is my first post to Haskell Café. I am a hobbyist programmer who has lots<br>
of experience with imperative and OO languages ranging from 80286 assembly to<br>
Ada and Ruby. Last four years I've been learning Haskell, which has been a<br>
painfully educational experience - I have a good understanding about how CPUs<br>
work, but very little understanding about maths. This is a very long post, I apologize.<br>
<br>
Now I'm trying to create a tool which automatically generates foreign function<br>
interface (FFI) imports from C and C++ to Haskell. I have written a GCC plugin<br>
which extracts all relevant (and lots of irrelevant) information from GCC's<br>
TREEs and dumps the output as JSON. It also dumps preprocessor macros which is<br>
one of the reasons this tol is being given birth.<br>
<br>
The tool is used like Shake - import Development.Familiar and write code which<br>
glues all relevant data processing and FFI generation functions together.<br>
<br>
This is also going to be a reusable library which others can use for whatever<br>
they find the data to be useful for. This could include making FFI bindings to<br>
other languages. Some code analysis tools also might find the data useful.<br>
<br>
I'm having a hard time importing this data to Haskell in a type safe way.<br>
GCC's TREEs are structured in an OO way. I have tried to find a more<br>
functional way of representing them, but so far with no luck.<br>
<br>
The JSON data is typed, and the hierarchy is exactly the same as in GCC. Below<br>
I construct a tree of the hierarchy where I list a few of possible types and<br>
very few of the fields the data types contain. For listing fields and their<br>
types I use a syntax similar to Haskell. This shortened listing should be<br>
enough for illustration:<br>
<br>
* macro: (data fields include: name :: string, tokens :: [token], etc.)<br>
* tree: all nodes have a unique ID to be able to recover the cycles<br>
    among the node graph; (id :: integer)<br>
* * translation_unit: (declarations :: [top_level_declaration])<br>
* * constant: a compile-time constant value; (type :: type)<br>
* * * complex_constant: (value :: complex)<br>
* * * integer_constant: (value :: integer)<br>
* * namespace_decl: (name :: identifier,<br>
                     declarations :: [top_level_declaration])<br>
* * declaration: (name :: identifier, type :: type)<br>
* * * const_decl: One component of enum type; (value :: type)<br>
* * * function_decl: (type :: function_type, params :: [param_decl],<br>
                      result :: result_decl)<br>
* * * type_decl: (no additional fields)<br>
* * type: (declaration :: type_decl, name :: identifier,<br>
           size :: integer_constant, alignment :: integer,<br>
           qualifiers :: [qualifier], completeness :: bool)<br>
* * * array_type: (element_type :: type, element_count :: integer)<br>
* * * numeric_type: (precision :: integer, signed :: bool,<br>
                     min_value :: integer_constant,<br>
                     max_value :: integer_constant)<br>
* * * * enumeral_type: (values :: [const_decl])<br>
* * * function_type: (param_types :: [type], result_type :: type)<br>
* * * pointer_type: (referred_type :: type)<br>
* * * record_type: struct (C or C++)/union;<br>
        (base_types :: [(type, access_info)],<br>
         fields :: [field_decl or const_decl or type_decl],<br>
         methods :: [method_decl])<br>
* reference: Any node may be replaced by a reference. They can be<br>
    forward or backward references. (referred_id :: integer)<br>
<br>
As you may see, tree nodes form many many cycles together. Subclasses<br>
sometimes provide stronger invariants for their fields than the parent<br>
classes. For example all declarations are associated with a type and for<br>
function_decl nodes this type is always a function_type.<br>
<br>
Now to my question. How to represent this in Haskell. Because of the enormous<br>
amount of fields per tree node, I certainly need to use records.<br>
<br>
-- Haskell follows:<br>
data BaseTree = BaseTree { id :: Int, ... ... }<br>
data BaseDecl = BaseDecl { baseTree :: BaseTree, name :: Identifier,<br>
                           declType :: Type, ... }<br>
data ConstDecl = ConstDecl { baseDecl :: BaseDecl, value :: ConstValue }<br>
data ConstValue = ComplexConst Complex | IntegerConst Integer<br>
data TypeDecl = TypeDecl { baseDecl :: BaseDecl }<br>
<br>
But... What shall I do about the heterogenous lists which many nodes contain.<br>
I wish I don't need to make myriards of ADTs for them, like:<br>
<br>
data AnyTopLevelDecl = ATLDConst ConstDecl<br>
                     | ATLDFunction FunctionDecl<br>
                     | ATLDNamespace NamespaceDecl<br>
                     | ATLDType TypeDecl -- ...<br>
data StructFieldDecl = SFDConst ConstDecl<br>
                     | SFDField FieldDecl<br>
                     | SFDType TypeDecl<br>
<br>
And so forth, basicly each heterogenous list gets its own ADT, because there<br>
is often variance in which node types can appear in the lists.<br>
<br>
I could use one big ADT like AnyDecl. However, to me it would feel like a bad<br>
design, if my types allowed RecordType nodes to reference NamespaceDecls, and<br>
therefore I don't want to pack all nodes into one type, unless I could use<br>
some type parameters or constraints to restrict the possible values the ADT<br>
could take.<br>
<br>
At first I thought that the following could solve my problem:<br>
<br>
data SomeDecl a = SomeDecl where<br>
    SomeConst :: ConstDecl -> SomeDecl ConstDecl<br>
    SomeField :: FieldDecl ->SomeDecl FieldDecl<br>
    SomeFunction :: FunctionDecl -> SomeDecl FunctionDecl<br>
    SomeType :: TypeDecl -> SomeDecl TypeDecl<br>
<br>
-- and then I would use type classes like this<br>
class TopLevelDecl decl where<br>
    -- No methods needed<br>
instance TopLevelDecl ConstDecl<br>
instance TopLevelDecl FunctionDecl<br>
instance TopLevelDecl TypeDecl<br>
<br>
-- And then I could write functions like this:<br>
handleTopLevelDecl :: TopLevelDecl d => SomeDecl d -> Whatever<br>
handleTopLevelDecl (FunctionDecl f) = -- ...<br>
-- and I'd list all cases which have a TopLevelDecl instance, but not<br>
-- those which don't have. I also thought that my data types could look like<br>
-- this:<br>
<br>
data NamespaceDecl where<br>
    NamespaceDecl :: {<br>
        baseTree :: BaseTree,<br>
        forall a. TopLevelDecl a => declarations :: [a]<br>
        }<br>
<br>
Obviously this does not work, because type classes are open, and even though<br>
GHC prevents me from calling handleTopLevelDecl with (SOmeDecl FieldDecl), it<br>
still complains if I don't define an equation for it, because in some other<br>
module somebody might make a TopLevelDecl instance for FieldDecl.<br>
<br>
Now I would like to know if there is a way to solve my problem in an elegant<br>
way, e.g. by using type families.<br>
<br>
My second question is how to resolve the cyclicity of the node graph. I don't<br>
want to tie the knot, because I want to be able to manipulate the graph.<br>
<br>
Maps are one option, yes:<br>
<br>
data AnyNode = (list all possible nodes)<br>
type Id = Int<br>
type NodeIdMap = Map Id AnyNode<br>
<br>
-- Then my data types refer to other nodes like this:<br>
data FunctionDecl = FunctionDecl {<br>
    parameters :: [Id]<br>
    }<br>
<br>
Now I lose all type safety. I would have to insert a run-time check to every<br>
dereference of an Id if I want to make sure that function parameter<br>
declarations don't contain StringConstants.<br>
<br>
I've also considered using STRefs. During JSON parsing I would need to<br>
populate the nodes with the node Ids they refer to and then have a separate<br>
pass which turns all Ids to typed STRefs. At least with this approach I would<br>
get all possible run-time errors straight after parsing, and not when the data<br>
is used.<br>
<br>
I'm again sorry for this long elaboration. However I think that if you<br>
consider answering me you have a pretty good understanding of my problem and<br>
also a good knowledge of my level of understanding Haskell. I would like to<br>
unlearn OO-style thinking, and I would want to find a data and type<br>
representation which feels Haskellish. However I don't want to cut down the<br>
data. I want all information to be accessible in case somebody needs it.<br>
<br>
Thank you in advance!<br>
<span class="HOEnZb"><font color="#888888"><br>
--<br>
Aura<br>
______________________________<wbr>_________________<br>
Haskell-Cafe mailing list<br>
To (un)subscribe, modify options or view archives go to:<br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-<wbr>bin/mailman/listinfo/haskell-<wbr>cafe</a><br>
Only members subscribed via the mailman list are allowed to post.</font></span></blockquote></div><br></div>