{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

module Distribution.Types.PkgconfigName
  ( PkgconfigName
  , unPkgconfigName
  , mkPkgconfigName
  ) where

import Distribution.Compat.Prelude
import Distribution.Utils.ShortText
import Prelude ()

import Distribution.Parsec
import Distribution.Pretty

import qualified Distribution.Compat.CharParsing as P
import qualified Text.PrettyPrint as Disp

-- | A pkg-config library name
--
-- This is parsed as any valid argument to the pkg-config utility.
--
-- @since 2.0.0.2
newtype PkgconfigName = PkgconfigName ShortText
  deriving ((forall x. PkgconfigName -> Rep PkgconfigName x)
-> (forall x. Rep PkgconfigName x -> PkgconfigName)
-> Generic PkgconfigName
forall x. Rep PkgconfigName x -> PkgconfigName
forall x. PkgconfigName -> Rep PkgconfigName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PkgconfigName -> Rep PkgconfigName x
from :: forall x. PkgconfigName -> Rep PkgconfigName x
$cto :: forall x. Rep PkgconfigName x -> PkgconfigName
to :: forall x. Rep PkgconfigName x -> PkgconfigName
Generic, ReadPrec [PkgconfigName]
ReadPrec PkgconfigName
Int -> ReadS PkgconfigName
ReadS [PkgconfigName]
(Int -> ReadS PkgconfigName)
-> ReadS [PkgconfigName]
-> ReadPrec PkgconfigName
-> ReadPrec [PkgconfigName]
-> Read PkgconfigName
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PkgconfigName
readsPrec :: Int -> ReadS PkgconfigName
$creadList :: ReadS [PkgconfigName]
readList :: ReadS [PkgconfigName]
$creadPrec :: ReadPrec PkgconfigName
readPrec :: ReadPrec PkgconfigName
$creadListPrec :: ReadPrec [PkgconfigName]
readListPrec :: ReadPrec [PkgconfigName]
Read, Int -> PkgconfigName -> ShowS
[PkgconfigName] -> ShowS
PkgconfigName -> String
(Int -> PkgconfigName -> ShowS)
-> (PkgconfigName -> String)
-> ([PkgconfigName] -> ShowS)
-> Show PkgconfigName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PkgconfigName -> ShowS
showsPrec :: Int -> PkgconfigName -> ShowS
$cshow :: PkgconfigName -> String
show :: PkgconfigName -> String
$cshowList :: [PkgconfigName] -> ShowS
showList :: [PkgconfigName] -> ShowS
Show, PkgconfigName -> PkgconfigName -> Bool
(PkgconfigName -> PkgconfigName -> Bool)
-> (PkgconfigName -> PkgconfigName -> Bool) -> Eq PkgconfigName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PkgconfigName -> PkgconfigName -> Bool
== :: PkgconfigName -> PkgconfigName -> Bool
$c/= :: PkgconfigName -> PkgconfigName -> Bool
/= :: PkgconfigName -> PkgconfigName -> Bool
Eq, Eq PkgconfigName
Eq PkgconfigName =>
(PkgconfigName -> PkgconfigName -> Ordering)
-> (PkgconfigName -> PkgconfigName -> Bool)
-> (PkgconfigName -> PkgconfigName -> Bool)
-> (PkgconfigName -> PkgconfigName -> Bool)
-> (PkgconfigName -> PkgconfigName -> Bool)
-> (PkgconfigName -> PkgconfigName -> PkgconfigName)
-> (PkgconfigName -> PkgconfigName -> PkgconfigName)
-> Ord PkgconfigName
PkgconfigName -> PkgconfigName -> Bool
PkgconfigName -> PkgconfigName -> Ordering
PkgconfigName -> PkgconfigName -> PkgconfigName
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PkgconfigName -> PkgconfigName -> Ordering
compare :: PkgconfigName -> PkgconfigName -> Ordering
$c< :: PkgconfigName -> PkgconfigName -> Bool
< :: PkgconfigName -> PkgconfigName -> Bool
$c<= :: PkgconfigName -> PkgconfigName -> Bool
<= :: PkgconfigName -> PkgconfigName -> Bool
$c> :: PkgconfigName -> PkgconfigName -> Bool
> :: PkgconfigName -> PkgconfigName -> Bool
$c>= :: PkgconfigName -> PkgconfigName -> Bool
>= :: PkgconfigName -> PkgconfigName -> Bool
$cmax :: PkgconfigName -> PkgconfigName -> PkgconfigName
max :: PkgconfigName -> PkgconfigName -> PkgconfigName
$cmin :: PkgconfigName -> PkgconfigName -> PkgconfigName
min :: PkgconfigName -> PkgconfigName -> PkgconfigName
Ord, Typeable, Typeable PkgconfigName
Typeable PkgconfigName =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> PkgconfigName -> c PkgconfigName)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c PkgconfigName)
-> (PkgconfigName -> Constr)
-> (PkgconfigName -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c PkgconfigName))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c PkgconfigName))
-> ((forall b. Data b => b -> b) -> PkgconfigName -> PkgconfigName)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> PkgconfigName -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> PkgconfigName -> r)
-> (forall u. (forall d. Data d => d -> u) -> PkgconfigName -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> PkgconfigName -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> PkgconfigName -> m PkgconfigName)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> PkgconfigName -> m PkgconfigName)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> PkgconfigName -> m PkgconfigName)
-> Data PkgconfigName
PkgconfigName -> Constr
PkgconfigName -> DataType
(forall b. Data b => b -> b) -> PkgconfigName -> PkgconfigName
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> PkgconfigName -> u
forall u. (forall d. Data d => d -> u) -> PkgconfigName -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PkgconfigName -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PkgconfigName -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PkgconfigName -> m PkgconfigName
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PkgconfigName -> m PkgconfigName
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PkgconfigName
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PkgconfigName -> c PkgconfigName
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PkgconfigName)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PkgconfigName)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PkgconfigName -> c PkgconfigName
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PkgconfigName -> c PkgconfigName
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PkgconfigName
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PkgconfigName
$ctoConstr :: PkgconfigName -> Constr
toConstr :: PkgconfigName -> Constr
$cdataTypeOf :: PkgconfigName -> DataType
dataTypeOf :: PkgconfigName -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PkgconfigName)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PkgconfigName)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PkgconfigName)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PkgconfigName)
$cgmapT :: (forall b. Data b => b -> b) -> PkgconfigName -> PkgconfigName
gmapT :: (forall b. Data b => b -> b) -> PkgconfigName -> PkgconfigName
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PkgconfigName -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PkgconfigName -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PkgconfigName -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PkgconfigName -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PkgconfigName -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> PkgconfigName -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PkgconfigName -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PkgconfigName -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PkgconfigName -> m PkgconfigName
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PkgconfigName -> m PkgconfigName
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PkgconfigName -> m PkgconfigName
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PkgconfigName -> m PkgconfigName
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PkgconfigName -> m PkgconfigName
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PkgconfigName -> m PkgconfigName
Data)

