module Config.Tokens
( Token(..)
, Located(..)
, Position(..)
, Error(..)
, layoutPass
) where
import Data.Text (Text)
data Position = Position
{ posIndex, posLine, posColumn :: {-# UNPACK #-} !Int }
deriving (Read, Show)
data Located a = Located
{ locPosition :: {-# UNPACK #-} !Position
, locThing :: !a
}
deriving (Read, Show)
instance Functor Located where
fmap f (Located p x) = Located p (f x)
data Token
= Section Text
| String Text
| Atom Text
| Bullet
| Comma
| Number Int Integer
| Floating Integer Integer
| OpenList
| CloseList
| OpenMap
| CloseMap
| Error Error
| LayoutSep
| LayoutEnd
| EOF
deriving (Show)
data Error
= UntermComment
| UntermCommentString
| UntermString
| UntermFile
| BadEscape Text
| NoMatch Char
deriving (Show)
layoutPass ::
[Located Token] ->
[Located Token]
layoutPass toks = foldr step (\_ -> []) toks []
step ::
Located Token ->
([Int] -> [Located Token]) ->
[Int] ->
[Located Token]
step t next cols =
case cols of
col:_ | toCol t == col -> t{locThing=LayoutSep} : t : next cols
col:cols' | toCol t < col -> t{locThing=LayoutEnd} : step t next cols'
_ | usesLayout t -> t : next (toCol t : cols)
_ -> t : next cols
toCol :: Located a -> Int
toCol = posColumn . locPosition
usesLayout :: Located Token -> Bool
usesLayout t
| Section{} <- locThing t = True
| Bullet <- locThing t = True
| otherwise = False