Extract core stuff into own crates

This commit extracts five new crates:

- nu-source, which contains the core source-code handling logic in Nu,
  including Text, Span, and also the pretty.rs-based debug logic
- nu-parser, which is the parser and expander logic
- nu-protocol, which is the bulk of the types and basic conveniences
  used by plugins
- nu-errors, which contains ShellError, ParseError and error handling
  conveniences
- nu-textview, which is the textview plugin extracted into a crate

One of the major consequences of this refactor is that it's no longer
possible to `impl X for Spanned<Y>` outside of the `nu-source` crate, so
a lot of types became more concrete (Value became a concrete type
instead of Spanned<Value>, for example).

This also turned a number of inherent methods in the main nu crate into
plain functions (impl Value {} became a bunch of functions in the
`value` namespace in `crate::data::value`).
This commit is contained in:
Yehuda Katz
2019-11-25 18:30:48 -08:00
parent 2eae5a2a89
commit e4226def16
205 changed files with 3491 additions and 2605 deletions

View File

@ -0,0 +1,26 @@
[package]
name = "nu-errors"
version = "0.1.0"
authors = ["Yehuda Katz <wycats@gmail.com>"]
edition = "2018"
# See more keys and their definitions at https://doc.rust-lang.org/cargo/reference/manifest.html
[dependencies]
nu-source = { path = "../nu-source" }
ansi_term = "0.12.1"
bigdecimal = { version = "0.1.0", features = ["serde"] }
derive-new = "0.5.8"
language-reporting = "0.4.0"
num-bigint = { version = "0.2.3", features = ["serde"] }
num-traits = "0.2.8"
serde = { version = "1.0.102", features = ["derive"] }
nom = "5.0.1"
nom_locate = "1.0.0"
# implement conversions
subprocess = "0.1.18"
serde_yaml = "0.8"
toml = "0.5.5"
serde_json = "1.0.41"

885
crates/nu-errors/src/lib.rs Normal file
View File

@ -0,0 +1,885 @@
use ansi_term::Color;
use bigdecimal::BigDecimal;
use derive_new::new;
use language_reporting::{Diagnostic, Label, Severity};
use nu_source::{b, DebugDocBuilder, PrettyDebug, Span, Spanned, SpannedItem, TracableContext};
use num_bigint::BigInt;
use num_traits::ToPrimitive;
use serde::{Deserialize, Serialize};
use std::fmt;
use std::ops::Range;
// TODO: Spanned<T> -> HasSpanAndItem<T> ?
#[derive(Debug, Eq, PartialEq, Clone, Ord, PartialOrd, Hash, Serialize, Deserialize)]
pub enum Description {
Source(Spanned<String>),
Synthetic(String),
}
impl Description {
fn from_spanned(item: Spanned<impl Into<String>>) -> Description {
Description::Source(item.map(|s| s.into()))
}
fn into_label(self) -> Result<Label<Span>, String> {
match self {
Description::Source(s) => Ok(Label::new_primary(s.span).with_message(s.item)),
Description::Synthetic(s) => Err(s),
}
}
}
impl PrettyDebug for Description {
fn pretty(&self) -> DebugDocBuilder {
match self {
Description::Source(s) => b::description(&s.item),
Description::Synthetic(s) => b::description(s),
}
}
}
#[derive(Debug, Clone)]
pub enum ParseErrorReason {
Eof {
expected: &'static str,
span: Span,
},
Mismatch {
expected: &'static str,
actual: Spanned<String>,
},
ArgumentError {
command: Spanned<String>,
error: ArgumentError,
},
}
#[derive(Debug, Clone)]
pub struct ParseError {
reason: ParseErrorReason,
}
impl ParseError {
pub fn unexpected_eof(expected: &'static str, span: Span) -> ParseError {
ParseError {
reason: ParseErrorReason::Eof { expected, span },
}
}
pub fn mismatch(expected: &'static str, actual: Spanned<impl Into<String>>) -> ParseError {
let Spanned { span, item } = actual;
ParseError {
reason: ParseErrorReason::Mismatch {
expected,
actual: item.into().spanned(span),
},
}
}
pub fn argument_error(command: Spanned<impl Into<String>>, kind: ArgumentError) -> ParseError {
ParseError {
reason: ParseErrorReason::ArgumentError {
command: command.item.into().spanned(command.span),
error: kind,
},
}
}
}
impl From<ParseError> for ShellError {
fn from(error: ParseError) -> ShellError {
match error.reason {
ParseErrorReason::Eof { expected, span } => ShellError::unexpected_eof(expected, span),
ParseErrorReason::Mismatch { actual, expected } => {
ShellError::type_error(expected, actual.clone())
}
ParseErrorReason::ArgumentError { command, error } => {
ShellError::argument_error(command, error)
}
}
}
}
#[derive(Debug, Eq, PartialEq, Clone, Ord, Hash, PartialOrd, Serialize, Deserialize)]
pub enum ArgumentError {
MissingMandatoryFlag(String),
MissingMandatoryPositional(String),
MissingValueForName(String),
InvalidExternalWord,
}
impl PrettyDebug for ArgumentError {
fn pretty(&self) -> DebugDocBuilder {
match self {
ArgumentError::MissingMandatoryFlag(flag) => {
b::description("missing `")
+ b::description(flag)
+ b::description("` as mandatory flag")
}
ArgumentError::MissingMandatoryPositional(pos) => {
b::description("missing `")
+ b::description(pos)
+ b::description("` as mandatory positional argument")
}
ArgumentError::MissingValueForName(name) => {
b::description("missing value for flag `")
+ b::description(name)
+ b::description("`")
}
ArgumentError::InvalidExternalWord => b::description("invalid word"),
}
}
}
#[derive(Debug, Eq, PartialEq, Ord, PartialOrd, Clone, Serialize, Deserialize, Hash)]
pub struct ShellError {
error: ProximateShellError,
cause: Option<Box<ProximateShellError>>,
}
impl PrettyDebug for ShellError {
fn pretty(&self) -> DebugDocBuilder {
match &self.error {
ProximateShellError::SyntaxError { problem } => {
b::error("Syntax Error")
+ b::space()
+ b::delimit("(", b::description(&problem.item), ")")
}
ProximateShellError::UnexpectedEof { .. } => b::error("Unexpected end"),
ProximateShellError::TypeError { expected, actual } => {
b::error("Type Error")
+ b::space()
+ b::delimit(
"(",
b::description("expected:")
+ b::space()
+ b::description(expected)
+ b::description(",")
+ b::space()
+ b::description("actual:")
+ b::space()
+ b::option(actual.item.as_ref().map(|actual| b::description(actual))),
")",
)
}
ProximateShellError::MissingProperty { subpath, expr } => {
b::error("Missing Property")
+ b::space()
+ b::delimit(
"(",
b::description("expr:")
+ b::space()
+ expr.pretty()
+ b::description(",")
+ b::space()
+ b::description("subpath:")
+ b::space()
+ subpath.pretty(),
")",
)
}
ProximateShellError::InvalidIntegerIndex { subpath, .. } => {
b::error("Invalid integer index")
+ b::space()
+ b::delimit(
"(",
b::description("subpath:") + b::space() + subpath.pretty(),
")",
)
}
ProximateShellError::MissingValue { reason, .. } => {
b::error("Missing Value")
+ b::space()
+ b::delimit(
"(",
b::description("reason:") + b::space() + b::description(reason),
")",
)
}
ProximateShellError::ArgumentError { command, error } => {
b::error("Argument Error")
+ b::space()
+ b::delimit(
"(",
b::description("command:")
+ b::space()
+ b::description(&command.item)
+ b::description(",")
+ b::space()
+ b::description("error:")
+ b::space()
+ error.pretty(),
")",
)
}
ProximateShellError::RangeError {
kind,
actual_kind,
operation,
} => {
b::error("Range Error")
+ b::space()
+ b::delimit(
"(",
b::description("expected:")
+ b::space()
+ kind.pretty()
+ b::description(",")
+ b::space()
+ b::description("actual:")
+ b::space()
+ b::description(&actual_kind.item)
+ b::description(",")
+ b::space()
+ b::description("operation:")
+ b::space()
+ b::description(operation),
")",
)
}
ProximateShellError::Diagnostic(_) => b::error("diagnostic"),
ProximateShellError::CoerceError { left, right } => {
b::error("Coercion Error")
+ b::space()
+ b::delimit(
"(",
b::description("left:")
+ b::space()
+ b::description(&left.item)
+ b::description(",")
+ b::space()
+ b::description("right:")
+ b::space()
+ b::description(&right.item),
")",
)
}
ProximateShellError::UntaggedRuntimeError { reason } => {
b::error("Unknown Error") + b::delimit("(", b::description(reason), ")")
}
}
}
}
impl std::fmt::Display for ShellError {
fn fmt(&self, f: &mut std::fmt::Formatter<'_>) -> std::fmt::Result {
write!(f, "{}", self.pretty().display())
}
}
impl serde::de::Error for ShellError {
fn custom<T>(msg: T) -> Self
where
T: std::fmt::Display,
{
ShellError::untagged_runtime_error(msg.to_string())
}
}
impl ShellError {
pub fn type_error(
expected: impl Into<String>,
actual: Spanned<impl Into<String>>,
) -> ShellError {
ProximateShellError::TypeError {
expected: expected.into(),
actual: actual.map(|i| Some(i.into())),
}
.start()
}
pub fn missing_property(
subpath: Spanned<impl Into<String>>,
expr: Spanned<impl Into<String>>,
) -> ShellError {
ProximateShellError::MissingProperty {
subpath: Description::from_spanned(subpath),
expr: Description::from_spanned(expr),
}
.start()
}
pub fn invalid_integer_index(
subpath: Spanned<impl Into<String>>,
integer: impl Into<Span>,
) -> ShellError {
ProximateShellError::InvalidIntegerIndex {
subpath: Description::from_spanned(subpath),
integer: integer.into(),
}
.start()
}
pub fn untagged_runtime_error(error: impl Into<String>) -> ShellError {
ProximateShellError::UntaggedRuntimeError {
reason: error.into(),
}
.start()
}
pub fn unexpected_eof(expected: impl Into<String>, span: impl Into<Span>) -> ShellError {
ProximateShellError::UnexpectedEof {
expected: expected.into(),
span: span.into(),
}
.start()
}
pub fn range_error(
expected: impl Into<ExpectedRange>,
actual: &Spanned<impl fmt::Debug>,
operation: impl Into<String>,
) -> ShellError {
ProximateShellError::RangeError {
kind: expected.into(),
actual_kind: format!("{:?}", actual.item).spanned(actual.span),
operation: operation.into(),
}
.start()
}
pub fn syntax_error(problem: Spanned<impl Into<String>>) -> ShellError {
ProximateShellError::SyntaxError {
problem: problem.map(|p| p.into()),
}
.start()
}
pub fn coerce_error(
left: Spanned<impl Into<String>>,
right: Spanned<impl Into<String>>,
) -> ShellError {
ProximateShellError::CoerceError {
left: left.map(|l| l.into()),
right: right.map(|r| r.into()),
}
.start()
}
pub fn argument_error(command: Spanned<impl Into<String>>, kind: ArgumentError) -> ShellError {
ProximateShellError::ArgumentError {
command: command.map(|c| c.into()),
error: kind,
}
.start()
}
pub fn parse_error(
error: nom::Err<(
nom_locate::LocatedSpanEx<&str, TracableContext>,
nom::error::ErrorKind,
)>,
) -> ShellError {
use language_reporting::*;
match error {
nom::Err::Incomplete(_) => {
// TODO: Get span of EOF
let diagnostic = Diagnostic::new(
Severity::Error,
format!("Parse Error: Unexpected end of line"),
);
ShellError::diagnostic(diagnostic)
}
nom::Err::Failure(span) | nom::Err::Error(span) => {
let diagnostic = Diagnostic::new(Severity::Error, format!("Parse Error"))
.with_label(Label::new_primary(Span::from(span.0)));
ShellError::diagnostic(diagnostic)
}
}
}
pub fn diagnostic(diagnostic: Diagnostic<Span>) -> ShellError {
ProximateShellError::Diagnostic(ShellDiagnostic { diagnostic }).start()
}
pub fn to_diagnostic(self) -> Diagnostic<Span> {
match self.error {
ProximateShellError::MissingValue { span, reason } => {
let mut d = Diagnostic::new(
Severity::Bug,
format!("Internal Error (missing value) :: {}", reason),
);
if let Some(span) = span {
d = d.with_label(Label::new_primary(span));
}
d
}
ProximateShellError::ArgumentError {
command,
error,
} => match error {
ArgumentError::InvalidExternalWord => Diagnostic::new(
Severity::Error,
format!("Invalid bare word for Nu command (did you intend to invoke an external command?)"))
.with_label(Label::new_primary(command.span)),
ArgumentError::MissingMandatoryFlag(name) => Diagnostic::new(
Severity::Error,
format!(
"{} requires {}{}",
Color::Cyan.paint(&command.item),
Color::Black.bold().paint("--"),
Color::Black.bold().paint(name)
),
)
.with_label(Label::new_primary(command.span)),
ArgumentError::MissingMandatoryPositional(name) => Diagnostic::new(
Severity::Error,
format!(
"{} requires {} parameter",
Color::Cyan.paint(&command.item),
Color::Green.bold().paint(name.clone())
),
)
.with_label(
Label::new_primary(command.span).with_message(format!("requires {} parameter", name)),
),
ArgumentError::MissingValueForName(name) => Diagnostic::new(
Severity::Error,
format!(
"{} is missing value for flag {}{}",
Color::Cyan.paint(&command.item),
Color::Black.bold().paint("--"),
Color::Black.bold().paint(name)
),
)
.with_label(Label::new_primary(command.span)),
},
ProximateShellError::TypeError {
expected,
actual:
Spanned {
item: Some(actual),
span,
},
} => Diagnostic::new(Severity::Error, "Type Error").with_label(
Label::new_primary(span)
.with_message(format!("Expected {}, found {}", expected, actual)),
),
ProximateShellError::TypeError {
expected,
actual:
Spanned {
item: None,
span
},
} => Diagnostic::new(Severity::Error, "Type Error")
.with_label(Label::new_primary(span).with_message(expected)),
ProximateShellError::UnexpectedEof {
expected, span
} => Diagnostic::new(Severity::Error, format!("Unexpected end of input"))
.with_label(Label::new_primary(span).with_message(format!("Expected {}", expected))),
ProximateShellError::RangeError {
kind,
operation,
actual_kind:
Spanned {
item,
span
},
} => Diagnostic::new(Severity::Error, "Range Error").with_label(
Label::new_primary(span).with_message(format!(
"Expected to convert {} to {} while {}, but it was out of range",
item,
kind.desc(),
operation
)),
),
ProximateShellError::SyntaxError {
problem:
Spanned {
span,
item
},
} => Diagnostic::new(Severity::Error, "Syntax Error")
.with_label(Label::new_primary(span).with_message(item)),
ProximateShellError::MissingProperty { subpath, expr, .. } => {
let subpath = subpath.into_label();
let expr = expr.into_label();
let mut diag = Diagnostic::new(Severity::Error, "Missing property");
match subpath {
Ok(label) => diag = diag.with_label(label),
Err(ty) => diag.message = format!("Missing property (for {})", ty),
}
if let Ok(label) = expr {
diag = diag.with_label(label);
}
diag
}
ProximateShellError::InvalidIntegerIndex { subpath,integer } => {
let subpath = subpath.into_label();
let mut diag = Diagnostic::new(Severity::Error, "Invalid integer property");
match subpath {
Ok(label) => diag = diag.with_label(label),
Err(ty) => diag.message = format!("Invalid integer property (for {})", ty)
}
diag = diag.with_label(Label::new_secondary(integer).with_message("integer"));
diag
}
ProximateShellError::Diagnostic(diag) => diag.diagnostic,
ProximateShellError::CoerceError { left, right } => {
Diagnostic::new(Severity::Error, "Coercion error")
.with_label(Label::new_primary(left.span).with_message(left.item))
.with_label(Label::new_secondary(right.span).with_message(right.item))
}
ProximateShellError::UntaggedRuntimeError { reason } => Diagnostic::new(Severity::Error, format!("Error: {}", reason))
}
}
pub fn labeled_error(
msg: impl Into<String>,
label: impl Into<String>,
span: impl Into<Span>,
) -> ShellError {
ShellError::diagnostic(
Diagnostic::new(Severity::Error, msg.into())
.with_label(Label::new_primary(span.into()).with_message(label.into())),
)
}
pub fn labeled_error_with_secondary(
msg: impl Into<String>,
primary_label: impl Into<String>,
primary_span: impl Into<Span>,
secondary_label: impl Into<String>,
secondary_span: impl Into<Span>,
) -> ShellError {
ShellError::diagnostic(
Diagnostic::new_error(msg.into())
.with_label(
Label::new_primary(primary_span.into()).with_message(primary_label.into()),
)
.with_label(
Label::new_secondary(secondary_span.into())
.with_message(secondary_label.into()),
),
)
}
pub fn unimplemented(title: impl Into<String>) -> ShellError {
ShellError::untagged_runtime_error(&format!("Unimplemented: {}", title.into()))
}
pub fn unexpected(title: impl Into<String>) -> ShellError {
ShellError::untagged_runtime_error(&format!("Unexpected: {}", title.into()))
}
}
#[derive(Debug, Eq, PartialEq, Ord, PartialOrd, Hash, Clone, Serialize, Deserialize)]
pub enum ExpectedRange {
I8,
I16,
I32,
I64,
I128,
U8,
U16,
U32,
U64,
U128,
F32,
F64,
Usize,
Size,
BigInt,
BigDecimal,
Range { start: usize, end: usize },
}
impl From<Range<usize>> for ExpectedRange {
fn from(range: Range<usize>) -> Self {
ExpectedRange::Range {
start: range.start,
end: range.end,
}
}
}
impl PrettyDebug for ExpectedRange {
fn pretty(&self) -> DebugDocBuilder {
b::description(self.desc())
}
}
impl ExpectedRange {
fn desc(&self) -> String {
match self {
ExpectedRange::I8 => "an 8-bit signed integer",
ExpectedRange::I16 => "a 16-bit signed integer",
ExpectedRange::I32 => "a 32-bit signed integer",
ExpectedRange::I64 => "a 64-bit signed integer",
ExpectedRange::I128 => "a 128-bit signed integer",
ExpectedRange::U8 => "an 8-bit unsigned integer",
ExpectedRange::U16 => "a 16-bit unsigned integer",
ExpectedRange::U32 => "a 32-bit unsigned integer",
ExpectedRange::U64 => "a 64-bit unsigned integer",
ExpectedRange::U128 => "a 128-bit unsigned integer",
ExpectedRange::F32 => "a 32-bit float",
ExpectedRange::F64 => "a 64-bit float",
ExpectedRange::Usize => "an list index",
ExpectedRange::Size => "a list offset",
ExpectedRange::BigDecimal => "a decimal",
ExpectedRange::BigInt => "an integer",
ExpectedRange::Range { start, end } => return format!("{} to {}", start, end),
}
.to_string()
}
}
#[derive(Debug, Eq, PartialEq, Clone, Ord, PartialOrd, Serialize, Deserialize, Hash)]
pub enum ProximateShellError {
SyntaxError {
problem: Spanned<String>,
},
UnexpectedEof {
expected: String,
span: Span,
},
TypeError {
expected: String,
actual: Spanned<Option<String>>,
},
MissingProperty {
subpath: Description,
expr: Description,
},
InvalidIntegerIndex {
subpath: Description,
integer: Span,
},
MissingValue {
span: Option<Span>,
reason: String,
},
ArgumentError {
command: Spanned<String>,
error: ArgumentError,
},
RangeError {
kind: ExpectedRange,
actual_kind: Spanned<String>,
operation: String,
},
Diagnostic(ShellDiagnostic),
CoerceError {
left: Spanned<String>,
right: Spanned<String>,
},
UntaggedRuntimeError {
reason: String,
},
}
impl ProximateShellError {
fn start(self) -> ShellError {
ShellError {
cause: None,
error: self,
}
}
}
#[derive(Debug, Clone, Serialize, Deserialize)]
pub struct ShellDiagnostic {
pub(crate) diagnostic: Diagnostic<Span>,
}
impl std::hash::Hash for ShellDiagnostic {
fn hash<H: std::hash::Hasher>(&self, state: &mut H) {
self.diagnostic.severity.hash(state);
self.diagnostic.code.hash(state);
self.diagnostic.message.hash(state);
for label in &self.diagnostic.labels {
label.span.hash(state);
label.message.hash(state);
match label.style {
language_reporting::LabelStyle::Primary => 0.hash(state),
language_reporting::LabelStyle::Secondary => 1.hash(state),
}
}
}
}
impl PartialEq for ShellDiagnostic {
fn eq(&self, _other: &ShellDiagnostic) -> bool {
false
}
}
impl Eq for ShellDiagnostic {}
impl std::cmp::PartialOrd for ShellDiagnostic {
fn partial_cmp(&self, _other: &Self) -> Option<std::cmp::Ordering> {
Some(std::cmp::Ordering::Less)
}
}
impl std::cmp::Ord for ShellDiagnostic {
fn cmp(&self, _other: &Self) -> std::cmp::Ordering {
std::cmp::Ordering::Less
}
}
#[derive(Debug, Ord, PartialOrd, Eq, PartialEq, new, Clone, Serialize, Deserialize)]
pub struct StringError {
title: String,
error: String,
}
impl std::error::Error for ShellError {}
impl std::convert::From<Box<dyn std::error::Error>> for ShellError {
fn from(input: Box<dyn std::error::Error>) -> ShellError {
ShellError::untagged_runtime_error(format!("{}", input))
}
}
impl std::convert::From<std::io::Error> for ShellError {
fn from(input: std::io::Error) -> ShellError {
ShellError::untagged_runtime_error(format!("{}", input))
}
}
impl std::convert::From<subprocess::PopenError> for ShellError {
fn from(input: subprocess::PopenError) -> ShellError {
ShellError::untagged_runtime_error(format!("{}", input))
}
}
impl std::convert::From<serde_yaml::Error> for ShellError {
fn from(input: serde_yaml::Error) -> ShellError {
ShellError::untagged_runtime_error(format!("{:?}", input))
}
}
impl std::convert::From<toml::ser::Error> for ShellError {
fn from(input: toml::ser::Error) -> ShellError {
ShellError::untagged_runtime_error(format!("{:?}", input))
}
}
impl std::convert::From<serde_json::Error> for ShellError {
fn from(input: serde_json::Error) -> ShellError {
ShellError::untagged_runtime_error(format!("{:?}", input))
}
}
impl std::convert::From<Box<dyn std::error::Error + Send + Sync>> for ShellError {
fn from(input: Box<dyn std::error::Error + Send + Sync>) -> ShellError {
ShellError::untagged_runtime_error(format!("{:?}", input))
}
}
pub trait CoerceInto<U> {
fn coerce_into(self, operation: impl Into<String>) -> Result<U, ShellError>;
}
trait ToExpectedRange {
fn to_expected_range() -> ExpectedRange;
}
macro_rules! ranged_int {
($ty:tt -> $op:tt -> $variant:tt) => {
impl ToExpectedRange for $ty {
fn to_expected_range() -> ExpectedRange {
ExpectedRange::$variant
}
}
impl CoerceInto<$ty> for nu_source::Tagged<BigInt> {
fn coerce_into(self, operation: impl Into<String>) -> Result<$ty, ShellError> {
match self.$op() {
Some(v) => Ok(v),
None => Err(ShellError::range_error(
$ty::to_expected_range(),
&self.item.spanned(self.tag.span),
operation.into(),
)),
}
}
}
impl CoerceInto<$ty> for nu_source::Tagged<&BigInt> {
fn coerce_into(self, operation: impl Into<String>) -> Result<$ty, ShellError> {
match self.$op() {
Some(v) => Ok(v),
None => Err(ShellError::range_error(
$ty::to_expected_range(),
&self.item.spanned(self.tag.span),
operation.into(),
)),
}
}
}
};
}
ranged_int!(u8 -> to_u8 -> U8);
ranged_int!(u16 -> to_u16 -> U16);
ranged_int!(u32 -> to_u32 -> U32);
ranged_int!(u64 -> to_u64 -> U64);
ranged_int!(i8 -> to_i8 -> I8);
ranged_int!(i16 -> to_i16 -> I16);
ranged_int!(i32 -> to_i32 -> I32);
ranged_int!(i64 -> to_i64 -> I64);
macro_rules! ranged_decimal {
($ty:tt -> $op:tt -> $variant:tt) => {
impl ToExpectedRange for $ty {
fn to_expected_range() -> ExpectedRange {
ExpectedRange::$variant
}
}
impl CoerceInto<$ty> for nu_source::Tagged<BigDecimal> {
fn coerce_into(self, operation: impl Into<String>) -> Result<$ty, ShellError> {
match self.$op() {
Some(v) => Ok(v),
None => Err(ShellError::range_error(
$ty::to_expected_range(),
&self.item.spanned(self.tag.span),
operation.into(),
)),
}
}
}
impl CoerceInto<$ty> for nu_source::Tagged<&BigDecimal> {
fn coerce_into(self, operation: impl Into<String>) -> Result<$ty, ShellError> {
match self.$op() {
Some(v) => Ok(v),
None => Err(ShellError::range_error(
$ty::to_expected_range(),
&self.item.spanned(self.tag.span),
operation.into(),
)),
}
}
}
};
}
ranged_decimal!(f32 -> to_f32 -> F32);
ranged_decimal!(f64 -> to_f64 -> F64);

View File

@ -0,0 +1,37 @@
[package]
name = "nu-parser"
version = "0.1.0"
authors = ["Yehuda Katz <wycats@gmail.com>"]
edition = "2018"
# See more keys and their definitions at https://doc.rust-lang.org/cargo/reference/manifest.html
[dependencies]
nu-errors = { path = "../nu-errors" }
nu-source = { path = "../nu-source" }
nu-protocol = { path = "../nu-protocol" }
pretty_env_logger = "0.3.1"
pretty = "0.5.2"
termcolor = "1.0.5"
log = "0.4.8"
indexmap = { version = "1.3.0", features = ["serde-1"] }
serde = { version = "1.0.102", features = ["derive"] }
nom = "5.0.1"
nom_locate = "1.0.0"
nom-tracable = "0.4.1"
num-traits = "0.2.8"
num-bigint = { version = "0.2.3", features = ["serde"] }
bigdecimal = { version = "0.1.0", features = ["serde"] }
derive-new = "0.5.8"
getset = "0.0.9"
cfg-if = "0.1"
itertools = "0.8.1"
shellexpand = "1.0.0"
ansi_term = "0.12.1"
ptree = {version = "0.2" }
language-reporting = "0.4.0"
unicode-xid = "0.2.0"
[dev-dependencies]
pretty_assertions = "0.6.1"

View File

@ -0,0 +1,98 @@
pub mod classified;
use crate::commands::classified::ClassifiedCommand;
use crate::hir::expand_external_tokens::ExternalTokensShape;
use crate::hir::syntax_shape::{expand_syntax, ExpandContext};
use crate::hir::tokens_iterator::TokensIterator;
use nu_errors::ParseError;
use nu_source::{b, DebugDocBuilder, HasSpan, PrettyDebug, Span, Spanned, Tag, Tagged};
// Classify this command as an external command, which doesn't give special meaning
// to nu syntactic constructs, and passes all arguments to the external command as
// strings.
pub(crate) fn external_command(
tokens: &mut TokensIterator,
context: &ExpandContext,
name: Tagged<&str>,
) -> Result<ClassifiedCommand, ParseError> {
let Spanned { item, span } = expand_syntax(&ExternalTokensShape, tokens, context)?.tokens;
Ok(ClassifiedCommand::External(ExternalCommand {
name: name.to_string(),
name_tag: name.tag(),
args: ExternalArgs {
list: item
.iter()
.map(|x| ExternalArg {
tag: x.span.into(),
arg: x.item.clone(),
})
.collect(),
span,
},
}))
}
#[derive(Debug, Clone, Eq, PartialEq)]
pub struct ExternalArg {
pub arg: String,
pub tag: Tag,
}
impl std::ops::Deref for ExternalArg {
type Target = str;
fn deref(&self) -> &str {
&self.arg
}
}
#[derive(Debug, Clone, Eq, PartialEq)]
pub struct ExternalArgs {
pub list: Vec<ExternalArg>,
pub span: Span,
}
impl ExternalArgs {
pub fn iter(&self) -> impl Iterator<Item = &ExternalArg> {
self.list.iter()
}
}
impl std::ops::Deref for ExternalArgs {
type Target = [ExternalArg];
fn deref(&self) -> &[ExternalArg] {
&self.list
}
}
#[derive(Debug, Clone, Eq, PartialEq)]
pub struct ExternalCommand {
pub name: String,
pub name_tag: Tag,
pub args: ExternalArgs,
}
impl PrettyDebug for ExternalCommand {
fn pretty(&self) -> DebugDocBuilder {
b::typed(
"external command",
b::description(&self.name)
+ b::preceded(
b::space(),
b::intersperse(
self.args.iter().map(|a| b::primitive(format!("{}", a.arg))),
b::space(),
),
),
)
}
}
impl HasSpan for ExternalCommand {
fn span(&self) -> Span {
self.name_tag.span.until(self.args.span)
}
}

View File

@ -0,0 +1,112 @@
use crate::commands::ExternalCommand;
use crate::hir;
use crate::parse::token_tree::TokenNode;
use derive_new::new;
use nu_source::{b, DebugDocBuilder, HasSpan, PrettyDebugWithSource, Span, Tag};
#[derive(Debug, Clone, Eq, PartialEq)]
pub enum ClassifiedCommand {
#[allow(unused)]
Expr(TokenNode),
#[allow(unused)]
Dynamic(hir::Call),
Internal(InternalCommand),
External(ExternalCommand),
}
impl PrettyDebugWithSource for ClassifiedCommand {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
match self {
ClassifiedCommand::Expr(token) => b::typed("command", token.pretty_debug(source)),
ClassifiedCommand::Dynamic(call) => b::typed("command", call.pretty_debug(source)),
ClassifiedCommand::Internal(internal) => internal.pretty_debug(source),
ClassifiedCommand::External(external) => external.pretty_debug(source),
}
}
}
impl HasSpan for ClassifiedCommand {
fn span(&self) -> Span {
match self {
ClassifiedCommand::Expr(node) => node.span(),
ClassifiedCommand::Internal(command) => command.span(),
ClassifiedCommand::Dynamic(call) => call.span,
ClassifiedCommand::External(command) => command.span(),
}
}
}
#[derive(new, Debug, Clone, Eq, PartialEq)]
pub struct InternalCommand {
pub name: String,
pub name_tag: Tag,
pub args: hir::Call,
}
impl PrettyDebugWithSource for InternalCommand {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
b::typed(
"internal command",
b::description(&self.name) + b::space() + self.args.pretty_debug(source),
)
}
}
impl HasSpan for InternalCommand {
fn span(&self) -> Span {
let start = self.name_tag.span;
start.until(self.args.span)
}
}
#[derive(new, Debug, Eq, PartialEq)]
pub(crate) struct DynamicCommand {
pub(crate) args: hir::Call,
}
#[derive(Debug, Clone)]
pub struct Commands {
pub list: Vec<ClassifiedCommand>,
pub span: Span,
}
impl std::ops::Deref for Commands {
type Target = [ClassifiedCommand];
fn deref(&self) -> &Self::Target {
&self.list
}
}
#[derive(Debug, Clone)]
pub struct ClassifiedPipeline {
pub commands: Commands,
}
impl ClassifiedPipeline {
pub fn commands(list: Vec<ClassifiedCommand>, span: impl Into<Span>) -> ClassifiedPipeline {
ClassifiedPipeline {
commands: Commands {
list,
span: span.into(),
},
}
}
}
impl HasSpan for ClassifiedPipeline {
fn span(&self) -> Span {
self.commands.span
}
}
impl PrettyDebugWithSource for ClassifiedPipeline {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
b::intersperse(
self.commands.iter().map(|c| c.pretty_debug(source)),
b::operator(" | "),
)
.or(b::delimit("<", b::description("empty pipeline"), ">"))
}
}

View File