-- | Convert 'PkgconfigName' to 'String'
--
-- @since 2.0.0.2
unPkgconfigName :: PkgconfigName -> String
unPkgconfigName :: PkgconfigName -> String
unPkgconfigName (PkgconfigName ShortText
s) = ShortText -> String
fromShortText ShortText
s

-- | Construct a 'PkgconfigName' from a 'String'
--
-- 'mkPkgconfigName' is the inverse to 'unPkgconfigName'
--
-- Note: No validations are performed to ensure that the resulting
-- 'PkgconfigName' is valid
--
-- @since 2.0.0.2
mkPkgconfigName :: String -> PkgconfigName
mkPkgconfigName :: String -> PkgconfigName
mkPkgconfigName = ShortText -> PkgconfigName
PkgconfigName (ShortText -> PkgconfigName)
-> (String -> ShortText) -> String -> PkgconfigName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShortText
toShortText

-- | 'mkPkgconfigName'
--
-- @since 2.0.0.2
instance IsString PkgconfigName where
  fromString :: String -> PkgconfigName
fromString = String -> PkgconfigName
mkPkgconfigName

instance Binary PkgconfigName
instance Structured PkgconfigName

-- pkg-config allows versions and other letters in package names, eg
-- "gtk+-2.0" is a valid pkg-config package _name_.  It then has a package
-- version number like 2.10.13
instance Pretty PkgconfigName where
  pretty :: PkgconfigName -> Doc
pretty = String -> Doc
Disp.text (String -> Doc)
-> (PkgconfigName -> String) -> PkgconfigName -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PkgconfigName -> String
unPkgconfigName

instance Parsec PkgconfigName where
  parsec :: forall (m :: * -> *). CabalParsing m => m PkgconfigName
parsec = String -> PkgconfigName
mkPkgconfigName (String -> PkgconfigName) -> m String -> m PkgconfigName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Bool) -> m String
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m String
P.munch1 Char -> Bool
isNameChar
    where
      -- https://gitlab.haskell.org/ghc/ghc/issues/17752
      isNameChar :: Char -> Bool
isNameChar Char
'-' = Bool
True
      isNameChar Char
'_' = Bool
True
      isNameChar Char
'.' = Bool
True
      isNameChar Char
'+' = Bool
True
      isNameChar Char
c = Char -> Bool
isAlphaNum Char
c

instance NFData PkgconfigName where
  rnf :: PkgconfigName -> ()
rnf (PkgconfigName ShortText
pkg) = ShortText -> ()
forall a. NFData a => a -> ()
rnf ShortText
pkg