module RESTng.System.PersistableResource where import RESTng.Database.SQL (OrderDirection) import RESTng.RESTngMonad (RESTng, liftHDBC_0) import RESTng.System.Resource (Proxy) import RESTng.System.RelationalResource import RESTng.Utils(safeHead) class PersistableResource a where insert :: a -> RESTng a update :: a -> RESTng () delete :: Integer -> Proxy a -> RESTng () select :: [(String,String)] -> -- restrictions [(String,OrderDirection)] -> -- order by Proxy a -> RESTng [a] find :: Integer -> Proxy a -> RESTng (Maybe a) persistableFunctions :: ( a -> RESTng a, --insert a -> RESTng (), --update Integer -> Proxy a -> RESTng (), --delete [(String,String)] -> [(String,OrderDirection)] -> Proxy a -> RESTng [a], --select Integer -> Proxy a -> RESTng (Maybe a) --find ) persistableFunctions = (insert, update, delete, select, find) insert = ins where (ins,upd,del,sel,fin) = persistableFunctions update = upd where (ins,upd,del,sel,fin) = persistableFunctions delete = del where (ins,upd,del,sel,fin) = persistableFunctions select = sel where (ins,upd,del,sel,fin) = persistableFunctions find = fin where (ins,upd,del,sel,fin) = persistableFunctions persistableFromRelational :: RelationalResource a => ( a -> RESTng a, --insert a -> RESTng (), --update Integer -> Proxy a -> RESTng (), --delete [(String,String)] -> [(String,OrderDirection)] -> Proxy a -> RESTng [a], --select Integer -> Proxy a -> RESTng (Maybe a) --find ) persistableFromRelational = (r_insert, r_update, r_delete, r_select, r_find) r_insert :: RelationalResource a => a -> RESTng a r_insert a = liftHDBC_0 (dbInsert a) r_update :: RelationalResource a => a -> RESTng () r_update a = liftHDBC_0 (dbUpdate a) >> return () r_delete :: RelationalResource a => Integer -> Proxy a -> RESTng () r_delete k pa = liftHDBC_0 (dbDelete k pa) >> return () r_select :: RelationalResource a => [(String,String)] -> [(String,OrderDirection)] -> Proxy a -> RESTng [a] r_select filt ordBy pa = liftHDBC_0 (dbSelect filt ordBy pa) r_find :: RelationalResource a => Integer -> Proxy a -> RESTng (Maybe a) r_find k pa = liftHDBC_0 (dbSelectOne k pa) ---------------------------------------------------------- select01 :: PersistableResource a => [(String,String)] -> Proxy a -> RESTng (Maybe a) select01 crit p = select crit [] p >>= (return . safeHead)