abi: add struct types and move some terminal definitions

This commit is contained in:
Mark Poliakov 2024-03-13 13:11:46 +02:00
parent 2577e28ce1
commit 12b481398d
17 changed files with 296 additions and 152 deletions

View File

@ -47,12 +47,12 @@ fn generate_syscall_dispatcher<P: AsRef<Path>>(out_dir: P) {
fat_pointer_width: TypeWidth::U128,
},
)
.unwrap_fancy("");
.unwrap_fancy(yggdrasil_abi_def::ABI_FILE);
let generated_dispatcher = out_dir.as_ref().join("generated_dispatcher.rs");
let file = prettyplease::unparse(
&abi.emit_syscall_dispatcher("handle_syscall", "impls")
.unwrap_fancy(""),
.expect("Could not generate syscall dispatcher"),
);
fs::write(generated_dispatcher, file.as_bytes()).unwrap();

View File

@ -26,13 +26,11 @@ extern {
type FileMetadataUpdate = yggdrasil_abi::io::FileMetadataUpdate;
type DirectoryEntry = yggdrasil_abi::io::DirectoryEntry;
type FileAttr = yggdrasil_abi::io::FileAttr;
#[thin]
type SeekFrom = yggdrasil_abi::io::SeekFrom;
#[thin]
type MessageDestination = yggdrasil_abi::io::MessageDestination;
type TerminalOptions = yggdrasil_abi::io::TerminalOptions;
type TerminalSize = yggdrasil_abi::io::TerminalSize;
}
// abi::error
@ -80,6 +78,7 @@ enum Signal(u32) {
}
newtype ProcessId(u32);
newtype ProcessGroupId(u32);
newtype ThreadId(u32);
// abi::io
@ -148,6 +147,80 @@ enum PollControl(u32) {
AddFd = 1,
}
// abi::io::terminal
#[derive(Clone, Copy, Debug)]
#[repr(C)]
struct TerminalControlCharacters {
/// End-of-file character (0x04, ^D)
pub eof: u8,
/// Erase character (0x7F, ^?)
pub erase: u8,
/// Word erase character (0x17, ^W)
pub werase: u8,
/// Interrupt character (0x03, ^C)
pub interrupt: u8,
/// Kill character (0x15, ^U)
pub kill: u8,
}
/// Controls the line discipline of the terminal
#[default(SIGNAL | CANONICAL | ECHO | ECHO_ERASE | ECHO_KILL | ECHO_NL)]
bitfield TerminalLineOptions(u32) {
/// Enables signal processing for special bytes (INTR, QUIT, etc.)
SIGNAL: 0,
/// Enables canonical mode
CANONICAL: 1,
/// Echo input characters back
ECHO: 2,
/// If CANONICAL is set, ERASE character erases chars, WORD_ERASE erases words
ECHO_ERASE: 3,
/// If CANONICAL is set, KILL erases lines
ECHO_KILL: 4,
/// If CANONICAL is set, echo newline even if ECHO is not set
ECHO_NL: 5,
}
/// Defines how output to the terminal should be processed
#[default(NL_TO_CRNL)]
bitfield TerminalOutputOptions(u32) {
/// Translate \n to \r\n
NL_TO_CRNL: 0,
}
/// Defines how input should be presented to the reader
#[default(CR_TO_NL)]
bitfield TerminalInputOptions(u32) {
/// Translate \n to \r on input
NL_TO_CR: 0,
/// Translate \r to \n on input
CR_TO_NL: 1,
}
/// Terminal I/O transformation and control settings
#[derive(Clone, Copy, Debug)]
#[repr(C)]
struct TerminalOptions {
/// Controls output processing
pub output: TerminalOutputOptions,
/// Controls input processing
pub input: TerminalInputOptions,
/// Controls special bytes and line discipline
pub line: TerminalLineOptions,
/// Specifies control characters of the terminal
pub chars: TerminalControlCharacters,
}
/// Describes terminal size in rows and columns
#[derive(Clone, Copy, Debug)]
#[repr(C)]
struct TerminalSize {
/// Number of text rows
pub rows: usize,
/// Number of text columns
pub columns: usize,
}
// abi::net
enum SocketType(u32) {

View File

@ -17,7 +17,7 @@ fn generate_abi() {
fat_pointer_width: TypeWidth::U64,
},
)
.unwrap_fancy("Could not parse/read ABI file");
.unwrap_fancy(yggdrasil_abi_def::ABI_FILE);
let types = prettyplease::unparse(
&abi.emit_file(true, false)

View File

@ -1,83 +1,7 @@
use crate::bitflags;
bitflags! {
#[doc = "Defines how output to the terminal should be processed"]
#[default = (NL_TO_CRNL)]
pub struct TerminalOutputOptions: u32 {
#[doc = "Translate \n to \r\n"]
const NL_TO_CRNL: bit 0;
}
}
bitflags! {
#[doc = "Defines how input should be presented to the reader"]
#[default = (CR_TO_NL)]
pub struct TerminalInputOptions: u32 {
#[doc = "Translate \n to \r on input"]
const NL_TO_CR: bit 0;
#[doc = "Translate \r to \n on input"]
const CR_TO_NL: bit 1;
}
}
bitflags! {
#[doc = "Controls the line discipline of the terminal"]
#[default = (SIGNAL | CANONICAL | ECHO | ECHO_ERASE | ECHO_KILL | ECHO_NL)]
pub struct TerminalLineOptions: u32 {
#[doc = "Enables signal processing for special bytes (INTR, QUIT, etc.)"]
const SIGNAL: bit 0;
#[doc = "Enables canonical mode"]
const CANONICAL: bit 1;
#[doc = "Echo input characters back"]
const ECHO: bit 2;
#[doc = "If CANONICAL is set, ERASE character erases chars, WORD_ERASE erases words"]
const ECHO_ERASE: bit 3;
#[doc = "If CANONICAL is set, KILL erases lines"]
const ECHO_KILL: bit 4;
#[doc = "If CANONICAL is set, echo newline even if ECHO is not set"]
const ECHO_NL: bit 5;
}
}
/// Specifies a set of special control characters
#[derive(Clone, Copy, Debug)]
#[repr(C)]
pub struct TerminalControlCharacters {
/// End-of-file character (0x04, ^D)
pub eof: u8,
/// Erase character (0x7F, ^?)
pub erase: u8,
/// Word erase character (0x17, ^W)
pub werase: u8,
/// Interrupt character (0x03, ^C)
pub interrupt: u8,
/// Kill character (0x15, ^U)
pub kill: u8,
}
/// Terminal I/O transformation and control settings
#[derive(Clone, Copy, Debug)]
#[repr(C)]
pub struct TerminalOptions {
/// Controls output processing
pub output: TerminalOutputOptions,
/// Controls input processing
pub input: TerminalInputOptions,
/// Controls special bytes and line discipline
pub line: TerminalLineOptions,
/// Specifies control characters of the terminal
pub chars: TerminalControlCharacters,
}
/// Describes terminal size in rows and columns
#[derive(Clone, Copy, Debug)]
#[repr(C)]
pub struct TerminalSize {
/// Number of text rows
pub rows: usize,
/// Number of text columns
pub columns: usize,
}
pub use crate::generated::{
TerminalControlCharacters, TerminalInputOptions, TerminalLineOptions, TerminalOptions,
TerminalOutputOptions, TerminalSize,
};
impl TerminalControlCharacters {
/// const-version of [Default] trait impl

View File

@ -49,7 +49,7 @@ fn generate_abi() {
fat_pointer_width: TypeWidth::U64,
},
)
.unwrap_fancy("Could not parse/read ABI file");
.unwrap_fancy(yggdrasil_abi_def::ABI_FILE);
let calls = prettyplease::unparse(
&abi.emit_file(false, true)

View File

@ -12,7 +12,10 @@ mod generated {
// Import all the necessary types from generated ABI
use abi::{
error::Error,
io::{ChannelPublisherId, FileMode, OpenOptions, PollControl, RawFd},
io::{
ChannelPublisherId, FileMode, OpenOptions, PollControl, RawFd, TerminalOptions,
TerminalSize,
},
mem::MappingSource,
net::SocketType,
process::{ProcessId, Signal},

View File

@ -12,42 +12,6 @@ dependencies = [
"thiserror",
]
[[package]]
name = "abi-lib"
version = "0.1.0"
dependencies = [
"compiler_builtins",
"rustc-std-workspace-core",
]
[[package]]
name = "compiler_builtins"
version = "0.1.108"
source = "registry+https://github.com/rust-lang/crates.io-index"
checksum = "d68bc55329711cd719c2687bb147bc06211b0521f97ef398280108ccb23227e9"
dependencies = [
"rustc-std-workspace-core",
]
[[package]]
name = "example-abi"
version = "0.1.0"
dependencies = [
"abi-generator",
"abi-lib",
"prettyplease",
]
[[package]]
name = "prettyplease"
version = "0.2.16"
source = "registry+https://github.com/rust-lang/crates.io-index"
checksum = "a41cf62165e97c7f814d2221421dbb9afcbcdb0a88068e5ea206e19951c2cbb5"
dependencies = [
"proc-macro2",
"syn",
]
[[package]]
name = "proc-macro2"
version = "1.0.78"
@ -66,12 +30,6 @@ dependencies = [
"proc-macro2",
]
[[package]]
name = "rustc-std-workspace-core"
version = "1.0.0"
source = "registry+https://github.com/rust-lang/crates.io-index"
checksum = "1956f5517128a2b6f23ab2dadf1a976f4f5b27962e7724c2bf3d45e539ec098c"
[[package]]
name = "syn"
version = "2.0.52"

View File

@ -4,7 +4,7 @@ version = "0.1.0"
edition = "2021"
[dependencies]
proc-macro2 = "^1.0.63"
proc-macro2 = { version = "^1.0.63", features = ["span-locations"] }
quote = "^1.0"
syn = { version = "2.0.32", features = ["full"] }
thiserror = "1.0.47"

View File

@ -8,9 +8,11 @@ pub mod ty;
use crate::{
abi::ty::{AbiPrimitive, ComplexType, SimpleType},
error::Error,
syntax::{
parse_abi, Attributes, BitfieldRange, BitfieldType, BitfieldTypeField,
DocumentTypeDefinition, EnumType, EnumTypeVariant, NewType, ParseError, TypeRepr,
parse_abi, Attributes, BitfieldDefaultValue, BitfieldRange, BitfieldType,
BitfieldTypeField, DocumentTypeDefinition, EnumType, EnumTypeVariant, NewType, ParseError,
StructType, TypeRepr,
},
TargetEnv,
};
@ -101,7 +103,7 @@ impl AbiBuilder {
&self,
dispatcher_fn: &str,
impl_mod: &str,
) -> Result<syn::File, ParseError> {
) -> Result<syn::File, Error> {
let dispatcher_fn = syn::Ident::new(dispatcher_fn, Span::call_site());
let impl_mod = syn::Ident::new(impl_mod, Span::call_site());
@ -269,6 +271,13 @@ impl Abi {
}
}
impl GenerateTypeDefinition for StructType {
fn generate_type_definition(&self, _abi_type: &ComplexType, _env: &TargetEnv) -> TokenStream {
let Self { inner } = self;
quote!(#inner)
}
}
impl GenerateTypeDefinition for EnumType {
fn generate_type_definition(&self, abi_type: &ComplexType, env: &TargetEnv) -> TokenStream {
let Self {
@ -363,6 +372,8 @@ fn generate_transparent_struct(
) -> TokenStream {
let TypeRepr(repr) = &repr;
let attributes = attributes.filtered(|attr| !attr.path().is_ident("default"));
let direct = quote! {
#attributes
#[derive(Clone, Copy, PartialEq, Eq, PartialOrd, Ord, Debug, Hash)]
@ -440,6 +451,11 @@ impl GenerateTypeDefinition for BitfieldType {
fields,
} = self;
// Find default attribute, if any
let default_attr: Option<Result<BitfieldDefaultValue, _>> = attributes
.iter()
.find_map(|attr| attr.path().is_ident("default").then_some(attr.parse_args()));
let base = generate_transparent_struct(
attributes,
name,
@ -465,6 +481,24 @@ impl GenerateTypeDefinition for BitfieldType {
}
}
let const_default_fn = if let Some(default_attr) = default_attr {
// TODO handle error
let default_attr = default_attr.unwrap();
let value = default_attr
.items
.into_iter()
.map(|ident| quote!(Self::#ident.bits()))
.collect::<Punctuated<_, Token![|]>>();
quote! {
pub const fn const_default() -> Self {
Self(#value)
}
}
} else {
TokenStream::new()
};
let base = quote! {
#base
@ -478,6 +512,12 @@ impl GenerateTypeDefinition for BitfieldType {
pub const fn contains(&self, value: Self) -> bool {
self.0 & value.0 == value.0
}
pub const fn contains_any(&self, value: Self) -> bool {
self.0 & value.0 != 0
}
#const_default_fn
}
impl core::ops::BitOrAssign for #name {
@ -527,6 +567,7 @@ impl GenerateTypeDefinition for DocumentTypeDefinition {
Self::Enum(inner) => inner.generate_type_definition(abi_type, env),
Self::Bitfield(inner) => inner.generate_type_definition(abi_type, env),
Self::NewType(inner) => inner.generate_type_definition(abi_type, env),
Self::Struct(inner) => inner.generate_type_definition(abi_type, env),
// Extern types require no definition
Self::ExternType(_) => TokenStream::new(),
}

View File

@ -22,6 +22,11 @@ pub enum ComplexType {
Result(Rc<ComplexType>),
Option(Rc<ComplexType>),
Tuple(Vec<Rc<ComplexType>>),
Struct {
name: syn::Ident,
kind: ExternKind,
arguments: syn::PathArguments,
},
Extern {
kind: ExternKind,
alias: syn::Type,
@ -62,6 +67,7 @@ impl Type for ComplexType {
},
Self::Tuple(_) => TypeWidth::Unknown,
Self::Extern { .. } => TypeWidth::Unknown,
Self::Struct { .. } => TypeWidth::Unknown,
// MaybeUninit has the same layout as its underlying data
Self::MaybeUninit(ty) => ty.width(env),
}
@ -99,6 +105,7 @@ impl Type for ComplexType {
} => {
quote!(#alias #arguments)
}
Self::Struct { name, .. } => quote!(#name),
Self::MaybeUninit(ty) => {
let ty = ty.as_rust_type();
quote!(core::mem::MaybeUninit<#ty>)
@ -174,6 +181,7 @@ impl fmt::Debug for ComplexType {
}
r.finish()
}
Self::Struct { .. } => todo!(),
Self::Extern { alias, .. } => f.debug_tuple("Extern").field(&quote!(#alias)).finish(),
Self::MaybeUninit(ty) => f.debug_tuple("MaybeUninit").field(&ty).finish(),
}

View File

@ -20,6 +20,7 @@ pub enum AbiPrimitive {
I32,
U64,
I64,
U128,
USize,
}
@ -31,6 +32,7 @@ impl Type for AbiPrimitive {
Self::U16 | Self::I16 => TypeWidth::U16,
Self::U32 | Self::I32 => TypeWidth::U32,
Self::U64 | Self::I64 => TypeWidth::U64,
Self::U128 => TypeWidth::U128,
Self::USize => env.thin_pointer_width,
// ???
Self::Bool => TypeWidth::U32,
@ -52,16 +54,17 @@ impl Type for AbiPrimitive {
Self::I32 => quote!(i32),
Self::U64 => quote!(u64),
Self::I64 => quote!(i64),
Self::U128 => quote!(u128),
Self::USize => quote!(usize),
Self::Bool => quote!(bool),
}
}
fn emit_to_syscall_arguments(&self, _env: &TargetEnv, value: &Ident) -> TokenStream {
if *self == Self::USize {
quote!(#value)
} else {
quote!(#value as usize)
match self {
Self::USize => quote!(#value),
Self::U128 => todo!("Emit to syscall for u128"),
_ => quote!(#value as usize),
}
}
@ -73,6 +76,7 @@ impl Type for AbiPrimitive {
) -> (TokenStream, usize) {
match self {
Self::Bool => (quote!(#args[#index] != 0), 1),
Self::U128 => todo!("Emit from syscall for u128"),
_ => {
let ty = self.as_rust_type();
(quote!(#args[#index] as #ty), 1)
@ -94,6 +98,7 @@ impl FromStr for AbiPrimitive {
"u32" => Ok(Self::U32),
"i64" => Ok(Self::I64),
"u64" => Ok(Self::U64),
"u128" => Ok(Self::U128),
"bool" => Ok(Self::Bool),
"usize" => Ok(Self::USize),
_ => Err(()),

View File

@ -7,6 +7,11 @@ use super::{
document::DocumentItemAttributes,
};
#[derive(Clone)]
pub struct BitfieldDefaultValue {
pub items: Punctuated<syn::Ident, Token![|]>,
}
#[derive(Clone)]
pub enum BitfieldRange {
Single(syn::LitInt),
@ -34,6 +39,13 @@ impl DocumentItemAttributes for BitfieldType {
}
}
impl syn::parse::Parse for BitfieldDefaultValue {
fn parse(input: syn::parse::ParseStream) -> syn::Result<Self> {
let items = input.parse_terminated(syn::Ident::parse, Token![|])?;
Ok(Self { items })
}
}
impl syn::parse::Parse for BitfieldRange {
fn parse(input: syn::parse::ParseStream<'_>) -> syn::Result<Self> {
let start = input.parse()?;

View File

@ -13,6 +13,10 @@ impl Attributes {
pub fn new() -> Self {
Self(vec![])
}
pub fn filtered<P: Fn(&syn::Attribute) -> bool>(&self, pred: P) -> Self {
Self(self.0.iter().cloned().filter(pred).collect())
}
}
impl Deref for Attributes {

View File

@ -6,6 +6,7 @@ use super::{
enum_type::EnumType,
extern_block::{ExternType, ExternTypeBlock},
newtype::NewType,
struct_type::StructType,
syscall::SyscallDefinition,
};
@ -15,6 +16,7 @@ pub enum DocumentTypeDefinition {
Bitfield(BitfieldType),
Enum(EnumType),
ExternType(ExternType),
Struct(StructType),
}
pub struct Document {
@ -33,6 +35,7 @@ enum DocumentItem {
NewType(NewType),
Bitfield(BitfieldType),
Enum(EnumType),
Struct(StructType),
// Syscall definitions
SyscallDefinition(SyscallDefinition),
@ -64,6 +67,8 @@ impl syn::parse::Parse for DocumentItem {
} else if lookahead.peek(Token![enum]) {
input.parse::<Token![enum]>()?;
EnumType::parse(input).map(Self::Enum)
} else if lookahead.peek(Token![struct]) {
StructType::parse(input).map(Self::Struct)
} else {
todo!()
}?;
@ -82,6 +87,7 @@ impl DocumentItemAttributes for DocumentItem {
Self::Bitfield(inner) => inner.extend_attributes(attrs),
Self::SyscallDefinition(inner) => inner.extend_attributes(attrs),
Self::ExternTypeBlock(_) => unreachable!(),
Self::Struct(inner) => inner.extend_attributes(attrs),
}
}
}
@ -112,6 +118,7 @@ impl syn::parse::Parse for Document {
.map(DocumentTypeDefinition::ExternType),
);
}
DocumentItem::Struct(inner) => types.push(DocumentTypeDefinition::Struct(inner)),
DocumentItem::SyscallDefinition(inner) => {
syscalls.push(inner);
}
@ -130,6 +137,7 @@ impl ToTokens for DocumentItem {
Self::NewType(inner) => inner.to_tokens(tokens),
Self::SyscallDefinition(inner) => inner.to_tokens(tokens),
Self::ExternTypeBlock(inner) => inner.to_tokens(tokens),
Self::Struct(inner) => inner.to_tokens(tokens),
}
}
}

View File

@ -1,11 +1,31 @@
use std::path::Path;
use std::ops::Range;
use proc_macro2::Span;
use quote::quote;
use syn::spanned::Spanned;
trait SpanHelper {
fn matching_columns(&self, line: usize) -> Range<usize>;
}
impl SpanHelper for Span {
fn matching_columns(&self, line: usize) -> Range<usize> {
let start = self.start();
let end = self.end();
if line == start.line && line == end.line {
start.column..end.column
} else {
todo!()
}
}
}
pub enum SyntaxError {
UnhandledType(syn::Type),
UndefinedIdentifier(syn::Ident),
PrimitiveReprRequired(syn::Ident),
}
pub enum ParseError {
@ -15,7 +35,7 @@ pub enum ParseError {
}
pub trait UnwrapFancy<T> {
fn unwrap_fancy<P: AsRef<Path>>(self, context: P) -> T;
fn unwrap_fancy<S: AsRef<str>>(self, source_code: S) -> T;
}
impl From<std::io::Error> for ParseError {
@ -41,37 +61,76 @@ impl SyntaxError {
match self {
Self::UndefinedIdentifier(id) => id.span(),
Self::UnhandledType(ty) => ty.span(),
Self::PrimitiveReprRequired(id) => id.span(),
}
}
pub fn describe(&self) -> String {
match self {
Self::UnhandledType(_ty) => "Unhandled type".into(),
Self::UnhandledType(ty) => format!("Unhandled type '{}'", quote!(#ty)),
Self::UndefinedIdentifier(id) => format!("Undefined identifier '{}'", id),
Self::PrimitiveReprRequired(id) => {
format!("Primitive repr required in type definition, got '{}'", id)
}
}
}
pub fn print(&self, source_code: &str) {
let span = self.span();
let start = span.start();
let end = span.end();
let line_range = start.line..=end.line;
let lines_context = source_code
.split('\n')
.skip(start.line.saturating_sub(2))
.take(3 + end.line - start.line);
if start.line == end.line {
eprintln!("[ERROR] {}:", self.describe());
}
for (i, line) in lines_context.enumerate() {
let line_idx = i + start.line - 1;
eprintln!("{:4} | {}", line_idx, line);
if line_range.contains(&line_idx) {
let columns = span.matching_columns(line_idx);
eprint!("{0:4} | {0:>width$}", "", width = columns.start);
for _ in columns {
eprint!("~");
}
eprintln!();
}
}
eprintln!();
}
}
impl<T> UnwrapFancy<T> for Result<T, ParseError> {
fn unwrap_fancy<P: AsRef<Path>>(self, path: P) -> T {
fn unwrap_fancy<S: AsRef<str>>(self, source_code: S) -> T {
match self {
Self::Ok(value) => value,
Self::Err(err) => {
match err {
let n_errors = match err {
ParseError::IoError(err) => {
eprintln!("{}: {}", path.as_ref().display(), err);
eprintln!("ABI read error: {}", err);
1
}
ParseError::HardError(err) => {
eprintln!("{}: {}", path.as_ref().display(), err);
eprintln!("{}", err);
1
}
ParseError::SyntaxError(errs) => {
eprintln!("{}:", path.as_ref().display());
for err in errs {
eprintln!("* ...: {}", err.describe());
for err in errs.iter() {
err.print(source_code.as_ref());
}
errs.len()
}
}
panic!("Compilation aborted");
};
panic!("Compilation aborted, {} error(s)", n_errors);
}
}
}

View File

@ -15,19 +15,21 @@ mod bitfield_type;
mod enum_type;
mod extern_block;
mod newtype;
mod struct_type;
mod document;
mod error;
mod syscall;
pub use bitfield_type::{BitfieldRange, BitfieldType, BitfieldTypeField};
pub use bitfield_type::{BitfieldDefaultValue, BitfieldRange, BitfieldType, BitfieldTypeField};
pub use common::{Attributes, TypeRepr};
pub use document::{Document, DocumentTypeDefinition};
pub use enum_type::{EnumType, EnumTypeVariant};
pub use error::{ParseError, SyntaxError, UnwrapFancy};
pub use extern_block::{ExternType, ExternTypeBlock};
pub use newtype::NewType;
pub use struct_type::StructType;
pub fn parse_abi_document(input: &str) -> Result<Document, ParseError> {
let document: Document = syn::parse_str(input)?;
@ -167,7 +169,8 @@ fn process_type(t: &syn::Type, known_types: &TypeEnv) -> Result<Rc<ComplexType>,
fn require_primitive_repr(repr: &TypeRepr) -> Result<AbiPrimitive, ParseError> {
let TypeRepr(repr) = repr;
Ok(AbiPrimitive::from_str(repr.to_string().as_str()).expect("TODO proper error message"))
Ok(AbiPrimitive::from_str(repr.to_string().as_str())
.map_err(|_| ParseError::syntax1(SyntaxError::PrimitiveReprRequired(repr.clone())))?)
}
fn make_single_ident_type(ident: syn::Ident) -> syn::Type {
@ -242,6 +245,21 @@ fn process_enum_type(
))
}
fn process_struct_type(
def: &StructType,
_known_types: &TypeEnv,
) -> Result<(syn::Ident, Rc<ComplexType>), ParseError> {
let name = def.inner.ident.clone();
Ok((
name.clone(),
Rc::new(ComplexType::Struct {
name,
kind: ExternKind::None,
arguments: syn::PathArguments::None,
}),
))
}
fn process_newtype(
def: &NewType,
_known_types: &TypeEnv,
@ -269,6 +287,8 @@ fn process_type_definition(
.map(|(ident, def_ty)| (ident, ProcessedType::Local(def_ty, def.clone()))),
DocumentTypeDefinition::NewType(inner) => process_newtype(inner, known_types)
.map(|(ident, def_ty)| (ident, ProcessedType::Local(def_ty, def.clone()))),
DocumentTypeDefinition::Struct(inner) => process_struct_type(inner, known_types)
.map(|(ident, def_ty)| (ident, ProcessedType::Local(def_ty, def.clone()))),
}
}

View File

@ -0,0 +1,29 @@
use quote::{quote, ToTokens};
use super::document::DocumentItemAttributes;
#[derive(Clone)]
pub struct StructType {
pub inner: syn::ItemStruct,
}
impl syn::parse::Parse for StructType {
fn parse(input: syn::parse::ParseStream) -> syn::Result<Self> {
let mut inner: syn::ItemStruct = input.parse()?;
inner.vis = syn::Visibility::Public(syn::token::Pub(input.span()));
Ok(Self { inner })
}
}
impl DocumentItemAttributes for StructType {
fn extend_attributes<I: IntoIterator<Item = syn::Attribute>>(&mut self, attrs: I) {
self.inner.attrs.extend(attrs);
}
}
impl ToTokens for StructType {
fn to_tokens(&self, tokens: &mut proc_macro2::TokenStream) {
let Self { inner } = self;
tokens.extend(quote!(#inner));
}
}