{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE PatternSynonyms #-}

module Distribution.Types.ComponentName (
  ComponentName(.., CFLibName, CExeName, CTestName, CBenchName),
  showComponentName,
  componentNameRaw,
  componentNameStanza,
  componentNameString,
  ) where

import Prelude ()
import Distribution.Compat.Prelude

import Distribution.Types.UnqualComponentName
import Distribution.Types.LibraryName
import Distribution.Pretty
import Distribution.Parsec

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

-- Libraries live in a separate namespace, so must distinguish
data ComponentName = CLibName   LibraryName
                   | CNotLibName NotLibComponentName
                   deriving (ComponentName -> ComponentName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ComponentName -> ComponentName -> Bool
$c/= :: ComponentName -> ComponentName -> Bool
== :: ComponentName -> ComponentName -> Bool
$c== :: ComponentName -> ComponentName -> Bool
Eq, forall x. Rep ComponentName x -> ComponentName
forall x. ComponentName -> Rep ComponentName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ComponentName x -> ComponentName
$cfrom :: forall x. ComponentName -> Rep ComponentName x
Generic, Eq ComponentName
ComponentName -> ComponentName -> Bool
ComponentName -> ComponentName -> Ordering
ComponentName -> ComponentName -> ComponentName
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
min :: ComponentName -> ComponentName -> ComponentName
$cmin :: ComponentName -> ComponentName -> ComponentName
max :: ComponentName -> ComponentName -> ComponentName
$cmax :: ComponentName -> ComponentName -> ComponentName
>= :: ComponentName -> ComponentName -> Bool
$c>= :: ComponentName -> ComponentName -> Bool
> :: ComponentName -> ComponentName -> Bool
$c> :: ComponentName -> ComponentName -> Bool
<= :: ComponentName -> ComponentName -> Bool
$c<= :: ComponentName -> ComponentName -> Bool
< :: ComponentName -> ComponentName -> Bool
$c< :: ComponentName -> ComponentName -> Bool
compare :: ComponentName -> ComponentName -> Ordering
$ccompare :: ComponentName -> ComponentName -> Ordering
Ord, ReadPrec [ComponentName]
ReadPrec ComponentName
Int -> ReadS ComponentName
ReadS [ComponentName]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ComponentName]
$creadListPrec :: ReadPrec [ComponentName]
readPrec :: ReadPrec ComponentName
$creadPrec :: ReadPrec ComponentName
readList :: ReadS [ComponentName]
$creadList :: ReadS [ComponentName]
readsPrec :: Int -> ReadS ComponentName
$creadsPrec :: Int -> ReadS ComponentName
Read, Int -> ComponentName -> ShowS
[ComponentName] -> ShowS
ComponentName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ComponentName] -> ShowS
$cshowList :: [ComponentName] -> ShowS
show :: ComponentName -> String
$cshow :: ComponentName -> String
showsPrec :: Int -> ComponentName -> ShowS
$cshowsPrec :: Int -> ComponentName -> ShowS
Show, Typeable)

