{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric      #-}
module Distribution.SPDX.LicenseExpression (
    LicenseExpression (..),
    SimpleLicenseExpression (..),
    simpleLicenseExpression,
    ) where

import Distribution.Compat.Prelude
import Prelude ()

import Distribution.Parsec
import Distribution.Pretty
import Distribution.SPDX.LicenseExceptionId
import Distribution.SPDX.LicenseId
import Distribution.SPDX.LicenseListVersion
import Distribution.SPDX.LicenseReference
import Distribution.Utils.Generic           (isAsciiAlphaNum)
import Text.PrettyPrint                     ((<+>))

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

-- | SPDX License Expression.
--
-- @
-- idstring              = 1*(ALPHA \/ DIGIT \/ "-" \/ "." )
-- license id            = \<short form license identifier inAppendix I.1>
-- license exception id  = \<short form license exception identifier inAppendix I.2>
-- license ref           = [\"DocumentRef-"1*(idstring)":"]\"LicenseRef-"1*(idstring)
--
-- simple expression     = license id \/ license id"+" \/ license ref
--
-- compound expression   = 1*1(simple expression \/
--                         simple expression \"WITH" license exception id \/
--                         compound expression \"AND" compound expression \/
--                         compound expression \"OR" compound expression ) \/
--                         "(" compound expression ")" )
--
-- license expression    = 1*1(simple expression / compound expression)
-- @
data LicenseExpression
    = ELicense !SimpleLicenseExpression !(Maybe LicenseExceptionId)
    | EAnd !LicenseExpression !LicenseExpression
    | EOr !LicenseExpression !LicenseExpression
    deriving (Int -> LicenseExpression -> ShowS
[LicenseExpression] -> ShowS
LicenseExpression -> String
(Int -> LicenseExpression -> ShowS)
-> (LicenseExpression -> String)
-> ([LicenseExpression] -> ShowS)
-> Show LicenseExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LicenseExpression] -> ShowS
$cshowList :: [LicenseExpression] -> ShowS
show :: LicenseExpression -> String
$cshow :: LicenseExpression -> String
showsPrec :: Int -> LicenseExpression -> ShowS
$cshowsPrec :: Int -> LicenseExpression -> ShowS
Show, ReadPrec [LicenseExpression]
ReadPrec LicenseExpression
Int -> ReadS LicenseExpression
ReadS [LicenseExpression]
(Int -> ReadS LicenseExpression)
-> ReadS [LicenseExpression]
-> ReadPrec LicenseExpression
-> ReadPrec [LicenseExpression]
-> Read LicenseExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LicenseExpression]
$creadListPrec :: ReadPrec [LicenseExpression]
readPrec :: ReadPrec LicenseExpression
$creadPrec :: ReadPrec LicenseExpression
readList :: ReadS [LicenseExpression]
$creadList :: ReadS [LicenseExpression]
readsPrec :: Int -> ReadS LicenseExpression
$creadsPrec :: Int -> ReadS LicenseExpression
Read, LicenseExpression -> LicenseExpression -> Bool
(LicenseExpression -> LicenseExpression -> Bool)
-> (LicenseExpression -> LicenseExpression -> Bool)
-> Eq LicenseExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LicenseExpression -> LicenseExpression -> Bool
$c/= :: LicenseExpression -> LicenseExpression -> Bool
== :: LicenseExpression -> LicenseExpression -> Bool
$c== :: LicenseExpression -> LicenseExpression -> Bool
Eq, Eq LicenseExpression
Eq LicenseExpression
-> (LicenseExpression -> LicenseExpression -> Ordering)
-> (LicenseExpression -> LicenseExpression -> Bool)
-> (LicenseExpression -> LicenseExpression -> Bool)
-> (LicenseExpression -> LicenseExpression -> Bool)
-> (LicenseExpression -> LicenseExpression -> Bool)
-> (LicenseExpression -> LicenseExpression -> LicenseExpression)
-> (LicenseExpression -> LicenseExpression -> LicenseExpression)
-> Ord LicenseExpression
LicenseExpression -> LicenseExpression -> Bool
LicenseExpression -> LicenseExpression -> Ordering
LicenseExpression -> LicenseExpression -> LicenseExpression
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 :: LicenseExpression -> LicenseExpression -> LicenseExpression
$cmin :: LicenseExpression -> LicenseExpression -> LicenseExpression
max :: LicenseExpression -> LicenseExpression -> LicenseExpression
$cmax :: LicenseExpression -> LicenseExpression -> LicenseExpression
>= :: LicenseExpression -> LicenseExpression -> Bool
$c>= :: LicenseExpression -> LicenseExpression -> Bool
> :: LicenseExpression -> LicenseExpression -> Bool
$c> :: LicenseExpression -> LicenseExpression -> Bool
<= :: LicenseExpression -> LicenseExpression -> Bool
$c<= :: LicenseExpression -> LicenseExpression -> Bool
< :: LicenseExpression -> LicenseExpression -> Bool
$c< :: LicenseExpression -> LicenseExpression -> Bool
compare :: LicenseExpression -> LicenseExpression -> Ordering
$ccompare :: LicenseExpression -> LicenseExpression -> Ordering
$cp1Ord :: Eq LicenseExpression
Ord, Typeable, Typeable LicenseExpression
DataType
Constr
Typeable LicenseExpression
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> LicenseExpression
    -> c LicenseExpression)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c LicenseExpression)
