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

-----------------------------------------------------------------------------
-- |
-- Module      :  Distribution.License
-- Description :  The License data type.
-- Copyright   :  Isaac Jones 2003-2005
--                Duncan Coutts 2008
-- License     :  BSD3
--
-- Maintainer  :  cabal-devel@haskell.org
-- Portability :  portable
--
-- Package descriptions contain fields for specifying the name of a software
-- license and the name of the file containing the text of that license. While
-- package authors may choose any license they like, Cabal provides an
-- enumeration of a small set of common free and open source software licenses.
-- This is done so that Hackage can recognise licenses, so that tools can detect
-- <https://en.wikipedia.org/wiki/License_compatibility licensing conflicts>,
-- and to deter
-- <https://en.wikipedia.org/wiki/License_proliferation license proliferation>.
--
-- It is recommended that all package authors use the @license-file@ or
-- @license-files@ fields in their package descriptions. Further information
-- about these fields can be found in the
-- <http://www.haskell.org/cabal/users-guide/developing-packages.html#package-descriptions Cabal users guide>.
--
-- = Additional resources
--
-- The following websites provide information about free and open source
-- software licenses:
--
-- * <http://www.opensource.org The Open Source Initiative (OSI)>
--
-- * <https://www.fsf.org The Free Software Foundation (FSF)>
--
-- = Disclaimer
--
-- The descriptions of software licenses provided by this documentation are
-- intended for informational purposes only and in no way constitute legal
-- advice. Please read the text of the licenses and consult a lawyer for any
-- advice regarding software licensing.

module Distribution.License (
    License(..),
    knownLicenses,
    licenseToSPDX,
    licenseFromSPDX,
  ) where

import Distribution.Compat.Prelude
import Prelude ()

import Distribution.Parsec
import Distribution.Pretty
import Distribution.Version

import qualified Distribution.Compat.CharParsing as P
import qualified Data.Map.Strict                 as Map
import qualified Distribution.SPDX               as SPDX
import qualified Text.PrettyPrint                as Disp

