module Distribution.Simple.GHC.IPIConvert (
    PackageIdentifier, convertPackageId,
    License, convertLicense,
    convertModuleName
  ) where
import Prelude ()
import Distribution.Compat.Prelude
import qualified Distribution.Types.PackageId as Current
import qualified Distribution.Types.PackageName as Current
import qualified Distribution.License as Current
import qualified Distribution.SPDX as SPDX
import Distribution.Version
import Distribution.ModuleName
import Distribution.Text
data PackageIdentifier = PackageIdentifier {
    pkgName    :: String,
    pkgVersion :: Version
  }
  deriving Read
convertPackageId :: PackageIdentifier -> Current.PackageId
convertPackageId PackageIdentifier { pkgName = n, pkgVersion = v } =
  Current.PackageIdentifier (Current.mkPackageName n) v
data License = GPL | LGPL | BSD3 | BSD4
             | PublicDomain | AllRightsReserved | OtherLicense
  deriving Read
convertModuleName :: String -> ModuleName
convertModuleName s = fromMaybe (error "convertModuleName") $ simpleParse s
convertLicense :: License -> Either SPDX.License Current.License
convertLicense GPL               = Right $ Current.GPL  Nothing
convertLicense LGPL              = Right $ Current.LGPL Nothing
convertLicense BSD3              = Right $ Current.BSD3
convertLicense BSD4              = Right $ Current.BSD4
convertLicense PublicDomain      = Right $ Current.PublicDomain
convertLicense AllRightsReserved = Right $ Current.AllRightsReserved
convertLicense OtherLicense      = Right $ Current.OtherLicense