{-# LANGUAGE TypeFamilies #-} module Descript.Misc.Build.Read.File.SFile ( SFile (..) , FileSummary (..) , mkSFile , loadSFile , ifile , defaultFileScope ) where import Descript.Misc.Build.Read.File.Scope import Descript.Misc.Error import Descript.Misc.Summary import qualified Text.Megaparsec.Error as Parsec import Text.Megaparsec.Error hiding (ParseError) import Data.Text (Text) import qualified Data.Text.IO as Text import System.FilePath -- | A self-contained source file. data SFile = SFile { sfileName :: String , sfileContents :: Text } deriving (Eq, Ord, Read, Show) -- | Can get a summary of an instance given the file it came from. class FileSummary a where -- A summary of the value, given the file it came from. summaryF :: SFile -> a -> String instance (FileSummary e, Summary a) => FileSummary (Result e a) where summaryF file (Failure err) = "Failure: " ++ summaryF file err summaryF _ (Success val) = summary val instance (ShowErrorComponent e, t ~ Char) => FileSummary (Parsec.ParseError t e) where summaryF file err = parseErrorPretty' (sfileContents file) err -- | Creates a file at the given path. mkSFile :: FilePath -> Text -> SFile mkSFile path contents = SFile { sfileName = takeBaseName path , sfileContents = contents } -- | Reads the file with the given path. loadSFile :: FilePath -> IO SFile loadSFile path = mkSFile path <$> Text.readFile path -- | Creates a file for text in "interactive mode" (e.g. from a -- console). ifile :: Text -> SFile ifile contents = SFile { sfileName = ifileName , sfileContents = contents } -- | The scope of the module in the file, if the module doesn't have an -- explicit scope. defaultFileScope :: SFile -> AbsScope defaultFileScope = AbsScope . pure . sfileName ifileName :: String ifileName = ""