module Extensions.Package
(
getPackageExtentions
, getPackageExtentionsBySources
, getModuleAndCabalExtentions
, getModuleExtentions
, getModuleAndCabalExtentionsBySource
, getModuleExtentionsBySource
) where
import Control.Exception (catch)
import Data.ByteString (ByteString)
import Data.Functor ((<&>))
import Data.Map.Merge.Strict (mapMissing, merge, zipWithMatched)
import Data.Map.Strict (Map)
import Extensions.Cabal (parseCabalFileExtensions)
import Extensions.Module (parseFile, parseSourceWithPath)
import Extensions.Types (CabalAndModuleExtensions (..), CabalException, ExtensionsError (..),
ExtensionsResult, ModuleParseError, ParsedExtensions (..),
mergeAnyExtensions)
import qualified Data.Map.Strict as Map
getPackageExtentions
:: FilePath
-> IO (Map FilePath ExtensionsResult)
getPackageExtentions :: FilePath -> IO (Map FilePath ExtensionsResult)
getPackageExtentions FilePath
cabalFile = do
Map FilePath ParsedExtensions
cabalMap <- FilePath -> IO (Map FilePath ParsedExtensions)
parseCabalFileExtensions FilePath
cabalFile
forall (t :: * -> *) k a b.
Applicative t =>
(k -> a -> t b) -> Map k a -> t (Map k b)
Map.traverseWithKey FilePath -> ParsedExtensions -> IO ExtensionsResult
perModuleParseMerge Map FilePath ParsedExtensions
cabalMap
where
perModuleParseMerge :: FilePath -> ParsedExtensions -> IO ExtensionsResult
perModuleParseMerge :: FilePath -> ParsedExtensions -> IO ExtensionsResult
perModuleParseMerge FilePath
path ParsedExtensions
cabalExts = do
Either ModuleParseError ParsedExtensions
moduleRes <- FilePath -> IO (Either ModuleParseError ParsedExtensions)
parseFile FilePath
path
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ParsedExtensions
-> FilePath
-> Either ModuleParseError ParsedExtensions
-> ExtensionsResult
mergeCabalAndModule ParsedExtensions
cabalExts FilePath
path Either ModuleParseError ParsedExtensions
moduleRes
getPackageExtentionsBySources
:: FilePath
-> Map FilePath ByteString
-> IO (Map FilePath ExtensionsResult)
getPackageExtentionsBySources :: FilePath
-> Map FilePath ByteString -> IO (Map FilePath ExtensionsResult)
getPackageExtentionsBySources FilePath
cabalFile Map FilePath ByteString
sourcesMap =
FilePath
-> IO (Either ExtensionsError (Map FilePath ParsedExtensions))
parseCabalHandleException FilePath
cabalFile forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \case
Left ExtensionsError
err -> forall a b. a -> Either a b
Left ExtensionsError
err forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Map FilePath ByteString
sourcesMap
Right Map FilePath ParsedExtensions
cabalMap -> forall k a c b.
Ord k =>
SimpleWhenMissing k a c
-> SimpleWhenMissing k b c
-> SimpleWhenMatched k a b c
-> Map k a
-> Map k b
-> Map k c
merge
(forall (f :: * -> *) k x y.
Applicative f =>
(k -> x -> y) -> WhenMissing f k x y
mapMissing FilePath -> ParsedExtensions -> ExtensionsResult
cabalNotSource)
(forall (f :: * -> *) k x y.
Applicative f =>
(k -> x -> y) -> WhenMissing f k x y
mapMissing FilePath -> ByteString -> ExtensionsResult
sourceNotCabal)
(forall (f :: * -> *) k x y z.
Applicative f =>
(k -> x -> y -> z) -> WhenMatched f k x y z
zipWithMatched FilePath -> ParsedExtensions -> ByteString -> ExtensionsResult
cabalAndSource)
Map FilePath ParsedExtensions
cabalMap
Map FilePath ByteString
sourcesMap
where
cabalNotSource :: FilePath -> ParsedExtensions -> ExtensionsResult
cabalNotSource :: FilePath -> ParsedExtensions -> ExtensionsResult
cabalNotSource FilePath
path ParsedExtensions
_cabalExts = forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ FilePath -> ExtensionsError
SourceNotFound FilePath
path
sourceNotCabal :: FilePath -> ByteString -> ExtensionsResult
sourceNotCabal :: FilePath -> ByteString -> ExtensionsResult
sourceNotCabal FilePath
path ByteString
_source = forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ FilePath -> ExtensionsError
NotCabalModule FilePath
path
cabalAndSource
:: FilePath
-> ParsedExtensions
-> ByteString
-> ExtensionsResult
cabalAndSource :: FilePath -> ParsedExtensions -> ByteString -> ExtensionsResult
cabalAndSource FilePath
path ParsedExtensions
cabalExts ByteString
source =
ParsedExtensions
-> FilePath
-> Either ModuleParseError ParsedExtensions
-> ExtensionsResult
mergeCabalAndModule ParsedExtensions
cabalExts FilePath
path forall a b. (a -> b) -> a -> b
$ FilePath -> ByteString -> Either ModuleParseError ParsedExtensions
parseSourceWithPath FilePath
path ByteString
source
getModuleAndCabalExtentions
:: FilePath
-> FilePath
-> IO (Either ExtensionsError CabalAndModuleExtensions)
getModuleAndCabalExtentions :: FilePath
-> FilePath -> IO (Either ExtensionsError CabalAndModuleExtensions)
getModuleAndCabalExtentions FilePath
cabalFile FilePath
path =
FilePath
-> IO (Either ExtensionsError (Map FilePath ParsedExtensions))
parseCabalHandleException FilePath
cabalFile forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Left ExtensionsError
err -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left ExtensionsError
err
Right Map FilePath ParsedExtensions
cabalMap -> case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup FilePath
path Map FilePath ParsedExtensions
cabalMap of
Maybe ParsedExtensions
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ FilePath -> ExtensionsError
NotCabalModule FilePath
path
Just ParsedExtensions
cabalExts -> FilePath
-> ParsedExtensions
-> Either ModuleParseError ParsedExtensions
-> Either ExtensionsError CabalAndModuleExtensions
getCabalAndModuleExts FilePath
path ParsedExtensions
cabalExts forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO (Either ModuleParseError ParsedExtensions)
parseFile FilePath
path
getModuleExtentions
:: FilePath
-> FilePath
-> IO ExtensionsResult
getModuleExtentions :: FilePath -> FilePath -> IO ExtensionsResult
getModuleExtentions FilePath
cabalFile FilePath
path =
FilePath
-> IO (Either ExtensionsError (Map FilePath ParsedExtensions))
parseCabalHandleException FilePath
cabalFile forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Left ExtensionsError
err -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left ExtensionsError
err
Right Map FilePath ParsedExtensions
cabalMap -> case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup FilePath
path Map FilePath ParsedExtensions
cabalMap of
Maybe ParsedExtensions
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ FilePath -> ExtensionsError
NotCabalModule FilePath
path
Just ParsedExtensions
cabalExts -> do
Either ModuleParseError ParsedExtensions
moduleRes <- FilePath -> IO (Either ModuleParseError ParsedExtensions)
parseFile FilePath
path
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ParsedExtensions
-> FilePath
-> Either ModuleParseError ParsedExtensions
-> ExtensionsResult
mergeCabalAndModule ParsedExtensions
cabalExts FilePath
path Either ModuleParseError ParsedExtensions
moduleRes
getModuleAndCabalExtentionsBySource
:: FilePath
-> FilePath
-> ByteString
-> IO (Either ExtensionsError CabalAndModuleExtensions)
getModuleAndCabalExtentionsBySource :: FilePath
-> FilePath
-> ByteString
-> IO (Either ExtensionsError CabalAndModuleExtensions)
getModuleAndCabalExtentionsBySource FilePath
cabalFile FilePath
path ByteString
source =
FilePath
-> IO (Either ExtensionsError (Map FilePath ParsedExtensions))
parseCabalHandleException FilePath
cabalFile forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \case
Left ExtensionsError
cabalError -> forall a b. a -> Either a b
Left ExtensionsError
cabalError
Right Map FilePath ParsedExtensions
cabalMap -> case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup FilePath
path Map FilePath ParsedExtensions
cabalMap of
Maybe ParsedExtensions
Nothing -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ FilePath -> ExtensionsError
NotCabalModule FilePath
path
Just ParsedExtensions
cabalExts -> FilePath
-> ParsedExtensions
-> Either ModuleParseError ParsedExtensions
-> Either ExtensionsError CabalAndModuleExtensions
getCabalAndModuleExts FilePath
path ParsedExtensions
cabalExts
(FilePath -> ByteString -> Either ModuleParseError ParsedExtensions
parseSourceWithPath FilePath
path ByteString
source)
getModuleExtentionsBySource
:: FilePath
-> FilePath
-> ByteString
-> IO ExtensionsResult
getModuleExtentionsBySource :: FilePath -> FilePath -> ByteString -> IO ExtensionsResult
getModuleExtentionsBySource FilePath
cabalFile FilePath
path ByteString
source =
FilePath
-> IO (Either ExtensionsError (Map FilePath ParsedExtensions))
parseCabalHandleException FilePath
cabalFile forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \case
Left ExtensionsError
cabalError -> forall a b. a -> Either a b
Left ExtensionsError
cabalError
Right Map FilePath ParsedExtensions
cabalMap -> case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup FilePath
path Map FilePath ParsedExtensions
cabalMap of
Maybe ParsedExtensions
Nothing -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ FilePath -> ExtensionsError
NotCabalModule FilePath
path
Just ParsedExtensions
cabalExts -> ParsedExtensions
-> FilePath
-> Either ModuleParseError ParsedExtensions
-> ExtensionsResult
mergeCabalAndModule ParsedExtensions
cabalExts FilePath
path
(FilePath -> ByteString -> Either ModuleParseError ParsedExtensions
parseSourceWithPath FilePath
path ByteString
source)
mergeCabalAndModule
:: ParsedExtensions
-> FilePath
-> Either ModuleParseError ParsedExtensions
-> ExtensionsResult
mergeCabalAndModule :: ParsedExtensions
-> FilePath
-> Either ModuleParseError ParsedExtensions
-> ExtensionsResult
mergeCabalAndModule ParsedExtensions
cabalExts FilePath
path Either ModuleParseError ParsedExtensions
moduleRes = case Either ModuleParseError ParsedExtensions
moduleRes of
Right ParsedExtensions
moduleExts -> ParsedExtensions -> ParsedExtensions -> ExtensionsResult
mergeAnyExtensions ParsedExtensions
cabalExts ParsedExtensions
moduleExts
Left ModuleParseError
parseErr -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ FilePath -> ModuleParseError -> ExtensionsError
ModuleParseError FilePath
path ModuleParseError
parseErr
parseCabalHandleException
:: FilePath
-> IO (Either ExtensionsError (Map FilePath ParsedExtensions))
parseCabalHandleException :: FilePath
-> IO (Either ExtensionsError (Map FilePath ParsedExtensions))
parseCabalHandleException FilePath
cabalFile = (forall a b. b -> Either a b
Right forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO (Map FilePath ParsedExtensions)
parseCabalFileExtensions FilePath
cabalFile)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` CabalException
-> IO (Either ExtensionsError (Map FilePath ParsedExtensions))
handleCabalException
handleCabalException
:: CabalException
-> IO (Either ExtensionsError (Map FilePath ParsedExtensions))
handleCabalException :: CabalException
-> IO (Either ExtensionsError (Map FilePath ParsedExtensions))
handleCabalException = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left forall b c a. (b -> c) -> (a -> b) -> a -> c
. CabalException -> ExtensionsError
CabalError
getCabalAndModuleExts
:: FilePath
-> ParsedExtensions
-> Either ModuleParseError ParsedExtensions
-> Either ExtensionsError CabalAndModuleExtensions
getCabalAndModuleExts :: FilePath
-> ParsedExtensions
-> Either ModuleParseError ParsedExtensions
-> Either ExtensionsError CabalAndModuleExtensions
getCabalAndModuleExts FilePath
path ParsedExtensions
cabalExts Either ModuleParseError ParsedExtensions
moduleRes = case Either ModuleParseError ParsedExtensions
moduleRes of
Left ModuleParseError
err -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ FilePath -> ModuleParseError -> ExtensionsError
ModuleParseError FilePath
path ModuleParseError
err
Right ParsedExtensions
moduleExts -> forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ CabalAndModuleExtensions
{ cabalExtensions :: ParsedExtensions
cabalExtensions = ParsedExtensions
cabalExts
, moduleExtensions :: ParsedExtensions
moduleExtensions = ParsedExtensions
moduleExts
}