First Types
This commit is contained in:
51
app/Main.hs
51
app/Main.hs
@ -1,8 +1,53 @@
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
|
||||
module Main where
|
||||
|
||||
import qualified MyLib (someFunc)
|
||||
import Agent.Server.Config (Config, configFile, loadConfigOrDefault, saveConfig)
|
||||
import Agent.Tools.Time ()
|
||||
import Agent.Tools.Tool (Tool, getToolListTH, toMarkdownDL)
|
||||
import Control.Concurrent (threadDelay)
|
||||
import Control.Exception (AsyncException (UserInterrupt), bracket, catch)
|
||||
import Control.Monad (when)
|
||||
import qualified Data.ByteString as BS
|
||||
import Data.Default
|
||||
import Data.Either (fromRight, isRight)
|
||||
import Data.Either.Extra (fromRight')
|
||||
import Data.Proxy
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.Text.IO as T
|
||||
import Data.Yaml (decodeFileThrow)
|
||||
import qualified Data.Yaml as YAML
|
||||
import Language.Haskell.TH
|
||||
import System.IO (hFlush, stdout)
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
putStrLn "Hello, Haskell!"
|
||||
MyLib.someFunc
|
||||
(conf :: Config) <- (configFile >>= maybe (return def) decodeFileThrow)
|
||||
|
||||
let availableTools = ($(getToolListTH) :: [Tool])
|
||||
putStrLn "# HAgent\n"
|
||||
putStrLn "\n## Cofig\n"
|
||||
BS.putStr $ (YAML.encode conf) <> "\n"
|
||||
putStrLn "## Available Tools\n"
|
||||
mapM_ T.putStrLn $ toMarkdownDL <$> availableTools
|
||||
bracket acquireResource releaseResource $ \_ ->
|
||||
mainLoop `catch` handler
|
||||
where
|
||||
acquireResource :: IO ()
|
||||
acquireResource = putStrLn "Acquiring resource..."
|
||||
|
||||
releaseResource :: () -> IO ()
|
||||
releaseResource _ = putStrLn "Releasing resource..."
|
||||
|
||||
mainLoop :: IO ()
|
||||
mainLoop = do
|
||||
putStr "waiting for work ...\r"
|
||||
hFlush stdout
|
||||
-- Simulate work
|
||||
-- Add your main loop logic here
|
||||
threadDelay 1000000
|
||||
mainLoop
|
||||
|
||||
handler :: AsyncException -> IO ()
|
||||
handler UserInterrupt = putStrLn "\nCaught Ctrl-C. Exiting gracefully."
|
||||
|
Reference in New Issue
Block a user