module Haste.Object (
    JSObj, Type (..),
    (#), asString, asBool, asNumber, typeOf, lookupPath, toObject
  ) where
import Haste.Prim
import Haste.Foreign
type JSObj = Maybe JSAny
data Type = TUndefined | TNumber | TBoolean | TString | TFunction | TObject
  deriving (Show, Eq, Enum)
instance FromAny Type where
  fromAny = fmap toEnum . fromAny
class JSLookup a where
  infixl 4 #
  
  (#) :: a -> JSString -> IO JSObj
instance JSLookup JSObj where
  Just o # prop = look o prop
  _      # _    = return Nothing
instance JSLookup a => JSLookup (IO a) where
  o # prop = o >>= (# prop)
lookupPath :: JSObj -> [JSString] -> IO JSObj
lookupPath = ffi "(function(o,as){\
                   for(var i in as){\
                     o = o[as[i]];\
                     if(typeof o==='undefined'){return null;}\
                   }\
                   return o;})"
look :: JSAny -> JSString -> IO (Maybe JSAny)
look = ffi "(function(o,s){return o[s] === undefined ? null : o[s];})"
-- | Convert the object to a 'JSString'.
asString :: JSObj -> IO (Maybe JSString)
asString = maybe (return Nothing) go
  where
    go = ffi "(function(o){return String(o);})"
-- | Convert the object to a 'Bool'.
asBool :: JSObj -> IO (Maybe Bool)
asBool = maybe (return Nothing) go
  where
    go = ffi "(function(o){return Boolean(o);})"
-- | Convert the object to a 'Double'.
asNumber :: JSObj -> IO (Maybe Double)
asNumber = maybe (return Nothing) go
  where
    go = ffi "(function(o){return Number(o);})"
-- | Get the type of a JS object.
typeOf :: JSObj -> IO Type
typeOf = maybe (return TUndefined) go
  where
    go = ffi "(function(o){\
               switch(typeof o){\
                 case 'undefined': return 0;\
                 case 'number':    return 1;\
                 case 'boolean':   return 2;\
                 case 'string':    return 3;\
                 case 'function':  return 4;\
                 default:          return 5;\
               }\
             })"