-- | Indicates the license under which a package's source code is released.
-- Versions of the licenses not listed here will be rejected by Hackage and
-- cause @cabal check@ to issue a warning.
data License =
    -- TODO: * remove BSD4

    -- | GNU General Public License,
    -- <https://www.gnu.org/licenses/old-licenses/gpl-2.0.html version 2> or
    -- <https://www.gnu.org/licenses/gpl.html version 3>.
    GPL (Maybe Version)

    -- | <https://www.gnu.org/licenses/agpl.html GNU Affero General Public License, version 3>.
  | AGPL (Maybe Version)

    -- | GNU Lesser General Public License,
    -- <https://www.gnu.org/licenses/old-licenses/lgpl-2.1.html version 2.1> or
    -- <https://www.gnu.org/licenses/lgpl.html version 3>.
  | LGPL (Maybe Version)

    -- | <http://www.opensource.org/licenses/bsd-license 2-clause BSD license>.
  | BSD2

    -- | <http://www.opensource.org/licenses/bsd-3-clause 3-clause BSD license>.
  | BSD3

    -- | <http://directory.fsf.org/wiki/License:BSD_4Clause 4-clause BSD license>.
    -- This license has not been approved by the OSI and is incompatible with
    -- the GNU GPL. It is provided for historical reasons and should be avoided.
  | BSD4

    -- | <http://www.opensource.org/licenses/MIT MIT license>.
  | MIT

    -- | <http://www.isc.org/downloads/software-support-policy/isc-license/ ISC license>
  | ISC

    -- | <https://www.mozilla.org/MPL/ Mozilla Public License, version 2.0>.
  | MPL Version

    -- | <https://www.apache.org/licenses/ Apache License, version 2.0>.
  | Apache (Maybe Version)

    -- | The author of a package disclaims any copyright to its source code and
    -- dedicates it to the public domain. This is not a software license. Please
    -- note that it is not possible to dedicate works to the public domain in
    -- every jurisdiction, nor is a work that is in the public domain in one
    -- jurisdiction necessarily in the public domain elsewhere.
  | PublicDomain

    -- | Explicitly 'All Rights Reserved', eg for proprietary software. The
    -- package may not be legally modified or redistributed by anyone but the
    -- rightsholder.
  | AllRightsReserved

    -- | No license specified which legally defaults to 'All Rights Reserved'.
    -- The package may not be legally modified or redistributed by anyone but
    -- the rightsholder.
  | UnspecifiedLicense

    -- | Any other software license.
  | OtherLicense

    -- | Indicates an erroneous license name.
  | UnknownLicense String
  deriving ((forall x. License -> Rep License x)
-> (forall x. Rep License x -> License) -> Generic License
forall x. Rep License x -> License
forall x. License -> Rep License x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep License x -> License
$cfrom :: forall x. License -> Rep License x
Generic, ReadPrec [License]
ReadPrec License
Int -> ReadS License
ReadS [License]
(Int -> ReadS License)
-> ReadS [License]
-> ReadPrec License
-> ReadPrec [License]
-> Read License
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [License]
$creadListPrec :: ReadPrec [License]
readPrec :: ReadPrec License
$creadPrec :: ReadPrec License
readList :: ReadS [License]
$creadList :: ReadS [License]
readsPrec :: Int -> ReadS License
$creadsPrec :: Int -> ReadS License
Read, Int -> License -> ShowS
[License] -> ShowS
License -> String
(Int -> License -> ShowS)
-> (License -> String) -> ([License] -> ShowS) -> Show License
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [License] -> ShowS
$cshowList :: [License] -> ShowS
show :: License -> String
$cshow :: License -> String
showsPrec :: Int -> License -> ShowS
$cshowsPrec :: Int -> License -> ShowS
Show, License -> License -> Bool
(License -> License -> Bool)
-> (License -> License -> Bool) -> Eq License
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: License -> License -> Bool
$c/= :: License -> License -> Bool
== :: License -> License -> Bool
$c== :: License -> License -> Bool
Eq, Typeable, Typeable License
Typeable License
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> License -> c License)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c License)
-> (License -> Constr)
-> (License -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c License))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License))
-> ((forall b. Data b => b -> b) -> License -> License)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> License -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> License -> r)
-> (forall u. (forall d. Data d => d -> u) -> License -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> License -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> License -> m License)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> License -> m License)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> License -> m License)
-> Data License
License -> DataType
License -> Constr
(forall b. Data b => b -> b) -> License -> License
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) -> License -> u
forall u. (forall d. Data d => d -> u) -> License -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> License -> m License
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> License -> m License
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c License
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> License -> c License
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c License)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> License -> m License
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> License -> m License
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> License -> m License
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> License -> m License
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> License -> m License
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> License -> m License
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> License -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> License -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> License -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> License -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
gmapT :: (forall b. Data b => b -> b) -> License -> License
$cgmapT :: (forall b. Data b => b -> b) -> License -> License
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c License)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c License)
dataTypeOf :: License -> DataType
$cdataTypeOf :: License -> DataType
toConstr :: License -> Constr
$ctoConstr :: License -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c License
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c License
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> License -> c License
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> License -> c License
Data)

instance Binary License
instance Structured License
instance NFData License where rnf :: License -> ()
rnf = License -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf

-- | The list of all currently recognised licenses.
knownLicenses :: [License]
knownLicenses :: [License]
knownLicenses = [ Maybe Version -> License
GPL  Maybe Version
forall {a}. Maybe a
unversioned, Maybe Version -> License
GPL  ([Int] -> Maybe Version
version [Int
2]),    Maybe Version -> License
GPL  ([Int] -> Maybe Version
version [Int
3])
                , Maybe Version -> License
LGPL Maybe Version
forall {a}. Maybe a
unversioned, Maybe Version -> License
LGPL ([Int] -> Maybe Version
version [Int
2, Int
1]), Maybe Version -> License
LGPL ([Int] -> Maybe Version
version [Int
3])
                , Maybe Version -> License
AGPL Maybe Version
forall {a}. Maybe a
unversioned,                        Maybe Version -> License
AGPL ([Int] -> Maybe Version
version [Int
3])
                , License
BSD2, License
BSD3, License
MIT, License
ISC
                , Version -> License
MPL ([Int] -> Version
mkVersion [Int
2, Int
0])
                , Maybe Version -> License
Apache Maybe Version
forall {a}. Maybe a
unversioned, Maybe Version -> License
Apache ([Int] -> Maybe Version
version [Int
2, Int
0])
                , License
PublicDomain, License
AllRightsReserved, License
OtherLicense]
  where
    unversioned :: Maybe a