-> (LicenseExpression -> Constr)
-> (LicenseExpression -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c LicenseExpression))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c LicenseExpression))
-> ((forall b. Data b => b -> b)
    -> LicenseExpression -> LicenseExpression)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> LicenseExpression -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> LicenseExpression -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> LicenseExpression -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> LicenseExpression -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> LicenseExpression -> m LicenseExpression)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> LicenseExpression -> m LicenseExpression)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> LicenseExpression -> m LicenseExpression)
-> Data LicenseExpression
LicenseExpression -> DataType
LicenseExpression -> Constr
(forall b. Data b => b -> b)
-> LicenseExpression -> LicenseExpression
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LicenseExpression -> c LicenseExpression
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LicenseExpression
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) -> LicenseExpression -> u
forall u. (forall d. Data d => d -> u) -> LicenseExpression -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LicenseExpression -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LicenseExpression -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> LicenseExpression -> m LicenseExpression
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LicenseExpression -> m LicenseExpression
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LicenseExpression
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LicenseExpression -> c LicenseExpression
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LicenseExpression)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LicenseExpression)
$cEOr :: Constr
$cEAnd :: Constr
$cELicense :: Constr
$tLicenseExpression :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> LicenseExpression -> m LicenseExpression
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LicenseExpression -> m LicenseExpression
gmapMp :: (forall d. Data d => d -> m d)
-> LicenseExpression -> m LicenseExpression
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LicenseExpression -> m LicenseExpression
gmapM :: (forall d. Data d => d -> m d)
-> LicenseExpression -> m LicenseExpression
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> LicenseExpression -> m LicenseExpression
gmapQi :: Int -> (forall d. Data d => d -> u) -> LicenseExpression -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> LicenseExpression -> u
gmapQ :: (forall d. Data d => d -> u) -> LicenseExpression -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> LicenseExpression -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LicenseExpression -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LicenseExpression -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LicenseExpression -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LicenseExpression -> r
gmapT :: (forall b. Data b => b -> b)
-> LicenseExpression -> LicenseExpression
$cgmapT :: (forall b. Data b => b -> b)
-> LicenseExpression -> LicenseExpression
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LicenseExpression)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LicenseExpression)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c LicenseExpression)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LicenseExpression)
dataTypeOf :: LicenseExpression -> DataType
$cdataTypeOf :: LicenseExpression -> DataType
toConstr :: LicenseExpression -> Constr
$ctoConstr :: LicenseExpression -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LicenseExpression
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LicenseExpression
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LicenseExpression -> c LicenseExpression
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LicenseExpression -> c LicenseExpression
$cp1Data :: Typeable LicenseExpression
Data, (forall x. LicenseExpression -> Rep LicenseExpression x)
-> (forall x. Rep LicenseExpression x -> LicenseExpression)
-> Generic LicenseExpression
forall x. Rep LicenseExpression x -> LicenseExpression
forall x. LicenseExpression -> Rep LicenseExpression x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LicenseExpression x -> LicenseExpression
$cfrom :: forall x. LicenseExpression -> Rep LicenseExpression x
Generic)

