{-| Copyright : (c) Hisaket VioletRed, 2022 License : AGPL-3.0-or-later Maintainer : hisaket@outlook.jp Stability : experimental Portability : POSIX Example\: >>> import qualified Polysemy.SequentialAccess as SA >>> import qualified Polysemy.SequentialAccess.Text as SAT >>> import Polysemy ( runFinal, embedToFinal, embed ) >>> import Polysemy.Resource ( resourceToIOFinal ) >>> import Polysemy.Path >>> import Polysemy.FS.Scoped ( scopedFile, AccessMode (RwAccess) ) >>> import Control.Monad.Extra ( whenM ) >>> import System.Directory ( doesFileExist, removeFile ) >>> import Control.Exception ( throwIO ) >>> :{ runFinal $ embedToFinal $ resourceToIOFinal $ rwAccessToIO do let path = [absfile|/tmp/polysemy-scoped-fs-test|] embed $ whenM (doesFileExist $ toFilePath path) $ throwIO $ userError "Abort to prevent overwriting." scopedFile @RwAccess path do SA.extend "This text will be deleted." SA.resize SA.NullSize SA.extend "foo" SA.extend "bar" SA.seek SA.TOF embed . print =<< SA.read SA.ToEnd embed $ removeFile $ toFilePath path :} "foobar" -} module Polysemy.FS.Scoped.Text where import Polysemy.FS.Scoped.Text.Internal ( readToIO, extendToIO, clearToIO, cursorToIO, scopedTextFileToIO ) import Polysemy ( embed, Embed, Members, interpret ) import Polysemy.FS.Scoped ( Access , AccessMode (ReadAccess, AppendAccess, RwAccess, WriteAccess) , Format (TextFormat) ) import qualified Polysemy.SequentialAccess.Text as SAT import qualified System.IO as IO import qualified Data.Text.IO as TIO import qualified Polysemy.SequentialAccess as SA import Control.Category ( (>>>) ) import Polysemy.Resource ( Resource ) -- | An interpreter for read open mode with text. readAccessToIO :: Members '[Embed IO, Resource] r => Access TextFormat ReadAccess (SAT.ReadLine ': SAT.ReadToEnd ': SAT.Cursor) r b readAccessToIO = scopedTextFileToIO IO.ReadMode \h -> readToIO h >>> cursorToIO h -- | An interpreter for write open mode with text. writeAccessToIO :: Members '[Embed IO, Resource] r => Access TextFormat WriteAccess (SAT.Extend ': SAT.Clear ': SAT.Cursor) r b writeAccessToIO = scopedTextFileToIO IO.WriteMode \h -> extendToIO h >>> clearToIO h >>> cursorToIO h -- | An interpreter for read and write open mode with text. rwAccessToIO :: Members '[Embed IO, Resource] r => Access TextFormat RwAccess (SAT.ReadLine ': SAT.ReadToEnd ': SAT.Extend ': SAT.Clear ': SAT.Cursor) r b rwAccessToIO = scopedTextFileToIO IO.ReadWriteMode \h -> readToIO h >>> extendToIO h >>> clearToIO h >>> cursorToIO h -- | An interpreter for append open mode with text. appendAccessToIO :: Members '[Embed IO, Resource] r => Access TextFormat AppendAccess '[SAT.Append, SAT.Clear] r b appendAccessToIO = scopedTextFileToIO IO.AppendMode \h -> clearToIO h . interpret \(SA.Append t) -> embed $ TIO.hPutStr h t