{-
    Copyright 2015,2016 Markus Ongyerth, Stephan Guenther

    This file is part of Monky.

    Monky is free software: you can redistribute it and/or modify
    it under the terms of the GNU Lesser General Public License as published by
    the Free Software Foundation, either version 3 of the License, or
    (at your option) any later version.

    Monky is distributed in the hope that it will be useful,
    but WITHOUT ANY WARRANTY; without even the implied warranty of
    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
    GNU Lesser General Public License for more details.

    You should have received a copy of the GNU Lesser General Public License
    along with Monky.  If not, see <http://www.gnu.org/licenses/>.
-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE CPP #-}
{-|
Module      : Monky.Modules
Description : The module definition used by 'startLoop'
Maintainer  : ongy, moepi
Stability   : experimental
Portability : Linux

The EvtModule and PollModule classes have to be implemented by monky compatible modules
-}
module Monky.Modules
  ( MonkyOut(..)
  , MonkyOutput(..)
  , PollModule(..)
  , EvtModule(..)
  , Modules(..)
  , EvtModules(..)
  , PollModules(..)
  , pollPack
  , evtPack
  )
where

import Control.Arrow ((***))
import Data.Word (Word8)
import Data.Text (Text)
import qualified Data.Text.Encoding as E

import Data.Serialize

#if MIN_VERSION_base(4,8,0)
#else
import Control.Applicative ((<$>))
#endif

-- |A data type to encode general output types
data MonkyOut
  = MonkyPlain Text -- ^Plaintext output
  | MonkyBar Int -- ^A Vertical bar, in %
  | MonkyHBar Int -- ^A horizontal bar, in pixel
  -- Temporary (FG,BG)
  -- Color format (and somewhat image) are not fix yet, so don't rely on them to much
  | MonkyColor (Text, Text) MonkyOut -- ^Colorize the enclosed output TODO: Color format
  | MonkyImage Text Char -- ^Path to an image to display (for icons), or Unicode glyph that should be used
  deriving (Show, Read)

-- |Class that output converters have to implement
class MonkyOutput a where
  -- |Create one tick of output from a list of collection module output
  doLine
    :: a -- ^The output handle, may have a connection handle
    -> [[MonkyOut]] -- ^The outputs generated by collection modules
    -> IO () -- ^IO() since the output module chooses how to transfer the data to the display client

-- |The "New" class for collection modules
class PollModule a where
  -- |Get the current (new) output
  getOutput
    :: a -- ^The handle, may store data from previous calls
    -> IO [MonkyOut] -- ^A list of outputs to build
  -- |Initialize the module, this is called once before data collection starts
  initialize
    :: a -- ^The handle to initialize
    -> IO ()
  -- |Default implementation
  initialize _ = return ()

-- |The class for eventing modules
class EvtModule a where
  {- |Start your own event loop. The second argument is the consumer of your output.

   Doing this in an opaque way gives a way to chain actions to your event handling
   -}
  startEvtLoop :: a -> ([MonkyOut] -> IO ()) -> IO ()

-- |A wrapper around module instances so they can be put into a list.
data PollModules = forall a . PollModule a => NMW a Int
-- |A wrapper around EvtModule for so they can be in a list
data EvtModules = forall a . EvtModule a => DW a

-- |Wrapper around 'PollModules' and 'EvtModules' so we can pass all modules in one list to 'startLoop'
data Modules
  = Poll PollModules
  | Evt EvtModules

-- |Function to make packaging modules easier
pollPack :: PollModule a
         => Int -- ^The refresh rate for this module
         -> IO a -- ^The function to get a module (get??Handle)
         -> IO Modules -- ^The packed module ready to be given to 'startLoop'
pollPack i = fmap (Poll . flip NMW i)


-- |'pollPack' for 'EvtModule's
evtPack :: EvtModule a
        => IO a
        -> IO Modules
evtPack = fmap (Evt . DW)

-- "Official" Serialize instance for sending MonkyOuts over the network
instance Serialize MonkyOut where
  put (MonkyPlain t) = do
    put (1 :: Word8)
    put $ E.encodeUtf8 t
  put (MonkyBar i) = do
    put (2 :: Word8)
    put i
  put (MonkyHBar i) = do
    put (3 :: Word8)
    put i
  put (MonkyColor c out) = do
    put (4 :: Word8)
    put $ E.encodeUtf8 *** E.encodeUtf8 $ c
    put out
  put (MonkyImage t c) = do
    put (5 :: Word8)
    put $ E.encodeUtf8 t
    put c

  get = do
    t <- get :: Get Word8
    case t of
      1 -> MonkyPlain . E.decodeUtf8 <$> get
      2 -> MonkyBar <$> get
      3 -> MonkyHBar <$> get
      4 -> do
        c   <- get
        out <- get
        return $ MonkyColor (E.decodeUtf8 *** E.decodeUtf8 $ c) out
      5 -> do
          i <- E.decodeUtf8 <$> get
          c <- get
          return $ MonkyImage i c
      _ -> fail ("Could not decode MonkyOut, got type: " ++ show t)