module Component.Input
  ( InputIn(..)
  , InputOut(..)
  , input
  , defaultInputIn
  ) where

import qualified Data.Map               as M
import qualified Data.Maybe             as Maybe
import           Data.Text              (Text)
import qualified Data.Text              as T
import           Data.Time              (NominalDiffTime)
import           Data.Validation        (Validation (Failure, Success))
import qualified Data.Validation        as V
import           Reflex.Dom             (Dynamic, Event, MonadWidget, Reflex,
                                         (&), (.~))
import qualified Reflex.Dom             as R

import qualified Common.Util.Validation as ValidationUtil
import           Component.Button       (ButtonIn (..), ButtonOut (..))
import qualified Component.Button       as Button
import qualified Icon

data InputIn a = InputIn
  { _inputIn_hasResetButton :: Bool
  , _inputIn_label          :: Text
  , _inputIn_initialValue   :: Text
  , _inputIn_inputType      :: Text
  , _inputIn_validation     :: Text -> Validation Text a
  }

defaultInputIn :: InputIn Text
defaultInputIn = InputIn
  { _inputIn_hasResetButton = True
  , _inputIn_label          = ""
  , _inputIn_initialValue   = ""
  , _inputIn_inputType      = "text"
  , _inputIn_validation     = V.Success
  }

data InputOut t a = InputOut
  { _inputOut_raw   :: Dynamic t Text
  , _inputOut_value :: Dynamic t (Validation Text a)
  , _inputOut_enter :: Event t ()
  }

input
  :: forall t m a b. MonadWidget t m
  => InputIn a
  -> Event t Text -- reset
  -> Event t b    -- validate
  -> m (InputOut t a)
input inputIn reset validate = do
  rec
    let resetValue = R.leftmost
          [ reset
          , fmap (const "") resetClic
          ]

        inputAttr = R.ffor value (\v ->
          if T.null v && _inputIn_inputType inputIn /= "date"
            then M.empty
            else M.singleton "class" "filled")

        value =  R._textInput_value textInput

        containerAttr = R.ffor inputError (\e ->
          M.singleton "class" $ T.intercalate " "
            [ "textInput"
            , if Maybe.isJust e then "error" else ""
            ])

    let valueWithValidation = R.ffor value (\v -> (v, _inputIn_validation inputIn $ v))
    inputError <- getInputError valueWithValidation validate

    (textInput, resetClic) <- R.elDynAttr "div" containerAttr $ do

      textInput <- R.el "label" $ do
        textInput <- R.textInput $ R.def
          & R.attributes .~ inputAttr
          & R.setValue .~ resetValue
          & R.textInputConfig_initialValue .~ (_inputIn_initialValue inputIn)
          & R.textInputConfig_inputType .~ (_inputIn_inputType inputIn)

        R.divClass "label" $
          R.text (_inputIn_label inputIn)

        return textInput

      resetClic <-
        if _inputIn_hasResetButton inputIn
          then
            _buttonOut_clic <$> (Button.button $
              (Button.defaultButtonIn Icon.cross)
                { _buttonIn_class   = R.constDyn "reset"
                , _buttonIn_tabIndex = Just (-1)
                })
          else
            return R.never

      R.divClass "errorMessage" $
        R.dynText . fmap (Maybe.fromMaybe "") $ inputError

      return (textInput, resetClic)

  let enter = fmap (const ()) $ R.ffilter ((==) 13) . R._textInput_keypress $ textInput

  return $ InputOut
    { _inputOut_raw = value
    , _inputOut_value = fmap snd valueWithValidation
    , _inputOut_enter = enter
    }

getInputError
  :: forall t m a b c. MonadWidget t m
  => Dynamic t (Text, Validation Text a)
  -> Event t c
  -> m (Dynamic t (Maybe Text))
getInputError validatedValue validate = do
  let errorDynamic = fmap (\(t, v) -> (t, validationError v)) validatedValue
      errorEvent = R.updated errorDynamic
  delayedError <- R.debounce (1 :: NominalDiffTime) errorEvent
  fmap (fmap fst) $ R.foldDyn
    (\event (err, hasBeenResetted) ->
      case event of
        ModifiedEvent t ->
          (Nothing, T.null t)

        ValidateEvent e ->
          (e, False)

        DelayEvent e ->
          if hasBeenResetted then
            (Nothing, False)
          else
            (e, False)
    )
    (Nothing, False)
    (R.leftmost
      [ fmap (\(t, _) -> ModifiedEvent t) errorEvent
      , fmap (\(_, e) -> DelayEvent e) delayedError
      , R.attachWith (\(_, e) _ -> ValidateEvent e) (R.current errorDynamic) validate
      ])

validationError :: (Validation Text a) -> Maybe Text
validationError (Failure e) = Just e
validationError _           = Nothing

data InputEvent
  = ModifiedEvent Text
  | DelayEvent (Maybe Text)
  | ValidateEvent (Maybe Text)