EventLoop -> Core, DefaultConfig -> Config

This commit is contained in:
Don Stewart 2007-11-05 02:17:05 +00:00
parent c9142952c2
commit 30af3a8f84
4 changed files with 17 additions and 15 deletions

18
Main.hs
View File

@ -14,8 +14,8 @@
module Main (main) where
import XMonad.EventLoop (makeMain)
import XMonad.DefaultConfig (defaultConfig)
import XMonad.Core
import XMonad.Config
import Control.Exception (handle)
import System.IO
@ -25,6 +25,14 @@ import System.Environment
import System.Exit
import System.Posix.Process (executeFile)
-- | The entry point into xmonad. Attempts to compile any custom main
-- for xmonad, and if it doesn't find one, just launches the default.
main :: IO ()
main = do
handle (hPrint stderr) buildLaunch
-- if buildLaunch returns, execute the trusted core
makeMain defaultConfig
-- | Build "~/.xmonad/Main.hs" with ghc, then execute it. If there are no
-- errors, this function does not return. An exception is raised in any of
-- these cases:
@ -43,9 +51,3 @@ buildLaunch = do
args <- getArgs
executeFile (dir ++ "/Main") False args Nothing
return ()
main :: IO ()
main = do
handle (hPrint stderr) buildLaunch
-- if buildLaunch returns, execute the trusted core
makeMain defaultConfig

View File

@ -1,7 +1,7 @@
{-# OPTIONS -fno-warn-missing-signatures #-}
-----------------------------------------------------------------------------
-- |
-- Module : DefaultConfig.hs
-- Module : XMonad.Config
-- Copyright : (c) Spencer Janssen 2007
-- License : BSD3-style (see LICENSE)
--
@ -15,7 +15,7 @@
--
------------------------------------------------------------------------
module XMonad.DefaultConfig (defaultConfig) where
module XMonad.Config (defaultConfig) where
--
-- Useful imports

View File

@ -1,7 +1,7 @@
{-# LANGUAGE MultiParamTypeClasses #-}
----------------------------------------------------------------------------
-- |
-- Module : EventLoop.hs
-- Module : Core.hs
-- Copyright : (c) Spencer Janssen 2007
-- License : BSD3-style (see LICENSE)
--
@ -13,7 +13,7 @@
--
-----------------------------------------------------------------------------
module XMonad.EventLoop (makeMain) where
module XMonad.Core (makeMain) where
import Data.Bits
import qualified Data.Map as M

View File

@ -21,15 +21,15 @@ build-depends: base>=2.0, mtl, unix, X11==1.3.0
extra-source-files: README TODO tests/loc.hs tests/Properties.hs man/xmonad.1.in
util/GenerateManpage.hs man/xmonad.1 man/xmonad.html
exposed-modules: XMonad
XMonad.DefaultConfig
XMonad.EventLoop
XMonad.Config
XMonad.Core
XMonad.Layouts
XMonad.Operations
XMonad.StackSet
executable: xmonad
main-is: Main.hs
other-modules: XMonad.EventLoop XMonad.Layouts XMonad.Operations XMonad.StackSet XMonad
other-modules: XMonad.Core XMonad.Layouts XMonad.Operations XMonad.StackSet XMonad
ghc-options: -funbox-strict-fields -O2 -fasm -Wall -optl-Wl,-s
ghc-prof-options: -prof -auto-all
extensions: GeneralizedNewtypeDeriving