{-# LANGUAGE DeriveFunctor #-} module Descript.Misc.Build.Read.File.DFile ( GenDFile (..) , mkTextFile , loadTextFile , fileName , fileContents ) where import Descript.Misc.Build.Read.File.DepResolve import Descript.Misc.Build.Read.File.SFile import Data.Text import qualified Data.Text.IO as Text import System.FilePath -- | A (dependent) source file. It can be an actual file on disk, or a -- virtual representation. It just needs a name, contents, and a -- resolver to other files. Dependencies are obtained through the monad -- 'u', and they're of type 'a'. data GenDFile u d = DFile { depResolver :: GenDepResolver u d , sfile :: SFile } deriving (Show, Functor) -- | Creates a file with the given path and contents, which uses the -- default resolver. mkTextFile :: FilePath -> Text -> GenDFile IO Text mkTextFile path contents = DFile { depResolver = defaultTextResolver $ takeDirectory path , sfile = mkSFile path contents } -- | Reads the file with the given path. loadTextFile :: FilePath -> IO (GenDFile IO Text) loadTextFile path = mkTextFile path <$> Text.readFile path -- | The name of the file. fileName :: GenDFile u d -> String fileName = sfileName . sfile -- | The textual representation of the file. fileContents :: GenDFile u d -> Text fileContents = sfileContents . sfile