module Hydrogen.Syntax.Types where import Hydrogen.Prelude import Hydrogen.Parsing type POPs a = [(SourcePos, POP a)] data POP a where Token :: TokenType -> [Char] -> [Char] -> POP a Block :: BlockType -> [Char] -> POPs a -> POP a Value :: a -> String -> POP a deriving (Eq, Show, Typeable, Generic) instance Serialize a => Serialize (POP a) data TokenType where AposString :: TokenType QuotString :: TokenType TickString :: TokenType SomethingT :: TokenType deriving (Eq, Ord, Enum, Show, Typeable, Generic) instance Serialize TokenType data BlockType where Grouping :: BlockType Brackets :: BlockType Mustache :: BlockType deriving (Eq, Ord, Enum, Show, Typeable, Generic) instance Serialize BlockType data Token where TSpecial :: Char -> Token TBraceOpen :: [Char] -> Char -> Token TBraceClose :: Char -> Token TSomething :: [Char] -> Token TIndent :: Int -> Token TSpaces :: Token TString :: [Char] -> Char -> [Char] -> Token deriving (Eq, Ord, Show, Typeable, Generic) instance Serialize Token