module Output where import System.IO import Types import Translate (createCode, mkSynthList, prettyCode, mkPropTypes, mkInitVals) import Data.Maybe (mapMaybe, catMaybes) import Text.PrettyPrint.HughesPJ import Language.C.Pretty import Language.C.Syntax.AST import Debug.Trace(trace) import Helpers(split) import Data.List (isPrefixOf) mkImplementation :: [Maybe GraphicsElement] -> String -> IO () mkImplementation graphics file = let code = mapMaybe createCode (catMaybes graphics) con = imFileStart file graphics ++ drawRect (prettyCode code) ++ imFileEnd in do fun <- readFile "functions.c" writeFile (file++".m") (fileHeader++"\n\n"++fun++"\n\n"++con) mkHeader :: [Maybe GraphicsElement] -> String -> IO () mkHeader graphics file = writeFile (file++".h") (hFileStart file ++ hMembers graphics ++ "\n}\n" ++ hProperties graphics ++ hFileEnd) fileHeader :: String fileHeader = "/* This file is generated using svg2q v.0.2.\n\ \\tPlease feel free to report any bugs. */\n\n\n" imInit :: [Maybe GraphicsElement] -> String imInit ge = let a = mapMaybe mkInitVals (catMaybes ge) in prettyCode a imFileStart :: String -> [Maybe GraphicsElement] -> String imFileStart file graphics= "#include \""++file++".h\"\n\n\ \@implementation "++file++"\n\n"++ imSynths (mkSynthList graphics) ++"\n\n\ \- (id)initWithFrame:(CGRect) frame {\ \\n\tself = [super initWithFrame:frame];\ \\n\t if (self) {\ \\n\t\t // init code.\n"++ imInit graphics ++ "\n\t}\ \\n\treturn self;\ \\n}\n\n" imFileEnd :: String imFileEnd = imScale++"- (void) dealloc {\n\t\ \[super dealloc];\n\ \}\n\n\ \@end\n" drawRect :: String -> String drawRect c = "- (void) drawRect: (CGRect) rect {\n" ++ c ++ "}\n\n" imSynths :: [String] -> String imSynths = foldr (\y x -> x++"@synthesize "++y++";\n") "" hFileStart :: String -> String hFileStart file = fileHeader++ "#import ;\n\n\ \@interface "++file++" : UIView {\n" hFileEnd :: String hFileEnd = "\n\n@end\n" hProperties :: [Maybe GraphicsElement] -> String hProperties xs = let ge = catMaybes xs -- [GraphicsElement] sl = map mkPropTypes ge -- [[String]] sl' = concat sl -- [String] pl = map hProp sl' -- [String] in foldr (++) "" pl hProp :: String -> String hProp s | isPrefixOf "NS" s = "\t@property(nonatomic, retain) "++s++";\n" | otherwise = "\t@property(nonatomic, assign) "++s++";\n" hMem :: String -> String hMem x= "\t"++x++";\n" hMembers :: [Maybe GraphicsElement] -> String hMembers xs = let ge = catMaybes xs sl = map mkPropTypes ge sl' = concat sl pl = map hMem sl' in foldr (++) "" pl++"\n\n\n" imScale :: String imScale = "- (void) redraw {\ \\n\t[self drawRect: [self frame]];\ \\n}\n\n"