unversioned = Maybe a
forall {a}. Maybe a
Nothing
    version :: [Int] -> Maybe Version
version     = Version -> Maybe Version
forall a. a -> Maybe a
Just (Version -> Maybe Version)
-> ([Int] -> Version) -> [Int] -> Maybe Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> Version
mkVersion

-- | Convert old 'License' to SPDX 'SPDX.License'.
-- Non-SPDX licenses are converted to 'SPDX.LicenseRef'.
--
-- @since 2.2.0.0
licenseToSPDX :: License -> SPDX.License
licenseToSPDX :: License -> License
licenseToSPDX License
l = case License
l of
    GPL Maybe Version
v | Maybe Version
v Maybe Version -> Maybe Version -> Bool
forall a. Eq a => a -> a -> Bool
== [Int] -> Maybe Version
version [Int
2]      -> LicenseId -> License
spdx LicenseId
SPDX.GPL_2_0_only
    GPL Maybe Version
v | Maybe Version
v Maybe Version -> Maybe Version -> Bool
forall a. Eq a => a -> a -> Bool
== [Int] -> Maybe Version
version [Int
3]      -> LicenseId -> License
spdx LicenseId
SPDX.GPL_3_0_only
    LGPL Maybe Version
v | Maybe Version
v Maybe Version -> Maybe Version -> Bool
forall a. Eq a => a -> a -> Bool
== [Int] -> Maybe Version
version [Int
2,Int
1]   -> LicenseId -> License
spdx LicenseId
SPDX.LGPL_2_1_only
    LGPL Maybe Version
v | Maybe Version
v Maybe Version -> Maybe Version -> Bool
forall a. Eq a => a -> a -> Bool
== [Int] -> Maybe Version
version [Int
3]     -> LicenseId -> License
spdx LicenseId
SPDX.LGPL_3_0_only
    AGPL Maybe Version
v | Maybe Version
v Maybe Version -> Maybe Version -> Bool
forall a. Eq a => a -> a -> Bool
== [Int] -> Maybe Version
version [Int
3]     -> LicenseId -> License
spdx LicenseId
SPDX.AGPL_3_0_only
    License
BSD2                          -> LicenseId -> License
spdx LicenseId
SPDX.BSD_2_Clause
    License
BSD3                          -> LicenseId -> License
spdx LicenseId
SPDX.BSD_3_Clause
    License
BSD4                          -> LicenseId -> License
spdx LicenseId
SPDX.BSD_4_Clause
    License
MIT                           -> LicenseId -> License
spdx LicenseId
SPDX.MIT
    License
ISC                           -> LicenseId -> License
spdx LicenseId
SPDX.ISC
    MPL Version
v | Version
v Version -> Version -> Bool
forall a. Eq a => a -> a -> Bool
== [Int] -> Version
mkVersion [Int
2,Int
0]  -> LicenseId -> License
spdx LicenseId
SPDX.MPL_2_0
    Apache Maybe Version
v | Maybe Version
v Maybe Version -> Maybe Version -> Bool
forall a. Eq a => a -> a -> Bool
== [Int] -> Maybe Version
version [Int
2,Int
0] -> LicenseId -> License
spdx LicenseId
SPDX.Apache_2_0
    License
AllRightsReserved             -> License
SPDX.NONE
    License
UnspecifiedLicense            -> License
SPDX.NONE
    License
OtherLicense                  -> LicenseRef -> License
ref (Maybe String -> String -> LicenseRef
SPDX.mkLicenseRef' Maybe String
forall {a}. Maybe a
Nothing String
"OtherLicense")
    License
PublicDomain                  -> LicenseRef -> License
ref (Maybe String -> String -> LicenseRef
SPDX.mkLicenseRef' Maybe String
forall {a}. Maybe a
Nothing String
"PublicDomain")
    UnknownLicense String
str            -> LicenseRef -> License
ref (Maybe String -> String -> LicenseRef
SPDX.mkLicenseRef' Maybe String
forall {a}. Maybe a
Nothing String
str)
    License
_                             -> LicenseRef -> License
ref (Maybe String -> String -> LicenseRef
SPDX.mkLicenseRef' Maybe String
forall {a}. Maybe a
Nothing (String -> LicenseRef) -> String -> LicenseRef
forall a b. (a -> b) -> a -> b
$ License -> String
forall a. Pretty a => a -> String
prettyShow License
l)
  where
    version :: [Int] -> Maybe Version
