renamed modules after restructuring UI data
This commit is contained in:
		@@ -12,7 +12,7 @@ import Control.Monad.RWS.Strict (RWST)
 | 
			
		||||
import Control.Lens
 | 
			
		||||
import Graphics.Rendering.OpenGL.GL.Texturing.Objects (TextureObject)
 | 
			
		||||
import Render.Types
 | 
			
		||||
import UI.UIBaseData
 | 
			
		||||
import UI.UIBase
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
--Static Read-Only-State
 | 
			
		||||
 
 | 
			
		||||
@@ -12,12 +12,11 @@ import           Data.Maybe
 | 
			
		||||
import           Foreign.Marshal.Array                (pokeArray)
 | 
			
		||||
import           Foreign.Marshal.Alloc                (allocaBytes)
 | 
			
		||||
import qualified Graphics.UI.SDL                      as SDL
 | 
			
		||||
import           Render.Misc                          (genColorData)
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
import Render.Misc                                    (curb,genColorData)
 | 
			
		||||
import Types
 | 
			
		||||
import Render.Misc                                    (curb) -- TODO: necessary import ?
 | 
			
		||||
import UI.UIBaseData
 | 
			
		||||
import UI.UIClasses
 | 
			
		||||
import UI.UIWidgets
 | 
			
		||||
import UI.UIOperations
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
 
 | 
			
		||||
@@ -1,7 +1,7 @@
 | 
			
		||||
{-# LANGUAGE GeneralizedNewtypeDeriving, TemplateHaskell, DeriveGeneric #-}
 | 
			
		||||
-- data and classes are separated into several modules to avoid cyclic dependencies with the Type module
 | 
			
		||||
-- TODO: exclude UIMouseState constructor
 | 
			
		||||
module UI.UIBaseData where
 | 
			
		||||
-- widget data is separated into several modules to avoid cyclic dependencies with the Type module
 | 
			
		||||
-- TODO: exclude UIMouseState constructor from export?
 | 
			
		||||
module UI.UIBase where
 | 
			
		||||
 | 
			
		||||
import           Control.Lens             ((^.), (.~), (%~), (&), ix, to, mapped, traverse, makeLenses)
 | 
			
		||||
import           Control.Monad            (liftM)
 | 
			
		||||
@@ -6,7 +6,7 @@ import qualified Data.HashMap.Strict             as Map
 | 
			
		||||
import           Data.Maybe
 | 
			
		||||
 | 
			
		||||
import Types
 | 
			
		||||
import UI.UIBaseData
 | 
			
		||||
import UI.UIBase
 | 
			
		||||
 | 
			
		||||
toGUIAny :: Map.HashMap UIId (GUIWidget m) -> UIId -> GUIWidget m
 | 
			
		||||
toGUIAny m uid = fromMaybe (error "map does not contain requested key") (Map.lookup uid m)
 | 
			
		||||
 
 | 
			
		||||
@@ -1,6 +1,6 @@
 | 
			
		||||
{-# LANGUAGE InstanceSigs, MultiParamTypeClasses, FlexibleInstances #-}
 | 
			
		||||
 | 
			
		||||
module UI.UIClasses (module UI.UIClasses, module UI.UIBaseData) where
 | 
			
		||||
module UI.UIWidgets (module UI.UIWidgets, module UI.UIBase) where
 | 
			
		||||
 | 
			
		||||
import           Control.Lens                         ((^.), (.~), (&))
 | 
			
		||||
import           Control.Monad
 | 
			
		||||
@@ -11,7 +11,7 @@ import           Data.Maybe
 | 
			
		||||
import qualified Data.HashMap.Strict as Map
 | 
			
		||||
 | 
			
		||||
import           Types
 | 
			
		||||
import UI.UIBaseData
 | 
			
		||||
import UI.UIBase
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
createContainer :: (Monad m) => (ScreenUnit, ScreenUnit, ScreenUnit, ScreenUnit) -> [UIId] -> Int -> GUIWidget m
 | 
			
		||||
		Reference in New Issue
	
	Block a user