-- | Simple License Expressions.
data SimpleLicenseExpression
    = ELicenseId LicenseId
      -- ^ An SPDX License List Short Form Identifier. For example: @GPL-2.0-only@
    | ELicenseIdPlus LicenseId
      -- ^ An SPDX License List Short Form Identifier with a unary"+" operator suffix to represent the current version of the license or any later version.  For example: @GPL-2.0+@
    | ELicenseRef LicenseRef
      -- ^ A SPDX user defined license reference: For example: @LicenseRef-23@, @LicenseRef-MIT-Style-1@, or @DocumentRef-spdx-tool-1.2:LicenseRef-MIT-Style-2@
    deriving (Int -> SimpleLicenseExpression -> ShowS
[SimpleLicenseExpression] -> ShowS
SimpleLicenseExpression -> String
(Int -> SimpleLicenseExpression -> ShowS)
-> (SimpleLicenseExpression -> String)
-> ([SimpleLicenseExpression] -> ShowS)
-> Show SimpleLicenseExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SimpleLicenseExpression] -> ShowS
$cshowList :: [SimpleLicenseExpression] -> ShowS
show :: SimpleLicenseExpression -> String
$cshow :: SimpleLicenseExpression -> String
showsPrec :: Int -> SimpleLicenseExpression -> ShowS
$cshowsPrec :: Int -> SimpleLicenseExpression -> ShowS
Show, ReadPrec [SimpleLicenseExpression]
ReadPrec SimpleLicenseExpression
Int -> ReadS SimpleLicenseExpression
ReadS [SimpleLicenseExpression]
(Int -> ReadS SimpleLicenseExpression)
-> ReadS [SimpleLicenseExpression]
-> ReadPrec SimpleLicenseExpression
-> ReadPrec [SimpleLicenseExpression]
-> Read SimpleLicenseExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SimpleLicenseExpression]
$creadListPrec :: ReadPrec [SimpleLicenseExpression]
readPrec :: ReadPrec SimpleLicenseExpression
$creadPrec :: ReadPrec SimpleLicenseExpression
readList :: ReadS [SimpleLicenseExpression]
$creadList :: ReadS [SimpleLicenseExpression]
readsPrec :: Int -> ReadS SimpleLicenseExpression
$creadsPrec :: Int -> ReadS SimpleLicenseExpression
Read, SimpleLicenseExpression -> SimpleLicenseExpression -> Bool
(SimpleLicenseExpression -> SimpleLicenseExpression -> Bool)
-> (SimpleLicenseExpression -> SimpleLicenseExpression -> Bool)
-> Eq SimpleLicenseExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SimpleLicenseExpression -> SimpleLicenseExpression -> Bool
$c/= :: SimpleLicenseExpression -> SimpleLicenseExpression -> Bool
== :: SimpleLicenseExpression -> SimpleLicenseExpression -> Bool
$c== :: SimpleLicenseExpression -> SimpleLicenseExpression -> Bool
Eq, Eq SimpleLicenseExpression
Eq SimpleLicenseExpression
-> (SimpleLicenseExpression -> SimpleLicenseExpression -> Ordering)
-> (SimpleLicenseExpression -> SimpleLicenseExpression -> Bool)
-> (SimpleLicenseExpression -> SimpleLicenseExpression -> Bool)
-> (SimpleLicenseExpression -> SimpleLicenseExpression -> Bool)
-> (SimpleLicenseExpression -> SimpleLicenseExpression -> Bool)
-> (SimpleLicenseExpression
    -> SimpleLicenseExpression -> SimpleLicenseExpression)
-> (SimpleLicenseExpression
    -> SimpleLicenseExpression -> SimpleLicenseExpression)
-> Ord SimpleLicenseExpression
SimpleLicenseExpression -> SimpleLicenseExpression -> Bool
SimpleLicenseExpression -> SimpleLicenseExpression -> Ordering
SimpleLicenseExpression
-> SimpleLicenseExpression -> SimpleLicenseExpression
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 :: SimpleLicenseExpression
-> SimpleLicenseExpression -> SimpleLicenseExpression
$cmin :: SimpleLicenseExpression
-> SimpleLicenseExpression -> SimpleLicenseExpression
max :: SimpleLicenseExpression
-> SimpleLicenseExpression -> SimpleLicenseExpression
$cmax :: SimpleLicenseExpression
-> SimpleLicenseExpression -> SimpleLicenseExpression
>= :: SimpleLicenseExpression -> SimpleLicenseExpression -> Bool
$c>= :: SimpleLicenseExpression -> SimpleLicenseExpression -> Bool
> :: SimpleLicenseExpression -> SimpleLicenseExpression -> Bool
$c> :: SimpleLicenseExpression -> SimpleLicenseExpression -> Bool
<= :: SimpleLicenseExpression -> SimpleLicenseExpression -> Bool
$c<= :: SimpleLicenseExpression -> SimpleLicenseExpression -> Bool
< :: SimpleLicenseExpression -> SimpleLicenseExpression -> Bool
$c< :: SimpleLicenseExpression -> SimpleLicenseExpression -> Bool
compare :: SimpleLicenseExpression -> SimpleLicenseExpression -> Ordering
$ccompare :: SimpleLicenseExpression -> SimpleLicenseExpression -> Ordering
$cp1Ord :: Eq SimpleLicenseExpression
Ord, Typeable, Typeable SimpleLicenseExpression
DataType
Constr
Typeable SimpleLicenseExpression
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> SimpleLicenseExpression
    -> c SimpleLicenseExpression)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c SimpleLicenseExpression)
