tools/pas2c/Pas2C.hs
changeset 11840 24f309d75da8
parent 11398 c3a535886806
child 13306 806347b3c978
equal deleted inserted replaced
11839:4f44013e33d4 11840:24f309d75da8
     1 {-# LANGUAGE ScopedTypeVariables #-}
     1 {-# LANGUAGE ScopedTypeVariables #-}
     2 {-# LANGUAGE FlexibleContexts #-}
       
     3 module Pas2C where
     2 module Pas2C where
     4 
     3 
     5 import Text.PrettyPrint.HughesPJ
     4 import Text.PrettyPrint.HughesPJ
     6 import Data.Maybe
     5 import Data.Maybe
     7 import Data.Char
     6 import Data.Char
   296     mapM_ injectNamespace (Identifier "pas2cSystem" undefined : unitIds)
   295     mapM_ injectNamespace (Identifier "pas2cSystem" undefined : unitIds)
   297     mapM_ injectNamespace (Identifier "pas2cRedo" undefined : unitIds)
   296     mapM_ injectNamespace (Identifier "pas2cRedo" undefined : unitIds)
   298     mapM_ (id2C IOInsert . setBaseType BTUnit) unitIds
   297     mapM_ (id2C IOInsert . setBaseType BTUnit) unitIds
   299     return $ vcat . map (\i -> text $ "#include \"" ++ i ++ ".h\"") $ uses2List uses
   298     return $ vcat . map (\i -> text $ "#include \"" ++ i ++ ".h\"") $ uses2List uses
   300     where
   299     where
       
   300     injectNamespace :: Identifier -> State RenderState ()
   301     injectNamespace (Identifier i _) = do
   301     injectNamespace (Identifier i _) = do
   302         getNS <- gets (flip Map.lookup . namespaces)
   302         getNS <- gets (flip Map.lookup . namespaces)
   303         modify (\s -> s{currentScope = Map.unionWith (++) (fromMaybe Map.empty (getNS i)) $ currentScope s})
   303         modify (\s -> s{currentScope = Map.unionWith (++) (fromMaybe Map.empty (getNS i)) $ currentScope s})
   304 
   304 
   305 uses2List :: Uses -> [String]
   305 uses2List :: Uses -> [String]