@ -0,0 +1,51 @@
use nu_source::ShellAnnotation;
use pretty::{Render, RenderAnnotated};
use std::io;
use termcolor::WriteColor;
pub struct TermColored<'a, W> {
color_stack: Vec<ShellAnnotation>,
upstream: &'a mut W,
}
impl<'a, W> TermColored<'a, W> {
pub fn new(upstream: &'a mut W) -> TermColored<'a, W> {
TermColored {
color_stack: Vec::new(),
upstream,
}
}
}
impl<'a, W> Render for TermColored<'a, W>
where
W: io::Write,
{
type Error = io::Error;
fn write_str(&mut self, s: &str) -> io::Result<usize> {
self.upstream.write(s.as_bytes())
}
fn write_str_all(&mut self, s: &str) -> io::Result<()> {
self.upstream.write_all(s.as_bytes())
}
}
impl<'a, W> RenderAnnotated<ShellAnnotation> for TermColored<'a, W>
where
W: WriteColor,
{
fn push_annotation(&mut self, ann: &ShellAnnotation) -> Result<(), Self::Error> {
self.color_stack.push(*ann);
self.upstream.set_color(&(*ann).into())
}
fn pop_annotation(&mut self) -> Result<(), Self::Error> {
self.color_stack.pop();
match self.color_stack.last() {
Some(previous) => self.upstream.set_color(&(*previous).into()),
None => self.upstream.reset(),
}
}
}

366
crates/nu-parser/src/hir.rs Normal file
View File

@ -0,0 +1,366 @@
pub(crate) mod baseline_parse;
pub(crate) mod binary;
pub(crate) mod expand_external_tokens;
pub(crate) mod external_command;
pub(crate) mod named;
pub(crate) mod path;
pub mod syntax_shape;
pub(crate) mod tokens_iterator;
use crate::hir::syntax_shape::Member;
use crate::parse::operator::Operator;
use crate::parse::parser::Number;
use crate::parse::unit::Unit;
use derive_new::new;
use getset::Getters;
#[cfg(not(coloring_in_tokens))]
use nu_errors::ShellError;
#[cfg(not(coloring_in_tokens))]
use nu_protocol::{EvaluatedArgs, Scope};
use nu_protocol::{PathMember, ShellTypeName};
#[cfg(not(coloring_in_tokens))]
use nu_source::Text;
use nu_source::{
b, DebugDocBuilder, HasSpan, PrettyDebug, PrettyDebugWithSource, Span, Spanned, SpannedItem,
};
use serde::{Deserialize, Serialize};
use std::path::PathBuf;
use crate::parse::tokens::RawNumber;
pub(crate) use self::binary::Binary;
pub(crate) use self::path::Path;
pub(crate) use self::syntax_shape::ExpandContext;
pub(crate) use self::tokens_iterator::TokensIterator;
pub use self::external_command::ExternalCommand;
pub use self::named::{NamedArguments, NamedValue};
#[derive(Debug, Clone, Eq, PartialEq, Getters, Serialize, Deserialize, new)]
pub struct Call {
#[get = "pub(crate)"]
pub head: Box<Expression>,
#[get = "pub(crate)"]
pub positional: Option<Vec<Expression>>,
#[get = "pub(crate)"]
pub named: Option<NamedArguments>,
pub span: Span,
}
impl PrettyDebugWithSource for Call {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
b::delimit(
"(",
self.head.pretty_debug(source)
+ b::preceded_option(
Some(b::space()),
self.positional.as_ref().map(|pos| {
b::intersperse(pos.iter().map(|expr| expr.pretty_debug(source)), b::space())
}),
)
+ b::preceded_option(
Some(b::space()),
self.named.as_ref().map(|named| named.pretty_debug(source)),
),
")",
)
}
}
#[derive(Debug, Clone, Eq, PartialEq, Ord, PartialOrd, Hash, Serialize, Deserialize)]
pub enum RawExpression {
Literal(Literal),
ExternalWord,
Synthetic(Synthetic),
Variable(Variable),
Binary(Box<Binary>),
Block(Vec<Expression>),
List(Vec<Expression>),
Path(Box<Path>),
FilePath(PathBuf),
ExternalCommand(ExternalCommand),
Command(Span),
Boolean(bool),
}
impl ShellTypeName for RawExpression {
fn type_name(&self) -> &'static str {
match self {
RawExpression::Literal(literal) => literal.type_name(),
RawExpression::Synthetic(synthetic) => synthetic.type_name(),
RawExpression::Command(..) => "command",
RawExpression::ExternalWord => "external word",
RawExpression::FilePath(..) => "file path",
RawExpression::Variable(..) => "variable",
RawExpression::List(..) => "list",
RawExpression::Binary(..) => "binary",
RawExpression::Block(..) => "block",
RawExpression::Path(..) => "variable path",
RawExpression::Boolean(..) => "boolean",
RawExpression::ExternalCommand(..) => "external",
}
}
}
#[derive(Debug, Clone, Eq, PartialEq, Ord, PartialOrd, Hash, Serialize, Deserialize)]
pub enum Synthetic {
String(String),
}
impl ShellTypeName for Synthetic {
fn type_name(&self) -> &'static str {
match self {
Synthetic::String(_) => "string",
}
}
}
impl RawExpression {
pub fn into_expr(self, span: impl Into<Span>) -> Expression {
Expression {
expr: self,
span: span.into(),
}
}
pub fn into_unspanned_expr(self) -> Expression {
Expression {
expr: self,
span: Span::unknown(),
}
}
}
#[derive(Debug, Clone, Eq, PartialEq, Ord, PartialOrd, Hash, Serialize, Deserialize)]
pub struct Expression {
pub expr: RawExpression,
pub span: Span,
}
impl std::ops::Deref for Expression {
type Target = RawExpression;
fn deref(&self) -> &RawExpression {
&self.expr
}
}
impl HasSpan for Expression {
fn span(&self) -> Span {
self.span
}
}
impl PrettyDebugWithSource for Expression {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
match &self.expr {
RawExpression::Literal(literal) => literal.spanned(self.span).pretty_debug(source),
RawExpression::ExternalWord => {
b::typed("external word", b::primitive(self.span.slice(source)))
}
RawExpression::Synthetic(s) => match s {
Synthetic::String(s) => b::typed("synthetic", b::primitive(format!("{:?}", s))),
},
RawExpression::Variable(_) => b::keyword(self.span.slice(source)),
RawExpression::Binary(binary) => binary.pretty_debug(source),
RawExpression::Block(_) => b::opaque("block"),
RawExpression::List(list) => b::delimit(
"[",
b::intersperse(
list.iter().map(|item| item.pretty_debug(source)),
b::space(),
),
"]",
),
RawExpression::Path(path) => path.pretty_debug(source),
RawExpression::FilePath(path) => b::typed("path", b::primitive(path.display())),
RawExpression::ExternalCommand(external) => b::typed(
"external command",
b::primitive(external.name.slice(source)),
),
RawExpression::Command(command) => {
b::typed("command", b::primitive(command.slice(source)))
}
RawExpression::Boolean(boolean) => match boolean {
true => b::primitive("$yes"),
false => b::primitive("$no"),
},
}
}
}
impl Expression {
pub fn number(i: impl Into<Number>, span: impl Into<Span>) -> Expression {
let span = span.into();
RawExpression::Literal(RawLiteral::Number(i.into()).into_literal(span)).into_expr(span)
}
pub fn size(i: impl Into<Number>, unit: impl Into<Unit>, span: impl Into<Span>) -> Expression {
let span = span.into();
RawExpression::Literal(RawLiteral::Size(i.into(), unit.into()).into_literal(span))
.into_expr(span)
}
pub fn synthetic_string(s: impl Into<String>) -> Expression {
RawExpression::Synthetic(Synthetic::String(s.into())).into_unspanned_expr()
}
pub fn string(inner: impl Into<Span>, outer: impl Into<Span>) -> Expression {
let outer = outer.into();
RawExpression::Literal(RawLiteral::String(inner.into()).into_literal(outer))
.into_expr(outer)
}
pub fn column_path(members: Vec<Member>, span: impl Into<Span>) -> Expression {
let span = span.into();
RawExpression::Literal(RawLiteral::ColumnPath(members).into_literal(span)).into_expr(span)
}
pub fn path(
head: Expression,
tail: Vec<impl Into<PathMember>>,
span: impl Into<Span>,
) -> Expression {
let tail = tail.into_iter().map(|t| t.into()).collect();
RawExpression::Path(Box::new(Path::new(head, tail))).into_expr(span.into())
}
pub fn dot_member(head: Expression, next: impl Into<PathMember>) -> Expression {
let Expression { expr: item, span } = head;
let next = next.into();
let new_span = head.span.until(next.span);
match item {
RawExpression::Path(path) => {
let (head, mut tail) = path.parts();
tail.push(next);
Expression::path(head, tail, new_span)
}
other => Expression::path(other.into_expr(span), vec![next], new_span),
}
}
pub fn infix(
left: Expression,
op: Spanned<impl Into<Operator>>,
right: Expression,
) -> Expression {
let new_span = left.span.until(right.span);
RawExpression::Binary(Box::new(Binary::new(left, op.map(|o| o.into()), right)))
.into_expr(new_span)
}
pub fn file_path(path: impl Into<PathBuf>, outer: impl Into<Span>) -> Expression {
RawExpression::FilePath(path.into()).into_expr(outer)
}
pub fn list(list: Vec<Expression>, span: impl Into<Span>) -> Expression {
RawExpression::List(list).into_expr(span)
}
pub fn bare(span: impl Into<Span>) -> Expression {
let span = span.into();
RawExpression::Literal(RawLiteral::Bare.into_literal(span)).into_expr(span)
}
pub fn pattern(inner: impl Into<String>, outer: impl Into<Span>) -> Expression {
let outer = outer.into();
RawExpression::Literal(RawLiteral::GlobPattern(inner.into()).into_literal(outer))
.into_expr(outer)
}
pub fn variable(inner: impl Into<Span>, outer: impl Into<Span>) -> Expression {
RawExpression::Variable(Variable::Other(inner.into())).into_expr(outer)
}
pub fn external_command(inner: impl Into<Span>, outer: impl Into<Span>) -> Expression {
RawExpression::ExternalCommand(ExternalCommand::new(inner.into())).into_expr(outer)
}
pub fn it_variable(inner: impl Into<Span>, outer: impl Into<Span>) -> Expression {
RawExpression::Variable(Variable::It(inner.into())).into_expr(outer)
}
}
impl From<Spanned<Path>> for Expression {
fn from(path: Spanned<Path>) -> Expression {
RawExpression::Path(Box::new(path.item)).into_expr(path.span)
}
}
/// Literals are expressions that are:
///
/// 1. Copy
/// 2. Can be evaluated without additional context
/// 3. Evaluation cannot produce an error
#[derive(Debug, Clone, Eq, PartialEq, Ord, PartialOrd, Hash, Serialize, Deserialize)]
pub enum RawLiteral {
Number(Number),
Size(Number, Unit),
String(Span),
GlobPattern(String),
ColumnPath(Vec<Member>),
Bare,
}
impl RawLiteral {
pub fn into_literal(self, span: impl Into<Span>) -> Literal {
Literal {
literal: self,
span: span.into(),
}
}
}
#[derive(Debug, Clone, Eq, PartialEq, Ord, PartialOrd, Hash, Serialize, Deserialize)]
pub struct Literal {
pub literal: RawLiteral,
pub span: Span,
}
impl ShellTypeName for Literal {
fn type_name(&self) -> &'static str {
match &self.literal {
RawLiteral::Number(..) => "number",
RawLiteral::Size(..) => "size",
RawLiteral::String(..) => "string",
RawLiteral::ColumnPath(..) => "column path",
RawLiteral::Bare => "string",
RawLiteral::GlobPattern(_) => "pattern",
}
}
}
impl PrettyDebugWithSource for Literal {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
match &self.literal {
RawLiteral::Number(number) => number.pretty(),
RawLiteral::Size(number, unit) => (number.pretty() + unit.pretty()).group(),
RawLiteral::String(string) => b::primitive(format!("{:?}", string.slice(source))),
RawLiteral::GlobPattern(pattern) => b::typed("pattern", b::primitive(pattern)),
RawLiteral::ColumnPath(path) => b::typed(
"column path",
b::intersperse_with_source(path.iter(), b::space(), source),
),
RawLiteral::Bare => b::primitive(self.span.slice(source)),
}
}
}
#[derive(Debug, Clone, Eq, PartialEq, Ord, PartialOrd, Hash, Serialize, Deserialize)]
pub enum Variable {
It(Span),
Other(Span),
}

View File

@ -0,0 +1,2 @@
#[cfg(test)]
mod tests;

View File

@ -0,0 +1,176 @@
use crate::commands::classified::{ClassifiedCommand, InternalCommand};
use crate::hir::TokensIterator;
use crate::hir::{self, named::NamedValue, syntax_shape::*, NamedArguments};
use crate::parse::files::Files;
use crate::parse::token_tree_builder::{CurriedToken, TokenTreeBuilder as b};
use crate::TokenNode;
use derive_new::new;
use indexmap::IndexMap;
use nu_errors::ShellError;
use nu_protocol::{PathMember, Signature, SyntaxShape};
use nu_source::{HasSpan, Span, Tag, Text};
use pretty_assertions::assert_eq;
use std::fmt::Debug;
#[test]
fn test_parse_string() {
parse_tokens(StringShape, vec![b::string("hello")], |tokens| {
hir::Expression::string(inner_string_span(tokens[0].span()), tokens[0].span())
});
}
#[test]
fn test_parse_path() {
parse_tokens(
VariablePathShape,
vec![b::var("it"), b::op("."), b::bare("cpu")],
|tokens| {
let (outer_var, inner_var) = tokens[0].expect_var();
let bare = tokens[2].expect_bare();
hir::Expression::path(
hir::Expression::it_variable(inner_var, outer_var),
vec![PathMember::string("cpu", bare)],
outer_var.until(bare),
)
},
);
parse_tokens(
VariablePathShape,
vec![
b::var("cpu"),
b::op("."),
b::bare("amount"),
b::op("."),
b::string("max ghz"),
],
|tokens| {
let (outer_var, inner_var) = tokens[0].expect_var();
let amount = tokens[2].expect_bare();
let (outer_max_ghz, _) = tokens[4].expect_string();
hir::Expression::path(
hir::Expression::variable(inner_var, outer_var),
vec![
PathMember::string("amount", amount),
PathMember::string("max ghz", outer_max_ghz),
],
outer_var.until(outer_max_ghz),
)
},
);
}
#[test]
fn test_parse_command() {
parse_tokens(
ClassifiedCommandShape,
vec![b::bare("ls"), b::sp(), b::pattern("*.txt")],
|tokens| {
let bare = tokens[0].expect_bare();
let pat = tokens[2].expect_pattern();
let mut map = IndexMap::new();
map.insert("full".to_string(), NamedValue::AbsentSwitch);
ClassifiedCommand::Internal(InternalCommand::new(
"ls".to_string(),
Tag {
span: bare,
anchor: None,
},
hir::Call {
head: Box::new(hir::RawExpression::Command(bare).into_expr(bare)),
positional: Some(vec![hir::Expression::pattern("*.txt", pat)]),
named: Some(NamedArguments { named: map }),
span: bare.until(pat),
},
))
},
);
}
#[derive(new)]
struct TestRegistry {
#[new(default)]
signatures: indexmap::IndexMap<String, Signature>,
}
impl TestRegistry {
fn insert(&mut self, key: &str, value: Signature) {
self.signatures.insert(key.to_string(), value);
}
}
impl SignatureRegistry for TestRegistry {
fn has(&self, name: &str) -> bool {
self.signatures.contains_key(name)
}
fn get(&self, name: &str) -> Option<Signature> {
self.signatures.get(name).map(|sig| sig.clone())
}
}
fn with_empty_context(source: &Text, callback: impl FnOnce(ExpandContext)) {
let mut registry = TestRegistry::new();
registry.insert(
"ls",
Signature::build("ls")
.optional(
"path",
SyntaxShape::Pattern,
"a path to get the directory contents from",
)
.switch("full", "list all available columns for each entry"),
);
callback(ExpandContext::new(Box::new(registry), source, None))
}
fn parse_tokens<T: Eq + HasSpan + Clone + Debug + 'static>(
shape: impl ExpandSyntax<Output = T>,
tokens: Vec<CurriedToken>,
expected: impl FnOnce(&[TokenNode]) -> T,
) {
let tokens = b::token_list(tokens);
let (tokens, source) = b::build(tokens);
let text = Text::from(source);
with_empty_context(&text, |context| {
let tokens = tokens.expect_list();
let mut iterator = TokensIterator::all(tokens.item, text.clone(), tokens.span);
let expr = expand_syntax(&shape, &mut iterator, &context);
let expr = match expr {
Ok(expr) => expr,
Err(err) => {
print_err(err.into(), context.source().clone());
panic!("Parse failed");
}
};
assert_eq!(expr, expected(tokens.item));
})
}
fn inner_string_span(span: Span) -> Span {
Span::new(span.start() + 1, span.end() - 1)
}
pub fn print_err(err: ShellError, source: &Text) {
let diag = err.to_diagnostic();
let writer = termcolor::StandardStream::stderr(termcolor::ColorChoice::Auto);
let mut source = source.to_string();
source.push_str(" ");
let files = Files::new(source);
let _ = std::panic::catch_unwind(move || {
let _ = language_reporting::emit(
&mut writer.lock(),
&files,
&diag,
&language_reporting::DefaultConfig,
);
});
}

View File

@ -0,0 +1,31 @@
use crate::{hir::Expression, Operator};
use derive_new::new;
use getset::Getters;
use nu_source::{b, DebugDocBuilder, PrettyDebugWithSource, Spanned};
use serde::{Deserialize, Serialize};
#[derive(
Debug, Clone, Eq, PartialEq, Ord, PartialOrd, Hash, Getters, Serialize, Deserialize, new,
)]
#[get = "pub"]
pub struct Binary {
left: Expression,
op: Spanned<Operator>,
right: Expression,
}
impl PrettyDebugWithSource for Binary {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
b::delimit(
"<",
self.left.pretty_debug(source)
+ b::space()
+ b::keyword(self.op.span.slice(source))
+ b::space()
+ self.right.pretty_debug(source),
">",
)
.group()
}
}

View File

@ -0,0 +1,382 @@
#[cfg(not(coloring_in_tokens))]
use crate::hir::syntax_shape::FlatShape;
use crate::{
hir::syntax_shape::{
color_syntax, expand_atom, expand_expr, expand_syntax, AtomicToken, ColorSyntax,
ExpandContext, ExpandExpression, ExpandSyntax, ExpansionRule, MaybeSpaceShape,
UnspannedAtomicToken,
},
hir::Expression,
TokensIterator,
};
use nu_errors::ParseError;
use nu_source::{b, DebugDocBuilder, HasSpan, PrettyDebug, Span, Spanned, SpannedItem};
#[derive(Debug, Clone)]
pub struct ExternalTokensSyntax {
pub tokens: Spanned<Vec<Spanned<String>>>,
}
impl HasSpan for ExternalTokensSyntax {
fn span(&self) -> Span {
self.tokens.span
}
}
impl PrettyDebug for ExternalTokensSyntax {
fn pretty(&self) -> DebugDocBuilder {
b::intersperse(
self.tokens
.iter()
.map(|token| b::primitive(format!("{:?}", token.item))),
b::space(),
)
}
}
#[derive(Debug, Copy, Clone)]
pub struct ExternalTokensShape;
impl ExpandSyntax for ExternalTokensShape {
type Output = ExternalTokensSyntax;
fn name(&self) -> &'static str {
"external command"
}
fn expand_syntax<'a, 'b>(
&self,
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<Self::Output, ParseError> {
let mut out: Vec<Spanned<String>> = vec![];
let start = token_nodes.span_at_cursor();
loop {
match expand_syntax(&ExternalExpressionShape, token_nodes, context) {
Err(_) | Ok(None) => break,
Ok(Some(span)) => out.push(span.spanned_string(context.source())),
}
}
let end = token_nodes.span_at_cursor();
Ok(ExternalTokensSyntax {
tokens: out.spanned(start.until(end)),
})
}
}
#[cfg(not(coloring_in_tokens))]
impl ColorSyntax for ExternalTokensShape {
type Info = ();
type Input = ();
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> Self::Info {
loop {
// Allow a space
color_syntax(&MaybeSpaceShape, token_nodes, context, shapes);
// Process an external expression. External expressions are mostly words, with a
// few exceptions (like $variables and path expansion rules)
match color_syntax(&ExternalExpression, token_nodes, context, shapes).1 {
ExternalExpressionResult::Eof => break,
ExternalExpressionResult::Processed => continue,
}
}
}
}
#[cfg(coloring_in_tokens)]
impl ColorSyntax for ExternalTokensShape {
type Info = ();
type Input = ();
fn name(&self) -> &'static str {
"ExternalTokensShape"
}
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Self::Info {
loop {
// Allow a space
color_syntax(&MaybeSpaceShape, token_nodes, context);
// Process an external expression. External expressions are mostly words, with a
// few exceptions (like $variables and path expansion rules)
match color_syntax(&ExternalExpression, token_nodes, context).1 {
ExternalExpressionResult::Eof => break,
ExternalExpressionResult::Processed => continue,
}
}
}
}
#[derive(Debug, Copy, Clone)]
pub struct ExternalExpressionShape;
impl ExpandSyntax for ExternalExpressionShape {
type Output = Option<Span>;
fn name(&self) -> &'static str {
"external expression"
}
fn expand_syntax<'a, 'b>(
&self,
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<Self::Output, ParseError> {
expand_syntax(&MaybeSpaceShape, token_nodes, context)?;
let first = expand_atom(
token_nodes,
"external command",
context,
ExpansionRule::new().allow_external_command(),
)?
.span;
let mut last = first;
loop {
let continuation = expand_expr(&ExternalContinuationShape, token_nodes, context);
if let Ok(continuation) = continuation {
last = continuation.span;
} else {
break;
}
}
Ok(Some(first.until(last)))
}
}
#[derive(Debug, Copy, Clone)]
struct ExternalExpression;
impl ExpandSyntax for ExternalExpression {
type Output = Option<Span>;
fn name(&self) -> &'static str {
"external expression"
}
fn expand_syntax<'a, 'b>(
&self,
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<Self::Output, ParseError> {
expand_syntax(&MaybeSpaceShape, token_nodes, context)?;
let first = expand_syntax(&ExternalHeadShape, token_nodes, context)?.span;
let mut last = first;
loop {
let continuation = expand_syntax(&ExternalContinuationShape, token_nodes, context);
if let Ok(continuation) = continuation {
last = continuation.span;
} else {
break;
}
}
Ok(Some(first.until(last)))
}
}
#[derive(Debug, Copy, Clone)]
struct ExternalHeadShape;
impl ExpandExpression for ExternalHeadShape {
fn name(&self) -> &'static str {
"external argument"
}
fn expand_expr<'a, 'b>(
&self,
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<Expression, ParseError> {
let atom = expand_atom(
token_nodes,
"external argument",
context,
ExpansionRule::new()
.allow_external_word()
.treat_size_as_word(),
)?;
let span = atom.span;
Ok(match &atom.unspanned {
UnspannedAtomicToken::Eof { .. } => unreachable!("ExpansionRule doesn't allow EOF"),
UnspannedAtomicToken::Error { .. } => unreachable!("ExpansionRule doesn't allow Error"),
UnspannedAtomicToken::Size { .. } => unreachable!("ExpansionRule treats size as word"),
UnspannedAtomicToken::Whitespace { .. } => {
unreachable!("ExpansionRule doesn't allow Whitespace")
}
UnspannedAtomicToken::ShorthandFlag { .. }
| UnspannedAtomicToken::SquareDelimited { .. } => {
return Err(ParseError::mismatch(
"external command name",
"pipeline".spanned(atom.span),
))
}
UnspannedAtomicToken::ExternalCommand { command } => {
Expression::external_command(*command, span)
}
UnspannedAtomicToken::Number { number } => {
Expression::number(number.to_number(context.source()), span)
}
UnspannedAtomicToken::String { body } => Expression::string(*body, span),
UnspannedAtomicToken::ItVariable { name } => Expression::it_variable(*name, span),
UnspannedAtomicToken::Variable { name } => Expression::variable(*name, span),
UnspannedAtomicToken::ExternalWord { .. }
| UnspannedAtomicToken::GlobPattern { .. }
| UnspannedAtomicToken::Word { .. }
| UnspannedAtomicToken::Dot { .. }
| UnspannedAtomicToken::Operator { .. } => Expression::external_command(span, span),
})
}
}
#[derive(Debug, Copy, Clone)]
struct ExternalContinuationShape;
impl ExpandExpression for ExternalContinuationShape {
fn name(&self) -> &'static str {
"external argument"
}
fn expand_expr<'a, 'b>(
&self,
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<Expression, ParseError> {
let atom = expand_atom(
token_nodes,
"external argument",
context,
ExpansionRule::new()
.allow_external_word()
.treat_size_as_word(),
)?;
let span = atom.span;
Ok(match &atom.unspanned {
UnspannedAtomicToken::Eof { .. } => unreachable!("ExpansionRule doesn't allow EOF"),
UnspannedAtomicToken::Error { .. } => unreachable!("ExpansionRule doesn't allow Error"),
UnspannedAtomicToken::Number { number } => {
Expression::number(number.to_number(context.source()), span)
}
UnspannedAtomicToken::Size { .. } => unreachable!("ExpansionRule treats size as word"),
UnspannedAtomicToken::ExternalCommand { .. } => {
unreachable!("ExpansionRule doesn't allow ExternalCommand")
}
UnspannedAtomicToken::Whitespace { .. } => {
unreachable!("ExpansionRule doesn't allow Whitespace")
}
UnspannedAtomicToken::String { body } => Expression::string(*body, span),
UnspannedAtomicToken::ItVariable { name } => Expression::it_variable(*name, span),
UnspannedAtomicToken::Variable { name } => Expression::variable(*name, span),
UnspannedAtomicToken::ExternalWord { .. }
| UnspannedAtomicToken::GlobPattern { .. }
| UnspannedAtomicToken::Word { .. }
| UnspannedAtomicToken::ShorthandFlag { .. }
| UnspannedAtomicToken::Dot { .. }
| UnspannedAtomicToken::Operator { .. } => Expression::bare(span),
UnspannedAtomicToken::SquareDelimited { .. } => {
return Err(ParseError::mismatch(
"external argument",
"pipeline".spanned(atom.span),
))
}
})
}
}
#[cfg(coloring_in_tokens)]
impl ColorSyntax for ExternalExpression {
type Info = ExternalExpressionResult;
type Input = ();
fn name(&self) -> &'static str {
"ExternalExpression"
}
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> ExternalExpressionResult {
let atom = match expand_atom(
token_nodes,
"external word",
context,
ExpansionRule::permissive(),
) {
Err(_) => unreachable!("TODO: separate infallible expand_atom"),
Ok(AtomicToken {
unspanned: UnspannedAtomicToken::Eof { .. },
..
}) => return ExternalExpressionResult::Eof,
Ok(atom) => atom,
};
token_nodes.mutate_shapes(|shapes| atom.color_tokens(shapes));
return ExternalExpressionResult::Processed;
}
}
#[must_use]
enum ExternalExpressionResult {
Eof,
Processed,
}
#[cfg(not(coloring_in_tokens))]
impl ColorSyntax for ExternalExpression {
type Info = ExternalExpressionResult;
type Input = ();
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> ExternalExpressionResult {
let atom = match expand_atom(
token_nodes,
"external word",
context,
ExpansionRule::permissive(),
) {
Err(_) => unreachable!("TODO: separate infallible expand_atom"),
Ok(AtomicToken {
unspanned: UnspannedAtomicToken::Eof { .. },
..
}) => return ExternalExpressionResult::Eof,
Ok(atom) => atom,
};
atom.color_tokens(shapes);
return ExternalExpressionResult::Processed;
}
}

View File

@ -0,0 +1,12 @@
use derive_new::new;
use getset::Getters;
use nu_source::Span;
use serde::{Deserialize, Serialize};
#[derive(
Debug, Clone, Eq, PartialEq, Ord, PartialOrd, Hash, Getters, Serialize, Deserialize, new,
)]
#[get = "pub"]
pub struct ExternalCommand {
pub(crate) name: Span,
}

View File

@ -0,0 +1,86 @@
use crate::hir::Expression;
use crate::Flag;
use indexmap::IndexMap;
use log::trace;
use nu_source::{b, DebugDocBuilder, PrettyDebugWithSource, Tag};
use serde::{Deserialize, Serialize};
#[derive(Debug, Clone, Eq, PartialEq, Serialize, Deserialize)]
pub enum NamedValue {
AbsentSwitch,
PresentSwitch(Tag),
AbsentValue,
Value(Expression),
}
impl PrettyDebugWithSource for NamedValue {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
match self {
NamedValue::AbsentSwitch => b::typed("switch", b::description("absent")),
NamedValue::PresentSwitch(_) => b::typed("switch", b::description("present")),
NamedValue::AbsentValue => b::description("absent"),
NamedValue::Value(value) => value.pretty_debug(source),
}
}
}
#[derive(Debug, Clone, Eq, PartialEq, Serialize, Deserialize)]
pub struct NamedArguments {
pub named: IndexMap<String, NamedValue>,
}
impl NamedArguments {
pub fn new() -> NamedArguments {
NamedArguments {
named: IndexMap::new(),
}
}
pub fn iter(&self) -> impl Iterator<Item = (&String, &NamedValue)> {
self.named.iter()
}
}
impl NamedArguments {
pub fn insert_switch(&mut self, name: impl Into<String>, switch: Option<Flag>) {
let name = name.into();
trace!("Inserting switch -- {} = {:?}", name, switch);
match switch {
None => self.named.insert(name.into(), NamedValue::AbsentSwitch),
Some(flag) => self.named.insert(
name,
NamedValue::PresentSwitch(Tag {
span: *flag.name(),
anchor: None,
}),
),
};
}
pub fn insert_optional(&mut self, name: impl Into<String>, expr: Option<Expression>) {
match expr {
None => self.named.insert(name.into(), NamedValue::AbsentValue),
Some(expr) => self.named.insert(name.into(), NamedValue::Value(expr)),
};
}
pub fn insert_mandatory(&mut self, name: impl Into<String>, expr: Expression) {
self.named.insert(name.into(), NamedValue::Value(expr));
}
}
impl PrettyDebugWithSource for NamedArguments {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
b::delimit(
"(",
b::intersperse(
self.named
.iter()
.map(|(key, value)| b::key(key) + b::equals() + value.pretty_debug(source)),
b::space(),
),
")",
)
}
}

View File

@ -0,0 +1,41 @@
use crate::hir::Expression;
use derive_new::new;
use getset::{Getters, MutGetters};
use nu_protocol::PathMember;
use nu_source::{b, DebugDocBuilder, PrettyDebug, PrettyDebugWithSource};
use serde::{Deserialize, Serialize};
#[derive(
Debug,
Clone,
Eq,
PartialEq,
Ord,
PartialOrd,
Hash,
Getters,
MutGetters,
Serialize,
Deserialize,
new,
)]
#[get = "pub"]
pub struct Path {
head: Expression,
#[get_mut = "pub(crate)"]
tail: Vec<PathMember>,
}
impl PrettyDebugWithSource for Path {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
self.head.pretty_debug(source)
+ b::operator(".")
+ b::intersperse(self.tail.iter().map(|m| m.pretty()), b::operator("."))
}
}
impl Path {
pub(crate) fn parts(self) -> (Expression, Vec<PathMember>) {
(self.head, self.tail)
}
}

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,495 @@
#[cfg(not(coloring_in_tokens))]
use crate::hir::syntax_shape::FlatShape;
use crate::{
hir,
hir::syntax_shape::{
color_fallible_syntax, color_syntax_with, continue_expression, expand_expr, expand_syntax,
DelimitedShape, ExpandContext, ExpandExpression, ExpressionContinuationShape,
ExpressionListShape, FallibleColorSyntax, MemberShape, PathTailShape, PathTailSyntax,
VariablePathShape,
},
hir::tokens_iterator::TokensIterator,
parse::token_tree::Delimiter,
};
use nu_errors::{ParseError, ShellError};
use nu_source::Span;
#[cfg(not(coloring_in_tokens))]
use nu_source::Spanned;
#[derive(Debug, Copy, Clone)]
pub struct AnyBlockShape;
#[cfg(not(coloring_in_tokens))]
impl FallibleColorSyntax for AnyBlockShape {
type Info = ();
type Input = ();
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> Result<(), ShellError> {
let block = token_nodes.peek_non_ws().not_eof("block");
let block = match block {
Err(_) => return Ok(()),
Ok(block) => block,
};
// is it just a block?
let block = block.node.as_block();
match block {
// If so, color it as a block
Some((children, spans)) => {
let mut token_nodes = TokensIterator::new(
children.item,
children.span,
context.source.clone(),
false,
);
color_syntax_with(
&DelimitedShape,
&(Delimiter::Brace, spans.0, spans.1),
&mut token_nodes,
context,
shapes,
);
return Ok(());
}
_ => {}
}
// Otherwise, look for a shorthand block. If none found, fail
color_fallible_syntax(&ShorthandBlock, token_nodes, context, shapes)
}
}
#[cfg(coloring_in_tokens)]
impl FallibleColorSyntax for AnyBlockShape {
type Info = ();
type Input = ();
fn name(&self) -> &'static str {
"AnyBlockShape"
}
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<(), ShellError> {
let block = token_nodes.peek_non_ws().not_eof("block");
let block = match block {
Err(_) => return Ok(()),
Ok(block) => block,
};
// is it just a block?
let block = block.node.as_block();
match block {
// If so, color it as a block
Some((children, spans)) => {
token_nodes.child(children, context.source.clone(), |token_nodes| {
color_syntax_with(
&DelimitedShape,
&(Delimiter::Brace, spans.0, spans.1),
token_nodes,
context,
);
});
return Ok(());
}
_ => {}
}
// Otherwise, look for a shorthand block. If none found, fail
color_fallible_syntax(&ShorthandBlock, token_nodes, context)
}
}
impl ExpandExpression for AnyBlockShape {
fn name(&self) -> &'static str {
"any block"
}
fn expand_expr<'a, 'b>(
&self,
token_nodes: &mut TokensIterator<'_>,
context: &ExpandContext,
) -> Result<hir::Expression, ParseError> {
let block = token_nodes.peek_non_ws().not_eof("block")?;
// is it just a block?
let block = block.node.as_block();
match block {
Some((block, _tags)) => {
let mut iterator =
TokensIterator::new(&block.item, block.span, context.source.clone(), false);
let exprs = expand_syntax(&ExpressionListShape, &mut iterator, context)?.exprs;
return Ok(hir::RawExpression::Block(exprs.item).into_expr(block.span));
}
_ => {}
}
expand_syntax(&ShorthandBlock, token_nodes, context)
}
}
#[derive(Debug, Copy, Clone)]
pub struct ShorthandBlock;
#[cfg(not(coloring_in_tokens))]
impl FallibleColorSyntax for ShorthandBlock {
type Info = ();
type Input = ();
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> Result<(), ShellError> {
// Try to find a shorthand head. If none found, fail
color_fallible_syntax(&ShorthandPath, token_nodes, context, shapes)?;
loop {
// Check to see whether there's any continuation after the head expression
let result =
color_fallible_syntax(&ExpressionContinuationShape, token_nodes, context, shapes);
match result {
// if no continuation was found, we're done
Err(_) => break,
// if a continuation was found, look for another one
Ok(_) => continue,
}
}
Ok(())
}
}
#[cfg(coloring_in_tokens)]
impl FallibleColorSyntax for ShorthandBlock {
type Info = ();
type Input = ();
fn name(&self) -> &'static str {
"ShorthandBlock"
}
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<(), ShellError> {
// Try to find a shorthand head. If none found, fail
color_fallible_syntax(&ShorthandPath, token_nodes, context)?;
loop {
// Check to see whether there's any continuation after the head expression
let result = color_fallible_syntax(&ExpressionContinuationShape, token_nodes, context);
match result {
// if no continuation was found, we're done
Err(_) => break,
// if a continuation was found, look for another one
Ok(_) => continue,
}
}
Ok(())
}
}
impl ExpandExpression for ShorthandBlock {
fn name(&self) -> &'static str {
"shorthand block"
}
fn expand_expr<'a, 'b>(
&self,
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<hir::Expression, ParseError> {
let path = expand_expr(&ShorthandPath, token_nodes, context)?;
let start = path.span;
let expr = continue_expression(path, token_nodes, context);
let end = expr.span;
let block = hir::RawExpression::Block(vec![expr]).into_expr(start.until(end));
Ok(block)
}
}
/// A shorthand for `$it.foo."bar"`, used inside of a shorthand block
#[derive(Debug, Copy, Clone)]
pub struct ShorthandPath;
#[cfg(not(coloring_in_tokens))]
impl FallibleColorSyntax for ShorthandPath {
type Info = ();
type Input = ();
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> Result<(), ShellError> {
token_nodes.atomic(|token_nodes| {
let variable = color_fallible_syntax(&VariablePathShape, token_nodes, context, shapes);
match variable {
Ok(_) => {
// if it's a variable path, that's the head part
return Ok(());
}
Err(_) => {
// otherwise, we'll try to find a member path
}
}
// look for a member (`<member>` -> `$it.<member>`)
color_fallible_syntax(&MemberShape, token_nodes, context, shapes)?;
// Now that we've synthesized the head, of the path, proceed to expand the tail of the path
// like any other path.
let tail = color_fallible_syntax(&PathTailShape, token_nodes, context, shapes);
match tail {
Ok(_) => {}
Err(_) => {
// It's ok if there's no path tail; a single member is sufficient
}
}
Ok(())
})
}
}
#[cfg(coloring_in_tokens)]
impl FallibleColorSyntax for ShorthandPath {
type Info = ();
type Input = ();
fn name(&self) -> &'static str {
"ShorthandPath"
}
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<(), ShellError> {
token_nodes.atomic(|token_nodes| {
let variable = color_fallible_syntax(&VariablePathShape, token_nodes, context);
match variable {
Ok(_) => {
// if it's a variable path, that's the head part
return Ok(());
}
Err(_) => {
// otherwise, we'll try to find a member path
}
}
// look for a member (`<member>` -> `$it.<member>`)
color_fallible_syntax(&MemberShape, token_nodes, context)?;
// Now that we've synthesized the head, of the path, proceed to expand the tail of the path
// like any other path.
let tail = color_fallible_syntax(&PathTailShape, token_nodes, context);
match tail {
Ok(_) => {}
Err(_) => {
// It's ok if there's no path tail; a single member is sufficient
}
}
Ok(())
})
}
}
impl ExpandExpression for ShorthandPath {
fn name(&self) -> &'static str {
"shorthand path"
}
fn expand_expr<'a, 'b>(
&self,
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<hir::Expression, ParseError> {
// if it's a variable path, that's the head part
let path = expand_expr(&VariablePathShape, token_nodes, context);
match path {
Ok(path) => return Ok(path),
Err(_) => {}
}
// Synthesize the head of the shorthand path (`<member>` -> `$it.<member>`)
let mut head = expand_expr(&ShorthandHeadShape, token_nodes, context)?;
// Now that we've synthesized the head, of the path, proceed to expand the tail of the path
// like any other path.
let tail = expand_syntax(&PathTailShape, token_nodes, context);
match tail {
Err(_) => return Ok(head),
Ok(PathTailSyntax { tail, .. }) => {
// For each member that `PathTailShape` expanded, join it onto the existing expression
// to form a new path
for member in tail {
head = hir::Expression::dot_member(head, member);
}
Ok(head)
}
}
}
}
/// A shorthand for `$it.foo."bar"`, used inside of a shorthand block
#[derive(Debug, Copy, Clone)]
pub struct ShorthandHeadShape;
#[cfg(not(coloring_in_tokens))]
impl FallibleColorSyntax for ShorthandHeadShape {
type Info = ();
type Input = ();
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
_context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> Result<(), ShellError> {
use crate::parse::token_tree::TokenNode;
use crate::parse::tokens::{Token, UnspannedToken};
use nu_source::SpannedItem;
// A shorthand path must not be at EOF
let peeked = token_nodes.peek_non_ws().not_eof("shorthand path head")?;
match peeked.node {
// If the head of a shorthand path is a bare token, it expands to `$it.bare`
TokenNode::Token(Token {
unspanned: UnspannedToken::Bare,
span,
}) => {
peeked.commit();
shapes.push(FlatShape::BareMember.spanned(*span));
Ok(())
}
// If the head of a shorthand path is a string, it expands to `$it."some string"`
TokenNode::Token(Token {
unspanned: UnspannedToken::String(_),
span: outer,
}) => {
peeked.commit();
shapes.push(FlatShape::StringMember.spanned(*outer));
Ok(())
}
other => Err(ShellError::type_error(
"shorthand head",
other.spanned_type_name(),
)),
}
}
}
#[cfg(coloring_in_tokens)]
#[cfg(not(coloring_in_tokens))]
impl FallibleColorSyntax for ShorthandHeadShape {
type Info = ();
type Input = ();
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
_context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> Result<(), ShellError> {
// A shorthand path must not be at EOF
let peeked = token_nodes.peek_non_ws().not_eof("shorthand path head")?;
match peeked.node {
// If the head of a shorthand path is a bare token, it expands to `$it.bare`
TokenNode::Token(Spanned {
item: UnspannedToken::Bare,
span,
}) => {
peeked.commit();
shapes.push(FlatShape::BareMember.spanned(*span));
Ok(())
}
// If the head of a shorthand path is a string, it expands to `$it."some string"`
TokenNode::Token(Spanned {
item: UnspannedToken::String(_),
span: outer,
}) => {
peeked.commit();
shapes.push(FlatShape::StringMember.spanned(*outer));
Ok(())
}
other => Err(ShellError::type_error(
"shorthand head",
other.tagged_type_name(),
)),
}
}
}
impl ExpandExpression for ShorthandHeadShape {
fn name(&self) -> &'static str {
"shorthand head"
}
fn expand_expr<'a, 'b>(
&self,
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<hir::Expression, ParseError> {
let head = expand_syntax(&MemberShape, token_nodes, context)?;
let head = head.to_path_member(context.source);
// Synthesize an `$it` expression
let it = synthetic_it();
let span = head.span;
Ok(hir::Expression::path(it, vec![head], span))
}
}
fn synthetic_it() -> hir::Expression {
hir::Expression::it_variable(Span::unknown(), Span::unknown())
}

