module Output where import Types import Translate (prettyCode, mkInitVals, codeString, mkAllocs, varNames, mkMember) import Data.Maybe (mapMaybe, catMaybes) mkImplementation :: [Maybe GraphicsElement] -> String -> IO () mkImplementation graphics file = let cl = mapMaybe codeString (catMaybes graphics) code = foldl (++) "" cl con = imFileStart file graphics ++ drawRect code ++ imDealloc (catMaybes graphics) ++ imFileEnd in writeFile (file++".m") (fileHeader++"\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.3.2.\n\ \\tPlease feel free to report any bugs. */\n\n\n" imInit :: [Maybe GraphicsElement] -> String imInit ge = let b = mapMaybe mkInitVals (catMaybes ge) a = foldl (++) "" (mapMaybe mkAllocs (catMaybes ge)) in a ++ prettyCode b imFileStart :: String -> [Maybe GraphicsElement] -> String imFileStart file graphics= "#include \""++file++".h\"\n\n\ \@implementation "++file++"\n\n"++ imSynths (mapMaybe varNames (catMaybes graphics)) ++"\n\n\ \- (id)initWithCoder:(NSCoder*) aDecoder {\ \\n\tself = [super initWithCoder:aDecoder];\ \\n\t if (self) {\ \\n\t\t // init code.\n\ \\t\t self.scaleFactor = 1;\n"++ imInit graphics ++ "\n\t}\ \\n\treturn self;\ \\n}\n\n" imDealloc :: [GraphicsElement] -> String imDealloc xs = let vn = mapMaybe varNames xs rl = foldl (\x y -> x++"\t["++y++" release];\n") "" vn in "-(void) dealloc {\n"++rl++ "\t[super dealloc];\n}" imFileEnd :: String imFileEnd = "\n\n@end\n" drawRect :: String -> String drawRect c = "- (void) drawRect: (CGRect) rect {\n\ \\tCGContextRef context = UIGraphicsGetCurrentContext();\n\ \\tCGContextScaleCTM(context, scaleFactor, scaleFactor);\n" ++ c ++ "}\n\n" imSynths :: [String] -> String imSynths = foldr (\y x -> x++"@synthesize "++y++";\n") "@synthesize scaleFactor;\n" hFileStart :: String -> String hFileStart file = fileHeader++ "#import \"svg2q.h\";\n\ \#import ;\n\n\ \@interface "++file++" : UIView {\n" hFileEnd :: String hFileEnd = "\n\n@end\n" hProperties :: [Maybe GraphicsElement] -> String hProperties xs = let m = (mapMaybe mkMember (catMaybes xs)) pl = map hProp m in foldl (++) "\t@property(nonatomic, assign)\tfloat scaleFactor;\n" pl hProp :: String -> String hProp s = "\t@property(nonatomic, retain) "++s hMem :: String -> String hMem x= "\t"++x++";\n" hMembers :: [Maybe GraphicsElement] -> String hMembers xs = foldl (++) "float scaleFactor;\n" (mapMaybe mkMember (catMaybes xs)) imScale :: String imScale = "- (void) redraw {\ \\n\t[self setNeedsDisplay];\ \\n}\n\n"