File: Main.hs

package info (click to toggle)
glirc 2.40.1-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 1,056 kB
  • sloc: haskell: 15,053; ansic: 84; makefile: 6
file content (91 lines) | stat: -rw-r--r-- 2,824 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
{-|
 -
Description : Entry-point of executable
Copyright   : (c) Eric Mertens, 2016
License     : ISC
Maintainer  : emertens@gmail.com

Entry point into glirc. This module sets up VTY and launches the client.
-}
module Main where

import Control.Exception
import Control.Lens
import Control.Monad
import Data.List (nub)
import Data.Text (Text)
import System.Exit
import System.IO
import Graphics.Vty
import Graphics.Vty.Platform.Unix (mkVty)

import Client.Configuration
import Client.EventLoop
import Client.Options
import Client.State
import Client.State.Extensions
import Client.State.Focus

import Exports ()

-- | Main action for IRC client
main :: IO ()
main =
  do opts <- getOptions
     let mbPath = view optConfigFile opts
     (path,cfg) <- loadConfiguration' mbPath
     withClientState path cfg $ \st0 ->
       withVty $ \vty ->
         do st1 <- clientStartExtensions    st0
            st2 <- initialNetworkLogic opts st1
            st3 <- updateTerminalSize vty   st2
            eventLoop vty st3

initialNetworkLogic :: Options -> ClientState -> IO ClientState
initialNetworkLogic opts st = addInitialNetworks (nub networks) st
  where
    networks
      | view optNoConnect opts = view optInitialNetworks opts
      | otherwise              = view optInitialNetworks opts ++ clientAutoconnects st

-- | Load configuration and handle errors along the way.
loadConfiguration' :: Maybe FilePath -> IO (FilePath, Configuration)
loadConfiguration' mbPath =
  do cfgRes <- loadConfiguration mbPath
     case cfgRes of
       Right x -> return x
       Left (ConfigurationReadFailed e) ->
         report "Failed to open configuration:" e
       Left (ConfigurationParseFailed p e) ->
         report ("Failed to parse configuration file: " ++ p) e
       Left (ConfigurationMalformed p e) ->
         report ("Malformed configuration file: " ++ p ++ "\n(try --config-format)") e
  where
    report problem msg =
      do hPutStrLn stderr problem
         hPutStrLn stderr msg
         exitFailure

-- | Create connections for the given networks.
-- Set the client focus to the first network listed.
addInitialNetworks ::
  [Text] {- networks -} ->
  ClientState           ->
  IO ClientState
addInitialNetworks [] st = return st
addInitialNetworks (n:ns) st =
  do st' <- foldM (\st_ n -> addConnection 0 Nothing Nothing n st_) st (n:ns)
     return $! set clientFocus (NetworkFocus n) st'

-- | Initialize a 'Vty' value and run a continuation. Shutdown the 'Vty'
-- once the continuation finishes.
withVty :: (Vty -> IO a) -> IO a
withVty = bracket buildVty shutdown

-- | Generate the initial 'Vty' value and enable the features glirc uses.
buildVty :: IO Vty
buildVty =
 do vty <- mkVty defaultConfig
    setMode (outputIface vty) BracketedPaste True
    setMode (outputIface vty) Focus True
    pure vty