spdx-0.2.2.0: SPDX license expression language

Copyright(c) 2015 Oleg Grenrus
LicenseBSD3
MaintainerOleg Grenrus <oleg.grenrus@iki.fi>
Safe HaskellSafe
LanguageHaskell98

Data.SPDX

Contents

Description

 

Synopsis

Types

data LicenseId Source #

Opaque license identifier type.

Instances

Eq LicenseId Source # 
Data LicenseId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LicenseId -> c LicenseId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LicenseId #

toConstr :: LicenseId -> Constr #

dataTypeOf :: LicenseId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LicenseId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LicenseId) #

gmapT :: (forall b. Data b => b -> b) -> LicenseId -> LicenseId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LicenseId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LicenseId -> r #

gmapQ :: (forall d. Data d => d -> u) -> LicenseId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LicenseId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LicenseId -> m LicenseId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LicenseId -> m LicenseId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LicenseId -> m LicenseId #

Ord LicenseId Source # 
Read LicenseId Source # 
Show LicenseId Source # 
Generic LicenseId Source # 

Associated Types

type Rep LicenseId :: * -> * #

type Rep LicenseId Source # 
type Rep LicenseId = D1 (MetaData "LicenseId" "Data.SPDX.Types" "spdx-0.2.2.0-6sTWw4uv4IO3OJf6P0KC10" True) (C1 (MetaCons "LicenseId" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

data LicenseExceptionId Source #

Opaque license exception identifier type.

Instances

Eq LicenseExceptionId Source # 
Data LicenseExceptionId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LicenseExceptionId -> c LicenseExceptionId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LicenseExceptionId #

toConstr :: LicenseExceptionId -> Constr #

dataTypeOf :: LicenseExceptionId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LicenseExceptionId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LicenseExceptionId) #

gmapT :: (forall b. Data b => b -> b) -> LicenseExceptionId -> LicenseExceptionId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LicenseExceptionId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LicenseExceptionId -> r #

gmapQ :: (forall d. Data d => d -> u) -> LicenseExceptionId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LicenseExceptionId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LicenseExceptionId -> m LicenseExceptionId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LicenseExceptionId -> m LicenseExceptionId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LicenseExceptionId -> m LicenseExceptionId #

Ord LicenseExceptionId Source # 
Read LicenseExceptionId Source # 
Show LicenseExceptionId Source # 
Generic LicenseExceptionId Source # 
type Rep LicenseExceptionId Source # 
type Rep LicenseExceptionId = D1 (MetaData "LicenseExceptionId" "Data.SPDX.Types" "spdx-0.2.2.0-6sTWw4uv4IO3OJf6P0KC10" True) (C1 (MetaCons "LicenseExceptionId" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

data LicenseRef Source #

Constructors

LicenseRef 

Instances

Eq LicenseRef Source # 
Data LicenseRef Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LicenseRef -> c LicenseRef #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LicenseRef #

toConstr :: LicenseRef -> Constr #

dataTypeOf :: LicenseRef -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LicenseRef) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LicenseRef) #

gmapT :: (forall b. Data b => b -> b) -> LicenseRef -> LicenseRef #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LicenseRef -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LicenseRef -> r #

gmapQ :: (forall d. Data d => d -> u) -> LicenseRef -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LicenseRef -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LicenseRef -> m LicenseRef #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LicenseRef -> m LicenseRef #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LicenseRef -> m LicenseRef #

Ord LicenseRef Source # 
Read LicenseRef Source # 
Show LicenseRef Source # 
Generic LicenseRef Source # 

Associated Types

type Rep LicenseRef :: * -> * #

type Rep LicenseRef Source # 
type Rep LicenseRef = D1 (MetaData "LicenseRef" "Data.SPDX.Types" "spdx-0.2.2.0-6sTWw4uv4IO3OJf6P0KC10" False) (C1 (MetaCons "LicenseRef" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "lrDocument") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe String))) (S1 (MetaSel (Just Symbol "lrLicense") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String))))

data LicenseExpression Source #

Instances

Eq LicenseExpression Source # 
Data LicenseExpression Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LicenseExpression -> c LicenseExpression #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LicenseExpression #

toConstr :: LicenseExpression -> Constr #

dataTypeOf :: LicenseExpression -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LicenseExpression) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LicenseExpression) #

gmapT :: (forall b. Data b => b -> b) -> LicenseExpression -> LicenseExpression #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LicenseExpression -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LicenseExpression -> r #

gmapQ :: (forall d. Data d => d -> u) -> LicenseExpression -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LicenseExpression -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LicenseExpression -> m LicenseExpression #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LicenseExpression -> m LicenseExpression #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LicenseExpression -> m LicenseExpression #

Ord LicenseExpression Source # 
Read LicenseExpression Source # 
Show LicenseExpression Source # 
Generic LicenseExpression Source # 
type Rep LicenseExpression Source # 

Data

licenses :: [(LicenseId, String, Bool)] Source #

A list of LicenseId, license name and whether the license is OSI approved.

See http://spdx.org/licenses/.

licenseIdentifiers :: [LicenseId] Source #

A list of SPDX licenses identifiers.

See http://spdx.org/licenses/.

mkLicenseId :: String -> Maybe LicenseId Source #

Lookup LicenseId by string representation

Ranges

lookupLicenseRange :: LicenseId -> [LicenseId] Source #

Lookup newer licenses we know about

>>> lookupLicenseRange $ fromJust $ mkLicenseId "MIT"
[LicenseId "MIT"]
>>> lookupLicenseRange $ fromJust $ mkLicenseId "GPL-2.0"
[LicenseId "GPL-2.0",LicenseId "GPL-3.0"]
>>> lookupLicenseRange $ fromJust $ mkLicenseId "LGPL-2.0"
[LicenseId "LGPL-2.0",LicenseId "LGPL-2.1",LicenseId "LGPL-3.0"]

Parsing

parseExpression :: String -> [LicenseExpression] Source #

Parse SPDX License Expression

>>> parseExpression "LGPL-2.1 OR MIT"
[EDisjunction (ELicense False (Right (LicenseId "LGPL-2.1")) Nothing) (ELicense False (Right (LicenseId "MIT")) Nothing)]

Prettifying

Inverse of parsing

Logic

satisfies Source #

Arguments

:: LicenseExpression

package license

-> LicenseExpression

license policy

-> Bool 
⟦ satisfies a b ⟧ ≡ a ≥ b ≡ a ∧ b = b
>>> unsafeParseExpr "GPL-3.0" `satisfies` unsafeParseExpr "ISC AND MIT"
False
>>> unsafeParseExpr "Zlib" `satisfies` unsafeParseExpr "ISC AND MIT AND Zlib"
True
>>> unsafeParseExpr "(MIT OR GPL-2.0)" `satisfies` unsafeParseExpr "(ISC AND MIT)"
True
>>> unsafeParseExpr "(MIT AND GPL-2.0)" `satisfies` unsafeParseExpr "(MIT AND GPL-2.0)"
True
>>> unsafeParseExpr "(MIT AND GPL-2.0)" `satisfies` unsafeParseExpr "(ISC AND GPL-2.0)"
False

equivalent :: LicenseExpression -> LicenseExpression -> Bool Source #

Check wheather two LicenseExpression are equivalent.

>>> unsafeParseExpr "(MIT AND GPL-2.0)" `equivalent` unsafeParseExpr "(GPL-2.0 AND MIT)"
True
>>> unsafeParseExpr "MIT" `equivalent` unsafeParseExpr "MIT OR BSD-3-Clause"
False