version = Version -> Maybe Version
forall a. a -> Maybe a
Just (Version -> Maybe Version)
-> ([Int] -> Version) -> [Int] -> Maybe Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> Version
mkVersion
    spdx :: LicenseId -> License
spdx    = LicenseExpression -> License
SPDX.License (LicenseExpression -> License)
-> (LicenseId -> LicenseExpression) -> LicenseId -> License
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LicenseId -> LicenseExpression
SPDX.simpleLicenseExpression
    ref :: LicenseRef -> License
ref  LicenseRef
r  = LicenseExpression -> License
SPDX.License (LicenseExpression -> License) -> LicenseExpression -> License
forall a b. (a -> b) -> a -> b
$ SimpleLicenseExpression
-> Maybe LicenseExceptionId -> LicenseExpression
SPDX.ELicense (LicenseRef -> SimpleLicenseExpression
SPDX.ELicenseRef LicenseRef
r) Maybe LicenseExceptionId
forall {a}. Maybe a
Nothing

-- | Convert 'SPDX.License' to 'License',
--
-- This is lossy conversion. We try our best.
--
-- >>> licenseFromSPDX . licenseToSPDX $ BSD3
-- BSD3
--
-- >>> licenseFromSPDX . licenseToSPDX $ GPL (Just (mkVersion [3]))
-- GPL (Just (mkVersion [3]))
--
-- >>> licenseFromSPDX . licenseToSPDX $ PublicDomain
-- UnknownLicense "LicenseRefPublicDomain"
--
-- >>> licenseFromSPDX $ SPDX.License $ SPDX.simpleLicenseExpression SPDX.EUPL_1_1
-- UnknownLicense "EUPL-1.1"
--
-- >>> licenseFromSPDX . licenseToSPDX $ AllRightsReserved
-- AllRightsReserved
--
-- >>> licenseFromSPDX <$> simpleParsec "BSD-3-Clause OR GPL-3.0-only"
-- Just (UnknownLicense "BSD3ClauseORGPL30only")
--
-- @since 2.2.0.0
licenseFromSPDX :: SPDX.License -> License
licenseFromSPDX :: License -> License
licenseFromSPDX License
SPDX.NONE = License
AllRightsReserved
licenseFromSPDX License
l =
    License -> Maybe License -> License
forall a. a -> Maybe a -> a
fromMaybe (String -> License
mungle (String -> License) -> String -> License
forall a b. (a -> b) -> a -> b
$ License -> String
forall a. Pretty a => a -> String
prettyShow License
l) (Maybe License -> License) -> Maybe License -> License
forall a b. (a -> b) -> a -> b
$ License -> Map License License -> Maybe License
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup License
l Map License License
m
  where
    m :: Map.Map SPDX.License License
    m :: Map License License
m = [(License, License)] -> Map License License
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(License, License)] -> Map License License)
-> [(License, License)] -> Map License License
forall a b. (a -> b) -> a -> b
$ ((License, License) -> Bool)
-> [(License, License)] -> [(License, License)]
forall a. (a -> Bool) -> [a] -> [a]
filter (License -> Bool
isSimple (License -> Bool)
-> ((License, License) -> License) -> (License, License) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (License, License) -> License
forall a b. (a, b) -> a
fst ) ([(License, License)] -> [(License, License)])
-> [(License, License)] -> [(License, License)]
forall a b. (a -> b) -> a -> b
$
        (License -> (License, License))
-> [License] -> [(License, License)]
forall a b. (a -> b) -> [a] -> [b]
map (\License
x -> (License -> License
licenseToSPDX License
x, License
x)) [License]
knownLicenses

    isSimple :: License -> Bool
isSimple (SPDX.License (SPDX.ELicense (SPDX.ELicenseId LicenseId
_) Maybe LicenseExceptionId
Nothing)) = Bool
True
    isSimple License
_ = Bool
False

    mungle :: String -> License
mungle String
name = License -> Maybe License -> License
forall a. a -> Maybe a -> a
fromMaybe (String -> License
UnknownLicense ((Char -> Maybe Char) -> ShowS
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Char -> Maybe Char
mangle String
name)) (String -> Maybe License
forall a. Parsec a => String -> Maybe a
simpleParsec String
name)

    mangle :: Char -> Maybe Char
mangle Char
c
        | Char -> Bool