View File

@ -0,0 +1,504 @@
pub(crate) mod atom;
pub(crate) mod delimited;
pub(crate) mod file_path;
pub(crate) mod list;
pub(crate) mod number;
pub(crate) mod pattern;
pub(crate) mod string;
pub(crate) mod unit;
pub(crate) mod variable_path;
use crate::hir::syntax_shape::{
color_delimited_square, color_fallible_syntax, color_fallible_syntax_with, expand_atom,
expand_delimited_square, expand_expr, expand_syntax, BareShape, ColorableDotShape, DotShape,
ExpandContext, ExpandExpression, ExpandSyntax, ExpansionRule, ExpressionContinuation,
ExpressionContinuationShape, FallibleColorSyntax, FlatShape, UnspannedAtomicToken,
};
use crate::{
hir,
hir::{Expression, TokensIterator},
};
use nu_errors::{ParseError, ShellError};
use nu_source::{HasSpan, Span, Spanned, SpannedItem, Tag};
use std::path::PathBuf;
#[derive(Debug, Copy, Clone)]
pub struct AnyExpressionShape;
impl ExpandExpression for AnyExpressionShape {
fn name(&self) -> &'static str {
"any expression"
}
fn expand_expr<'a, 'b>(
&self,
token_nodes: &mut TokensIterator<'_>,
context: &ExpandContext,
) -> Result<hir::Expression, ParseError> {
// Look for an expression at the cursor
let head = expand_expr(&AnyExpressionStartShape, token_nodes, context)?;
Ok(continue_expression(head, token_nodes, context))
}
}
#[cfg(not(coloring_in_tokens))]
impl FallibleColorSyntax for AnyExpressionShape {
type Info = ();
type Input = ();
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> Result<(), ShellError> {
// Look for an expression at the cursor
color_fallible_syntax(&AnyExpressionStartShape, token_nodes, context, shapes)?;
match continue_coloring_expression(token_nodes, context, shapes) {
Err(_) => {
// it's fine for there to be no continuation
}
Ok(()) => {}
}
Ok(())
}
}
#[cfg(coloring_in_tokens)]
impl FallibleColorSyntax for AnyExpressionShape {
type Info = ();
type Input = ();
fn name(&self) -> &'static str {
"AnyExpressionShape"
}
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<(), ShellError> {
// Look for an expression at the cursor
color_fallible_syntax(&AnyExpressionStartShape, token_nodes, context)?;
match continue_coloring_expression(token_nodes, context) {
Err(_) => {
// it's fine for there to be no continuation
}
Ok(()) => {}
}
Ok(())
}
}
pub(crate) fn continue_expression(
mut head: hir::Expression,
token_nodes: &mut TokensIterator<'_>,
context: &ExpandContext,
) -> hir::Expression {
loop {
// Check to see whether there's any continuation after the head expression
let continuation = expand_syntax(&ExpressionContinuationShape, token_nodes, context);
match continuation {
// If there's no continuation, return the head
Err(_) => return head,
// Otherwise, form a new expression by combining the head with the continuation
Ok(continuation) => match continuation {
// If the continuation is a `.member`, form a path with the new member
ExpressionContinuation::DotSuffix(_dot, member) => {
head = Expression::dot_member(head, member);
}
// Otherwise, if the continuation is an infix suffix, form an infix expression
ExpressionContinuation::InfixSuffix(op, expr) => {
head = Expression::infix(head, op, expr);
}
},
}
}
}
#[cfg(not(coloring_in_tokens))]
pub(crate) fn continue_coloring_expression(
token_nodes: &mut TokensIterator<'_>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> Result<(), ShellError> {
// if there's not even one expression continuation, fail
color_fallible_syntax(&ExpressionContinuationShape, token_nodes, context, shapes)?;
loop {
// Check to see whether there's any continuation after the head expression
let result =
color_fallible_syntax(&ExpressionContinuationShape, token_nodes, context, shapes);
match result {
Err(_) => {
// We already saw one continuation, so just return
return Ok(());
}
Ok(_) => {}
}
}
}
#[cfg(coloring_in_tokens)]
pub(crate) fn continue_coloring_expression(
token_nodes: &mut TokensIterator<'_>,
context: &ExpandContext,
) -> Result<(), ShellError> {
// if there's not even one expression continuation, fail
color_fallible_syntax(&ExpressionContinuationShape, token_nodes, context)?;
loop {
// Check to see whether there's any continuation after the head expression
let result = color_fallible_syntax(&ExpressionContinuationShape, token_nodes, context);
match result {
Err(_) => {
// We already saw one continuation, so just return
return Ok(());
}
Ok(_) => {}
}
}
}
#[derive(Debug, Copy, Clone)]
pub struct AnyExpressionStartShape;
impl ExpandExpression for AnyExpressionStartShape {
fn name(&self) -> &'static str {
"any expression start"
}
fn expand_expr<'a, 'b>(
&self,
token_nodes: &mut TokensIterator<'_>,
context: &ExpandContext,
) -> Result<hir::Expression, ParseError> {
let atom = expand_atom(token_nodes, "expression", context, ExpansionRule::new())?;
match atom.unspanned {
UnspannedAtomicToken::Size { number, unit } => {
return Ok(hir::Expression::size(
number.to_number(context.source),
unit.item,
Tag {
span: atom.span,
anchor: None,
},
))
}
UnspannedAtomicToken::SquareDelimited { nodes, .. } => {
expand_delimited_square(&nodes, atom.span.into(), context)
}
UnspannedAtomicToken::Word { .. } => {
let end = expand_syntax(&BareTailShape, token_nodes, context)?;
Ok(hir::Expression::bare(atom.span.until_option(end)))
}
other => {
return other
.into_atomic_token(atom.span)
.into_hir(context, "expression")
}
}
}
}
#[cfg(not(coloring_in_tokens))]
impl FallibleColorSyntax for AnyExpressionStartShape {
type Info = ();
type Input = ();
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> Result<(), ShellError> {
let atom = token_nodes.spanned(|token_nodes| {
expand_atom(
token_nodes,
"expression",
context,
ExpansionRule::permissive(),
)
});
let atom = match atom {
Spanned {
item: Err(_err),
span,
} => {
shapes.push(FlatShape::Error.spanned(span));
return Ok(());
}
Spanned {
item: Ok(value), ..
} => value,
};
match &atom.unspanned {
UnspannedAtomicToken::Size { number, unit } => shapes.push(
FlatShape::Size {
number: number.span(),
unit: unit.span.into(),
}
.spanned(atom.span),
),
UnspannedAtomicToken::SquareDelimited { nodes, spans } => {
color_delimited_square(*spans, &nodes, atom.span.into(), context, shapes)
}
UnspannedAtomicToken::Word { .. } => {
shapes.push(FlatShape::Word.spanned(atom.span));
}
_ => atom.color_tokens(shapes),
}
Ok(())
}
}
#[cfg(coloring_in_tokens)]
impl FallibleColorSyntax for AnyExpressionStartShape {
type Info = ();
type Input = ();
fn name(&self) -> &'static str {
"AnyExpressionStartShape"
}
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<(), ShellError> {
let atom = token_nodes.spanned(|token_nodes| {
expand_atom(
token_nodes,
"expression",
context,
ExpansionRule::permissive(),
)
});
let atom = match atom {
Spanned {
item: Err(_err),
span,
} => {
token_nodes.color_shape(FlatShape::Error.spanned(span));
return Ok(());
}
Spanned {
item: Ok(value), ..
} => value,
};
match atom.unspanned {
UnspannedAtomicToken::Size { number, unit } => token_nodes.color_shape(
FlatShape::Size {
number: number.span(),
unit: unit.span.into(),
}
.spanned(atom.span),
),
UnspannedAtomicToken::SquareDelimited { nodes, spans } => {
token_nodes.child(
(&nodes[..]).spanned(atom.span),
context.source.clone(),
|tokens| {
color_delimited_square(spans, tokens, atom.span.into(), context);
},
);
}
UnspannedAtomicToken::Word { .. } | UnspannedAtomicToken::Dot { .. } => {
token_nodes.color_shape(FlatShape::Word.spanned(atom.span));
}
_ => token_nodes.mutate_shapes(|shapes| atom.color_tokens(shapes)),
}
Ok(())
}
}
#[derive(Debug, Copy, Clone)]
pub struct BareTailShape;
#[cfg(not(coloring_in_tokens))]
impl FallibleColorSyntax for BareTailShape {
type Info = ();
type Input = ();
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> Result<(), ShellError> {
let len = shapes.len();
loop {
let word = color_fallible_syntax_with(
&BareShape,
&FlatShape::Word,
token_nodes,
context,
shapes,
);
match word {
// if a word was found, continue
Ok(_) => continue,
// if a word wasn't found, try to find a dot
Err(_) => {}
}
// try to find a dot
let dot = color_fallible_syntax_with(
&ColorableDotShape,
&FlatShape::Word,
token_nodes,
context,
shapes,
);
match dot {
// if a dot was found, try to find another word
Ok(_) => continue,
// otherwise, we're done
Err(_) => break,
}
}
if shapes.len() > len {
Ok(())
} else {
Err(ShellError::syntax_error(
"No tokens matched BareTailShape".spanned_unknown(),
))
}
}
}
#[cfg(coloring_in_tokens)]
impl FallibleColorSyntax for BareTailShape {
type Info = ();
type Input = ();
fn name(&self) -> &'static str {
"BareTailShape"
}
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<(), ShellError> {
let len = token_nodes.state().shapes().len();
loop {
let word =
color_fallible_syntax_with(&BareShape, &FlatShape::Word, token_nodes, context);
match word {
// if a word was found, continue
Ok(_) => continue,
// if a word wasn't found, try to find a dot
Err(_) => {}
}
// try to find a dot
let dot = color_fallible_syntax_with(
&ColorableDotShape,
&FlatShape::Word,
token_nodes,
context,
);
match dot {
// if a dot was found, try to find another word
Ok(_) => continue,
// otherwise, we're done
Err(_) => break,
}
}
if token_nodes.state().shapes().len() > len {
Ok(())
} else {
Err(ShellError::syntax_error(
"No tokens matched BareTailShape".spanned_unknown(),
))
}
}
}
impl ExpandSyntax for BareTailShape {
fn name(&self) -> &'static str {
"word continuation"
}
type Output = Option<Span>;
fn expand_syntax<'a, 'b>(
&self,
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<Option<Span>, ParseError> {
let mut end: Option<Span> = None;
loop {
match expand_syntax(&BareShape, token_nodes, context) {
Ok(bare) => {
end = Some(bare.span);
continue;
}
Err(_) => match expand_syntax(&DotShape, token_nodes, context) {
Ok(dot) => {
end = Some(dot);
continue;
}
Err(_) => break,
},
}
}
Ok(end)
}
}
pub fn expand_file_path(string: &str, context: &ExpandContext) -> PathBuf {
let expanded = shellexpand::tilde_with_context(string, || context.homedir());
PathBuf::from(expanded.as_ref())
}

View File

@ -0,0 +1,698 @@
use crate::hir::syntax_shape::FlatShape;
use crate::hir::syntax_shape::{
expand_syntax, expression::expand_file_path, parse_single_node, BarePathShape,
BarePatternShape, ExpandContext, UnitShape, UnitSyntax,
};
use crate::parse::token_tree::{DelimitedNode, Delimiter, TokenNode};
use crate::parse::tokens::UnspannedToken;
use crate::parse::unit::Unit;
use crate::{
hir,
hir::{Expression, RawNumber, TokensIterator},
parse::flag::{Flag, FlagKind},
};
use nu_errors::{ParseError, ShellError};
use nu_protocol::ShellTypeName;
use nu_source::{b, DebugDocBuilder, HasSpan, PrettyDebugWithSource, Span, Spanned, SpannedItem};
use std::ops::Deref;
#[derive(Debug, Clone)]
pub enum UnspannedAtomicToken<'tokens> {
Eof {
span: Span,
},
Error {
error: Spanned<ShellError>,
},
Number {
number: RawNumber,
},
Size {
number: RawNumber,
unit: Spanned<Unit>,
},
String {
body: Span,
},
ItVariable {
name: Span,
},
Variable {
name: Span,
},
ExternalCommand {
command: Span,
},
ExternalWord {
text: Span,
},
GlobPattern {
pattern: Span,
},
Word {
text: Span,
},
#[allow(unused)]
Dot {
text: Span,
},
SquareDelimited {
spans: (Span, Span),
nodes: &'tokens Vec<TokenNode>,
},
ShorthandFlag {
name: Span,
},
Operator {
text: Span,
},
Whitespace {
text: Span,
},
}
impl<'tokens> UnspannedAtomicToken<'tokens> {
pub fn into_atomic_token(self, span: impl Into<Span>) -> AtomicToken<'tokens> {
AtomicToken {
unspanned: self,
span: span.into(),
}
}
}
impl<'tokens> ShellTypeName for UnspannedAtomicToken<'tokens> {
fn type_name(&self) -> &'static str {
match &self {
UnspannedAtomicToken::Eof { .. } => "eof",
UnspannedAtomicToken::Error { .. } => "error",
UnspannedAtomicToken::Operator { .. } => "operator",
UnspannedAtomicToken::ShorthandFlag { .. } => "shorthand flag",
UnspannedAtomicToken::Whitespace { .. } => "whitespace",
UnspannedAtomicToken::Dot { .. } => "dot",
UnspannedAtomicToken::Number { .. } => "number",
UnspannedAtomicToken::Size { .. } => "size",
UnspannedAtomicToken::String { .. } => "string",
UnspannedAtomicToken::ItVariable { .. } => "$it",
UnspannedAtomicToken::Variable { .. } => "variable",
UnspannedAtomicToken::ExternalCommand { .. } => "external command",
UnspannedAtomicToken::ExternalWord { .. } => "external word",
UnspannedAtomicToken::GlobPattern { .. } => "file pattern",
UnspannedAtomicToken::Word { .. } => "word",
UnspannedAtomicToken::SquareDelimited { .. } => "array literal",
}
}
}
#[derive(Debug, Clone)]
pub struct AtomicToken<'tokens> {
pub unspanned: UnspannedAtomicToken<'tokens>,
pub span: Span,
}
impl<'tokens> Deref for AtomicToken<'tokens> {
type Target = UnspannedAtomicToken<'tokens>;
fn deref(&self) -> &UnspannedAtomicToken<'tokens> {
&self.unspanned
}
}
impl<'tokens> AtomicToken<'tokens> {
pub fn into_hir(
&self,
context: &ExpandContext,
expected: &'static str,
) -> Result<hir::Expression, ParseError> {
Ok(match &self.unspanned {
UnspannedAtomicToken::Eof { .. } => {
return Err(ParseError::mismatch(
expected,
"eof atomic token".spanned(self.span),
))
}
UnspannedAtomicToken::Error { .. } => {
return Err(ParseError::mismatch(
expected,
"eof atomic token".spanned(self.span),
))
}
UnspannedAtomicToken::Operator { .. } => {
return Err(ParseError::mismatch(
expected,
"operator".spanned(self.span),
))
}
UnspannedAtomicToken::ShorthandFlag { .. } => {
return Err(ParseError::mismatch(
expected,
"shorthand flag".spanned(self.span),
))
}
UnspannedAtomicToken::Whitespace { .. } => {
return Err(ParseError::mismatch(
expected,
"whitespace".spanned(self.span),
))
}
UnspannedAtomicToken::Dot { .. } => {
return Err(ParseError::mismatch(expected, "dot".spanned(self.span)))
}
UnspannedAtomicToken::Number { number } => {
Expression::number(number.to_number(context.source), self.span)
}
UnspannedAtomicToken::Size { number, unit } => {
Expression::size(number.to_number(context.source), **unit, self.span)
}
UnspannedAtomicToken::String { body } => Expression::string(*body, self.span),
UnspannedAtomicToken::ItVariable { name } => Expression::it_variable(*name, self.span),
UnspannedAtomicToken::Variable { name } => Expression::variable(*name, self.span),
UnspannedAtomicToken::ExternalCommand { command } => {
Expression::external_command(*command, self.span)
}
UnspannedAtomicToken::ExternalWord { text } => Expression::string(*text, self.span),
UnspannedAtomicToken::GlobPattern { pattern } => Expression::pattern(
expand_file_path(pattern.slice(context.source), context).to_string_lossy(),
self.span,
),
UnspannedAtomicToken::Word { text } => Expression::string(*text, *text),
UnspannedAtomicToken::SquareDelimited { .. } => unimplemented!("into_hir"),
})
}
#[cfg(not(coloring_in_tokens))]
pub fn spanned_type_name(&self) -> Spanned<&'static str> {
match &self.unspanned {
UnspannedAtomicToken::Eof { .. } => "eof",
UnspannedAtomicToken::Error { .. } => "error",
UnspannedAtomicToken::Operator { .. } => "operator",
UnspannedAtomicToken::ShorthandFlag { .. } => "shorthand flag",
UnspannedAtomicToken::Whitespace { .. } => "whitespace",
UnspannedAtomicToken::Dot { .. } => "dot",
UnspannedAtomicToken::Number { .. } => "number",
UnspannedAtomicToken::Size { .. } => "size",
UnspannedAtomicToken::String { .. } => "string",
UnspannedAtomicToken::ItVariable { .. } => "$it",
UnspannedAtomicToken::Variable { .. } => "variable",
UnspannedAtomicToken::ExternalCommand { .. } => "external command",
UnspannedAtomicToken::ExternalWord { .. } => "external word",
UnspannedAtomicToken::GlobPattern { .. } => "file pattern",
UnspannedAtomicToken::Word { .. } => "word",
UnspannedAtomicToken::SquareDelimited { .. } => "array literal",
}
.spanned(self.span)
}
pub(crate) fn color_tokens(&self, shapes: &mut Vec<Spanned<FlatShape>>) {
match &self.unspanned {
UnspannedAtomicToken::Eof { .. } => {}
UnspannedAtomicToken::Error { .. } => {
return shapes.push(FlatShape::Error.spanned(self.span))
}
UnspannedAtomicToken::Operator { .. } => {
return shapes.push(FlatShape::Operator.spanned(self.span));
}
UnspannedAtomicToken::ShorthandFlag { .. } => {
return shapes.push(FlatShape::ShorthandFlag.spanned(self.span));
}
UnspannedAtomicToken::Whitespace { .. } => {
return shapes.push(FlatShape::Whitespace.spanned(self.span));
}
UnspannedAtomicToken::Number {
number: RawNumber::Decimal(_),
} => {
return shapes.push(FlatShape::Decimal.spanned(self.span));
}
UnspannedAtomicToken::Number {
number: RawNumber::Int(_),
} => {
return shapes.push(FlatShape::Int.spanned(self.span));
}
UnspannedAtomicToken::Size { number, unit } => {
return shapes.push(
FlatShape::Size {
number: number.span(),
unit: unit.span,
}
.spanned(self.span),
);
}
UnspannedAtomicToken::String { .. } => {
return shapes.push(FlatShape::String.spanned(self.span))
}
UnspannedAtomicToken::ItVariable { .. } => {
return shapes.push(FlatShape::ItVariable.spanned(self.span))
}
UnspannedAtomicToken::Variable { .. } => {
return shapes.push(FlatShape::Variable.spanned(self.span))
}
UnspannedAtomicToken::ExternalCommand { .. } => {
return shapes.push(FlatShape::ExternalCommand.spanned(self.span));
}
UnspannedAtomicToken::ExternalWord { .. } => {
return shapes.push(FlatShape::ExternalWord.spanned(self.span))
}
UnspannedAtomicToken::GlobPattern { .. } => {
return shapes.push(FlatShape::GlobPattern.spanned(self.span))
}
UnspannedAtomicToken::Word { .. } => {
return shapes.push(FlatShape::Word.spanned(self.span))
}
_ => return shapes.push(FlatShape::Error.spanned(self.span)),
}
}
}
impl PrettyDebugWithSource for AtomicToken<'_> {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
fn atom(value: DebugDocBuilder) -> DebugDocBuilder {
b::delimit("(", b::kind("atom") + b::space() + value.group(), ")").group()
}
fn atom_kind(kind: impl std::fmt::Display, value: DebugDocBuilder) -> DebugDocBuilder {
b::delimit(
"(",
(b::kind("atom") + b::delimit("[", b::kind(kind), "]")).group()
+ b::space()
+ value.group(),
")",
)
.group()
}
atom(match &self.unspanned {
UnspannedAtomicToken::Eof { .. } => b::description("eof"),
UnspannedAtomicToken::Error { .. } => b::error("error"),
UnspannedAtomicToken::Number { number } => number.pretty_debug(source),
UnspannedAtomicToken::Size { number, unit } => {
number.pretty_debug(source) + b::keyword(unit.span.slice(source))
}
UnspannedAtomicToken::String { body } => b::primitive(body.slice(source)),
UnspannedAtomicToken::ItVariable { .. } | UnspannedAtomicToken::Variable { .. } => {
b::keyword(self.span.slice(source))
}
UnspannedAtomicToken::ExternalCommand { .. } => b::primitive(self.span.slice(source)),
UnspannedAtomicToken::ExternalWord { text } => {
atom_kind("external word", b::primitive(text.slice(source)))
}
UnspannedAtomicToken::GlobPattern { pattern } => {
atom_kind("pattern", b::primitive(pattern.slice(source)))
}
UnspannedAtomicToken::Word { text } => {
atom_kind("word", b::primitive(text.slice(source)))
}
UnspannedAtomicToken::SquareDelimited { nodes, .. } => b::delimit(
"[",
b::intersperse_with_source(nodes.iter(), b::space(), source),
"]",
),
UnspannedAtomicToken::ShorthandFlag { name } => {
atom_kind("shorthand flag", b::key(name.slice(source)))
}
UnspannedAtomicToken::Dot { .. } => atom(b::kind("dot")),
UnspannedAtomicToken::Operator { text } => {
atom_kind("operator", b::keyword(text.slice(source)))
}
UnspannedAtomicToken::Whitespace { text } => atom_kind(
"whitespace",
b::description(format!("{:?}", text.slice(source))),
),
})
}
}
#[derive(Debug)]
pub enum WhitespaceHandling {
#[allow(unused)]
AllowWhitespace,
RejectWhitespace,
}
#[derive(Debug)]
pub struct ExpansionRule {
pub(crate) allow_external_command: bool,
pub(crate) allow_external_word: bool,
pub(crate) allow_operator: bool,
pub(crate) allow_eof: bool,
pub(crate) treat_size_as_word: bool,
pub(crate) separate_members: bool,
pub(crate) commit_errors: bool,
pub(crate) whitespace: WhitespaceHandling,
}
impl ExpansionRule {
pub fn new() -> ExpansionRule {
ExpansionRule {
allow_external_command: false,
allow_external_word: false,
allow_operator: false,
allow_eof: false,
treat_size_as_word: false,
separate_members: false,
commit_errors: false,
whitespace: WhitespaceHandling::RejectWhitespace,
}
}
/// The intent of permissive mode is to return an atomic token for every possible
/// input token. This is important for error-correcting parsing, such as the
/// syntax highlighter.
pub fn permissive() -> ExpansionRule {
ExpansionRule {
allow_external_command: true,
allow_external_word: true,
allow_operator: true,
allow_eof: true,
separate_members: false,
treat_size_as_word: false,
commit_errors: true,
whitespace: WhitespaceHandling::AllowWhitespace,
}
}
#[allow(unused)]
pub fn allow_external_command(mut self) -> ExpansionRule {
self.allow_external_command = true;
self
}
#[allow(unused)]
pub fn allow_operator(mut self) -> ExpansionRule {
self.allow_operator = true;
self
}
#[allow(unused)]
pub fn no_operator(mut self) -> ExpansionRule {
self.allow_operator = false;
self
}
#[allow(unused)]
pub fn no_external_command(mut self) -> ExpansionRule {
self.allow_external_command = false;
self
}
#[allow(unused)]
pub fn allow_external_word(mut self) -> ExpansionRule {
self.allow_external_word = true;
self
}
#[allow(unused)]
pub fn no_external_word(mut self) -> ExpansionRule {
self.allow_external_word = false;
self
}
#[allow(unused)]
pub fn treat_size_as_word(mut self) -> ExpansionRule {
self.treat_size_as_word = true;
self
}
#[allow(unused)]
pub fn separate_members(mut self) -> ExpansionRule {
self.separate_members = true;
self
}
#[allow(unused)]
pub fn no_separate_members(mut self) -> ExpansionRule {
self.separate_members = false;
self
}
#[allow(unused)]
pub fn commit_errors(mut self) -> ExpansionRule {
self.commit_errors = true;
self
}
#[allow(unused)]
pub fn allow_whitespace(mut self) -> ExpansionRule {
self.whitespace = WhitespaceHandling::AllowWhitespace;
self
}
#[allow(unused)]
pub fn reject_whitespace(mut self) -> ExpansionRule {
self.whitespace = WhitespaceHandling::RejectWhitespace;
self
}
}
pub fn expand_atom<'me, 'content>(
token_nodes: &'me mut TokensIterator<'content>,
expected: &'static str,
context: &ExpandContext,
rule: ExpansionRule,
) -> Result<AtomicToken<'content>, ParseError> {
token_nodes.with_expand_tracer(|_, tracer| tracer.start("atom"));
let result = expand_atom_inner(token_nodes, expected, context, rule);
token_nodes.with_expand_tracer(|_, tracer| match &result {
Ok(result) => {
tracer.add_result(result.clone());
tracer.success();
}
Err(err) => tracer.failed(err),
});
result
}
/// If the caller of expand_atom throws away the returned atomic token returned, it
/// must use a checkpoint to roll it back.
fn expand_atom_inner<'me, 'content>(
token_nodes: &'me mut TokensIterator<'content>,
expected: &'static str,
context: &ExpandContext,
rule: ExpansionRule,
) -> Result<AtomicToken<'content>, ParseError> {
if token_nodes.at_end() {
match rule.allow_eof {
true => {
return Ok(UnspannedAtomicToken::Eof {
span: Span::unknown(),
}
.into_atomic_token(Span::unknown()))
}
false => return Err(ParseError::unexpected_eof("anything", Span::unknown())),
}
}
// First, we'll need to handle the situation where more than one token corresponds
// to a single atomic token
// If treat_size_as_word, don't try to parse the head of the token stream
// as a size.
match rule.treat_size_as_word {
true => {}
false => match expand_syntax(&UnitShape, token_nodes, context) {
// If the head of the stream isn't a valid unit, we'll try to parse
// it again next as a word
Err(_) => {}
// But if it was a valid unit, we're done here
Ok(UnitSyntax {
unit: (number, unit),
span,
}) => return Ok(UnspannedAtomicToken::Size { number, unit }.into_atomic_token(span)),
},
}
match rule.separate_members {
false => {}
true => {
let mut next = token_nodes.peek_any();
match next.node {
Some(token) if token.is_word() => {
next.commit();
return Ok(UnspannedAtomicToken::Word { text: token.span() }
.into_atomic_token(token.span()));
}
Some(token) if token.is_int() => {
next.commit();
return Ok(UnspannedAtomicToken::Number {
number: RawNumber::Int(token.span()),
}
.into_atomic_token(token.span()));
}
_ => {}
}
}
}
// Try to parse the head of the stream as a bare path. A bare path includes
// words as well as `.`s, connected together without whitespace.
match expand_syntax(&BarePathShape, token_nodes, context) {
// If we didn't find a bare path
Err(_) => {}
Ok(span) => {
let next = token_nodes.peek_any();
match next.node {
Some(token) if token.is_pattern() => {
// if the very next token is a pattern, we're looking at a glob, not a
// word, and we should try to parse it as a glob next
}
_ => return Ok(UnspannedAtomicToken::Word { text: span }.into_atomic_token(span)),
}
}
}
// Try to parse the head of the stream as a pattern. A pattern includes
// words, words with `*` as well as `.`s, connected together without whitespace.
match expand_syntax(&BarePatternShape, token_nodes, context) {
// If we didn't find a bare path
Err(_) => {}
Ok(span) => {
return Ok(UnspannedAtomicToken::GlobPattern { pattern: span }.into_atomic_token(span))
}
}
// The next token corresponds to at most one atomic token
// We need to `peek` because `parse_single_node` doesn't cover all of the
// cases that `expand_atom` covers. We should probably collapse the two
// if possible.
let peeked = token_nodes.peek_any().not_eof(expected)?;
match peeked.node {
TokenNode::Token(_) => {
// handle this next
}
TokenNode::Error(error) => {
peeked.commit();
return Ok(UnspannedAtomicToken::Error {
error: error.clone(),
}
.into_atomic_token(error.span));
}
// [ ... ]
TokenNode::Delimited(Spanned {
item:
DelimitedNode {
delimiter: Delimiter::Square,
spans,
children,
},
span,
}) => {
peeked.commit();
let span = *span;
return Ok(UnspannedAtomicToken::SquareDelimited {
nodes: children,
spans: *spans,
}
.into_atomic_token(span));
}
TokenNode::Flag(Flag {
kind: FlagKind::Shorthand,
name,
span,
}) => {
peeked.commit();
return Ok(UnspannedAtomicToken::ShorthandFlag { name: *name }.into_atomic_token(*span));
}
TokenNode::Flag(Flag {
kind: FlagKind::Longhand,
name,
span,
}) => {
peeked.commit();
return Ok(UnspannedAtomicToken::ShorthandFlag { name: *name }.into_atomic_token(*span));
}
// If we see whitespace, process the whitespace according to the whitespace
// handling rules
TokenNode::Whitespace(span) => match rule.whitespace {
// if whitespace is allowed, return a whitespace token
WhitespaceHandling::AllowWhitespace => {
peeked.commit();
return Ok(
UnspannedAtomicToken::Whitespace { text: *span }.into_atomic_token(*span)
);
}
// if whitespace is disallowed, return an error
WhitespaceHandling::RejectWhitespace => {
return Err(ParseError::mismatch(expected, "whitespace".spanned(*span)))
}
},
other => {
let span = peeked.node.span();
peeked.commit();
return Ok(UnspannedAtomicToken::Error {
error: ShellError::type_error("token", other.type_name().spanned(span))
.spanned(span),
}
.into_atomic_token(span));
}
}
parse_single_node(token_nodes, expected, |token, token_span, err| {
Ok(match token {
// First, the error cases. Each error case corresponds to a expansion rule
// flag that can be used to allow the case
// rule.allow_operator
UnspannedToken::Operator(_) if !rule.allow_operator => return Err(err.error()),
// rule.allow_external_command
UnspannedToken::ExternalCommand(_) if !rule.allow_external_command => {
return Err(ParseError::mismatch(
expected,
token.type_name().spanned(token_span),
))
}
// rule.allow_external_word
UnspannedToken::ExternalWord if !rule.allow_external_word => {
return Err(ParseError::mismatch(
expected,
"external word".spanned(token_span),
))
}
UnspannedToken::Number(number) => {
UnspannedAtomicToken::Number { number }.into_atomic_token(token_span)
}
UnspannedToken::Operator(_) => {
UnspannedAtomicToken::Operator { text: token_span }.into_atomic_token(token_span)
}
UnspannedToken::String(body) => {
UnspannedAtomicToken::String { body }.into_atomic_token(token_span)
}
UnspannedToken::Variable(name) if name.slice(context.source) == "it" => {
UnspannedAtomicToken::ItVariable { name }.into_atomic_token(token_span)
}
UnspannedToken::Variable(name) => {
UnspannedAtomicToken::Variable { name }.into_atomic_token(token_span)
}
UnspannedToken::ExternalCommand(command) => {
UnspannedAtomicToken::ExternalCommand { command }.into_atomic_token(token_span)
}
UnspannedToken::ExternalWord => UnspannedAtomicToken::ExternalWord { text: token_span }
.into_atomic_token(token_span),
UnspannedToken::GlobPattern => UnspannedAtomicToken::GlobPattern {
pattern: token_span,
}
.into_atomic_token(token_span),
UnspannedToken::Bare => {
UnspannedAtomicToken::Word { text: token_span }.into_atomic_token(token_span)
}
})
})
}

View File

