fpco-api-1.2.0.2: Simple interface to the FP Complete IDE API.

Safe HaskellNone

FP.API.Common

Synopsis

Documentation

class (Applicative m, MonadIO m, MonadBaseControl IO m, Applicative m', MonadIO m', MonadBaseControl IO m') => FpClient m m' | m -> m' whereSource

Methods

runCallback :: m' a -> m aSource

clientInfo :: m (ClientInfo m')Source

makeRequest :: (Data command, Show command) => Text -> Int -> ClientRoute -> command -> m (Maybe ByteString)Source

data Join k a b Source

Constructors

Join (Map k a) (Map k b) 

emptyJoin :: Ord k => Join k a bSource

joinAInput :: Ord k => Join k a b -> k -> a -> (Join k a b, Maybe b)Source

joinBInput :: Ord k => Join k a b -> k -> b -> (Join k a b, Maybe a)Source

jobCallback :: MonadIO m' => ProjectCallbacks m' -> JobId -> (Either Text Value -> m' ()) -> m' ()Source

ideCommand :: (Data command, Show command, Data a, Show a, FpClient m m') => (Returns' a -> command) -> m aSource

ideCommandFail :: forall command a m m'. (Data command, Show command, Data a, Show a, FpClient m m') => (Returns' a -> command) -> m ()Source

(for testing purposes)

makeFayAsyncCall :: forall command a m m'. (Data command, Show command, Data a, Show a, FpClient m m') => (Returns' a -> command) -> m (Either Text a)Source

fayCommand :: (Data command, Show command, Data a, FpClient m m') => (Returns' a -> command) -> m aSource

callFay :: (Data command, Show command, Data a, FpClient m m') => ClientRoute -> (Returns' a -> command) -> m aSource

makeFayCall :: (Data command, Show command, Data a, FpClient m m') => ClientRoute -> (Returns a -> command) -> m aSource

makeFayCall' :: (Data command, Show command, Data a, FpClient m m') => ClientRoute -> command -> m aSource

This is the same thing as makeFayCall, but with a less restrictive type that doens't enforce that the return type of the command is correct.

saveProfile :: FpClient m m' => Theme -> Int -> Bool -> m ()Source

hoogleSearchFail :: FpClient m m' => Bool -> Text -> Text -> m ()Source

putStdinFail :: FpClient m m' => ProcId -> Text -> m ()Source

gitDiffFail :: FpClient m m' => m ()Source

gitPullFail :: FpClient m m' => Text -> m ()Source

gitPushFail :: FpClient m m' => Text -> m ()Source

gitCommitFail :: FpClient m m' => Text -> m ()Source

setRootFail :: FpClient m m' => Text -> Text -> m ()Source

getGitHistoryFail :: FpClient m m' => Int -> Int -> m ()Source

runTargetFail :: FpClient m m' => Bool -> m ()Source

pingFail :: FpClient m m' => m ()Source

setPublicFail :: FpClient m m' => Bool -> m ()Source

setGitConfig :: FpClient m m' => Text -> Text -> m ()Source

ping :: FpClient m m' => m ()Source

deleteProject :: FpClient m m' => Text -> m ()Source

setPublic :: FpClient m m' => Bool -> m ()Source