isAlphaNum Char
c = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
c
        | Bool
otherwise = Maybe Char
forall {a}. Maybe a
Nothing

instance Pretty License where
  pretty :: License -> Doc
pretty (GPL  Maybe Version
version)         = String -> Doc
Disp.text String
"GPL"    Doc -> Doc -> Doc
<<>> Maybe Version -> Doc
dispOptVersion Maybe Version
version
  pretty (LGPL Maybe Version
version)         = String -> Doc
Disp.text String
"LGPL"   Doc -> Doc -> Doc
<<>> Maybe Version -> Doc
dispOptVersion Maybe Version
version
  pretty (AGPL Maybe Version
version)         = String -> Doc
Disp.text String
"AGPL"   Doc -> Doc -> Doc
<<>> Maybe Version -> Doc
dispOptVersion Maybe Version
version
  pretty (MPL  Version
version)         = String -> Doc
Disp.text String
"MPL"    Doc -> Doc -> Doc
<<>> Version -> Doc
dispVersion    Version
version
  pretty (Apache Maybe Version
version)       = String -> Doc
Disp.text String
"Apache" Doc -> Doc -> Doc
<<>> Maybe Version -> Doc
dispOptVersion Maybe Version
version
  pretty (UnknownLicense String
other) = String -> Doc
Disp.text String
other
  pretty License
other                  = String -> Doc
Disp.text (License -> String
forall a. Show a => a -> String
show License
other)

instance Parsec License where
  parsec :: forall (m :: * -> *). CabalParsing m => m License
parsec = do
    String
name    <- (Char -> Bool) -> m String
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m String
P.munch1 Char -> Bool
isAlphaNum
    Maybe Version
version <- m Version -> m (Maybe Version)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
P.optional (Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
'-' m Char -> m Version -> m Version
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> m Version
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec)
    License -> m License
forall (m :: * -> *) a. Monad m => a -> m a
return (License -> m License) -> License -> m License
forall a b. (a -> b) -> a -> b
$! case (String
name, Maybe Version
version :: Maybe Version) of
      (String
"GPL",               Maybe Version
_      )  -> Maybe Version -> License
GPL  Maybe Version
version
      (String
"LGPL",              Maybe Version
_      )  -> Maybe Version -> License
LGPL Maybe Version
version
      (String
"AGPL",              Maybe Version
_      )  -> Maybe Version -> License
AGPL Maybe Version
version
      (String
"BSD2",              Maybe Version
Nothing)  -> License
BSD2
      (String
"BSD3",              Maybe Version
Nothing)  -> License
BSD3
      (String
"BSD4",              Maybe Version
Nothing)  -> License
BSD4
      (String
"ISC",               Maybe Version
Nothing)  -> License
ISC
      (String
"MIT",               Maybe Version
Nothing)  -> License
MIT
      (String
"MPL",         Just Version
version')  -> Version -> License
MPL Version
version'
      (String
"Apache",            Maybe Version
_      )  -> Maybe Version -> License
Apache Maybe Version
version
      (String
"PublicDomain",      Maybe Version
Nothing)  -> License
PublicDomain
      (String
"AllRightsReserved", Maybe Version
Nothing)  -> License
AllRightsReserved
      (String
"OtherLicense",      Maybe Version
Nothing)  -> License
OtherLicense
      (String, Maybe Version)
_                               -> String -> License
UnknownLicense (String -> License) -> String -> License
forall a b. (a -> b) -> a -> b
$ String
name String -> ShowS
forall a. [a] -> [a] -> [a]
++
                                         String -> (Version -> String) -> Maybe Version -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" ((Char
'-'Char -> ShowS
forall a. a -> [a] -> [a]
:) ShowS -> (Version -> String) -> Version -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> String
forall a. Pretty a => a -> String
prettyShow) Maybe Version
version

dispOptVersion :: Maybe Version -> Disp.Doc
dispOptVersion :: Maybe Version -> Doc
dispOptVersion Maybe Version
Nothing  = Doc
Disp.empty
dispOptVersion (Just Version
v) = Version -> Doc
dispVersion Version
v

dispVersion :: Version -> Disp.Doc
dispVersion :: Version -> Doc
dispVersion Version
v = Char -> Doc
Disp.char Char
'-' Doc -> Doc -> Doc
<<>> Version -> Doc
forall a. Pretty a => a -> Doc
pretty Version
v