@ -0,0 +1,90 @@
use crate::hir::syntax_shape::{
color_syntax, expand_syntax, ColorSyntax, ExpandContext, ExpressionListShape, TokenNode,
};
use crate::{hir, hir::TokensIterator, Delimiter, FlatShape};
use nu_errors::ParseError;
#[cfg(not(coloring_in_tokens))]
use nu_source::Spanned;
use nu_source::{Span, SpannedItem, Tag};
pub fn expand_delimited_square(
children: &Vec<TokenNode>,
span: Span,
context: &ExpandContext,
) -> Result<hir::Expression, ParseError> {
let mut tokens = TokensIterator::new(&children, span, context.source.clone(), false);
let list = expand_syntax(&ExpressionListShape, &mut tokens, context);
Ok(hir::Expression::list(
list?.exprs.item,
Tag { span, anchor: None },
))
}
#[cfg(not(coloring_in_tokens))]
pub fn color_delimited_square(
(open, close): (Span, Span),
children: &Vec<TokenNode>,
span: Span,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) {
shapes.push(FlatShape::OpenDelimiter(Delimiter::Square).spanned(open));
let mut tokens = TokensIterator::new(&children, span, context.source.clone(), false);
let _list = color_syntax(&ExpressionListShape, &mut tokens, context, shapes);
shapes.push(FlatShape::CloseDelimiter(Delimiter::Square).spanned(close));
}
#[cfg(coloring_in_tokens)]
pub fn color_delimited_square(
(open, close): (Span, Span),
token_nodes: &mut TokensIterator,
_span: Span,
context: &ExpandContext,
) {
token_nodes.color_shape(FlatShape::OpenDelimiter(Delimiter::Square).spanned(open));
let _list = color_syntax(&ExpressionListShape, token_nodes, context);
token_nodes.color_shape(FlatShape::CloseDelimiter(Delimiter::Square).spanned(close));
}
#[derive(Debug, Copy, Clone)]
pub struct DelimitedShape;
#[cfg(not(coloring_in_tokens))]
impl ColorSyntax for DelimitedShape {
type Info = ();
type Input = (Delimiter, Span, Span);
fn color_syntax<'a, 'b>(
&self,
(delimiter, open, close): &(Delimiter, Span, Span),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> Self::Info {
shapes.push(FlatShape::OpenDelimiter(*delimiter).spanned(*open));
color_syntax(&ExpressionListShape, token_nodes, context, shapes);
shapes.push(FlatShape::CloseDelimiter(*delimiter).spanned(*close));
}
}
#[cfg(coloring_in_tokens)]
impl ColorSyntax for DelimitedShape {
type Info = ();
type Input = (Delimiter, Span, Span);
fn name(&self) -> &'static str {
"DelimitedShape"
}
fn color_syntax<'a, 'b>(
&self,
(delimiter, open, close): &(Delimiter, Span, Span),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Self::Info {
token_nodes.color_shape(FlatShape::OpenDelimiter(*delimiter).spanned(*open));
color_syntax(&ExpressionListShape, token_nodes, context);
token_nodes.color_shape(FlatShape::CloseDelimiter(*delimiter).spanned(*close));
}
}

View File

@ -0,0 +1,121 @@
use crate::hir::syntax_shape::expression::atom::{
expand_atom, ExpansionRule, UnspannedAtomicToken,
};
use crate::hir::syntax_shape::{
expression::expand_file_path, ExpandContext, ExpandExpression, FallibleColorSyntax, FlatShape,
};
use crate::{hir, hir::TokensIterator};
use nu_errors::{ParseError, ShellError};
use nu_source::SpannedItem;
#[derive(Debug, Copy, Clone)]
pub struct FilePathShape;
#[cfg(not(coloring_in_tokens))]
impl FallibleColorSyntax for FilePathShape {
type Info = ();
type Input = ();
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<nu_source::Spanned<FlatShape>>,
) -> Result<(), ShellError> {
let atom = expand_atom(
token_nodes,
"file path",
context,
ExpansionRule::permissive(),
);
let atom = match atom {
Err(_) => return Ok(()),
Ok(atom) => atom,
};
match &atom.unspanned {
UnspannedAtomicToken::Word { .. }
| UnspannedAtomicToken::String { .. }
| UnspannedAtomicToken::Number { .. }
| UnspannedAtomicToken::Size { .. } => {
shapes.push(FlatShape::Path.spanned(atom.span));
}
_ => atom.color_tokens(shapes),
}
Ok(())
}
}
#[cfg(coloring_in_tokens)]
impl FallibleColorSyntax for FilePathShape {
type Info = ();
type Input = ();
fn name(&self) -> &'static str {
"FilePathShape"
}
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<(), ShellError> {
let atom = expand_atom(
token_nodes,
"file path",
context,
ExpansionRule::permissive(),
);
let atom = match atom {
Err(_) => return Ok(()),
Ok(atom) => atom,
};
match atom.unspanned {
UnspannedAtomicToken::Word { .. }
| UnspannedAtomicToken::String { .. }
| UnspannedAtomicToken::Number { .. }
| UnspannedAtomicToken::Size { .. } => {
token_nodes.color_shape(FlatShape::Path.spanned(atom.span));
}
_ => token_nodes.mutate_shapes(|shapes| atom.color_tokens(shapes)),
}
Ok(())
}
}
impl ExpandExpression for FilePathShape {
fn name(&self) -> &'static str {
"file path"
}
fn expand_expr<'a, 'b>(
&self,
token_nodes: &mut TokensIterator<'_>,
context: &ExpandContext,
) -> Result<hir::Expression, ParseError> {
let atom = expand_atom(token_nodes, "file path", context, ExpansionRule::new())?;
match atom.unspanned {
UnspannedAtomicToken::Word { text: body } | UnspannedAtomicToken::String { body } => {
let path = expand_file_path(body.slice(context.source), context);
return Ok(hir::Expression::file_path(path, atom.span));
}
UnspannedAtomicToken::Number { .. } | UnspannedAtomicToken::Size { .. } => {
let path = atom.span.slice(context.source);
return Ok(hir::Expression::file_path(path, atom.span));
}
_ => return atom.into_hir(context, "file path"),
}
}
}

View File

@ -0,0 +1,344 @@
#[cfg(not(coloring_in_tokens))]
use crate::hir::syntax_shape::FlatShape;
use crate::{
hir,
hir::syntax_shape::{
color_fallible_syntax, color_syntax, expand_atom, expand_expr, maybe_spaced, spaced,
AnyExpressionShape, ColorSyntax, ExpandContext, ExpandSyntax, ExpansionRule,
MaybeSpaceShape, SpaceShape,
},
hir::TokensIterator,
};
use nu_errors::ParseError;
use nu_source::{b, DebugDocBuilder, HasSpan, PrettyDebugWithSource, Span, Spanned, SpannedItem};
#[derive(Debug, Clone)]
pub struct ExpressionListSyntax {
pub exprs: Spanned<Vec<hir::Expression>>,
}
impl HasSpan for ExpressionListSyntax {
fn span(&self) -> Span {
self.exprs.span
}
}
impl PrettyDebugWithSource for ExpressionListSyntax {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
b::intersperse(
self.exprs.iter().map(|e| e.pretty_debug(source)),
b::space(),
)
}
}
#[derive(Debug, Copy, Clone)]
pub struct ExpressionListShape;
impl ExpandSyntax for ExpressionListShape {
type Output = ExpressionListSyntax;
fn name(&self) -> &'static str {
"expression list"
}
fn expand_syntax<'a, 'b>(
&self,
token_nodes: &mut TokensIterator<'_>,
context: &ExpandContext,
) -> Result<ExpressionListSyntax, ParseError> {
let mut exprs = vec![];
let start = token_nodes.span_at_cursor();
if token_nodes.at_end_possible_ws() {
return Ok(ExpressionListSyntax {
exprs: exprs.spanned(start),
});
}
let expr = expand_expr(&maybe_spaced(AnyExpressionShape), token_nodes, context)?;
exprs.push(expr);
loop {
if token_nodes.at_end_possible_ws() {
let end = token_nodes.span_at_cursor();
return Ok(ExpressionListSyntax {
exprs: exprs.spanned(start.until(end)),
});
}
let expr = expand_expr(&spaced(AnyExpressionShape), token_nodes, context)?;
exprs.push(expr);
}
}
}
#[cfg(not(coloring_in_tokens))]
impl ColorSyntax for ExpressionListShape {
type Info = ();
type Input = ();
/// The intent of this method is to fully color an expression list shape infallibly.
/// This means that if we can't expand a token into an expression, we fall back to
/// a simpler coloring strategy.
///
/// This would apply to something like `where x >`, which includes an incomplete
/// binary operator. Since we will fail to process it as a binary operator, we'll
/// fall back to a simpler coloring and move on.
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) {
// We encountered a parsing error and will continue with simpler coloring ("backoff
// coloring mode")
let mut backoff = false;
// Consume any leading whitespace
color_syntax(&MaybeSpaceShape, token_nodes, context, shapes);
loop {
// If we reached the very end of the token stream, we're done
if token_nodes.at_end() {
return;
}
if backoff {
let len = shapes.len();
// If we previously encountered a parsing error, use backoff coloring mode
color_syntax(&SimplestExpression, token_nodes, context, shapes);
if len == shapes.len() && !token_nodes.at_end() {
// This should never happen, but if it does, a panic is better than an infinite loop
panic!("Unexpected tokens left that couldn't be colored even with SimplestExpression")
}
} else {
// Try to color the head of the stream as an expression
match color_fallible_syntax(&AnyExpressionShape, token_nodes, context, shapes) {
// If no expression was found, switch to backoff coloring mode
Err(_) => {
backoff = true;
continue;
}
Ok(_) => {}
}
// If an expression was found, consume a space
match color_fallible_syntax(&SpaceShape, token_nodes, context, shapes) {
Err(_) => {
// If no space was found, we're either at the end or there's an error.
// Either way, switch to backoff coloring mode. If we're at the end
// it won't have any consequences.
backoff = true;
}
Ok(_) => {
// Otherwise, move on to the next expression
}
}
}
}
}
}
#[cfg(coloring_in_tokens)]
impl ColorSyntax for ExpressionListShape {
type Info = ();
type Input = ();
fn name(&self) -> &'static str {
"ExpressionListShape"
}
/// The intent of this method is to fully color an expression list shape infallibly.
/// This means that if we can't expand a token into an expression, we fall back to
/// a simpler coloring strategy.
///
/// This would apply to something like `where x >`, which includes an incomplete
/// binary operator. Since we will fail to process it as a binary operator, we'll
/// fall back to a simpler coloring and move on.
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) {
// We encountered a parsing error and will continue with simpler coloring ("backoff
// coloring mode")
let mut backoff = false;
// Consume any leading whitespace
color_syntax(&MaybeSpaceShape, token_nodes, context);
loop {
// If we reached the very end of the token stream, we're done
if token_nodes.at_end() {
return;
}
if backoff {
let len = token_nodes.state().shapes().len();
// If we previously encountered a parsing error, use backoff coloring mode
color_syntax(&SimplestExpression, token_nodes, context);
if len == token_nodes.state().shapes().len() && !token_nodes.at_end() {
// This should never happen, but if it does, a panic is better than an infinite loop
panic!("Unexpected tokens left that couldn't be colored even with SimplestExpression")
}
} else {
// Try to color the head of the stream as an expression
match color_fallible_syntax(&AnyExpressionShape, token_nodes, context) {
// If no expression was found, switch to backoff coloring mode
Err(_) => {
backoff = true;
continue;
}
Ok(_) => {}
}
// If an expression was found, consume a space
match color_fallible_syntax(&SpaceShape, token_nodes, context) {
Err(_) => {
// If no space was found, we're either at the end or there's an error.
// Either way, switch to backoff coloring mode. If we're at the end
// it won't have any consequences.
backoff = true;
}
Ok(_) => {
// Otherwise, move on to the next expression
}
}
}
}
}
}
/// BackoffColoringMode consumes all of the remaining tokens in an infallible way
#[derive(Debug, Copy, Clone)]
pub struct BackoffColoringMode;
#[cfg(not(coloring_in_tokens))]
impl ColorSyntax for BackoffColoringMode {
type Info = ();
type Input = ();
fn color_syntax<'a, 'b>(
&self,
_input: &Self::Input,
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> Self::Info {
loop {
if token_nodes.at_end() {
break;
}
let len = shapes.len();
color_syntax(&SimplestExpression, token_nodes, context, shapes);
if len == shapes.len() && !token_nodes.at_end() {
// This shouldn't happen, but if it does, a panic is better than an infinite loop
panic!("SimplestExpression failed to consume any tokens, but it's not at the end. This is unexpected\n== token nodes==\n{:#?}\n\n== shapes ==\n{:#?}", token_nodes, shapes);
}
}
}
}
#[cfg(coloring_in_tokens)]
impl ColorSyntax for BackoffColoringMode {
type Info = ();
type Input = ();
fn name(&self) -> &'static str {
"BackoffColoringMode"
}
fn color_syntax<'a, 'b>(
&self,
_input: &Self::Input,
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Self::Info {
loop {
if token_nodes.at_end() {
break;
}
let len = token_nodes.state().shapes().len();
color_syntax(&SimplestExpression, token_nodes, context);
if len == token_nodes.state().shapes().len() && !token_nodes.at_end() {
// This shouldn't happen, but if it does, a panic is better than an infinite loop
panic!("SimplestExpression failed to consume any tokens, but it's not at the end. This is unexpected\n== token nodes==\n{:#?}\n\n== shapes ==\n{:#?}", token_nodes, token_nodes.state().shapes());
}
}
}
}
/// The point of `SimplestExpression` is to serve as an infallible base case for coloring.
/// As a last ditch effort, if we can't find any way to parse the head of the stream as an
/// expression, fall back to simple coloring.
#[derive(Debug, Copy, Clone)]
pub struct SimplestExpression;
#[cfg(not(coloring_in_tokens))]
impl ColorSyntax for SimplestExpression {
type Info = ();
type Input = ();
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) {
let atom = expand_atom(
token_nodes,
"any token",
context,
ExpansionRule::permissive(),
);
match atom {
Err(_) => {}
Ok(atom) => atom.color_tokens(shapes),
}
}
}
#[cfg(coloring_in_tokens)]
impl ColorSyntax for SimplestExpression {
type Info = ();
type Input = ();
fn name(&self) -> &'static str {
"SimplestExpression"
}
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) {
let atom = expand_atom(
token_nodes,
"any token",
context,
ExpansionRule::permissive(),
);
match atom {
Err(_) => {}
Ok(atom) => token_nodes.mutate_shapes(|shapes| atom.color_tokens(shapes)),
}
}
}

View File

@ -0,0 +1,230 @@
use crate::hir::syntax_shape::{
expand_atom, parse_single_node, ExpandContext, ExpandExpression, ExpansionRule,
FallibleColorSyntax, FlatShape, TestSyntax,
};
use crate::hir::tokens_iterator::Peeked;
use crate::parse::tokens::UnspannedToken;
use crate::{
hir,
hir::{RawNumber, TokensIterator},
};
use nu_errors::{ParseError, ShellError};
use nu_source::{Spanned, SpannedItem};
#[derive(Debug, Copy, Clone)]
pub struct NumberShape;
impl ExpandExpression for NumberShape {
fn name(&self) -> &'static str {
"number"
}
fn expand_expr<'a, 'b>(
&self,
token_nodes: &mut TokensIterator<'_>,
context: &ExpandContext,
) -> Result<hir::Expression, ParseError> {
parse_single_node(token_nodes, "Number", |token, token_span, err| {
Ok(match token {
UnspannedToken::GlobPattern | UnspannedToken::Operator(..) => {
return Err(err.error())
}
UnspannedToken::Variable(tag) if tag.slice(context.source) == "it" => {
hir::Expression::it_variable(tag, token_span)
}
UnspannedToken::ExternalCommand(tag) => {
hir::Expression::external_command(tag, token_span)
}
UnspannedToken::ExternalWord => {
return Err(ParseError::mismatch(
"number",
"syntax error".spanned(token_span),
))
}
UnspannedToken::Variable(tag) => hir::Expression::variable(tag, token_span),
UnspannedToken::Number(number) => {
hir::Expression::number(number.to_number(context.source), token_span)
}
UnspannedToken::Bare => hir::Expression::bare(token_span),
UnspannedToken::String(tag) => hir::Expression::string(tag, token_span),
})
})
}
}
#[cfg(not(coloring_in_tokens))]
impl FallibleColorSyntax for NumberShape {
type Info = ();
type Input = ();
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> Result<(), ShellError> {
let atom = token_nodes.spanned(|token_nodes| {
expand_atom(token_nodes, "number", context, ExpansionRule::permissive())
});
let atom = match atom {
Spanned { item: Err(_), span } => {
shapes.push(FlatShape::Error.spanned(span));
return Ok(());
}
Spanned { item: Ok(atom), .. } => atom,
};
atom.color_tokens(shapes);
Ok(())
}
}
#[cfg(coloring_in_tokens)]
impl FallibleColorSyntax for NumberShape {
type Info = ();
type Input = ();
fn name(&self) -> &'static str {
"NumberShape"
}
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<(), ShellError> {
let atom = token_nodes.spanned(|token_nodes| {
expand_atom(token_nodes, "number", context, ExpansionRule::permissive())
});
let atom = match atom {
Spanned { item: Err(_), span } => {
token_nodes.color_shape(FlatShape::Error.spanned(span));
return Ok(());
}
Spanned { item: Ok(atom), .. } => atom,
};
token_nodes.mutate_shapes(|shapes| atom.color_tokens(shapes));
Ok(())
}
}
#[derive(Debug, Copy, Clone)]
pub struct IntShape;
impl ExpandExpression for IntShape {
fn name(&self) -> &'static str {
"integer"
}
fn expand_expr<'a, 'b>(
&self,
token_nodes: &mut TokensIterator<'_>,
context: &ExpandContext,
) -> Result<hir::Expression, ParseError> {
parse_single_node(token_nodes, "Integer", |token, token_span, err| {
Ok(match token {
UnspannedToken::GlobPattern
| UnspannedToken::Operator(..)
| UnspannedToken::ExternalWord => return Err(err.error()),
UnspannedToken::Variable(span) if span.slice(context.source) == "it" => {
hir::Expression::it_variable(span, token_span)
}
UnspannedToken::ExternalCommand(span) => {
hir::Expression::external_command(span, token_span)
}
UnspannedToken::Variable(span) => hir::Expression::variable(span, token_span),
UnspannedToken::Number(number @ RawNumber::Int(_)) => {
hir::Expression::number(number.to_number(context.source), token_span)
}
UnspannedToken::Number(_) => return Err(err.error()),
UnspannedToken::Bare => hir::Expression::bare(token_span),
UnspannedToken::String(span) => hir::Expression::string(span, token_span),
})
})
}
}
#[cfg(not(coloring_in_tokens))]
impl FallibleColorSyntax for IntShape {
type Info = ();
type Input = ();
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> Result<(), ShellError> {
let atom = token_nodes.spanned(|token_nodes| {
expand_atom(token_nodes, "integer", context, ExpansionRule::permissive())
});
let atom = match atom {
Spanned { item: Err(_), span } => {
shapes.push(FlatShape::Error.spanned(span));
return Ok(());
}
Spanned { item: Ok(atom), .. } => atom,
};
atom.color_tokens(shapes);
Ok(())
}
}
#[cfg(coloring_in_tokens)]
impl FallibleColorSyntax for IntShape {
type Info = ();
type Input = ();
fn name(&self) -> &'static str {
"IntShape"
}
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<(), ShellError> {
let atom = token_nodes.spanned(|token_nodes| {
expand_atom(token_nodes, "integer", context, ExpansionRule::permissive())
});
let atom = match atom {
Spanned { item: Err(_), span } => {
token_nodes.color_shape(FlatShape::Error.spanned(span));
return Ok(());
}
Spanned { item: Ok(atom), .. } => atom,
};
token_nodes.mutate_shapes(|shapes| atom.color_tokens(shapes));
Ok(())
}
}
impl TestSyntax for NumberShape {
fn test<'a, 'b>(
&self,
token_nodes: &'b mut TokensIterator<'a>,
_context: &ExpandContext,
) -> Option<Peeked<'a, 'b>> {
let peeked = token_nodes.peek_any();
match peeked.node {
Some(token) if token.is_number() => Some(peeked),
_ => None,
}
}
}

View File

@ -0,0 +1,133 @@
use crate::hir::syntax_shape::{
expand_atom, expand_bare, expression::expand_file_path, ExpandContext, ExpandExpression,
ExpandSyntax, ExpansionRule, FallibleColorSyntax, FlatShape, UnspannedAtomicToken,
};
use crate::parse::tokens::{Token, UnspannedToken};
use crate::{hir, hir::TokensIterator, Operator, TokenNode};
use nu_errors::{ParseError, ShellError};
#[cfg(coloring_in_tokens)]
use nu_protocol::ShellTypeName;
#[cfg(not(coloring_in_tokens))]
use nu_source::Spanned;
use nu_source::{Span, SpannedItem};
#[derive(Debug, Copy, Clone)]
pub struct PatternShape;
#[cfg(not(coloring_in_tokens))]
impl FallibleColorSyntax for PatternShape {
type Info = ();
type Input = ();
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> Result<(), ShellError> {
token_nodes.atomic(|token_nodes| {
let atom = expand_atom(token_nodes, "pattern", context, ExpansionRule::permissive())?;
match &atom.unspanned {
UnspannedAtomicToken::GlobPattern { .. } | UnspannedAtomicToken::Word { .. } => {
shapes.push(FlatShape::GlobPattern.spanned(atom.span));
Ok(())
}
_ => Err(ShellError::type_error("pattern", atom.spanned_type_name())),
}
})
}
}
#[cfg(coloring_in_tokens)]
impl FallibleColorSyntax for PatternShape {
type Info = ();
type Input = ();
fn name(&self) -> &'static str {
"PatternShape"
}
fn color_syntax<'a, 'b>(
&self,
_input: &(),
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<(), ShellError> {
token_nodes.atomic(|token_nodes| {
let atom = expand_atom(token_nodes, "pattern", context, ExpansionRule::permissive())?;
match &atom.unspanned {
UnspannedAtomicToken::GlobPattern { .. } | UnspannedAtomicToken::Word { .. } => {
token_nodes.color_shape(FlatShape::GlobPattern.spanned(atom.span));
Ok(())
}
other => Err(ShellError::type_error(
"pattern",
other.type_name().spanned(atom.span),
)),
}
})
}
}
impl ExpandExpression for PatternShape {
fn name(&self) -> &'static str {
"glob pattern"
}
fn expand_expr<'a, 'b>(
&self,
token_nodes: &mut TokensIterator<'_>,
context: &ExpandContext,
) -> Result<hir::Expression, ParseError> {
let atom = expand_atom(token_nodes, "pattern", context, ExpansionRule::new())?;
match atom.unspanned {
UnspannedAtomicToken::Word { text: body }
| UnspannedAtomicToken::String { body }
| UnspannedAtomicToken::GlobPattern { pattern: body } => {
let path = expand_file_path(body.slice(context.source), context);
return Ok(hir::Expression::pattern(path.to_string_lossy(), atom.span));
}
_ => return atom.into_hir(context, "pattern"),
}
}
}
#[derive(Debug, Copy, Clone)]
pub struct BarePatternShape;
impl ExpandSyntax for BarePatternShape {
type Output = Span;
fn name(&self) -> &'static str {
"bare pattern"
}
fn expand_syntax<'a, 'b>(
&self,
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<Span, ParseError> {
expand_bare(token_nodes, context, |token| match token {
TokenNode::Token(Token {
unspanned: UnspannedToken::Bare,
..
})
| TokenNode::Token(Token {
unspanned: UnspannedToken::Operator(Operator::Dot),
..
})
| TokenNode::Token(Token {
unspanned: UnspannedToken::GlobPattern,
..
}) => true,
_ => false,
})
}
}

View File

@ -0,0 +1,123 @@
use crate::hir::syntax_shape::{
expand_atom, expand_variable, parse_single_node, AtomicToken, ExpandContext, ExpandExpression,
ExpansionRule, FallibleColorSyntax, FlatShape, TestSyntax, UnspannedAtomicToken,
};
use crate::hir::tokens_iterator::Peeked;
use crate::parse::tokens::UnspannedToken;
use crate::{hir, hir::TokensIterator};
use nu_errors::{ParseError, ShellError};
#[cfg(not(coloring_in_tokens))]
use nu_source::Spanned;
use nu_source::SpannedItem;
#[derive(Debug, Copy, Clone)]
pub struct StringShape;
#[cfg(not(coloring_in_tokens))]
impl FallibleColorSyntax for StringShape {
type Info = ();
type Input = FlatShape;
fn color_syntax<'a, 'b>(
&self,
input: &FlatShape,
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> Result<(), ShellError> {
let atom = expand_atom(token_nodes, "string", context, ExpansionRule::permissive());
let atom = match atom {
Err(_) => return Ok(()),
Ok(atom) => atom,
};
match atom {
AtomicToken {
unspanned: UnspannedAtomicToken::String { .. },
span,
} => shapes.push((*input).spanned(span)),
other => other.color_tokens(shapes),
}
Ok(())
}
}
#[cfg(coloring_in_tokens)]
impl FallibleColorSyntax for StringShape {
type Info = ();
type Input = FlatShape;
fn name(&self) -> &'static str {
"StringShape"
}
fn color_syntax<'a, 'b>(
&self,
input: &FlatShape,
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<(), ShellError> {
let atom = expand_atom(token_nodes, "string", context, ExpansionRule::permissive());
let atom = match atom {
Err(_) => return Ok(()),
Ok(atom) => atom,
};
match atom {
AtomicToken {
unspanned: UnspannedAtomicToken::String { .. },
span,
} => token_nodes.color_shape((*input).spanned(span)),
atom => token_nodes.mutate_shapes(|shapes| atom.color_tokens(shapes)),
}
Ok(())
}
}
impl ExpandExpression for StringShape {
fn name(&self) -> &'static str {
"string"
}
fn expand_expr<'a, 'b>(
&self,
token_nodes: &mut TokensIterator<'_>,
context: &ExpandContext,
) -> Result<hir::Expression, ParseError> {
parse_single_node(token_nodes, "String", |token, token_span, err| {
Ok(match token {
UnspannedToken::GlobPattern
| UnspannedToken::Operator(..)
| UnspannedToken::ExternalWord => return Err(err.error()),
UnspannedToken::Variable(span) => {
expand_variable(span, token_span, &context.source)
}
UnspannedToken::ExternalCommand(span) => {
hir::Expression::external_command(span, token_span)
}
UnspannedToken::Number(_) => hir::Expression::bare(token_span),
UnspannedToken::Bare => hir::Expression::bare(token_span),
UnspannedToken::String(span) => hir::Expression::string(span, token_span),
})
})
}
}
impl TestSyntax for StringShape {
fn test<'a, 'b>(
&self,
token_nodes: &'b mut TokensIterator<'a>,
_context: &ExpandContext,
) -> Option<Peeked<'a, 'b>> {
let peeked = token_nodes.peek_any();
match peeked.node {
Some(token) if token.is_string() => Some(peeked),
_ => None,
}
}
}

View File

@ -0,0 +1,124 @@
use crate::hir::syntax_shape::{ExpandContext, ExpandSyntax};
use crate::parse::tokens::RawNumber;
use crate::parse::tokens::Token;
use crate::parse::tokens::UnspannedToken;
use crate::parse::unit::Unit;
use crate::{hir::TokensIterator, TokenNode};
use nom::branch::alt;
use nom::bytes::complete::tag;
use nom::character::complete::digit1;
use nom::combinator::{all_consuming, opt, value};
use nom::IResult;
use nu_errors::ParseError;
use nu_source::{b, DebugDocBuilder, HasSpan, PrettyDebugWithSource, Span, Spanned, SpannedItem};
#[derive(Debug, Clone)]
pub struct UnitSyntax {
pub unit: (RawNumber, Spanned<Unit>),
pub span: Span,
}
impl PrettyDebugWithSource for UnitSyntax {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
b::typed(
"unit",
self.unit.0.pretty_debug(source) + b::space() + self.unit.1.pretty_debug(source),
)
}
}
impl HasSpan for UnitSyntax {
fn span(&self) -> Span {
self.span
}
}
#[derive(Debug, Copy, Clone)]
pub struct UnitShape;
impl ExpandSyntax for UnitShape {
type Output = UnitSyntax;
fn name(&self) -> &'static str {
"unit"
}
fn expand_syntax<'a, 'b>(
&self,
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Result<UnitSyntax, ParseError> {
let peeked = token_nodes.peek_any().not_eof("unit")?;
let span = match peeked.node {
TokenNode::Token(Token {
unspanned: UnspannedToken::Bare,
span,
}) => *span,
_ => return Err(peeked.type_error("unit")),
};
let unit = unit_size(span.slice(context.source), span);
let (_, (number, unit)) = match unit {
Err(_) => return Err(ParseError::mismatch("unit", "word".spanned(span))),
Ok((number, unit)) => (number, unit),
};
peeked.commit();
Ok(UnitSyntax {
unit: (number, unit),
span,
})
}
}
fn unit_size(input: &str, bare_span: Span) -> IResult<&str, (RawNumber, Spanned<Unit>)> {
let (input, digits) = digit1(input)?;
let (input, dot) = opt(tag("."))(input)?;
let (input, number) = match dot {
Some(dot) => {
let (input, rest) = digit1(input)?;
(
input,
RawNumber::decimal(Span::new(
bare_span.start(),
bare_span.start() + digits.len() + dot.len() + rest.len(),
)),
)
}
None => (
input,
RawNumber::int(Span::new(
bare_span.start(),
bare_span.start() + digits.len(),
)),
),
};
let (input, unit) = all_consuming(alt((
value(Unit::Byte, alt((tag("B"), tag("b")))),
value(Unit::Kilobyte, alt((tag("KB"), tag("kb"), tag("Kb")))),
value(Unit::Megabyte, alt((tag("MB"), tag("mb"), tag("Mb")))),
value(Unit::Gigabyte, alt((tag("GB"), tag("gb"), tag("Gb")))),
value(Unit::Terabyte, alt((tag("TB"), tag("tb"), tag("Tb")))),
value(Unit::Petabyte, alt((tag("PB"), tag("pb"), tag("Pb")))),
value(Unit::Second, tag("s")),
value(Unit::Minute, tag("m")),
value(Unit::Hour, tag("h")),
value(Unit::Day, tag("d")),
value(Unit::Week, tag("w")),
value(Unit::Month, tag("M")),
value(Unit::Year, tag("y")),
)))(input)?;
let start_span = number.span().end();
Ok((
input,
(number, unit.spanned(Span::new(start_span, bare_span.end()))),
))
}

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,98 @@
use crate::parse::flag::{Flag, FlagKind};
use crate::parse::operator::Operator;
use crate::parse::token_tree::{Delimiter, TokenNode};
use crate::parse::tokens::{RawNumber, UnspannedToken};
use nu_source::{HasSpan, Span, Spanned, SpannedItem, Text};
#[derive(Debug, Copy, Clone)]
pub enum FlatShape {
OpenDelimiter(Delimiter),
CloseDelimiter(Delimiter),
ItVariable,
Variable,
Operator,
Dot,
InternalCommand,
ExternalCommand,
ExternalWord,
BareMember,
StringMember,
String,
Path,
Word,
Pipe,
GlobPattern,
Flag,
ShorthandFlag,
Int,
Decimal,
Whitespace,
Error,
Size { number: Span, unit: Span },
}
impl FlatShape {
pub fn from(token: &TokenNode, source: &Text, shapes: &mut Vec<Spanned<FlatShape>>) -> () {
match token {
TokenNode::Token(token) => match token.unspanned {
UnspannedToken::Number(RawNumber::Int(_)) => {
shapes.push(FlatShape::Int.spanned(token.span))
}
UnspannedToken::Number(RawNumber::Decimal(_)) => {
shapes.push(FlatShape::Decimal.spanned(token.span))
}
UnspannedToken::Operator(Operator::Dot) => {
shapes.push(FlatShape::Dot.spanned(token.span))
}
UnspannedToken::Operator(_) => shapes.push(FlatShape::Operator.spanned(token.span)),
UnspannedToken::String(_) => shapes.push(FlatShape::String.spanned(token.span)),
UnspannedToken::Variable(v) if v.slice(source) == "it" => {
shapes.push(FlatShape::ItVariable.spanned(token.span))
}
UnspannedToken::Variable(_) => shapes.push(FlatShape::Variable.spanned(token.span)),
UnspannedToken::ExternalCommand(_) => {
shapes.push(FlatShape::ExternalCommand.spanned(token.span))
}
UnspannedToken::ExternalWord => {
shapes.push(FlatShape::ExternalWord.spanned(token.span))
}
UnspannedToken::GlobPattern => {
shapes.push(FlatShape::GlobPattern.spanned(token.span))
}
UnspannedToken::Bare => shapes.push(FlatShape::Word.spanned(token.span)),
},
TokenNode::Call(_) => unimplemented!(),
TokenNode::Nodes(nodes) => {
for node in &nodes.item {
FlatShape::from(node, source, shapes);
}
}
TokenNode::Delimited(v) => {
shapes.push(FlatShape::OpenDelimiter(v.item.delimiter).spanned(v.item.spans.0));
for token in &v.item.children {
FlatShape::from(token, source, shapes);
}
shapes.push(FlatShape::CloseDelimiter(v.item.delimiter).spanned(v.item.spans.1));
}
TokenNode::Pipeline(pipeline) => {
for part in &pipeline.parts {
if let Some(_) = part.pipe {
shapes.push(FlatShape::Pipe.spanned(part.span()));
}
}
}
TokenNode::Flag(Flag {
kind: FlagKind::Longhand,
span,
..
}) => shapes.push(FlatShape::Flag.spanned(*span)),
TokenNode::Flag(Flag {
kind: FlagKind::Shorthand,
span,
..
}) => shapes.push(FlatShape::ShorthandFlag.spanned(*span)),
TokenNode::Whitespace(_) => shapes.push(FlatShape::Whitespace.spanned(token.span())),
TokenNode::Error(v) => shapes.push(FlatShape::Error.spanned(v.span)),
}
}
}

View File