-> (SimpleLicenseExpression -> Constr)
-> (SimpleLicenseExpression -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c SimpleLicenseExpression))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c SimpleLicenseExpression))
-> ((forall b. Data b => b -> b)
    -> SimpleLicenseExpression -> SimpleLicenseExpression)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> SimpleLicenseExpression
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> SimpleLicenseExpression
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> SimpleLicenseExpression -> [u])
-> (forall u.
    Int
    -> (forall d. Data d => d -> u) -> SimpleLicenseExpression -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> SimpleLicenseExpression -> m SimpleLicenseExpression)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> SimpleLicenseExpression -> m SimpleLicenseExpression)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> SimpleLicenseExpression -> m SimpleLicenseExpression)
-> Data SimpleLicenseExpression
SimpleLicenseExpression -> DataType
SimpleLicenseExpression -> Constr
(forall b. Data b => b -> b)
-> SimpleLicenseExpression -> SimpleLicenseExpression
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SimpleLicenseExpression
-> c SimpleLicenseExpression
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SimpleLicenseExpression
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) -> SimpleLicenseExpression -> u
forall u.
(forall d. Data d => d -> u) -> SimpleLicenseExpression -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> SimpleLicenseExpression
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> SimpleLicenseExpression
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SimpleLicenseExpression -> m SimpleLicenseExpression
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SimpleLicenseExpression -> m SimpleLicenseExpression
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SimpleLicenseExpression
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SimpleLicenseExpression
-> c SimpleLicenseExpression
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SimpleLicenseExpression)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SimpleLicenseExpression)
$cELicenseRef :: Constr
$cELicenseIdPlus :: Constr
$cELicenseId :: Constr
$tSimpleLicenseExpression :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> SimpleLicenseExpression -> m SimpleLicenseExpression
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SimpleLicenseExpression -> m SimpleLicenseExpression
gmapMp :: (forall d. Data d => d -> m d)
-> SimpleLicenseExpression -> m SimpleLicenseExpression
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SimpleLicenseExpression -> m SimpleLicenseExpression
gmapM :: (forall d. Data d => d -> m d)
-> SimpleLicenseExpression -> m SimpleLicenseExpression
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SimpleLicenseExpression -> m SimpleLicenseExpression
gmapQi :: Int -> (forall d. Data d => d -> u) -> SimpleLicenseExpression -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SimpleLicenseExpression -> u
gmapQ :: (forall d. Data d => d -> u) -> SimpleLicenseExpression -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> SimpleLicenseExpression -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> SimpleLicenseExpression
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> SimpleLicenseExpression
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> SimpleLicenseExpression
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> SimpleLicenseExpression
-> r
gmapT :: (forall b. Data b => b -> b)
-> SimpleLicenseExpression -> SimpleLicenseExpression
$cgmapT :: (forall b. Data b => b -> b)
-> SimpleLicenseExpression -> SimpleLicenseExpression
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SimpleLicenseExpression)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SimpleLicenseExpression)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c SimpleLicenseExpression)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SimpleLicenseExpression)
dataTypeOf :: SimpleLicenseExpression -> DataType
$cdataTypeOf :: SimpleLicenseExpression -> DataType
toConstr :: SimpleLicenseExpression -> Constr
$ctoConstr :: SimpleLicenseExpression -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SimpleLicenseExpression
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SimpleLicenseExpression
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SimpleLicenseExpression
-> c SimpleLicenseExpression
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SimpleLicenseExpression
-> c SimpleLicenseExpression
$cp1Data :: Typeable SimpleLicenseExpression
Data, (forall x.
 SimpleLicenseExpression -> Rep SimpleLicenseExpression x)
-> (forall x.
    Rep SimpleLicenseExpression x -> SimpleLicenseExpression)
