-- |
--
module Distribution.SPDX.Extra (
  -- * Types
  -- | We don't export the constructors, as they change with Cabal version.
  License,
  LicenseExpression,
  SimpleLicenseExpression,
  LicenseId,
  LicenseExceptionId,

  -- * Logic
  satisfies,
  equivalent,
  ) where

import Distribution.SPDX
       (License (..), LicenseExceptionId, LicenseExpression (..), LicenseId,
       SimpleLicenseExpression (..))
import Distribution.SPDX.Extra.Internal (LatticeSyntax (..))

import qualified Distribution.SPDX.Extra.Internal as LS

-- |
--
-- @⟦ satisfies a b ⟧ ≡ a ≥ b ≡ a ∧ b = b @
--
-- >>> unsafeParseExpr "GPL-3.0-only" `satisfies` unsafeParseExpr "ISC AND MIT"
-- False
--
-- >>> unsafeParseExpr "Zlib" `satisfies` unsafeParseExpr "ISC AND MIT AND Zlib"
-- True
--
-- >>> unsafeParseExpr "(MIT OR GPL-2.0-only)" `satisfies` unsafeParseExpr "(ISC AND MIT)"
-- True
--
-- >>> unsafeParseExpr "(MIT AND GPL-2.0-only)" `satisfies` unsafeParseExpr "(MIT AND GPL-2.0-only)"
-- True
--
-- >>> unsafeParseExpr "(MIT AND GPL-2.0-only)" `satisfies` unsafeParseExpr "(ISC AND GPL-2.0-only)"
-- False
--
satisfies :: License -- ^ package license
          -> License -- ^ license policy
          -> Bool
satisfies :: License -> License -> Bool
satisfies License
a License
b = License -> LatticeSyntax Lic
exprToLSLic License
b LatticeSyntax Lic -> LatticeSyntax Lic -> Bool
forall a. Ord a => LatticeSyntax a -> LatticeSyntax a -> Bool
`LS.preorder` License -> LatticeSyntax Lic
exprToLSLic License
a

-- | Check wheather two 'LicenseExpression' are equivalent.
--
-- >>> unsafeParseExpr "(MIT AND GPL-2.0-only)" `equivalent` unsafeParseExpr "(GPL-2.0-only AND MIT)"
-- True
--
-- >>> unsafeParseExpr "MIT" `equivalent` unsafeParseExpr "MIT OR BSD-3-Clause"
-- False
--
equivalent :: License -> License -> Bool
equivalent :: License -> License -> Bool
equivalent License
a License
b = License -> LatticeSyntax Lic
exprToLSLic License
a LatticeSyntax Lic -> LatticeSyntax Lic -> Bool
forall a. Ord a => LatticeSyntax a -> LatticeSyntax a -> Bool
`LS.equivalent` License -> LatticeSyntax Lic
exprToLSLic License
b

-------------------------------------------------------------------------------
-- internal
-------------------------------------------------------------------------------

data Lic = Lic !SimpleLicenseExpression !(Maybe LicenseExceptionId)
  deriving (Lic -> Lic -> Bool
(Lic -> Lic -> Bool) -> (Lic -> Lic -> Bool) -> Eq Lic
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Lic -> Lic -> Bool
$c/= :: Lic -> Lic -> Bool
== :: Lic -> Lic -> Bool
$c== :: Lic -> Lic -> Bool
Eq, Eq Lic
Eq Lic
-> (Lic -> Lic -> Ordering)
-> (Lic -> Lic -> Bool)
-> (Lic -> Lic -> Bool)
-> (Lic -> Lic -> Bool)
-> (Lic -> Lic -> Bool)
-> (Lic -> Lic -> Lic)
-> (Lic -> Lic -> Lic)
-> Ord Lic
Lic -> Lic -> Bool
Lic -> Lic -> Ordering
Lic -> Lic -> Lic
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 :: Lic -> Lic -> Lic
$cmin :: Lic -> Lic -> Lic
max :: Lic -> Lic -> Lic
$cmax :: Lic -> Lic -> Lic
>= :: Lic -> Lic -> Bool
$c>= :: Lic -> Lic -> Bool
> :: Lic -> Lic -> Bool
$c> :: Lic -> Lic -> Bool
<= :: Lic -> Lic -> Bool
$c<= :: Lic -> Lic -> Bool
< :: Lic -> Lic -> Bool
$c< :: Lic -> Lic -> Bool
compare :: Lic -> Lic -> Ordering
$ccompare :: Lic -> Lic -> Ordering
$cp1Ord :: Eq Lic
Ord)

exprToLSLic :: License -> LatticeSyntax Lic
exprToLSLic :: License -> LatticeSyntax Lic
exprToLSLic License
NONE          = Bool -> LatticeSyntax Lic
forall a. Bool -> LatticeSyntax a
LBound Bool
False
exprToLSLic (License LicenseExpression
lic) = LicenseExpression -> LatticeSyntax Lic
licTo LicenseExpression
lic

licTo :: LicenseExpression -> LatticeSyntax Lic
licTo :: LicenseExpression -> LatticeSyntax Lic
licTo (ELicense SimpleLicenseExpression
lic Maybe LicenseExceptionId
exc) = Lic -> LatticeSyntax Lic
forall a. a -> LatticeSyntax a
LVar (SimpleLicenseExpression -> Maybe LicenseExceptionId -> Lic
Lic SimpleLicenseExpression
lic Maybe LicenseExceptionId
exc)
licTo (EAnd LicenseExpression
a LicenseExpression
b)         = LatticeSyntax Lic -> LatticeSyntax Lic -> LatticeSyntax Lic
forall a. LatticeSyntax a -> LatticeSyntax a -> LatticeSyntax a
LMeet (LicenseExpression -> LatticeSyntax Lic
licTo LicenseExpression
a) (LicenseExpression -> LatticeSyntax Lic
licTo LicenseExpression
b)
licTo (EOr LicenseExpression
a LicenseExpression
b)          = LatticeSyntax Lic -> LatticeSyntax Lic -> LatticeSyntax Lic
forall a. LatticeSyntax a -> LatticeSyntax a -> LatticeSyntax a
LJoin (LicenseExpression -> LatticeSyntax Lic
licTo LicenseExpression
a) (LicenseExpression -> LatticeSyntax Lic
licTo LicenseExpression
b)

-- $setup
-- >>> import Distribution.Parsec.Class (simpleParsec)
-- >>> let unsafeParseExpr e = maybe (error $ "invalid: " ++ e) (id :: License -> License) (simpleParsec e)