@ -0,0 +1,859 @@
pub(crate) mod debug;
use self::debug::{ColorTracer, ExpandTracer};
#[cfg(coloring_in_tokens)]
use crate::hir::syntax_shape::FlatShape;
use crate::hir::Expression;
use crate::TokenNode;
#[allow(unused)]
use getset::{Getters, MutGetters};
use nu_errors::{ParseError, ShellError};
use nu_source::{HasFallibleSpan, Span, SpannedItem, Spanned, HasSpan, Tag, Text};
cfg_if::cfg_if! {
if #[cfg(coloring_in_tokens)] {
#[derive(Getters, Debug)]
pub struct TokensIteratorState<'content> {
tokens: &'content [TokenNode],
span: Span,
skip_ws: bool,
index: usize,
seen: indexmap::IndexSet<usize>,
#[get = "pub"]
shapes: Vec<Spanned<FlatShape>>,
}
} else {
#[derive(Getters, Debug)]
pub struct TokensIteratorState<'content> {
tokens: &'content [TokenNode],
span: Span,
skip_ws: bool,
index: usize,
seen: indexmap::IndexSet<usize>,
}
}
}
#[derive(Getters, MutGetters, Debug)]
pub struct TokensIterator<'content> {
#[get = "pub"]
#[get_mut = "pub"]
state: TokensIteratorState<'content>,
#[get = "pub"]
#[get_mut = "pub"]
color_tracer: ColorTracer,
#[get = "pub"]
#[get_mut = "pub"]
expand_tracer: ExpandTracer,
}
#[derive(Debug)]
pub struct Checkpoint<'content, 'me> {
pub(crate) iterator: &'me mut TokensIterator<'content>,
index: usize,
seen: indexmap::IndexSet<usize>,
#[cfg(coloring_in_tokens)]
shape_start: usize,
committed: bool,
}
impl<'content, 'me> Checkpoint<'content, 'me> {
pub(crate) fn commit(mut self) {
self.committed = true;
}
}
impl<'content, 'me> std::ops::Drop for Checkpoint<'content, 'me> {
fn drop(&mut self) {
if !self.committed {
let state = &mut self.iterator.state;
state.index = self.index;
state.seen = self.seen.clone();
#[cfg(coloring_in_tokens)]
state.shapes.truncate(self.shape_start);
}
}
}
#[derive(Debug)]
pub struct Peeked<'content, 'me> {
pub(crate) node: Option<&'content TokenNode>,
iterator: &'me mut TokensIterator<'content>,
from: usize,
to: usize,
}
impl<'content, 'me> Peeked<'content, 'me> {
pub fn commit(&mut self) -> Option<&'content TokenNode> {
let Peeked {
node,
iterator,
from,
to,
} = self;
let node = (*node)?;
iterator.commit(*from, *to);
Some(node)
}
pub fn not_eof(self, expected: &'static str) -> Result<PeekedNode<'content, 'me>, ParseError> {
match self.node {
None => Err(ParseError::unexpected_eof(
expected,
self.iterator.eof_span(),
)),
Some(node) => Ok(PeekedNode {
node,
iterator: self.iterator,
from: self.from,
to: self.to,
}),
}
}
pub fn type_error(&self, expected: &'static str) -> ParseError {
peek_error(&self.node, self.iterator.eof_span(), expected)
}
}
#[derive(Debug)]
pub struct PeekedNode<'content, 'me> {
pub(crate) node: &'content TokenNode,
iterator: &'me mut TokensIterator<'content>,
from: usize,
to: usize,
}
impl<'content, 'me> PeekedNode<'content, 'me> {
pub fn commit(self) -> &'content TokenNode {
let PeekedNode {
node,
iterator,
from,
to,
} = self;
iterator.commit(from, to);
node
}
pub fn rollback(self) {}
pub fn type_error(&self, expected: &'static str) -> ParseError {
peek_error(&Some(self.node), self.iterator.eof_span(), expected)
}
}
pub fn peek_error(node: &Option<&TokenNode>, eof_span: Span, expected: &'static str) -> ParseError {
match node {
None => ParseError::unexpected_eof(expected, eof_span),
Some(node) => ParseError::mismatch(expected, node.type_name().spanned(node.span())),
}
}
impl<'content> TokensIterator<'content> {
pub fn new(
items: &'content [TokenNode],
span: Span,
source: Text,
skip_ws: bool,
) -> TokensIterator<'content> {
cfg_if::cfg_if! {
if #[cfg(coloring_in_tokens)] {
TokensIterator {
state: TokensIteratorState {
tokens: items,
span,
skip_ws,
index: 0,
seen: indexmap::IndexSet::new(),
shapes: vec![],
},
color_tracer: ColorTracer::new(source.clone()),
expand_tracer: ExpandTracer::new(source.clone()),
}
} else {
TokensIterator {
state: TokensIteratorState {
tokens: items,
span,
skip_ws,
index: 0,
seen: indexmap::IndexSet::new(),
},
color_tracer: ColorTracer::new(source.clone()),
expand_tracer: ExpandTracer::new(source.clone()),
}
}
}
}
pub fn all(
tokens: &'content [TokenNode],
source: Text,
span: Span,
) -> TokensIterator<'content> {
TokensIterator::new(tokens, span, source, false)
}
pub fn len(&self) -> usize {
self.state.tokens.len()
}
pub fn spanned<T>(
&mut self,
block: impl FnOnce(&mut TokensIterator<'content>) -> T,
) -> Spanned<T> {
let start = self.span_at_cursor();
let result = block(self);
let end = self.span_at_cursor();
result.spanned(start.until(end))
}
#[cfg(coloring_in_tokens)]
pub fn color_shape(&mut self, shape: Spanned<FlatShape>) {
self.with_color_tracer(|_, tracer| tracer.add_shape(shape));
self.state.shapes.push(shape);
}
#[cfg(coloring_in_tokens)]
pub fn mutate_shapes(&mut self, block: impl FnOnce(&mut Vec<Spanned<FlatShape>>)) {
let new_shapes: Vec<Spanned<FlatShape>> = {
let shapes = &mut self.state.shapes;
let len = shapes.len();
block(shapes);
(len..(shapes.len())).map(|i| shapes[i]).collect()
};
self.with_color_tracer(|_, tracer| {
for shape in new_shapes {
tracer.add_shape(shape)
}
});
}
#[cfg(coloring_in_tokens)]
pub fn silently_mutate_shapes(&mut self, block: impl FnOnce(&mut Vec<Spanned<FlatShape>>)) {
let shapes = &mut self.state.shapes;
block(shapes);
}
#[cfg(coloring_in_tokens)]
pub fn sort_shapes(&mut self) {
// This is pretty dubious, but it works. We should look into a better algorithm that doesn't end up requiring
// this solution.
self.state
.shapes
.sort_by(|a, b| a.span.start().cmp(&b.span.start()));
}
#[cfg(coloring_in_tokens)]
pub fn child<'me, T>(
&'me mut self,
tokens: Spanned<&'me [TokenNode]>,
source: Text,
block: impl FnOnce(&mut TokensIterator<'me>) -> T,
) -> T {
let mut shapes = vec![];
std::mem::swap(&mut shapes, &mut self.state.shapes);
let mut color_tracer = ColorTracer::new(source.clone());
std::mem::swap(&mut color_tracer, &mut self.color_tracer);
let mut expand_tracer = ExpandTracer::new(source.clone());
std::mem::swap(&mut expand_tracer, &mut self.expand_tracer);
cfg_if::cfg_if! {
if #[cfg(coloring_in_tokens)] {
let mut iterator = TokensIterator {
state: TokensIteratorState {
tokens: tokens.item,
span: tokens.span,
skip_ws: false,
index: 0,
seen: indexmap::IndexSet::new(),
shapes,
},
color_tracer,
expand_tracer,
};
} else {
let mut iterator = TokensIterator {
state: TokensIteratorState {
tokens: tokens.item,
span: tokens.span,
skip_ws: false,
index: 0,
seen: indexmap::IndexSet::new(),
},
color_tracer,
expand_tracer,
};
}
}
let result = block(&mut iterator);
std::mem::swap(&mut iterator.state.shapes, &mut self.state.shapes);
std::mem::swap(&mut iterator.color_tracer, &mut self.color_tracer);
std::mem::swap(&mut iterator.expand_tracer, &mut self.expand_tracer);
result
}
#[cfg(not(coloring_in_tokens))]
pub fn child<'me, T>(
&'me mut self,
tokens: Spanned<&'me [TokenNode]>,
source: Text,
block: impl FnOnce(&mut TokensIterator<'me>) -> T,
) -> T {
let mut color_tracer = ColorTracer::new(source.clone());
std::mem::swap(&mut color_tracer, &mut self.color_tracer);
let mut expand_tracer = ExpandTracer::new(source.clone());
std::mem::swap(&mut expand_tracer, &mut self.expand_tracer);
let mut iterator = TokensIterator {
state: TokensIteratorState {
tokens: tokens.item,
span: tokens.span,
skip_ws: false,
index: 0,
seen: indexmap::IndexSet::new(),
},
color_tracer,
expand_tracer,
};
let result = block(&mut iterator);
std::mem::swap(&mut iterator.color_tracer, &mut self.color_tracer);
std::mem::swap(&mut iterator.expand_tracer, &mut self.expand_tracer);
result
}
pub fn with_color_tracer(
&mut self,
block: impl FnOnce(&mut TokensIteratorState, &mut ColorTracer),
) {
let state = &mut self.state;
let color_tracer = &mut self.color_tracer;
block(state, color_tracer)
}
pub fn with_expand_tracer(
&mut self,
block: impl FnOnce(&mut TokensIteratorState, &mut ExpandTracer),
) {
let state = &mut self.state;
let tracer = &mut self.expand_tracer;
block(state, tracer)
}
#[cfg(coloring_in_tokens)]
pub fn color_frame<T>(
&mut self,
desc: &'static str,
block: impl FnOnce(&mut TokensIterator) -> T,
) -> T {
self.with_color_tracer(|_, tracer| tracer.start(desc));
let result = block(self);
self.with_color_tracer(|_, tracer| {
tracer.success();
});
result
}
pub fn expand_frame<T>(
&mut self,
desc: &'static str,
block: impl FnOnce(&mut TokensIterator<'content>) -> Result<T, ParseError>,
) -> Result<T, ParseError>
where
T: std::fmt::Debug + Clone + HasFallibleSpan + 'static,
{
self.with_expand_tracer(|_, tracer| tracer.start(desc));
let result = block(self);
self.with_expand_tracer(|_, tracer| match &result {
Ok(result) => {
tracer.add_result(result.clone());
tracer.success();
}
Err(err) => tracer.failed(err),
});
result
}
pub fn expand_expr_frame(
&mut self,
desc: &'static str,
block: impl FnOnce(&mut TokensIterator) -> Result<Expression, ParseError>,
) -> Result<Expression, ParseError> {
self.with_expand_tracer(|_, tracer| tracer.start(desc));
let result = block(self);
self.with_expand_tracer(|_, tracer| match &result {
Ok(expr) => {
tracer.add_expr(expr.clone());
tracer.success()
}
Err(err) => tracer.failed(err),
});
result
}
pub fn color_fallible_frame<T>(
&mut self,
desc: &'static str,
block: impl FnOnce(&mut TokensIterator) -> Result<T, ShellError>,
) -> Result<T, ShellError> {
self.with_color_tracer(|_, tracer| tracer.start(desc));
if self.at_end() {
self.with_color_tracer(|_, tracer| tracer.eof_frame());
return Err(ShellError::unexpected_eof("coloring", Tag::unknown()));
}
let result = block(self);
self.with_color_tracer(|_, tracer| match &result {
Ok(_) => {
tracer.success();
}
Err(err) => tracer.failed(err),
});
result
}
/// Use a checkpoint when you need to peek more than one token ahead, but can't be sure
/// that you'll succeed.
pub fn checkpoint<'me>(&'me mut self) -> Checkpoint<'content, 'me> {
let state = &mut self.state;
let index = state.index;
#[cfg(coloring_in_tokens)]
let shape_start = state.shapes.len();
let seen = state.seen.clone();
Checkpoint {
iterator: self,
index,
seen,
committed: false,
#[cfg(coloring_in_tokens)]
shape_start,
}
}
/// Use a checkpoint when you need to peek more than one token ahead, but can't be sure
/// that you'll succeed.
pub fn atomic<'me, T>(
&'me mut self,
block: impl FnOnce(&mut TokensIterator<'content>) -> Result<T, ShellError>,
) -> Result<T, ShellError> {
let state = &mut self.state;
let index = state.index;
#[cfg(coloring_in_tokens)]
let shape_start = state.shapes.len();
let seen = state.seen.clone();
let checkpoint = Checkpoint {
iterator: self,
index,
seen,
committed: false,
#[cfg(coloring_in_tokens)]
shape_start,
};
let value = block(checkpoint.iterator)?;
checkpoint.commit();
return Ok(value);
}
/// Use a checkpoint when you need to peek more than one token ahead, but can't be sure
/// that you'll succeed.
pub fn atomic_parse<'me, T>(
&'me mut self,
block: impl FnOnce(&mut TokensIterator<'content>) -> Result<T, ParseError>,
) -> Result<T, ParseError> {
let state = &mut self.state;
let index = state.index;
#[cfg(coloring_in_tokens)]
let shape_start = state.shapes.len();
let seen = state.seen.clone();
let checkpoint = Checkpoint {
iterator: self,
index,
seen,
committed: false,
#[cfg(coloring_in_tokens)]
shape_start,
};
let value = block(checkpoint.iterator)?;
checkpoint.commit();
return Ok(value);
}
#[cfg(coloring_in_tokens)]
/// Use a checkpoint when you need to peek more than one token ahead, but can't be sure
/// that you'll succeed.
pub fn atomic_returning_shapes<'me, T>(
&'me mut self,
block: impl FnOnce(&mut TokensIterator<'content>) -> Result<T, ShellError>,
) -> (Result<T, ShellError>, Vec<Spanned<FlatShape>>) {
let index = self.state.index;
let mut shapes = vec![];
let seen = self.state.seen.clone();
std::mem::swap(&mut self.state.shapes, &mut shapes);
let checkpoint = Checkpoint {
iterator: self,
index,
seen,
committed: false,
shape_start: 0,
};
let value = block(checkpoint.iterator);
let value = match value {
Err(err) => {
drop(checkpoint);
std::mem::swap(&mut self.state.shapes, &mut shapes);
return (Err(err), vec![]);
}
Ok(value) => value,
};
checkpoint.commit();
std::mem::swap(&mut self.state.shapes, &mut shapes);
return (Ok(value), shapes);
}
fn eof_span(&self) -> Span {
Span::new(self.state.span.end(), self.state.span.end())
}
pub fn typed_span_at_cursor(&mut self) -> Spanned<&'static str> {
let next = self.peek_any();
match next.node {
None => "end".spanned(self.eof_span()),
Some(node) => node.spanned_type_name(),
}
}
pub fn span_at_cursor(&mut self) -> Span {
let next = self.peek_any();
match next.node {
None => self.eof_span(),
Some(node) => node.span(),
}
}
pub fn remove(&mut self, position: usize) {
self.state.seen.insert(position);
}
pub fn at_end(&self) -> bool {
peek(self, self.state.skip_ws).is_none()
}
pub fn at_end_possible_ws(&self) -> bool {
peek(self, true).is_none()
}
pub fn advance(&mut self) {
self.state.seen.insert(self.state.index);
self.state.index += 1;
}
pub fn extract<T>(&mut self, f: impl Fn(&TokenNode) -> Option<T>) -> Option<(usize, T)> {
let state = &mut self.state;
for (i, item) in state.tokens.iter().enumerate() {
if state.seen.contains(&i) {
continue;
}
match f(item) {
None => {
continue;
}
Some(value) => {
state.seen.insert(i);
return Some((i, value));
}
}
}
None
}
pub fn move_to(&mut self, pos: usize) {
self.state.index = pos;
}
pub fn restart(&mut self) {
self.state.index = 0;
}
// pub fn clone(&self) -> TokensIterator<'content> {
// let state = &self.state;
// TokensIterator {
// state: TokensIteratorState {
// tokens: state.tokens,
// span: state.span,
// index: state.index,
// seen: state.seen.clone(),
// skip_ws: state.skip_ws,
// #[cfg(coloring_in_tokens)]
// shapes: state.shapes.clone(),
// },
// color_tracer: self.color_tracer.clone(),
// expand_tracer: self.expand_tracer.clone(),
// }
// }
// Peek the next token, not including whitespace
pub fn peek_non_ws<'me>(&'me mut self) -> Peeked<'content, 'me> {
start_next(self, true)
}
// Peek the next token, including whitespace
pub fn peek_any<'me>(&'me mut self) -> Peeked<'content, 'me> {
start_next(self, false)
}
// Peek the next token, including whitespace, but not EOF
pub fn peek_any_token<'me, T>(
&'me mut self,
expected: &'static str,
block: impl FnOnce(&'content TokenNode) -> Result<T, ParseError>,
) -> Result<T, ParseError> {
let peeked = start_next(self, false);
let peeked = peeked.not_eof(expected);
match peeked {
Err(err) => return Err(err),
Ok(peeked) => match block(peeked.node) {
Err(err) => return Err(err),
Ok(val) => {
peeked.commit();
return Ok(val);
}
},
}
}
fn commit(&mut self, from: usize, to: usize) {
for index in from..to {
self.state.seen.insert(index);
}
self.state.index = to;
}
pub fn pos(&self, skip_ws: bool) -> Option<usize> {
peek_pos(self, skip_ws)
}
pub fn debug_remaining(&self) -> Vec<TokenNode> {
// TODO: TODO: TODO: Clean up
vec![]
// let mut tokens = self.clone();
// tokens.restart();
// tokens.cloned().collect()
}
}
impl<'content> Iterator for TokensIterator<'content> {
type Item = &'content TokenNode;
fn next(&mut self) -> Option<Self::Item> {
next(self, self.state.skip_ws)
}
}
fn peek<'content, 'me>(
iterator: &'me TokensIterator<'content>,
skip_ws: bool,
) -> Option<&'me TokenNode> {
let state = iterator.state();
let mut to = state.index;
loop {
if to >= state.tokens.len() {
return None;
}
if state.seen.contains(&to) {
to += 1;
continue;
}
if to >= state.tokens.len() {
return None;
}
let node = &state.tokens[to];
match node {
TokenNode::Whitespace(_) if skip_ws => {
to += 1;
}
_ => {
return Some(node);
}
}
}
}
fn peek_pos<'content, 'me>(
iterator: &'me TokensIterator<'content>,
skip_ws: bool,
) -> Option<usize> {
let state = iterator.state();
let mut to = state.index;
loop {
if to >= state.tokens.len() {
return None;
}
if state.seen.contains(&to) {
to += 1;
continue;
}
if to >= state.tokens.len() {
return None;
}
let node = &state.tokens[to];
match node {
TokenNode::Whitespace(_) if skip_ws => {
to += 1;
}
_ => return Some(to),
}
}
}
fn start_next<'content, 'me>(
iterator: &'me mut TokensIterator<'content>,
skip_ws: bool,
) -> Peeked<'content, 'me> {
let state = iterator.state();
let from = state.index;
let mut to = state.index;
loop {
if to >= state.tokens.len() {
return Peeked {
node: None,
iterator,
from,
to,
};
}
if state.seen.contains(&to) {
to += 1;
continue;
}
if to >= state.tokens.len() {
return Peeked {
node: None,
iterator,
from,
to,
};
}
let node = &state.tokens[to];
match node {
TokenNode::Whitespace(_) if skip_ws => {
to += 1;
}
_ => {
to += 1;
return Peeked {
node: Some(node),
iterator,
from,
to,
};
}
}
}
}
fn next<'me, 'content>(
iterator: &'me mut TokensIterator<'content>,
skip_ws: bool,
) -> Option<&'content TokenNode> {
loop {
if iterator.state().index >= iterator.state().tokens.len() {
return None;
}
if iterator.state().seen.contains(&iterator.state().index) {
iterator.advance();
continue;
}
if iterator.state().index >= iterator.state().tokens.len() {
return None;
}
match &iterator.state().tokens[iterator.state().index] {
TokenNode::Whitespace(_) if skip_ws => {
iterator.advance();
}
other => {
iterator.advance();
return Some(other);
}
}
}
}

View File

@ -0,0 +1,38 @@
#![allow(unused)]
pub(crate) mod color_trace;
pub(crate) mod expand_trace;
pub(crate) use self::color_trace::*;
pub(crate) use self::expand_trace::*;
use crate::hir::tokens_iterator::TokensIteratorState;
use nu_source::{PrettyDebug, PrettyDebugWithSource, Text};
#[derive(Debug)]
pub(crate) enum DebugIteratorToken {
Seen(String),
Unseen(String),
Cursor,
}
pub(crate) fn debug_tokens(state: &TokensIteratorState, source: &str) -> Vec<DebugIteratorToken> {
let mut out = vec![];
for (i, token) in state.tokens.iter().enumerate() {
if state.index == i {
out.push(DebugIteratorToken::Cursor);
}
if state.seen.contains(&i) {
out.push(DebugIteratorToken::Seen(format!("{}", token.debug(source))));
} else {
out.push(DebugIteratorToken::Unseen(format!(
"{}",
token.debug(source)
)));
}
}
out
}

View File

@ -0,0 +1,353 @@
use crate::hir::syntax_shape::FlatShape;
use ansi_term::Color;
use log::trace;
use nu_errors::ShellError;
use nu_source::{Spanned, Text};
use ptree::*;
use std::borrow::Cow;
use std::io;
#[derive(Debug, Clone)]
pub enum FrameChild {
#[allow(unused)]
Shape(Spanned<FlatShape>),
Frame(ColorFrame),
}
impl FrameChild {
fn colored_leaf_description(&self, text: &Text, f: &mut impl io::Write) -> io::Result<()> {
match self {
FrameChild::Shape(shape) => write!(
f,
"{} {:?}",
Color::White
.bold()
.on(Color::Green)
.paint(format!("{:?}", shape.item)),
shape.span.slice(text)
),
FrameChild::Frame(frame) => frame.colored_leaf_description(f),
}
}
fn into_tree_child(self, text: &Text) -> TreeChild {
match self {
FrameChild::Shape(shape) => TreeChild::Shape(shape, text.clone()),
FrameChild::Frame(frame) => TreeChild::Frame(frame, text.clone()),
}
}
}
#[derive(Debug, Clone)]
pub struct ColorFrame {
description: &'static str,
children: Vec<FrameChild>,
error: Option<ShellError>,
}
impl ColorFrame {
fn colored_leaf_description(&self, f: &mut impl io::Write) -> io::Result<()> {
if self.has_only_error_descendents() {
if self.children.len() == 0 {
write!(
f,
"{}",
Color::White.bold().on(Color::Red).paint(self.description)
)
} else {
write!(f, "{}", Color::Red.normal().paint(self.description))
}
} else if self.has_descendent_shapes() {
write!(f, "{}", Color::Green.normal().paint(self.description))
} else {
write!(f, "{}", Color::Yellow.bold().paint(self.description))
}
}
fn colored_description(&self, text: &Text, f: &mut impl io::Write) -> io::Result<()> {
if self.children.len() == 1 {
let child = &self.children[0];
self.colored_leaf_description(f)?;
write!(f, " -> ")?;
child.colored_leaf_description(text, f)
} else {
self.colored_leaf_description(f)
}
}
fn children_for_formatting(&self, text: &Text) -> Vec<TreeChild> {
if self.children.len() == 1 {
let child = &self.children[0];
match child {
FrameChild::Shape(_) => vec![],
FrameChild::Frame(frame) => frame.tree_children(text),
}
} else {
self.tree_children(text)
}
}
fn tree_children(&self, text: &Text) -> Vec<TreeChild> {
self.children
.clone()
.into_iter()
.map(|c| c.into_tree_child(text))
.collect()
}
#[allow(unused)]
fn add_shape(&mut self, shape: Spanned<FlatShape>) {
self.children.push(FrameChild::Shape(shape))
}
fn has_child_shapes(&self) -> bool {
self.any_child_shape(|_| true)
}
fn any_child_shape(&self, predicate: impl Fn(Spanned<FlatShape>) -> bool) -> bool {
for item in &self.children {
match item {
FrameChild::Shape(shape) => {
if predicate(*shape) {
return true;
}
}
_ => {}
}
}
false
}
fn any_child_frame(&self, predicate: impl Fn(&ColorFrame) -> bool) -> bool {
for item in &self.children {
match item {
FrameChild::Frame(frame) => {
if predicate(frame) {
return true;
}
}
_ => {}
}
}
false
}
fn has_descendent_shapes(&self) -> bool {
if self.has_child_shapes() {
true
} else {
self.any_child_frame(|frame| frame.has_descendent_shapes())
}
}
fn has_only_error_descendents(&self) -> bool {
if self.children.len() == 0 {
// if this frame has no children at all, it has only error descendents if this frame
// is an error
self.error.is_some()
} else {
// otherwise, it has only error descendents if all of its children terminate in an
// error (transitively)
let mut seen_error = false;
for child in &self.children {
match child {
// if this frame has at least one child shape, this frame has non-error descendents
FrameChild::Shape(_) => return false,
FrameChild::Frame(frame) => {
// if the chi
if frame.has_only_error_descendents() {
seen_error = true;
} else {
return false;
}
}
}
}
seen_error
}
}
}
#[derive(Debug, Clone)]
pub enum TreeChild {
Shape(Spanned<FlatShape>, Text),
Frame(ColorFrame, Text),
}
impl TreeChild {
fn colored_leaf_description(&self, f: &mut impl io::Write) -> io::Result<()> {
match self {
TreeChild::Shape(shape, text) => write!(
f,
"{} {:?}",
Color::White
.bold()
.on(Color::Green)
.paint(format!("{:?}", shape.item)),
shape.span.slice(text)
),
TreeChild::Frame(frame, _) => frame.colored_leaf_description(f),
}
}
}
impl TreeItem for TreeChild {
type Child = TreeChild;
fn write_self<W: io::Write>(&self, f: &mut W, _style: &Style) -> io::Result<()> {
match self {
shape @ TreeChild::Shape(..) => shape.colored_leaf_description(f),
TreeChild::Frame(frame, text) => frame.colored_description(text, f),
}
}
fn children(&self) -> Cow<[Self::Child]> {
match self {
TreeChild::Shape(..) => Cow::Borrowed(&[]),
TreeChild::Frame(frame, text) => Cow::Owned(frame.children_for_formatting(text)),
}
}
}
#[derive(Debug, Clone)]
pub struct ColorTracer {
frame_stack: Vec<ColorFrame>,
source: Text,
}
impl ColorTracer {
pub fn print(self, source: Text) -> PrintTracer {
PrintTracer {
tracer: self,
source,
}
}
pub fn new(source: Text) -> ColorTracer {
let root = ColorFrame {
description: "Trace",
children: vec![],
error: None,
};
ColorTracer {
frame_stack: vec![root],
source,
}
}
fn current_frame(&mut self) -> &mut ColorFrame {
let frames = &mut self.frame_stack;
let last = frames.len() - 1;
&mut frames[last]
}
fn pop_frame(&mut self) -> ColorFrame {
trace!(target: "nu::color_syntax", "Popping {:#?}", self);
let result = self.frame_stack.pop().expect("Can't pop root tracer frame");
if self.frame_stack.len() == 0 {
panic!("Can't pop root tracer frame {:#?}", self);
}
self.debug();
result
}
pub fn start(&mut self, description: &'static str) {
let frame = ColorFrame {
description,
children: vec![],
error: None,
};
self.frame_stack.push(frame);
self.debug();
}
pub fn eof_frame(&mut self) {
let current = self.pop_frame();
self.current_frame()
.children
.push(FrameChild::Frame(current));
}
#[allow(unused)]
pub fn finish(&mut self) {
loop {
if self.frame_stack.len() == 1 {
break;
}
let frame = self.pop_frame();
self.current_frame().children.push(FrameChild::Frame(frame));
}
}
#[allow(unused)]
pub fn add_shape(&mut self, shape: Spanned<FlatShape>) {
self.current_frame().add_shape(shape);
}
pub fn success(&mut self) {
let current = self.pop_frame();
self.current_frame()
.children
.push(FrameChild::Frame(current));
}
pub fn failed(&mut self, error: &ShellError) {
let mut current = self.pop_frame();
current.error = Some(error.clone());
self.current_frame()
.children
.push(FrameChild::Frame(current));
}
fn debug(&self) {
trace!(target: "nu::color_syntax",
"frames = {:?}",
self.frame_stack
.iter()
.map(|f| f.description)
.collect::<Vec<_>>()
);
trace!(target: "nu::color_syntax", "{:#?}", self);
}
}
#[derive(Debug, Clone)]
pub struct PrintTracer {
tracer: ColorTracer,
source: Text,
}
impl TreeItem for PrintTracer {
type Child = TreeChild;
fn write_self<W: io::Write>(&self, f: &mut W, style: &Style) -> io::Result<()> {
write!(f, "{}", style.paint("Color Trace"))
}
fn children(&self) -> Cow<[Self::Child]> {
Cow::Owned(vec![TreeChild::Frame(
self.tracer.frame_stack[0].clone(),
self.source.clone(),
)])
}
}

View File

@ -0,0 +1,370 @@
use crate::hir::Expression;
use ansi_term::Color;
use log::trace;
use nu_errors::ParseError;
use nu_protocol::ShellTypeName;
use nu_source::{DebugDoc, PrettyDebug, PrettyDebugWithSource, Text};
use ptree::*;
use std::borrow::Cow;
use std::io;
#[derive(Debug)]
pub enum FrameChild {
Expr(Expression),
Frame(ExprFrame),
Result(DebugDoc),
}
impl FrameChild {
fn get_error_leaf(&self) -> Option<&'static str> {
match self {
FrameChild::Frame(frame) if frame.error.is_some() => {
if frame.children.len() == 0 {
Some(frame.description)
} else {
None
}
}
_ => None,
}
}
fn to_tree_child(&self, text: &Text) -> TreeChild {
match self {
FrameChild::Expr(expr) => TreeChild::OkExpr(expr.clone(), text.clone()),
FrameChild::Result(result) => {
let result = format!("{}", result.display());
TreeChild::OkNonExpr(result)
}
FrameChild::Frame(frame) => {
if frame.error.is_some() {
if frame.children.len() == 0 {
TreeChild::ErrorLeaf(vec![frame.description])
} else {
TreeChild::ErrorFrame(frame.to_tree_frame(text), text.clone())
}
} else {
TreeChild::OkFrame(frame.to_tree_frame(text), text.clone())
}
}
}
}
}
#[derive(Debug)]
pub struct ExprFrame {
description: &'static str,
children: Vec<FrameChild>,
error: Option<ParseError>,
}
impl ExprFrame {
fn to_tree_frame(&self, text: &Text) -> TreeFrame {
let mut children = vec![];
let mut errors = vec![];
for child in &self.children {
if let Some(error_leaf) = child.get_error_leaf() {
errors.push(error_leaf);
continue;
} else if errors.len() > 0 {
children.push(TreeChild::ErrorLeaf(errors));
errors = vec![];
}
children.push(child.to_tree_child(text));
}
if errors.len() > 0 {
children.push(TreeChild::ErrorLeaf(errors));
}
TreeFrame {
description: self.description,
children,
error: self.error.clone(),
}
}
fn add_expr(&mut self, expr: Expression) {
self.children.push(FrameChild::Expr(expr))
}
fn add_result(&mut self, result: impl PrettyDebug) {
self.children.push(FrameChild::Result(result.to_doc()))
}
}
#[derive(Debug, Clone)]
pub struct TreeFrame {
description: &'static str,
children: Vec<TreeChild>,
error: Option<ParseError>,
}
impl TreeFrame {
fn leaf_description(&self, f: &mut impl io::Write) -> io::Result<()> {
if self.children.len() == 1 {
if self.error.is_some() {
write!(f, "{}", Color::Red.normal().paint(self.description))?;
} else if self.has_descendent_green() {
write!(f, "{}", Color::Green.normal().paint(self.description))?;
} else {
write!(f, "{}", Color::Yellow.bold().paint(self.description))?;
}
write!(f, " -> ")?;
self.children[0].leaf_description(f)
} else {
if self.error.is_some() {
if self.children.len() == 0 {
write!(
f,
"{}",
Color::White.bold().on(Color::Red).paint(self.description)
)
} else {
write!(f, "{}", Color::Red.normal().paint(self.description))
}
} else if self.has_descendent_green() {
write!(f, "{}", Color::Green.normal().paint(self.description))
} else {
write!(f, "{}", Color::Yellow.bold().paint(self.description))
}
}
}
fn has_child_green(&self) -> bool {
self.children.iter().any(|item| match item {
TreeChild::OkFrame(..) | TreeChild::ErrorFrame(..) | TreeChild::ErrorLeaf(..) => false,
TreeChild::OkExpr(..) | TreeChild::OkNonExpr(..) => true,
})
}
fn any_child_frame(&self, predicate: impl Fn(&TreeFrame) -> bool) -> bool {
for item in &self.children {
match item {
TreeChild::OkFrame(frame, ..) => {
if predicate(frame) {
return true;
}
}
_ => {}
}
}
false
}
fn has_descendent_green(&self) -> bool {
if self.has_child_green() {
true
} else {
self.any_child_frame(|frame| frame.has_child_green())
}
}
fn children_for_formatting(&self, text: &Text) -> Vec<TreeChild> {
if self.children.len() == 1 {
let child: &TreeChild = &self.children[0];
match child {
TreeChild::OkExpr(..) | TreeChild::OkNonExpr(..) | TreeChild::ErrorLeaf(..) => {
vec![]
}
TreeChild::OkFrame(frame, _) | TreeChild::ErrorFrame(frame, _) => {
frame.children_for_formatting(text)
}
}
} else {
self.children.clone()
}
}
}
#[derive(Debug, Clone)]
pub enum TreeChild {
OkNonExpr(String),
OkExpr(Expression, Text),
OkFrame(TreeFrame, Text),
ErrorFrame(TreeFrame, Text),
ErrorLeaf(Vec<&'static str>),
}
impl TreeChild {
fn leaf_description(&self, f: &mut impl io::Write) -> io::Result<()> {
match self {
TreeChild::OkExpr(expr, text) => write!(
f,
"{} {} {}",
Color::Cyan.normal().paint("returns"),
Color::White.bold().on(Color::Green).paint(expr.type_name()),
expr.span.slice(text)
),
TreeChild::OkNonExpr(result) => write!(
f,
"{} {}",
Color::Cyan.normal().paint("returns"),
Color::White
.bold()
.on(Color::Green)
.paint(format!("{}", result))
),
TreeChild::ErrorLeaf(desc) => {
let last = desc.len() - 1;
for (i, item) in desc.iter().enumerate() {
write!(f, "{}", Color::White.bold().on(Color::Red).paint(*item))?;
if i != last {
write!(f, "{}", Color::White.normal().paint(", "))?;
}
}
Ok(())
}
TreeChild::ErrorFrame(frame, _) | TreeChild::OkFrame(frame, _) => {
frame.leaf_description(f)
}
}
}
}
impl TreeItem for TreeChild {
type Child = TreeChild;
fn write_self<W: io::Write>(&self, f: &mut W, _style: &Style) -> io::Result<()> {
self.leaf_description(f)
}
fn children(&self) -> Cow<[Self::Child]> {
match self {
TreeChild::OkExpr(..) | TreeChild::OkNonExpr(..) | TreeChild::ErrorLeaf(..) => {
Cow::Borrowed(&[])
}
TreeChild::OkFrame(frame, text) | TreeChild::ErrorFrame(frame, text) => {
Cow::Owned(frame.children_for_formatting(text))
}
}
}
}
#[derive(Debug)]
pub struct ExpandTracer {
frame_stack: Vec<ExprFrame>,
source: Text,
}
impl ExpandTracer {
pub fn print(&self, source: Text) -> PrintTracer {
let root = self
.frame_stack
.iter()
.nth(0)
.unwrap()
.to_tree_frame(&source);
PrintTracer { root, source }
}
pub fn new(source: Text) -> ExpandTracer {
let root = ExprFrame {
description: "Trace",
children: vec![],
error: None,
};
ExpandTracer {
frame_stack: vec![root],
source,
}
}
fn current_frame(&mut self) -> &mut ExprFrame {
let frames = &mut self.frame_stack;
let last = frames.len() - 1;
&mut frames[last]
}
fn pop_frame(&mut self) -> ExprFrame {
let result = self.frame_stack.pop().expect("Can't pop root tracer frame");
if self.frame_stack.len() == 0 {
panic!("Can't pop root tracer frame");
}
self.debug();
result
}
pub fn start(&mut self, description: &'static str) {
let frame = ExprFrame {
description,
children: vec![],
error: None,
};
self.frame_stack.push(frame);
self.debug();
}
pub fn add_expr(&mut self, shape: Expression) {
self.current_frame().add_expr(shape);
}
pub fn add_result(&mut self, result: impl PrettyDebugWithSource) {
let source = self.source.clone();
self.current_frame().add_result(result.debuggable(source));
}
pub fn success(&mut self) {
trace!(target: "parser::expand_syntax", "success {:#?}", self);
let current = self.pop_frame();
self.current_frame()
.children
.push(FrameChild::Frame(current));
}
pub fn failed(&mut self, error: &ParseError) {
let mut current = self.pop_frame();
current.error = Some(error.clone());
self.current_frame()
.children
.push(FrameChild::Frame(current));
}
fn debug(&self) {
trace!(target: "nu::parser::expand",
"frames = {:?}",
self.frame_stack
.iter()
.map(|f| f.description)
.collect::<Vec<_>>()
);
trace!(target: "nu::parser::expand", "{:#?}", self);
}
}
#[derive(Debug, Clone)]
pub struct PrintTracer {
root: TreeFrame,
source: Text,
}
impl TreeItem for PrintTracer {
type Child = TreeChild;
fn write_self<W: io::Write>(&self, f: &mut W, style: &Style) -> io::Result<()> {
write!(f, "{}", style.paint("Expansion Trace"))
}
fn children(&self) -> Cow<[Self::Child]> {
Cow::Borrowed(&self.root.children)
}
}

View File

@ -0,0 +1,16 @@
use crate::hir::TokensIterator;
use crate::parse::token_tree_builder::TokenTreeBuilder as b;
use crate::Span;
#[test]
fn supplies_tokens() {
let tokens = b::token_list(vec![b::var("it"), b::op("."), b::bare("cpu")]);
let (tokens, _) = b::build(tokens);
let tokens = tokens.expect_list();
let mut iterator = TokensIterator::all(tokens, Span::unknown());
iterator.next().unwrap().expect_var();
iterator.next().unwrap().expect_dot();
iterator.next().unwrap().expect_bare();
}

View File

@ -0,0 +1,30 @@
pub mod commands;
pub mod debug;
pub mod hir;
pub mod parse;
pub mod parse_command;
pub use crate::commands::classified::{ClassifiedCommand, ClassifiedPipeline, InternalCommand};
pub use crate::commands::ExternalCommand;
pub use crate::hir::syntax_shape::flat_shape::FlatShape;
pub use crate::hir::syntax_shape::{expand_syntax, ExpandSyntax, PipelineShape, SignatureRegistry};
pub use crate::hir::tokens_iterator::TokensIterator;
pub use crate::parse::files::Files;
pub use crate::parse::flag::Flag;
pub use crate::parse::operator::Operator;
pub use crate::parse::parser::pipeline;
pub use crate::parse::parser::Number;
pub use crate::parse::token_tree::{Delimiter, TokenNode};
pub use crate::parse::token_tree_builder::TokenTreeBuilder;
use nu_errors::ShellError;
use nu_source::nom_input;
pub fn parse(input: &str) -> Result<TokenNode, ShellError> {
let _ = pretty_env_logger::try_init();
match pipeline(nom_input(input)) {
Ok((_rest, val)) => Ok(val),
Err(err) => Err(ShellError::parse_error(err)),
}
}

View File

@ -0,0 +1,11 @@
pub(crate) mod call_node;
pub(crate) mod files;
pub(crate) mod flag;
pub(crate) mod operator;
pub(crate) mod parser;
pub(crate) mod pipeline;
pub(crate) mod token_tree;
pub(crate) mod token_tree_builder;
pub(crate) mod tokens;
pub(crate) mod unit;
pub(crate) mod util;

View File

@ -0,0 +1,45 @@
use crate::TokenNode;
use getset::Getters;
use nu_source::{b, DebugDocBuilder, PrettyDebugWithSource};
#[derive(Debug, Clone, Eq, PartialEq, Ord, PartialOrd, Getters)]
pub struct CallNode {
#[get = "pub(crate)"]
head: Box<TokenNode>,
#[get = "pub(crate)"]
children: Option<Vec<TokenNode>>,
}
impl PrettyDebugWithSource for CallNode {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
b::typed(
"call",
self.head.pretty_debug(source)
+ b::preceded(
b::space(),
b::intersperse(
self.children.iter().flat_map(|children| {
children.iter().map(|child| child.pretty_debug(source))
}),
b::space(),
),
),
)
}
}
impl CallNode {
pub fn new(head: Box<TokenNode>, children: Vec<TokenNode>) -> CallNode {
if children.len() == 0 {
CallNode {
head,
children: None,
}
} else {
CallNode {
head,
children: Some(children),
}
}
}
}