-> Generic SimpleLicenseExpression
forall x. Rep SimpleLicenseExpression x -> SimpleLicenseExpression
forall x. SimpleLicenseExpression -> Rep SimpleLicenseExpression x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SimpleLicenseExpression x -> SimpleLicenseExpression
$cfrom :: forall x. SimpleLicenseExpression -> Rep SimpleLicenseExpression x
Generic)

simpleLicenseExpression :: LicenseId -> LicenseExpression
simpleLicenseExpression :: LicenseId -> LicenseExpression
simpleLicenseExpression LicenseId
i = SimpleLicenseExpression
-> Maybe LicenseExceptionId -> LicenseExpression
ELicense (LicenseId -> SimpleLicenseExpression
ELicenseId LicenseId
i) Maybe LicenseExceptionId
forall a. Maybe a
Nothing

instance Binary LicenseExpression
instance Binary SimpleLicenseExpression

instance Pretty LicenseExpression where
    pretty :: LicenseExpression -> Doc
pretty = Int -> LicenseExpression -> Doc
go Int
0
      where
        go :: Int -> LicenseExpression -> Disp.Doc
        go :: Int -> LicenseExpression -> Doc
go Int
_ (ELicense SimpleLicenseExpression
lic Maybe LicenseExceptionId
exc) =
            let doc :: Doc
doc = SimpleLicenseExpression -> Doc
forall a. Pretty a => a -> Doc
pretty SimpleLicenseExpression
lic
            in (Doc -> Doc)
-> (LicenseExceptionId -> Doc -> Doc)
-> Maybe LicenseExceptionId
-> Doc
-> Doc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Doc -> Doc
forall a. a -> a
id (\LicenseExceptionId
e Doc
d -> Doc
d Doc -> Doc -> Doc
<+> String -> Doc
Disp.text String
"WITH" Doc -> Doc -> Doc
<+> LicenseExceptionId -> Doc
forall a. Pretty a => a -> Doc
pretty LicenseExceptionId
e) Maybe LicenseExceptionId
exc Doc
doc
        go Int
d (EAnd LicenseExpression
e1 LicenseExpression
e2) = Bool -> Doc -> Doc
parens (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0) (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Int -> LicenseExpression -> Doc
go Int
0 LicenseExpression
e1 Doc -> Doc -> Doc
<+> String -> Doc
Disp.text String
"AND" Doc -> Doc -> Doc
<+> Int -> LicenseExpression -> Doc
go Int
0 LicenseExpression
e2
        go Int
d (EOr  LicenseExpression
e1 LicenseExpression
e2) = Bool -> Doc -> Doc
parens (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1) (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Int -> LicenseExpression -> Doc
go Int
1 LicenseExpression
e1 Doc -> Doc -> Doc
<+> String -> Doc
Disp.text String
"OR" Doc -> Doc -> Doc
<+> Int -> LicenseExpression -> Doc
go Int
1 LicenseExpression
e2


        parens :: Bool -> Doc -> Doc
parens Bool
False Doc
doc = Doc
doc
        parens Bool
True  Doc
doc = Doc -> Doc
Disp.parens Doc
doc

instance Pretty SimpleLicenseExpression where
    pretty :: SimpleLicenseExpression -> Doc
pretty (ELicenseId LicenseId
i)     = LicenseId -> Doc
forall a. Pretty a => a -> Doc
pretty LicenseId
i
    pretty (ELicenseIdPlus LicenseId
i) = LicenseId -> Doc
forall a. Pretty a => a -> Doc
pretty LicenseId
i Doc -> Doc -> Doc
<<>> Char -> Doc
Disp.char Char
'+'
    pretty (ELicenseRef LicenseRef
r)    = LicenseRef -> Doc
forall a. Pretty a => a -> Doc
pretty LicenseRef
r

instance Parsec SimpleLicenseExpression where
    parsec :: m SimpleLicenseExpression
parsec = m String
forall (m :: * -> *). CharParsing m => m String
idstring m String
-> (String -> m SimpleLicenseExpression)
-> m SimpleLicenseExpression
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> m SimpleLicenseExpression
forall (m :: * -> *).
CabalParsing m =>
String -> m SimpleLicenseExpression
simple where
        simple :: String -> m SimpleLicenseExpression
simple String
n
            | Just String
l <- String
"LicenseRef-" String -> String -> Maybe String
forall a. Eq a => [a] -> [a] -> Maybe [a]
`isPrefixOfMaybe` String
n =
                m SimpleLicenseExpression
-> (LicenseRef -> m SimpleLicenseExpression)
-> Maybe LicenseRef
-> m SimpleLicenseExpression
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> m SimpleLicenseExpression
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m SimpleLicenseExpression)
-> String -> m SimpleLicenseExpression
forall a b. (a -> b) -> a -> b
$ String
"Incorrect LicenseRef format: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
n) (SimpleLicenseExpression -> m SimpleLicenseExpression
forall (m :: * -> *) a. Monad m => a -> m a
return (SimpleLicenseExpression -> m SimpleLicenseExpression)
-> (LicenseRef -> SimpleLicenseExpression)
-> LicenseRef
-> m SimpleLicenseExpression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LicenseRef -> SimpleLicenseExpression
ELicenseRef) (Maybe LicenseRef -> m SimpleLicenseExpression)
-> Maybe LicenseRef -> m SimpleLicenseExpression
forall a b. (a -> b) -> a -> b
$ Maybe String -> String -> Maybe LicenseRef
mkLicenseRef Maybe String
forall a. Maybe a
Nothing String
l
            | Just String
