start fontifier

This commit is contained in:
Armin Friedl 2016-08-07 16:07:57 +02:00
parent 8228e3cdaf
commit 5f508d7a27
2 changed files with 53 additions and 12 deletions

40
src/App/Fontifier.hs Normal file
View file

@ -0,0 +1,40 @@
{-# LANGUAGE TemplateHaskell #-} -- needed for lenses
module Fontifier (fontMap, fontify) where
{---- Imports ----}
---- Brick, for markup specifications ----
import Brick.AttrMap (AttrMap, attrMap, attrName)
import Brick.Util (bg, fg)
import qualified Graphics.Vty as Vty
---- Various ----
import Lens.Micro
import Lens.Micro.TH (makeLenses)
{---- Type Definitions ----}
-- defines an attribute for a text slice
data Fontification = FT { _ftStart :: Integer -- start index in string
, _ftEnd :: Integer -- end index in string
, _ftAttr :: String -- attribute name
}
makeLenses ''Fontification
{---- Functions ----}
fontMap :: AttrMap
fontMap = attrMap Vty.defAttr
[
(attrName "assignment" , fg Vty.blue),
(attrName "return" , fg Vty.green),
(attrName "guard" , fg Vty.yellow),
(attrName "err_braces" , fg Vty.red), -- unbalanced braces
(attrName "err_string" , fg Vty.red) -- unterminated strings
]
-- calls the fontification functions
-- and returns a list of attributes for text slices
fontify :: String -> [Fontification]
fontify s = []

View file

@ -1,5 +1,4 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} -- needed for lenses
{-# LANGUAGE TemplateHaskell #-}
module Gui (runEditor) where module Gui (runEditor) where
@ -22,6 +21,9 @@ import Data.Text.Markup (Markup, (@@))
import System.IO (IOMode (..), hClose, hGetContents, import System.IO (IOMode (..), hClose, hGetContents,
openFile) openFile)
---- Markup ----
import qualified Fontifier as Fontifier
---- Various ---- ---- Various ----
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import Data.List import Data.List
@ -45,7 +47,6 @@ makeLenses ''HeditState
{---- Functions ----} {---- Functions ----}
runEditor :: FilePath -> IO () runEditor :: FilePath -> IO ()
@ -73,7 +74,7 @@ theApp = App { appDraw = drawUI
, appChooseCursor = showFirstCursor , appChooseCursor = showFirstCursor
, appHandleEvent = appEvent , appHandleEvent = appEvent
, appStartEvent = return , appStartEvent = return
, appAttrMap = const (attrMap Vty.defAttr [ ]) , appAttrMap = const $ Fontifier.fontMap
, appLiftVtyEvent = id , appLiftVtyEvent = id
} }
@ -109,14 +110,14 @@ appEvent st ev
-- TODO Refactor parts into SyntaxChecker.hs somehow -- TODO Refactor
-- Rough idea: -- 1) Forget the monad thing that used to stand here, no need to
-- 1) make some monad that carries kind of markup-info -- introduce state
-- state from one checker function to the next -- 2) Rough idea:
-- 2) call checker functions in editor -- -> call Fontifier.fontify (public interface to whatever
-- 3) get (combined) markup-info from checkers -- the fontification functions do)
-- 4) apply markup-info in editor function -- -> get list of attributes for text slices
-- -> apply attributes to text in editor gui
brackets :: [(Char,Char)] brackets :: [(Char,Char)]
brackets = [('(',')'),('[',']'),('{','}')] brackets = [('(',')'),('[',']'),('{','}')]