Skip to content

Instantly share code, notes, and snippets.

@hvariant
Last active October 21, 2019 13:18
Show Gist options
  • Select an option

  • Save hvariant/c9ddd9d7f7f72a3586b36a5a41d8a6ec to your computer and use it in GitHub Desktop.

Select an option

Save hvariant/c9ddd9d7f7f72a3586b36a5a41d8a6ec to your computer and use it in GitHub Desktop.
convert a C struct to Rust struct, incomplete and probably wrong but works 100% some of the time
import Language.C
import Language.C.System.GCC
import Language.C.Data.Ident
import Language.C.Syntax.AST
import Control.Monad
import Data.Char
import Data.Void
import Text.Casing
main = parseMyFile "tranrec.h" >>= toRust
parseMyFile :: FilePath -> IO CTranslUnit
parseMyFile input_file =
do parse_result <- parseCFile (newGCC "gcc") Nothing [] input_file
case parse_result of
Left parse_err -> error (show parse_err)
Right ast -> return ast
toRust :: CTranslUnit -> IO ()
toRust (CTranslUnit decs _) = void . sequenceA . map toRustVisitExt $ decs
toRustVisitExt :: (Show a) => CExternalDeclaration a -> IO ()
toRustVisitExt (CDeclExt s) = toRustVisitDecl s
toRustVisitExt _ = pure ()
getIdent :: (Show a) => CDeclarator a -> String
getIdent (CDeclr Nothing _ _ _ _) = ""
getIdent (CDeclr (Just (Ident s _ _)) _ _ _ _) = s
toRustVisitDecl :: (Show a) => CDeclaration a -> IO ()
toRustVisitDecl (CDecl specs ((Just decl, _, _):[]) _) = do
putStrLn (take 10 $ repeat '=')
toRustVisitDeclSpec (getIdent decl) specs
putStrLn (take 10 $ repeat '=')
toRustVisitDecl _ = pure ()
toRustVisitDeclSpec :: (Show a) => String -> [CDeclarationSpecifier a] -> IO ()
toRustVisitDeclSpec typenam ((CStorageSpec (CTypedef _)) : (CTypeSpec (CSUType body _)) : []) = do
putStrLn ("struct " ++ typenam ++ " {")
toRustStructBody body
putStrLn "}"
toRustVisitDeclSpec _ _ = pure ()
toRustStructBody :: (Show a) => CStructureUnion a -> IO ()
toRustStructBody (CStruct CStructTag _ (Just mattrs) _ _) = void . sequenceA . fmap toRustStructMember $ mattrs
toRustStructBody _ = pure ()
toRustStructMember :: (Show a) => CDeclaration a -> IO ()
toRustStructMember (CDecl ((CTypeSpec (CCharType _)):[]) (((Just (CDeclr (Just (Ident name _ _)) (CArrDeclr _ (CArrSize False (CConst (CIntConst n _))) _:[]) _ _ _)), _, _):[]) _) =
putStr (replicate 4 ' ') >> putStr (snakecase name) >> putStr ": ArrayWithSize<U" >> putStr (show n) >> putStrLn ">,"
toRustStructMember (CDecl typespecs (((Just (CDeclr (Just (Ident name _ _)) _ _ _ _)), _, _):[]) _) =
putStr (replicate 4 ' ') >> putStr (snakecase name) >> putStr ": " >> printTypeSpec typespecs >> putStrLn ","
where printTypeSpec ((CTypeSpec (CLongType _)):(CTypeSpec (CLongType _)):[]) = putStr "i64"
printTypeSpec ((CTypeSpec (CIntType _)):[]) = putStr "i32"
printTypeSpec ((CTypeSpec (CShortType _)):[]) = putStr "i16"
printTypeSpec ((CTypeSpec (CCharType _)):[]) = putStr "u8"
printTypeSpec ((CTypeSpec (CTypeDef (Ident name _ _) _)):[]) = putStr name
printTypeSpec t = putStr "unknown type >" >> putStr (show t) >> putStr "<"
toRustStructMember _ = undefined
-- the casing library is great: https://hackage.haskell.org/package/casing-0.1.2.1
snakecase :: String -> String
snakecase = toQuietSnake . fromHumps . dropWhile isLower
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment