Skip to content

Commit

Permalink
Added command line options
Browse files Browse the repository at this point in the history
  • Loading branch information
geekrelief committed Oct 30, 2008
1 parent 9796ed4 commit 152a4cb
Show file tree
Hide file tree
Showing 6 changed files with 754 additions and 54 deletions.
21 changes: 21 additions & 0 deletions ActionhaXe/CLArgs.hs
@@ -0,0 +1,21 @@
module ActionhaXe.CLArgs (CLArg(..), Conf(..), clargs) where

import System.Console.ParseArgs
import Data.Generics

data CLArg = NumberToInt
| Input
| OutputDir
deriving (Eq, Ord, Show, Data, Typeable)

data Conf = Conf{ confArgs::Args CLArg, confInput::String, confOutput::String }
| ConfNone
deriving (Show, Data, Typeable)

initArg f desc = Arg{ argIndex = f, argAbbr = Nothing, argName = Nothing, argData = Nothing, argDesc = desc }

clargs =
[
(initArg NumberToInt "translate :Number to :Int (default :Float)"){ argAbbr = Just 'i', argName = Just "intnum" }
, (initArg Input "input to convert") { argData = argDataRequired "directory | file" ArgtypeString }
]
6 changes: 4 additions & 2 deletions ActionhaXe/Data.hs
Expand Up @@ -18,6 +18,8 @@
module ActionhaXe.Data where

import ActionhaXe.Lexer
import ActionhaXe.CLArgs

import Text.Parsec
import Text.Parsec.Prim

Expand Down Expand Up @@ -240,11 +242,11 @@ type AsDefTuple = (AsDef, AsDefInfo)
data AsStateEl = AsStateEl { sid::Int, scope::Map AsDef AsDefInfo }
deriving (Show, Data, Typeable)

data AsState = AsState{ filename::String, outfile::String, curId::Int, flags::Map String String, accessors::Map String (AsType, Bool, Bool), initMembers::[String], path::[Int], scopes::Tree AsStateEl }
data AsState = AsState{ conf::Conf, filename::String, outfile::String, curId::Int, flags::Map String String, accessors::Map String (AsType, Bool, Bool), initMembers::[String], path::[Int], scopes::Tree AsStateEl }
deriving (Show, Data, Typeable)

initState :: AsState
initState = AsState{ filename = "", outfile = "", curId = 0, path = [0], flags = Map.empty, accessors = Map.empty, initMembers = [], scopes = newScope 0}
initState = AsState{ conf = ConfNone, filename = "", outfile = "", curId = 0, path = [0], flags = Map.empty, accessors = Map.empty, initMembers = [], scopes = newScope 0}

getProperty name =
do x <- getState
Expand Down
79 changes: 49 additions & 30 deletions ActionhaXe/Translator.hs
Expand Up @@ -23,6 +23,9 @@ import ActionhaXe.Lexer
import ActionhaXe.Data
import ActionhaXe.Prim
import ActionhaXe.Parser
import ActionhaXe.CLArgs
import qualified System.Console.ParseArgs as PA

import Data.Map (Map)
import qualified Data.Map as Map
import Control.Monad.State
Expand Down Expand Up @@ -62,6 +65,9 @@ getMembers = do st <- get
put st{initMembers = []}
return ret

getCLArg f = do st <- get
return $ PA.gotArg (confArgs (conf st)) f

maybeEl f i = maybe "" (\m -> f m) i

cleanup s = subRegex (mkRegex "\\$") s "_S_"
Expand Down Expand Up @@ -94,10 +100,13 @@ classBlock (Block l bs r) = do
x <- get
let a = accessors x
let al = Map.toList a
let props = foldl (\str (k, (t, g, s)) -> str ++ showws l ++ "public var " ++ k ++ "("
++ (if g then "get"++ [toUpper $ head k] ++ tail k else "null") ++ ", "
++ (if s then "set"++ [toUpper $ head k] ++ tail k else "null")
++ ") : " ++ datatype t ++ ";") "" al
props <- foldlM (\str (k, (t, g, s)) -> do{ t' <- datatype t
; return $ str ++ showws l ++ "public var " ++ k ++ "("
++ (if g then "get"++ [toUpper $ head k] ++ tail k else "null") ++ ", "
++ (if s then "set"++ [toUpper $ head k] ++ tail k else "null")
++ ") : " ++ t' ++ ";"
}
) "" al
bi <- foldlM (\s b -> do{ x <- classBlockItem b; return $ s ++ x} ) "" bs
return $ showd l ++ props ++ showw l ++ bi ++ showb r

