-----------------------------------------------------------------------------

-- |
-- Module      :  Distribution.Lex
-- Copyright   :  Ben Gamari 2015-2019
--
-- Maintainer  :  cabal-devel@haskell.org
-- Portability :  portable
--
-- This module contains a simple lexer supporting quoted strings
module Distribution.Lex
  ( tokenizeQuotedWords
  ) where

import Distribution.Compat.DList
import Distribution.Compat.Prelude
import Prelude ()

-- | A simple parser supporting quoted strings.
--
-- Please be aware that this will only split strings when seeing whitespace
-- outside of quotation marks, i.e, @"foo\"bar baz\"qux quux"@ will be
-- converted to @["foobar bazqux", "quux"]@.
--
-- This behavior can be useful when parsing text like
-- @"ghc-options: -Wl,\"some option with spaces\""@, for instance.
tokenizeQuotedWords :: String -> [String]
tokenizeQuotedWords :: String -> [String]
tokenizeQuotedWords = (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (String -> Bool) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> DList Char -> String -> [String]
go Bool
False DList Char
forall a. Monoid a => a
mempty
  where
    go
      :: Bool
      -- \^ in quoted region
      -> DList Char
      -- \^ accumulator
      -> String
      -- \^ string to be parsed
      -> [String]
    -- \^ parse result
    go :: Bool -> DList Char -> String -> [String]
go Bool
_ DList Char
accum []
      | [] <- String
accum' = []
      | Bool
otherwise = [String
accum']
      where
        accum' :: String
accum' = DList Char -> String
forall a. DList a -> [a]
runDList DList Char
accum
    go Bool
False DList Char
accum (Char
c : String
cs)
      | Char -> Bool
isSpace Char
c = DList Char -> String
forall a. DList a -> [a]
runDList DList Char
accum String -> [String] -> [String]
forall a. a -> [a] -> [a]
: Bool -> DList Char -> String -> [String]
go Bool
False DList Char
forall a. Monoid a => a
mempty String
cs
      | Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'"' = Bool -> DList Char -> String -> [String]
go Bool
True DList Char
accum String
cs
    go Bool
True DList Char
accum (Char
c : String
cs)
      | Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'"' = Bool -> DList Char -> String -> [String]
go Bool
False DList Char
accum String
cs
    go Bool
quoted DList Char
accum (Char
c : String
cs) =
      Bool -> DList Char -> String -> [String]
go Bool
quoted (DList Char
accum DList Char -> DList Char -> DList Char
forall a. Monoid a => a -> a -> a
`mappend` Char -> DList Char
forall a. a -> DList a
singleton Char
c) String
cs