composing many quotations into linq queries - linq

I'm working on a project in which I'm trying to use F# and Linq for UDF's and stored procs in an SQL server.
Part of that has been to statically define all the valid queries, the sorting criteria, and a means of scoring the results of the queries.
I've so far been fairly successful, but I'm running into serious difficulty composing sortBy expressions.
Here's the basic concept
let sorter =
let exprMap:Map<string,Quotations.Expr<seq<Product> -> seq<Product>>> =
Map.ofList
["ProductName",<# Seq.sortBy (fun prod -> prod.Name) #> ]
// .. more entries ..
let sortBuilder sortkeys =
Array.foldBack
(fun criteria acc -> <# %(exprMap.[criteria]) >> (%acc) #>)
sortkeys
<# Seq.map id #>
This ends up being used later in the query executor like so
let execQuery = fun (predicates,sorts,scorer) ->
<# seq { for prod in (%dc).Products do
if (%predicates) prod then yield prod }
|> (%sorts)
|> (%scorer) #>
Using these basic outlines, everything works as long as I don't use (%sorts). Each time I pass that in, I get not recognized in F# to Linq translator. I've tried a number of different attempts at using combinators, but I have the sense I'm missing something. If I stub out the sorter function with the following
<# Seq.sortBy (fun prod -> prod.Name) |> Seq.sortBy (fun prod -> prod.Style) #>
It works as expected. However using a combinator like this:
let (|>*) = fun f g -> <# fun c -> ((%f) c) |> (%g) #>
does not..
Any ideas?

Unfortunately, I don't have any good answer to this question.
I'm afraid that the F# LINQ translator is currently very sensitive to the structure of the query. Using composition, you should be able to get the same quotation you get if you write it by hand, so you may need to generate exactly the same thing that worked if written by hand.
For example with your sorter, you may need something like (I didn't try it, but I think this should produce exactly the same quotation as the usual code that works):
let (|>*) f g = fun c -> <# (%c) |> (%f) |> (%g) #>
<# seq { for prod in (%dc).Products do
if (%predicates) prod then yield prod } #> |>
( <# Seq.sortBy (fun prod -> prod.Name) #> |>*
<# Seq.sortBy (fun prod -> prod.Style) #> )
The problem is that if you include lambda functions in the quotation, the F# translator needs to deal with them - probably by partially evaluating them (because otherwise the LINQ to SQL translator would fail). There are quite a few tricky cases in this...
However, the F# team has been doing some improvements in this area recently. I think the best thing to do would be to find a simple repro case and send it to fsbugs at microsoft dot com. PowerPack releases are not that "sensitive" so you may be able to get the source code with the recent changes if you ask and offer help with testing (but no promises).

Related

Haskell debugging an arbitrary lambda expression

I have a set of lambda expressions which I'm passing to other lambdas. All lambdas rely only on their arguments, they don't call any outside functions. Of course, sometimes it gets quite confusing and I'll pass an function with the incorrect number of arguments to another, creating a GHCi exception.
I want to make a debug function which will take an arbitrary lambda expression (with an unknown number of arguments) and return a string based on the structure and function of the lambda.
For example, say I have the following lambda expressions:
i = \x -> x
k = \x y -> x
s = \x y z -> x z (y z)
debug (s k) should return "\a b -> b"
debug (s s k) should return "\a b -> a b a" (if I simplified that correctly)
debug s should return "\a b c -> a c (b c)"
What would be a good way of doing this?
I think the way to do this would be to define a small lambda calculus DSL in Haskell (or use an existing implementation). This way, instead of using the native Haskell formulation, you would write something like
k = Lam "x" (Lam "y" (App (Var "x") (Var "y")))
s = Lam "x" (Lam "y" (Lam "z" (App (App (Var "x") (Var "z")
(App (Var "y") (Var "z"))))
and similarly for s and i. You would then write/use an evaluation function so that you could write
debug e = eval e
debug (App s k)
which would give you the final form in your own syntax. Additionally you would need a sort of interpreter to convert your DSL syntax to Haskell, so that you can actually use the functions in your code.
Implementing this does seem like quite a lot of (tricky) work, and it's probably not exactly what you had in mind (especially if you need the evaluation for typed syntax), but I'm sure it would be a great learning experience. A good reference would be chapter 6 of "Write you a Haskell". Using an existing implementation would be a lot easier (but less fun :)).
If this is merely for debugging purposes you might benefit from looking at the core syntax ghc compiles to. See chapter 25 of Real world Haskell, the ghc flag to use is -ddump-simpl. But this would mean looking at generated code rather than generating a representation inside your program. I'm also not sure to what extent you would be able to identify specific functions in the Core code easily (I have no experience with this so YMMV).
It would of course be pretty cool if using show on functions would give the kind of output you describe but there are probably very good reasons functions are not an instance of Show (I wouldn't be able to tell you).
You can actually achieve that by utilising pretty-printing from Template Haskell, which comes with GHC out of the box.
First, the formatting function should be defined in separate module (that's a TH restriction):
module LambdaPrint where
import Control.Monad
import Language.Haskell.TH.Ppr
import Language.Haskell.TH.Syntax
showDef :: Name -> Q Exp
showDef = liftM (LitE . StringL . pprint) . reify
Then use it:
{-# LANGUAGE TemplateHaskell #-}
import LambdaPrint
y :: a -> a
y = \a -> a
$(return []) --workaround for GHC 7.8+
test = $(showDef 'y)
The result is more or less readable, not counting fully qualified names:
*Main> test
"Main.y :: forall a_0 . a_0 -> a_0"
Few words about what's going on. showDef is a macro function which reifies the definition of some name from the environment and pretty-prints it in a string literal expression. To use it, you need to quote the name of the lambda (using ') and splice the result (which is a quoted string expression) into some expression (using $(...)).

When generalizing monad, performance drops nearly 50%

I have code that does some parsing of files according to specified rules. The whole parsing takes place in a monad that is a stack of ReaderT/STTrans/ErrorT.
type RunningRule s a = ReaderT (STRef s LocalVarMap) (STT s (ErrorT String Identity)) a
Because it would be handy to run some IO in the code (e.g. to query external databases), I thought I would generalize the parsing, so that it could run both in Identity or IO base monad, depending on the functionality I would desire. This changed the signature to:
type RunningRule s m a = ReaderT (STRef s LocalVarMap) (STT s (ErrorT String m)) a
After changing the appropriate type signatures (and using some extensions to get around the types) I ran it again in the Identity monad and it was ~50% slower. Although essentially nothing changed, it is much slower. Is this normal behaviour? Is there some simple way how to make this faster? (e.g. combining the ErrorT and ReaderT (and possibly STT) stack into one monad transformer?)
To add a sample of code - it is a thing that based on a parsed input (given in C-like language) constructs a parser. The code looks like this:
compileRule :: forall m. (Monad m, Functor m) =>
-> [Data -> m (Either String Data)] -- For tying the knot
-> ParsedRule -- This is the rule we are compiling
-> Data -> m (Either String Data) -- The real parsing
compileRule compiled (ParsedRule name parsedlines) =
\input -> runRunningRule input $ do
sequence_ compiledlines
where
compiledlines = map compile parsedlines
compile (Expression expr) = compileEx expr >> return ()
compile (Assignment var expr) =
...
compileEx (Function "check" expr) = do
value <- expr
case value of
True -> return ()
False -> fail "Check failed"
where
code = compileEx expr
This is not so unusual, no. You should try using SPECIALIZE pragmas to specialize to Identity, and maybe IO too. Use -ddump-simpl and watch for warnings about rule left hand sides being too complicated. When specialization doesn't happen as it should, GHC ends up passing around typeclass dictionaries at runtime. This is inherently somewhat inefficient, but more importantly it prevents GHC from inlining class methods to enable further simplification.

How to iterate through a UTF-8 string correctly in OCaml?

Say I have some input word like "føøbær" and I want a hash table of letter frequencies s.t. f→1, ø→2 – how do I do this in OCaml?
The http://pleac.sourceforge.net/pleac_ocaml/strings.html examples only work on ASCII and https://ocaml-batteries-team.github.io/batteries-included/hdoc2/BatUTF8.html doesn't say how to actually create a BatUTF8.t from a string.
The BatUTF8 module you refer to defines its type t as string, thus there is no conversion needed: a BatUTF8.t is a string. Apparently, the module encourages you to validate your string before using other functions. I guess that a proper way of operating would be something like:
let s = "føøbær"
let () = BatUTF8.validate s
let () = BatUTF8.iter add_to_table s
Looking at the code of Batteries, I found this of_string_unsafe, so perhaps this is the way:
open Batteries
BatUTF8.iter (fun c -> …Hashtbl.add table c …) (BatUTF8.of_string_unsafe "føøbær")`
although, since it's termed "unsafe" (the doc's don't say why), maybe this is equivalent:
BatUTF8.iter (fun c -> …Hashtbl.add table c …) "føøbær"
At least it works for the example word here.
Camomile also seems to iterate through it correctly:
module C = CamomileLibraryDefault.Camomile
C.iter (fun c -> …Hashtbl.add table c …) "føøbær"
I don't know of the tradeoffs between Camomile and BatUTF8 here, though they end up storing different types (BatUChar vs C.Pervasives.UChar).

What is the most up to date way to compile code quotations in F#

I'm building a symbolic derivative engine. For example
let f = <# fun x:double -> x * x #>
let df = der f
and the resulting expression will be
<# 2 * x #>
The actual equations could be arbitrarily complex.
The generation of the derivatives are not too hard using recursive
pattern matching and transformations but in the end I want to use
the generated equations in tight numerical loops as if I had hand
written them. This is numerical computing code so faster is always
better ( if possible )
I've looked at the FSharpX quotation compiler but it looks like an interpreter rather than a compiler.
I have not tested this, but the code that translates F# quotations to LINQ expressions (and compiles them) has now moved from F# PowerPack into the F# Core library, so I think that is the most up-to-date version:
open Microsoft.FSharp.Linq.RuntimeHelpers
LeafExpressionConverter.EvaluateQuotation <# 1 + 2 #>
and to use it for lambdas
let d=LeafExpressionConverter.EvaluateQuotation <# fun y -> y+1.0 #>
:?> ( double -> double )
Console.WriteLine(d 10)
outputs
11
Note the cast at the end to convert the ''obj'' to a lambda of the correct type

How to Convert Expr<'a -> 'b> to Expression<Func<'a, obj>>

I'm using F# 3.0 with .NET 4.5 beta, and I'm trying to convert an F# quotation of type Expr<'a -> 'b> to a LINQ Expression<Func<'a, 'b>>.
I've found several questions that have solutions to this problem, but those techniques don't seem to work any longer, presumably due to changes in either F# 3.0 or .NET 4.5.
Converting F# Quotations into LINQ Expressions
Expression<Func<T, bool>> from a F# func
In both cases, when I run the code from the solutions of either question, the following action throws an exception:
mc.Arguments.[0] :?> LambdaExpression
...where mc is a MethodCallExpression. The exception is:
System.InvalidCastException: Unable to cast object of type 'System.Linq.Expressions.MethodCallExpressionN' to type 'System.Linq.Expressions.LambdaExpression'.
No, the extra "N" at the end of MethodCallExpressionN is not a typo. Does anyone have a suggestion? Thanks.
UPDATE
Here's a complete reproduction. It turns out this code works fine on an expression like <# fun x -> x + 1 #>. My problem is that in my case I need to convert an Expr<'a -> 'b> into Expr<'a -> obj> so that I don't have to litter all my lambda expressions with box. I did so by splicing the original expression into this one: <# %exp >> box #>. This produces an object with the correct type, but the code to convert to Expression<Func<'a, obj>> no longer works.
module Expr =
open System
open System.Linq.Expressions
open Microsoft.FSharp.Quotations
open Microsoft.FSharp.Linq.QuotationEvaluation
let rec private translateExpr (linq:Expression) =
match linq with
| :? MethodCallExpression as mc ->
let le = mc.Arguments.[0] :?> LambdaExpression
let args, body = translateExpr le.Body
le.Parameters.[0] :: args, body
| _ -> [], linq
let ToFuncExpression (expr:Expr<'a -> 'b>) =
let args, body = expr.ToLinqExpression() |> translateExpr
Expression.Lambda<Func<'a, 'b>>(body, Array.ofList args)
let exp = <# fun x -> x + 1 #>
let r = Expr.ToFuncExpression <# %exp >> box #>
printfn "%A" r
Can you post a more complete sample and also include the F# expression that you're trying to convert?
I tried to test the behaviour on .NET 4.5 using a minimal sample and it worked for me. Here is what I did:
I created new F# 3.0 project and copied Linq.fs and Linq.fsi from the 2.0 version of F# PowerPack. (Or is there a 3.0 version of the ToLinqExpression method available somewhere in F# 3.0?)
I used the code from Daniel's earlier answer and called the function as follows:
let r = toLinq <# fun x -> x + 1 #>
printfn "%A" r
This did not throw any exception and it printed x => (x + 1), which looks correct to me.
EDIT: To answer the updated question - both of the code samples that you referred to (mine and Daniel's) assume that the body of the quotation is an explicitly constructed function, so they only work on quotations of a specific structure: <# fun x -> ... #>.
You can fix the problem by using splicing in an explicitly constructed function. The following works for me:
let exp = <# fun x -> x + 1 #>
let r = toLinq <# fun a -> box ((%exp) a) #>
printfn "%A" r
This contains application of an F# function, so the generated Expression contains a call to ToFSharpFunc (which converts a delegate to an F# function) and then invocation of this. This may be an issue if you want Expression that standard .NET tools can understand (in which case, you'd have to post-process the C# expression tree and remove these constructs).

Resources