hnix-0.16.0: Haskell implementation of the Nix language
Safe HaskellNone
LanguageHaskell2010

Nix.Pretty

Synopsis

Documentation

data NixDoc ann Source #

This type represents a pretty printed nix expression together with some information about the expression.

Constructors

NixDoc 

Fields

  • getDoc :: Doc ann

    Rendered expression. Without surrounding parenthesis.

  • rootOp :: OperatorInfo

    The root operator is the operator at the root of the expression tree. For example, in '(a * b) + c', + would be the root operator. It is needed to determine if we need to wrap the expression in parentheses.

  • wasPath :: Bool
     

antiquote :: NixDoc ann -> Doc ann Source #

Represent Nix antiquotes.

${ expr }

simpleExpr :: Doc ann -> NixDoc ann Source #

A simple expression is never wrapped in parentheses. The expression behaves as if its root operator had a precedence higher than all other operators (including function application).

pathExpr :: Doc ann -> NixDoc ann Source #

leastPrecedence :: Doc ann -> NixDoc ann Source #

An expression that behaves as if its root operator had a precedence lower than all other operators. That ensures that the expression is wrapped in parentheses in almost always, but it's still rendered without parentheses in cases where parentheses are never required (such as in the LHS of a binding).

precedenceWrap :: OperatorInfo -> NixDoc ann -> Doc ann Source #

Determine if to return doc wraped into parens, according the given operator.

prettyString :: NString (NixDoc ann) -> Doc ann Source #

Handle Output representation of the string escape codes.

prettyParamSet :: forall ann. Variadic -> ParamSet (NixDoc ann) -> Doc ann Source #

prettyOriginExpr :: forall t f m ann. HasCitations1 m (NValue t f m) f => NExprLocF (Maybe (NValue t f m)) -> Doc ann Source #

prettyExtractFromProvenance :: forall t f m ann. HasCitations1 m (NValue t f m) f => [Provenance m (NValue t f m)] -> Doc ann Source #

Takes original expression from inside provenance information. Prettifies that expression.

exprFNixDoc :: forall ann. NExprF (NixDoc ann) -> NixDoc ann Source #

valueToExpr :: forall t f m. MonadDataContext f m => NValue t f m -> NExpr Source #

prettyNValue :: forall t f m ann. MonadDataContext f m => NValue t f m -> Doc ann Source #

data ValueOrigin Source #

During the output, which can print only representation of value, lazy thunks need to looked into & so - be evaluated (*sic) This type is a simple manual witness "is the thunk gets shown".

Constructors

WasThunk 
Value 

Instances

Instances details
Eq ValueOrigin Source # 
Instance details

Defined in Nix.Pretty

prettyProv Source #

Arguments

:: forall t f m ann. (HasCitations m (NValue t f m) t, HasCitations1 m (NValue t f m) f, MonadThunk t m (NValue t f m), MonadDataContext f m) 
=> ValueOrigin

Was thunk?

-> NValue t f m 
-> Doc ann 

prettyNValueProv :: forall t f m ann. (HasCitations m (NValue t f m) t, HasCitations1 m (NValue t f m) f, MonadThunk t m (NValue t f m), MonadDataContext f m) => NValue t f m -> Doc ann Source #

prettyNThunk :: forall t f m ann. (HasCitations m (NValue t f m) t, HasCitations1 m (NValue t f m) f, MonadThunk t m (NValue t f m), MonadDataContext f m) => t -> m (Doc ann) Source #

printNix :: forall t f m. MonadDataContext f m => NValue t f m -> Text Source #

This function is used only by the testing code.