Flatten module hierarchy

This commit is contained in:
Don Stewart 2007-03-07 02:23:32 +00:00
parent 99ef0175d2
commit 07ee2a19cd
4 changed files with 6 additions and 5 deletions

View File

@ -1,6 +1,6 @@
{-# OPTIONS_GHC -fglasgow-exts #-}
module Thunk.Wm where
module Wm where
import Data.Sequence
import Control.Monad.State

View File

@ -1,4 +1,4 @@
module Thunk.XlibExtras where
module XlibExtras where
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Types

View File

@ -12,7 +12,7 @@ build-depends: base >= 2.0, X11, unix, mtl
executable: thunk
main-is: thunk.hs
extensions: ForeignFunctionInterface
other-modules: Thunk.XlibExtras
other-modules: XlibExtras
ghc-options: -O
include-dirs: include
-- OpenBSD:

View File

@ -10,8 +10,9 @@ import System.IO
import Graphics.X11.Xlib
import System.Process (runCommand)
import System.Exit
import Thunk.Wm
import Thunk.XlibExtras
import Wm
import XlibExtras
handler :: Event -> Wm ()
handler (MapRequestEvent {window = w}) = manage w