Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type Parser = Parsec Void Text
- type ParseErrorBundle = ParseErrorBundle Text Void
- data Trivium
- = EmptyLine
- | LineComment Text
- | BlockComment [Text]
- type Trivia = [Trivium]
- newtype TrailingComment = TrailingComment Text
- data Ann a = Ann a (Maybe TrailingComment) Trivia
- type Leaf = Ann Token
- data StringPart
- type Path = Ann [StringPart]
- type String = Ann [[StringPart]]
- data SimpleSelector
- data Selector = Selector (Maybe Leaf) SimpleSelector (Maybe (Leaf, Term))
- data Binder
- data Term
- data ParamAttr
- = ParamAttr Leaf (Maybe (Leaf, Expression)) (Maybe Leaf)
- | ParamEllipsis Leaf
- data Parameter
- data Expression
- = Term Term
- | With Leaf Expression Leaf Expression
- | Let Leaf [Binder] Leaf Expression
- | Assert Leaf Expression Leaf Expression
- | If Leaf Expression Leaf Expression Leaf Expression
- | Abstraction Parameter Leaf Expression
- | Application Expression Expression
- | Operation Expression Leaf Expression
- | MemberCheck Expression Leaf [Selector]
- | Negation Leaf Expression
- | Inversion Leaf Expression
- data File = File Leaf Expression
- data Token
- = Integer Int
- | Float Double
- | Identifier Text
- | EnvPath Text
- | KAssert
- | KElse
- | KIf
- | KIn
- | KInherit
- | KLet
- | KOr
- | KRec
- | KThen
- | KWith
- | TBraceOpen
- | TBraceClose
- | TBrackOpen
- | TBrackClose
- | TInterOpen
- | TInterClose
- | TParenOpen
- | TParenClose
- | TAssign
- | TAt
- | TColon
- | TComma
- | TDot
- | TDoubleQuote
- | TDoubleSingleQuote
- | TEllipsis
- | TQuestion
- | TSemicolon
- | TConcat
- | TNegate
- | TUpdate
- | TPlus
- | TMinus
- | TMul
- | TDiv
- | TAnd
- | TOr
- | TEqual
- | TGreater
- | TGreaterEqual
- | TImplies
- | TLess
- | TLessEqual
- | TNot
- | TUnequal
- | SOF
- data Fixity
- data Operator
- operators :: [[Operator]]
- tokenText :: Token -> Text
Documentation
type ParseErrorBundle = ParseErrorBundle Text Void Source #
A megaparsec
ParseErrorBundle
specified for use with nixfmt
.
newtype TrailingComment Source #
Instances
Show TrailingComment Source # | |
Defined in Nixfmt.Types showsPrec :: Int -> TrailingComment -> ShowS # show :: TrailingComment -> String # showList :: [TrailingComment] -> ShowS # | |
Eq TrailingComment Source # | |
Defined in Nixfmt.Types (==) :: TrailingComment -> TrailingComment -> Bool # (/=) :: TrailingComment -> TrailingComment -> Bool # | |
Pretty TrailingComment Source # | |
Defined in Nixfmt.Pretty pretty :: TrailingComment -> Doc Source # |
data StringPart Source #
Instances
Show StringPart Source # | |
Defined in Nixfmt.Types showsPrec :: Int -> StringPart -> ShowS # show :: StringPart -> String # showList :: [StringPart] -> ShowS # | |
Eq StringPart Source # | |
Defined in Nixfmt.Types (==) :: StringPart -> StringPart -> Bool # (/=) :: StringPart -> StringPart -> Bool # | |
Pretty StringPart Source # | |
Defined in Nixfmt.Pretty pretty :: StringPart -> Doc Source # | |
Pretty [StringPart] Source # | |
Defined in Nixfmt.Pretty pretty :: [StringPart] -> Doc Source # | |
Pretty [[StringPart]] Source # | |
Defined in Nixfmt.Pretty pretty :: [[StringPart]] -> Doc Source # |
type Path = Ann [StringPart] Source #
type String = Ann [[StringPart]] Source #
data SimpleSelector Source #
Instances
Show SimpleSelector Source # | |
Defined in Nixfmt.Types showsPrec :: Int -> SimpleSelector -> ShowS # show :: SimpleSelector -> String # showList :: [SimpleSelector] -> ShowS # | |
Eq SimpleSelector Source # | |
Defined in Nixfmt.Types (==) :: SimpleSelector -> SimpleSelector -> Bool # (/=) :: SimpleSelector -> SimpleSelector -> Bool # | |
Pretty SimpleSelector Source # | |
Defined in Nixfmt.Pretty pretty :: SimpleSelector -> Doc Source # |
Token Leaf | |
String String | |
Path Path | |
List Leaf [Term] Leaf | |
Set (Maybe Leaf) Leaf [Binder] Leaf | |
Selection Term [Selector] | |
Parenthesized Leaf Expression Leaf |
ParamAttr Leaf (Maybe (Leaf, Expression)) (Maybe Leaf) | |
ParamEllipsis Leaf |
data Expression Source #
Instances
Show Expression Source # | |
Defined in Nixfmt.Types showsPrec :: Int -> Expression -> ShowS # show :: Expression -> String # showList :: [Expression] -> ShowS # | |
Eq Expression Source # | |
Defined in Nixfmt.Types (==) :: Expression -> Expression -> Bool # (/=) :: Expression -> Expression -> Bool # | |
Pretty Expression Source # | |
Defined in Nixfmt.Pretty pretty :: Expression -> Doc Source # |