Skip to content

Commit

Permalink
Some cleanups
Browse files Browse the repository at this point in the history
  • Loading branch information
jacobstanley committed Aug 24, 2011
1 parent 5a733b4 commit 54587cf
Showing 1 changed file with 10 additions and 21 deletions.
31 changes: 10 additions & 21 deletions mkstdcall.hs
@@ -1,20 +1,17 @@
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeSynonymInstances #-}

import Data.Generics
import Control.Monad (guard)
import Control.Applicative ((<$>))
import Language.C
import Language.C.Data.Ident (Ident(..))
import Language.C.System.GCC
import Data.Maybe (catMaybes, listToMaybe, mapMaybe)
import Data.List (isPrefixOf)

-- OverloadedStrings
import GHC.Exts (IsString(..))

import Debug.Trace (trace)
------------------------------------------------------------------------

main :: IO ()
main = do
Expand All @@ -33,10 +30,7 @@ main = do

------------------------------------------------------------------------

decl :: CExtDecl -> Maybe CDecl
decl (CDeclExt x) = Just x
decl _ = Nothing

-- | Wraps any function declarations with stdcall function definitions
wrapWithStdcall :: CExtDecl -> CExtDecl
wrapWithStdcall orig@(CDeclExt d) = maybe orig CFDefExt (wrapWithStdcallD d)
wrapWithStdcall x = x
Expand Down Expand Up @@ -92,16 +86,10 @@ call' :: CExpr -> [CExpr] -> CExpr
call' fun args = CCall fun args undefNode

var :: String -> CExpr
var name = CVar (ident name) undefNode
var nam = CVar (ident nam) undefNode

ident :: String -> Ident
ident name = Ident name 0 undefNode

instance IsString CExpr where
fromString = var

instance IsString Ident where
fromString = ident
ident nam = Ident nam 0 undefNode

------------------------------------------------------------------------
-- Exported Functions / Calling Conventions
Expand Down Expand Up @@ -158,10 +146,10 @@ class Rename a where
rename :: (String -> String) -> a -> a

instance Rename Ident where
rename f (Ident name h n) = Ident (f name) h n
rename f (Ident nam h n) = Ident (f nam) h n

instance Rename CDeclr where
rename f (CDeclr ident d t a n) = CDeclr (rename f <$> ident) d t a n
rename f (CDeclr idnt d t a n) = CDeclr (rename f <$> idnt) d t a n

instance Rename CDecl where
rename f (CDecl ss ds n) = CDecl ss (map go ds) n
Expand All @@ -179,14 +167,15 @@ instance Rename CExtDecl where
------------------------------------------------------------------------
-- Scrap Your Boilerplat

gany :: forall a b. (Typeable a, Data b) => (a -> Bool) -> b -> Bool
gany p = everything (||) (False `mkQ` p)

------------------------------------------------------------------------
-- Pretty Printing

parseFile :: String -> IO CTranslUnit
parseFile name = do
result <- parseCFile (newGCC "gcc") Nothing [] name
parseFile path = do
result <- parseCFile (newGCC "gcc") Nothing [] path
case result of
Left msg -> error (show msg)
Right ast -> return ast
Expand Down

0 comments on commit 54587cf

Please sign in to comment.