Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Using "bind" with an async function

Let's say I have some function that returns Async<Result<string>>:

let getData id = async {
   return Ok (string id)
}

Now the input to this function is the result of another function that returns Result<int>.

I'm struggling on how to compose the 2 together with Result.bind inside the async CE.

For example:

let main = async {
    let id = Ok 123
    let! x = id |> Result.bind getData

    return x
}

This doesn't work, I get the error:

error FS0001: Type mismatch. Expecting a
    'Result<int,'a> -> Async<'b>'    
but given a
    'Result<int,'a> -> Result<'c,'a>'   

Or if I don't use let! I get and just use let

error FS0001: Type mismatch. Expecting a
    'int -> Result<'a,'b>'    
but given a
    'int -> Async<Result<string,'c>>

I've seen some answers that say don't use Result<'a> and just let the Async exception handling do the hard work, but I face the same problems with Option<'a> and Option.bind.

I know I could use Option.isSome/isNone and/or write my own isOk/isError functions for Result, but I feel I shouldn't have to.

Any ideas on the best way to compose something like this together?

like image 911
DaveShaw Avatar asked Dec 24 '22 01:12

DaveShaw


1 Answers

The problem is Result.bind can not be used with getData because the signatures do not match. Result.bind expects a function that produces a Result<> but getData produces an Async<Result<_,_>>. You need a bind for Async<Result<_,_>>.

Define an AsyncResult.bind function for Async<Result<_,_>> like this:

module AsyncResult =
    let bind  fRA  vRA = async { 
        let! vR       = vRA
        match   vR with
        | Ok    v -> return! fRA v
        | Error m -> return  Error m 
    }

now you can compose your getData function with a function that returns a Result like this:

let composed p = resultFunction p |> async.Return |> AsyncResult.bind getData

If you define a CE for AsyncResult then you can compose it like this:

let composed2 p =  asyncResult {
    let! id = resultFunction p |> async.Return
    return! getData id
}

Here is a full implementation I use for handling Async<Result<>>.

First some useful definitions for Result:

module Result =
    open Result

    let rtn                          = Ok
    let toOption                   r = r   |> function Ok v -> Some v |       _ -> None
    let defaultWith              f r = r   |> function Ok v ->      v | Error e -> f e
    let defaultValue             d r = r   |> function Ok v ->      v | Error _ -> d
    let failIfTrue               m v = if     v then m |> Error  else Ok () 
    let failIfFalse              m v = if not v then m |> Error  else Ok () 
    let iter                  fE f r = r   |> map f |> defaultWith fE : unit
    let get                        r = r   |>          defaultWith (string >> failwith)
    let ofOption              f   vO = vO  |> Option.map Ok           |> Option.defaultWith (f >> Error)
    let insertO                  vRO = vRO |> Option.map(map Some)    |> Option.defaultWith(fun () -> Ok None)
    let absorbO               f  vOR = vOR |> bind (ofOption f)

... and for Async:

module Async =
    let inline rtn   v    = async.Return v
    let inline bind  f vA = async.Bind(  vA, f)
    let inline map   f    = bind (f >> rtn)
    let inline iterS (f: 'a->unit) = map f >> Async.RunSynchronously
    let inline iterA f             = map f >> Async.Start

... and now for AsyncResult:

type AsyncResult<'v, 'm> = Async<Result<'v, 'm>>

module AsyncResult =
    let mapError fE v  = v |> Async.map (Result.mapError fE)

    let rtn        v   = async.Return(Ok v  )
    let rtnR       vR  = async.Return    vR
    let iterS fE f vRA = Async.iterS (Result.iter fE f) vRA
    let iterA fE f vRA = Async.iterA (Result.iter fE f) vRA
    let bind  fRA  vRA = async { 
        let! vR       = vRA
        match   vR with
        | Ok    v -> return! fRA v
        | Error m -> return  Error m 
    }
    let inline map  f m = bind  (f >> rtn) m            
    let rec whileLoop cond fRA =
        if   cond () 
        then fRA  () |> bind (fun () -> whileLoop cond fRA)
        else rtn  ()
    let (>>=)                              v f = bind f v
    let rec    traverseSeq     f            sq = let folder head tail = f head >>= (fun h -> tail >>= (fun t -> List.Cons(h,t) |> rtn))
                                                 Array.foldBack folder (Seq.toArray sq) (rtn List.empty) |> map Seq.ofList
    let inline sequenceSeq                  sq = traverseSeq id sq
    let insertO   vRAO                         = vRAO |> Option.map(map Some) |> Option.defaultWith(fun () -> rtn None)
    let insertR ( vRAR:Result<_,_>)            = vRAR |> function | Error m -> rtn (Error m) | Ok v -> map Ok v
    let absorbR   vRRA                         = vRRA |> Async.map (Result.bind    id)
    let absorbO f vORA                         = vORA |> Async.map (Result.absorbO  f)

Finally, a builder for the CE asyncResult { ... }

type AsyncResultBuilder() =
    member __.ReturnFrom vRA        : Async<Result<'v  , 'm>> =                       vRA
    member __.ReturnFrom vR         : Async<Result<'v  , 'm>> = AsyncResult.rtnR      vR
    member __.Return     v          : Async<Result<'v  , 'm>> = AsyncResult.rtn       v  
    member __.Zero       ()         : Async<Result<unit, 'm>> = AsyncResult.rtn       () 
    member __.Bind      (vRA,  fRA) : Async<Result<'b  , 'm>> = AsyncResult.bind fRA  vRA
    member __.Bind      (vR ,  fRA) : Async<Result<'b  , 'm>> = AsyncResult.bind fRA (vR  |> AsyncResult.rtnR)
    member __.Combine   (vRA,  fRA) : Async<Result<'b  , 'm>> = AsyncResult.bind fRA  vRA
    member __.Combine   (vR ,  fRA) : Async<Result<'b  , 'm>> = AsyncResult.bind fRA (vR  |> AsyncResult.rtnR)
    member __.Delay            fRA                            = fRA
    member __.Run              fRA                            = AsyncResult.rtn () |> AsyncResult.bind fRA
    member __.TryWith   (fRA , hnd) : Async<Result<'a  , 'm>> = async { try return! fRA() with e -> return! hnd e  }
    member __.TryFinally(fRA , fn ) : Async<Result<'a  , 'm>> = async { try return! fRA() finally   fn  () }
    member __.Using(resource , fRA) : Async<Result<'a  , 'm>> = async.Using(resource,       fRA)
    member __.While   (guard , fRA) : Async<Result<unit, 'a>> = AsyncResult.whileLoop guard fRA 
    member th.For  (s: 'a seq, fRA) : Async<Result<unit, 'b>> = th.Using(s.GetEnumerator (), fun enum ->
                                                                    th.While(enum.MoveNext,
                                                                      th.Delay(fun () -> fRA enum.Current)))
let asyncResult = AsyncResultBuilder()


[<AutoOpen>]
module Extensions =      
    type AsyncResultBuilder with
      member __.ReturnFrom (vA: Async<'a>     ) : Async<Result<'a, 'b>> =                       Async.map Ok vA
      member __.Bind       (vA: Async<'a>, fRA) : Async<Result<'b, 'c>> = AsyncResult.bind fRA (Async.map Ok vA)
      member __.Combine    (vA: Async<'a>, fRA) : Async<Result<'b, 'c>> = AsyncResult.bind fRA (Async.map Ok vA)
like image 144
AMieres Avatar answered Jan 05 '23 03:01

AMieres