{- |
Copyright: (c) 2020 Kowainik
SPDX-License-Identifier: MPL-2.0
Maintainer: Kowainik <xrom.xkov@gmail.com>

File (or module) specific information.
-}

module Stan.FileInfo
    ( FileMap
    , FileInfo (..)

    , extensionsToText
    , isExtensionDisabled
    ) where

import Extensions (Extensions (..), ExtensionsError, ExtensionsResult, OnOffExtension (..),
                   ParsedExtensions (..), showOnOffExtension)
import GHC.LanguageExtensions.Type (Extension)

import Stan.Core.ModuleName (ModuleName)
import Stan.Observation (Observations)

import qualified Data.Set as Set


-- | File specific information.
data FileInfo = FileInfo
    { FileInfo -> FilePath
fileInfoPath             :: !FilePath
    , FileInfo -> ModuleName
fileInfoModuleName       :: !ModuleName
    , FileInfo -> Int
fileInfoLoc              :: !Int
    , FileInfo -> Either ExtensionsError ParsedExtensions
fileInfoCabalExtensions  :: !(Either ExtensionsError ParsedExtensions)
    , FileInfo -> Either ExtensionsError ParsedExtensions
fileInfoExtensions       :: !(Either ExtensionsError ParsedExtensions)
    , FileInfo -> ExtensionsResult
fileInfoMergedExtensions :: !ExtensionsResult
    , FileInfo -> Observations
fileInfoObservations     :: !Observations
    } deriving stock (Int -> FileInfo -> ShowS
[FileInfo] -> ShowS
FileInfo -> FilePath
(Int -> FileInfo -> ShowS)
-> (FileInfo -> FilePath) -> ([FileInfo] -> ShowS) -> Show FileInfo
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [FileInfo] -> ShowS
$cshowList :: [FileInfo] -> ShowS
show :: FileInfo -> FilePath
$cshow :: FileInfo -> FilePath
showsPrec :: Int -> FileInfo -> ShowS
$cshowsPrec :: Int -> FileInfo -> ShowS
Show, FileInfo -> FileInfo -> Bool
(FileInfo -> FileInfo -> Bool)
-> (FileInfo -> FileInfo -> Bool) -> Eq FileInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileInfo -> FileInfo -> Bool
$c/= :: FileInfo -> FileInfo -> Bool
== :: FileInfo -> FileInfo -> Bool
$c== :: FileInfo -> FileInfo -> Bool
Eq)

type FileMap = Map FilePath FileInfo

-- | Return the list of pretty-printed extensions.
extensionsToText :: Either ExtensionsError ParsedExtensions -> [Text]
extensionsToText :: Either ExtensionsError ParsedExtensions -> [Text]
extensionsToText = \case
    Left _ -> ["Unable to extract extensions"]
    Right ParsedExtensions{..} ->
        let exts :: [Text]
exts = (OnOffExtension -> Text) -> [OnOffExtension] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map OnOffExtension -> Text
showOnOffExtension [OnOffExtension]
parsedExtensionsAll in
        case Maybe SafeHaskellExtension
parsedExtensionsSafe of
            Just s :: SafeHaskellExtension
s  -> SafeHaskellExtension -> Text
forall b a. (Show a, IsString b) => a -> b
show SafeHaskellExtension
s Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
exts
            Nothing -> [Text]
exts

{- | Check whether the given extension is disabled
-}
isExtensionDisabled :: Extension -> ExtensionsResult -> Bool
isExtensionDisabled :: Extension -> ExtensionsResult -> Bool
isExtensionDisabled ext :: Extension
ext = \case
    Left _ -> Bool
True  -- no info about extensions, consider it disabled
    Right Extensions{..} ->
           OnOffExtension -> Set OnOffExtension -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.notMember (Extension -> OnOffExtension
On Extension
ext) Set OnOffExtension
extensionsAll
        Bool -> Bool -> Bool
|| OnOffExtension -> Set OnOffExtension -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member (Extension -> OnOffExtension
Off Extension
ext) Set OnOffExtension
extensionsAll