{-# LANGUAGE TemplateHaskell #-}
module Network.Protocol.OpenSource.License (
OSIIdentifier(..)
, OSILink(..)
, OSIOtherName(..)
, OSIText(..)
, OSILicense(..)
, allLicenses
, licensesMatchingKeyword
, licenseById
, licenseBySchemeAndIdentifier
) where
import Control.Monad.Trans.Except (ExceptT(..))
import Data.Aeson (eitherDecode)
import Data.Aeson.TH (defaultOptions, deriveJSON, Options(..))
import Data.Char (toLower)
import Data.Text (Text)
import Network.HTTP.Client (httpLbs, newManager, parseUrlThrow, responseBody)
import Network.HTTP.Client.TLS (tlsManagerSettings)
data OSIIdentifier = OSIIdentifier {
oiIdentifier :: Text
, oiScheme :: Text
} deriving (Eq, Read, Show)
$(deriveJSON defaultOptions{fieldLabelModifier = (map toLower . drop 2), constructorTagModifier = map toLower} ''OSIIdentifier)
data OSILink = OSILink {
olNote :: Text
, olUrl :: Text
} deriving (Eq, Read, Show)
$(deriveJSON defaultOptions{fieldLabelModifier = (map toLower . drop 2), constructorTagModifier = map toLower} ''OSILink)
data OSIOtherName = OSIOtherName {
oonName :: Text
, oonNote :: Maybe Text
} deriving (Eq, Read, Show)
$(deriveJSON defaultOptions{fieldLabelModifier = (map toLower . drop 3), constructorTagModifier = map toLower} ''OSIOtherName)
data OSIText = OSIText {
otMedia_type :: Text
, otTitle :: Text
, otURL :: Text
} deriving (Eq, Read, Show)
$(deriveJSON defaultOptions{fieldLabelModifier = (map toLower . drop 2), constructorTagModifier = map toLower} ''OSIText)
data OSILicense = OSILicense {
olId :: Text
, olName :: Text
, olSuperseded_by :: Maybe Text
, olKeywords :: [Text]
, olIdentifiers :: [OSIIdentifier]
, olLinks :: [OSILink]
, olOther_names :: [OSIOtherName]
, olText :: [OSIText]
} deriving (Eq, Read, Show)
$(deriveJSON defaultOptions{fieldLabelModifier = (map toLower . drop 2), constructorTagModifier = map toLower} ''OSILicense)
getLicenses :: String -> ExceptT String IO [OSILicense]
getLicenses k = ExceptT $ do
manager <- newManager tlsManagerSettings
request <- parseUrlThrow $ "https://api.opensource.org/licenses/" ++ k
response <- httpLbs request manager
return . eitherDecode . responseBody $ response
allLicenses :: ExceptT String IO [OSILicense]
allLicenses = getLicenses ""
licensesMatchingKeyword :: String -> ExceptT String IO [OSILicense]
licensesMatchingKeyword = getLicenses
getLicense :: String -> ExceptT String IO OSILicense
getLicense k = ExceptT $ do
manager <- newManager tlsManagerSettings
request <- parseUrlThrow $ "https://api.opensource.org/license/" ++ k
response <- httpLbs request manager
return . eitherDecode . responseBody $ response
licenseById :: String -> ExceptT String IO OSILicense
licenseById = getLicense
licenseBySchemeAndIdentifier :: String -> String -> ExceptT String IO OSILicense
licenseBySchemeAndIdentifier s i = getLicense (concat [s, "/", i])