Skip to content

Commit

Permalink
Handle Cartfile entries with no new lines at EOL
Browse files Browse the repository at this point in the history
  • Loading branch information
tmspzz committed Feb 13, 2019
1 parent 15b2993 commit cb95a54
Show file tree
Hide file tree
Showing 3 changed files with 46 additions and 19 deletions.
1 change: 1 addition & 0 deletions src/Configuration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ import qualified Data.Text.IO as T
import System.Directory
import System.FilePath
import Types
import Debug.Trace


getCartfileEntires :: RomeMonad [CartfileEntry]
Expand Down
42 changes: 34 additions & 8 deletions src/Data/Carthage/Cartfile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ import qualified Text.Parsec as Parsec
import qualified Text.Parsec.String as Parsec
import qualified Text.Parsec.Utils as Parsec
import Data.Carthage.Common
import Debug.Trace

newtype Location = Location { unLocation :: String }
deriving (Eq, Show, Ord)
Expand Down Expand Up @@ -55,20 +56,45 @@ quotedContent :: Parsec.Parsec String () String
quotedContent =
Parsec.char '"' *> Parsec.parseUnquotedString <* Parsec.char '"'

parseCartfileResolvedLine :: Parsec.Parsec String () CartfileEntry
parseCartfileResolvedLine = do
parseCartfileEntry :: Parsec.Parsec String () CartfileEntry
parseCartfileEntry = do
hosting <- repoHosting
location <- Location <$> quotedContent
_ <- Parsec.many1 Parsec.space
version <- Version <$> quotedContent
return CartfileEntry {..}

parseMaybeCartfileEntry :: Parsec.Parsec String () (Maybe CartfileEntry)
parseMaybeCartfileEntry =
Parsec.optional Parsec.spaces
*> (parseCartfileResolvedLine `Parsec.onceAndConsumeTill` Parsec.endOfLine)

parseCartfileResolved
:: MonadIO m => String -> m (Either Parsec.ParseError [CartfileEntry])
parseCartfileResolved = liftIO . Parsec.parseFromFile
(catMaybes <$> Parsec.many (Parsec.try parseMaybeCartfileEntry))
( catMaybes
<$> ( (Parsec.many $ do
line <-
Parsec.optional Parsec.endOfLine
*> ( Parsec.try parseEmtpyLine
<|> Parsec.try parseDependency
<|> Parsec.try parseComment
)
<* Parsec.optional Parsec.endOfLine
case line of
Dependency entry ->
return $ Just entry
_ -> return Nothing
)
<* Parsec.eof
)
)

data CartfileLine = EmptyLine | Comment | Dependency { entry :: CartfileEntry } deriving (Eq, Show)

parseDependency :: Parsec.Parsec String () CartfileLine
parseDependency = Dependency <$> parseCartfileEntry

parseComment :: Parsec.Parsec String () CartfileLine
parseComment =
Parsec.char '#'
>> Parsec.manyTill Parsec.anyChar (Parsec.lookAhead Parsec.endOfLine)
>> return Comment

parseEmtpyLine :: Parsec.Parsec String () CartfileLine
parseEmtpyLine = Parsec.many1 Parsec.space >> return EmptyLine
22 changes: 11 additions & 11 deletions src/Text/Parsec/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
module Text.Parsec.Utils
( parseWhiteSpaces
, parseUnquotedString
, onceAndConsumeTill
-- , onceAndConsumeTill
) where


Expand All @@ -23,13 +23,13 @@ parseUnquotedString =
Parsec.many1 (Parsec.noneOf ['"', ' ', '\t', '\n', '\'', '\\', '\r'])


-- | @onceOrConsumeTill p@ end@ tries to apply the parser @p@ /once/ and consumes
-- | the input until @end@. Returns a `Maybe` of the value of @p@.
-- | Thanks to Tobias Mayer, Berlin Haskell Group.
onceAndConsumeTill
:: (Parsec.Stream s Identity Char)
=> Parsec.Parsec s u a
-> Parsec.Parsec s u b
-> Parsec.Parsec s u (Maybe a)
onceAndConsumeTill p end = Parsec.optionMaybe (Parsec.try p) <* consume
where consume = Parsec.try end <|> Parsec.anyChar *> consume
-- -- | @onceOrConsumeTill p@ end@ tries to apply the parser @p@ /once/ and consumes
-- -- | the input until @end@. Returns a `Maybe` of the value of @p@.
-- -- | Thanks to Tobias Mayer, Berlin Haskell Group.
-- onceAndConsumeTill
-- :: (Parsec.Stream s Identity Char)
-- => Parsec.Parsec s u a
-- -> Parsec.Parsec s u b
-- -> Parsec.Parsec s u (Maybe a)
-- onceAndConsumeTill p end = Parsec.optionMaybe (Parsec.try p) <* consume
-- where consume = Parsec.try end <|> Parsec.anyChar *> consume

0 comments on commit cb95a54

Please sign in to comment.