{-# LINE 1 "templates/wrappers.hs" #-} -- ----------------------------------------------------------------------------- -- Alex wrapper code. -- -- This code is in the PUBLIC DOMAIN; you may copy it freely and use -- it for any purpose whatsoever. import Data.Word (Word8) import Data.Int (Int64) import qualified Data.Char import qualified Data.ByteString.Lazy as ByteString import qualified Data.ByteString.Internal as ByteString (w2c) type Byte = Word8 -- ----------------------------------------------------------------------------- -- The input type type AlexInput = (AlexPosn, -- current position, Char, -- previous char ByteString.ByteString, -- current input string Int64) -- bytes consumed so far ignorePendingBytes :: AlexInput -> AlexInput ignorePendingBytes i = i -- no pending bytes when lexing bytestrings alexInputPrevChar :: AlexInput -> Char alexInputPrevChar (_,c,_,_) = c alexGetByte :: AlexInput -> Maybe (Byte,AlexInput) alexGetByte (p,_,cs,n) = case ByteString.uncons cs of Nothing -> Nothing Just (b, cs') -> let c = ByteString.w2c b p' = alexMove p c n' = n+1 in p' `seq` cs' `seq` n' `seq` Just (b, (p', c, cs',n')) -- ----------------------------------------------------------------------------- -- Token positions -- `Posn' records the location of a token in the input text. It has three -- fields: the address (number of chacaters preceding the token), line number -- and column of a token within the file. `start_pos' gives the position of the -- start of the file and `eof_pos' a standard encoding for the end of file. -- `move_pos' calculates the new position after traversing a given character, -- assuming the usual eight character tab stops. data AlexPosn = AlexPn !Int !Int !Int deriving (Eq,Show) alexStartPos :: AlexPosn alexStartPos = AlexPn 0 1 1 alexMove :: AlexPosn -> Char -> AlexPosn alexMove (AlexPn a l c) '\t' = AlexPn (a+1) l (c+alex_tab_size-((c-1) `mod` alex_tab_size)) alexMove (AlexPn a l _) '\n' = AlexPn (a+1) (l+1) 1 alexMove (AlexPn a l c) _ = AlexPn (a+1) l (c+1) -- ----------------------------------------------------------------------------- -- Monad (default and with ByteString input) -- ----------------------------------------------------------------------------- -- Basic wrapper -- ----------------------------------------------------------------------------- -- Basic wrapper, ByteString version -- ----------------------------------------------------------------------------- -- Posn wrapper -- Adds text positions to the basic model. -- ----------------------------------------------------------------------------- -- Posn wrapper, ByteString version --alexScanTokens :: ByteString.ByteString -> [token] alexScanTokens str0 = go (alexStartPos,'\n',str0,0) where go inp__@(pos,_,str,n) = case alexScan inp__ 0 of AlexEOF -> [] AlexError ((AlexPn _ line column),_,_,_) -> error $ "lexical error at line " ++ (show line) ++ ", column " ++ (show column) AlexSkip inp__' _len -> go inp__' AlexToken inp__'@(_,_,_,n') _ act -> act pos (ByteString.take (n'-n) str) : go inp__' -- ----------------------------------------------------------------------------- -- GScan wrapper -- For compatibility with previous versions of Alex, and because we can.