module Distribution.License (
    License(..),
    knownLicenses,
    licenseToSPDX,
    licenseFromSPDX,
  ) where
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.Parsec.Class
import Distribution.Pretty
import Distribution.Text
import Distribution.Version
import qualified Distribution.Compat.CharParsing as P
import qualified Data.Map.Strict                 as Map
import qualified Distribution.Compat.ReadP       as Parse
import qualified Distribution.SPDX               as SPDX
import qualified Text.PrettyPrint                as Disp
data License =
    
    
    
    
    GPL (Maybe Version)
    
  | AGPL (Maybe Version)
    
    
    
  | LGPL (Maybe Version)
    
  | BSD2
    
  | BSD3
    
    
    
  | BSD4
    
  | MIT
    
  | ISC
    
  | MPL Version
    
  | Apache (Maybe Version)
    
    
    
    
    
  | PublicDomain
    
    
    
  | AllRightsReserved
    
    
    
  | UnspecifiedLicense
    
  | OtherLicense
    
  | UnknownLicense String
  deriving (Generic, Read, Show, Eq, Typeable, Data)
instance Binary License
instance NFData License where rnf = genericRnf
knownLicenses :: [License]
knownLicenses = [ GPL  unversioned, GPL  (version [2]),    GPL  (version [3])
                , LGPL unversioned, LGPL (version [2, 1]), LGPL (version [3])
                , AGPL unversioned,                        AGPL (version [3])
                , BSD2, BSD3, MIT, ISC
                , MPL (mkVersion [2, 0])
                , Apache unversioned, Apache (version [2, 0])
                , PublicDomain, AllRightsReserved, OtherLicense]
  where
    unversioned = Nothing
    version     = Just . mkVersion
licenseToSPDX :: License -> SPDX.License
licenseToSPDX l = case l of
    GPL v | v == version [2]      -> spdx SPDX.GPL_2_0_only
    GPL v | v == version [3]      -> spdx SPDX.GPL_3_0_only
    LGPL v | v == version [2,1]   -> spdx SPDX.LGPL_2_1_only
    LGPL v | v == version [3]     -> spdx SPDX.LGPL_3_0_only
    AGPL v | v == version [3]     -> spdx SPDX.AGPL_3_0_only
    BSD2                          -> spdx SPDX.BSD_2_Clause
    BSD3                          -> spdx SPDX.BSD_3_Clause
    BSD4                          -> spdx SPDX.BSD_4_Clause
    MIT                           -> spdx SPDX.MIT
    ISC                           -> spdx SPDX.ISC
    MPL v | v == mkVersion [2,0]  -> spdx SPDX.MPL_2_0
    Apache v | v == version [2,0] -> spdx SPDX.Apache_2_0
    AllRightsReserved             -> SPDX.NONE
    UnspecifiedLicense            -> SPDX.NONE
    OtherLicense                  -> ref (SPDX.mkLicenseRef' Nothing "OtherLicense")
    PublicDomain                  -> ref (SPDX.mkLicenseRef' Nothing "PublicDomain")
    UnknownLicense str            -> ref (SPDX.mkLicenseRef' Nothing str)
    _                             -> ref (SPDX.mkLicenseRef' Nothing $ prettyShow l)
  where
    version = Just . mkVersion
    spdx    = SPDX.License . SPDX.simpleLicenseExpression
    ref  r  = SPDX.License $ SPDX.ELicense (SPDX.ELicenseRef r) Nothing
licenseFromSPDX :: SPDX.License -> License
licenseFromSPDX SPDX.NONE = AllRightsReserved
licenseFromSPDX l =
    fromMaybe (mungle $ prettyShow l) $ Map.lookup l m
  where
    m :: Map.Map SPDX.License License
    m = Map.fromList $ filter (isSimple . fst ) $
        map (\x -> (licenseToSPDX x, x)) knownLicenses
    isSimple (SPDX.License (SPDX.ELicense (SPDX.ELicenseId _) Nothing)) = True
    isSimple _ = False
    mungle name = fromMaybe (UnknownLicense (mapMaybe mangle name)) (simpleParsec name)
    mangle c
        | isAlphaNum c = Just c
        | otherwise = Nothing
instance Pretty License where
  pretty (GPL  version)         = Disp.text "GPL"    <<>> dispOptVersion version
  pretty (LGPL version)         = Disp.text "LGPL"   <<>> dispOptVersion version
  pretty (AGPL version)         = Disp.text "AGPL"   <<>> dispOptVersion version
  pretty (MPL  version)         = Disp.text "MPL"    <<>> dispVersion    version
  pretty (Apache version)       = Disp.text "Apache" <<>> dispOptVersion version
  pretty (UnknownLicense other) = Disp.text other
  pretty other                  = Disp.text (show other)
instance Parsec License where
  parsec = do
    name    <- P.munch1 isAlphaNum
    version <- P.optional (P.char '-' *> parsec)
    return $! case (name, version :: Maybe Version) of
      ("GPL",               _      )  -> GPL  version
      ("LGPL",              _      )  -> LGPL version
      ("AGPL",              _      )  -> AGPL version
      ("BSD2",              Nothing)  -> BSD2
      ("BSD3",              Nothing)  -> BSD3
      ("BSD4",              Nothing)  -> BSD4
      ("ISC",               Nothing)  -> ISC
      ("MIT",               Nothing)  -> MIT
      ("MPL",         Just version')  -> MPL version'
      ("Apache",            _      )  -> Apache version
      ("PublicDomain",      Nothing)  -> PublicDomain
      ("AllRightsReserved", Nothing)  -> AllRightsReserved
      ("OtherLicense",      Nothing)  -> OtherLicense
      _                               -> UnknownLicense $ name ++
                                         maybe "" (('-':) . display) version
instance Text License where
  parse = do
    name    <- Parse.munch1 (\c -> isAlphaNum c && c /= '-')
    version <- Parse.option Nothing (Parse.char '-' >> fmap Just parse)
    return $! case (name, version :: Maybe Version) of
      ("GPL",               _      ) -> GPL  version
      ("LGPL",              _      ) -> LGPL version
      ("AGPL",              _      ) -> AGPL version
      ("BSD2",              Nothing) -> BSD2
      ("BSD3",              Nothing) -> BSD3
      ("BSD4",              Nothing) -> BSD4
      ("ISC",               Nothing) -> ISC
      ("MIT",               Nothing) -> MIT
      ("MPL",         Just version') -> MPL version'
      ("Apache",            _      ) -> Apache version
      ("PublicDomain",      Nothing) -> PublicDomain
      ("AllRightsReserved", Nothing) -> AllRightsReserved
      ("OtherLicense",      Nothing) -> OtherLicense
      _                              -> UnknownLicense $ name ++
                                        maybe "" (('-':) . display) version
dispOptVersion :: Maybe Version -> Disp.Doc
dispOptVersion Nothing  = Disp.empty
dispOptVersion (Just v) = dispVersion v
dispVersion :: Version -> Disp.Doc
dispVersion v = Disp.char '-' <<>> disp v