View File

@ -0,0 +1,101 @@
use derive_new::new;
use language_reporting::{FileName, Location};
use log::trace;
use nu_source::Span;
#[derive(new, Debug, Clone)]
pub struct Files {
snippet: String,
}
impl language_reporting::ReportingFiles for Files {
type Span = Span;
type FileId = usize;
fn byte_span(
&self,
_file: Self::FileId,
from_index: usize,
to_index: usize,
) -> Option<Self::Span> {
Some(Span::new(from_index, to_index))
}
fn file_id(&self, _tag: Self::Span) -> Self::FileId {
0
}
fn file_name(&self, _file: Self::FileId) -> FileName {
FileName::Verbatim(format!("shell"))
}
fn byte_index(&self, _file: Self::FileId, _line: usize, _column: usize) -> Option<usize> {
unimplemented!("byte_index")
}
fn location(&self, _file: Self::FileId, byte_index: usize) -> Option<Location> {
let source = &self.snippet;
let mut seen_lines = 0;
let mut seen_bytes = 0;
for (pos, slice) in source.match_indices('\n') {
trace!(
"SEARCH={} SEEN={} POS={} SLICE={:?} LEN={} ALL={:?}",
byte_index,
seen_bytes,
pos,
slice,
source.len(),
source
);
if pos >= byte_index {
return Some(language_reporting::Location::new(
seen_lines,
byte_index - seen_bytes,
));
} else {
seen_lines += 1;
seen_bytes = pos;
}
}
if seen_lines == 0 {
Some(language_reporting::Location::new(0, byte_index))
} else {
panic!("byte index {} wasn't valid", byte_index);
}
}
fn line_span(&self, _file: Self::FileId, lineno: usize) -> Option<Self::Span> {
let source = &self.snippet;
let mut seen_lines = 0;
let mut seen_bytes = 0;
for (pos, _) in source.match_indices('\n') {
if seen_lines == lineno {
return Some(Span::new(seen_bytes, pos + 1));
} else {
seen_lines += 1;
seen_bytes = pos + 1;
}
}
if seen_lines == 0 {
Some(Span::new(0, self.snippet.len() - 1))
} else {
None
}
}
fn source(&self, span: Self::Span) -> Option<String> {
trace!("source(tag={:?}) snippet={:?}", span, self.snippet);
if span.start() > span.end() {
return None;
} else if span.end() > self.snippet.len() {
return None;
}
Some(span.slice(&self.snippet).to_string())
}
}

View File

@ -0,0 +1,39 @@
use crate::hir::syntax_shape::flat_shape::FlatShape;
use derive_new::new;
use getset::Getters;
use nu_source::{Span, b, Spanned, SpannedItem, PrettyDebugWithSource, DebugDocBuilder};
use serde::{Deserialize, Serialize};
#[derive(Debug, Clone, Copy, PartialEq, Eq, PartialOrd, Ord, Hash, Deserialize, Serialize)]
pub enum FlagKind {
Shorthand,
Longhand,
}
#[derive(Debug, Clone, Copy, PartialEq, Eq, PartialOrd, Ord, Hash, Getters, new)]
#[get = "pub(crate)"]
pub struct Flag {
pub(crate) kind: FlagKind,
pub(crate) name: Span,
pub(crate) span: Span,
}
impl PrettyDebugWithSource for Flag {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
let prefix = match self.kind {
FlagKind::Longhand => b::description("--"),
FlagKind::Shorthand => b::description("-"),
};
prefix + b::description(self.name.slice(source))
}
}
impl Flag {
pub fn color(&self) -> Spanned<FlatShape> {
match self.kind {
FlagKind::Longhand => FlatShape::Flag.spanned(self.span),
FlagKind::Shorthand => FlatShape::ShorthandFlag.spanned(self.span),
}
}
}

View File

@ -0,0 +1,67 @@
use serde::{Deserialize, Serialize};
use nu_source::{b, PrettyDebug, DebugDocBuilder};
use std::str::FromStr;
#[derive(Debug, Clone, Copy, PartialEq, Eq, PartialOrd, Ord, Hash, Deserialize, Serialize)]
pub enum Operator {
Equal,
NotEqual,
LessThan,
GreaterThan,
LessThanOrEqual,
GreaterThanOrEqual,
Dot,
Contains,
NotContains,
}
impl PrettyDebug for Operator {
fn pretty(&self) -> DebugDocBuilder {
b::operator(self.as_str())
}
}
impl Operator {
pub fn print(&self) -> String {
self.as_str().to_string()
}
pub fn as_str(&self) -> &str {
match *self {
Operator::Equal => "==",
Operator::NotEqual => "!=",
Operator::LessThan => "<",
Operator::GreaterThan => ">",
Operator::LessThanOrEqual => "<=",
Operator::GreaterThanOrEqual => ">=",
Operator::Dot => ".",
Operator::Contains => "=~",
Operator::NotContains => "!~",
}
}
}
impl From<&str> for Operator {
fn from(input: &str) -> Operator {
Operator::from_str(input).unwrap()
}
}
impl FromStr for Operator {
type Err = ();
fn from_str(input: &str) -> Result<Self, <Self as std::str::FromStr>::Err> {
match input {
"==" => Ok(Operator::Equal),
"!=" => Ok(Operator::NotEqual),
"<" => Ok(Operator::LessThan),
">" => Ok(Operator::GreaterThan),
"<=" => Ok(Operator::LessThanOrEqual),
">=" => Ok(Operator::GreaterThanOrEqual),
"." => Ok(Operator::Dot),
"=~" => Ok(Operator::Contains),
"!~" => Ok(Operator::NotContains),
_ => Err(()),
}
}
}

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,75 @@
use crate::TokenNode;
use derive_new::new;
use getset::Getters;
use nu_source::{b, DebugDocBuilder, PrettyDebugWithSource, Span, Spanned, HasSpan};
#[derive(Debug, Clone, PartialEq, Eq, PartialOrd, Ord, Getters, new)]
pub struct Pipeline {
#[get = "pub"]
pub(crate) parts: Vec<PipelineElement>,
pub(crate) span: Span,
}
#[derive(Debug, Clone, Eq, PartialEq, Ord, PartialOrd, Getters, new)]
pub struct Tokens {
pub(crate) tokens: Vec<TokenNode>,
pub(crate) span: Span,
}
impl Tokens {
pub fn iter(&self) -> impl Iterator<Item = &TokenNode> {
self.tokens.iter()
}
}
#[derive(Debug, Clone, Eq, PartialEq, Ord, PartialOrd, Getters)]
pub struct PipelineElement {
pub pipe: Option<Span>,
pub tokens: Tokens,
}
impl HasSpan for PipelineElement {
fn span(&self) -> Span {
match self.pipe {
Option::None => self.tokens.span,
Option::Some(pipe) => pipe.until(self.tokens.span),
}
}
}
impl PipelineElement {
pub fn new(pipe: Option<Span>, tokens: Spanned<Vec<TokenNode>>) -> PipelineElement {
PipelineElement {
pipe,
tokens: Tokens {
tokens: tokens.item,
span: tokens.span,
},
}
}
pub fn tokens(&self) -> &[TokenNode] {
&self.tokens.tokens
}
}
impl PrettyDebugWithSource for Pipeline {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
b::intersperse(
self.parts.iter().map(|token| token.pretty_debug(source)),
b::operator(" | "),
)
}
}
impl PrettyDebugWithSource for PipelineElement {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
b::intersperse(
self.tokens.iter().map(|token| match token {
TokenNode::Whitespace(_) => b::blank(),
token => token.pretty_debug(source),
}),
b::space(),
)
}
}

View File

@ -0,0 +1,440 @@
use crate::parse::{call_node::*, flag::*, operator::*, pipeline::*, tokens::*};
use derive_new::new;
use getset::Getters;
use nu_errors::{ParseError, ShellError};
use nu_protocol::ShellTypeName;
use nu_source::{
b, DebugDocBuilder, HasSpan, PrettyDebugWithSource, Span, Spanned, SpannedItem, Tagged,
TaggedItem, Text,
};
use std::fmt;
#[derive(Debug, Clone, Eq, PartialEq, Ord, PartialOrd)]
pub enum TokenNode {
Token(Token),
Call(Spanned<CallNode>),
Nodes(Spanned<Vec<TokenNode>>),
Delimited(Spanned<DelimitedNode>),
Pipeline(Pipeline),
Flag(Flag),
Whitespace(Span),
Error(Spanned<ShellError>),
}
impl PrettyDebugWithSource for TokenNode {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
match self {
TokenNode::Token(token) => token.pretty_debug(source),
TokenNode::Call(call) => call.pretty_debug(source),
TokenNode::Nodes(nodes) => b::intersperse(
nodes.iter().map(|node| node.pretty_debug(source)),
b::space(),
),
TokenNode::Delimited(delimited) => delimited.pretty_debug(source),
TokenNode::Pipeline(pipeline) => pipeline.pretty_debug(source),
TokenNode::Flag(flag) => flag.pretty_debug(source),
TokenNode::Whitespace(space) => b::typed(
"whitespace",
b::description(format!("{:?}", space.slice(source))),
),
TokenNode::Error(_) => b::error("error"),
}
}
}
impl HasSpan for TokenNode {
fn span(&self) -> Span {
self.get_span()
}
}
pub struct DebugTokenNode<'a> {
node: &'a TokenNode,
source: &'a Text,
}
impl fmt::Debug for DebugTokenNode<'_> {
fn fmt(&self, f: &mut fmt::Formatter) -> fmt::Result {
match self.node {
TokenNode::Token(t) => write!(f, "{:?}", t.debug(self.source)),
TokenNode::Call(s) => {
write!(f, "(")?;
write!(f, "{}", s.head().debug(self.source))?;
if let Some(children) = s.children() {
for child in children {
write!(f, "{}", child.debug(self.source))?;
}
}
write!(f, ")")
}
TokenNode::Delimited(d) => {
write!(
f,
"{}",
match d.delimiter {
Delimiter::Brace => "{",
Delimiter::Paren => "(",
Delimiter::Square => "[",
}
)?;
for child in d.children() {
write!(f, "{:?}", child.old_debug(self.source))?;
}
write!(
f,
"{}",
match d.delimiter {
Delimiter::Brace => "}",
Delimiter::Paren => ")",
Delimiter::Square => "]",
}
)
}
TokenNode::Pipeline(pipeline) => write!(f, "{}", pipeline.debug(self.source)),
TokenNode::Error(_) => write!(f, "<error>"),
rest => write!(f, "{}", rest.span().slice(self.source)),
}
}
}
impl From<&TokenNode> for Span {
fn from(token: &TokenNode) -> Span {
token.get_span()
}
}
impl TokenNode {
pub fn get_span(&self) -> Span {
match self {
TokenNode::Token(t) => t.span,
TokenNode::Nodes(t) => t.span,
TokenNode::Call(s) => s.span,
TokenNode::Delimited(s) => s.span,
TokenNode::Pipeline(s) => s.span,
TokenNode::Flag(s) => s.span,
TokenNode::Whitespace(s) => *s,
TokenNode::Error(s) => s.span,
}
}
pub fn type_name(&self) -> &'static str {
match self {
TokenNode::Token(t) => t.type_name(),
TokenNode::Nodes(_) => "nodes",
TokenNode::Call(_) => "command",
TokenNode::Delimited(d) => d.type_name(),
TokenNode::Pipeline(_) => "pipeline",
TokenNode::Flag(_) => "flag",
TokenNode::Whitespace(_) => "whitespace",
TokenNode::Error(_) => "error",
}
}
pub fn spanned_type_name(&self) -> Spanned<&'static str> {
self.type_name().spanned(self.span())
}
pub fn tagged_type_name(&self) -> Tagged<&'static str> {
self.type_name().tagged(self.span())
}
pub fn old_debug<'a>(&'a self, source: &'a Text) -> DebugTokenNode<'a> {
DebugTokenNode { node: self, source }
}
pub fn as_external_arg(&self, source: &Text) -> String {
self.span().slice(source).to_string()
}
pub fn source<'a>(&self, source: &'a Text) -> &'a str {
self.span().slice(source)
}
pub fn get_variable(&self) -> Result<(Span, Span), ShellError> {
match self {
TokenNode::Token(Token {
unspanned: UnspannedToken::Variable(inner_span),
span: outer_span,
}) => Ok((*outer_span, *inner_span)),
_ => Err(ShellError::type_error(
"variable",
self.type_name().spanned(self.span()),
)),
}
}
pub fn is_bare(&self) -> bool {
match self {
TokenNode::Token(Token {
unspanned: UnspannedToken::Bare,
..
}) => true,
_ => false,
}
}
pub fn is_string(&self) -> bool {
match self {
TokenNode::Token(Token {
unspanned: UnspannedToken::String(_),
..
}) => true,
_ => false,
}
}
pub fn is_number(&self) -> bool {
match self {
TokenNode::Token(Token {
unspanned: UnspannedToken::Number(_),
..
}) => true,
_ => false,
}
}
pub fn as_string(&self) -> Option<(Span, Span)> {
match self {
TokenNode::Token(Token {
unspanned: UnspannedToken::String(inner_span),
span: outer_span,
}) => Some((*outer_span, *inner_span)),
_ => None,
}
}
pub fn is_pattern(&self) -> bool {
match self {
TokenNode::Token(Token {
unspanned: UnspannedToken::GlobPattern,
..
}) => true,
_ => false,
}
}
pub fn is_word(&self) -> bool {
match self {
TokenNode::Token(Token {
unspanned: UnspannedToken::Bare,
..
}) => true,
_ => false,
}
}
pub fn is_int(&self) -> bool {
match self {
TokenNode::Token(Token {
unspanned: UnspannedToken::Number(RawNumber::Int(_)),
..
}) => true,
_ => false,
}
}
pub fn is_dot(&self) -> bool {
match self {
TokenNode::Token(Token {
unspanned: UnspannedToken::Operator(Operator::Dot),
..
}) => true,
_ => false,
}
}
pub fn as_block(&self) -> Option<(Spanned<&[TokenNode]>, (Span, Span))> {
match self {
TokenNode::Delimited(Spanned {
item:
DelimitedNode {
delimiter,
children,
spans,
},
span,
}) if *delimiter == Delimiter::Brace => Some(((&children[..]).spanned(*span), *spans)),
_ => None,
}
}
pub fn is_external(&self) -> bool {
match self {
TokenNode::Token(Token {
unspanned: UnspannedToken::ExternalCommand(..),
..
}) => true,
_ => false,
}
}
pub(crate) fn as_flag(&self, value: &str, source: &Text) -> Option<Flag> {
match self {
TokenNode::Flag(flag @ Flag { .. }) if value == flag.name().slice(source) => {
Some(*flag)
}
_ => None,
}
}
pub fn as_pipeline(&self) -> Result<Pipeline, ParseError> {
match self {
TokenNode::Pipeline(pipeline) => Ok(pipeline.clone()),
other => Err(ParseError::mismatch(
"pipeline",
other.type_name().spanned(other.span()),
)),
}
}
pub fn is_whitespace(&self) -> bool {
match self {
TokenNode::Whitespace(_) => true,
_ => false,
}
}
}
#[derive(Debug, Clone, Eq, PartialEq, Ord, PartialOrd, Getters, new)]
#[get = "pub(crate)"]
pub struct DelimitedNode {
pub(crate) delimiter: Delimiter,
pub(crate) spans: (Span, Span),
pub(crate) children: Vec<TokenNode>,
}
impl PrettyDebugWithSource for DelimitedNode {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
b::delimit(
self.delimiter.open(),
b::intersperse(
self.children.iter().map(|child| child.pretty_debug(source)),
b::space(),
),
self.delimiter.close(),
)
}
}
impl DelimitedNode {
pub fn type_name(&self) -> &'static str {
match self.delimiter {
Delimiter::Brace => "braced expression",
Delimiter::Paren => "parenthesized expression",
Delimiter::Square => "array literal or index operator",
}
}
}
#[derive(Debug, Copy, Clone, Eq, PartialEq, Ord, PartialOrd)]
pub enum Delimiter {
Paren,
Brace,
Square,
}
impl Delimiter {
pub(crate) fn open(&self) -> &'static str {
match self {
Delimiter::Paren => "(",
Delimiter::Brace => "{",
Delimiter::Square => "[",
}
}
pub(crate) fn close(&self) -> &'static str {
match self {
Delimiter::Paren => ")",
Delimiter::Brace => "}",
Delimiter::Square => "]",
}
}
}
#[derive(Debug, Clone, Eq, PartialEq, Ord, PartialOrd, Getters, new)]
#[get = "pub(crate)"]
pub struct PathNode {
head: Box<TokenNode>,
tail: Vec<TokenNode>,
}
#[cfg(test)]
impl TokenNode {
pub fn expect_external(&self) -> Span {
match self {
TokenNode::Token(Token {
unspanned: UnspannedToken::ExternalCommand(span),
..
}) => *span,
other => panic!(
"Only call expect_external if you checked is_external first, found {:?}",
other
),
}
}
pub fn expect_string(&self) -> (Span, Span) {
match self {
TokenNode::Token(Token {
unspanned: UnspannedToken::String(inner_span),
span: outer_span,
}) => (*outer_span, *inner_span),
other => panic!("Expected string, found {:?}", other),
}
}
pub fn expect_list(&self) -> Spanned<&[TokenNode]> {
match self {
TokenNode::Nodes(token_nodes) => token_nodes[..].spanned(token_nodes.span),
other => panic!("Expected list, found {:?}", other),
}
}
pub fn expect_pattern(&self) -> Span {
match self {
TokenNode::Token(Token {
unspanned: UnspannedToken::GlobPattern,
span: outer_span,
}) => *outer_span,
other => panic!("Expected pattern, found {:?}", other),
}
}
pub fn expect_var(&self) -> (Span, Span) {
match self {
TokenNode::Token(Token {
unspanned: UnspannedToken::Variable(inner_span),
span: outer_span,
}) => (*outer_span, *inner_span),
other => panic!("Expected var, found {:?}", other),
}
}
pub fn expect_dot(&self) -> Span {
match self {
TokenNode::Token(Token {
unspanned: UnspannedToken::Operator(Operator::Dot),
span,
}) => *span,
other => panic!("Expected dot, found {:?}", other),
}
}
pub fn expect_bare(&self) -> Span {
match self {
TokenNode::Token(Token {
unspanned: UnspannedToken::Bare,
span,
}) => *span,
other => panic!("Expected bare, found {:?}", other),
}
}
}

View File

@ -0,0 +1,414 @@
use crate::parse::call_node::CallNode;
use crate::parse::flag::{Flag, FlagKind};
use crate::parse::operator::Operator;
use crate::parse::pipeline::{Pipeline, PipelineElement};
use crate::parse::token_tree::{DelimitedNode, Delimiter, TokenNode};
use crate::parse::tokens::{RawNumber, UnspannedToken};
use bigdecimal::BigDecimal;
use nu_source::{Span, Spanned, SpannedItem};
use num_bigint::BigInt;
pub struct TokenTreeBuilder {
pos: usize,
output: String,
}
impl TokenTreeBuilder {
pub fn new() -> TokenTreeBuilder {
TokenTreeBuilder {
pos: 0,
output: String::new(),
}
}
}
pub type CurriedToken = Box<dyn FnOnce(&mut TokenTreeBuilder) -> TokenNode + 'static>;
pub type CurriedCall = Box<dyn FnOnce(&mut TokenTreeBuilder) -> Spanned<CallNode> + 'static>;
impl TokenTreeBuilder {
pub fn build(block: impl FnOnce(&mut Self) -> TokenNode) -> (TokenNode, String) {
let mut builder = TokenTreeBuilder::new();
let node = block(&mut builder);
(node, builder.output)
}
fn build_spanned<T>(
&mut self,
callback: impl FnOnce(&mut TokenTreeBuilder) -> T,
) -> Spanned<T> {
let start = self.pos;
let ret = callback(self);
let end = self.pos;
ret.spanned(Span::new(start, end))
}
pub fn pipeline(input: Vec<Vec<CurriedToken>>) -> CurriedToken {
Box::new(move |b| {
let start = b.pos;
let mut out: Vec<PipelineElement> = vec![];
let mut input = input.into_iter().peekable();
let head = input
.next()
.expect("A pipeline must contain at least one element");
let pipe = None;
let head = b.build_spanned(|b| head.into_iter().map(|node| node(b)).collect());
out.push(PipelineElement::new(pipe, head));
loop {
match input.next() {
None => break,
Some(node) => {
let pipe = Some(b.consume_span("|"));
let node =
b.build_spanned(|b| node.into_iter().map(|node| node(b)).collect());
out.push(PipelineElement::new(pipe, node));
}
}
}
let end = b.pos;
TokenTreeBuilder::spanned_pipeline(out, Span::new(start, end))
})
}
pub fn spanned_pipeline(input: Vec<PipelineElement>, span: impl Into<Span>) -> TokenNode {
TokenNode::Pipeline(Pipeline::new(input, span.into()))
}
pub fn token_list(input: Vec<CurriedToken>) -> CurriedToken {
Box::new(move |b| {
let start = b.pos;
let tokens = input.into_iter().map(|i| i(b)).collect();
let end = b.pos;
TokenTreeBuilder::spanned_token_list(tokens, Span::new(start, end))
})
}
pub fn spanned_token_list(input: Vec<TokenNode>, span: impl Into<Span>) -> TokenNode {
TokenNode::Nodes(input.spanned(span.into()))
}
pub fn op(input: impl Into<Operator>) -> CurriedToken {
let input = input.into();
Box::new(move |b| {
let (start, end) = b.consume(input.as_str());
b.pos = end;
TokenTreeBuilder::spanned_op(input, Span::new(start, end))
})
}
pub fn spanned_op(input: impl Into<Operator>, span: impl Into<Span>) -> TokenNode {
TokenNode::Token(UnspannedToken::Operator(input.into()).into_token(span))
}
pub fn string(input: impl Into<String>) -> CurriedToken {
let input = input.into();
Box::new(move |b| {
let (start, _) = b.consume("\"");
let (inner_start, inner_end) = b.consume(&input);
let (_, end) = b.consume("\"");
b.pos = end;
TokenTreeBuilder::spanned_string(
Span::new(inner_start, inner_end),
Span::new(start, end),
)
})
}
pub fn spanned_string(input: impl Into<Span>, span: impl Into<Span>) -> TokenNode {
TokenNode::Token(UnspannedToken::String(input.into()).into_token(span))
}
pub fn bare(input: impl Into<String>) -> CurriedToken {
let input = input.into();
Box::new(move |b| {
let (start, end) = b.consume(&input);
b.pos = end;
TokenTreeBuilder::spanned_bare(Span::new(start, end))
})
}
pub fn spanned_bare(span: impl Into<Span>) -> TokenNode {
TokenNode::Token(UnspannedToken::Bare.into_token(span))
}
pub fn pattern(input: impl Into<String>) -> CurriedToken {
let input = input.into();
Box::new(move |b| {
let (start, end) = b.consume(&input);
b.pos = end;
TokenTreeBuilder::spanned_pattern(Span::new(start, end))
})
}
pub fn spanned_pattern(input: impl Into<Span>) -> TokenNode {
TokenNode::Token(UnspannedToken::GlobPattern.into_token(input))
}
pub fn external_word(input: impl Into<String>) -> CurriedToken {
let input = input.into();
Box::new(move |b| {
let (start, end) = b.consume(&input);
b.pos = end;
TokenTreeBuilder::spanned_external_word(Span::new(start, end))
})
}
pub fn spanned_external_word(input: impl Into<Span>) -> TokenNode {
TokenNode::Token(UnspannedToken::ExternalWord.into_token(input))
}
pub fn external_command(input: impl Into<String>) -> CurriedToken {
let input = input.into();
Box::new(move |b| {
let (outer_start, _) = b.consume("^");
let (inner_start, end) = b.consume(&input);
b.pos = end;
TokenTreeBuilder::spanned_external_command(
Span::new(inner_start, end),
Span::new(outer_start, end),
)
})
}
pub fn spanned_external_command(inner: impl Into<Span>, outer: impl Into<Span>) -> TokenNode {
TokenNode::Token(UnspannedToken::ExternalCommand(inner.into()).into_token(outer))
}
pub fn int(input: impl Into<BigInt>) -> CurriedToken {
let int = input.into();
Box::new(move |b| {
let (start, end) = b.consume(&int.to_string());
b.pos = end;
TokenTreeBuilder::spanned_number(
RawNumber::Int(Span::new(start, end)),
Span::new(start, end),
)
})
}
pub fn decimal(input: impl Into<BigDecimal>) -> CurriedToken {
let decimal = input.into();
Box::new(move |b| {
let (start, end) = b.consume(&decimal.to_string());
b.pos = end;
TokenTreeBuilder::spanned_number(
RawNumber::Decimal(Span::new(start, end)),
Span::new(start, end),
)
})
}
pub fn spanned_number(input: impl Into<RawNumber>, span: impl Into<Span>) -> TokenNode {
TokenNode::Token(UnspannedToken::Number(input.into()).into_token(span))
}
pub fn var(input: impl Into<String>) -> CurriedToken {
let input = input.into();
Box::new(move |b| {
let (start, _) = b.consume("$");
let (inner_start, end) = b.consume(&input);
TokenTreeBuilder::spanned_var(Span::new(inner_start, end), Span::new(start, end))
})
}
pub fn spanned_var(input: impl Into<Span>, span: impl Into<Span>) -> TokenNode {
TokenNode::Token(UnspannedToken::Variable(input.into()).into_token(span))
}
pub fn flag(input: impl Into<String>) -> CurriedToken {
let input = input.into();
Box::new(move |b| {
let (start, _) = b.consume("--");
let (inner_start, end) = b.consume(&input);
TokenTreeBuilder::spanned_flag(Span::new(inner_start, end), Span::new(start, end))
})
}
pub fn spanned_flag(input: impl Into<Span>, span: impl Into<Span>) -> TokenNode {
TokenNode::Flag(Flag::new(FlagKind::Longhand, input.into(), span.into()))
}
pub fn shorthand(input: impl Into<String>) -> CurriedToken {
let input = input.into();
Box::new(move |b| {
let (start, _) = b.consume("-");
let (inner_start, end) = b.consume(&input);
TokenTreeBuilder::spanned_shorthand((inner_start, end), (start, end))
})
}
pub fn spanned_shorthand(input: impl Into<Span>, span: impl Into<Span>) -> TokenNode {
TokenNode::Flag(Flag::new(FlagKind::Shorthand, input.into(), span.into()))
}
pub fn call(head: CurriedToken, input: Vec<CurriedToken>) -> CurriedCall {
Box::new(move |b| {
let start = b.pos;
let head_node = head(b);
let mut nodes = vec![head_node];
for item in input {
nodes.push(item(b));
}
let end = b.pos;
TokenTreeBuilder::spanned_call(nodes, Span::new(start, end))
})
}
pub fn spanned_call(input: Vec<TokenNode>, span: impl Into<Span>) -> Spanned<CallNode> {
if input.len() == 0 {
panic!("BUG: spanned call (TODO)")
}
let mut input = input.into_iter();
let head = input.next().unwrap();
let tail = input.collect();
CallNode::new(Box::new(head), tail).spanned(span.into())
}
fn consume_delimiter(
&mut self,
input: Vec<CurriedToken>,
_open: &str,
_close: &str,
) -> (Span, Span, Span, Vec<TokenNode>) {
let (start_open_paren, end_open_paren) = self.consume("(");
let mut output = vec![];
for item in input {
output.push(item(self));
}
let (start_close_paren, end_close_paren) = self.consume(")");
let open = Span::new(start_open_paren, end_open_paren);
let close = Span::new(start_close_paren, end_close_paren);
let whole = Span::new(start_open_paren, end_close_paren);
(open, close, whole, output)
}
pub fn parens(input: Vec<CurriedToken>) -> CurriedToken {
Box::new(move |b| {
let (open, close, whole, output) = b.consume_delimiter(input, "(", ")");
TokenTreeBuilder::spanned_parens(output, (open, close), whole)
})
}
pub fn spanned_parens(
input: impl Into<Vec<TokenNode>>,
spans: (Span, Span),
span: impl Into<Span>,
) -> TokenNode {
TokenNode::Delimited(
DelimitedNode::new(Delimiter::Paren, spans, input.into()).spanned(span.into()),
)
}
pub fn square(input: Vec<CurriedToken>) -> CurriedToken {
Box::new(move |b| {
let (open, close, whole, tokens) = b.consume_delimiter(input, "[", "]");
TokenTreeBuilder::spanned_square(tokens, (open, close), whole)
})
}
pub fn spanned_square(
input: impl Into<Vec<TokenNode>>,
spans: (Span, Span),
span: impl Into<Span>,
) -> TokenNode {
TokenNode::Delimited(
DelimitedNode::new(Delimiter::Square, spans, input.into()).spanned(span.into()),
)
}
pub fn braced(input: Vec<CurriedToken>) -> CurriedToken {
Box::new(move |b| {
let (open, close, whole, tokens) = b.consume_delimiter(input, "{", "}");
TokenTreeBuilder::spanned_brace(tokens, (open, close), whole)
})
}
pub fn spanned_brace(
input: impl Into<Vec<TokenNode>>,
spans: (Span, Span),
span: impl Into<Span>,
) -> TokenNode {
TokenNode::Delimited(
DelimitedNode::new(Delimiter::Brace, spans, input.into()).spanned(span.into()),
)
}
pub fn sp() -> CurriedToken {
Box::new(|b| {
let (start, end) = b.consume(" ");
TokenNode::Whitespace(Span::new(start, end))
})
}
pub fn ws(input: impl Into<String>) -> CurriedToken {
let input = input.into();
Box::new(move |b| {
let (start, end) = b.consume(&input);
TokenTreeBuilder::spanned_ws(Span::new(start, end))
})
}
pub fn spanned_ws(span: impl Into<Span>) -> TokenNode {
TokenNode::Whitespace(span.into())
}
fn consume(&mut self, input: &str) -> (usize, usize) {
let start = self.pos;
self.pos += input.len();
self.output.push_str(input);
(start, self.pos)
}
fn consume_span(&mut self, input: &str) -> Span {
let start = self.pos;
self.pos += input.len();
self.output.push_str(input);
Span::new(start, self.pos)
}
}

View File

