Does F# documentation have a way to search for functions by their types?

后端 未结 3 1080
长情又很酷
长情又很酷 2020-12-30 01:24

Say I want to know if F# has a library function of type

(\'T -> bool) -> \'T list -> int

ie, something that counts how many items

3条回答
  •  不知归路
    2020-12-30 01:44

    I don't know of any such tool. However it might be a fun exercise to write one using System.Reflection (or even better, the Metadata library in the PowerPack), so that you could take equivalence modulo type variable names, etc. into account.

    EDIT - I was right - it was a fun exercise. What follows has a lot of warts, but isn't too bad for ~150 lines of code. Hopefully this will be enough to get someone started who wants to work on a real tool. It doesn't do anything advanced like checking for functions with reordered parameters, and the Metadata library is a bit picky about using fully qualified names so you need to be a bit careful. To answer the question in your original post, I executed

    find "('a -> Microsoft.FSharp.Core.bool) -> Microsoft.FSharp.Collections.list`1<'a> -> Microsoft.FSharp.Core.int" 
    

    and got the following list of candidates:

    Microsoft.FSharp.Core.Operators.( + )
    Microsoft.FSharp.Core.Operators.( - )
    Microsoft.FSharp.Core.Operators.( * )
    Microsoft.FSharp.Core.Operators.( / )
    Microsoft.FSharp.Core.Operators.( % )
    Microsoft.FSharp.Core.Operators.sqrt
    Microsoft.FSharp.Core.LanguagePrimitives.EnumOfValue
    Microsoft.FSharp.Core.LanguagePrimitives.EnumToValue
    Microsoft.FSharp.Core.LanguagePrimitives.AdditionDynamic
    Microsoft.FSharp.Core.LanguagePrimitives.CheckedAdditionDynamic
    Microsoft.FSharp.Core.LanguagePrimitives.MultiplyDynamic
    Microsoft.FSharp.Core.LanguagePrimitives.CheckedMultiplyDynamic
    Microsoft.FSharp.Core.LanguagePrimitives.GenericZero
    Microsoft.FSharp.Core.LanguagePrimitives.GenericOne
    Microsoft.FSharp.Collections.List.find
    Microsoft.FSharp.Collections.List.findIndex
    Microsoft.FSharp.Collections.List.maxBy
    Microsoft.FSharp.Collections.List.minBy
    

    Of these, only List.findIndex has exactly the generic type you're looking for, but with the right combination of type parameters so do the others (e.g. if 'a = int then List.find has the desired type). Unfortunately, constraints aren't taken into account in the search so the non-List functions can't actually match.

    Without further ado, here's the code I used - you'll need to add a reference to the FSharp.PowerPack.Metadata assembly to get it to work.

    open Microsoft.FSharp.Metadata
    open System.Text.RegularExpressions
    
    (* type parameters let us switch out representation if need be *)
    type Tag<'ty> = | Tuple | Arr | Ground of 'ty
    type Ty<'ty,'a> = Param of 'a | Complex of Tag<'ty> * Ty<'ty,'a> list
    
    (* Gets something stable from an FSharpEntity so that we can see if two are identical *)
    let rec getType (e:FSharpEntity) =
      if (e.IsAbbreviation) then
        getType e.AbbreviatedType.NamedEntity
      else
        e.ReflectionType
    
    (* FSharpType -> Ty *)
    let rec cvt (e:FSharpType) =
      if e.IsTuple then
        Complex(Tuple, e.GenericArguments |> Seq.map cvt |> List.ofSeq)
      elif e.IsFunction then
        Complex(Arr, e.GenericArguments |> Seq.map cvt |> List.ofSeq)
      elif e.IsGenericParameter then
        Param e.GenericParameter.Name
      else
        Complex(Ground(e.NamedEntity |> getType), e.GenericArguments |> Seq.map cvt |> List.ofSeq)
    
    (* substitute type for variable within another type *)
    let rec subst v t = function
    | Complex(tag,l) -> Complex(tag, l |> List.map (subst v t))
    | Param i when i = v -> t
    | Param j -> Param j
    
    (* get type variables used in a type *)
    let rec usedVars = function
    | Param i -> Set.singleton i
    | Complex(tag, l) -> Set.unionMany (List.map usedVars l)
    
    (* Find most general unifier (if any) for two types *)
    let mgu t1 t2 =
      let rec mgu subs = function
      | [] -> Some subs
      | (Complex(tag1,l1),Complex(tag2,l2))::rest ->
           if tag1 <> tag2 then
             None
           else
             let rec loop r = function
             | [],[] -> mgu subs r
             | [],_ | _,[] -> None
             | x::xs, y::ys -> loop ((x,y)::r) (xs,ys)
             loop rest (l1,l2)
      | (Param i, Param j)::rest when i = j -> mgu subs rest
      | ((Param i, x) | (x, Param i))::rest ->
           if (Set.contains i (usedVars x)) then
             None (* type would be infinite when unifying *)
           else
             mgu ((i,x)::subs) (rest |> List.map (fun (t1,t2) -> (subst i x t1, subst i x t2)))
      mgu [] [t1,t2]
    
    (* Active patterns for parsing - this is ugly... *)
    let (|StartsWith|_|) r s =
      let m = Regex.Match(s, r)
      if m.Success && m.Index = 0 then
        Some(m.Value, s.Substring(m.Length))
      else None
    
    let rec (|Any|) (|P|_|) = function
    | P(x,Any (|P|_|) (l,r)) -> x::l, r
    | s -> [],s
    
    let rec (|Any1|_|) (|P|_|) = function
    | P(x,Any (|P|_|) (l,r)) -> Some(x::l, r)
    | _ -> None
    
    let (|Seq|_|) (|P|_|) (|Q|_|) = function
    | P(x,Q(y,r)) -> Some((x,y),r)
    | _ -> None
    
    let (|Choice|_|) (|P|_|) (|Q|_|) = function
    | P(p) -> Some p
    | Q(p) -> Some p
    | _ -> None
    
    let (|Delimit|_|) s (|P|_|) = function
    | P(x,Any ((|Seq|_|) ((|StartsWith|_|) s) (|P|_|)) (l,r)) -> Some(x::(List.map snd l), r)
    | _ -> None
    
    let (|Delimit1|_|) s (|P|_|) = function
    | P(x,StartsWith s (_,Delimit s (|P|_|) (l,r))) -> Some(x::l, r)
    | _ -> None
    
    (* Basically a BNF grammar for types *)
    let rec (|TyE|_|) = function
    | ArrE(p) | TupleE(p) | AtomE(p) -> Some(p)
    | _ -> None
    and (|ArrE|_|) = function
    | Choice (|TupleE|_|) (|AtomE|_|) (dom,StartsWith "->" (_,TyE(rng,r))) -> Some(Complex(Arr,[dom;rng]), r)
    | _ -> None
    and (|TupleE|_|) = function
    | Delimit1 @"\*" (|AtomE|_|) (l,r) -> Some(Complex(Tuple,l), r)
    | _ -> None
    and (|AtomE|_|) = function
    | ParamE(x,r) | GroundE(x,r) | StartsWith @"\(" (_,TyE(x,StartsWith @"\)" (_,r))) -> Some(x,r)
    | _ -> None
    and (|ParamE|_|) = function
    | StartsWith "'[a-zA-Z0-9]+" (s,r) -> Some(Param s, r)
    | _ -> None
    and (|GroundE|_|) = function
    | StartsWith "[`.a-zA-Z0-9]+" (gnd, StartsWith "<" (_, Delimit "," (|TyE|_|) (l, StartsWith ">" (_,r)))) -> 
          let ty = FSharpAssembly.FSharpLibrary.GetEntity gnd |> getType
          Some(Complex(Ground(ty), l), r)
    | StartsWith "[`.a-zA-Z0-9]+" (gnd, r) ->
          let ty = FSharpAssembly.FSharpLibrary.GetEntity gnd |> getType
          Some(Complex(Ground(ty), []), r)
    | _ -> None
    
    (* parse a string into a type *)
    let parse (s:string) =
      (* remove whitespace before matching *)
      match s.Replace(" ","") with
      | TyE(ty,"") -> ty
      | _ -> failwith "Not a well-formed type"
    
    (* an infinite stream of possible variable names - for performing renaming *)
    let rec names = 
      let letters = ['a' .. 'z'] |> List.map string
      seq {
        yield! letters
        for n in names do
          for l in letters do
            yield n + l
      }
    
    (* finds entities in the F# library with the requested signature, modulo type parameter unification *)
    let find s =
      let ty = parse s
      let vars = usedVars ty
      seq {
        for e in FSharpAssembly.FSharpLibrary.Entities do
        for m in e.MembersOrValues do
          (* need try/catch to avoid error on weird types like "[]`1" *)
          match (try Some(cvt m.Type) with _ -> None) with
          | Some ty2 ->
            (* rename all type variables from the query to avoid incorrectly unifying with type variables in signatures *)
            let used = usedVars ty2
            let newVars = Seq.choose (fun v -> if Set.contains v used then None else Some(Param v)) names
            let varMap = Map.ofSeq (Seq.zip vars newVars)
            let ty = Map.fold (fun t v p -> subst v p t) ty varMap
            match mgu ty ty2 with
            | None -> ()
            | Some _ -> yield sprintf "%s.%s.%s" e.Namespace e.DisplayName m.DisplayName 
          | _ -> () }
    

提交回复
热议问题