mirror of
				https://github.com/Drezil/dear-imgui.hs.git
				synced 2025-11-04 07:01:06 +01:00 
			
		
		
		
	Parse enums from headers & generate code (#19)
This commit is contained in:
		
							
								
								
									
										392
									
								
								generator/DearImGui/Generator/Parser.hs
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										392
									
								
								generator/DearImGui/Generator/Parser.hs
									
									
									
									
									
										Normal file
									
								
							@@ -0,0 +1,392 @@
 | 
			
		||||
{-# LANGUAGE BlockArguments #-}
 | 
			
		||||
{-# LANGUAGE DerivingStrategies #-}
 | 
			
		||||
{-# LANGUAGE DuplicateRecordFields #-}
 | 
			
		||||
{-# LANGUAGE FlexibleContexts #-}
 | 
			
		||||
{-# LANGUAGE LambdaCase #-}
 | 
			
		||||
{-# LANGUAGE NamedFieldPuns #-}
 | 
			
		||||
{-# LANGUAGE OverloadedStrings #-}
 | 
			
		||||
{-# LANGUAGE RecordWildCards #-}
 | 
			
		||||
{-# LANGUAGE ScopedTypeVariables #-}
 | 
			
		||||
{-# LANGUAGE TemplateHaskellQuotes #-}
 | 
			
		||||
{-# LANGUAGE TypeApplications #-}
 | 
			
		||||
{-# LANGUAGE ViewPatterns #-}
 | 
			
		||||
 | 
			
		||||
module DearImGui.Generator.Parser
 | 
			
		||||
  ( CustomParseError(..)
 | 
			
		||||
  , headers
 | 
			
		||||
  )
 | 
			
		||||
  where
 | 
			
		||||
 | 
			
		||||
-- base
 | 
			
		||||
import Control.Applicative
 | 
			
		||||
  ( (<|>), many, optional, some )
 | 
			
		||||
import Control.Monad
 | 
			
		||||
  ( void )
 | 
			
		||||
import Data.Bits
 | 
			
		||||
  ( Bits(shiftL) )
 | 
			
		||||
import Data.Char
 | 
			
		||||
  ( isSpace, toLower )
 | 
			
		||||
import Data.Either
 | 
			
		||||
  ( partitionEithers )
 | 
			
		||||
import Data.Functor
 | 
			
		||||
  ( ($>) )
 | 
			
		||||
import Data.Int
 | 
			
		||||
  ( Int64 )
 | 
			
		||||
import Data.Maybe
 | 
			
		||||
  ( catMaybes, fromMaybe )
 | 
			
		||||
import Foreign.C.Types
 | 
			
		||||
  ( CInt )
 | 
			
		||||
 | 
			
		||||
-- template-haskell
 | 
			
		||||
import qualified Language.Haskell.TH as TH
 | 
			
		||||
  ( Name )
 | 
			
		||||
 | 
			
		||||
-- megaparsec
 | 
			
		||||
import Text.Megaparsec
 | 
			
		||||
  ( MonadParsec(..), ShowErrorComponent(..)
 | 
			
		||||
  , (<?>), anySingle, customFailure, single
 | 
			
		||||
  )
 | 
			
		||||
 | 
			
		||||
-- parser-combinators
 | 
			
		||||
import Control.Applicative.Combinators
 | 
			
		||||
  ( manyTill, option, sepBy1, skipManyTill )
 | 
			
		||||
 | 
			
		||||
-- scientific
 | 
			
		||||
import Data.Scientific
 | 
			
		||||
  ( floatingOrInteger, toBoundedInteger )
 | 
			
		||||
 | 
			
		||||
-- text
 | 
			
		||||
import Data.Text
 | 
			
		||||
  ( Text )
 | 
			
		||||
import qualified Data.Text as Text
 | 
			
		||||
  ( all, any, breakOn, drop, dropWhile, dropWhileEnd
 | 
			
		||||
  , length, stripPrefix, unlines, unpack
 | 
			
		||||
  )
 | 
			
		||||
 | 
			
		||||
-- transformers
 | 
			
		||||
import Control.Monad.Trans.State.Strict
 | 
			
		||||
  ( StateT(..)
 | 
			
		||||
  , get, modify'
 | 
			
		||||
  )
 | 
			
		||||
 | 
			
		||||
-- unordered-containers
 | 
			
		||||
import Data.HashMap.Strict
 | 
			
		||||
  ( HashMap )
 | 
			
		||||
import qualified Data.HashMap.Strict as HashMap
 | 
			
		||||
  ( fromList, insert, lookup )
 | 
			
		||||
 | 
			
		||||
-- dear-imgui-generator 
 | 
			
		||||
import DearImGui.Generator.Tokeniser
 | 
			
		||||
  ( Tok(..) )
 | 
			
		||||
import DearImGui.Generator.Types
 | 
			
		||||
  ( Comment(..), Enumeration(..), Headers(..) )
 | 
			
		||||
 | 
			
		||||
--------------------------------------------------------------------------------
 | 
			
		||||
-- Parse error type.
 | 
			
		||||
 | 
			
		||||
data CustomParseError
 | 
			
		||||
  = Couldn'tLookupEnumValues
 | 
			
		||||
    { enumName :: !Text
 | 
			
		||||
    , problems :: ![Text]
 | 
			
		||||
    }
 | 
			
		||||
  | MissingForwardDeclaration
 | 
			
		||||
    { enumName :: !Text }
 | 
			
		||||
  | UnexpectedSection
 | 
			
		||||
    { sectionName :: !Text
 | 
			
		||||
    , problem     :: ![Text]
 | 
			
		||||
    }
 | 
			
		||||
  deriving stock ( Show, Eq, Ord )
 | 
			
		||||
 | 
			
		||||
instance ShowErrorComponent CustomParseError where
 | 
			
		||||
  showErrorComponent ( Couldn'tLookupEnumValues { enumName, problems } ) = Text.unpack $
 | 
			
		||||
    "Couldn't lookup the following values in enum " <> enumName <> ":\n"
 | 
			
		||||
    <> Text.unlines ( map ( " - "  <> ) problems )
 | 
			
		||||
  showErrorComponent ( MissingForwardDeclaration { enumName } ) = Text.unpack $
 | 
			
		||||
    "Missing forward declaration for enum named " <> enumName
 | 
			
		||||
  showErrorComponent ( UnexpectedSection { sectionName, problem } ) = Text.unpack $
 | 
			
		||||
    "Unexpected section name.\n\
 | 
			
		||||
    \Expected: " <> sectionName <> "\n\
 | 
			
		||||
    \  Actual: " <> Text.unlines ( map ( " "  <> ) problem )
 | 
			
		||||
 | 
			
		||||
--------------------------------------------------------------------------------
 | 
			
		||||
-- Parsing headers.
 | 
			
		||||
 | 
			
		||||
headers :: MonadParsec CustomParseError [Tok] m => m Headers
 | 
			
		||||
headers = do
 | 
			
		||||
  _ <- skipManyTill anySingle ( namedSection "Header mess" )
 | 
			
		||||
  _ <- skipManyTill anySingle ( namedSection "Forward declarations" )
 | 
			
		||||
  ( _structNames, enumNamesAndTypes ) <- forwardDeclarations
 | 
			
		||||
  _ <- skipManyTill anySingle ( namedSection "Dear ImGui end-user API functions" )
 | 
			
		||||
  _ <- skipManyTill anySingle ( namedSection "Flags & Enumerations" )
 | 
			
		||||
  ( _defines, enums ) <- partitionEithers <$>
 | 
			
		||||
    manyTill
 | 
			
		||||
      (   ( Left  <$> try ignoreDefine )
 | 
			
		||||
      <|> ( Right <$> enumeration enumNamesAndTypes )
 | 
			
		||||
      )
 | 
			
		||||
      ( namedSection "Helpers: Memory allocations macros, ImVector<>" )
 | 
			
		||||
  _ <- skipManyTill anySingle ( namedSection "ImGuiStyle" )
 | 
			
		||||
  _ <- skipManyTill anySingle ( namedSection "ImGuiIO" )
 | 
			
		||||
  _ <- skipManyTill anySingle ( namedSection "Misc data structures" )
 | 
			
		||||
  _ <- skipManyTill anySingle ( namedSection "Obsolete functions" )
 | 
			
		||||
  _ <- skipManyTill anySingle ( namedSection "Helpers" )
 | 
			
		||||
  _ <- skipManyTill anySingle ( namedSection "Drawing API" )
 | 
			
		||||
  _ <- skipManyTill anySingle ( namedSection "Font API" )
 | 
			
		||||
 | 
			
		||||
  pure ( Headers { enums } )
 | 
			
		||||
 | 
			
		||||
--------------------------------------------------------------------------------
 | 
			
		||||
-- Parsing forward declarations.
 | 
			
		||||
 | 
			
		||||
forwardDeclarations
 | 
			
		||||
  :: MonadParsec CustomParseError [Tok] m
 | 
			
		||||
  => m ( HashMap Text Comment, HashMap Text ( TH.Name, Comment ) )
 | 
			
		||||
forwardDeclarations = do
 | 
			
		||||
  _ <- many comment
 | 
			
		||||
  structs <- many do
 | 
			
		||||
    keyword "struct"
 | 
			
		||||
    structName <- identifier
 | 
			
		||||
    reservedSymbol ';'
 | 
			
		||||
    doc <- comment
 | 
			
		||||
    pure ( structName, doc )
 | 
			
		||||
  _ <- many comment
 | 
			
		||||
  enums <- many do
 | 
			
		||||
    keyword "typedef"
 | 
			
		||||
    ty <- enumTypeName
 | 
			
		||||
    enumName <- identifier
 | 
			
		||||
    reservedSymbol ';'
 | 
			
		||||
    doc <- commentText <$> comment
 | 
			
		||||
    pure ( enumName, ( ty, CommentText <$> Text.drop 2 . snd $ Text.breakOn "//" doc ) )
 | 
			
		||||
  -- Stopping after simple structs and enums for now.
 | 
			
		||||
  pure ( HashMap.fromList structs, HashMap.fromList enums )
 | 
			
		||||
 | 
			
		||||
enumTypeName :: MonadParsec e [Tok] m => m TH.Name
 | 
			
		||||
enumTypeName = keyword "int" $> ''CInt
 | 
			
		||||
 | 
			
		||||
--------------------------------------------------------------------------------
 | 
			
		||||
-- Parsing enumerations.
 | 
			
		||||
 | 
			
		||||
data EnumState = EnumState
 | 
			
		||||
  { enumValues       :: HashMap Text Integer
 | 
			
		||||
  , currEnumTag      :: Integer
 | 
			
		||||
  , enumSize         :: Integer
 | 
			
		||||
  , hasExplicitCount :: Bool
 | 
			
		||||
  }
 | 
			
		||||
 | 
			
		||||
enumeration :: MonadParsec CustomParseError [Tok] m => HashMap Text ( TH.Name, Comment ) -> m Enumeration
 | 
			
		||||
enumeration enumNamesAndTypes = do
 | 
			
		||||
  inlineDocs <- many comment
 | 
			
		||||
  keyword "enum"
 | 
			
		||||
  fullEnumName <- identifier
 | 
			
		||||
  let
 | 
			
		||||
    enumName :: Text
 | 
			
		||||
    enumName = Text.dropWhileEnd ( == '_' ) fullEnumName
 | 
			
		||||
  ( enumType, forwardDoc ) <- case HashMap.lookup enumName enumNamesAndTypes of
 | 
			
		||||
    Just res -> pure res
 | 
			
		||||
    Nothing  -> customFailure ( MissingForwardDeclaration { enumName } )
 | 
			
		||||
  let
 | 
			
		||||
    docs :: [Comment]
 | 
			
		||||
    docs = forwardDoc : CommentText "" : inlineDocs
 | 
			
		||||
  reservedSymbol '{'
 | 
			
		||||
  ( patterns, EnumState { enumSize, hasExplicitCount } ) <- 
 | 
			
		||||
    ( `runStateT` EnumState { enumValues = mempty, currEnumTag = 0, enumSize = 0, hasExplicitCount = False } ) $
 | 
			
		||||
      catMaybes
 | 
			
		||||
          <$> many
 | 
			
		||||
               (   some ignoredPatternContent $> Nothing
 | 
			
		||||
               <|> enumerationPattern fullEnumName
 | 
			
		||||
               )
 | 
			
		||||
  reservedSymbol '}'
 | 
			
		||||
  reservedSymbol  ';'
 | 
			
		||||
  pure ( Enumeration { .. } )
 | 
			
		||||
 | 
			
		||||
ignoredPatternContent :: MonadParsec e [Tok] m => m ()
 | 
			
		||||
ignoredPatternContent = void ( try comment ) <|> cppConditional
 | 
			
		||||
 | 
			
		||||
enumerationPattern
 | 
			
		||||
  :: MonadParsec CustomParseError [ Tok ] m
 | 
			
		||||
  => Text
 | 
			
		||||
  -> StateT EnumState m ( Maybe ( Text, Integer, Comment ) )
 | 
			
		||||
enumerationPattern enumName = do
 | 
			
		||||
  mbPatNameVal <- patternNameAndValue enumName
 | 
			
		||||
  _ <- optional $ reservedSymbol ','
 | 
			
		||||
  comm <- fromMaybe ( CommentText "" ) <$> optional comment
 | 
			
		||||
  pure $
 | 
			
		||||
    case mbPatNameVal of
 | 
			
		||||
      Nothing                    -> Nothing
 | 
			
		||||
      Just ( patName, patValue ) -> Just ( patName, patValue, comm )
 | 
			
		||||
 | 
			
		||||
patternNameAndValue
 | 
			
		||||
  :: forall m
 | 
			
		||||
  .  MonadParsec CustomParseError [ Tok ] m
 | 
			
		||||
  => Text
 | 
			
		||||
  -> StateT EnumState m ( Maybe ( Text, Integer ) )
 | 
			
		||||
patternNameAndValue enumName =
 | 
			
		||||
  try do
 | 
			
		||||
      sz <- count
 | 
			
		||||
      modify' ( ( \ st -> st { enumSize = sz, hasExplicitCount = True } ) :: EnumState -> EnumState )
 | 
			
		||||
      pure Nothing
 | 
			
		||||
  <|> do
 | 
			
		||||
        pat@( _, val ) <- value
 | 
			
		||||
        modify' ( \ st -> st { enumSize = ( enumSize :: EnumState -> Integer ) st + 1, currEnumTag = val + 1} )
 | 
			
		||||
        pure ( Just pat )
 | 
			
		||||
  where
 | 
			
		||||
    count :: StateT EnumState m Integer
 | 
			
		||||
    count = do
 | 
			
		||||
      _ <- single ( Identifier $ enumName <> "COUNT" )
 | 
			
		||||
      mbVal <- optional do
 | 
			
		||||
        _ <- reservedSymbol '='
 | 
			
		||||
        integerExpression
 | 
			
		||||
      case mbVal of
 | 
			
		||||
        Nothing -> currEnumTag <$> get
 | 
			
		||||
        Just ct -> pure ct
 | 
			
		||||
    value :: StateT EnumState m ( Text, Integer )
 | 
			
		||||
    value = do
 | 
			
		||||
      name <- identifier
 | 
			
		||||
      val <- patternRHS
 | 
			
		||||
      modify' ( \ st -> st { enumValues = HashMap.insert name val ( enumValues st ) } )
 | 
			
		||||
      pure ( name, val )
 | 
			
		||||
    patternRHS :: StateT EnumState m Integer
 | 
			
		||||
    patternRHS =
 | 
			
		||||
      ( do
 | 
			
		||||
        reservedSymbol '='
 | 
			
		||||
        try integerExpression <|> try disjunction
 | 
			
		||||
      )
 | 
			
		||||
      <|> ( currEnumTag <$> get )
 | 
			
		||||
 | 
			
		||||
    disjunction :: StateT EnumState m Integer
 | 
			
		||||
    disjunction = do
 | 
			
		||||
      ( summands :: [Text] ) <- identifier `sepBy1` symbol "|"
 | 
			
		||||
      valsMap <- enumValues <$> get
 | 
			
		||||
      let
 | 
			
		||||
        res :: Either [ Text ] Integer
 | 
			
		||||
        res = foldr
 | 
			
		||||
          ( \ summand errsOrVal -> case HashMap.lookup summand valsMap of
 | 
			
		||||
            Nothing -> case errsOrVal of { Right _  -> Left [ summand ]; Left errs -> Left ( summand : errs ) }
 | 
			
		||||
            Just v  -> case errsOrVal of { Right v' -> Right ( v + v' ); Left errs -> Left errs }
 | 
			
		||||
          )
 | 
			
		||||
          ( Right 0 )
 | 
			
		||||
          summands
 | 
			
		||||
      case res of
 | 
			
		||||
        Left problems -> customFailure ( Couldn'tLookupEnumValues { enumName, problems } )
 | 
			
		||||
        Right v -> pure v
 | 
			
		||||
 | 
			
		||||
--------------------------------------------------------------------------------
 | 
			
		||||
-- Simple token parsers.
 | 
			
		||||
 | 
			
		||||
comment :: MonadParsec e [ Tok ] m => m Comment
 | 
			
		||||
comment = CommentText <$>
 | 
			
		||||
  token ( \ case { Comment comm -> Just comm; _ -> Nothing } ) mempty
 | 
			
		||||
    <?> "comment"
 | 
			
		||||
 | 
			
		||||
keyword :: MonadParsec e [ Tok ] m => Text -> m ()
 | 
			
		||||
keyword kw = token ( \ case { Keyword kw' | kw == kw' -> Just (); _ -> Nothing } ) mempty
 | 
			
		||||
  <?> ( Text.unpack kw <> " (keyword)" )
 | 
			
		||||
 | 
			
		||||
identifier :: MonadParsec e [ Tok ] m => m Text
 | 
			
		||||
identifier = token ( \ case { Identifier i -> Just i; _ -> Nothing } ) mempty
 | 
			
		||||
  <?> "identifier"
 | 
			
		||||
 | 
			
		||||
{-
 | 
			
		||||
prefixedIdentifier :: MonadParsec e [ Tok ] m => Text -> m Text
 | 
			
		||||
prefixedIdentifier prefix =
 | 
			
		||||
  token
 | 
			
		||||
    ( \ case
 | 
			
		||||
      { Identifier i -> Text.dropWhile ( == '_' ) <$> Text.stripPrefix prefix i
 | 
			
		||||
      ; _ -> Nothing
 | 
			
		||||
      }
 | 
			
		||||
    ) mempty
 | 
			
		||||
-}
 | 
			
		||||
 | 
			
		||||
reservedSymbol :: MonadParsec e [ Tok ] m => Char -> m ()
 | 
			
		||||
reservedSymbol s = token ( \ case { ReservedSymbol s' | s == s' -> Just (); _ -> Nothing } ) mempty
 | 
			
		||||
  <?> ( [s] <> " (reserved symbol)" )
 | 
			
		||||
 | 
			
		||||
symbol :: MonadParsec e [ Tok ] m => Text -> m ()
 | 
			
		||||
symbol s = token ( \ case { Symbolic s' | s == s' -> Just (); _ -> Nothing } ) mempty
 | 
			
		||||
  <?> ( Text.unpack s <> " (symbol)" )
 | 
			
		||||
 | 
			
		||||
integerExpression :: MonadParsec e [ Tok ] m => m Integer
 | 
			
		||||
integerExpression = try integerPower <|> integer
 | 
			
		||||
 | 
			
		||||
integerPower :: MonadParsec e [ Tok ] m => m Integer
 | 
			
		||||
integerPower = do
 | 
			
		||||
  a <- integer
 | 
			
		||||
  _ <- symbol "<<"
 | 
			
		||||
  i <- integer
 | 
			
		||||
  pure ( a `shiftL` fromIntegral i )
 | 
			
		||||
 | 
			
		||||
integer :: forall e m. MonadParsec e [ Tok ] m => m Integer
 | 
			
		||||
integer =
 | 
			
		||||
  option id mkSign <*>
 | 
			
		||||
    token
 | 
			
		||||
      ( \ case {
 | 
			
		||||
        Number i suff
 | 
			
		||||
          | Just  _  <- toBoundedInteger @Int64 i
 | 
			
		||||
          , Right i' <- floatingOrInteger @Float @Integer i
 | 
			
		||||
          , not ( Text.any ( (== 'f' ) . toLower ) suff )
 | 
			
		||||
          -> Just i';
 | 
			
		||||
         _ -> Nothing
 | 
			
		||||
        }
 | 
			
		||||
      )
 | 
			
		||||
      mempty
 | 
			
		||||
    <?> "integer"
 | 
			
		||||
  where
 | 
			
		||||
    mkSign :: m ( Integer -> Integer )
 | 
			
		||||
    mkSign = ( symbol "+" $> id ) <|> ( symbol "-" $> negate )
 | 
			
		||||
 | 
			
		||||
section :: MonadParsec e [ Tok ] m => m [Text]
 | 
			
		||||
section =
 | 
			
		||||
  do
 | 
			
		||||
    sectionText <- try do
 | 
			
		||||
      separator
 | 
			
		||||
      token
 | 
			
		||||
        ( \ case
 | 
			
		||||
          { Comment txt -> fmap ( Text.dropWhile isSpace )
 | 
			
		||||
                         . Text.stripPrefix "[SECTION]"
 | 
			
		||||
                         . Text.dropWhile isSpace
 | 
			
		||||
                         $ txt
 | 
			
		||||
          ; _ -> Nothing
 | 
			
		||||
          }
 | 
			
		||||
        ) mempty
 | 
			
		||||
    rest <- endOfSectionHeader
 | 
			
		||||
    pure ( sectionText : filter ( not . Text.all ( \ c -> c == '-' || isSpace c ) ) rest )
 | 
			
		||||
  <?> "section"
 | 
			
		||||
 | 
			
		||||
separator :: MonadParsec e [ Tok ] m => m ()
 | 
			
		||||
separator = token
 | 
			
		||||
  ( \ case
 | 
			
		||||
    { Comment hyphens | Text.length hyphens > 10 && Text.all ( == '-') hyphens -> Just ()
 | 
			
		||||
    ; _ -> Nothing
 | 
			
		||||
    }
 | 
			
		||||
  ) mempty
 | 
			
		||||
  <?> "separator"
 | 
			
		||||
 | 
			
		||||
endOfSectionHeader :: MonadParsec e [ Tok ] m => m [Text]
 | 
			
		||||
endOfSectionHeader =  try ( (:) <$> ( commentText <$> comment ) <*> endOfSectionHeader )
 | 
			
		||||
                  <|> ( separator $> [] )
 | 
			
		||||
 | 
			
		||||
namedSection :: MonadParsec CustomParseError [ Tok ] m => Text -> m ()
 | 
			
		||||
namedSection sectionName =
 | 
			
		||||
  do
 | 
			
		||||
    sectionTexts <- section
 | 
			
		||||
    case sectionTexts of
 | 
			
		||||
      sectionText : _
 | 
			
		||||
        | Just _ <- Text.stripPrefix sectionName sectionText
 | 
			
		||||
        -> pure ()
 | 
			
		||||
      _ -> customFailure ( UnexpectedSection { sectionName, problem = sectionTexts } )
 | 
			
		||||
  <?> ( "section named " <> Text.unpack sectionName )
 | 
			
		||||
 | 
			
		||||
cppDirective :: MonadParsec e [Tok] m => ( Text -> Maybe a ) -> m a
 | 
			
		||||
cppDirective f = token ( \case { BeginCPP a -> f a; _ -> Nothing } ) mempty
 | 
			
		||||
 | 
			
		||||
cppConditional :: MonadParsec e [Tok] m => m ()
 | 
			
		||||
cppConditional = do
 | 
			
		||||
  void $ cppDirective ( \case { "ifdef" -> Just True; "ifndef" -> Just False; _ -> Nothing } )
 | 
			
		||||
  -- assumes no nesting
 | 
			
		||||
  void $ skipManyTill anySingle ( cppDirective ( \case { "endif" -> Just (); _ -> Nothing } ) )
 | 
			
		||||
  void $ skipManyTill anySingle ( single EndCPPLine )
 | 
			
		||||
 | 
			
		||||
ignoreDefine :: MonadParsec e [Tok] m => m ()
 | 
			
		||||
ignoreDefine = do
 | 
			
		||||
  void $ many comment
 | 
			
		||||
  void $ cppDirective ( \case { "define" -> Just (); _ -> Nothing } )
 | 
			
		||||
  void $ skipManyTill anySingle ( single EndCPPLine )
 | 
			
		||||
							
								
								
									
										197
									
								
								generator/DearImGui/Generator/Tokeniser.hs
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										197
									
								
								generator/DearImGui/Generator/Tokeniser.hs
									
									
									
									
									
										Normal file
									
								
							@@ -0,0 +1,197 @@
 | 
			
		||||
{-# LANGUAGE DerivingStrategies #-}
 | 
			
		||||
{-# LANGUAGE FlexibleContexts #-}
 | 
			
		||||
{-# LANGUAGE FlexibleInstances #-}
 | 
			
		||||
{-# LANGUAGE LambdaCase #-}
 | 
			
		||||
{-# LANGUAGE OverloadedStrings #-}
 | 
			
		||||
{-# LANGUAGE TypeApplications #-}
 | 
			
		||||
{-# LANGUAGE ViewPatterns #-}
 | 
			
		||||
 | 
			
		||||
module DearImGui.Generator.Tokeniser where
 | 
			
		||||
 | 
			
		||||
-- base
 | 
			
		||||
import Control.Arrow
 | 
			
		||||
  ( first, second )
 | 
			
		||||
import Control.Applicative
 | 
			
		||||
  ( (<|>), some )
 | 
			
		||||
import Data.Char
 | 
			
		||||
  ( isAlpha, isAlphaNum, isDigit, isPunctuation, isSpace, isSymbol, toLower )
 | 
			
		||||
import Data.Function
 | 
			
		||||
  ( (&) )
 | 
			
		||||
import Data.Functor
 | 
			
		||||
  ( ($>) )
 | 
			
		||||
import Data.Monoid
 | 
			
		||||
  ( Sum(..) )
 | 
			
		||||
 | 
			
		||||
-- megaparsec
 | 
			
		||||
import Text.Megaparsec
 | 
			
		||||
  ( MonadParsec, VisualStream(..)
 | 
			
		||||
  , chunk, parseMaybe, satisfy, try
 | 
			
		||||
  )
 | 
			
		||||
import Text.Megaparsec.Char.Lexer
 | 
			
		||||
  ( hexadecimal, scientific )
 | 
			
		||||
 | 
			
		||||
-- parser-combinators
 | 
			
		||||
import Control.Monad.Combinators
 | 
			
		||||
  ( optional )
 | 
			
		||||
 | 
			
		||||
-- scientific
 | 
			
		||||
import Data.Scientific
 | 
			
		||||
  ( Scientific )
 | 
			
		||||
 | 
			
		||||
-- text
 | 
			
		||||
import Data.Text
 | 
			
		||||
  ( Text )
 | 
			
		||||
import qualified Data.Text as Text
 | 
			
		||||
  ( break, breakOn, cons, drop, dropWhile
 | 
			
		||||
  , head, last, length
 | 
			
		||||
  , pack, snoc, span, strip, tail, take
 | 
			
		||||
  , uncons, unpack
 | 
			
		||||
  )
 | 
			
		||||
 | 
			
		||||
-- unordered-containers
 | 
			
		||||
import Data.HashSet
 | 
			
		||||
  ( HashSet )
 | 
			
		||||
import qualified Data.HashSet as HashSet
 | 
			
		||||
  ( fromList, member )
 | 
			
		||||
 | 
			
		||||
--------------------------------------------------------------------------------
 | 
			
		||||
 | 
			
		||||
data TokeniserError
 | 
			
		||||
  = Couldn'tParseNumber { problem :: !Text }
 | 
			
		||||
  | UnhandledCase { unhandled :: !( Char, Text ) }
 | 
			
		||||
  deriving stock ( Eq, Ord, Show )
 | 
			
		||||
 | 
			
		||||
data Tok
 | 
			
		||||
  = Keyword        !Text
 | 
			
		||||
  | ReservedSymbol !Char
 | 
			
		||||
  | Symbolic       !Text
 | 
			
		||||
  | Identifier     !Text
 | 
			
		||||
  | Comment        !Text
 | 
			
		||||
  | Char           !Char
 | 
			
		||||
  | String         !Text
 | 
			
		||||
  | Number         !Scientific !Text
 | 
			
		||||
  | BeginCPP       !Text
 | 
			
		||||
  | EndCPPLine
 | 
			
		||||
  deriving stock ( Show, Eq, Ord )
 | 
			
		||||
 | 
			
		||||
showToken :: Tok -> String
 | 
			
		||||
showToken = \case
 | 
			
		||||
  Keyword        t -> Text.unpack t
 | 
			
		||||
  ReservedSymbol c -> [c]
 | 
			
		||||
  Symbolic       t -> Text.unpack t
 | 
			
		||||
  Identifier     t -> Text.unpack t
 | 
			
		||||
  Comment        t -> Text.unpack t
 | 
			
		||||
  Char           c -> [c]
 | 
			
		||||
  String         t -> Text.unpack t
 | 
			
		||||
  Number       s t -> show s <> Text.unpack t
 | 
			
		||||
  BeginCPP       t -> "#" <> Text.unpack t
 | 
			
		||||
  EndCPPLine       -> "EndCppLine"
 | 
			
		||||
 | 
			
		||||
tokenLength :: Tok -> Int
 | 
			
		||||
tokenLength = \case
 | 
			
		||||
  Keyword        t -> Text.length t
 | 
			
		||||
  ReservedSymbol _ -> 1
 | 
			
		||||
  Symbolic       t -> Text.length t
 | 
			
		||||
  Identifier     t -> Text.length t
 | 
			
		||||
  Comment        t -> Text.length t
 | 
			
		||||
  Char           _ -> 1
 | 
			
		||||
  String         t -> Text.length t
 | 
			
		||||
  Number       s t -> length ( show s ) + Text.length t
 | 
			
		||||
  BeginCPP       t -> 1 + Text.length t
 | 
			
		||||
  EndCPPLine       -> length ( "EndCPPLine" :: String )
 | 
			
		||||
 | 
			
		||||
instance VisualStream [Tok] where
 | 
			
		||||
  showTokens   _ = foldMap showToken
 | 
			
		||||
  tokensLength _ = getSum . foldMap ( Sum . tokenLength )
 | 
			
		||||
 | 
			
		||||
keywords :: HashSet Text
 | 
			
		||||
keywords = HashSet.fromList
 | 
			
		||||
  [ "auto", "break", "case", "char", "const", "continue", "default", "do", "double"
 | 
			
		||||
  , "else", "enum", "extern", "float", "for", "goto", "if", "inline", "int", "long"
 | 
			
		||||
  , "register", "restrict", "return", "short", "signed", "sizeof", "static", "struct"
 | 
			
		||||
  , "switch", "typedef", "union", "unsigned", "void", "volatile", "while"
 | 
			
		||||
  ]
 | 
			
		||||
 | 
			
		||||
reservedSymbols :: HashSet Char
 | 
			
		||||
reservedSymbols = HashSet.fromList [ '(', ')', '{', '}', ',', ';', '=', '#' ]
 | 
			
		||||
 | 
			
		||||
tokenise :: Text -> Either TokeniserError [ Tok ]
 | 
			
		||||
tokenise ( Text.uncons -> Just ( c, cs ) )
 | 
			
		||||
  | isSpace c
 | 
			
		||||
  = tokenise ( Text.dropWhile isSpace cs )
 | 
			
		||||
  | isAlpha c || c == '_'
 | 
			
		||||
  , let
 | 
			
		||||
      this, rest :: Text
 | 
			
		||||
      ( this, rest ) = first ( c `Text.cons` ) $ Text.span ( \ x -> isAlphaNum x || x == '_' ) cs
 | 
			
		||||
  = if this `HashSet.member` keywords
 | 
			
		||||
    then ( Keyword    this : ) <$> tokenise rest
 | 
			
		||||
    else ( Identifier this : ) <$> tokenise rest
 | 
			
		||||
  | isDigit c
 | 
			
		||||
  , let
 | 
			
		||||
      this, rest :: Text
 | 
			
		||||
      ( this, rest ) = continuePastExponent $ first ( c `Text.cons` ) $ Text.span ( \ x -> isAlphaNum x || x == '.' ) cs
 | 
			
		||||
  = case parseMaybe @() parseNumber this of
 | 
			
		||||
      Just numTok -> ( numTok : ) <$> tokenise rest
 | 
			
		||||
      Nothing     -> Left ( Couldn'tParseNumber { problem = this } )
 | 
			
		||||
  | c == '\''
 | 
			
		||||
  , Just ( '\'', rest ) <- Text.uncons ( Text.drop 1 cs )
 | 
			
		||||
  = ( Char ( Text.head cs ) : ) <$> tokenise rest
 | 
			
		||||
  | c == '\"'
 | 
			
		||||
  , let
 | 
			
		||||
      this, rest :: Text
 | 
			
		||||
      ( this, rest ) = second Text.tail $ Text.break ( == '"') cs
 | 
			
		||||
  = ( String this : ) <$> tokenise rest
 | 
			
		||||
  | c == '#'
 | 
			
		||||
  , let
 | 
			
		||||
      directive, line, rest :: Text
 | 
			
		||||
      ( directive, ( line, rest ) )
 | 
			
		||||
        = cs
 | 
			
		||||
        & Text.break ( isSpace )
 | 
			
		||||
        & second ( Text.break ( `elem` [ '\n', '\r' ] ) )
 | 
			
		||||
  = do
 | 
			
		||||
      lineTokens <- tokenise line
 | 
			
		||||
      restTokens <- tokenise rest
 | 
			
		||||
      pure ( ( BeginCPP directive : lineTokens ) <> ( EndCPPLine : restTokens ) )
 | 
			
		||||
  | c `HashSet.member` reservedSymbols
 | 
			
		||||
  = ( ReservedSymbol c : ) <$> tokenise cs
 | 
			
		||||
  | c == '/'
 | 
			
		||||
  = case Text.take 1 cs of
 | 
			
		||||
    "/" ->
 | 
			
		||||
      let
 | 
			
		||||
        comm, rest :: Text
 | 
			
		||||
        ( comm, rest ) = first Text.strip $ Text.break ( `elem` [ '\n', '\r' ] ) ( Text.drop 1 cs )
 | 
			
		||||
      in ( Comment comm : ) <$> tokenise rest
 | 
			
		||||
    "*" ->
 | 
			
		||||
      let
 | 
			
		||||
        comm, rest :: Text
 | 
			
		||||
        ( comm, rest ) = Text.breakOn "*/" ( Text.drop 1 cs )
 | 
			
		||||
      in ( Comment comm : ) <$> tokenise rest
 | 
			
		||||
    _ ->
 | 
			
		||||
      let
 | 
			
		||||
        this, rest :: Text
 | 
			
		||||
        ( this, rest ) = first ( c `Text.cons` ) $ Text.span ( \ x -> x /= '_' && ( isSymbol x || isPunctuation x ) ) cs
 | 
			
		||||
      in ( Symbolic this : ) <$> tokenise rest
 | 
			
		||||
  | isSymbol c || isPunctuation c
 | 
			
		||||
  , let
 | 
			
		||||
      this, rest :: Text
 | 
			
		||||
      ( this, rest ) = first ( c `Text.cons` ) $ Text.span ( \ x -> x /= '_' && ( isSymbol x || isPunctuation x ) ) cs
 | 
			
		||||
  = ( Symbolic this : ) <$> tokenise rest
 | 
			
		||||
  | otherwise
 | 
			
		||||
  = Left $ UnhandledCase { unhandled = ( c, cs ) }
 | 
			
		||||
tokenise _ = Right []
 | 
			
		||||
 | 
			
		||||
continuePastExponent :: ( Text, Text ) -> ( Text, Text )
 | 
			
		||||
continuePastExponent ( this, rest )
 | 
			
		||||
  | toLower ( Text.last this ) `elem` [ 'e', 'p' ]
 | 
			
		||||
  , Just ( r, rs ) <- Text.uncons rest
 | 
			
		||||
  , r `elem` [ '+', '-' ]
 | 
			
		||||
  , ( this', rest' ) <- Text.span isAlphaNum rs
 | 
			
		||||
  = ( this `Text.snoc` r <> this', rest' )
 | 
			
		||||
  | otherwise
 | 
			
		||||
  = ( this, rest )
 | 
			
		||||
 | 
			
		||||
parseNumber :: MonadParsec e Text m => m Tok
 | 
			
		||||
parseNumber = try ( chunk "0.f" $> Number 0 "f" ) <|> do
 | 
			
		||||
  value <- try ( chunk "0x" *> hexadecimal ) <|> scientific
 | 
			
		||||
  mbSuffix <- fmap ( maybe "" Text.pack ) . optional . some $ satisfy ( \ s -> toLower s `elem` ( "uflz" :: String ) )
 | 
			
		||||
  pure ( Number value mbSuffix )
 | 
			
		||||
							
								
								
									
										42
									
								
								generator/DearImGui/Generator/Types.hs
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										42
									
								
								generator/DearImGui/Generator/Types.hs
									
									
									
									
									
										Normal file
									
								
							@@ -0,0 +1,42 @@
 | 
			
		||||
{-# LANGUAGE BangPatterns #-}
 | 
			
		||||
{-# LANGUAGE DeriveLift #-}
 | 
			
		||||
{-# LANGUAGE DerivingStrategies #-}
 | 
			
		||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
 | 
			
		||||
{-# LANGUAGE RecordWildCards #-}
 | 
			
		||||
{-# LANGUAGE TemplateHaskellQuotes #-}
 | 
			
		||||
 | 
			
		||||
module DearImGui.Generator.Types where
 | 
			
		||||
 | 
			
		||||
-- template-haskell
 | 
			
		||||
import qualified Language.Haskell.TH.Syntax as TH
 | 
			
		||||
  ( Lift(..), Name(..) )
 | 
			
		||||
 | 
			
		||||
-- text
 | 
			
		||||
import Data.Text
 | 
			
		||||
  ( Text )
 | 
			
		||||
 | 
			
		||||
-- th-lift
 | 
			
		||||
import Language.Haskell.TH.Lift
 | 
			
		||||
  () -- 'Lift' instance for Name
 | 
			
		||||
 | 
			
		||||
--------------------------------------------------------------------------------
 | 
			
		||||
 | 
			
		||||
newtype Comment = CommentText { commentText :: Text }
 | 
			
		||||
  deriving stock   ( Show, TH.Lift )
 | 
			
		||||
  deriving newtype ( Eq, Ord )
 | 
			
		||||
 | 
			
		||||
data Enumeration
 | 
			
		||||
  = Enumeration
 | 
			
		||||
  { docs             :: ![Comment]
 | 
			
		||||
  , enumName         :: !Text
 | 
			
		||||
  , enumSize         :: !Integer
 | 
			
		||||
  , enumType         :: !TH.Name
 | 
			
		||||
  , hasExplicitCount :: !Bool
 | 
			
		||||
  , patterns         :: [ ( Text, Integer, Comment ) ]
 | 
			
		||||
  }
 | 
			
		||||
  deriving stock ( Show, TH.Lift )
 | 
			
		||||
 | 
			
		||||
data Headers
 | 
			
		||||
  = Headers
 | 
			
		||||
  { enums :: [ Enumeration ] }
 | 
			
		||||
  deriving stock ( Show, TH.Lift )
 | 
			
		||||
		Reference in New Issue
	
	Block a user