Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- parseNixFile :: MonadFile m => FilePath -> m (Result NExpr)
- parseNixFileLoc :: MonadFile m => FilePath -> m (Result NExprLoc)
- parseNixText :: Text -> Result NExpr
- parseNixTextLoc :: Text -> Result NExprLoc
- parseFromFileEx :: MonadFile m => Parser a -> FilePath -> m (Result a)
- type Parser = ParsecT Void Text Identity
- parseFromText :: Parser a -> Text -> Result a
- data Result a
- reservedNames :: HashSet Text
- data OperatorInfo = OperatorInfo {
- precedence :: Int
- associativity :: NAssoc
- operatorName :: Text
- data NSpecialOp
- data NAssoc
- data NOperatorDef
- getUnaryOperator :: NUnaryOp -> OperatorInfo
- getBinaryOperator :: NBinaryOp -> OperatorInfo
- getSpecialOperator :: NSpecialOp -> OperatorInfo
- nixToplevelForm :: Parser NExprLoc
- nixExpr :: Parser NExprLoc
- nixSet :: Parser NExprLoc
- nixBinders :: Parser [Binding NExprLoc]
- nixSelector :: Parser (Ann SrcSpan (NAttrPath NExprLoc))
- nixSym :: Parser NExprLoc
- nixPath :: Parser NExprLoc
- nixString :: Parser NExprLoc
- nixUri :: Parser NExprLoc
- nixSearchPath :: Parser NExprLoc
- nixFloat :: Parser NExprLoc
- nixInt :: Parser NExprLoc
- nixBool :: Parser NExprLoc
- nixNull :: Parser NExprLoc
- symbol :: Text -> Parser Text
- whiteSpace :: Parser ()
Documentation
data OperatorInfo Source #
OperatorInfo | |
|
Instances
data NSpecialOp Source #
Instances
Instances
Eq NAssoc Source # | |
Data NAssoc Source # | |
Defined in Nix.Parser gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NAssoc -> c NAssoc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NAssoc # toConstr :: NAssoc -> Constr # dataTypeOf :: NAssoc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NAssoc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NAssoc) # gmapT :: (forall b. Data b => b -> b) -> NAssoc -> NAssoc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NAssoc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NAssoc -> r # gmapQ :: (forall d. Data d => d -> u) -> NAssoc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NAssoc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NAssoc -> m NAssoc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NAssoc -> m NAssoc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NAssoc -> m NAssoc # | |
Ord NAssoc Source # | |
Show NAssoc Source # | |
Generic NAssoc Source # | |
NFData NAssoc Source # | |
Defined in Nix.Parser | |
type Rep NAssoc Source # | |
Defined in Nix.Parser |
data NOperatorDef Source #
Instances
nixSearchPath :: Parser NExprLoc Source #
A path surrounded by angle brackets, indicating that it should be looked up in the NIX_PATH environment variable at evaluation.
whiteSpace :: Parser () Source #