11namespace FSharp.Data.GraphQL.Server.Middleware
22
33open System
4- open System.Linq
5- open System.Linq .Expressions
6- open System.Runtime .InteropServices
7- open Microsoft.FSharp .Quotations
84
95/// A filter definition for a field value.
10- type FieldFilter < 'Val > =
11- { FieldName : string
12- Value : 'Val }
6+ type FieldFilter < 'Val > = { FieldName : string ; Value : 'Val }
137
148/// A filter definition for an object list.
159type ObjectListFilter =
@@ -22,10 +16,68 @@ type ObjectListFilter =
2216 | StartsWith of FieldFilter < string >
2317 | EndsWith of FieldFilter < string >
2418 | Contains of FieldFilter < string >
25- | OfTypes of FieldFilter < Type list >
19+ | OfTypes of Type list
2620 | FilterField of FieldFilter < ObjectListFilter >
2721 | NoFilter
2822
23+ open System.Linq
24+ open System.Linq .Expressions
25+ open System.Runtime .InteropServices
26+ open System.Reflection
27+
28+ /// <summary>
29+ /// Allows to specify discriminator comparison or discriminator getter
30+ /// and a function that return discriminator value depending on entity type
31+ /// </summary>
32+ /// <example id="item-1"><code lang="fsharp">
33+ /// // discriminator custom condition
34+ /// let result () =
35+ /// queryable.Apply(
36+ /// filter,
37+ /// ObjectListFilterLinqOptions (
38+ /// (fun entity discriminator -> entity.Discriminator.StartsWith discriminator),
39+ /// (function
40+ /// | t when Type.(=)(t, typeof<Cat>) -> "cat+v1"
41+ /// | t when Type.(=)(t, typeof<Dog>) -> "dog+v1")
42+ /// )
43+ /// )
44+ /// </code></example>
45+ /// <example id="item-2"><code lang="fsharp">
46+ /// // discriminator equals
47+ /// let result () =
48+ /// queryable.Apply(
49+ /// filter,
50+ /// ObjectListFilterLinqOptions (
51+ /// (fun entity -> entity.Discriminator),
52+ /// (function
53+ /// | t when Type.(=)(t, typeof<Cat>) -> "cat"
54+ /// | t when Type.(=)(t, typeof<Dog>) -> "dog")
55+ /// )
56+ /// )
57+ /// </code></example>
58+ [<Struct>]
59+ type ObjectListFilterLinqOptions < 'T , 'D >
60+ ([< Optional>] compareDiscriminator : Expression< Func< 'T, 'D, bool>> | null , [< Optional>] getDiscriminatorValue : ( Type -> 'D) | null ) =
61+
62+ member _.CompareDiscriminator = compareDiscriminator |> ValueOption.ofObj
63+ member _.GetDiscriminatorValue = getDiscriminatorValue |> ValueOption.ofObj
64+
65+ static member None = ObjectListFilterLinqOptions< 'T, 'D> ( null , null )
66+
67+ static member GetCompareDiscriminator ( getDiscriminatorValue : Expression < Func < 'T , 'D >>) =
68+ let tParam = Expression.Parameter ( typeof< 'T>, " x" )
69+ let dParam = Expression.Parameter ( typeof< 'D>, " d" )
70+ let body = Expression.Equal ( Expression.Invoke ( getDiscriminatorValue, tParam), dParam)
71+ Expression.Lambda< Func< 'T, 'D, bool>> ( body, tParam, dParam)
72+
73+ new ( getDiscriminator : Expression < Func < 'T , 'D >>) =
74+ ObjectListFilterLinqOptions< 'T, 'D> ( ObjectListFilterLinqOptions.GetCompareDiscriminator getDiscriminator, null )
75+ new ( compareDiscriminator : Expression < Func < 'T , 'D , bool >>) = ObjectListFilterLinqOptions< 'T, 'D> ( compareDiscriminator, null )
76+ new ( getDiscriminatorValue : Type -> 'D ) =
77+ ObjectListFilterLinqOptions< 'T, 'D> ( compareDiscriminator = null , getDiscriminatorValue = getDiscriminatorValue)
78+ new ( getDiscriminator : Expression < Func < 'T , 'D >>, getDiscriminatorValue : Type -> 'D ) =
79+ ObjectListFilterLinqOptions< 'T, 'D> ( ObjectListFilterLinqOptions.GetCompareDiscriminator getDiscriminator, getDiscriminatorValue)
80+
2981/// Contains tooling for working with ObjectListFilter.
3082module ObjectListFilter =
3183 /// Contains operators for building and comparing ObjectListFilter values.
@@ -60,116 +112,162 @@ module ObjectListFilter =
60112 /// Creates a new ObjectListFilter representing a NOT opreation for the existing one.
61113 let ( !!! ) filter = Not filter
62114
63- //[<AutoOpen>]
64- //module ObjectListFilterExtensions =
65-
66- // type ObjectListFilter with
67-
68- // member filter.Apply<'T, 'D>(query : IQueryable<'T>,
69- // compareDiscriminator : Expr<'T -> 'D -> 'D> | null,
70- // getDiscriminatorValue : (Type -> 'D) | null) =
71- // filter.Apply(query, compareDiscriminator, getDiscriminatorValue)
72-
73- // member filter.Apply<'T, 'D>(query : IQueryable<'T>,
74- // [<Optional>] getDiscriminator : Expr<'T -> 'D> | null,
75- // [<Optional>] getDiscriminatorValue : (Type -> 'D) | null) =
76- // // Helper to create parameter expression for the lambda
77- // let param = Expression.Parameter(typeof<'T>, "x")
78-
79- // // Helper to get property value
80- // let getPropertyExpr fieldName =
81- // Expression.PropertyOrField(param, fieldName)
82-
83- // // Helper to create lambda from body expression
84- // let makeLambda (body: Expression) =
85- // let delegateType = typedefof<Func<_,_>>.MakeGenericType([|typeof<'T>; body.Type|])
86- // Expression.Lambda(delegateType, body, param)
87-
88- // // Helper to create Where expression
89- // let whereExpr predicate =
90- // let whereMethod =
91- // typeof<Queryable>.GetMethods()
92- // |> Seq.where (fun m -> m.Name = "Where")
93- // |> Seq.find (fun m ->
94- // let parameters = m.GetParameters()
95- // parameters.Length = 2
96- // && parameters[1].ParameterType.GetGenericTypeDefinition() = typedefof<Expression<Func<_,_>>>)
97- // |> fun m -> m.MakeGenericMethod([|typeof<'T>|])
98- // Expression.Call(whereMethod, [|query.Expression; makeLambda predicate|])
99-
100- // // Helper for discriminator comparison
101- // let buildTypeDiscriminatorCheck (t: Type) =
102- // match getDiscriminator, getDiscriminatorValue with
103- // | null, _ | _, null -> None
104- // | discExpr, discValueFn ->
105- // let compiled = QuotationEvaluator.Eval(discExpr)
106- // let discriminatorValue = discValueFn t
107- // let discExpr = getPropertyExpr "__discriminator" // Assuming discriminator field name
108- // let valueExpr = Expression.Constant(discriminatorValue)
109- // Some(Expression.Equal(discExpr, valueExpr))
110-
111- // // Main filter logic
112- // let rec buildFilterExpr filter =
113- // match filter with
114- // | NoFilter -> query.Expression
115- // | And (f1, f2) ->
116- // let q1 = buildFilterExpr f1 |> Expression.Lambda<Func<IQueryable<'T>>>|> _.Compile().Invoke()
117- // buildFilterExpr f2 |> Expression.Lambda<Func<IQueryable<'T>>> |> _.Compile().Invoke(q1).Expression
118- // | Or (f1, f2) ->
119- // let expr1 = buildFilterExpr f1
120- // let expr2 = buildFilterExpr f2
121- // let unionMethod =
122- // typeof<Queryable>.GetMethods()
123- // |> Array.find (fun m -> m.Name = "Union")
124- // |> fun m -> m.MakeGenericMethod([|typeof<'T>|])
125- // Expression.Call(unionMethod, [|expr1; expr2|])
126- // | Not f ->
127- // let exceptMethod =
128- // typeof<Queryable>.GetMethods()
129- // |> Array.find (fun m -> m.Name = "Except")
130- // |> fun m -> m.MakeGenericMethod([|typeof<'T>|])
131- // Expression.Call(exceptMethod, [|query.Expression; buildFilterExpr f|])
132- // | Equals f ->
133- // Expression.Equal(getPropertyExpr f.FieldName, Expression.Constant(f.Value)) |> whereExpr
134- // | GreaterThan f ->
135- // Expression.GreaterThan(getPropertyExpr f.FieldName, Expression.Constant(f.Value)) |> whereExpr
136- // | LessThan f ->
137- // Expression.LessThan(getPropertyExpr f.FieldName, Expression.Constant(f.Value)) |> whereExpr
138- // | StartsWith f ->
139- // let methodInfo = typeof<string>.GetMethod("StartsWith", [|typeof<string>|])
140- // Expression.Call(getPropertyExpr f.FieldName, methodInfo, Expression.Constant(f.Value)) |> whereExpr
141- // | EndsWith f ->
142- // let methodInfo = typeof<string>.GetMethod("EndsWith", [|typeof<string>|])
143- // Expression.Call(getPropertyExpr f.FieldName, methodInfo, Expression.Constant(f.Value)) |> whereExpr
144- // | Contains f ->
145- // let methodInfo = typeof<string>.GetMethod("Contains", [|typeof<string>|])
146- // Expression.Call(getPropertyExpr f.FieldName, methodInfo, Expression.Constant(f.Value)) |> whereExpr
147- // | OfTypes types ->
148- // match types.Value with
149- // | [] -> query.Expression // No types specified, return original query
150- // | types ->
151- // let typeChecks =
152- // types
153- // |> List.choose buildTypeDiscriminatorCheck
154- // |> List.fold (fun acc expr ->
155- // match acc with
156- // | None -> Some expr
157- // | Some prevExpr -> Some(Expression.OrElse(prevExpr, expr))) None
158-
159- // match typeChecks with
160- // | None -> query.Expression
161- // | Some expr -> whereExpr expr
162- // | FilterField f ->
163- // let propExpr = getPropertyExpr f.FieldName
164- // match propExpr.Type.GetInterfaces()
165- // |> Array.tryFind (fun t ->
166- // t.IsGenericType && t.GetGenericTypeDefinition() = typedefof<IQueryable<_>>) with
167- // | Some queryableType ->
168- // let elementType = queryableType.GetGenericArguments().[0]
169- // let subFilter = f.Value
170- // let subQuery = Expression.Convert(propExpr, queryableType)
171- // Expression.Call(typeof<Queryable>, "Any", [|elementType|], subQuery) |> whereExpr
172- // | None -> query.Expression
173-
174- // // Create and execute the final expression
175- // query.Provider.CreateQuery<'T>(buildFilterExpr filter)
115+ let private genericWhereMethod =
116+ typeof< Queryable>. GetMethods ()
117+ |> Seq.where ( fun m -> m.Name = " Where" )
118+ |> Seq.find ( fun m ->
119+ let parameters = m.GetParameters ()
120+ parameters.Length = 2
121+ && parameters[ 1 ]. ParameterType.GetGenericTypeDefinition () = typedefof< Expression< Func<_, _>>>)
122+
123+ // Helper to create Where expression
124+ let whereExpr < 'T > ( query : IQueryable < 'T >) ( param : ParameterExpression ) predicate =
125+ let whereMethod = genericWhereMethod.MakeGenericMethod ([| typeof< 'T> |])
126+ Expression.Call ( whereMethod, [| query.Expression; Expression.Lambda< Func< 'T, bool>> ( predicate, param) |])
127+
128+ let private StringStartsWithMethod = typeof< string>. GetMethod ( " StartsWith" , [| typeof< string> |])
129+ let private StringEndsWithMethod = typeof< string>. GetMethod ( " EndsWith" , [| typeof< string> |])
130+ let private StringContainsMethod = typeof< string>. GetMethod ( " Contains" , [| typeof< string> |])
131+ let private getEnumerableContainsMethod ( memberType : Type ) =
132+ match
133+ typeof< Enumerable>
134+ .GetMethods( BindingFlags.Static ||| BindingFlags.Public)
135+ .FirstOrDefault ( fun m -> m.Name = " Contains" && m.GetParameters() .Length = 2 )
136+ with
137+ | null -> raise ( MissingMemberException " Static 'Contains' method with 2 parameters not found on 'Enumerable' class" )
138+ | containsGenericStaticMethod ->
139+ if
140+ memberType.IsGenericType
141+ && memberType.GenericTypeArguments.Length = 1
142+ then
143+ containsGenericStaticMethod.MakeGenericMethod ( memberType.GenericTypeArguments)
144+ else
145+ let ienumerable =
146+ memberType
147+ .GetInterfaces()
148+ .First ( fun i -> i.FullName.StartsWith " System.Collections.Generic.IEnumerable`1" )
149+ containsGenericStaticMethod.MakeGenericMethod ([| ienumerable.GenericTypeArguments[ 0 ] |])
150+
151+ let getField ( param : ParameterExpression ) fieldName = Expression.PropertyOrField ( param, fieldName)
152+
153+ [<Struct>]
154+ type SourceExpression private ( expression : Expression ) =
155+ new ( parameter : ParameterExpression ) = SourceExpression ( parameter :> Expression)
156+ new ( ``member`` : MemberExpression ) = SourceExpression ( `` member `` :> Expression)
157+ member _.Value = expression
158+ static member op_Implicit ( source : SourceExpression ) = source.Value
159+ static member op_Implicit ( parameter : ParameterExpression ) = SourceExpression ( parameter :> Expression)
160+ static member op_Implicit ( ``member`` : MemberExpression ) = SourceExpression ( `` member `` :> Expression)
161+
162+ let rec buildFilterExpr ( param : SourceExpression ) buildTypeDiscriminatorCheck filter : Expression =
163+ let build = buildFilterExpr param buildTypeDiscriminatorCheck
164+ match filter with
165+ | NoFilter -> Expression.Constant ( true )
166+ | Not f -> f |> build |> Expression.Not :> Expression
167+ | And ( f1, f2) -> Expression.AndAlso ( build f1, build f2)
168+ | Or ( f1, f2) -> Expression.OrElse ( build f1, build f2)
169+ | Equals f -> Expression.Equal ( Expression.PropertyOrField ( param, f.FieldName), Expression.Constant ( f.Value))
170+ | GreaterThan f -> Expression.GreaterThan ( Expression.PropertyOrField ( param, f.FieldName), Expression.Constant ( f.Value))
171+ | LessThan f -> Expression.LessThan ( Expression.PropertyOrField ( param, f.FieldName), Expression.Constant ( f.Value))
172+ | StartsWith f -> Expression.Call ( Expression.PropertyOrField ( param, f.FieldName), StringStartsWithMethod, Expression.Constant ( f.Value))
173+ | EndsWith f -> Expression.Call ( Expression.PropertyOrField ( param, f.FieldName), StringEndsWithMethod, Expression.Constant ( f.Value))
174+ | Contains f ->
175+ let ``member`` = Expression.PropertyOrField ( param, f.FieldName)
176+ let isEnumerable ( memberType : Type ) =
177+ not ( Type.(=) ( memberType, typeof< string>))
178+ && typeof< System.Collections.IEnumerable>. IsAssignableFrom ( memberType)
179+ && memberType
180+ .GetInterfaces()
181+ .Any ( fun i -> i.FullName.StartsWith " System.Collections.Generic.IEnumerable`1" )
182+ match `` member `` .Member with
183+ | :? PropertyInfo as prop when prop.PropertyType |> isEnumerable ->
184+ match
185+ prop.PropertyType
186+ .GetMethods( BindingFlags.Instance ||| BindingFlags.Public)
187+ .FirstOrDefault ( fun m -> m.Name = " Contains" && m.GetParameters() .Length = 1 )
188+ with
189+ | null ->
190+ Expression.Call (
191+ getEnumerableContainsMethod prop.PropertyType,
192+ Expression.PropertyOrField ( param, f.FieldName),
193+ Expression.Constant ( f.Value)
194+ )
195+ | instanceContainsMethod ->
196+ Expression.Call ( Expression.PropertyOrField ( param, f.FieldName), instanceContainsMethod, Expression.Constant ( f.Value))
197+ | :? FieldInfo as field when field.FieldType |> isEnumerable ->
198+ Expression.Call (
199+ getEnumerableContainsMethod field.FieldType,
200+ Expression.PropertyOrField ( param, f.FieldName),
201+ Expression.Constant ( f.Value)
202+ )
203+ | _ -> Expression.Call ( `` member `` , StringContainsMethod, Expression.Constant ( f.Value))
204+ | OfTypes types ->
205+ types
206+ |> Seq.map ( fun t -> buildTypeDiscriminatorCheck param t)
207+ |> Seq.reduce ( fun acc expr -> Expression.Or ( acc, expr))
208+ | FilterField f ->
209+ let paramExpr = Expression.PropertyOrField ( param, f.FieldName)
210+ buildFilterExpr ( SourceExpression paramExpr) buildTypeDiscriminatorCheck f.Value
211+
212+ let apply ( options : ObjectListFilterLinqOptions < 'T , 'D >) ( filter : ObjectListFilter ) ( query : IQueryable < 'T >) =
213+ match filter with
214+ | NoFilter -> query
215+ | _ ->
216+ // Helper for discriminator comparison
217+ let buildTypeDiscriminatorCheck ( param : SourceExpression ) ( t : Type ) =
218+ match options.CompareDiscriminator, options.GetDiscriminatorValue with
219+ | ValueNone, ValueNone ->
220+ Expression.Equal (
221+ // Default discriminator property
222+ Expression.PropertyOrField ( param, " __typename" ),
223+ // Default discriminator value
224+ Expression.Constant ( t.FullName)
225+ )
226+ :> Expression
227+ | ValueSome discExpr, ValueNone ->
228+ Expression.Invoke (
229+ // Provided discriminator comparison
230+ discExpr,
231+ param,
232+ // Default discriminator value gathered from type
233+ Expression.Constant ( t.FullName)
234+ )
235+ :> Expression
236+ | ValueNone, ValueSome discValueFn ->
237+ let discriminatorValue = discValueFn t
238+ Expression.Equal (
239+ // Default discriminator property
240+ Expression.PropertyOrField ( param, " __typename" ),
241+ // Provided discriminator value gathered from type
242+ Expression.Constant ( discriminatorValue)
243+ )
244+ :> Expression
245+ | ValueSome discExpr, ValueSome discValueFn ->
246+ let discriminatorValue = discValueFn t
247+ Expression.Invoke (
248+ // Provided discriminator comparison
249+ discExpr,
250+ param,
251+ // Provided discriminator value gathered from type
252+ Expression.Constant ( discriminatorValue)
253+ )
254+ let queryExpr =
255+ let param = Expression.Parameter ( typeof< 'T>, " x" )
256+ let body = buildFilterExpr ( SourceExpression param) buildTypeDiscriminatorCheck filter
257+ whereExpr< 'T> query param body
258+ // Create and execute the final expression
259+ query.Provider.CreateQuery< 'T> ( queryExpr)
260+
261+ [<AutoOpen>]
262+ module ObjectListFilterExtensions =
263+
264+ open ObjectListFilter
265+
266+ type ObjectListFilter with
267+
268+ member inline filter.ApplyTo < 'T , 'D > ( query : IQueryable < 'T >, [<Optional>] options : ObjectListFilterLinqOptions < 'T , 'D >) =
269+ apply options filter query
270+
271+ type IQueryable < 'T > with
272+
273+ member inline query.Apply ( filter : ObjectListFilter , [<Optional>] options : ObjectListFilterLinqOptions < 'T , 'D >) = apply options filter query
0 commit comments