data NotLibComponentName
                   = CNLFLibName  { NotLibComponentName -> UnqualComponentName
toCompName :: UnqualComponentName }
                   | CNLExeName   { toCompName :: UnqualComponentName }
                   | CNLTestName  { toCompName :: UnqualComponentName }
                   | CNLBenchName { toCompName :: UnqualComponentName }
                   deriving (NotLibComponentName -> NotLibComponentName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NotLibComponentName -> NotLibComponentName -> Bool
$c/= :: NotLibComponentName -> NotLibComponentName -> Bool
== :: NotLibComponentName -> NotLibComponentName -> Bool
$c== :: NotLibComponentName -> NotLibComponentName -> Bool
Eq, forall x. Rep NotLibComponentName x -> NotLibComponentName
forall x. NotLibComponentName -> Rep NotLibComponentName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NotLibComponentName x -> NotLibComponentName
$cfrom :: forall x. NotLibComponentName -> Rep NotLibComponentName x
Generic, Eq NotLibComponentName
NotLibComponentName -> NotLibComponentName -> Bool
NotLibComponentName -> NotLibComponentName -> Ordering
NotLibComponentName -> NotLibComponentName -> NotLibComponentName
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
min :: NotLibComponentName -> NotLibComponentName -> NotLibComponentName
$cmin :: NotLibComponentName -> NotLibComponentName -> NotLibComponentName
max :: NotLibComponentName -> NotLibComponentName -> NotLibComponentName
$cmax :: NotLibComponentName -> NotLibComponentName -> NotLibComponentName
>= :: NotLibComponentName -> NotLibComponentName -> Bool
$c>= :: NotLibComponentName -> NotLibComponentName -> Bool
> :: NotLibComponentName -> NotLibComponentName -> Bool
$c> :: NotLibComponentName -> NotLibComponentName -> Bool
<= :: NotLibComponentName -> NotLibComponentName -> Bool
$c<= :: NotLibComponentName -> NotLibComponentName -> Bool
< :: NotLibComponentName -> NotLibComponentName -> Bool
$c< :: NotLibComponentName -> NotLibComponentName -> Bool
compare :: NotLibComponentName -> NotLibComponentName -> Ordering
$ccompare :: NotLibComponentName -> NotLibComponentName -> Ordering
Ord, ReadPrec [NotLibComponentName]
ReadPrec NotLibComponentName
Int -> ReadS NotLibComponentName
ReadS [NotLibComponentName]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NotLibComponentName]
$creadListPrec :: ReadPrec [NotLibComponentName]
readPrec :: ReadPrec NotLibComponentName
$creadPrec :: ReadPrec NotLibComponentName
readList :: ReadS [NotLibComponentName]
$creadList :: ReadS [NotLibComponentName]
readsPrec :: Int -> ReadS NotLibComponentName
$creadsPrec :: Int -> ReadS NotLibComponentName
Read, Int -> NotLibComponentName -> ShowS
[NotLibComponentName] -> ShowS
NotLibComponentName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NotLibComponentName] -> ShowS
$cshowList :: [NotLibComponentName] -> ShowS
show :: NotLibComponentName -> String
$cshow :: NotLibComponentName -> String
showsPrec :: Int -> NotLibComponentName -> ShowS
$cshowsPrec :: Int -> NotLibComponentName -> ShowS
Show, Typeable)

