-- | Common syntax highlighting functions for Emacs and JSON

module Agda.Utils.IO.TempFile
  ( writeToTempFile
  ) where

import qualified Control.Exception as E
import qualified System.Directory as D
import qualified System.IO as IO

-- | Creates a temporary file, writes some stuff, and returns the filepath
writeToTempFile :: String -> IO FilePath
writeToTempFile :: String -> IO String
writeToTempFile String
content = do
  String
dir      <- IO String
D.getTemporaryDirectory
  IO (String, Handle)
-> ((String, Handle) -> IO ())
-> ((String, Handle) -> IO String)
-> IO String
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
E.bracket (String -> String -> IO (String, Handle)
IO.openTempFile String
dir String
"agda2-mode") (Handle -> IO ()
IO.hClose (Handle -> IO ())
-> ((String, Handle) -> Handle) -> (String, Handle) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, Handle) -> Handle
forall a b. (a, b) -> b
snd) (((String, Handle) -> IO String) -> IO String)
-> ((String, Handle) -> IO String) -> IO String
forall a b. (a -> b) -> a -> b
$ \ (String
filepath, Handle
handle) -> do
    Handle -> TextEncoding -> IO ()
IO.hSetEncoding Handle
handle TextEncoding
IO.utf8
    Handle -> String -> IO ()
IO.hPutStr Handle
handle String
content
    String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
filepath