module Distribution.Parsec.Newtypes (
alaList,
alaList',
CommaVCat (..),
CommaFSep (..),
VCat (..),
FSep (..),
NoCommaFSep (..),
List,
SpecVersion (..),
TestedWith (..),
Token (..),
Token' (..),
MQuoted (..),
FreeText (..),
FilePathNT (..),
) where
import Distribution.Compat.Newtype
import Distribution.Compat.Prelude
import Prelude ()
import Data.Functor.Identity (Identity (..))
import Data.List (dropWhileEnd)
import qualified Distribution.Compat.Parsec as P
import Distribution.Compiler (CompilerFlavor)
import Distribution.Parsec.Class
import Distribution.Parsec.Common (PWarning)
import Distribution.Pretty
import Distribution.Version (Version, VersionRange, anyVersion)
import Text.PrettyPrint (Doc, comma, fsep, punctuate, vcat, (<+>))
data CommaVCat = CommaVCat
data CommaFSep = CommaFSep
data VCat = VCat
data FSep = FSep
data NoCommaFSep = NoCommaFSep
data P sep = P
class Sep sep where
prettySep :: P sep -> [Doc] -> Doc
parseSep
:: P.Stream s Identity Char
=> P sep
-> P.Parsec s [PWarning] a
-> P.Parsec s [PWarning] [a]
instance Sep CommaVCat where
prettySep _ = vcat . punctuate comma
parseSep _ = parsecCommaList
instance Sep CommaFSep where
prettySep _ = fsep . punctuate comma
parseSep _ = parsecCommaList
instance Sep VCat where
prettySep _ = vcat
parseSep _ = parsecOptCommaList
instance Sep FSep where
prettySep _ = fsep
parseSep _ = parsecOptCommaList
instance Sep NoCommaFSep where
prettySep _ = fsep
parseSep _ p = many (p <* P.spaces)
newtype List sep b a = List { getList :: [a] }
alaList :: sep -> [a] -> List sep (Identity a) a
alaList _ = List
alaList' :: sep -> (a -> b) -> [a] -> List sep b a
alaList' _ _ = List
instance Newtype (List sep wrapper a) [a] where
pack = List
unpack = getList
instance (Newtype b a, Sep sep, Parsec b) => Parsec (List sep b a) where
parsec = pack . map (unpack :: b -> a) <$> parseSep (P :: P sep) parsec
instance (Newtype b a, Sep sep, Pretty b) => Pretty (List sep b a) where
pretty = prettySep (P :: P sep) . map (pretty . (pack :: a -> b)) . unpack
newtype Token = Token { getToken :: String }
instance Newtype Token String where
pack = Token
unpack = getToken
instance Parsec Token where
parsec = pack <$> parsecToken
instance Pretty Token where
pretty = showToken . unpack
newtype Token' = Token' { getToken' :: String }
instance Newtype Token' String where
pack = Token'
unpack = getToken'
instance Parsec Token' where
parsec = pack <$> parsecToken'
instance Pretty Token' where
pretty = showToken . unpack
newtype MQuoted a = MQuoted { getMQuoted :: a }
instance Newtype (MQuoted a) a where
pack = MQuoted
unpack = getMQuoted
instance Parsec a => Parsec (MQuoted a) where
parsec = pack <$> parsecMaybeQuoted parsec
instance Pretty a => Pretty (MQuoted a) where
pretty = pretty . unpack
newtype SpecVersion = SpecVersion { getSpecVersion :: Either Version VersionRange }
instance Newtype SpecVersion (Either Version VersionRange) where
pack = SpecVersion
unpack = getSpecVersion
instance Parsec SpecVersion where
parsec = pack <$> parsecSpecVersion
where
parsecSpecVersion = Left <$> parsec <|> Right <$> parsec
instance Pretty SpecVersion where
pretty = either pretty pretty . unpack
newtype TestedWith = TestedWith { getTestedWith :: (CompilerFlavor, VersionRange) }
instance Newtype TestedWith (CompilerFlavor, VersionRange) where
pack = TestedWith
unpack = getTestedWith
instance Parsec TestedWith where
parsec = pack <$> parsecTestedWith
instance Pretty TestedWith where
pretty x = case unpack x of
(compiler, vr) -> pretty compiler <+> pretty vr
newtype FreeText = FreeText { getFreeText :: String }
instance Newtype FreeText String where
pack = FreeText
unpack = getFreeText
instance Parsec FreeText where
parsec = pack . dropDotLines <$ P.spaces <*> many P.anyChar
where
dropDotLines "." = "."
dropDotLines x = intercalate "\n" . map dotToEmpty . lines $ x
dotToEmpty x | trim' x == "." = ""
dotToEmpty x = trim x
trim' :: String -> String
trim' = dropWhileEnd (`elem` (" \t" :: String))
trim :: String -> String
trim = dropWhile isSpace . dropWhileEnd isSpace
instance Pretty FreeText where
pretty = showFreeText . unpack
newtype FilePathNT = FilePathNT { getFilePathNT :: String }
instance Newtype FilePathNT String where
pack = FilePathNT
unpack = getFilePathNT
instance Parsec FilePathNT where
parsec = pack <$> parsecToken
instance Pretty FilePathNT where
pretty = showFilePath . unpack
parsecTestedWith :: P.Stream s Identity Char => P.Parsec s [PWarning] (CompilerFlavor, VersionRange)
parsecTestedWith = do
name <- lexemeParsec
ver <- parsec <|> pure anyVersion
return (name, ver)