Skip to content

Commit e2f4232

Browse files
authored
Add support for Unix shebangs (#2175)
… as standardized in dhall-lang/dhall-lang#1158
1 parent 698101b commit e2f4232

File tree

3 files changed

+24
-15
lines changed

3 files changed

+24
-15
lines changed

dhall/src/Dhall/Parser/Expression.hs

Lines changed: 15 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,6 @@ module Dhall.Parser.Expression where
1010
import Control.Applicative (Alternative (..), liftA2, optional)
1111
import Data.ByteArray.Encoding (Base (..))
1212
import Data.Foldable (foldl')
13-
import Data.Functor (void)
1413
import Data.List.NonEmpty (NonEmpty (..))
1514
import Data.Text (Text)
1615
import Dhall.Src (Src (..))
@@ -113,7 +112,17 @@ data Parsers a = Parsers
113112
parsers :: forall a. Parser a -> Parsers a
114113
parsers embedded = Parsers {..}
115114
where
116-
completeExpression_ = whitespace *> expression <* whitespace
115+
completeExpression_ =
116+
optional shebang *> whitespace *> expression <* whitespace
117+
118+
shebang = do
119+
_ <- text "#!"
120+
121+
let predicate c = ('\x20' <= c && c <= '\x10FFFF') || c == '\t'
122+
123+
_ <- Dhall.Parser.Combinators.takeWhile predicate
124+
125+
endOfLine
117126

118127
expression =
119128
noted
@@ -718,7 +727,7 @@ parsers embedded = Parsers {..}
718727
, unescapedCharacterFast
719728
, unescapedCharacterSlow
720729
, tab
721-
, endOfLine
730+
, endOfLine_
722731
]
723732
where
724733
escapeSingleQuotes = do
@@ -757,7 +766,7 @@ parsers embedded = Parsers {..}
757766
where
758767
predicate c = c == '$' || c == '\''
759768

760-
endOfLine = do
769+
endOfLine_ = do
761770
a <- "\n" <|> "\r\n"
762771
b <- singleQuoteContinue
763772
return (Chunks [] a <> b)
@@ -769,12 +778,12 @@ parsers embedded = Parsers {..}
769778

770779
singleQuoteLiteral = do
771780
_ <- text "''"
781+
772782
_ <- endOfLine
783+
773784
a <- singleQuoteContinue
774785

775786
return (Dhall.Syntax.toDoubleQuoted a)
776-
where
777-
endOfLine = (void (char '\n') <|> void (text "\r\n")) <?> "newline"
778787

779788
textLiteral = (do
780789
literal <- doubleQuotedLiteral <|> singleQuoteLiteral

dhall/src/Dhall/Parser/Token.hs

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
-- | Parse Dhall tokens. Even though we don't have a tokenizer per-se this
55
--- module is useful for keeping some small parsing utilities.
66
module Dhall.Parser.Token (
7+
endOfLine,
78
validCodepoint,
89
whitespace,
910
lineComment,
@@ -135,6 +136,12 @@ import qualified Text.Parser.Token
135136

136137
import Numeric.Natural (Natural)
137138

139+
-- | Match an end-of-line character sequence
140+
endOfLine :: Parser Text
141+
endOfLine =
142+
( Text.Parser.Char.text "\n"
143+
<|> Text.Parser.Char.text "\r\n"
144+
) <?> "newline"
138145

139146
-- | Returns `True` if the given `Int` is a valid Unicode codepoint
140147
validCodepoint :: Int -> Bool
@@ -360,14 +367,9 @@ lineComment = do
360367

361368
commentText <- Dhall.Parser.Combinators.takeWhile predicate
362369

363-
endOfLine
370+
_ <- endOfLine
364371

365372
return ("--" <> commentText)
366-
where
367-
endOfLine =
368-
( void (Text.Parser.Char.char '\n' )
369-
<|> void (Text.Parser.Char.text "\r\n")
370-
) <?> "newline"
371373

372374
-- | Parsed text doesn't include opening braces
373375
blockComment :: Parser Text
@@ -396,8 +398,6 @@ blockCommentChunk =
396398
where
397399
predicate c = '\x20' <= c && c <= '\x10FFFF' || c == '\n' || c == '\t'
398400

399-
endOfLine = (Text.Parser.Char.text "\r\n" <?> "newline")
400-
401401
blockCommentContinue :: Parser Text
402402
blockCommentContinue = endOfComment <|> continue
403403
where

0 commit comments

Comments
 (0)