Skip to content

Instantly share code, notes, and snippets.

@Woody88
Last active February 20, 2019 15:28
Show Gist options
  • Save Woody88/cc6724ea83bcae7a658855a9fe0f752e to your computer and use it in GitHub Desktop.
Save Woody88/cc6724ea83bcae7a658855a9fe0f752e to your computer and use it in GitHub Desktop.
exports._getVisualforce = function(just){
return function(nothing){
if (typeof Visualforce !== "undefined" &&
typeof Visualforce.remoting !== "undefined" &&
typeof Visualforce.remoting.Manager !== "undefined") {
return just(Visualforce);
}
else {
return nothing;
}
}
}
exports._callApex = function(Visualforce_,
fullyQualifiedApexMethodName,
apexMethodParameters,
apexCallConfiguration,
error,
success){
return function (onError, onSuccess) { // and callbacks
console.log('hello world2');
var responseHandler = function(result, event){
console.log(event);
if (event.status){
onSuccess(success(result));
}
else
onSuccess(error(event.message));
}
if (typeof Visualforce_ !== "undefined" &&
typeof Visualforce_.remoting !== "undefined" &&
typeof Visualforce_.remoting.Manager !== "undefined") {
var req = Visualforce_.remoting.Manager.invokeAction(fullyQualifiedApexMethodName,
apexMethodParameters,
responseHandler,
apexCallConfiguration);
}
else {
onSuccess(error("Could not find Visualforce Remote Object", ""));
}
// Return a canceler, which is just another Aff effect.
return function (cancelError, cancelerError, cancelerSuccess) {
console.log('hello world3');
req.cancel(); // cancel the request
cancelerSuccess(); // invoke the success callback for the canceler
};
}
}
module Apex.Internal where
import Prelude
import Control.Monad.Error.Class (class MonadError, throwError)
import Control.Monad.Trans.Class (lift)
import Data.Either (Either(..), either)
import Data.Function.Uncurried (Fn5, Fn6, runFn5, runFn6)
import Data.Maybe (Maybe(..))
import Effect.Aff (Aff)
import Effect.Aff.Class (class MonadAff, liftAff)
import Effect.Aff.Compat (EffectFnAff(..), fromEffectFnAff)
import Effect.Class (liftEffect)
import Effect.Uncurried (EffectFn5, EffectFn6, runEffectFn5, runEffectFn6)
import Foreign (Foreign)
import Unsafe.Coerce (unsafeCoerce)
type ErrorMsg = String
type ErrorTrace = String
data ApexError = ApexError ErrorMsg
instance showApexError :: Show ApexError where
show (ApexError m) = m
getVisualforce :: Maybe Visualforce
getVisualforce = _getVisualforce Just Nothing
foreign import data Visualforce :: Type
foreign import _getVisualforce :: forall a. (a -> Maybe a) -> Maybe a -> Maybe a
callApex :: forall c. Visualforce -> String -> Foreign -> { |c} -> Aff (Either String Foreign)
callApex vf s args c = do
effectFnAff <- liftEffect $ runEffectFn6 _callApex vf s args c Left Right
fromEffectFnAff effectFnAff
callApex_ :: forall c. Visualforce -> String -> Foreign -> { |c} -> Aff (Either ApexError Foreign)
callApex_ vf s args c = do
effectFnAff <- liftEffect $ runEffectFn6 _callApex vf s args c (Left <<< ApexError) Right
fromEffectFnAff effectFnAff
foreign import _callApex
:: forall conf e b. EffectFn6 Visualforce String Foreign conf (e -> b) (Foreign -> b) (EffectFnAff b)
module Apex.RemoteAction where
import Prelude
import Apex.Internal (ApexError(..), Visualforce, callApex, callApex_)
import Control.Monad.Error.Class (class MonadError, throwError)
import Control.Monad.Except (runExcept)
import Data.Bifunctor (lmap)
import Data.Either (either)
import Data.Symbol (class IsSymbol, SProxy(..), reflectSymbol)
import Effect.Aff.Class (class MonadAff, liftAff)
import Foreign.Class (class Decode, class Encode, decode, encode)
import Type.Proxy (Proxy)
import Unsafe.Coerce (unsafeCoerce)
foreign import kind RemoteActionMethod
data RemoteActionProxy (action :: RemoteActionMethod) = RemoteActionProxy
class (IsSymbol controller, Encode args, Decode result) <= RemoteAction action controller args result | action -> controller args result where
invokeAction :: forall m. MonadAff m => MonadError ApexError m => RemoteActionProxy action -> Visualforce -> args -> m result
-- I am not able to create default definition for class so I decided to create a generate instance... why can we not define default functions for classes...?
instance remoteAction :: RemoteAction action controller args result where
invokeAction _ vf args = do
ev <- liftAff $ callApex vf (reflectSymbol $ SProxy :: _ controller) (encode args) { escape: true}
f <- either throwError pure ev
lmap show $ runExcept $ decode f --- Stopped here because I noticed that it didnt make sense since I did not define what result is
--- so how can tell the compiler that the `e` from MonadThrow will
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment