flp-0.1.0.0: A layout spec language for memory managers implemented in Rust.

Copyright(c) Alec Theriault 2017-2018
LicenseBSD-style
Maintaineralec.theriault@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Language.Rust.Pretty.Resolve

Description

NOTE: the following uses hithero unimplemented antiquoting syntax

An AST and its text form should be completely isomorphic, with parse and pretty being the functions allowing you to go back and forth between these forms. Unfortunately, this cannot really be the case. The AST form can express programs which cannot be literally pretty printed and still make sense. Sometimes, extra parens or semicolons need to be added.

Simple example

For example, consider the following interaction

>>> import Language.Rust.Quote
>>> import Language.Rust.Pretty
>>> :set -XQuasiQuotes
>>> x = [expr| 2 + 3 |]
>>> y = [expr| 1 * $x |]
>>> pretty y
0 * 1 + 2

The problem is that we haven't introduced the paren AST node (which we would have gotten had we parsed 1 * (2 + 3). This is where resolve steps in.

>>> Right y' = resolve y
>>> pretty y'
0 * (1 + 2)

More involved example

From the above, it is tempting to say: your pretty printer should be smarter! However, things are not always so simple. Consider the less obvious example:

>>> fnBody = [expr| { let y = x; x += 1; y } + x |]
>>> fn = [item| fn foo(mut x: i32) -> i32 { $fnBody } |]
>>> pretty fn
fn foo(mut x: i32) -> i32 {
  { let y = x; x += 1; y } + x
}

This is clearly not the desired output - this won't compile with rustc because of an invariant in blocks: if the block ends in an expression, that expression cannot start with a block. To fix this, we call resolve on the AST before pretty printing it.

>>> Right fn' = resolve fn
>>> pretty fn'
fn foo(mut x: i32) -> i32 {
  ({ let y = x; x += 1; y }) + x
}

And now we have generated valid code.

Synopsis

Documentation

class Resolve a where Source #

Since it is possible to have well-typed Haskell expressions which represent invalid Rust ASTs, it is convenient to fix, warn, or fail ASTs before printing them. The Resolve typeclass provides such a facility.

A non-exhaustive list of the more obvious issues it covers:

  • missing parens
  • invalid identifiers
  • invalid paths (for example, generic arguments on a module path)
  • inner attributes on things that support only outer attributes (and vice-versa)

Minimal complete definition

resolveM

Methods

resolve :: a -> Either ResolveFail a Source #

Convert some value to its resolved form. Informally, resolving a value involves checking that its invariants hold and, if they don't, report an error message or adjust the value so that the invariant holds.

A value of a type satsifying Parse and Pretty is resolved if parse . pretty is an identity operation on it. We further expect that resolve be an identity operation on any output of parse.

resolve' :: a -> a Source #

Same as resolve, but throws a ResolveFail exception if it cannot resolve. Although this function should not be used, it summarizes nicely the laws around Resolve:

parse' . pretty' . resolve' == id
resolve' . parse' = parse'

resolveVerbose :: a -> (a, Severity, [Issue]) Source #

Run resolution and get back the altered syntax tree, the highest Severity of issues, and the list of issues found. This allows you to see what corrections were applied to the tree. If the output severity is Error, the syntax tree returned will still be invalid.

Instances
Resolve Ident Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

Resolve TokenTree Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

