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

module Distribution.SPDX.LicenseReference
  ( LicenseRef
  , licenseRef
  , licenseDocumentRef
  , mkLicenseRef
  , mkLicenseRef'
  ) where

import Distribution.Compat.Prelude
import Prelude ()

import Distribution.Parsec
import Distribution.Pretty
import Distribution.Utils.Generic (isAsciiAlphaNum)

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

-- | A user defined license reference denoted by @LicenseRef-[idstring]@ (for a license not on the SPDX License List);
data LicenseRef = LicenseRef
  { LicenseRef -> Maybe String
_lrDocument :: !(Maybe String)
  , LicenseRef -> String
_lrLicense :: !String
  }
  deriving (Int -> LicenseRef -> ShowS
[LicenseRef] -> ShowS
LicenseRef -> String
(Int -> LicenseRef -> ShowS)
-> (LicenseRef -> String)
-> ([LicenseRef] -> ShowS)
-> Show LicenseRef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LicenseRef -> ShowS
showsPrec :: Int -> LicenseRef -> ShowS
$cshow :: LicenseRef -> String
show :: LicenseRef -> String
$cshowList :: [LicenseRef] -> ShowS
showList :: [LicenseRef] -> ShowS
Show, ReadPrec [LicenseRef]
ReadPrec LicenseRef
Int -> ReadS LicenseRef
ReadS [LicenseRef]
(Int -> ReadS LicenseRef)
-> ReadS [LicenseRef]
-> ReadPrec LicenseRef
-> ReadPrec [LicenseRef]
-> Read LicenseRef
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LicenseRef
readsPrec :: Int -> ReadS LicenseRef
$creadList :: ReadS [LicenseRef]
readList :: ReadS [LicenseRef]
$creadPrec :: ReadPrec LicenseRef
readPrec :: ReadPrec LicenseRef
$creadListPrec :: ReadPrec [LicenseRef]
readListPrec :: ReadPrec [LicenseRef]
Read, LicenseRef -> LicenseRef -> Bool
(LicenseRef -> LicenseRef -> Bool)
-> (LicenseRef -> LicenseRef -> Bool) -> Eq LicenseRef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LicenseRef -> LicenseRef -> Bool
== :: LicenseRef -> LicenseRef -> Bool
$c/= :: LicenseRef -> LicenseRef -> Bool
/= :: LicenseRef -> LicenseRef -> Bool
Eq, Eq LicenseRef
Eq LicenseRef =>
(LicenseRef -> LicenseRef -> Ordering)
-> (LicenseRef -> LicenseRef -> Bool)
-> (LicenseRef -> LicenseRef -> Bool)
-> (LicenseRef -> LicenseRef -> Bool)
-> (LicenseRef -> LicenseRef -> Bool)
-> (LicenseRef -> LicenseRef -> LicenseRef)
-> (LicenseRef -> LicenseRef -> LicenseRef)
-> Ord LicenseRef
LicenseRef -> LicenseRef -> Bool
LicenseRef -> LicenseRef -> Ordering
LicenseRef -> LicenseRef -> LicenseRef
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 :: LicenseRef -> LicenseRef -> Ordering
compare :: LicenseRef -> LicenseRef -> Ordering
$c< :: LicenseRef -> LicenseRef -> Bool
< :: LicenseRef -> LicenseRef -> Bool
$c<= :: LicenseRef -> LicenseRef -> Bool
<= :: LicenseRef -> LicenseRef -> Bool
$c> :: LicenseRef -> LicenseRef -> Bool
> :: LicenseRef -> LicenseRef -> Bool
$c>= :: LicenseRef -> LicenseRef -> Bool
>= :: LicenseRef -> LicenseRef -> Bool
$cmax :: LicenseRef -> LicenseRef -> LicenseRef
max :: LicenseRef -> LicenseRef -> LicenseRef
$cmin :: LicenseRef -> LicenseRef -> LicenseRef
min :: LicenseRef -> LicenseRef -> LicenseRef
Ord, Typeable, Typeable LicenseRef
Typeable LicenseRef =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> LicenseRef -> c LicenseRef)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c LicenseRef)
-> (LicenseRef -> Constr)
-> (LicenseRef -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c LicenseRef))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c LicenseRef))
-> ((forall b. Data b => b -> b) -> LicenseRef -> LicenseRef)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> LicenseRef -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> LicenseRef -> r)
-> (forall u. (forall d. Data d => d -> u) -> LicenseRef -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> LicenseRef -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> LicenseRef -> m LicenseRef)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> LicenseRef -> m LicenseRef)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> LicenseRef -> m LicenseRef)
-> Data LicenseRef
LicenseRef -> Constr
LicenseRef -> DataType
(forall b. Data b => b -> b) -> LicenseRef -> LicenseRef
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) -> LicenseRef -> u
forall u. (forall d. Data d => d -> u) -> LicenseRef -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LicenseRef -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LicenseRef -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> LicenseRef -> m LicenseRef
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LicenseRef -> m LicenseRef
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LicenseRef
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LicenseRef -> c LicenseRef
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LicenseRef)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LicenseRef)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LicenseRef -> c LicenseRef
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LicenseRef -> c LicenseRef
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LicenseRef
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LicenseRef
$ctoConstr :: LicenseRef -> Constr
toConstr :: LicenseRef -> Constr
$cdataTypeOf :: LicenseRef -> DataType
dataTypeOf :: LicenseRef -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LicenseRef)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LicenseRef)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LicenseRef)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LicenseRef)
$cgmapT :: (forall b. Data b => b -> b) -> LicenseRef -> LicenseRef
gmapT :: (forall b. Data b => b -> b) -> LicenseRef -> LicenseRef
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LicenseRef -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LicenseRef -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LicenseRef -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LicenseRef -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> LicenseRef -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> LicenseRef -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> LicenseRef -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> LicenseRef -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> LicenseRef -> m LicenseRef
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> LicenseRef -> m LicenseRef
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LicenseRef -> m LicenseRef
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LicenseRef -> m LicenseRef
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LicenseRef -> m LicenseRef
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LicenseRef -> m LicenseRef
Data, (forall x. LicenseRef -> Rep LicenseRef x)
-> (forall x. Rep LicenseRef x -> LicenseRef) -> Generic LicenseRef
forall x. Rep LicenseRef x -> LicenseRef
forall x. LicenseRef -> Rep LicenseRef x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LicenseRef -> Rep LicenseRef x
from :: forall x. LicenseRef -> Rep LicenseRef x
$cto :: forall x. Rep LicenseRef x -> LicenseRef
to :: forall x. Rep LicenseRef x -> LicenseRef
Generic)

