--------------------------------------------------------------------------------
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Patat.Presentation.SpeakerNotes
    ( SpeakerNotes (..)
    , toText

    , Handle
    , withHandle
    , write

    , parseSlideSettings
    ) where


--------------------------------------------------------------------------------
import           Control.Exception           (bracket)
import           Control.Monad               (when)
import qualified Data.IORef                  as IORef
import           Data.List                   (intersperse)
import qualified Data.Text                   as T
import qualified Data.Text.IO                as T
import           Patat.EncodingFallback      (EncodingFallback)
import qualified Patat.EncodingFallback      as EncodingFallback
import           Patat.Presentation.Settings
import           System.Directory            (removeFile)
import qualified System.IO                   as IO


--------------------------------------------------------------------------------
newtype SpeakerNotes = SpeakerNotes [T.Text]
    deriving (SpeakerNotes -> SpeakerNotes -> Bool
(SpeakerNotes -> SpeakerNotes -> Bool)
-> (SpeakerNotes -> SpeakerNotes -> Bool) -> Eq SpeakerNotes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SpeakerNotes -> SpeakerNotes -> Bool
== :: SpeakerNotes -> SpeakerNotes -> Bool
$c/= :: SpeakerNotes -> SpeakerNotes -> Bool
/= :: SpeakerNotes -> SpeakerNotes -> Bool
Eq, Semigroup SpeakerNotes
SpeakerNotes
Semigroup SpeakerNotes =>
SpeakerNotes
-> (SpeakerNotes -> SpeakerNotes -> SpeakerNotes)
-> ([SpeakerNotes] -> SpeakerNotes)
-> Monoid SpeakerNotes
[SpeakerNotes] -> SpeakerNotes
SpeakerNotes -> SpeakerNotes -> SpeakerNotes
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: SpeakerNotes
mempty :: SpeakerNotes
$cmappend :: SpeakerNotes -> SpeakerNotes -> SpeakerNotes
mappend :: SpeakerNotes -> SpeakerNotes -> SpeakerNotes
$cmconcat :: [SpeakerNotes] -> SpeakerNotes
mconcat :: [SpeakerNotes] -> SpeakerNotes
Monoid, NonEmpty SpeakerNotes -> SpeakerNotes
SpeakerNotes -> SpeakerNotes -> SpeakerNotes
(SpeakerNotes -> SpeakerNotes -> SpeakerNotes)
-> (NonEmpty SpeakerNotes -> SpeakerNotes)
-> (forall b. Integral b => b -> SpeakerNotes -> SpeakerNotes)
-> Semigroup SpeakerNotes
forall b. Integral b => b -> SpeakerNotes -> SpeakerNotes
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: SpeakerNotes -> SpeakerNotes -> SpeakerNotes
<> :: SpeakerNotes -> SpeakerNotes -> SpeakerNotes
$csconcat :: NonEmpty SpeakerNotes -> SpeakerNotes
sconcat :: NonEmpty SpeakerNotes -> SpeakerNotes
$cstimes :: forall b. Integral b => b -> SpeakerNotes -> SpeakerNotes
stimes :: forall b. Integral b => b -> SpeakerNotes -> SpeakerNotes
Semigroup, Int -> SpeakerNotes -> ShowS
[SpeakerNotes] -> ShowS
SpeakerNotes -> String
(Int -> SpeakerNotes -> ShowS)
-> (SpeakerNotes -> String)
-> ([SpeakerNotes] -> ShowS)
-> Show SpeakerNotes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SpeakerNotes -> ShowS
showsPrec :: Int -> SpeakerNotes -> ShowS
$cshow :: SpeakerNotes -> String
show :: SpeakerNotes -> String
$cshowList :: [SpeakerNotes] -> ShowS
showList :: [SpeakerNotes] -> ShowS
Show)


--------------------------------------------------------------------------------
toText :: SpeakerNotes -> T.Text
toText :: SpeakerNotes -> Text
toText (SpeakerNotes [Text]
sn) = [Text] -> Text
T.unlines ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
intersperse Text
forall a. Monoid a => a
mempty [Text]
sn


--------------------------------------------------------------------------------
data Handle = Handle
    { Handle -> SpeakerNotesSettings
hSettings :: !SpeakerNotesSettings
    , Handle -> IORef SpeakerNotes
hActive   :: !(IORef.IORef SpeakerNotes)
    }


--------------------------------------------------------------------------------
withHandle
    :: SpeakerNotesSettings -> (Handle -> IO a) -> IO a
withHandle :: forall a. SpeakerNotesSettings -> (Handle -> IO a) -> IO a
withHandle SpeakerNotesSettings
settings = IO Handle -> (Handle -> IO ()) -> (Handle -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
    (SpeakerNotesSettings -> IORef SpeakerNotes -> Handle
Handle SpeakerNotesSettings
settings (IORef SpeakerNotes -> Handle)
-> IO (IORef SpeakerNotes) -> IO Handle
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpeakerNotes -> IO (IORef SpeakerNotes)
forall a. a -> IO (IORef a)
IORef.newIORef SpeakerNotes
forall a. Monoid a => a
mempty)
    (\Handle
_ -> String -> IO ()
removeFile (SpeakerNotesSettings -> String
snsFile SpeakerNotesSettings
settings))


--------------------------------------------------------------------------------
write
    :: Handle -> EncodingFallback -> SpeakerNotes -> IO ()
write :: Handle -> EncodingFallback -> SpeakerNotes -> IO ()
write Handle
h EncodingFallback
encodingFallback SpeakerNotes
sn = do
    Bool
change <- IORef SpeakerNotes
-> (SpeakerNotes -> (SpeakerNotes, Bool)) -> IO Bool
forall a b. IORef a -> (a -> (a, b)) -> IO b
IORef.atomicModifyIORef' (Handle -> IORef SpeakerNotes
hActive Handle
h) ((SpeakerNotes -> (SpeakerNotes, Bool)) -> IO Bool)
-> (SpeakerNotes -> (SpeakerNotes, Bool)) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \SpeakerNotes
old -> (SpeakerNotes
sn, SpeakerNotes
old SpeakerNotes -> SpeakerNotes -> Bool
forall a. Eq a => a -> a -> Bool
/= SpeakerNotes
sn)
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
change (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IOMode -> (Handle -> IO ()) -> IO ()
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
IO.withFile (SpeakerNotesSettings -> String
snsFile (SpeakerNotesSettings -> String) -> SpeakerNotesSettings -> String
forall a b. (a -> b) -> a -> b
$ Handle -> SpeakerNotesSettings
hSettings Handle
h) IOMode
IO.WriteMode ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Handle
ioh ->
        Handle -> EncodingFallback -> IO () -> IO ()
forall a. Handle -> EncodingFallback -> IO a -> IO a
EncodingFallback.withHandle Handle
ioh EncodingFallback
encodingFallback (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        Handle -> Text -> IO ()
T.hPutStr Handle
ioh (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ SpeakerNotes -> Text
toText SpeakerNotes
sn