d <- String
"DocumentRef-" String -> String -> Maybe String
forall a. Eq a => [a] -> [a] -> Maybe [a]
`isPrefixOfMaybe` String
n = do
                String
_ <- String -> m String
forall (m :: * -> *). CharParsing m => String -> m String
P.string String
":LicenseRef-"
                String
l <- m String
forall (m :: * -> *). CharParsing m => m String
idstring
                m SimpleLicenseExpression
-> (LicenseRef -> m SimpleLicenseExpression)
-> Maybe LicenseRef
-> m SimpleLicenseExpression
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> m SimpleLicenseExpression
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m SimpleLicenseExpression)
-> String -> m SimpleLicenseExpression
forall a b. (a -> b) -> a -> b
$ String
"Incorrect LicenseRef format:" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
n) (SimpleLicenseExpression -> m SimpleLicenseExpression
forall (m :: * -> *) a. Monad m => a -> m a
return (SimpleLicenseExpression -> m SimpleLicenseExpression)
-> (LicenseRef -> SimpleLicenseExpression)
-> LicenseRef
-> m SimpleLicenseExpression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LicenseRef -> SimpleLicenseExpression
ELicenseRef) (Maybe LicenseRef -> m SimpleLicenseExpression)
-> Maybe LicenseRef -> m SimpleLicenseExpression
forall a b. (a -> b) -> a -> b
$ Maybe String -> String -> Maybe LicenseRef
mkLicenseRef (String -> Maybe String
forall a. a -> Maybe a
Just String
d) String
l
            | Bool
otherwise = do
                CabalSpecVersion
v <- m CabalSpecVersion
forall (m :: * -> *). CabalParsing m => m CabalSpecVersion
askCabalSpecVersion
                LicenseId
l <- m LicenseId
-> (LicenseId -> m LicenseId) -> Maybe LicenseId -> m LicenseId
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> m LicenseId
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m LicenseId) -> String -> m LicenseId
forall a b. (a -> b) -> a -> b
$ String
"Unknown SPDX license identifier: '" String -> ShowS
forall a. [a] -> [a] -> [a]
++  String
n String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"' " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
licenseIdMigrationMessage String
n) LicenseId -> m LicenseId
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe LicenseId -> m LicenseId) -> Maybe LicenseId -> m LicenseId
forall a b. (a -> b) -> a -> b
$
                    LicenseListVersion -> String -> Maybe LicenseId
mkLicenseId (CabalSpecVersion -> LicenseListVersion
cabalSpecVersionToSPDXListVersion CabalSpecVersion
v) String
n
                Bool
orLater <- Maybe Char -> Bool
forall a. Maybe a -> Bool
isJust (Maybe Char -> Bool) -> m (Maybe Char) -> m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m Char -> m (Maybe Char)
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
'+')
                if Bool
orLater
                then SimpleLicenseExpression -> m SimpleLicenseExpression
forall (m :: * -> *) a. Monad m => a -> m a
return (LicenseId -> SimpleLicenseExpression
ELicenseIdPlus LicenseId
l)
                else SimpleLicenseExpression -> m SimpleLicenseExpression
forall (m :: * -> *) a. Monad m => a -> m a
return (LicenseId -> SimpleLicenseExpression
ELicenseId LicenseId
l)

