nri-prelude-0.2.0.0: A Prelude inspired by the Elm programming language

Safe HaskellNone
LanguageHaskell2010

Task

Contents

Description

Tasks make it easy to describe asynchronous operations that may fail, like HTTP requests or writing to a database.

Synopsis

Tasks

data Task x a Source #

Here are some common tasks:

Instances
Monad (Task a) Source # 
Instance details

Defined in Platform.Internal

Methods

(>>=) :: Task a a0 -> (a0 -> Task a b) -> Task a b #

(>>) :: Task a a0 -> Task a b -> Task a b #

return :: a0 -> Task a a0 #

fail :: String -> Task a a0 #

Functor (Task x) Source # 
Instance details

Defined in Platform.Internal

Methods

fmap :: (a -> b) -> Task x a -> Task x b #

(<$) :: a -> Task x b -> Task x a #

Applicative (Task a) Source # 
Instance details

Defined in Platform.Internal

Methods

pure :: a0 -> Task a a0 #

(<*>) :: Task a (a0 -> b) -> Task a a0 -> Task a b #

liftA2 :: (a0 -> b -> c) -> Task a a0 -> Task a b -> Task a c #

(*>) :: Task a a0 -> Task a b -> Task a b #

(<*) :: Task a a0 -> Task a b -> Task a a0 #

perform :: LogHandler -> Task Never a -> IO a Source #

Just having a Task does not mean it is done. We must perform the task:

import qualified Task
import qualified Platform

main :: IO
main =
  Task.perform Platform.silentHandler Time.now

attempt :: LogHandler -> Task x a -> IO (Result x a) Source #

This is very similar to perform except it can handle failures!

Chains

andThen :: (a -> Task x b) -> Task x a -> Task x b Source #

Chain together a task and a callback. The first task will run, and if it is successful, you give the result to the callback resulting in another task. This task then gets run. We could use this to make a task that resolves an hour from now:

import qualified Time
import qualified Process

timeInOneHour : Task x Time.Posix
timeInOneHour =
  Process.sleep (60 * 60 * 1000)
    |> andThen (\_ -> Time.now)

First the process sleeps for an hour and then it tells us what time it is.

succeed :: a -> Task x a Source #

A task that succeeds immediately when run. It is usually used with andThen. You can use it like map if you want:

import qualified Time

timeInMillis : Task x Int
timeInMillis =
  Time.now
    |> andThen (\t -> succeed (Time.posixToMillis t))

fail :: x -> Task x a Source #

A task that fails immediately when run. Like with succeed, this can be used with andThen to check on the outcome of another task.

type Error = NotFound

notFound : Task Error a
notFound =
  fail NotFound

sequence :: List (Task x a) -> Task x (List a) Source #

Start with a list of tasks, and turn them into a single task that returns a list. The tasks will be run in order one-by-one and if any task fails the whole sequence fails.

sequence [ succeed 1, succeed 2 ] == succeed [ 1, 2 ]

Maps

map :: (a -> b) -> Task x a -> Task x b Source #

Transform a task. Maybe you want to figure out what time it will be in one hour:

import Task exposing (Task)
import qualified Time

timeInOneHour : Task x Time.Posix
timeInOneHour =
  Task.map addAnHour Time.now

addAnHour : Time.Posix -> Time.Posix
addAnHour time =
  Time.millisToPosix (Time.posixToMillis time + 60 * 60 * 1000)

map2 :: (a -> b -> result) -> Task x a -> Task x b -> Task x result Source #

Put the results of two tasks together. For example, if we wanted to know the current month, we could ask:

 import qualified Task exposing (Task)
 import qualified Time

 getMonth : Task x Int
 getMonth =
   Task.map2 Time.toMonth Time.here Time.now

Note: Say we were doing HTTP requests instead. map2 does each task in order, so it would try the first request and only continue after it succeeds. If it fails, the whole thing fails!

map3 :: (a -> b -> c -> result) -> Task x a -> Task x b -> Task x c -> Task x result Source #

 

map4 :: (a -> b -> c -> d -> result) -> Task x a -> Task x b -> Task x c -> Task x d -> Task x result Source #

 

map5 :: (a -> b -> c -> d -> e -> result) -> Task x a -> Task x b -> Task x c -> Task x d -> Task x e -> Task x result Source #

 

map6 :: (a -> b -> c -> d -> e -> f -> result) -> Task x a -> Task x b -> Task x c -> Task x d -> Task x e -> Task x f -> Task x result Source #

 

Errors

onError :: (x -> Task y a) -> Task x a -> Task y a Source #

Recover from a failure in a task. If the given task fails, we use the callback to recover.

fail "file not found"
  |> onError (\msg -> succeed 42)
  -- succeed 42

succeed 9
  |> onError (\msg -> succeed 42)
  -- succeed 9

mapError :: (x -> y) -> Task x a -> Task y a Source #

Transform the error value. This can be useful if you need a bunch of error types to match up.

type Error
  = Http Http.Error
  | WebGL WebGL.Error

getResources : Task Error Resource
getResources =
  sequence
    [ mapError Http serverTask
    , mapError WebGL textureTask
    ]

Special (custom helpers not found in Elm)

timeout :: Float -> err -> Task err a -> Task err a Source #

Run a task. If it doesn't complete within the given number of milliseconds then fail it with the provided error.

Process.sleep 2000
  |> timeout 1000 "overslept!"

parallel :: List (Task x a) -> Task x (List a) Source #

Start with a list of tasks, and turn them into a single task that returns a list. The tasks will be run in parallel and if any task fails the whole parallel call fails.

parallel [ succeed 1, succeed 2 ] == succeed [ 1, 2 ]