module Sifflet.Foreign.Haskell
    (HsPretty(..)
    , Module(..)
    , ExportSpec(..)
    , ImportDecl(..)
    , Decl(..)
    , operatorTable
    )
where
import Data.List (intercalate)
import qualified Data.Map as M
import Sifflet.Language.Expr
import Sifflet.Text.Pretty
class HsPretty a where
    hsPretty :: a -> String
    hsPrettyList :: String -> String -> String -> [a] -> String
    hsPrettyList pre tween post xs =
        pre ++ intercalate tween (map hsPretty xs) ++ post
instance HsPretty Symbol where
    hsPretty = pretty
instance HsPretty Operator where
    hsPretty = pretty
data Module = Module {moduleName :: String
                     , moduleExports :: Maybe ExportSpec
                     , moduleImports :: ImportDecl
                     , moduleDecls :: [Decl]
                     }
            deriving (Eq, Show)
instance HsPretty Module where
    hsPretty m = 
        let pmod = "module " ++ moduleName m
            pexports = case moduleExports m of
                         Nothing -> ""
                         Just exports -> hsPretty exports
            pimports = hsPretty (moduleImports m)
            pdecls = sepLines2 (map hsPretty (moduleDecls m))
        in unlines [pmod ++ " where",
                    pexports,
                    pimports,
                    pdecls]
data ExportSpec = ExportSpec [String]
                  deriving (Eq, Show)
instance HsPretty ExportSpec where
    hsPretty (ExportSpec exports) = 
        "(" ++ sepCommaSp exports ++ ")"
data ImportDecl = ImportDecl [String]
                  deriving (Eq, Show)
instance HsPretty ImportDecl where
    hsPretty (ImportDecl modnames) = 
        let idecl modname = "import " ++ modname
        in unlines (map idecl modnames)
par :: String -> String
par s = "(" ++ s ++ ")"
data Decl = Decl {declIdent :: String
                 , declType :: Maybe [String]
                 , declParams :: [String]
                 , declExpr :: Expr
                 }
          deriving (Eq, Show)
instance HsPretty Decl where
    hsPretty decl =
        let ptypeDecl = "" 
            pparams = case declParams decl of
                        [] -> ""
                        params -> " " ++ sepSpace params
            pbody = hsPretty (declExpr decl)
        in ptypeDecl ++ 
           declIdent decl ++ pparams ++ " =\n" ++
           "    " ++ pbody
instance HsPretty Expr where
    hsPretty pexpr =
        case pexpr of
          EUndefined -> "undefined"
          EChar c -> show c
          ENumber n -> show n
          EBool b -> show b
          EString s -> show s
          ESymbol sym -> hsPretty sym
          EList xs -> hsPrettyList "[" ", " "]" xs
          EIf c a b -> 
              unwords ["if", hsPretty c, "then", hsPretty a, "else", hsPretty b]
          EGroup e -> par (hsPretty e)
          ECall fexpr argExprs -> 
              hsPretty fexpr ++ " " ++ hsPrettyList "" " " "" argExprs
          EOp op left right -> 
              unwords [hsPretty left, hsPretty op, hsPretty right]
operatorTable :: M.Map String Operator
operatorTable = 
    M.fromList (map (\ op -> (opName op, op)) 
                    [ Operator "*" 7 True GroupLtoR 
                    , Operator "+" 6 True GroupLtoR 
                    , Operator "-" 6 False GroupLtoR  
                    , Operator ":" 5 False GroupRtoL  
                    , Operator "==" 4 False GroupNone 
                    , Operator "/=" 4 False GroupNone 
                    , Operator ">" 4 False GroupNone 
                    , Operator ">=" 4 False GroupNone 
                    , Operator "<" 4 False GroupNone 
                    , Operator "<=" 4 False GroupNone 
                    ])