@ -0,0 +1,217 @@
use crate::parse::parser::Number;
use crate::Operator;
use bigdecimal::BigDecimal;
use nu_protocol::ShellTypeName;
use nu_source::{
b, DebugDocBuilder, HasSpan, PrettyDebug, PrettyDebugWithSource, Span, Spanned, SpannedItem,
Text,
};
use num_bigint::BigInt;
use std::fmt;
use std::str::FromStr;
#[derive(Debug, Clone, Copy, Eq, PartialEq, Ord, PartialOrd, Hash)]
pub enum UnspannedToken {
Number(RawNumber),
Operator(Operator),
String(Span),
Variable(Span),
ExternalCommand(Span),
ExternalWord,
GlobPattern,
Bare,
}
impl UnspannedToken {
pub fn into_token(self, span: impl Into<Span>) -> Token {
Token {
unspanned: self,
span: span.into(),
}
}
}
impl ShellTypeName for UnspannedToken {
fn type_name(&self) -> &'static str {
match self {
UnspannedToken::Number(_) => "number",
UnspannedToken::Operator(..) => "operator",
UnspannedToken::String(_) => "string",
UnspannedToken::Variable(_) => "variable",
UnspannedToken::ExternalCommand(_) => "syntax error",
UnspannedToken::ExternalWord => "syntax error",
UnspannedToken::GlobPattern => "glob pattern",
UnspannedToken::Bare => "string",
}
}
}
#[derive(Debug, Clone, Copy, Eq, PartialEq, Ord, PartialOrd, Hash)]
pub enum RawNumber {
Int(Span),
Decimal(Span),
}
impl HasSpan for RawNumber {
fn span(&self) -> Span {
match self {
RawNumber::Int(span) => *span,
RawNumber::Decimal(span) => *span,
}
}
}
impl PrettyDebugWithSource for RawNumber {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
match self {
RawNumber::Int(span) => b::primitive(span.slice(source)),
RawNumber::Decimal(span) => b::primitive(span.slice(source)),
}
}
}
impl RawNumber {
pub fn int(span: impl Into<Span>) -> RawNumber {
let span = span.into();
RawNumber::Int(span)
}
pub fn decimal(span: impl Into<Span>) -> RawNumber {
let span = span.into();
RawNumber::Decimal(span)
}
pub(crate) fn to_number(self, source: &Text) -> Number {
match self {
RawNumber::Int(tag) => Number::Int(BigInt::from_str(tag.slice(source)).unwrap()),
RawNumber::Decimal(tag) => {
Number::Decimal(BigDecimal::from_str(tag.slice(source)).unwrap())
}
}
}
}
#[derive(Debug, Clone, Copy, Eq, PartialEq, Ord, PartialOrd, Hash)]
pub struct Token {
pub unspanned: UnspannedToken,
pub span: Span,
}
impl std::ops::Deref for Token {
type Target = UnspannedToken;
fn deref(&self) -> &UnspannedToken {
&self.unspanned
}
}
impl PrettyDebugWithSource for Token {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
match self.unspanned {
UnspannedToken::Number(number) => number.pretty_debug(source),
UnspannedToken::Operator(operator) => operator.pretty(),
UnspannedToken::String(_) => b::primitive(self.span.slice(source)),
UnspannedToken::Variable(_) => b::var(self.span.slice(source)),
UnspannedToken::ExternalCommand(_) => b::primitive(self.span.slice(source)),
UnspannedToken::ExternalWord => {
b::typed("external", b::description(self.span.slice(source)))
}
UnspannedToken::GlobPattern => {
b::typed("pattern", b::description(self.span.slice(source)))
}
UnspannedToken::Bare => b::primitive(self.span.slice(source)),
}
}
}
impl Token {
pub fn debug<'a>(&self, source: &'a Text) -> DebugToken<'a> {
DebugToken {
node: *self,
source,
}
}
pub fn extract_number(&self) -> Option<RawNumber> {
match self.unspanned {
UnspannedToken::Number(number) => Some(number),
_ => None,
}
}
pub fn extract_int(&self) -> Option<(Span, Span)> {
match self.unspanned {
UnspannedToken::Number(RawNumber::Int(int)) => Some((int, self.span)),
_ => None,
}
}
pub fn extract_decimal(&self) -> Option<(Span, Span)> {
match self.unspanned {
UnspannedToken::Number(RawNumber::Decimal(decimal)) => Some((decimal, self.span)),
_ => None,
}
}
pub fn extract_operator(&self) -> Option<Spanned<Operator>> {
match self.unspanned {
UnspannedToken::Operator(operator) => Some(operator.spanned(self.span)),
_ => None,
}
}
pub fn extract_string(&self) -> Option<(Span, Span)> {
match self.unspanned {
UnspannedToken::String(span) => Some((span, self.span)),
_ => None,
}
}
pub fn extract_variable(&self) -> Option<(Span, Span)> {
match self.unspanned {
UnspannedToken::Variable(span) => Some((span, self.span)),
_ => None,
}
}
pub fn extract_external_command(&self) -> Option<(Span, Span)> {
match self.unspanned {
UnspannedToken::ExternalCommand(span) => Some((span, self.span)),
_ => None,
}
}
pub fn extract_external_word(&self) -> Option<Span> {
match self.unspanned {
UnspannedToken::ExternalWord => Some(self.span),
_ => None,
}
}
pub fn extract_glob_pattern(&self) -> Option<Span> {
match self.unspanned {
UnspannedToken::GlobPattern => Some(self.span),
_ => None,
}
}
pub fn extract_bare(&self) -> Option<Span> {
match self.unspanned {
UnspannedToken::Bare => Some(self.span),
_ => None,
}
}
}
pub struct DebugToken<'a> {
node: Token,
source: &'a Text,
}
impl fmt::Debug for DebugToken<'_> {
fn fmt(&self, f: &mut fmt::Formatter) -> fmt::Result {
write!(f, "{}", self.node.span.slice(self.source))
}
}

View File

@ -0,0 +1,115 @@
use crate::parse::parser::Number;
use nu_protocol::{Primitive, UntaggedValue};
use nu_source::{b, DebugDocBuilder, PrettyDebug};
use num_traits::ToPrimitive;
use serde::{Deserialize, Serialize};
use std::str::FromStr;
#[derive(Debug, Clone, Copy, PartialEq, Eq, PartialOrd, Ord, Hash, Deserialize, Serialize)]
pub enum Unit {
// Filesize units
Byte,
Kilobyte,
Megabyte,
Gigabyte,
Terabyte,
Petabyte,
// Duration units
Second,
Minute,
Hour,
Day,
Week,
Month,
Year,
}
impl PrettyDebug for Unit {
fn pretty(&self) -> DebugDocBuilder {
b::keyword(self.as_str())
}
}
fn convert_number_to_u64(number: &Number) -> u64 {
match number {
Number::Int(big_int) => big_int.to_u64().unwrap(),
Number::Decimal(big_decimal) => big_decimal.to_u64().unwrap(),
}
}
impl Unit {
pub fn as_str(&self) -> &str {
match *self {
Unit::Byte => "B",
Unit::Kilobyte => "KB",
Unit::Megabyte => "MB",
Unit::Gigabyte => "GB",
Unit::Terabyte => "TB",
Unit::Petabyte => "PB",
Unit::Second => "s",
Unit::Minute => "m",
Unit::Hour => "h",
Unit::Day => "d",
Unit::Week => "w",
Unit::Month => "M",
Unit::Year => "y",
}
}
pub fn compute(&self, size: &Number) -> UntaggedValue {
let size = size.clone();
match &self {
Unit::Byte => number(size),
Unit::Kilobyte => number(size * 1024),
Unit::Megabyte => number(size * 1024 * 1024),
Unit::Gigabyte => number(size * 1024 * 1024 * 1024),
Unit::Terabyte => number(size * 1024 * 1024 * 1024 * 1024),
Unit::Petabyte => number(size * 1024 * 1024 * 1024 * 1024 * 1024),
Unit::Second => duration(convert_number_to_u64(&size)),
Unit::Minute => duration(60 * convert_number_to_u64(&size)),
Unit::Hour => duration(60 * 60 * convert_number_to_u64(&size)),
Unit::Day => duration(24 * 60 * 60 * convert_number_to_u64(&size)),
Unit::Week => duration(7 * 24 * 60 * 60 * convert_number_to_u64(&size)),
Unit::Month => duration(30 * 24 * 60 * 60 * convert_number_to_u64(&size)),
Unit::Year => duration(365 * 24 * 60 * 60 * convert_number_to_u64(&size)),
}
}
}
fn number(number: impl Into<Number>) -> UntaggedValue {
let number = number.into();
match number {
Number::Int(int) => UntaggedValue::Primitive(Primitive::Int(int)),
Number::Decimal(decimal) => UntaggedValue::Primitive(Primitive::Decimal(decimal)),
}
}
pub fn duration(secs: u64) -> UntaggedValue {
UntaggedValue::Primitive(Primitive::Duration(secs))
}
impl FromStr for Unit {
type Err = ();
fn from_str(input: &str) -> Result<Self, <Self as std::str::FromStr>::Err> {
match input {
"B" | "b" => Ok(Unit::Byte),
"KB" | "kb" | "Kb" | "K" | "k" => Ok(Unit::Kilobyte),
"MB" | "mb" | "Mb" => Ok(Unit::Megabyte),
"GB" | "gb" | "Gb" => Ok(Unit::Gigabyte),
"TB" | "tb" | "Tb" => Ok(Unit::Terabyte),
"PB" | "pb" | "Pb" => Ok(Unit::Petabyte),
"s" => Ok(Unit::Second),
"m" => Ok(Unit::Minute),
"h" => Ok(Unit::Hour),
"d" => Ok(Unit::Day),
"w" => Ok(Unit::Week),
"M" => Ok(Unit::Month),
"y" => Ok(Unit::Year),
_ => Err(()),
}
}
}

View File

@ -0,0 +1 @@

View File

@ -0,0 +1,615 @@
use crate::hir::syntax_shape::{
color_fallible_syntax, color_syntax, expand_expr, flat_shape::FlatShape, spaced,
BackoffColoringMode, ColorSyntax, MaybeSpaceShape,
};
use crate::TokensIterator;
use crate::{
hir::{self, ExpandContext, NamedArguments},
Flag,
};
use log::trace;
use nu_source::{PrettyDebugWithSource, Span, Spanned, SpannedItem, Text};
use nu_errors::{ArgumentError, ParseError};
use nu_protocol::{NamedType, PositionalType, Signature};
pub fn parse_command_tail(
config: &Signature,
context: &ExpandContext,
tail: &mut TokensIterator,
command_span: Span,
) -> Result<Option<(Option<Vec<hir::Expression>>, Option<NamedArguments>)>, ParseError> {
let mut named = NamedArguments::new();
trace_remaining("nodes", &tail, context.source());
for (name, kind) in &config.named {
trace!(target: "nu::parse", "looking for {} : {:?}", name, kind);
match &kind.0 {
NamedType::Switch => {
let flag = extract_switch(name, tail, context.source());
named.insert_switch(name, flag);
}
NamedType::Mandatory(syntax_type) => {
match extract_mandatory(config, name, tail, context.source(), command_span) {
Err(err) => return Err(err), // produce a correct diagnostic
Ok((pos, flag)) => {
tail.move_to(pos);
if tail.at_end() {
return Err(ParseError::argument_error(
config.name.clone().spanned(flag.span),
ArgumentError::MissingValueForName(name.to_string()),
));
}
let expr = expand_expr(&spaced(*syntax_type), tail, context)?;
tail.restart();
named.insert_mandatory(name, expr);
}
}
}
NamedType::Optional(syntax_type) => {
match extract_optional(name, tail, context.source()) {
Err(err) => return Err(err), // produce a correct diagnostic
Ok(Some((pos, flag))) => {
tail.move_to(pos);
if tail.at_end() {
return Err(ParseError::argument_error(
config.name.clone().spanned(flag.span),
ArgumentError::MissingValueForName(name.to_string()),
));
}
let expr = expand_expr(&spaced(*syntax_type), tail, context);
match expr {
Err(_) => named.insert_optional(name, None),
Ok(expr) => named.insert_optional(name, Some(expr)),
}
tail.restart();
}
Ok(None) => {
tail.restart();
named.insert_optional(name, None);
}
}
}
};
}
trace_remaining("after named", &tail, context.source());
let mut positional = vec![];
for arg in &config.positional {
trace!(target: "nu::parse", "Processing positional {:?}", arg);
match &arg.0 {
PositionalType::Mandatory(..) => {
if tail.at_end_possible_ws() {
return Err(ParseError::argument_error(
config.name.clone().spanned(command_span),
ArgumentError::MissingMandatoryPositional(arg.0.name().to_string()),
));
}
}
PositionalType::Optional(..) => {
if tail.at_end_possible_ws() {
break;
}
}
}
let result = expand_expr(&spaced(arg.0.syntax_type()), tail, context)?;
positional.push(result);
}
trace_remaining("after positional", &tail, context.source());
if let Some((syntax_type, _)) = config.rest_positional {
let mut out = vec![];
loop {
if tail.at_end_possible_ws() {
break;
}
let next = expand_expr(&spaced(syntax_type), tail, context)?;
out.push(next);
}
positional.extend(out);
}
trace_remaining("after rest", &tail, context.source());
trace!(target: "nu::parse", "Constructed positional={:?} named={:?}", positional, named);
let positional = if positional.len() == 0 {
None
} else {
Some(positional)
};
// TODO: Error if extra unconsumed positional arguments
let named = if named.named.is_empty() {
None
} else {
Some(named)
};
trace!(target: "nu::parse", "Normalized positional={:?} named={:?}", positional, named);
Ok(Some((positional, named)))
}
#[derive(Debug)]
struct ColoringArgs {
vec: Vec<Option<Vec<Spanned<FlatShape>>>>,
}
impl ColoringArgs {
fn new(len: usize) -> ColoringArgs {
let vec = vec![None; len];
ColoringArgs { vec }
}
fn insert(&mut self, pos: usize, shapes: Vec<Spanned<FlatShape>>) {
self.vec[pos] = Some(shapes);
}
fn spread_shapes(self, shapes: &mut Vec<Spanned<FlatShape>>) {
for item in self.vec {
match item {
None => {}
Some(vec) => {
shapes.extend(vec);
}
}
}
}
}
#[derive(Debug, Copy, Clone)]
pub struct CommandTailShape;
#[cfg(not(coloring_in_tokens))]
impl ColorSyntax for CommandTailShape {
type Info = ();
type Input = Signature;
fn color_syntax<'a, 'b>(
&self,
signature: &Signature,
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
shapes: &mut Vec<Spanned<FlatShape>>,
) -> Self::Info {
let mut args = ColoringArgs::new(token_nodes.len());
for (name, kind) in &signature.named {
trace!(target: "nu::color_syntax", "looking for {} : {:?}", name, kind);
match &kind.0 {
NamedType::Switch => {
match token_nodes.extract(|t| t.as_flag(name, context.source())) {
Some((pos, flag)) => args.insert(pos, vec![flag.color()]),
None => {}
}
}
NamedType::Mandatory(syntax_type) => {
match extract_mandatory(
signature,
name,
token_nodes,
context.source(),
Span::unknown(),
) {
Err(_) => {
// The mandatory flag didn't exist at all, so there's nothing to color
}
Ok((pos, flag)) => {
let mut shapes = vec![flag.color()];
token_nodes.move_to(pos);
if token_nodes.at_end() {
args.insert(pos, shapes);
token_nodes.restart();
continue;
}
// We can live with unmatched syntax after a mandatory flag
let _ = token_nodes.atomic(|token_nodes| {
color_syntax(&MaybeSpaceShape, token_nodes, context, &mut shapes);
// If the part after a mandatory flag isn't present, that's ok, but we
// should roll back any whitespace we chomped
color_fallible_syntax(
syntax_type,
token_nodes,
context,
&mut shapes,
)
});
args.insert(pos, shapes);
token_nodes.restart();
}
}
}
NamedType::Optional(syntax_type) => {
match extract_optional(name, token_nodes, context.source()) {
Err(_) => {
// The optional flag didn't exist at all, so there's nothing to color
}
Ok(Some((pos, flag))) => {
let mut shapes = vec![flag.color()];
token_nodes.move_to(pos);
if token_nodes.at_end() {
args.insert(pos, shapes);
token_nodes.restart();
continue;
}
// We can live with unmatched syntax after an optional flag
let _ = token_nodes.atomic(|token_nodes| {
color_syntax(&MaybeSpaceShape, token_nodes, context, &mut shapes);
// If the part after a mandatory flag isn't present, that's ok, but we
// should roll back any whitespace we chomped
color_fallible_syntax(
syntax_type,
token_nodes,
context,
&mut shapes,
)
});
args.insert(pos, shapes);
token_nodes.restart();
}
Ok(None) => {
token_nodes.restart();
}
}
}
};
}
for arg in &signature.positional {
trace!("Processing positional {:?}", arg);
match arg.0 {
PositionalType::Mandatory(..) => {
if token_nodes.at_end() {
break;
}
}
PositionalType::Optional(..) => {
if token_nodes.at_end() {
break;
}
}
}
let mut shapes = vec![];
let pos = token_nodes.pos(false);
match pos {
None => break,
Some(pos) => {
// We can live with an unmatched positional argument. Hopefully it will be
// matched by a future token
let _ = token_nodes.atomic(|token_nodes| {
color_syntax(&MaybeSpaceShape, token_nodes, context, &mut shapes);
// If no match, we should roll back any whitespace we chomped
color_fallible_syntax(
&arg.0.syntax_type(),
token_nodes,
context,
&mut shapes,
)?;
args.insert(pos, shapes);
Ok(())
});
}
}
}
if let Some((syntax_type, _)) = signature.rest_positional {
loop {
if token_nodes.at_end_possible_ws() {
break;
}
let pos = token_nodes.pos(false);
match pos {
None => break,
Some(pos) => {
let mut shapes = vec![];
// If any arguments don't match, we'll fall back to backoff coloring mode
let result = token_nodes.atomic(|token_nodes| {
color_syntax(&MaybeSpaceShape, token_nodes, context, &mut shapes);
// If no match, we should roll back any whitespace we chomped
color_fallible_syntax(&syntax_type, token_nodes, context, &mut shapes)?;
args.insert(pos, shapes);
Ok(())
});
match result {
Err(_) => break,
Ok(_) => continue,
}
}
}
}
}
args.spread_shapes(shapes);
// Consume any remaining tokens with backoff coloring mode
color_syntax(&BackoffColoringMode, token_nodes, context, shapes);
shapes.sort_by(|a, b| a.span.start().cmp(&b.span.start()));
}
}
#[cfg(coloring_in_tokens)]
impl ColorSyntax for CommandTailShape {
type Info = ();
type Input = Signature;
fn name(&self) -> &'static str {
"CommandTailShape"
}
fn color_syntax<'a, 'b>(
&self,
signature: &Signature,
token_nodes: &'b mut TokensIterator<'a>,
context: &ExpandContext,
) -> Self::Info {
use nu_protocol::SyntaxShape;
let mut args = ColoringArgs::new(token_nodes.len());
trace_remaining("nodes", &token_nodes, context.source());
fn insert_flag(
token_nodes: &mut TokensIterator,
syntax_type: &SyntaxShape,
args: &mut ColoringArgs,
flag: Flag,
pos: usize,
context: &ExpandContext,
) {
let (_, shapes) = token_nodes.atomic_returning_shapes(|token_nodes| {
token_nodes.color_shape(flag.color());
token_nodes.move_to(pos);
if token_nodes.at_end() {
return Ok(());
}
// We still want to color the flag even if the following tokens don't match, so don't
// propagate the error to the parent atomic block if it fails
let _ = token_nodes.atomic(|token_nodes| {
// We can live with unmatched syntax after a mandatory flag
color_syntax(&MaybeSpaceShape, token_nodes, context);
// If the part after a mandatory flag isn't present, that's ok, but we
// should roll back any whitespace we chomped
color_fallible_syntax(syntax_type, token_nodes, context)?;
Ok(())
});
Ok(())
});
args.insert(pos, shapes);
token_nodes.restart();
}
for (name, kind) in &signature.named {
trace!(target: "nu::color_syntax", "looking for {} : {:?}", name, kind);
match &kind.0 {
NamedType::Switch => {
match token_nodes.extract(|t| t.as_flag(name, context.source())) {
Some((pos, flag)) => args.insert(pos, vec![flag.color()]),
None => {}
}
}
NamedType::Mandatory(syntax_type) => {
match extract_mandatory(
signature,
name,
token_nodes,
context.source(),
Span::unknown(),
) {
Err(_) => {
// The mandatory flag didn't exist at all, so there's nothing to color
}
Ok((pos, flag)) => {
insert_flag(token_nodes, syntax_type, &mut args, flag, pos, context)
}
}
}
NamedType::Optional(syntax_type) => {
match extract_optional(name, token_nodes, context.source()) {
Err(_) => {
// The optional flag didn't exist at all, so there's nothing to color
}
Ok(Some((pos, flag))) => {
insert_flag(token_nodes, syntax_type, &mut args, flag, pos, context)
}
Ok(None) => {
token_nodes.restart();
}
}
}
};
}
trace_remaining("after named", &token_nodes, context.source());
for arg in &signature.positional {
trace!("Processing positional {:?}", arg);
match &arg.0 {
PositionalType::Mandatory(..) => {
if token_nodes.at_end() {
break;
}
}
PositionalType::Optional(..) => {
if token_nodes.at_end() {
break;
}
}
}
let pos = token_nodes.pos(false);
match pos {
None => break,
Some(pos) => {
// We can live with an unmatched positional argument. Hopefully it will be
// matched by a future token
let (_, shapes) = token_nodes.atomic_returning_shapes(|token_nodes| {
color_syntax(&MaybeSpaceShape, token_nodes, context);
// If no match, we should roll back any whitespace we chomped
color_fallible_syntax(&arg.0.syntax_type(), token_nodes, context)?;
Ok(())
});
args.insert(pos, shapes);
}
}
}
trace_remaining("after positional", &token_nodes, context.source());
if let Some((syntax_type, _)) = signature.rest_positional {
loop {
if token_nodes.at_end_possible_ws() {
break;
}
let pos = token_nodes.pos(false);
match pos {
None => break,
Some(pos) => {
// If any arguments don't match, we'll fall back to backoff coloring mode
let (result, shapes) = token_nodes.atomic_returning_shapes(|token_nodes| {
color_syntax(&MaybeSpaceShape, token_nodes, context);
// If no match, we should roll back any whitespace we chomped
color_fallible_syntax(&syntax_type, token_nodes, context)?;
Ok(())
});
args.insert(pos, shapes);
match result {
Err(_) => break,
Ok(_) => continue,
}
}
}
}
}
token_nodes.silently_mutate_shapes(|shapes| args.spread_shapes(shapes));
// Consume any remaining tokens with backoff coloring mode
color_syntax(&BackoffColoringMode, token_nodes, context);
// This is pretty dubious, but it works. We should look into a better algorithm that doesn't end up requiring
// this solution.
token_nodes.sort_shapes()
}
}
fn extract_switch(name: &str, tokens: &mut hir::TokensIterator<'_>, source: &Text) -> Option<Flag> {
tokens.extract(|t| t.as_flag(name, source)).map(|f| f.1)
}
fn extract_mandatory(
config: &Signature,
name: &str,
tokens: &mut hir::TokensIterator<'_>,
source: &Text,
span: Span,
) -> Result<(usize, Flag), ParseError> {
let flag = tokens.extract(|t| t.as_flag(name, source));
match flag {
None => Err(ParseError::argument_error(
config.name.clone().spanned(span),
ArgumentError::MissingMandatoryFlag(name.to_string()),
)),
Some((pos, flag)) => {
tokens.remove(pos);
Ok((pos, flag))
}
}
}
fn extract_optional(
name: &str,
tokens: &mut hir::TokensIterator<'_>,
source: &Text,
) -> Result<Option<(usize, Flag)>, ParseError> {
let flag = tokens.extract(|t| t.as_flag(name, source));
match flag {
None => Ok(None),
Some((pos, flag)) => {
tokens.remove(pos);
Ok(Some((pos, flag)))
}
}
}
pub fn trace_remaining(desc: &'static str, tail: &hir::TokensIterator<'_>, source: &Text) {
trace!(
target: "nu::parse",
"{} = {:?}",
desc,
itertools::join(
tail.debug_remaining()
.iter()
.map(|i| format!("%{}%", i.debug(source))),
" "
)
);
}

View File

@ -0,0 +1,35 @@
[package]
name = "nu-protocol"
version = "0.1.0"
authors = ["Yehuda Katz <wycats@gmail.com>"]
edition = "2018"
# See more keys and their definitions at https://doc.rust-lang.org/cargo/reference/manifest.html
[dependencies]
nu-source = { path = "../nu-source" }
nu-errors = { path = "../nu-errors" }
serde = { version = "1.0.102", features = ["derive"] }
indexmap = { version = "1.3.0", features = ["serde-1"] }
num-bigint = { version = "0.2.3", features = ["serde"] }
bigdecimal = { version = "0.1.0", features = ["serde"] }
chrono = { version = "0.4.9", features = ["serde"] }
num-traits = "0.2.8"
serde_bytes = "0.11.2"
getset = "0.0.9"
derive-new = "0.5.8"
ansi_term = "0.12.1"
language-reporting = "0.4.0"
nom = "5.0.1"
nom_locate = "1.0.0"
nom-tracable = "0.4.1"
typetag = "0.1.4"
query_interface = "0.3.5"
# implement conversions
subprocess = "0.1.18"
serde_yaml = "0.8"
toml = "0.5.5"
serde_json = "1.0.41"

View File

@ -0,0 +1,93 @@
use nu_errors::ShellError;
use crate::value::Value;
use derive_new::new;
use indexmap::IndexMap;
use nu_source::Tag;
use serde::{Deserialize, Serialize};
#[derive(Deserialize, Serialize, Debug, Clone)]
pub struct CallInfo {
pub args: EvaluatedArgs,
pub name_tag: Tag,
}
#[derive(Debug, Default, new, Serialize, Deserialize, Clone)]
pub struct EvaluatedArgs {
pub positional: Option<Vec<Value>>,
pub named: Option<IndexMap<String, Value>>,
}
impl EvaluatedArgs {
pub fn slice_from(&self, from: usize) -> Vec<Value> {
let positional = &self.positional;
match positional {
None => vec![],
Some(list) => list[from..].to_vec(),
}
}
pub fn nth(&self, pos: usize) -> Option<&Value> {
match &self.positional {
None => None,
Some(array) => array.iter().nth(pos),
}
}
pub fn expect_nth(&self, pos: usize) -> Result<&Value, ShellError> {
match &self.positional {
None => Err(ShellError::unimplemented("Better error: expect_nth")),
Some(array) => match array.iter().nth(pos) {
None => Err(ShellError::unimplemented("Better error: expect_nth")),
Some(item) => Ok(item),
},
}
}
pub fn len(&self) -> usize {
match &self.positional {
None => 0,
Some(array) => array.len(),
}
}
pub fn has(&self, name: &str) -> bool {
match &self.named {
None => false,
Some(named) => named.contains_key(name),
}
}
pub fn get(&self, name: &str) -> Option<&Value> {
match &self.named {
None => None,
Some(named) => named.get(name),
}
}
pub fn positional_iter(&self) -> PositionalIter<'_> {
match &self.positional {
None => PositionalIter::Empty,
Some(v) => {
let iter = v.iter();
PositionalIter::Array(iter)
}
}
}
}
pub enum PositionalIter<'a> {
Empty,
Array(std::slice::Iter<'a, Value>),
}
impl<'a> Iterator for PositionalIter<'a> {
type Item = &'a Value;
fn next(&mut self) -> Option<Self::Item> {
match self {
PositionalIter::Empty => None,
PositionalIter::Array(iter) => iter.next(),
}
}
}

View File

@ -0,0 +1,24 @@
#[macro_use]
mod macros;
mod call_info;
mod maybe_owned;
mod plugin;
mod return_value;
mod signature;
mod syntax_shape;
mod type_name;
mod value;
pub use crate::call_info::{CallInfo, EvaluatedArgs};
pub use crate::maybe_owned::MaybeOwned;
pub use crate::plugin::{serve_plugin, Plugin};
pub use crate::return_value::{CommandAction, ReturnSuccess, ReturnValue};
pub use crate::signature::{NamedType, PositionalType, Signature};
pub use crate::syntax_shape::SyntaxShape;
pub use crate::type_name::{PrettyType, ShellTypeName, SpannedTypeName};
pub use crate::value::column_path::{ColumnPath, PathMember, UnspannedPathMember};
pub use crate::value::dict::Dictionary;
pub use crate::value::evaluate::{Evaluate, EvaluateTrait, Scope};
pub use crate::value::primitive::Primitive;
pub use crate::value::{UntaggedValue, Value};

View File

@ -0,0 +1,12 @@
// These macros exist to differentiate between intentional writing to stdout
// and stray printlns left by accident
#[macro_export]
macro_rules! outln {
($($tokens:tt)*) => { println!($($tokens)*) }
}
#[macro_export]
macro_rules! errln {
($($tokens:tt)*) => { eprintln!($($tokens)*) }
}

View File

@ -0,0 +1,14 @@
#[derive(Debug)]
pub enum MaybeOwned<'a, T> {
Owned(T),
Borrowed(&'a T),
}
impl<T> MaybeOwned<'_, T> {
pub fn borrow(&self) -> &T {
match self {
MaybeOwned::Owned(v) => v,
MaybeOwned::Borrowed(v) => v,
}
}
}

View File

@ -0,0 +1,162 @@
use crate::call_info::CallInfo;
use crate::return_value::ReturnValue;
use crate::signature::Signature;
use crate::value::Value;
use nu_errors::ShellError;
use serde::{Deserialize, Serialize};
use std::io;
pub trait Plugin {
fn config(&mut self) -> Result<Signature, ShellError>;
fn begin_filter(&mut self, _call_info: CallInfo) -> Result<Vec<ReturnValue>, ShellError> {
Ok(vec![])
}
fn filter(&mut self, _input: Value) -> Result<Vec<ReturnValue>, ShellError> {
Ok(vec![])
}
fn end_filter(&mut self) -> Result<Vec<ReturnValue>, ShellError> {
Ok(vec![])
}
fn sink(&mut self, _call_info: CallInfo, _input: Vec<Value>) {}
fn quit(&mut self) {}
}
pub fn serve_plugin(plugin: &mut dyn Plugin) {
let args = std::env::args();
if args.len() > 1 {
let input = args.skip(1).next();
let input = match input {
Some(arg) => std::fs::read_to_string(arg),
None => {
send_response(ShellError::untagged_runtime_error("No input given."));
return;
}
};
if let Ok(input) = input {
let command = serde_json::from_str::<NuCommand>(&input);
match command {
Ok(NuCommand::config) => {
send_response(plugin.config());
return;
}
Ok(NuCommand::begin_filter { params }) => {
send_response(plugin.begin_filter(params));
}
Ok(NuCommand::filter { params }) => {
send_response(plugin.filter(params));
}
Ok(NuCommand::end_filter) => {
send_response(plugin.end_filter());
return;
}
Ok(NuCommand::sink { params }) => {
plugin.sink(params.0, params.1);
return;
}
Ok(NuCommand::quit) => {
plugin.quit();
return;
}
e => {
send_response(ShellError::untagged_runtime_error(format!(
"Could not handle plugin message: {} {:?}",
input, e
)));
return;
}
}
}
} else {
loop {
let mut input = String::new();
match io::stdin().read_line(&mut input) {
Ok(_) => {
let command = serde_json::from_str::<NuCommand>(&input);
match command {
Ok(NuCommand::config) => {
send_response(plugin.config());
break;
}
Ok(NuCommand::begin_filter { params }) => {
send_response(plugin.begin_filter(params));
}
Ok(NuCommand::filter { params }) => {
send_response(plugin.filter(params));
}
Ok(NuCommand::end_filter) => {
send_response(plugin.end_filter());
break;
}
Ok(NuCommand::sink { params }) => {
plugin.sink(params.0, params.1);
break;
}
Ok(NuCommand::quit) => {
plugin.quit();
break;
}
e => {
send_response(ShellError::untagged_runtime_error(format!(
"Could not handle plugin message: {} {:?}",
input, e
)));
break;
}
}
}
e => {
send_response(ShellError::untagged_runtime_error(format!(
"Could not handle plugin message: {:?}",
e,
)));
break;
}
}
}
}
}
#[derive(Debug, Serialize, Deserialize)]
pub struct JsonRpc<T> {
jsonrpc: String,
pub method: String,
pub params: T,
}
impl<T> JsonRpc<T> {
pub fn new<U: Into<String>>(method: U, params: T) -> Self {
JsonRpc {
jsonrpc: "2.0".into(),
method: method.into(),
params,
}
}
}
fn send_response<T: Serialize>(result: T) {
let response = JsonRpc::new("response", result);
let response_raw = serde_json::to_string(&response);
match response_raw {
Ok(response) => outln!("{}", response),
Err(err) => outln!("{}", err),
}
}
#[derive(Debug, Serialize, Deserialize)]
#[serde(tag = "method")]
#[allow(non_camel_case_types)]
pub enum NuCommand {
config,
begin_filter { params: CallInfo },
filter { params: Value },
end_filter,
sink { params: (CallInfo, Vec<Value>) },
quit,
}

View File

@ -0,0 +1,76 @@
use nu_errors::ShellError;
use crate::value::Value;
use nu_source::{b, DebugDocBuilder, PrettyDebug};
use serde::{Deserialize, Serialize};
#[derive(Debug, Clone, Serialize, Deserialize)]
pub enum CommandAction {
ChangePath(String),
Exit,
Error(ShellError),
EnterShell(String),
EnterValueShell(Value),
EnterHelpShell(Value),
PreviousShell,
NextShell,
LeaveShell,
}
impl PrettyDebug for CommandAction {
fn pretty(&self) -> DebugDocBuilder {
match self {
CommandAction::ChangePath(path) => b::typed("change path", b::description(path)),
CommandAction::Exit => b::description("exit"),
CommandAction::Error(_) => b::error("error"),
CommandAction::EnterShell(s) => b::typed("enter shell", b::description(s)),
CommandAction::EnterValueShell(v) => b::typed("enter value shell", v.pretty()),
CommandAction::EnterHelpShell(v) => b::typed("enter help shell", v.pretty()),
CommandAction::PreviousShell => b::description("previous shell"),
CommandAction::NextShell => b::description("next shell"),
CommandAction::LeaveShell => b::description("leave shell"),
}
}
}
#[derive(Debug, Clone, Serialize, Deserialize)]
pub enum ReturnSuccess {
Value(Value),
DebugValue(Value),
Action(CommandAction),
}
impl PrettyDebug for ReturnSuccess {
fn pretty(&self) -> DebugDocBuilder {
match self {
ReturnSuccess::Value(value) => b::typed("value", value.pretty()),
ReturnSuccess::DebugValue(value) => b::typed("debug value", value.pretty()),
ReturnSuccess::Action(action) => b::typed("action", action.pretty()),
}
}
}
pub type ReturnValue = Result<ReturnSuccess, ShellError>;
impl Into<ReturnValue> for Value {
fn into(self) -> ReturnValue {
Ok(ReturnSuccess::Value(self))
}
}
impl ReturnSuccess {
pub fn change_cwd(path: String) -> ReturnValue {
Ok(ReturnSuccess::Action(CommandAction::ChangePath(path)))
}
pub fn value(input: impl Into<Value>) -> ReturnValue {
Ok(ReturnSuccess::Value(input.into()))
}
pub fn debug_value(input: impl Into<Value>) -> ReturnValue {
Ok(ReturnSuccess::DebugValue(input.into()))
}
pub fn action(input: CommandAction) -> ReturnValue {
Ok(ReturnSuccess::Action(input))
}
}

View File

