Skip to content

Commit

Permalink
Merge branch 'strict-text'
Browse files Browse the repository at this point in the history
  • Loading branch information
steshaw committed Jun 17, 2017
2 parents 8586f90 + bf87e6b commit 5ba720d
Showing 1 changed file with 21 additions and 20 deletions.
41 changes: 21 additions & 20 deletions haskell/nix-derivation-parser/src/Parser.hs
Expand Up @@ -6,22 +6,22 @@ module Parser where

import Control.DeepSeq (NFData)
import Control.Monad (void)
import Data.Attoparsec.Text.Lazy (Parser)
import Data.Attoparsec.Text (Parser)
import Data.Map (Map)
import Data.Monoid ((<>))
import Data.Set (Set)
import Data.Text (Text)
import Data.Vector (Vector)
import Filesystem.Path.CurrentOS (FilePath)
import GHC.Generics (Generic)
import Prelude hiding (FilePath)
import Prelude hiding (FilePath, id)

import qualified Data.Attoparsec.Text.Lazy
import qualified Data.Attoparsec.Text
import qualified Data.Map
import qualified Data.Set
import qualified Data.Text
import qualified Data.Text as T
import qualified Data.Text.Lazy
import qualified Data.Text.Lazy as Text.Lazy
import qualified Data.Vector
import qualified Filesystem.Path.CurrentOS

Expand Down Expand Up @@ -49,7 +49,7 @@ instance NFData DerivationOutput
listOf :: Parser a -> Parser [a]
listOf element = do
void "["
es <- Data.Attoparsec.Text.Lazy.sepBy element ","
es <- Data.Attoparsec.Text.sepBy element ","
void "]"
pure es

Expand All @@ -70,16 +70,16 @@ mapOf keyValue = do
slowString :: Parser Text
slowString = do
void "\""
s <- Data.Attoparsec.Text.Lazy.many' char
s <- Data.Attoparsec.Text.many' char
void "\""
pure $ T.pack s
where
char :: Parser Char
char = do
c1 <- Data.Attoparsec.Text.Lazy.notChar '"'
c1 <- Data.Attoparsec.Text.notChar '"'
case c1 of
'\\' -> do
c2 <- Data.Attoparsec.Text.Lazy.anyChar
c2 <- Data.Attoparsec.Text.anyChar
pure $
case c2 of
'n' -> '\n'
Expand All @@ -98,27 +98,28 @@ slowString = do
--
fastString :: Parser Text
fastString = do
void "\""
let predicate c = not (c == '"' || c == '\\')
let loop = do
text0 <- Data.Attoparsec.Text.Lazy.takeWhile predicate
char0 <- Data.Attoparsec.Text.Lazy.anyChar
let predicate :: Char -> Bool
predicate c = not (c == '"' || c == '\\')
loop :: Parser Text.Lazy.Text
loop = do
text0 <- Data.Attoparsec.Text.takeWhile predicate
char0 <- Data.Attoparsec.Text.anyChar
text2 <-
case char0 of
'"' -> return ""
_ -> do
char1 <- Data.Attoparsec.Text.Lazy.anyChar
char1 <- Data.Attoparsec.Text.anyChar
char2 <-
case char1 of
'n' -> return '\n'
'r' -> return '\r'
't' -> return '\t'
_ -> return char1
text1 <- loop
return (Data.Text.Lazy.cons char2 text1)
return (Data.Text.Lazy.fromStrict text0 <> text2)
text <- loop
return $ Data.Text.Lazy.toStrict text
return (Text.Lazy.cons char2 text1)
return $ Text.Lazy.fromStrict text0 <> text2
void "\""
Text.Lazy.toStrict <$> loop

string :: Parser Text
string =
Expand All @@ -139,15 +140,15 @@ parseDerivation = do
let keyValue0 :: Parser (Text, DerivationOutput)
keyValue0 = do
void "("
key <- string
id <- string
void ","
path <- filePath
void ","
hashAlgo <- string
void ","
hash <- string
void ")"
return (key, DerivationOutput {..})
return (id, DerivationOutput {..})
outputs <- mapOf keyValue0
void ","
let keyValue1 = do
Expand Down

0 comments on commit 5ba720d

Please sign in to comment.