-- | License reference.
licenseRef :: LicenseRef -> String
licenseRef :: LicenseRef -> String
licenseRef = LicenseRef -> String
_lrLicense

-- | Document reference.
licenseDocumentRef :: LicenseRef -> Maybe String
licenseDocumentRef :: LicenseRef -> Maybe String
licenseDocumentRef = LicenseRef -> Maybe String
_lrDocument

instance Binary LicenseRef
instance Structured LicenseRef

instance NFData LicenseRef where
  rnf :: LicenseRef -> ()
rnf (LicenseRef Maybe String
d String
l) = Maybe String -> ()
forall a. NFData a => a -> ()
rnf Maybe String
d () -> () -> ()
forall a b. a -> b -> b
`seq` String -> ()
forall a. NFData a => a -> ()
rnf String
l

instance Pretty LicenseRef where
  pretty :: LicenseRef -> Doc
pretty (LicenseRef Maybe String
Nothing String
l) = String -> Doc
Disp.text String
"LicenseRef-" Doc -> Doc -> Doc
<<>> String -> Doc
Disp.text String
l
  pretty (LicenseRef (Just String
d) String
l) =
    String -> Doc
Disp.text String
"DocumentRef-" Doc -> Doc -> Doc
<<>> String -> Doc
Disp.text String
d Doc -> Doc -> Doc
<<>> Char -> Doc
Disp.char Char
':' Doc -> Doc -> Doc
<<>> String -> Doc
Disp.text String
"LicenseRef-" Doc -> Doc -> Doc
<<>> String -> Doc
Disp.text String
l

instance Parsec LicenseRef where
  parsec :: forall (m :: * -> *). CabalParsing m => m LicenseRef
parsec = m LicenseRef
name m LicenseRef -> m LicenseRef -> m LicenseRef
forall a. m a -> m a -> m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> m LicenseRef
doc
    where
      name :: m LicenseRef
name = do
        _ <- String -> m String
forall (m :: * -> *). CharParsing m => String -> m String
P.string String
"LicenseRef-"
        n <- some $ P.satisfy $ \Char
c -> Char -> Bool
isAsciiAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.'
        pure (LicenseRef Nothing n)

      doc :: m LicenseRef
doc = do
        _ <- String -> m String
forall (m :: * -> *). CharParsing m => String -> m String
P.string String
"DocumentRef-"
        d <- some $ P.satisfy $ \Char
c -> Char -> Bool
isAsciiAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.'
        _ <- P.char ':'
        _ <- P.string "LicenseRef-"
        n <- some $ P.satisfy $ \Char
c -> Char -> Bool
isAsciiAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.'
        pure (LicenseRef (Just d) n)

-- | Create 'LicenseRef' from optional document ref and name.
mkLicenseRef :: Maybe String -> String -> Maybe LicenseRef
mkLicenseRef :: Maybe String -> String -> Maybe LicenseRef
mkLicenseRef Maybe String
d String
l = do
  d' <- (String -> Maybe String) -> Maybe String -> Maybe (Maybe String)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Maybe a -> f (Maybe b)
traverse String -> Maybe String
forall {t :: * -> *}. Foldable t => t Char -> Maybe (t Char)
checkIdString Maybe String
d
  l' <- checkIdString l
  pure (LicenseRef d' l')
  where
    checkIdString :: t Char -> Maybe (t Char)
checkIdString t Char
s
      | (Char -> Bool) -> t Char -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\Char
c -> Char -> Bool
isAsciiAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.') t Char
s = t Char -> Maybe (t Char)
forall a. a -> Maybe a
Just t Char
s
      | Bool
otherwise = Maybe (t Char)
forall a. Maybe a
Nothing

-- | Like 'mkLicenseRef' but convert invalid characters into @-@.
mkLicenseRef' :: Maybe String -> String -> LicenseRef
mkLicenseRef' :: Maybe String -> String -> LicenseRef
mkLicenseRef' Maybe String
d String
l = Maybe String -> String -> LicenseRef
LicenseRef (ShowS -> Maybe String -> Maybe String
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShowS
f Maybe String
d) (ShowS
f String
l)
  where
    f :: ShowS
f = (Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
g
    g :: Char -> Char
g Char
c
      | Char -> Bool
isAsciiAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.' = Char
c
      | Bool
otherwise = Char
'-'