Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data NixDoc ann = NixDoc {
- withoutParens :: Doc ann
- rootOp :: OperatorInfo
- wasPath :: Bool
- mkNixDoc :: Doc ann -> OperatorInfo -> NixDoc ann
- simpleExpr :: Doc ann -> NixDoc ann
- pathExpr :: Doc ann -> NixDoc ann
- leastPrecedence :: Doc ann -> NixDoc ann
- appOp :: OperatorInfo
- appOpNonAssoc :: OperatorInfo
- selectOp :: OperatorInfo
- hasAttrOp :: OperatorInfo
- wrapParens :: OperatorInfo -> NixDoc ann -> Doc ann
- wrapPath :: OperatorInfo -> NixDoc ann -> Doc ann
- prettyString :: NString (NixDoc ann) -> Doc ann
- prettyParams :: Params (NixDoc ann) -> Doc ann
- prettyParamSet :: ParamSet (NixDoc ann) -> Bool -> Doc ann
- prettyBind :: Binding (NixDoc ann) -> Doc ann
- prettyKeyName :: NKeyName (NixDoc ann) -> Doc ann
- prettySelector :: NAttrPath (NixDoc ann) -> Doc ann
- prettyAtom :: NAtom -> NixDoc ann
- prettyNix :: NExpr -> Doc ann
- prettyOriginExpr :: forall t f m ann. HasCitations1 m (NValue t f m) f => NExprLocF (Maybe (NValue t f m)) -> Doc ann
- exprFNixDoc :: NExprF (NixDoc ann) -> NixDoc ann
- valueToExpr :: forall t f m. MonadDataContext f m => NValue t f m -> NExpr
- prettyNValue :: forall t f m ann. MonadDataContext f m => 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
- 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)
- printNix :: forall t f m. MonadDataContext f m => NValue t f m -> String
Documentation
This type represents a pretty printed nix expression together with some information about the expression.
NixDoc | |
|
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).
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).
appOp :: OperatorInfo Source #
wrapParens :: OperatorInfo -> NixDoc ann -> Doc ann Source #
prettyAtom :: NAtom -> NixDoc ann Source #
prettyOriginExpr :: forall t f m ann. HasCitations1 m (NValue t f m) f => NExprLocF (Maybe (NValue t f m)) -> Doc 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 #
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 -> String Source #
This function is used only by the testing code.
Orphan instances
(HasCitations1 m v f, HasCitations m v t) => HasCitations m v (NValue t f m) Source # | |
citations :: NValue t f m -> [Provenance m v] Source # addProvenance :: Provenance m v -> NValue t f m -> NValue t f m Source # | |
HasCitations1 m v f => HasCitations m v (NValue' t f m a) Source # | |
citations :: NValue' t f m a -> [Provenance m v] Source # addProvenance :: Provenance m v -> NValue' t f m a -> NValue' t f m a Source # |