-
Notifications
You must be signed in to change notification settings - Fork 8
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
- Loading branch information
Allen Nelson
committed
Jun 12, 2015
1 parent
78b43c4
commit 58cc658
Showing
9 changed files
with
415 additions
and
46 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1 @@ | ||
test*.nix |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -1,11 +1,16 @@ | ||
{-# LANGUAGE NoImplicitPrelude #-} | ||
module NixFromNpm (module NixFromNpm.Common, | ||
module NixFromNpm.SemVer, | ||
module NixFromNpm.ParseSemVer, | ||
module NixFromNpm.Parsers.Common, | ||
module NixFromNpm.Parsers.SemVer, | ||
module NixFromNpm.Parsers.NpmVersion, | ||
module NixFromNpm.Parsers.Nix, | ||
module NixFromNpm.NpmLookup) where | ||
|
||
import NixFromNpm.Common | ||
import NixFromNpm.SemVer | ||
import NixFromNpm.ParseSemVer | ||
import NixFromNpm.ParseNpmVersion | ||
import NixFromNpm.Parsers.Common (parse, parseFull) | ||
import NixFromNpm.Parsers.SemVer | ||
import NixFromNpm.Parsers.NpmVersion | ||
import NixFromNpm.Parsers.Nix hiding (Eq) | ||
import NixFromNpm.NpmLookup |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,42 @@ | ||
{-# LANGUAGE NoImplicitPrelude #-} | ||
{-# LANGUAGE OverloadedStrings #-} | ||
{-# LANGUAGE LambdaCase #-} | ||
module NixFromNpm.NixExpr where | ||
|
||
import NixFromNpm.Common | ||
|
||
data FuncArgs | ||
= Arg Name | ||
| Kwargs (HashMap Name (Maybe NixExpr)) Bool (Maybe Name) | ||
deriving (Show, Eq) | ||
|
||
data NixExpr | ||
= Var Name | ||
| Num Int | ||
| Bool Bool | ||
| Null | ||
| OneLineString NixString | ||
| MultiLineString NixString | ||
| Path FilePath | ||
| List [NixExpr] | ||
| Set [NixAssign] | ||
| Let [NixAssign] NixExpr | ||
| Function FuncArgs NixExpr | ||
| Apply NixExpr NixExpr | ||
| With NixExpr NixExpr | ||
| If NixExpr NixExpr NixExpr | ||
| Dot NixExpr [NixString] (Maybe NixExpr) | ||
| BinOp NixExpr Text NixExpr | ||
| Not NixExpr | ||
| Assert NixExpr NixExpr | ||
deriving (Show, Eq) | ||
|
||
data NixAssign | ||
= Assign [NixString] NixExpr | ||
| Inherit (Maybe NixExpr) (Set Name) | ||
deriving (Show, Eq) | ||
|
||
data NixString | ||
= Plain Text | ||
| Antiquote NixString NixExpr NixString | ||
deriving (Show, Eq) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,49 @@ | ||
{-# LANGUAGE NoImplicitPrelude #-} | ||
{-# LANGUAGE LambdaCase #-} | ||
{-# LANGUAGE OverloadedStrings #-} | ||
module NixFromNpm.Parsers.Common ( | ||
module Text.Parsec, | ||
module NixFromNpm.Common, | ||
Parser, | ||
parse, parseFull, spaces, spaces1, sstring, schar, lexeme, pInt | ||
) where | ||
|
||
import qualified Prelude as P | ||
import Text.Parsec hiding (many, (<|>), spaces, parse, State, uncons) | ||
import qualified Text.Parsec as Parsec | ||
|
||
import NixFromNpm.Common hiding (try) | ||
import NixFromNpm.SemVer | ||
|
||
type Parser = ParsecT String () Identity | ||
|
||
-- | Given a parser and a string, attempts to parse the string. | ||
parse :: Parser a -> Text -> Either ParseError a | ||
parse p = Parsec.parse p "" . unpack | ||
|
||
parseFull :: Parser a -> Text -> Either ParseError a | ||
parseFull p = Parsec.parse (p <* eof) "" . unpack | ||
|
||
-- | Consumes any spaces (not other whitespace). | ||
spaces :: Parser String | ||
spaces = many $ char ' ' | ||
|
||
-- | Consumes at least one space (not other whitespace). | ||
spaces1 :: Parser String | ||
spaces1 = many1 $ char ' ' | ||
|
||
-- | Parses the given string and any trailing spaces. | ||
sstring :: String -> Parser String | ||
sstring = lexeme . string | ||
|
||
-- | Parses the given character and any trailing spaces. | ||
schar :: Char -> Parser Char | ||
schar = lexeme . char | ||
|
||
-- | Parses `p` and any trailing spaces. | ||
lexeme :: Parser a -> Parser a | ||
lexeme p = p <* spaces | ||
|
||
-- | Parses an integer. | ||
pInt :: Parser Int | ||
pInt = lexeme $ P.read <$> many1 digit |
Oops, something went wrong.