@ -0,0 +1,189 @@
use crate::syntax_shape::SyntaxShape;
use indexmap::IndexMap;
use nu_source::{b, DebugDocBuilder, PrettyDebug, PrettyDebugWithSource};
use serde::{Deserialize, Serialize};
#[derive(Debug, Serialize, Deserialize, Clone)]
pub enum NamedType {
Switch,
Mandatory(SyntaxShape),
Optional(SyntaxShape),
}
#[derive(Debug, Clone, Serialize, Deserialize)]
pub enum PositionalType {
Mandatory(String, SyntaxShape),
Optional(String, SyntaxShape),
}
impl PrettyDebug for PositionalType {
fn pretty(&self) -> DebugDocBuilder {
match self {
PositionalType::Mandatory(string, shape) => {
b::description(string) + b::delimit("(", shape.pretty(), ")").as_kind().group()
}
PositionalType::Optional(string, shape) => {
b::description(string)
+ b::operator("?")
+ b::delimit("(", shape.pretty(), ")").as_kind().group()
}
}
}
}
impl PositionalType {
pub fn mandatory(name: &str, ty: SyntaxShape) -> PositionalType {
PositionalType::Mandatory(name.to_string(), ty)
}
pub fn mandatory_any(name: &str) -> PositionalType {
PositionalType::Mandatory(name.to_string(), SyntaxShape::Any)
}
pub fn mandatory_block(name: &str) -> PositionalType {
PositionalType::Mandatory(name.to_string(), SyntaxShape::Block)
}
pub fn optional(name: &str, ty: SyntaxShape) -> PositionalType {
PositionalType::Optional(name.to_string(), ty)
}
pub fn optional_any(name: &str) -> PositionalType {
PositionalType::Optional(name.to_string(), SyntaxShape::Any)
}
pub fn name(&self) -> &str {
match self {
PositionalType::Mandatory(s, _) => s,
PositionalType::Optional(s, _) => s,
}
}
pub fn syntax_type(&self) -> SyntaxShape {
match *self {
PositionalType::Mandatory(_, t) => t,
PositionalType::Optional(_, t) => t,
}
}
}
type Description = String;
#[derive(Debug, Serialize, Deserialize, Clone)]
pub struct Signature {
pub name: String,
pub usage: String,
pub positional: Vec<(PositionalType, Description)>,
pub rest_positional: Option<(SyntaxShape, Description)>,
pub named: IndexMap<String, (NamedType, Description)>,
pub is_filter: bool,
}
impl PrettyDebugWithSource for Signature {
fn pretty_debug(&self, source: &str) -> DebugDocBuilder {
b::typed(
"signature",
b::description(&self.name)
+ b::preceded(
b::space(),
b::intersperse(
self.positional
.iter()
.map(|(ty, _)| ty.pretty_debug(source)),
b::space(),
),
),
)
}
}
impl Signature {
pub fn new(name: String) -> Signature {
Signature {
name,
usage: String::new(),
positional: vec![],
rest_positional: None,
named: IndexMap::new(),
is_filter: false,
}
}
pub fn build(name: impl Into<String>) -> Signature {
Signature::new(name.into())
}
pub fn desc(mut self, usage: impl Into<String>) -> Signature {
self.usage = usage.into();
self
}
pub fn required(
mut self,
name: impl Into<String>,
ty: impl Into<SyntaxShape>,
desc: impl Into<String>,
) -> Signature {
self.positional.push((
PositionalType::Mandatory(name.into(), ty.into()),
desc.into(),
));
self
}
pub fn optional(
mut self,
name: impl Into<String>,
ty: impl Into<SyntaxShape>,
desc: impl Into<String>,
) -> Signature {
self.positional.push((
PositionalType::Optional(name.into(), ty.into()),
desc.into(),
));
self
}
pub fn named(
mut self,
name: impl Into<String>,
ty: impl Into<SyntaxShape>,
desc: impl Into<String>,
) -> Signature {
self.named
.insert(name.into(), (NamedType::Optional(ty.into()), desc.into()));
self
}
pub fn required_named(
mut self,
name: impl Into<String>,
ty: impl Into<SyntaxShape>,
desc: impl Into<String>,
) -> Signature {
self.named
.insert(name.into(), (NamedType::Mandatory(ty.into()), desc.into()));
self
}
pub fn switch(mut self, name: impl Into<String>, desc: impl Into<String>) -> Signature {
self.named
.insert(name.into(), (NamedType::Switch, desc.into()));
self
}
pub fn filter(mut self) -> Signature {
self.is_filter = true;
self
}
pub fn rest(mut self, ty: SyntaxShape, desc: impl Into<String>) -> Signature {
self.rest_positional = Some((ty, desc.into()));
self
}
}

View File

@ -0,0 +1,31 @@
use nu_source::{b, DebugDocBuilder, PrettyDebug};
use serde::{Deserialize, Serialize};
#[derive(Debug, Copy, Clone, Serialize, Deserialize)]
pub enum SyntaxShape {
Any,
String,
Member,
ColumnPath,
Number,
Int,
Path,
Pattern,
Block,
}
impl PrettyDebug for SyntaxShape {
fn pretty(&self) -> DebugDocBuilder {
b::kind(match self {
SyntaxShape::Any => "any shape",
SyntaxShape::String => "string shape",
SyntaxShape::Member => "member shape",
SyntaxShape::ColumnPath => "column path shape",
SyntaxShape::Number => "number shape",
SyntaxShape::Int => "integer shape",
SyntaxShape::Path => "file path shape",
SyntaxShape::Pattern => "pattern shape",
SyntaxShape::Block => "block shape",
})
}
}

View File

@ -0,0 +1,37 @@
use nu_source::{DebugDocBuilder, HasSpan, Spanned, SpannedItem, Tagged};
pub trait ShellTypeName {
fn type_name(&self) -> &'static str;
}
impl<T: ShellTypeName> ShellTypeName for Spanned<T> {
fn type_name(&self) -> &'static str {
self.item.type_name()
}
}
impl<T: ShellTypeName> ShellTypeName for &T {
fn type_name(&self) -> &'static str {
(*self).type_name()
}
}
pub trait SpannedTypeName {
fn spanned_type_name(&self) -> Spanned<&'static str>;
}
impl<T: ShellTypeName + HasSpan> SpannedTypeName for T {
fn spanned_type_name(&self) -> Spanned<&'static str> {
self.type_name().spanned(self.span())
}
}
impl<T: ShellTypeName> SpannedTypeName for Tagged<T> {
fn spanned_type_name(&self) -> Spanned<&'static str> {
self.item.type_name().spanned(self.tag.span)
}
}
pub trait PrettyType {
fn pretty_type(&self) -> DebugDocBuilder;
}

View File

@ -0,0 +1,205 @@
pub mod column_path;
mod convert;
mod debug;
pub mod dict;
pub mod evaluate;
pub mod primitive;
mod serde_bigdecimal;
mod serde_bigint;
use crate::type_name::{ShellTypeName, SpannedTypeName};
use crate::value::dict::Dictionary;
use crate::value::evaluate::Evaluate;
use crate::value::primitive::Primitive;
use nu_errors::ShellError;
use nu_source::{AnchorLocation, HasSpan, Span, Tag};
use serde::{Deserialize, Serialize};
use std::path::PathBuf;
#[derive(Debug, Clone, PartialEq, PartialOrd, Eq, Ord, Serialize, Deserialize)]
pub enum UntaggedValue {
Primitive(Primitive),
Row(Dictionary),
Table(Vec<Value>),
// Errors are a type of value too
Error(ShellError),
Block(Evaluate),
}
impl UntaggedValue {
pub fn retag(self, tag: impl Into<Tag>) -> Value {
Value {
value: self,
tag: tag.into(),
}
}
pub fn data_descriptors(&self) -> Vec<String> {
match self {
UntaggedValue::Primitive(_) => vec![],
UntaggedValue::Row(columns) => columns
.entries
.keys()
.into_iter()
.map(|x| x.to_string())
.collect(),
UntaggedValue::Block(_) => vec![],
UntaggedValue::Table(_) => vec![],
UntaggedValue::Error(_) => vec![],
}
}
pub fn into_value(self, tag: impl Into<Tag>) -> Value {
Value {
value: self,
tag: tag.into(),
}
}
pub fn into_untagged_value(self) -> Value {
Value {
value: self,
tag: Tag::unknown(),
}
}
pub fn is_true(&self) -> bool {
match self {
UntaggedValue::Primitive(Primitive::Boolean(true)) => true,
_ => false,
}
}
pub fn is_some(&self) -> bool {
!self.is_none()
}
pub fn is_none(&self) -> bool {
match self {
UntaggedValue::Primitive(Primitive::Nothing) => true,
_ => false,
}
}
pub fn is_error(&self) -> bool {
match self {
UntaggedValue::Error(_err) => true,
_ => false,
}
}
pub fn expect_error(&self) -> ShellError {
match self {
UntaggedValue::Error(err) => err.clone(),
_ => panic!("Don't call expect_error without first calling is_error"),
}
}
pub fn expect_string(&self) -> &str {
match self {
UntaggedValue::Primitive(Primitive::String(string)) => &string[..],
_ => panic!("expect_string assumes that the value must be a string"),
}
}
}
#[derive(Debug, Clone, PartialOrd, PartialEq, Ord, Eq, Serialize, Deserialize)]
pub struct Value {
pub value: UntaggedValue,
pub tag: Tag,
}
impl std::ops::Deref for Value {
type Target = UntaggedValue;
fn deref(&self) -> &Self::Target {
&self.value
}
}
impl Value {
pub fn anchor(&self) -> Option<AnchorLocation> {
self.tag.anchor()
}
pub fn anchor_name(&self) -> Option<String> {
self.tag.anchor_name()
}
pub fn tag(&self) -> Tag {
self.tag.clone()
}
pub fn as_string(&self) -> Result<&str, ShellError> {
match &self.value {
UntaggedValue::Primitive(Primitive::String(string)) => Ok(&string[..]),
_ => Err(ShellError::type_error("string", self.spanned_type_name())),
}
}
pub fn as_path(&self) -> Result<PathBuf, ShellError> {
match &self.value {
UntaggedValue::Primitive(Primitive::Path(path)) => Ok(path.clone()),
UntaggedValue::Primitive(Primitive::String(path_str)) => {
Ok(PathBuf::from(&path_str).clone())
}
_ => Err(ShellError::type_error("Path", self.spanned_type_name())),
}
}
}
impl Into<UntaggedValue> for &str {
fn into(self) -> UntaggedValue {
UntaggedValue::Primitive(Primitive::String(self.to_string()))
}
}
impl Into<UntaggedValue> for Value {
fn into(self) -> UntaggedValue {
self.value
}
}
impl<'a> Into<&'a UntaggedValue> for &'a Value {
fn into(self) -> &'a UntaggedValue {
&self.value
}
}
impl HasSpan for Value {
fn span(&self) -> Span {
self.tag.span
}
}
impl ShellTypeName for Value {
fn type_name(&self) -> &'static str {
ShellTypeName::type_name(&self.value)
}
}
impl ShellTypeName for UntaggedValue {
fn type_name(&self) -> &'static str {
match &self {
UntaggedValue::Primitive(p) => p.type_name(),
UntaggedValue::Row(_) => "row",
UntaggedValue::Table(_) => "table",
UntaggedValue::Error(_) => "error",
UntaggedValue::Block(_) => "block",
}
}
}
impl From<Primitive> for UntaggedValue {
fn from(input: Primitive) -> UntaggedValue {
UntaggedValue::Primitive(input)
}
}
impl From<String> for UntaggedValue {
fn from(input: String) -> UntaggedValue {
UntaggedValue::Primitive(Primitive::String(input))
}
}

View File

@ -0,0 +1,87 @@
use derive_new::new;
use getset::Getters;
use nu_source::{b, span_for_spanned_list, DebugDocBuilder, HasFallibleSpan, PrettyDebug, Span};
use num_bigint::BigInt;
use serde::{Deserialize, Serialize};
#[derive(Clone, Debug, Eq, PartialEq, Ord, PartialOrd, Hash, Serialize, Deserialize)]
pub enum UnspannedPathMember {
String(String),
Int(BigInt),
}
impl UnspannedPathMember {
pub fn into_path_member(self, span: impl Into<Span>) -> PathMember {
PathMember {
unspanned: self,
span: span.into(),
}
}
}
#[derive(Clone, Debug, Eq, PartialEq, Ord, PartialOrd, Hash, Serialize, Deserialize)]
pub struct PathMember {
pub unspanned: UnspannedPathMember,
pub span: Span,
}
impl PrettyDebug for &PathMember {
fn pretty(&self) -> DebugDocBuilder {
match &self.unspanned {
UnspannedPathMember::String(string) => b::primitive(format!("{:?}", string)),
UnspannedPathMember::Int(int) => b::primitive(format!("{}", int)),
}
}
}
#[derive(
Debug, Hash, Serialize, Deserialize, Ord, PartialOrd, Eq, PartialEq, Getters, Clone, new,
)]
pub struct ColumnPath {
#[get = "pub"]
members: Vec<PathMember>,
}
impl ColumnPath {
pub fn iter(&self) -> impl Iterator<Item = &PathMember> {
self.members.iter()
}
pub fn split_last(&self) -> (&PathMember, &[PathMember]) {
self.members.split_last().unwrap()
}
}
impl PrettyDebug for ColumnPath {
fn pretty(&self) -> DebugDocBuilder {
let members: Vec<DebugDocBuilder> =
self.members.iter().map(|member| member.pretty()).collect();
b::delimit(
"(",
b::description("path") + b::equals() + b::intersperse(members, b::space()),
")",
)
.nest()
}
}
impl HasFallibleSpan for ColumnPath {
fn maybe_span(&self) -> Option<Span> {
if self.members.len() == 0 {
None
} else {
Some(span_for_spanned_list(self.members.iter().map(|m| m.span)))
}
}
}
impl PathMember {
pub fn string(string: impl Into<String>, span: impl Into<Span>) -> PathMember {
UnspannedPathMember::String(string.into()).into_path_member(span)
}
pub fn int(int: impl Into<BigInt>, span: impl Into<Span>) -> PathMember {
UnspannedPathMember::Int(int.into()).into_path_member(span)
}
}

View File

@ -0,0 +1,55 @@
use nu_errors::{CoerceInto, ShellError};
use crate::type_name::SpannedTypeName;
use crate::value::dict::Dictionary;
use crate::value::primitive::Primitive;
use crate::value::{UntaggedValue, Value};
use nu_source::TaggedItem;
impl std::convert::TryFrom<&Value> for i64 {
type Error = ShellError;
fn try_from(value: &Value) -> Result<i64, ShellError> {
match &value.value {
UntaggedValue::Primitive(Primitive::Int(int)) => {
int.tagged(&value.tag).coerce_into("converting to i64")
}
_ => Err(ShellError::type_error("Integer", value.spanned_type_name())),
}
}
}
impl std::convert::TryFrom<&Value> for String {
type Error = ShellError;
fn try_from(value: &Value) -> Result<String, ShellError> {
match &value.value {
UntaggedValue::Primitive(Primitive::String(s)) => Ok(s.clone()),
_ => Err(ShellError::type_error("String", value.spanned_type_name())),
}
}
}
impl std::convert::TryFrom<&Value> for Vec<u8> {
type Error = ShellError;
fn try_from(value: &Value) -> Result<Vec<u8>, ShellError> {
match &value.value {
UntaggedValue::Primitive(Primitive::Binary(b)) => Ok(b.clone()),
_ => Err(ShellError::type_error("Binary", value.spanned_type_name())),
}
}
}
impl<'a> std::convert::TryFrom<&'a Value> for &'a Dictionary {
type Error = ShellError;
fn try_from(value: &'a Value) -> Result<&'a Dictionary, ShellError> {
match &value.value {
UntaggedValue::Row(d) => Ok(d),
_ => Err(ShellError::type_error(
"Dictionary",
value.spanned_type_name(),
)),
}
}
}

View File

@ -0,0 +1,81 @@
use crate::type_name::PrettyType;
use crate::value::primitive::Primitive;
use crate::value::{UntaggedValue, Value};
use nu_source::{b, DebugDocBuilder, PrettyDebug};
impl PrettyDebug for &Value {
fn pretty(&self) -> DebugDocBuilder {
PrettyDebug::pretty(*self)
}
}
impl PrettyDebug for Value {
fn pretty(&self) -> DebugDocBuilder {
match &self.value {
UntaggedValue::Primitive(p) => p.pretty(),
UntaggedValue::Row(row) => row.pretty_builder().nest(1).group().into(),
UntaggedValue::Table(table) => {
b::delimit("[", b::intersperse(table, b::space()), "]").nest()
}
UntaggedValue::Error(_) => b::error("error"),
UntaggedValue::Block(_) => b::opaque("block"),
}
}
}
impl PrettyType for Primitive {
fn pretty_type(&self) -> DebugDocBuilder {
match self {
Primitive::Nothing => ty("nothing"),
Primitive::Int(_) => ty("integer"),
Primitive::Decimal(_) => ty("decimal"),
Primitive::Bytes(_) => ty("bytesize"),
Primitive::String(_) => ty("string"),
Primitive::ColumnPath(_) => ty("column-path"),
Primitive::Pattern(_) => ty("pattern"),
Primitive::Boolean(_) => ty("boolean"),
Primitive::Date(_) => ty("date"),
Primitive::Duration(_) => ty("duration"),
Primitive::Path(_) => ty("path"),
Primitive::Binary(_) => ty("binary"),
Primitive::BeginningOfStream => b::keyword("beginning-of-stream"),
Primitive::EndOfStream => b::keyword("end-of-stream"),
}
}
}
impl PrettyDebug for Primitive {
fn pretty(&self) -> DebugDocBuilder {
match self {
Primitive::Nothing => b::primitive("nothing"),
Primitive::Int(int) => prim(format_args!("{}", int)),
Primitive::Decimal(decimal) => prim(format_args!("{}", decimal)),
Primitive::Bytes(bytes) => primitive_doc(bytes, "bytesize"),
Primitive::String(string) => prim(string),
Primitive::ColumnPath(path) => path.pretty(),
Primitive::Pattern(pattern) => primitive_doc(pattern, "pattern"),
Primitive::Boolean(boolean) => match boolean {
true => b::primitive("$yes"),
false => b::primitive("$no"),
},
Primitive::Date(date) => primitive_doc(date, "date"),
Primitive::Duration(duration) => primitive_doc(duration, "seconds"),
Primitive::Path(path) => primitive_doc(path, "path"),
Primitive::Binary(_) => b::opaque("binary"),
Primitive::BeginningOfStream => b::keyword("beginning-of-stream"),
Primitive::EndOfStream => b::keyword("end-of-stream"),
}
}
}
fn prim(name: impl std::fmt::Debug) -> DebugDocBuilder {
b::primitive(format!("{:?}", name))
}
fn primitive_doc(name: impl std::fmt::Debug, ty: impl Into<String>) -> DebugDocBuilder {
b::primitive(format!("{:?}", name)) + b::delimit("(", b::kind(ty.into()), ")")
}
fn ty(name: impl std::fmt::Debug) -> DebugDocBuilder {
b::kind(format!("{:?}", name))
}

View File

@ -0,0 +1,140 @@
use crate::maybe_owned::MaybeOwned;
use crate::value::primitive::Primitive;
use crate::value::{UntaggedValue, Value};
use derive_new::new;
use getset::Getters;
use indexmap::IndexMap;
use nu_source::{b, DebugDocBuilder, PrettyDebug, Spanned, Tag};
use serde::{Deserialize, Serialize};
use std::cmp::{Ord, Ordering, PartialOrd};
#[derive(Debug, Default, Serialize, Deserialize, PartialEq, Eq, Clone, Getters, new)]
pub struct Dictionary {
#[get = "pub"]
pub entries: IndexMap<String, Value>,
}
impl PartialOrd for Dictionary {
fn partial_cmp(&self, other: &Dictionary) -> Option<Ordering> {
let this: Vec<&String> = self.entries.keys().collect();
let that: Vec<&String> = other.entries.keys().collect();
if this != that {
return this.partial_cmp(&that);
}
let this: Vec<&Value> = self.entries.values().collect();
let that: Vec<&Value> = self.entries.values().collect();
this.partial_cmp(&that)
}
}
impl Ord for Dictionary {
fn cmp(&self, other: &Dictionary) -> Ordering {
let this: Vec<&String> = self.entries.keys().collect();
let that: Vec<&String> = other.entries.keys().collect();
if this != that {
return this.cmp(&that);
}
let this: Vec<&Value> = self.entries.values().collect();
let that: Vec<&Value> = self.entries.values().collect();
this.cmp(&that)
}
}
impl PartialEq<Value> for Dictionary {
fn eq(&self, other: &Value) -> bool {
match &other.value {
UntaggedValue::Row(d) => self == d,
_ => false,
}
}
}
#[derive(Debug, new)]
struct DebugEntry<'a> {
key: &'a str,
value: &'a Value,
}
impl<'a> PrettyDebug for DebugEntry<'a> {
fn pretty(&self) -> DebugDocBuilder {
(b::key(self.key.to_string()) + b::equals() + self.value.pretty().as_value()).group()
}
}
impl PrettyDebug for Dictionary {
fn pretty(&self) -> DebugDocBuilder {
b::delimit(
"(",
b::intersperse(
self.entries()
.iter()
.map(|(key, value)| DebugEntry::new(key, value)),
b::space(),
),
")",
)
}
}
impl From<IndexMap<String, Value>> for Dictionary {
fn from(input: IndexMap<String, Value>) -> Dictionary {
let mut out = IndexMap::default();
for (key, value) in input {
out.insert(key, value);
}
Dictionary::new(out)
}
}
impl Dictionary {
pub fn get_data(&self, desc: &String) -> MaybeOwned<'_, Value> {
match self.entries.get(desc) {
Some(v) => MaybeOwned::Borrowed(v),
None => MaybeOwned::Owned(
UntaggedValue::Primitive(Primitive::Nothing).into_untagged_value(),
),
}
}
pub fn keys(&self) -> impl Iterator<Item = &String> {
self.entries.keys()
}
pub fn get_data_by_key(&self, name: Spanned<&str>) -> Option<Value> {
let result = self
.entries
.iter()
.find(|(desc_name, _)| *desc_name == name.item)?
.1;
Some(
result
.value
.clone()
.into_value(Tag::new(result.tag.anchor(), name.span)),
)
}
pub fn get_mut_data_by_key(&mut self, name: &str) -> Option<&mut Value> {
match self
.entries
.iter_mut()
.find(|(desc_name, _)| *desc_name == name)
{
Some((_, v)) => Some(v),
None => None,
}
}
pub fn insert_data_at_key(&mut self, name: &str, value: Value) {
self.entries.insert(name.to_string(), value);
}
}

View File

@ -0,0 +1,102 @@
use crate::value::{Primitive, UntaggedValue, Value};
use indexmap::IndexMap;
use nu_errors::ShellError;
use query_interface::{interfaces, vtable_for, Object, ObjectHash};
use serde::{Deserialize, Serialize};
use std::cmp::{Ord, Ordering, PartialOrd};
use std::fmt::Debug;
#[derive(Debug)]
pub struct Scope {
pub it: Value,
pub vars: IndexMap<String, Value>,
}
impl Scope {
pub fn new(it: Value) -> Scope {
Scope {
it,
vars: IndexMap::new(),
}
}
}
impl Scope {
pub fn empty() -> Scope {
Scope {
it: UntaggedValue::Primitive(Primitive::Nothing).into_untagged_value(),
vars: IndexMap::new(),
}
}
pub fn it_value(value: Value) -> Scope {
Scope {
it: value,
vars: IndexMap::new(),
}
}
}
#[typetag::serde(tag = "type")]
pub trait EvaluateTrait: Debug + Send + Sync + Object + ObjectHash + 'static {
fn invoke(&self, scope: &Scope) -> Result<Value, ShellError>;
fn clone_box(&self) -> Evaluate;
}
interfaces!(Evaluate: dyn ObjectHash);
#[typetag::serde]
impl EvaluateTrait for Evaluate {
fn invoke(&self, scope: &Scope) -> Result<Value, ShellError> {
self.expr.invoke(scope)
}
fn clone_box(&self) -> Evaluate {
self.expr.clone_box()
}
}
#[derive(Debug, Serialize, Deserialize)]
pub struct Evaluate {
expr: Box<dyn EvaluateTrait>,
}
impl Evaluate {
pub fn new(evaluate: impl EvaluateTrait) -> Evaluate {
Evaluate {
expr: Box::new(evaluate),
}
}
}
impl std::hash::Hash for Evaluate {
fn hash<H: std::hash::Hasher>(&self, state: &mut H) {
self.expr.obj_hash(state)
}
}
impl Clone for Evaluate {
fn clone(&self) -> Evaluate {
self.expr.clone_box()
}
}
impl Ord for Evaluate {
fn cmp(&self, _: &Self) -> Ordering {
Ordering::Equal
}
}
impl PartialOrd for Evaluate {
fn partial_cmp(&self, _: &Evaluate) -> Option<Ordering> {
Some(Ordering::Equal)
}
}
impl PartialEq for Evaluate {
fn eq(&self, _: &Evaluate) -> bool {
true
}
}
impl Eq for Evaluate {}

View File

@ -0,0 +1,65 @@
use crate::type_name::ShellTypeName;
use crate::value::column_path::ColumnPath;
use crate::value::{serde_bigdecimal, serde_bigint};
use bigdecimal::BigDecimal;
use chrono::{DateTime, Utc};
use num_bigint::BigInt;
use num_traits::cast::FromPrimitive;
use serde::{Deserialize, Serialize};
use std::path::PathBuf;
#[derive(Debug, Clone, Ord, PartialOrd, Eq, PartialEq, Deserialize, Serialize)]
pub enum Primitive {
Nothing,
#[serde(with = "serde_bigint")]
Int(BigInt),
#[serde(with = "serde_bigdecimal")]
Decimal(BigDecimal),
Bytes(u64),
String(String),
ColumnPath(ColumnPath),
Pattern(String),
Boolean(bool),
Date(DateTime<Utc>),
Duration(u64), // Duration in seconds
Path(PathBuf),
#[serde(with = "serde_bytes")]
Binary(Vec<u8>),
// Stream markers (used as bookend markers rather than actual values)
BeginningOfStream,
EndOfStream,
}
impl From<BigDecimal> for Primitive {
fn from(decimal: BigDecimal) -> Primitive {
Primitive::Decimal(decimal)
}
}
impl From<f64> for Primitive {
fn from(float: f64) -> Primitive {
Primitive::Decimal(BigDecimal::from_f64(float).unwrap())
}
}
impl ShellTypeName for Primitive {
fn type_name(&self) -> &'static str {
match self {
Primitive::Nothing => "nothing",
Primitive::Int(_) => "integer",
Primitive::Decimal(_) => "decimal",
Primitive::Bytes(_) => "bytes",
Primitive::String(_) => "string",
Primitive::ColumnPath(_) => "column path",
Primitive::Pattern(_) => "pattern",
Primitive::Boolean(_) => "boolean",
Primitive::Date(_) => "date",
Primitive::Duration(_) => "duration",
Primitive::Path(_) => "file path",
Primitive::Binary(_) => "binary",
Primitive::BeginningOfStream => "marker<beginning of stream>",
Primitive::EndOfStream => "marker<end of stream>",
}
}
}

View File

@ -0,0 +1,24 @@
use bigdecimal::BigDecimal;
use num_traits::cast::FromPrimitive;
use num_traits::cast::ToPrimitive;
pub fn serialize<S>(big_decimal: &BigDecimal, serializer: S) -> Result<S::Ok, S::Error>
where
S: serde::Serializer,
{
serde::Serialize::serialize(
&big_decimal
.to_f64()
.ok_or(serde::ser::Error::custom("expected a f64-sized bignum"))?,
serializer,
)
}
pub fn deserialize<'de, D>(deserializer: D) -> Result<BigDecimal, D::Error>
where
D: serde::Deserializer<'de>,
{
let x: f64 = serde::Deserialize::deserialize(deserializer)?;
Ok(BigDecimal::from_f64(x)
.ok_or(serde::de::Error::custom("expected a f64-sized bigdecimal"))?)
}

View File

@ -0,0 +1,23 @@
use num_bigint::BigInt;
use num_traits::cast::FromPrimitive;
use num_traits::cast::ToPrimitive;
pub fn serialize<S>(big_int: &BigInt, serializer: S) -> Result<S::Ok, S::Error>
where
S: serde::Serializer,
{
serde::Serialize::serialize(
&big_int
.to_i64()
.ok_or(serde::ser::Error::custom("expected a i64-sized bignum"))?,
serializer,
)
}
pub fn deserialize<'de, D>(deserializer: D) -> Result<BigInt, D::Error>
where
D: serde::Deserializer<'de>,
{
let x: i64 = serde::Deserialize::deserialize(deserializer)?;
Ok(BigInt::from_i64(x).ok_or(serde::de::Error::custom("expected a i64-sized bignum"))?)
}

View File

@ -0,0 +1,22 @@
[package]
name = "nu-textview"
version = "0.1.0"
authors = ["Yehuda Katz <wycats@gmail.com>"]
edition = "2018"
# See more keys and their definitions at https://doc.rust-lang.org/cargo/reference/manifest.html
[[bin]]
name = "nu_plugin_textview"
path = "src/main.rs"
required-features = ["textview"]
[dependencies]
syntect = { version = "3.2.0" }
ansi_term = "0.12.1"
crossterm = { version = "0.10.2" }
nu = { path = "../.." }
nu-protocol = { path = "../nu-protocol" }
nu-source = { path = "../nu-source" }
url = "2.1.0"

View File

@ -0,0 +1,292 @@
use crossterm::{cursor, terminal, RawScreen};
use crossterm::{InputEvent, KeyEvent};
use nu::{CallInfo, Plugin, Primitive, ShellError, Signature, UntaggedValue, Value};
use nu_protocol::{outln, serve_plugin};
use nu_source::AnchorLocation;
use syntect::easy::HighlightLines;
use syntect::highlighting::{Style, ThemeSet};
use syntect::parsing::SyntaxSet;
use std::io::Write;
use std::path::Path;
enum DrawCommand {
DrawString(Style, String),
NextLine,
}
struct TextView;
impl TextView {
fn new() -> TextView {
TextView
}
}
impl Plugin for TextView {
fn config(&mut self) -> Result<Signature, ShellError> {
Ok(Signature::build("textview").desc("Autoview of text data."))
}
fn sink(&mut self, _call_info: CallInfo, input: Vec<Value>) {
view_text_value(&input[0]);
}
}
fn paint_textview(
draw_commands: &Vec<DrawCommand>,
starting_row: usize,
use_color_buffer: bool,
) -> usize {
let terminal = terminal();
let cursor = cursor();
let size = terminal.terminal_size();
// render
let mut pos = 0;
let width = size.0 as usize;
let height = size.1 as usize - 1;
let mut frame_buffer = vec![];
for command in draw_commands {
match command {
DrawCommand::DrawString(style, string) => {
for chr in string.chars() {
if chr == '\t' {
for _ in 0..8 {
frame_buffer.push((
' ',
style.foreground.r,
style.foreground.g,
style.foreground.b,
));
}
pos += 8;
} else {
frame_buffer.push((
chr,
style.foreground.r,
style.foreground.g,
style.foreground.b,
));
pos += 1;
}
}
}
DrawCommand::NextLine => {
for _ in 0..(width - pos % width) {
frame_buffer.push((' ', 0, 0, 0));
}
pos += width - pos % width;
}
}
}
let num_frame_buffer_rows = frame_buffer.len() / width;
let buffer_needs_scrolling = num_frame_buffer_rows > height;
// display
let mut ansi_strings = vec![];
let mut normal_chars = vec![];
for c in
&frame_buffer[starting_row * width..std::cmp::min(pos, (starting_row + height) * width)]
{
if use_color_buffer {
ansi_strings.push(ansi_term::Colour::RGB(c.1, c.2, c.3).paint(format!("{}", c.0)));
} else {
normal_chars.push(c.0);
}
}
if buffer_needs_scrolling {
let _ = cursor.goto(0, 0);
}
if use_color_buffer {
print!("{}", ansi_term::ANSIStrings(&ansi_strings));
} else {
let s: String = normal_chars.into_iter().collect();
print!("{}", s);
}
if buffer_needs_scrolling {
let _ = cursor.goto(0, size.1);
print!(
"{}",
ansi_term::Colour::Blue.paint("[ESC to quit, arrow keys to move]")
);
}
let _ = std::io::stdout().flush();
num_frame_buffer_rows
}
fn scroll_view_lines_if_needed(draw_commands: Vec<DrawCommand>, use_color_buffer: bool) {
let mut starting_row = 0;
if let Ok(_raw) = RawScreen::into_raw_mode() {
let terminal = terminal();
let mut size = terminal.terminal_size();
let height = size.1 as usize - 1;
let mut max_bottom_line = paint_textview(&draw_commands, starting_row, use_color_buffer);
// Only scroll if needed
if max_bottom_line > height as usize {
let cursor = cursor();
let _ = cursor.hide();
let input = crossterm::input();
let mut sync_stdin = input.read_sync();
loop {
if let Some(ev) = sync_stdin.next() {
match ev {
InputEvent::Keyboard(k) => match k {
KeyEvent::Esc => {
break;
}
KeyEvent::Up | KeyEvent::Char('k') => {
if starting_row > 0 {
starting_row -= 1;
max_bottom_line = paint_textview(
&draw_commands,
starting_row,
use_color_buffer,
);
}
}
KeyEvent::Down | KeyEvent::Char('j') => {
if starting_row < (max_bottom_line - height) {
starting_row += 1;
}
max_bottom_line =
paint_textview(&draw_commands, starting_row, use_color_buffer);
}
KeyEvent::PageUp | KeyEvent::Ctrl('b') => {
starting_row -= std::cmp::min(height, starting_row);
max_bottom_line =
paint_textview(&draw_commands, starting_row, use_color_buffer);
}
KeyEvent::PageDown | KeyEvent::Ctrl('f') | KeyEvent::Char(' ') => {
if starting_row < (max_bottom_line - height) {
starting_row += height;
if starting_row > (max_bottom_line - height) {
starting_row = max_bottom_line - height;
}
}
max_bottom_line =
paint_textview(&draw_commands, starting_row, use_color_buffer);
}
_ => {}
},
_ => {}
}
}
let new_size = terminal.terminal_size();
if size != new_size {
size = new_size;
let _ = terminal.clear(crossterm::ClearType::All);
max_bottom_line =
paint_textview(&draw_commands, starting_row, use_color_buffer);
}
}
let _ = cursor.show();
let _ = RawScreen::disable_raw_mode();
}
}
outln!("");
}
fn scroll_view(s: &str) {
let mut v = vec![];
for line in s.lines() {
v.push(DrawCommand::DrawString(Style::default(), line.to_string()));
v.push(DrawCommand::NextLine);
}
scroll_view_lines_if_needed(v, false);
}
fn view_text_value(value: &Value) {
let value_anchor = value.anchor();
match &value.value {
UntaggedValue::Primitive(Primitive::String(ref s)) => {
if let Some(source) = value_anchor {
let extension: Option<String> = match source {
AnchorLocation::File(file) => {
let path = Path::new(&file);
path.extension().map(|x| x.to_string_lossy().to_string())
}
AnchorLocation::Url(url) => {
let url = url::Url::parse(&url);
if let Ok(url) = url {
let url = url.clone();
if let Some(mut segments) = url.path_segments() {
if let Some(file) = segments.next_back() {
let path = Path::new(file);
path.extension().map(|x| x.to_string_lossy().to_string())
} else {
None
}
} else {
None
}
} else {
None
}
}
//FIXME: this probably isn't correct
AnchorLocation::Source(_source) => None,
};
match extension {
Some(extension) => {
// Load these once at the start of your program
let ps: SyntaxSet = syntect::dumps::from_binary(include_bytes!(
"../../../assets/syntaxes.bin"
));
if let Some(syntax) = ps.find_syntax_by_extension(&extension) {
let ts: ThemeSet = syntect::dumps::from_binary(include_bytes!(
"../../../assets/themes.bin"
));
let mut h = HighlightLines::new(syntax, &ts.themes["OneHalfDark"]);
let mut v = vec![];
for line in s.lines() {
let ranges: Vec<(Style, &str)> = h.highlight(line, &ps);
for range in ranges {
v.push(DrawCommand::DrawString(range.0, range.1.to_string()));
}
v.push(DrawCommand::NextLine);
}
scroll_view_lines_if_needed(v, true);
} else {
scroll_view(s);
}
}
_ => {
scroll_view(s);
}
}
} else {
scroll_view(s);
}
}
_ => {}
}
}
fn main() {
serve_plugin(&mut TextView::new());
}