{-
 *  Programmer:	Piotr Borek
 *  E-mail:     piotrborek@op.pl
 *  Copyright 2017 Piotr Borek
 *
 *  Distributed under the terms of the GPL (GNU Public License)
 *
 *  This program is free software; you can redistribute it and/or modify
 *  it under the terms of the GNU General Public License as published by
 *  the Free Software Foundation; either version 2 of the License, or
 *  (at your option) any later version.
 *
 *  This program 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 General Public License for more details.
 *
 *  You should have received a copy of the GNU General Public License
 *  along with this program; if not, write to the Free Software
 *  Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
-}
{-# LANGUAGE QuasiQuotes #-}

module Mp.UI.HelpPage (
    helpPageNew
) where

import           Simple.Locale.TranslateTH
import           Simple.UI.All

import           Mp.Locale.TranslateFile   ()
import           Mp.UI.MpData

helpPageNew :: UIApp MpData TextView
helpPageNew = textViewNew $ Just helpPageText

helpPageText :: String
helpPageText = unlines
    [ "          q : " ++ [tr|Detach from the server|]
    , "          Q : " ++ [tr|Quit|]
    , ""
    , "          1 : " ++ [tr|Help screen|]
    , "          2 : " ++ [tr|Queue screen|]
    , "          3 : " ++ [tr|Playlists screen|]
    , "          4 : " ++ [tr|Browser screen|]
    , ""
    , "        Tab : " ++ [tr|Next screen|]
    , "  Shift+Tab : " ++ [tr|Previous screen|]
    , ""
    , "         Up : " ++ [tr|Move cursor up|]
    , "       Down : " ++ [tr|Move cursor down|]
    , "     PageUp : " ++ [tr|Page up|]
    , "   PageDown : " ++ [tr|Page down|]
    , ""
    , "      Enter : " ++ [tr|Start playing|] ++ " / " ++ [tr|Enter directory|] ++ " / " ++ [tr|Enter playlist|]
    , "          s : " ++ [tr|Stop playing|]
    , "          p : " ++ [tr|Pause|] ++ " / " ++ [tr|resume playing|]
    , ""
    , "      space : " ++ [tr|Add file|] ++ " / " ++ [tr|directory|] ++ " / " ++ [tr|playlist|]
    , "          d : " ++ [tr|Remove file|] ++ " / " ++ [tr|directory|] ++ " / " ++ [tr|playlist|]
    , "          c : " ++ [tr|Clear the queue|]
    , "          l : " ++ [tr|Center|]
    , "          S : " ++ [tr|Save playlist|]
    , "     Ctrl+d : " ++ [tr|Delete playlist|]
    , "          ! : " ++ [tr|Go to root directory|]
    , "          @ : " ++ [tr|Go to parent directory|]
    , ""
    , "          > : " ++ [tr|Play next file|]
    , "          < : " ++ [tr|Play previous file|]
    , "          f : " ++ [tr|Seek forward|]
    , "          b : " ++ [tr|Seek backward|]
    , ""
    , "          r : " ++ [tr|Toggle repeat mode|]
    , "          z : " ++ [tr|Toggle random mode|]
    , ""
    , "          [ : " ++ [tr|Decrease volume|]
    , "          ] : " ++ [tr|Increase volume|]
    ]