idstring :: P.CharParsing m => m String
idstring :: m String
idstring = (Char -> Bool) -> m String
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m String
P.munch1 ((Char -> Bool) -> m String) -> (Char -> Bool) -> m String
forall a b. (a -> b) -> a -> b
$ \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
'.'

-- returns suffix part
isPrefixOfMaybe :: Eq a => [a] -> [a] -> Maybe [a]
isPrefixOfMaybe :: [a] -> [a] -> Maybe [a]
isPrefixOfMaybe [a]
pfx [a]
s
    | [a]
pfx [a] -> [a] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` [a]
s = [a] -> Maybe [a]
forall a. a -> Maybe a
Just (Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
drop ([a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
pfx) [a]
s)
    | Bool
otherwise          = Maybe [a]
forall a. Maybe a
Nothing

instance Parsec LicenseExpression where
    parsec :: m LicenseExpression
parsec = m LicenseExpression
expr
      where
        expr :: m LicenseExpression
expr = m LicenseExpression
compoundOr

        simple :: m LicenseExpression
simple = do
            SimpleLicenseExpression
s <- m SimpleLicenseExpression
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
            Maybe LicenseExceptionId
exc <- m (Maybe LicenseExceptionId)
exception
            LicenseExpression -> m LicenseExpression
forall (m :: * -> *) a. Monad m => a -> m a
return (LicenseExpression -> m LicenseExpression)
-> LicenseExpression -> m LicenseExpression
forall a b. (a -> b) -> a -> b
$ SimpleLicenseExpression
-> Maybe LicenseExceptionId -> LicenseExpression
ELicense SimpleLicenseExpression
s Maybe LicenseExceptionId
exc

        exception :: m (Maybe LicenseExceptionId)
exception = m LicenseExceptionId -> m (Maybe LicenseExceptionId)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
P.optional (m LicenseExceptionId -> m (Maybe LicenseExceptionId))
-> m LicenseExceptionId -> m (Maybe LicenseExceptionId)
forall a b. (a -> b) -> a -> b
$ m () -> m ()
forall (m :: * -> *) a. Parsing m => m a -> m a
P.try (m ()
spaces1 m () -> m String -> m String
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> String -> m String
forall (m :: * -> *). CharParsing m => String -> m String
P.string String
"WITH" m String -> m () -> m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> m ()
spaces1) m () -> m LicenseExceptionId -> m LicenseExceptionId
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> m LicenseExceptionId
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec

        compoundOr :: m LicenseExpression
compoundOr = do
            LicenseExpression
x <- m LicenseExpression
compoundAnd
            Maybe LicenseExpression
l <- m LicenseExpression -> m (Maybe LicenseExpression)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
P.optional (m LicenseExpression -> m (Maybe LicenseExpression))
-> m LicenseExpression -> m (Maybe LicenseExpression)
forall a b. (a -> b) -> a -> b
$ m () -> m ()
forall (m :: * -> *) a. Parsing m => m a -> m a
P.try (m ()
spaces1 m () -> m String -> m String
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> String -> m String
forall (m :: * -> *). CharParsing m => String -> m String
P.string String
"OR" m String -> m () -> m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> m ()
spaces1) m () -> m LicenseExpression -> m LicenseExpression
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> m LicenseExpression
compoundOr
            LicenseExpression -> m LicenseExpression
forall (m :: * -> *) a. Monad m => a -> m a
return (LicenseExpression -> m LicenseExpression)
-> LicenseExpression -> m LicenseExpression
forall a b. (a -> b) -> a -> b
$ (LicenseExpression -> LicenseExpression)
-> (LicenseExpression -> LicenseExpression -> LicenseExpression)
-> Maybe LicenseExpression
-> LicenseExpression
-> LicenseExpression
forall b a. b -> (a -> b) -> Maybe a -> b
maybe LicenseExpression -> LicenseExpression
forall a. a -> a
id ((LicenseExpression -> LicenseExpression -> LicenseExpression)
-> LicenseExpression -> LicenseExpression -> LicenseExpression
forall a b c. (a -> b -> c) -> b -> a -> c
flip LicenseExpression -> LicenseExpression -> LicenseExpression
EOr) Maybe LicenseExpression
l LicenseExpression
x

        compoundAnd :: m LicenseExpression
compoundAnd = do
            LicenseExpression
x <- m LicenseExpression
compound
            Maybe LicenseExpression
l <- m LicenseExpression -> m (Maybe LicenseExpression)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
P.optional (m LicenseExpression -> m (Maybe LicenseExpression))
-> m LicenseExpression -> m (Maybe LicenseExpression)
forall a b. (a -> b) -> a -> b
$ m () -> m ()
forall (m :: * -> *) a. Parsing m => m a -> m a
P.try (m ()
spaces1 m () -> m String -> m String
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> String -> m String
forall (m :: * -> *). CharParsing m => String -> m String
P.string String
"AND" m String -> m () -> m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> m ()
spaces1) m () -> m LicenseExpression -> m LicenseExpression
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> m LicenseExpression
compoundAnd
            LicenseExpression -> m LicenseExpression
forall (m :: * -> *) a. Monad m => a -> m a
return (LicenseExpression -> m LicenseExpression)
-> LicenseExpression -> m LicenseExpression
forall a b. (a -> b) -> a -> b
$ (LicenseExpression -> LicenseExpression)
-> (LicenseExpression -> LicenseExpression -> LicenseExpression)
-> Maybe LicenseExpression
-> LicenseExpression
-> LicenseExpression
forall b a. b -> (a -> b) -> Maybe a -> b
maybe LicenseExpression -> LicenseExpression
forall a. a -> a
id ((LicenseExpression -> LicenseExpression -> LicenseExpression)
-> LicenseExpression -> LicenseExpression -> LicenseExpression
forall a b c. (a -> b -> c) -> b -> a -> c
flip LicenseExpression -> LicenseExpression -> LicenseExpression
EAnd) Maybe LicenseExpression
l LicenseExpression
x

        compound :: m LicenseExpression
compound = m LicenseExpression
braces m LicenseExpression -> m LicenseExpression -> m LicenseExpression
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> m LicenseExpression
simple

        -- NOTE: we require that there's a space around AND & OR operators,
        -- i.e. @(MIT)AND(MIT)@ will cause parse-error.
        braces :: m LicenseExpression
braces = do
            Char
_ <- Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
'('
            ()
_ <- m ()
forall (m :: * -> *). CharParsing m => m ()
P.spaces
            LicenseExpression
x <- m LicenseExpression
expr
            Char
_ <- Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
')'
            LicenseExpression -> m LicenseExpression
forall (m :: * -> *) a. Monad m => a -> m a
return LicenseExpression
x

        spaces1 :: m ()
spaces1 = m Char
forall (m :: * -> *). CharParsing m => m Char
P.space m Char -> m () -> m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> m ()
forall (m :: * -> *). CharParsing m => m ()
P.spaces

-- notes:
--
-- There MUST NOT be whitespace between a license­id and any following "+".  This supports easy parsing and
-- backwards compatibility.  There MUST be whitespace on either side of the operator "WITH".  There MUST be
-- whitespace and/or parentheses on either side of the operators "AND" and "OR".
--
-- We handle that by having greedy 'idstring' parser, so MITAND would parse as invalid license identifier.

instance NFData LicenseExpression where
    rnf :: LicenseExpression -> ()
rnf (ELicense SimpleLicenseExpression
s Maybe LicenseExceptionId
e) = SimpleLicenseExpression -> ()
forall a. NFData a => a -> ()
rnf SimpleLicenseExpression
s () -> () -> ()
`seq` Maybe LicenseExceptionId -> ()
forall a. NFData a => a -> ()
rnf Maybe LicenseExceptionId
e
    rnf (EAnd LicenseExpression
x LicenseExpression
y)     = LicenseExpression -> ()
forall a. NFData a => a -> ()
rnf LicenseExpression
x () -> () -> ()
`seq` LicenseExpression -> ()
forall a. NFData a => a -> ()
rnf LicenseExpression
y
    rnf (EOr LicenseExpression
x LicenseExpression
y)      = LicenseExpression -> ()
forall a. NFData a => a -> ()
rnf LicenseExpression
x () -> () -> ()
`seq` LicenseExpression -> ()
forall a. NFData a => a -> ()
rnf LicenseExpression
y

instance NFData SimpleLicenseExpression where
    rnf :: SimpleLicenseExpression -> ()
rnf (ELicenseId LicenseId
i)     = LicenseId -> ()
forall a. NFData a => a -> ()
rnf LicenseId
i
    rnf (ELicenseIdPlus LicenseId
i) = LicenseId -> ()
forall a. NFData a => a -> ()
rnf LicenseId
i
    rnf (ELicenseRef LicenseRef
r)    = LicenseRef -> ()
forall a. NFData a => a -> ()
rnf LicenseRef
r