Expand Down Expand Up @@ -218,8 +227,9 @@ methodDecl (MethodDecl a f ac n s b) = do
accessor ac name s@(Signature l args r ret) t =
case ac of
Just x -> do{ a <- showArgs args
; t' <- datatypet t
; return $ showd x ++ [toUpper $ head $ showd name] ++ tail (showb name) ++ showb l ++ a ++ showd r ++ ":"
++ fst (datatypet t) ++ (case ret of { Just (c, t) -> snd (datatypet t); Nothing -> showw r})
++ fst t' ++ (case ret of { Just (c, t) -> snd t'; Nothing -> showw r})
}
Nothing -> do{ s' <- signature s; return $ showb name ++ s'}
accblock arg ac (Block l bs r) =
Expand All @@ -241,11 +251,12 @@ signatureArgs (Signature l args r ret) = do{ a <- showArgs args
}

rettype ret = case ret of
Just (c, t) -> showb c ++ datatype t
Nothing -> ""
Just (c, t) -> do{ t' <- datatype t; return $ showb c ++ t'}
Nothing -> return ""

signature (Signature l args r ret) = do{ a <- showArgs args
; return $ showb l ++ a ++ showb r ++ rettype ret
; ret' <- rettype ret
; return $ showb l ++ a ++ showb r ++ ret'
}

showArgs as = do{ as' <- mapM showArg as; return $ concat as'}
Expand Down Expand Up @@ -308,42 +319,50 @@ namespace ns = case ns of
Just x -> concat $ map (\n -> (case (showd n) of { "protected" -> "public"; _ -> showd n}) ++ showw n) x
Nothing -> ""

datatypet d = span (\c -> isAlphaNum c || c =='>' || c == '<') (datatype d)
datatypet d = do{ d' <- datatype d; return $ span (\c -> isAlphaNum c || c =='>' || c == '<') d'}

datatype :: AsType -> StateT AsState IO String
datatype d =
case d of
AsType n -> (case (showd n) of
"void" -> "Void"
"Boolean" -> "Bool"
"uint" -> "UInt"
"int" -> "Int"
"Number" -> "Number"
"String" -> "String"
"*" -> "Dynamic"
"Object" -> "Dynamic"
"Function"-> "Dynamic"
"Array" -> "Array<Dynamic>"
"XML" -> "XML"
"RegExp" -> "EReg"
) ++ showw n
AsTypeRest -> "Array<Dynamic>"
AsTypeUser n -> showb n

datatypeiM d Nothing = return $ datatype d
AsType n -> do d' <- (case (showd n) of
"void" -> return "Void"
"Boolean" -> return "Bool"
"uint" -> return "UInt"
"int" -> return "Int"
"Number" -> do ni <- getCLArg NumberToInt
if ni
then return "Int"
else return "Float"
"String" -> return "String"
"*" -> return "Dynamic"
"Object" -> return "Dynamic"
"Function"-> return "Dynamic"
"Array" -> return "Array<Dynamic>"
"XML" -> return "XML"
"RegExp" -> return "EReg"
)
return $ d' ++ showw n
AsTypeRest -> return "Array<Dynamic>"
AsTypeUser n -> return $ showb n

datatypeiM d Nothing = datatype d
datatypeiM d i =
case d of
AsType n -> do{ r <- case (showd n) of
"void" -> return "Void"
"Boolean" -> return "Bool"
"uint" -> return "UInt"
"int" -> return "Int"
"Number" -> do{ case i of
"Number" -> do case i of
Just (o, e) -> do{ if hasFloat e
then return "Float"
else return "Int"
}
Nothing -> return "Float"
}
Nothing -> do ni <- getCLArg NumberToInt
if ni
then return "Int"
else return "Float"

"String" -> return "String"
"*" -> return "Dynamic"
"Object" -> return "Dynamic"
Expand Down
12 changes: 6 additions & 6 deletions README
Expand Up @@ -2,20 +2,21 @@ as3tohaxe - An Actionscript 3 to haXe source file converter written in Haskell
Copyright (C) 2008 Don-Duong Quach

For more info check visit:
http://geekrelief.wordpress.com
http://groups.google.com/group/as3tohaxe
http://www.github.com/geekrelief/as3tohaxe
http://geekrelief.wordpress.com
Donations are appreciated!


-- Running --
Type 'as3tohaxe' and a directory or file to convert.
A directory named "hx_output" will be created in the current
directory if necessary. The supplied ".as" files will be
translated into haxe files and stored there. If the command
is run more than once, and pre-existing files will be skipped.
is run more than once, and pre-existing files will be overwritten.

-- Binary --
There is a binary 'as3tohaxe' included for Mac OSX 10.5.
Binaries for Mac OSX Leopard and Windows are available under
the Files section of the as3tohaxe google group.

-- Compiling --
Requirements
Expand All @@ -24,8 +25,7 @@ Requirements
- Cabal for parsec http://www.haskell.org/cabal/
- parsec 3 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/parsec

Running: ghc --make -XDeriveDataTypeable as3tohaxe.hs
will produce the binary 'as3tohaxe'
Compile with: ghc --make -XDeriveDataTypeable as3tohaxe.hs

-- License --
This program and its source is GPL licensed. Please read the LICENSE
Expand Down

0 comments on commit 152a4cb

Please sign in to comment.