module Data.Ruby.Marshal.RubyObject where
import Control.Applicative
import Prelude
import Control.Arrow ((***))
import Data.Ruby.Marshal.Encoding (RubyStringEncoding(..))
import qualified Data.ByteString as BS
import qualified Data.Map.Strict as DM
import qualified Data.Vector as V
data RubyObject
= RNil
| RBool !Bool
| RFixnum !Int
| RArray !(V.Vector RubyObject)
| RHash !(V.Vector (RubyObject, RubyObject))
| RIVar !(RubyObject, RubyStringEncoding)
| RString !BS.ByteString
| RFloat !Float
| RSymbol !BS.ByteString
| Unsupported
deriving (Eq, Ord, Show)
class Rubyable a where
toRuby :: a -> RubyObject
fromRuby :: RubyObject -> Maybe a
instance Rubyable RubyObject where
toRuby = id
fromRuby = Just
instance Rubyable () where
toRuby _ = RNil
fromRuby = \case
RNil -> Just ()
_ -> Nothing
instance Rubyable Bool where
toRuby = RBool
fromRuby = \case
RBool x -> Just x
_ -> Nothing
instance Rubyable Int where
toRuby = RFixnum
fromRuby = \case
RFixnum x -> Just x
_ -> Nothing
instance Rubyable a => Rubyable (V.Vector a) where
toRuby = RArray . V.map toRuby
fromRuby = \case
RArray x -> V.mapM fromRuby x
_ -> Nothing
instance (Rubyable a, Rubyable b) => Rubyable (V.Vector (a, b)) where
toRuby x = RHash $ V.map (toRuby *** toRuby) x
fromRuby = \case
RHash x -> V.mapM (\(k, v) -> (,) <$> fromRuby k <*> fromRuby v) x
_ -> Nothing
instance Rubyable BS.ByteString where
toRuby = RSymbol
fromRuby = \case
RSymbol x -> Just x
_ -> Nothing
instance Rubyable Float where
toRuby = RFloat
fromRuby = \case
RFloat x -> Just x
_ -> Nothing
instance Rubyable (BS.ByteString, RubyStringEncoding) where
toRuby (x, y) = RIVar (RString x, y)
fromRuby = \case
RIVar (RString x, y) -> Just (x, y)
_ -> Nothing
instance Rubyable a => Rubyable (Maybe a) where
toRuby = \case
Just x -> toRuby x
Nothing -> RNil
fromRuby = \case
RNil -> Just Nothing
x -> fromRuby x
instance Rubyable a => Rubyable [a] where
toRuby = toRuby . V.fromList
fromRuby x = V.toList <$> fromRuby x
instance (Rubyable a, Rubyable b) => Rubyable [(a, b)] where
toRuby = toRuby . V.fromList
fromRuby x = V.toList <$> fromRuby x
instance (Rubyable a, Rubyable b, Ord a) => Rubyable (DM.Map a b) where
toRuby = toRuby . DM.toList
fromRuby x = DM.fromList <$> fromRuby x