{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE RecordWildCards #-}
module GHC.Unit.Database
( GenericUnitInfo(..)
, type DbUnitInfo
, DbModule (..)
, DbInstUnitId (..)
, mapGenericUnitInfo
, DbMode(..)
, DbOpenMode(..)
, isDbOpenReadMode
, readPackageDbForGhc
, readPackageDbForGhcPkg
, writePackageDb
, PackageDbLock
, lockPackageDb
, unlockPackageDb
, mkMungePathUrl
, mungeUnitInfoPaths
)
where
import Prelude
import Data.Version (Version(..))
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BS.Char8
import qualified Data.ByteString.Lazy as BS.Lazy
import qualified Data.ByteString.Lazy.Internal as BS.Lazy (defaultChunkSize)
import qualified Data.Foldable as F
import qualified Data.Traversable as F
import Data.Bifunctor
import Data.Binary as Bin
import Data.Binary.Put as Bin
import Data.Binary.Get as Bin
import Control.Exception as Exception
import Control.Monad (when)
import System.FilePath as FilePath
import qualified System.FilePath.Posix as FilePath.Posix
import System.IO
import System.IO.Error
import GHC.IO.Exception (IOErrorType(InappropriateType))
import GHC.IO.Handle.Lock
import System.Directory
import Data.List (stripPrefix)
type DbUnitInfo = GenericUnitInfo BS.ByteString BS.ByteString BS.ByteString BS.ByteString BS.ByteString DbModule
data GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod = GenericUnitInfo
{ GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId :: uid
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> compid
unitInstanceOf :: compid
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(modulename, mod)]
unitInstantiations :: [(modulename, mod)]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> srcpkgid
unitPackageId :: srcpkgid
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> srcpkgname
unitPackageName :: srcpkgname
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Version
unitPackageVersion :: Version
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Maybe srcpkgname
unitComponentName :: Maybe srcpkgname
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> String
unitAbiHash :: String
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [uid]
unitDepends :: [uid]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(uid, String)]
unitAbiDepends :: [(uid, String)]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitImportDirs :: [FilePath]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitLibraries :: [String]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitExtDepLibsSys :: [String]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitExtDepLibsGhc :: [String]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitLibraryDirs :: [FilePath]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitLibraryDynDirs :: [FilePath]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitExtDepFrameworks :: [String]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitExtDepFrameworkDirs :: [FilePath]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitLinkerOptions :: [String]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitCcOptions :: [String]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitIncludes :: [String]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitIncludeDirs :: [FilePath]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitHaddockInterfaces :: [FilePath]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitHaddockHTMLs :: [FilePath]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(modulename, Maybe mod)]
unitExposedModules :: [(modulename, Maybe mod)]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [modulename]
unitHiddenModules :: [modulename]
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
unitIsIndefinite :: Bool
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
unitIsExposed :: Bool
, GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
unitIsTrusted :: Bool
}
deriving (GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
(GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool)
-> (GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool)
-> Eq
(GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall compid srcpkgid srcpkgname uid modulename mod.
(Eq uid, Eq compid, Eq modulename, Eq mod, Eq srcpkgid,
Eq srcpkgname) =>
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
/= :: GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
$c/= :: forall compid srcpkgid srcpkgname uid modulename mod.
(Eq uid, Eq compid, Eq modulename, Eq mod, Eq srcpkgid,
Eq srcpkgname) =>
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
== :: GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
$c== :: forall compid srcpkgid srcpkgname uid modulename mod.
(Eq uid, Eq compid, Eq modulename, Eq mod, Eq srcpkgid,
Eq srcpkgname) =>
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
Evidence bound by a type signature of the constraint type Eq mod
External instance of the constraint type Eq Char
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
External instance of the constraint type Eq Bool
External instance of the constraint type Eq Bool
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
Evidence bound by a type signature of the constraint type Eq modulename
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
Evidence bound by a type signature of the constraint type Eq mod
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
Evidence bound by a type signature of the constraint type Eq uid
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type Eq Version
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
Evidence bound by a type signature of the constraint type Eq modulename
Evidence bound by a type signature of the constraint type Eq mod
External instance of the constraint type forall a. Eq a => Eq [a]
Evidence bound by a type signature of the constraint type Eq srcpkgname
Evidence bound by a type signature of the constraint type Eq srcpkgid
Evidence bound by a type signature of the constraint type Eq mod
Evidence bound by a type signature of the constraint type Eq modulename
Evidence bound by a type signature of the constraint type Eq compid
Evidence bound by a type signature of the constraint type Eq uid
Eq, Int
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> ShowS
[GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod]
-> ShowS
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> String
(Int
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> ShowS)
-> (GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> String)
-> ([GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod]
-> ShowS)
-> Show
(GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall compid srcpkgid srcpkgname uid modulename mod.
(Show uid, Show compid, Show modulename, Show mod, Show srcpkgid,
Show srcpkgname) =>
Int
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> ShowS
forall compid srcpkgid srcpkgname uid modulename mod.
(Show uid, Show compid, Show modulename, Show mod, Show srcpkgid,
Show srcpkgname) =>
[GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod]
-> ShowS
forall compid srcpkgid srcpkgname uid modulename mod.
(Show uid, Show compid, Show modulename, Show mod, Show srcpkgid,
Show srcpkgname) =>
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> String
showList :: [GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod]
-> ShowS
$cshowList :: forall compid srcpkgid srcpkgname uid modulename mod.
(Show uid, Show compid, Show modulename, Show mod, Show srcpkgid,
Show srcpkgname) =>
[GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod]
-> ShowS
show :: GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> String
$cshow :: forall compid srcpkgid srcpkgname uid modulename mod.
(Show uid, Show compid, Show modulename, Show mod, Show srcpkgid,
Show srcpkgname) =>
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> String
showsPrec :: Int
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> ShowS
$cshowsPrec :: forall compid srcpkgid srcpkgname uid modulename mod.
(Show uid, Show compid, Show modulename, Show mod, Show srcpkgid,
Show srcpkgname) =>
Int
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> ShowS
External instance of the constraint type forall a. Show a => Show (Maybe a)
Evidence bound by a type signature of the constraint type Show mod
External instance of the constraint type Show Char
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
External instance of the constraint type Show Bool
External instance of the constraint type Show Bool
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
Evidence bound by a type signature of the constraint type Show modulename
External instance of the constraint type forall a. Show a => Show (Maybe a)
Evidence bound by a type signature of the constraint type Show mod
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
Evidence bound by a type signature of the constraint type Show uid
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type Show Char
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type Show Version
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
Evidence bound by a type signature of the constraint type Show modulename
Evidence bound by a type signature of the constraint type Show mod
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Ord Int
Evidence bound by a type signature of the constraint type Show srcpkgname
Evidence bound by a type signature of the constraint type Show srcpkgid
Evidence bound by a type signature of the constraint type Show mod
Evidence bound by a type signature of the constraint type Show modulename
Evidence bound by a type signature of the constraint type Show compid
Evidence bound by a type signature of the constraint type Show uid
Show)
mapGenericUnitInfo
:: (uid1 -> uid2)
-> (cid1 -> cid2)
-> (srcpkg1 -> srcpkg2)
-> (srcpkgname1 -> srcpkgname2)
-> (modname1 -> modname2)
-> (mod1 -> mod2)
-> (GenericUnitInfo cid1 srcpkg1 srcpkgname1 uid1 modname1 mod1
-> GenericUnitInfo cid2 srcpkg2 srcpkgname2 uid2 modname2 mod2)
mapGenericUnitInfo :: (uid1 -> uid2)
-> (cid1 -> cid2)
-> (srcpkg1 -> srcpkg2)
-> (srcpkgname1 -> srcpkgname2)
-> (modname1 -> modname2)
-> (mod1 -> mod2)
-> GenericUnitInfo cid1 srcpkg1 srcpkgname1 uid1 modname1 mod1
-> GenericUnitInfo cid2 srcpkg2 srcpkgname2 uid2 modname2 mod2
mapGenericUnitInfo uid1 -> uid2
fuid cid1 -> cid2
fcid srcpkg1 -> srcpkg2
fsrcpkg srcpkgname1 -> srcpkgname2
fsrcpkgname modname1 -> modname2
fmodname mod1 -> mod2
fmod g :: GenericUnitInfo cid1 srcpkg1 srcpkgname1 uid1 modname1 mod1
g@(GenericUnitInfo {uid1
cid1
srcpkg1
srcpkgname1
Bool
[uid1]
[modname1]
String
[String]
[(uid1, String)]
[(modname1, mod1)]
[(modname1, Maybe mod1)]
Maybe srcpkgname1
Version
unitIsTrusted :: Bool
unitIsExposed :: Bool
unitIsIndefinite :: Bool
unitHiddenModules :: [modname1]
unitExposedModules :: [(modname1, Maybe mod1)]
unitHaddockHTMLs :: [String]
unitHaddockInterfaces :: [String]
unitIncludeDirs :: [String]
unitIncludes :: [String]
unitCcOptions :: [String]
unitLinkerOptions :: [String]
unitExtDepFrameworkDirs :: [String]
unitExtDepFrameworks :: [String]
unitLibraryDynDirs :: [String]
unitLibraryDirs :: [String]
unitExtDepLibsGhc :: [String]
unitExtDepLibsSys :: [String]
unitLibraries :: [String]
unitImportDirs :: [String]
unitAbiDepends :: [(uid1, String)]
unitDepends :: [uid1]
unitAbiHash :: String
unitComponentName :: Maybe srcpkgname1
unitPackageVersion :: Version
unitPackageName :: srcpkgname1
unitPackageId :: srcpkg1
unitInstantiations :: [(modname1, mod1)]
unitInstanceOf :: cid1
unitId :: uid1
unitIsTrusted :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
unitIsExposed :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
unitIsIndefinite :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
unitHiddenModules :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [modulename]
unitExposedModules :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(modulename, Maybe mod)]
unitHaddockHTMLs :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitHaddockInterfaces :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitIncludeDirs :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitIncludes :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitCcOptions :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitLinkerOptions :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitExtDepFrameworkDirs :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitExtDepFrameworks :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitLibraryDynDirs :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitLibraryDirs :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitExtDepLibsGhc :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitExtDepLibsSys :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitLibraries :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitImportDirs :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitAbiDepends :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(uid, String)]
unitDepends :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [uid]
unitAbiHash :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> String
unitComponentName :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Maybe srcpkgname
unitPackageVersion :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Version
unitPackageName :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> srcpkgname
unitPackageId :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> srcpkgid
unitInstantiations :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(modulename, mod)]
unitInstanceOf :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> compid
unitId :: forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
..}) =
GenericUnitInfo cid1 srcpkg1 srcpkgname1 uid1 modname1 mod1
g { unitId :: uid2
unitId = uid1 -> uid2
fuid uid1
unitId
, unitInstanceOf :: cid2
unitInstanceOf = cid1 -> cid2
fcid cid1
unitInstanceOf
, unitInstantiations :: [(modname2, mod2)]
unitInstantiations = ((modname1, mod1) -> (modname2, mod2))
-> [(modname1, mod1)] -> [(modname2, mod2)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor []
fmap ((modname1 -> modname2)
-> (mod1 -> mod2) -> (modname1, mod1) -> (modname2, mod2)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
External instance of the constraint type Bifunctor (,)
bimap modname1 -> modname2
fmodname mod1 -> mod2
fmod) [(modname1, mod1)]
unitInstantiations
, unitPackageId :: srcpkg2
unitPackageId = srcpkg1 -> srcpkg2
fsrcpkg srcpkg1
unitPackageId
, unitPackageName :: srcpkgname2
unitPackageName = srcpkgname1 -> srcpkgname2
fsrcpkgname srcpkgname1
unitPackageName
, unitComponentName :: Maybe srcpkgname2
unitComponentName = (srcpkgname1 -> srcpkgname2)
-> Maybe srcpkgname1 -> Maybe srcpkgname2
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
fmap srcpkgname1 -> srcpkgname2
fsrcpkgname Maybe srcpkgname1
unitComponentName
, unitDepends :: [uid2]
unitDepends = (uid1 -> uid2) -> [uid1] -> [uid2]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor []
fmap uid1 -> uid2
fuid [uid1]
unitDepends
, unitAbiDepends :: [(uid2, String)]
unitAbiDepends = ((uid1, String) -> (uid2, String))
-> [(uid1, String)] -> [(uid2, String)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor []
fmap ((uid1 -> uid2) -> (uid1, String) -> (uid2, String)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
External instance of the constraint type Bifunctor (,)
first uid1 -> uid2
fuid) [(uid1, String)]
unitAbiDepends
, unitExposedModules :: [(modname2, Maybe mod2)]
unitExposedModules = ((modname1, Maybe mod1) -> (modname2, Maybe mod2))
-> [(modname1, Maybe mod1)] -> [(modname2, Maybe mod2)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor []
fmap ((modname1 -> modname2)
-> (Maybe mod1 -> Maybe mod2)
-> (modname1, Maybe mod1)
-> (modname2, Maybe mod2)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
External instance of the constraint type Bifunctor (,)
bimap modname1 -> modname2
fmodname ((mod1 -> mod2) -> Maybe mod1 -> Maybe mod2
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
fmap mod1 -> mod2
fmod)) [(modname1, Maybe mod1)]
unitExposedModules
, unitHiddenModules :: [modname2]
unitHiddenModules = (modname1 -> modname2) -> [modname1] -> [modname2]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor []
fmap modname1 -> modname2
fmodname [modname1]
unitHiddenModules
}
data DbModule
= DbModule
{ DbModule -> DbInstUnitId
dbModuleUnitId :: DbInstUnitId
, DbModule -> ByteString
dbModuleName :: BS.ByteString
}
| DbModuleVar
{ DbModule -> ByteString
dbModuleVarName :: BS.ByteString
}
deriving (DbModule -> DbModule -> Bool
(DbModule -> DbModule -> Bool)
-> (DbModule -> DbModule -> Bool) -> Eq DbModule
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DbModule -> DbModule -> Bool
$c/= :: DbModule -> DbModule -> Bool
== :: DbModule -> DbModule -> Bool
$c== :: DbModule -> DbModule -> Bool
External instance of the constraint type Eq ByteString
Instance of class: Eq of the constraint type Eq DbInstUnitId
Eq, Int -> DbModule -> ShowS
[DbModule] -> ShowS
DbModule -> String
(Int -> DbModule -> ShowS)
-> (DbModule -> String) -> ([DbModule] -> ShowS) -> Show DbModule
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DbModule] -> ShowS
$cshowList :: [DbModule] -> ShowS
show :: DbModule -> String
$cshow :: DbModule -> String
showsPrec :: Int -> DbModule -> ShowS
$cshowsPrec :: Int -> DbModule -> ShowS
External instance of the constraint type Show ByteString
External instance of the constraint type Show ByteString
External instance of the constraint type Ord Int
External instance of the constraint type Ord Int
Instance of class: Show of the constraint type Show DbInstUnitId
Show)
data DbInstUnitId
= DbInstUnitId
BS.ByteString
[(BS.ByteString, DbModule)]
| DbUnitId
BS.ByteString
deriving (DbInstUnitId -> DbInstUnitId -> Bool
(DbInstUnitId -> DbInstUnitId -> Bool)
-> (DbInstUnitId -> DbInstUnitId -> Bool) -> Eq DbInstUnitId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DbInstUnitId -> DbInstUnitId -> Bool
$c/= :: DbInstUnitId -> DbInstUnitId -> Bool
== :: DbInstUnitId -> DbInstUnitId -> Bool
$c== :: DbInstUnitId -> DbInstUnitId -> Bool
Instance of class: Eq of the constraint type Eq DbModule
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
External instance of the constraint type Eq ByteString
Instance of class: Eq of the constraint type Eq DbModule
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq ByteString
Instance of class: Eq of the constraint type Eq DbModule
Eq, Int -> DbInstUnitId -> ShowS
[DbInstUnitId] -> ShowS
DbInstUnitId -> String
(Int -> DbInstUnitId -> ShowS)
-> (DbInstUnitId -> String)
-> ([DbInstUnitId] -> ShowS)
-> Show DbInstUnitId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DbInstUnitId] -> ShowS
$cshowList :: [DbInstUnitId] -> ShowS
show :: DbInstUnitId -> String
$cshow :: DbInstUnitId -> String
showsPrec :: Int -> DbInstUnitId -> ShowS
$cshowsPrec :: Int -> DbInstUnitId -> ShowS
Instance of class: Show of the constraint type Show DbModule
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
External instance of the constraint type Show ByteString
Instance of class: Show of the constraint type Show DbModule
External instance of the constraint type Show ByteString
External instance of the constraint type Ord Int
External instance of the constraint type Show ByteString
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Ord Int
Instance of class: Show of the constraint type Show DbModule
Show)
newtype PackageDbLock = PackageDbLock Handle
lockPackageDb :: FilePath -> IO PackageDbLock
unlockPackageDb :: PackageDbLock -> IO ()
lockPackageDbWith :: LockMode -> FilePath -> IO PackageDbLock
lockPackageDbWith :: LockMode -> String -> IO PackageDbLock
lockPackageDbWith LockMode
mode String
file = do
(IOError -> Maybe ())
-> IO PackageDbLock -> (() -> IO PackageDbLock) -> IO PackageDbLock
forall e b a.
Exception e =>
(e -> Maybe b) -> IO a -> (b -> IO a) -> IO a
External instance of the constraint type Exception IOError
catchJust
(\IOError
e -> if IOError -> Bool
isPermissionError IOError
e then () -> Maybe ()
forall a. a -> Maybe a
Just () else Maybe ()
forall a. Maybe a
Nothing)
(IOMode -> IO PackageDbLock
lockFileOpenIn IOMode
ReadWriteMode)
(IO PackageDbLock -> () -> IO PackageDbLock
forall a b. a -> b -> a
const (IO PackageDbLock -> () -> IO PackageDbLock)
-> IO PackageDbLock -> () -> IO PackageDbLock
forall a b. (a -> b) -> a -> b
$ IOMode -> IO PackageDbLock
lockFileOpenIn IOMode
ReadMode)
where
lock :: String
lock = String
file String -> ShowS
<.> String
"lock"
lockFileOpenIn :: IOMode -> IO PackageDbLock
lockFileOpenIn IOMode
io_mode = IO Handle
-> (Handle -> IO ())
-> (Handle -> IO PackageDbLock)
-> IO PackageDbLock
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracketOnError
(String -> IOMode -> IO Handle
openBinaryFile String
lock IOMode
io_mode)
Handle -> IO ()
hClose
((Handle -> IO PackageDbLock) -> IO PackageDbLock)
-> (Handle -> IO PackageDbLock) -> IO PackageDbLock
forall a b. (a -> b) -> a -> b
$ \Handle
hnd -> do Handle -> LockMode -> IO ()
hLock Handle
hnd LockMode
mode IO () -> (FileLockingNotSupported -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
External instance of the constraint type Exception FileLockingNotSupported
`catch` \FileLockingNotSupported
FileLockingNotSupported -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ()
PackageDbLock -> IO PackageDbLock
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (PackageDbLock -> IO PackageDbLock)
-> PackageDbLock -> IO PackageDbLock
forall a b. (a -> b) -> a -> b
$ Handle -> PackageDbLock
PackageDbLock Handle
hnd
lockPackageDb :: String -> IO PackageDbLock
lockPackageDb = LockMode -> String -> IO PackageDbLock
lockPackageDbWith LockMode
ExclusiveLock
unlockPackageDb :: PackageDbLock -> IO ()
unlockPackageDb (PackageDbLock Handle
hnd) = do
Handle -> IO ()
hUnlock Handle
hnd
Handle -> IO ()
hClose Handle
hnd
data DbMode = DbReadOnly | DbReadWrite
data DbOpenMode (mode :: DbMode) t where
DbOpenReadOnly :: DbOpenMode 'DbReadOnly t
DbOpenReadWrite :: t -> DbOpenMode 'DbReadWrite t
deriving instance Functor (DbOpenMode mode)
deriving instance F.Foldable (DbOpenMode mode)
deriving instance F.Traversable (DbOpenMode mode)
isDbOpenReadMode :: DbOpenMode mode t -> Bool
isDbOpenReadMode :: DbOpenMode mode t -> Bool
isDbOpenReadMode = \case
DbOpenMode mode t
DbOpenReadOnly -> Bool
True
DbOpenReadWrite{} -> Bool
False
readPackageDbForGhc :: FilePath -> IO [DbUnitInfo]
readPackageDbForGhc :: String -> IO [DbUnitInfo]
readPackageDbForGhc String
file =
String
-> DbOpenMode 'DbReadOnly Any
-> Get [DbUnitInfo]
-> IO ([DbUnitInfo], DbOpenMode 'DbReadOnly PackageDbLock)
forall (mode :: DbMode) t pkgs.
String
-> DbOpenMode mode t
-> Get pkgs
-> IO (pkgs, DbOpenMode mode PackageDbLock)
decodeFromFile String
file DbOpenMode 'DbReadOnly Any
forall t. DbOpenMode 'DbReadOnly t
DbOpenReadOnly Get [DbUnitInfo]
getDbForGhc IO ([DbUnitInfo], DbOpenMode 'DbReadOnly PackageDbLock)
-> (([DbUnitInfo], DbOpenMode 'DbReadOnly PackageDbLock)
-> IO [DbUnitInfo])
-> IO [DbUnitInfo]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
External instance of the constraint type Monad IO
>>= \case
([DbUnitInfo]
pkgs, DbOpenMode 'DbReadOnly PackageDbLock
External instance of the constraint type Monad IO
DbOpenReadOnly) -> [DbUnitInfo] -> IO [DbUnitInfo]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return [DbUnitInfo]
pkgs
where
getDbForGhc :: Get [DbUnitInfo]
getDbForGhc = do
(Word32, Word32)
_version <- Get (Word32, Word32)
getHeader
Word32
_ghcPartLen <- Get Word32
forall t. Binary t => Get t
External instance of the constraint type Binary Word32
get :: Get Word32
[DbUnitInfo]
ghcPart <- Get [DbUnitInfo]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
Instance of class: Binary of the constraint type Binary DbUnitInfo
get
[DbUnitInfo] -> Get [DbUnitInfo]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return [DbUnitInfo]
ghcPart
readPackageDbForGhcPkg :: Binary pkgs => FilePath -> DbOpenMode mode t ->
IO (pkgs, DbOpenMode mode PackageDbLock)
readPackageDbForGhcPkg :: String
-> DbOpenMode mode t -> IO (pkgs, DbOpenMode mode PackageDbLock)
readPackageDbForGhcPkg String
file DbOpenMode mode t
mode =
String
-> DbOpenMode mode t
-> Get pkgs
-> IO (pkgs, DbOpenMode mode PackageDbLock)
forall (mode :: DbMode) t pkgs.
String
-> DbOpenMode mode t
-> Get pkgs
-> IO (pkgs, DbOpenMode mode PackageDbLock)
decodeFromFile String
file DbOpenMode mode t
mode Get pkgs
getDbForGhcPkg
where
getDbForGhcPkg :: Get pkgs
getDbForGhcPkg = do
(Word32, Word32)
_version <- Get (Word32, Word32)
getHeader
Word32
ghcPartLen <- Get Word32
forall t. Binary t => Get t
External instance of the constraint type Binary Word32
get :: Get Word32
()
_ghcPart <- Int -> Get ()
skip (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral Word32
fromIntegral Word32
ghcPartLen)
pkgs
ghcPkgPart <- Get pkgs
forall t. Binary t => Get t
Evidence bound by a type signature of the constraint type Binary pkgs
get
pkgs -> Get pkgs
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return pkgs
ghcPkgPart
writePackageDb :: Binary pkgs => FilePath -> [DbUnitInfo] -> pkgs -> IO ()
writePackageDb :: String -> [DbUnitInfo] -> pkgs -> IO ()
writePackageDb String
file [DbUnitInfo]
ghcPkgs pkgs
ghcPkgPart =
String -> ByteString -> IO ()
writeFileAtomic String
file (Put -> ByteString
runPut Put
putDbForGhcPkg)
where
putDbForGhcPkg :: Put
putDbForGhcPkg = do
Put
putHeader
Word32 -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Word32
put Word32
ghcPartLen
ByteString -> Put
putLazyByteString ByteString
ghcPart
pkgs -> Put
forall t. Binary t => t -> Put
Evidence bound by a type signature of the constraint type Binary pkgs
put pkgs
ghcPkgPart
where
ghcPartLen :: Word32
ghcPartLen :: Word32
ghcPartLen = Int64 -> Word32
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Word32
External instance of the constraint type Integral Int64
fromIntegral (ByteString -> Int64
BS.Lazy.length ByteString
ghcPart)
ghcPart :: ByteString
ghcPart = [DbUnitInfo] -> ByteString
forall a. Binary a => a -> ByteString
External instance of the constraint type forall a. Binary a => Binary [a]
Instance of class: Binary of the constraint type Binary DbUnitInfo
encode [DbUnitInfo]
ghcPkgs
getHeader :: Get (Word32, Word32)
= do
ByteString
magic <- Int -> Get ByteString
getByteString (ByteString -> Int
BS.length ByteString
headerMagic)
Bool -> Get () -> Get ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type Applicative Get
when (ByteString
magic ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq ByteString
/= ByteString
headerMagic) (Get () -> Get ()) -> Get () -> Get ()
forall a b. (a -> b) -> a -> b
$
String -> Get ()
forall (m :: * -> *) a. MonadFail m => String -> m a
External instance of the constraint type MonadFail Get
fail String
"not a ghc-pkg db file, wrong file magic number"
Word32
majorVersion <- Get Word32
forall t. Binary t => Get t
External instance of the constraint type Binary Word32
get :: Get Word32
Word32
minorVersion <- Get Word32
forall t. Binary t => Get t
External instance of the constraint type Binary Word32
get :: Get Word32
Bool -> Get () -> Get ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type Applicative Get
when (Word32
majorVersion Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Word32
/= Word32
1) (Get () -> Get ()) -> Get () -> Get ()
forall a b. (a -> b) -> a -> b
$
String -> Get ()
forall (m :: * -> *) a. MonadFail m => String -> m a
External instance of the constraint type MonadFail Get
fail String
"unsupported ghc-pkg db format version"
Word32
headerExtraLen <- Get Word32
forall t. Binary t => Get t
External instance of the constraint type Binary Word32
get :: Get Word32
Int -> Get ()
skip (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral Word32
fromIntegral Word32
headerExtraLen)
(Word32, Word32) -> Get (Word32, Word32)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return (Word32
majorVersion, Word32
minorVersion)
putHeader :: Put
= do
ByteString -> Put
putByteString ByteString
headerMagic
Word32 -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Word32
put Word32
majorVersion
Word32 -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Word32
put Word32
minorVersion
Word32 -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Word32
put Word32
headerExtraLen
where
majorVersion :: Word32
majorVersion = Word32
1 :: Word32
minorVersion :: Word32
minorVersion = Word32
0 :: Word32
headerExtraLen :: Word32
headerExtraLen = Word32
0 :: Word32
headerMagic :: BS.ByteString
= String -> ByteString
BS.Char8.pack String
"\0ghcpkg\0"
decodeFromFile :: FilePath -> DbOpenMode mode t -> Get pkgs ->
IO (pkgs, DbOpenMode mode PackageDbLock)
decodeFromFile :: String
-> DbOpenMode mode t
-> Get pkgs
-> IO (pkgs, DbOpenMode mode PackageDbLock)
decodeFromFile String
file DbOpenMode mode t
mode Get pkgs
decoder = case DbOpenMode mode t
mode of
DbOpenMode mode t
External instance of the constraint type Functor IO
DbOpenReadOnly -> do
#if defined(mingw32_HOST_OS)
bracket (lockPackageDbWith SharedLock file) unlockPackageDb $ \_ -> do
#endif
(, DbOpenMode 'DbReadOnly PackageDbLock
forall t. DbOpenMode 'DbReadOnly t
DbOpenReadOnly) (pkgs -> (pkgs, DbOpenMode 'DbReadOnly PackageDbLock))
-> IO pkgs -> IO (pkgs, DbOpenMode 'DbReadOnly PackageDbLock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> IO pkgs
decodeFileContents
DbOpenReadWrite{} -> do
IO PackageDbLock
-> (PackageDbLock -> IO ())
-> (PackageDbLock
-> IO (pkgs, DbOpenMode 'DbReadWrite PackageDbLock))
-> IO (pkgs, DbOpenMode 'DbReadWrite PackageDbLock)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracketOnError (String -> IO PackageDbLock
lockPackageDb String
file) PackageDbLock -> IO ()
unlockPackageDb ((PackageDbLock
-> IO (pkgs, DbOpenMode 'DbReadWrite PackageDbLock))
-> IO (pkgs, DbOpenMode 'DbReadWrite PackageDbLock))
-> (PackageDbLock
-> IO (pkgs, DbOpenMode 'DbReadWrite PackageDbLock))
-> IO (pkgs, DbOpenMode 'DbReadWrite PackageDbLock)
forall a b. (a -> b) -> a -> b
$ \PackageDbLock
lock -> do
(, PackageDbLock -> DbOpenMode 'DbReadWrite PackageDbLock
forall t. t -> DbOpenMode 'DbReadWrite t
DbOpenReadWrite PackageDbLock
lock) (pkgs -> (pkgs, DbOpenMode 'DbReadWrite PackageDbLock))
-> IO pkgs -> IO (pkgs, DbOpenMode 'DbReadWrite PackageDbLock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> IO pkgs
decodeFileContents
where
decodeFileContents :: IO pkgs
decodeFileContents = String -> IOMode -> (Handle -> IO pkgs) -> IO pkgs
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile String
file IOMode
ReadMode ((Handle -> IO pkgs) -> IO pkgs) -> (Handle -> IO pkgs) -> IO pkgs
forall a b. (a -> b) -> a -> b
$ \Handle
hnd ->
Handle -> Decoder pkgs -> IO pkgs
feed Handle
hnd (Get pkgs -> Decoder pkgs
forall a. Get a -> Decoder a
runGetIncremental Get pkgs
decoder)
feed :: Handle -> Decoder pkgs -> IO pkgs
feed Handle
hnd (Partial Maybe ByteString -> Decoder pkgs
k) = do ByteString
chunk <- Handle -> Int -> IO ByteString
BS.hGet Handle
hnd Int
BS.Lazy.defaultChunkSize
if ByteString -> Bool
BS.null ByteString
chunk
then Handle -> Decoder pkgs -> IO pkgs
feed Handle
hnd (Maybe ByteString -> Decoder pkgs
k Maybe ByteString
forall a. Maybe a
Nothing)
else Handle -> Decoder pkgs -> IO pkgs
feed Handle
hnd (Maybe ByteString -> Decoder pkgs
k (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
chunk))
feed Handle
_ (Done ByteString
_ Int64
_ pkgs
res) = pkgs -> IO pkgs
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return pkgs
res
feed Handle
_ (Fail ByteString
_ Int64
_ String
msg) = IOError -> IO pkgs
forall a. IOError -> IO a
ioError IOError
err
where
err :: IOError
err = IOErrorType -> String -> Maybe Handle -> Maybe String -> IOError
mkIOError IOErrorType
InappropriateType String
loc Maybe Handle
forall a. Maybe a
Nothing (String -> Maybe String
forall a. a -> Maybe a
Just String
file)
IOError -> String -> IOError
`ioeSetErrorString` String
msg
loc :: String
loc = String
"GHC.Unit.Database.readPackageDb"
writeFileAtomic :: FilePath -> BS.Lazy.ByteString -> IO ()
writeFileAtomic :: String -> ByteString -> IO ()
writeFileAtomic String
targetPath ByteString
content = do
let (String
targetDir, String
targetFile) = String -> (String, String)
splitFileName String
targetPath
IO (String, Handle)
-> ((String, Handle) -> IO ())
-> ((String, Handle) -> IO ())
-> IO ()
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
Exception.bracketOnError
(String -> String -> IO (String, Handle)
openBinaryTempFileWithDefaultPermissions String
targetDir (String -> IO (String, Handle)) -> String -> IO (String, Handle)
forall a b. (a -> b) -> a -> b
$ String
targetFile String -> ShowS
<.> String
"tmp")
(\(String
tmpPath, Handle
handle) -> Handle -> IO ()
hClose Handle
handle IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad IO
>> String -> IO ()
removeFile String
tmpPath)
(\(String
tmpPath, Handle
handle) -> do
Handle -> ByteString -> IO ()
BS.Lazy.hPut Handle
handle ByteString
content
Handle -> IO ()
hClose Handle
handle
String -> String -> IO ()
renameFile String
tmpPath String
targetPath)
instance Binary DbUnitInfo where
put :: DbUnitInfo -> Put
put (GenericUnitInfo
ByteString
unitId ByteString
unitInstanceOf [(ByteString, DbModule)]
unitInstantiations
ByteString
unitPackageId
ByteString
unitPackageName Version
unitPackageVersion
Maybe ByteString
unitComponentName
String
unitAbiHash [ByteString]
unitDepends [(ByteString, String)]
unitAbiDepends [String]
unitImportDirs
[String]
unitLibraries [String]
unitExtDepLibsSys [String]
unitExtDepLibsGhc
[String]
unitLibraryDirs [String]
unitLibraryDynDirs
[String]
unitExtDepFrameworks [String]
unitExtDepFrameworkDirs
[String]
unitLinkerOptions [String]
unitCcOptions
[String]
unitIncludes [String]
unitIncludeDirs
[String]
unitHaddockInterfaces [String]
unitHaddockHTMLs
[(ByteString, Maybe DbModule)]
unitExposedModules [ByteString]
unitHiddenModules
Bool
unitIsIndefinite Bool
unitIsExposed Bool
unitIsTrusted) = do
ByteString -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary ByteString
put ByteString
unitPackageId
ByteString -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary ByteString
put ByteString
unitPackageName
Version -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Version
put Version
unitPackageVersion
Maybe ByteString -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary ByteString
put Maybe ByteString
unitComponentName
ByteString -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary ByteString
put ByteString
unitId
ByteString -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary ByteString
put ByteString
unitInstanceOf
[(ByteString, DbModule)] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary ByteString
Instance of class: Binary of the constraint type Binary DbModule
put [(ByteString, DbModule)]
unitInstantiations
String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
unitAbiHash
[ByteString] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary ByteString
put [ByteString]
unitDepends
[(ByteString, String)] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary ByteString
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put [(ByteString, String)]
unitAbiDepends
[String] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put [String]
unitImportDirs
[String] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put [String]
unitLibraries
[String] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put [String]
unitExtDepLibsSys
[String] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put [String]
unitExtDepLibsGhc
[String] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put [String]
unitLibraryDirs
[String] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put [String]
unitLibraryDynDirs
[String] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put [String]
unitExtDepFrameworks
[String] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put [String]
unitExtDepFrameworkDirs
[String] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put [String]
unitLinkerOptions
[String] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put [String]
unitCcOptions
[String] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put [String]
unitIncludes
[String] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put [String]
unitIncludeDirs
[String] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put [String]
unitHaddockInterfaces
[String] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put [String]
unitHaddockHTMLs
[(ByteString, Maybe DbModule)] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary ByteString
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
Instance of class: Binary of the constraint type Binary DbModule
put [(ByteString, Maybe DbModule)]
unitExposedModules
[ByteString] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary ByteString
put [ByteString]
unitHiddenModules
Bool -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Bool
put Bool
unitIsIndefinite
Bool -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Bool
put Bool
unitIsExposed
Bool -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Bool
put Bool
unitIsTrusted
get :: Get DbUnitInfo
get = do
ByteString
unitPackageId <- Get ByteString
forall t. Binary t => Get t
External instance of the constraint type Binary ByteString
get
ByteString
unitPackageName <- Get ByteString
forall t. Binary t => Get t
External instance of the constraint type Binary ByteString
get
Version
unitPackageVersion <- Get Version
forall t. Binary t => Get t
External instance of the constraint type Binary Version
get
Maybe ByteString
unitComponentName <- Get (Maybe ByteString)
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary ByteString
get
ByteString
unitId <- Get ByteString
forall t. Binary t => Get t
External instance of the constraint type Binary ByteString
get
ByteString
unitInstanceOf <- Get ByteString
forall t. Binary t => Get t
External instance of the constraint type Binary ByteString
get
[(ByteString, DbModule)]
unitInstantiations <- Get [(ByteString, DbModule)]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary ByteString
Instance of class: Binary of the constraint type Binary DbModule
get
String
unitAbiHash <- Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
[ByteString]
unitDepends <- Get [ByteString]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary ByteString
get
[(ByteString, String)]
unitAbiDepends <- Get [(ByteString, String)]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary ByteString
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
[String]
unitImportDirs <- Get [String]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
[String]
unitLibraries <- Get [String]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
[String]
unitExtDepLibsSys <- Get [String]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
[String]
unitExtDepLibsGhc <- Get [String]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
[String]
libraryDirs <- Get [String]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
[String]
libraryDynDirs <- Get [String]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
[String]
frameworks <- Get [String]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
[String]
frameworkDirs <- Get [String]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
[String]
unitLinkerOptions <- Get [String]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
[String]
unitCcOptions <- Get [String]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
[String]
unitIncludes <- Get [String]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
[String]
unitIncludeDirs <- Get [String]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
[String]
unitHaddockInterfaces <- Get [String]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
[String]
unitHaddockHTMLs <- Get [String]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
[(ByteString, Maybe DbModule)]
unitExposedModules <- Get [(ByteString, Maybe DbModule)]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary ByteString
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
Instance of class: Binary of the constraint type Binary DbModule
get
[ByteString]
unitHiddenModules <- Get [ByteString]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary ByteString
get
Bool
unitIsIndefinite <- Get Bool
forall t. Binary t => Get t
External instance of the constraint type Binary Bool
get
Bool
unitIsExposed <- Get Bool
forall t. Binary t => Get t
External instance of the constraint type Binary Bool
get
Bool
unitIsTrusted <- Get Bool
forall t. Binary t => Get t
External instance of the constraint type Binary Bool
get
DbUnitInfo -> Get DbUnitInfo
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return (ByteString
-> ByteString
-> [(ByteString, DbModule)]
-> ByteString
-> ByteString
-> Version
-> Maybe ByteString
-> String
-> [ByteString]
-> [(ByteString, String)]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [(ByteString, Maybe DbModule)]
-> [ByteString]
-> Bool
-> Bool
-> Bool
-> DbUnitInfo
forall compid srcpkgid srcpkgname uid modulename mod.
uid
-> compid
-> [(modulename, mod)]
-> srcpkgid
-> srcpkgname
-> Version
-> Maybe srcpkgname
-> String
-> [uid]
-> [(uid, String)]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [(modulename, Maybe mod)]
-> [modulename]
-> Bool
-> Bool
-> Bool
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
GenericUnitInfo
ByteString
unitId
ByteString
unitInstanceOf
[(ByteString, DbModule)]
unitInstantiations
ByteString
unitPackageId
ByteString
unitPackageName
Version
unitPackageVersion
Maybe ByteString
unitComponentName
String
unitAbiHash
[ByteString]
unitDepends
[(ByteString, String)]
unitAbiDepends
[String]
unitImportDirs
[String]
unitLibraries [String]
unitExtDepLibsSys [String]
unitExtDepLibsGhc
[String]
libraryDirs [String]
libraryDynDirs
[String]
frameworks [String]
frameworkDirs
[String]
unitLinkerOptions [String]
unitCcOptions
[String]
unitIncludes [String]
unitIncludeDirs
[String]
unitHaddockInterfaces [String]
unitHaddockHTMLs
[(ByteString, Maybe DbModule)]
unitExposedModules
[ByteString]
unitHiddenModules
Bool
unitIsIndefinite Bool
unitIsExposed Bool
unitIsTrusted)
instance Binary DbModule where
put :: DbModule -> Put
put (DbModule DbInstUnitId
dbModuleUnitId ByteString
dbModuleName) = do
Word8 -> Put
putWord8 Word8
0
DbInstUnitId -> Put
forall t. Binary t => t -> Put
Instance of class: Binary of the constraint type Binary DbInstUnitId
put DbInstUnitId
dbModuleUnitId
ByteString -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary ByteString
put ByteString
dbModuleName
put (DbModuleVar ByteString
dbModuleVarName) = do
Word8 -> Put
putWord8 Word8
1
ByteString -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary ByteString
put ByteString
dbModuleVarName
get :: Get DbModule
get = do
Word8
b <- Get Word8
getWord8
case Word8
b of
Word8
0 -> DbInstUnitId -> ByteString -> DbModule
DbModule (DbInstUnitId -> ByteString -> DbModule)
-> Get DbInstUnitId -> Get (ByteString -> DbModule)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get DbInstUnitId
forall t. Binary t => Get t
Instance of class: Binary of the constraint type Binary DbInstUnitId
get Get (ByteString -> DbModule) -> Get ByteString -> Get DbModule
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get ByteString
forall t. Binary t => Get t
External instance of the constraint type Binary ByteString
get
Word8
_ -> ByteString -> DbModule
DbModuleVar (ByteString -> DbModule) -> Get ByteString -> Get DbModule
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get ByteString
forall t. Binary t => Get t
External instance of the constraint type Binary ByteString
get
instance Binary DbInstUnitId where
put :: DbInstUnitId -> Put
put (DbUnitId ByteString
uid) = do
Word8 -> Put
putWord8 Word8
0
ByteString -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary ByteString
put ByteString
uid
put (DbInstUnitId ByteString
dbUnitIdComponentId [(ByteString, DbModule)]
dbUnitIdInsts) = do
Word8 -> Put
putWord8 Word8
1
ByteString -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary ByteString
put ByteString
dbUnitIdComponentId
[(ByteString, DbModule)] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary ByteString
Instance of class: Binary of the constraint type Binary DbModule
put [(ByteString, DbModule)]
dbUnitIdInsts
get :: Get DbInstUnitId
get = do
Word8
b <- Get Word8
getWord8
case Word8
b of
Word8
0 -> ByteString -> DbInstUnitId
DbUnitId (ByteString -> DbInstUnitId) -> Get ByteString -> Get DbInstUnitId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get ByteString
forall t. Binary t => Get t
External instance of the constraint type Binary ByteString
get
Word8
_ -> ByteString -> [(ByteString, DbModule)] -> DbInstUnitId
DbInstUnitId (ByteString -> [(ByteString, DbModule)] -> DbInstUnitId)
-> Get ByteString -> Get ([(ByteString, DbModule)] -> DbInstUnitId)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get ByteString
forall t. Binary t => Get t
External instance of the constraint type Binary ByteString
get Get ([(ByteString, DbModule)] -> DbInstUnitId)
-> Get [(ByteString, DbModule)] -> Get DbInstUnitId
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get [(ByteString, DbModule)]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type Binary ByteString
Instance of class: Binary of the constraint type Binary DbModule
get
mkMungePathUrl :: FilePath -> FilePath -> (FilePath -> FilePath, FilePath -> FilePath)
mkMungePathUrl :: String -> String -> (ShowS, ShowS)
mkMungePathUrl String
top_dir String
pkgroot = (ShowS
munge_path, ShowS
munge_url)
where
munge_path :: ShowS
munge_path String
p
| Just String
p' <- String -> String -> Maybe String
stripVarPrefix String
"${pkgroot}" String
p = String
pkgroot String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
p'
| Just String
p' <- String -> String -> Maybe String
stripVarPrefix String
"$topdir" String
p = String
top_dir String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
p'
| Bool
otherwise = String
p
munge_url :: ShowS
munge_url String
p
| Just String
p' <- String -> String -> Maybe String
stripVarPrefix String
"${pkgrooturl}" String
p = String -> ShowS
toUrlPath String
pkgroot String
p'
| Just String
p' <- String -> String -> Maybe String
stripVarPrefix String
"$httptopdir" String
p = String -> ShowS
toUrlPath String
top_dir String
p'
| Bool
otherwise = String
p
toUrlPath :: String -> ShowS
toUrlPath String
r String
p = String
"file:///"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ [String] -> String
FilePath.Posix.joinPath
(String
r String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
(String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile ((Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
External instance of the constraint type Foldable []
all Char -> Bool
isPathSeparator)
(String -> [String]
FilePath.splitDirectories String
p))
stripVarPrefix :: String -> String -> Maybe String
stripVarPrefix String
var String
path = case String -> String -> Maybe String
forall a. Eq a => [a] -> [a] -> Maybe [a]
External instance of the constraint type Eq Char
stripPrefix String
var String
path of
Just [] -> String -> Maybe String
forall a. a -> Maybe a
Just []
Just cs :: String
cs@(Char
c : String
_) | Char -> Bool
isPathSeparator Char
c -> String -> Maybe String
forall a. a -> Maybe a
Just String
cs
Maybe String
_ -> Maybe String
forall a. Maybe a
Nothing
mungeUnitInfoPaths :: FilePath -> FilePath -> GenericUnitInfo a b c d e f -> GenericUnitInfo a b c d e f
mungeUnitInfoPaths :: String
-> String
-> GenericUnitInfo a b c d e f
-> GenericUnitInfo a b c d e f
mungeUnitInfoPaths String
top_dir String
pkgroot GenericUnitInfo a b c d e f
pkg =
GenericUnitInfo a b c d e f
pkg
{ unitImportDirs :: [String]
unitImportDirs = [String] -> [String]
munge_paths (GenericUnitInfo a b c d e f -> [String]
forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitImportDirs GenericUnitInfo a b c d e f
pkg)
, unitIncludeDirs :: [String]
unitIncludeDirs = [String] -> [String]
munge_paths (GenericUnitInfo a b c d e f -> [String]
forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitIncludeDirs GenericUnitInfo a b c d e f
pkg)
, unitLibraryDirs :: [String]
unitLibraryDirs = [String] -> [String]
munge_paths (GenericUnitInfo a b c d e f -> [String]
forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitLibraryDirs GenericUnitInfo a b c d e f
pkg)
, unitLibraryDynDirs :: [String]
unitLibraryDynDirs = [String] -> [String]
munge_paths (GenericUnitInfo a b c d e f -> [String]
forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitLibraryDynDirs GenericUnitInfo a b c d e f
pkg)
, unitExtDepFrameworkDirs :: [String]
unitExtDepFrameworkDirs = [String] -> [String]
munge_paths (GenericUnitInfo a b c d e f -> [String]
forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitExtDepFrameworkDirs GenericUnitInfo a b c d e f
pkg)
, unitHaddockInterfaces :: [String]
unitHaddockInterfaces = [String] -> [String]
munge_paths (GenericUnitInfo a b c d e f -> [String]
forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitHaddockInterfaces GenericUnitInfo a b c d e f
pkg)
, unitHaddockHTMLs :: [String]
unitHaddockHTMLs = [String] -> [String]
munge_paths ([String] -> [String]
munge_urls (GenericUnitInfo a b c d e f -> [String]
forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [String]
unitHaddockHTMLs GenericUnitInfo a b c d e f
pkg))
}
where
munge_paths :: [String] -> [String]
munge_paths = ShowS -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ShowS
munge_path
munge_urls :: [String] -> [String]
munge_urls = ShowS -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ShowS
munge_url
(ShowS
munge_path,ShowS
munge_url) = String -> String -> (ShowS, ShowS)
mkMungePathUrl String
top_dir String
pkgroot