pattern CFLibName :: UnqualComponentName -> ComponentName
pattern $bCFLibName :: UnqualComponentName -> ComponentName
$mCFLibName :: forall {r}.
ComponentName -> (UnqualComponentName -> r) -> ((# #) -> r) -> r
CFLibName  n = CNotLibName (CNLFLibName  n)

pattern CExeName :: UnqualComponentName -> ComponentName
pattern $bCExeName :: UnqualComponentName -> ComponentName
$mCExeName :: forall {r}.
ComponentName -> (UnqualComponentName -> r) -> ((# #) -> r) -> r
CExeName   n = CNotLibName (CNLExeName   n)

pattern CTestName :: UnqualComponentName -> ComponentName
pattern $bCTestName :: UnqualComponentName -> ComponentName
$mCTestName :: forall {r}.
ComponentName -> (UnqualComponentName -> r) -> ((# #) -> r) -> r
CTestName  n = CNotLibName (CNLTestName  n)

pattern CBenchName :: UnqualComponentName -> ComponentName
pattern $bCBenchName :: UnqualComponentName -> ComponentName
$mCBenchName :: forall {r}.
ComponentName -> (UnqualComponentName -> r) -> ((# #) -> r) -> r
CBenchName n = CNotLibName (CNLBenchName n)
{-# COMPLETE CLibName, CFLibName, CExeName, CTestName, CBenchName #-}

instance Binary NotLibComponentName
instance Structured NotLibComponentName

instance Binary ComponentName
instance Structured ComponentName

-- Build-target-ish syntax
instance Pretty ComponentName where
    pretty :: ComponentName -> Doc
pretty (CLibName LibraryName
lib)    = LibraryName -> Doc
prettyLibraryNameComponent LibraryName
lib
    pretty (CFLibName UnqualComponentName
str)   = String -> Doc
Disp.text String
"flib:" Doc -> Doc -> Doc
<<>> forall a. Pretty a => a -> Doc
pretty UnqualComponentName
str
    pretty (CExeName UnqualComponentName
str)    = String -> Doc
Disp.text String
"exe:" Doc -> Doc -> Doc
<<>> forall a. Pretty a => a -> Doc
pretty UnqualComponentName
str
    pretty (CTestName UnqualComponentName
str)   = String -> Doc
Disp.text String
"test:" Doc -> Doc -> Doc
<<>> forall a. Pretty a => a -> Doc
pretty UnqualComponentName
str
    pretty (CBenchName UnqualComponentName
str)  = String -> Doc
Disp.text String
"bench:" Doc -> Doc -> Doc
<<>> forall a. Pretty a => a -> Doc
pretty UnqualComponentName
str

instance Parsec ComponentName where
    -- note: this works as lib/flib/... all start with different character!
    parsec :: forall (m :: * -> *). CabalParsing m => m ComponentName
parsec = m ComponentName
parseComposite forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> m ComponentName
parseLib
      where
        parseLib :: m ComponentName
parseLib = LibraryName -> ComponentName
CLibName forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). CabalParsing m => m LibraryName
parsecLibraryNameComponent
        parseComposite :: m ComponentName
parseComposite = do
            UnqualComponentName -> ComponentName
ctor <- forall (m :: * -> *) a. Alternative m => [m a] -> m a
P.choice
                [ forall (m :: * -> *). CharParsing m => String -> m String
P.string String
"flib:" forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return UnqualComponentName -> ComponentName
CFLibName
                , forall (m :: * -> *). CharParsing m => String -> m String
P.string String
"exe:" forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return UnqualComponentName -> ComponentName
CExeName
                , forall (m :: * -> *). CharParsing m => String -> m String
P.string String
"bench:" forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return UnqualComponentName -> ComponentName
CBenchName
                , forall (m :: * -> *). CharParsing m => String -> m String
P.string String
"test:" forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return UnqualComponentName -> ComponentName
CTestName
                ]
            UnqualComponentName -> ComponentName
ctor forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec

showComponentName :: ComponentName -> String
showComponentName :: ComponentName -> String
showComponentName (CLibName LibraryName
lib)    = LibraryName -> String
showLibraryName LibraryName
lib
showComponentName (CFLibName  UnqualComponentName
name) = String
"foreign library '" forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> String
prettyShow UnqualComponentName
name forall a. [a] -> [a] -> [a]
++ String
"'"
showComponentName (CExeName   UnqualComponentName
name) = String
"executable '" forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> String
prettyShow UnqualComponentName
name forall a. [a] -> [a] -> [a]
++ String
"'"
showComponentName (CTestName  UnqualComponentName
name) = String
"test suite '" forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> String
prettyShow UnqualComponentName
name forall a. [a] -> [a] -> [a]
++ String
"'"
showComponentName (CBenchName UnqualComponentName
name) = String
"benchmark '" forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> String
prettyShow UnqualComponentName
name forall a. [a] -> [a] -> [a]
++ String
"'"

componentNameRaw :: ComponentName -> String
componentNameRaw :: ComponentName -> String
componentNameRaw l :: ComponentName
l@(CLibName  LibraryName
_) = ComponentName -> String
showComponentName ComponentName
l
componentNameRaw (CNotLibName NotLibComponentName
x) = forall a. Pretty a => a -> String
prettyShow forall a b. (a -> b) -> a -> b
$ NotLibComponentName -> UnqualComponentName
toCompName NotLibComponentName
x

componentNameStanza :: ComponentName -> String
componentNameStanza :: ComponentName -> String
componentNameStanza (CLibName LibraryName
lib)    = LibraryName -> String
libraryNameStanza LibraryName
lib
componentNameStanza (CFLibName  UnqualComponentName
name) = String
"foreign-library " forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> String
prettyShow UnqualComponentName
name
componentNameStanza (CExeName   UnqualComponentName
name) = String
"executable " forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> String
prettyShow UnqualComponentName
name
componentNameStanza (CTestName  UnqualComponentName
name) = String
"test-suite " forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> String
prettyShow UnqualComponentName
name
componentNameStanza (CBenchName UnqualComponentName
name) = String
"benchmark " forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> String
prettyShow UnqualComponentName
name

-- | This gets the underlying unqualified component name. In fact, it is
-- guaranteed to uniquely identify a component, returning
-- @Nothing@ if the 'ComponentName' was for the public
-- library.
componentNameString :: ComponentName -> Maybe UnqualComponentName
componentNameString :: ComponentName -> Maybe UnqualComponentName
componentNameString (CLibName  LibraryName
lib) = LibraryName -> Maybe UnqualComponentName
libraryNameString LibraryName
lib
componentNameString (CNotLibName NotLibComponentName
x) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ NotLibComponentName -> UnqualComponentName
toCompName NotLibComponentName
x