------------------------------------------------------------------
-- |
-- Module      :  Language.WebIDL.Lexer
-- Copyright   :  (c) Dmitry Golubovsky, 2009
-- License     :  BSD-style
-- 
-- Maintainer  :  golubovsky@gmail.com
-- Stability   :  experimental
-- Portability :  portable
-- 
--
--
-- FFI access to the WebIDL lexer from the es-operating-system project.
------------------------------------------------------------------

module Language.WebIDL.Lexer (
  Token (..)
 ,pickToken
 ,lexStdin) where


import HS_LEXER_H
import Control.Monad
import Data.ByteString (ByteString(..), packCString)
import Data.ByteString.UTF8 (toString)

-- |Data type to represent IDL tokens.

data Token = Token {
  tag :: Int                     -- ^whatever yylex() returns
 ,line :: Int                    -- ^starting line
 ,column:: Int                   -- ^starting column
 ,name :: String                 -- ^token value or an empty string
} deriving (Show)

fromIntegralM = return . fromIntegral

tokValue :: IO String

tokValue = do
  tok <- v_p_yylval
  nm <- tok --> V_name
  if nm == nullPtr 
    then return ""
    else do
      s <- packCString nm >>= return . toString
      f_free nm
      (tok, V_name) <-- nullPtr
      return s

-- |Get a token from the lexer. Upon EOF, token with tag 0 will be returned.

pickToken :: IO Token

pickToken = do
  tag <- f_yylex
  loc <- v_p_yylloc
  line <- loc --> V_first_line
  column <- loc --> V_first_column
  return Token `ap` fromIntegralM tag 
               `ap` fromIntegralM line 
               `ap` fromIntegralM column 
               `ap` tokValue


-- |Tokenize the standard input.

lexStdin :: IO [Token]

lexStdin = lsin [] where
  lsin ts = do
    t <- pickToken
    let ts' = t:ts
    case tag t of
      0 -> return (reverse ts')
      _ -> lsin ts'