Resolve TokenStream Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (WherePredicate a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (WhereClause a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (Visibility a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (UseTree a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (VariantData a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (Variant a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (TyParamBound a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (TyParam a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (Ty a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

Methods

resolve :: Ty a -> Either ResolveFail (Ty a) Source #

resolve' :: Ty a -> Ty a Source #

resolveVerbose :: Ty a -> (Ty a, Severity, [Issue]) Source #

resolveM :: Ty a -> ResolveM (Ty a)

(Typeable a, Monoid a) => Resolve (TraitRef a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (TraitItem a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (StructField a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (Stmt a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

Methods

resolve :: Stmt a -> Either ResolveFail (Stmt a) Source #

resolve' :: Stmt a -> Stmt a Source #

resolveVerbose :: Stmt a -> (Stmt a, Severity, [Issue]) Source #

resolveM :: Stmt a -> ResolveM (Stmt a)

(Typeable a, Monoid a) => Resolve (QSelf a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (PolyTraitRef a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (PathParameters a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (Path a) Source #

There are three potential instances for resolving a path (depending on what type it is). The Resolve instance for Path will let through any path.

Instance details

Defined in Language.Rust.Pretty.Resolve

Methods

resolve :: Path a -> Either ResolveFail (Path a) Source #

resolve' :: Path a -> Path a Source #

resolveVerbose :: Path a -> (Path a, Severity, [Issue]) Source #

resolveM :: Path a -> ResolveM (Path a)

(Typeable a, Monoid a) => Resolve (Pat a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

Methods

resolve :: Pat a -> Either ResolveFail (Pat a) Source #

resolve' :: Pat a -> Pat a Source #

resolveVerbose :: Pat a -> (Pat a, Severity, [Issue]) Source #

resolveM :: Pat a -> ResolveM (Pat a)

(Typeable a, Monoid a) => Resolve (MethodSig a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (Mac a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

Methods

resolve :: Mac a -> Either ResolveFail (Mac a) Source #

resolve' :: Mac a -> Mac a Source #

resolveVerbose :: Mac a -> (Mac a, Severity, [Issue]) Source #

resolveM :: Mac a -> ResolveM (Mac a)

Resolve (Lit a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

Methods

resolve :: Lit a -> Either ResolveFail (Lit a) Source #

resolve' :: Lit a -> Lit a Source #

resolveVerbose :: Lit a -> (Lit a, Severity, [Issue]) Source #

resolveM :: Lit a -> ResolveM (Lit a)

(Typeable a, Monoid a) => Resolve (SourceFile a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (LifetimeDef a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

Typeable a => Resolve (Lifetime a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (Item a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

Methods

resolve :: Item a -> Either ResolveFail (Item a) Source #

resolve' :: Item a -> Item a Source #

resolveVerbose :: Item a -> (Item a, Severity, [Issue]) Source #

resolveM :: Item a -> ResolveM (Item a)

(Typeable a, Monoid a) => Resolve (ImplItem a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (Generics a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (ForeignItem a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (FnDecl a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (FieldPat a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (Field a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (Expr a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

Methods

resolve :: Expr a -> Either ResolveFail (Expr a) Source #

resolve' :: Expr a -> Expr a Source #

resolveVerbose :: Expr a -> (Expr a, Severity, [Issue]) Source #

resolveM :: Expr a -> ResolveM (Expr a)

(Typeable a, Monoid a) => Resolve (Block a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (Attribute a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

(Typeable a, Monoid a) => Resolve (Arm a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

Methods

resolve :: Arm a -> Either ResolveFail (Arm a) Source #

resolve' :: Arm a -> Arm a Source #

resolveVerbose :: Arm a -> (Arm a, Severity, [Issue]) Source #

resolveM :: Arm a -> ResolveM (Arm a)

(Typeable a, Monoid a) => Resolve (Arg a) Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

Methods

resolve :: Arg a -> Either ResolveFail (Arg a) Source #

resolve' :: Arg a -> Arg a Source #

resolveVerbose :: Arg a -> (Arg a, Severity, [Issue]) Source #

resolveM :: Arg a -> ResolveM (Arg a)

data Issue Source #

Localized information about an issue in a syntax tree.

Constructors

Issue 

Fields

  • description :: String

    Description of the issue

  • severity :: !Severity

    Severity of the issue

  • location :: [Dynamic]

    The first element in this list is the syntax tree where the issue occurs. The next elements are increasingly zoomed out syntax trees centered on the first element. In lieu of positional information, this provides a next best way of debugging exactly where the problem is.

Instances
Show Issue Source # 
Instance details

Defined in Language.Rust.Pretty.Resolve

Methods

showsPrec :: Int -> Issue -> ShowS #

show :: Issue -> String #

showList :: [Issue] -> ShowS #

data Severity Source #

Diagnostic for how severe an Issue is.

Constructors

Clean

Everything is normal (this variant is returned when there was nothing to resolve)

Warning

There is something fishy looking (AST is valid, but may not be what you expect)

Correction

The AST was invalid, but in a way that could be corrected

Error

The AST was invalid in some way that could not be automatically fixed

data ResolveFail Source #

Exceptions that occur during resolving. Unlike parse errors, we don't have positional information. Instead, we try to provide some context via a list of syntax trees which let you "zoom out" from the problematic node.

Constructors

ResolveFail [Dynamic] String