functional revision 253159
1227825Stheraven// -*- C++ -*-
2227825Stheraven//===------------------------ functional ----------------------------------===//
3227825Stheraven//
4227825Stheraven//                     The LLVM Compiler Infrastructure
5227825Stheraven//
6227825Stheraven// This file is dual licensed under the MIT and the University of Illinois Open
7227825Stheraven// Source Licenses. See LICENSE.TXT for details.
8227825Stheraven//
9227825Stheraven//===----------------------------------------------------------------------===//
10227825Stheraven
11227825Stheraven#ifndef _LIBCPP_FUNCTIONAL
12227825Stheraven#define _LIBCPP_FUNCTIONAL
13227825Stheraven
14227825Stheraven/*
15227825Stheraven    functional synopsis
16227825Stheraven
17227825Stheravennamespace std
18227825Stheraven{
19227825Stheraven
20227825Stheraventemplate <class Arg, class Result>
21227825Stheravenstruct unary_function
22227825Stheraven{
23227825Stheraven    typedef Arg    argument_type;
24227825Stheraven    typedef Result result_type;
25227825Stheraven};
26227825Stheraven
27227825Stheraventemplate <class Arg1, class Arg2, class Result>
28227825Stheravenstruct binary_function
29227825Stheraven{
30227825Stheraven    typedef Arg1   first_argument_type;
31227825Stheraven    typedef Arg2   second_argument_type;
32227825Stheraven    typedef Result result_type;
33227825Stheraven};
34227825Stheraven
35227825Stheraventemplate <class T>
36227825Stheravenclass reference_wrapper
37227825Stheraven    : public unary_function<T1, R> // if wrapping a unary functor
38227825Stheraven    : public binary_function<T1, T2, R> // if wraping a binary functor
39227825Stheraven{
40227825Stheravenpublic:
41227825Stheraven    // types
42227825Stheraven    typedef T type;
43227825Stheraven    typedef see below result_type; // Not always defined
44227825Stheraven
45227825Stheraven    // construct/copy/destroy
46227825Stheraven    reference_wrapper(T&) noexcept;
47227825Stheraven    reference_wrapper(T&&) = delete; // do not bind to temps
48227825Stheraven    reference_wrapper(const reference_wrapper<T>& x) noexcept;
49227825Stheraven
50227825Stheraven    // assignment
51227825Stheraven    reference_wrapper& operator=(const reference_wrapper<T>& x) noexcept;
52227825Stheraven
53227825Stheraven    // access
54227825Stheraven    operator T& () const noexcept;
55227825Stheraven    T& get() const noexcept;
56227825Stheraven
57227825Stheraven    // invoke
58227825Stheraven    template <class... ArgTypes>
59227825Stheraven      typename result_of<T(ArgTypes...)>::type
60227825Stheraven          operator() (ArgTypes&&...) const;
61227825Stheraven};
62227825Stheraven
63227825Stheraventemplate <class T> reference_wrapper<T> ref(T& t) noexcept;
64227825Stheraventemplate <class T> void ref(const T&& t) = delete;
65227825Stheraventemplate <class T> reference_wrapper<T> ref(reference_wrapper<T>t) noexcept;
66227825Stheraven
67227825Stheraventemplate <class T> reference_wrapper<const T> cref(const T& t) noexcept;
68227825Stheraventemplate <class T> void cref(const T&& t) = delete;
69227825Stheraventemplate <class T> reference_wrapper<const T> cref(reference_wrapper<T> t) noexcept;
70227825Stheraven
71227825Stheraventemplate <class T>
72227825Stheravenstruct plus : binary_function<T, T, T>
73227825Stheraven{
74227825Stheraven    T operator()(const T& x, const T& y) const;
75227825Stheraven};
76227825Stheraven
77227825Stheraventemplate <class T>
78227825Stheravenstruct minus : binary_function<T, T, T>
79227825Stheraven{
80227825Stheraven    T operator()(const T& x, const T& y) const;
81227825Stheraven};
82227825Stheraven
83227825Stheraventemplate <class T>
84227825Stheravenstruct multiplies : binary_function<T, T, T>
85227825Stheraven{
86227825Stheraven    T operator()(const T& x, const T& y) const;
87227825Stheraven};
88227825Stheraven
89227825Stheraventemplate <class T>
90227825Stheravenstruct divides : binary_function<T, T, T>
91227825Stheraven{
92227825Stheraven    T operator()(const T& x, const T& y) const;
93227825Stheraven};
94227825Stheraven
95227825Stheraventemplate <class T>
96227825Stheravenstruct modulus : binary_function<T, T, T>
97227825Stheraven{
98227825Stheraven    T operator()(const T& x, const T& y) const;
99227825Stheraven};
100227825Stheraven
101227825Stheraventemplate <class T>
102227825Stheravenstruct negate : unary_function<T, T>
103227825Stheraven{
104227825Stheraven    T operator()(const T& x) const;
105227825Stheraven};
106227825Stheraven
107227825Stheraventemplate <class T>
108227825Stheravenstruct equal_to : binary_function<T, T, bool>
109227825Stheraven{
110227825Stheraven    bool operator()(const T& x, const T& y) const;
111227825Stheraven};
112227825Stheraven
113227825Stheraventemplate <class T>
114227825Stheravenstruct not_equal_to : binary_function<T, T, bool>
115227825Stheraven{
116227825Stheraven    bool operator()(const T& x, const T& y) const;
117227825Stheraven};
118227825Stheraven
119227825Stheraventemplate <class T>
120227825Stheravenstruct greater : binary_function<T, T, bool>
121227825Stheraven{
122227825Stheraven    bool operator()(const T& x, const T& y) const;
123227825Stheraven};
124227825Stheraven
125227825Stheraventemplate <class T>
126227825Stheravenstruct less : binary_function<T, T, bool>
127227825Stheraven{
128227825Stheraven    bool operator()(const T& x, const T& y) const;
129227825Stheraven};
130227825Stheraven
131227825Stheraventemplate <class T>
132227825Stheravenstruct greater_equal : binary_function<T, T, bool>
133227825Stheraven{
134227825Stheraven    bool operator()(const T& x, const T& y) const;
135227825Stheraven};
136227825Stheraven
137227825Stheraventemplate <class T>
138227825Stheravenstruct less_equal : binary_function<T, T, bool>
139227825Stheraven{
140227825Stheraven    bool operator()(const T& x, const T& y) const;
141227825Stheraven};
142227825Stheraven
143227825Stheraventemplate <class T>
144227825Stheravenstruct logical_and : binary_function<T, T, bool>
145227825Stheraven{
146227825Stheraven    bool operator()(const T& x, const T& y) const;
147227825Stheraven};
148227825Stheraven
149227825Stheraventemplate <class T>
150227825Stheravenstruct logical_or : binary_function<T, T, bool>
151227825Stheraven{
152227825Stheraven    bool operator()(const T& x, const T& y) const;
153227825Stheraven};
154227825Stheraven
155227825Stheraventemplate <class T>
156227825Stheravenstruct logical_not : unary_function<T, bool>
157227825Stheraven{
158227825Stheraven    bool operator()(const T& x) const;
159227825Stheraven};
160227825Stheraven
161227825Stheraventemplate <class Predicate>
162227825Stheravenclass unary_negate
163227825Stheraven    : public unary_function<typename Predicate::argument_type, bool>
164227825Stheraven{
165227825Stheravenpublic:
166227825Stheraven    explicit unary_negate(const Predicate& pred);
167227825Stheraven    bool operator()(const typename Predicate::argument_type& x) const;
168227825Stheraven};
169227825Stheraven
170227825Stheraventemplate <class Predicate> unary_negate<Predicate> not1(const Predicate& pred);
171227825Stheraven
172227825Stheraventemplate <class Predicate>
173227825Stheravenclass binary_negate
174227825Stheraven    : public binary_function<typename Predicate::first_argument_type,
175227825Stheraven                             typename Predicate::second_argument_type,
176227825Stheraven                             bool>
177227825Stheraven{
178227825Stheravenpublic:
179227825Stheraven    explicit binary_negate(const Predicate& pred);
180227825Stheraven    bool operator()(const typename Predicate::first_argument_type& x,
181227825Stheraven                    const typename Predicate::second_argument_type& y) const;
182227825Stheraven};
183227825Stheraven
184227825Stheraventemplate <class Predicate> binary_negate<Predicate> not2(const Predicate& pred);
185227825Stheraven
186227825Stheraventemplate<class T> struct is_bind_expression;
187227825Stheraventemplate<class T> struct is_placeholder;
188227825Stheraven
189227825Stheraventemplate<class Fn, class... BoundArgs>
190227825Stheraven  unspecified bind(Fn&&, BoundArgs&&...);
191227825Stheraventemplate<class R, class Fn, class... BoundArgs>
192227825Stheraven  unspecified bind(Fn&&, BoundArgs&&...);
193227825Stheraven
194227825Stheravennamespace placeholders {
195227825Stheraven  // M is the implementation-defined number of placeholders
196227825Stheraven  extern unspecified _1;
197227825Stheraven  extern unspecified _2;
198227825Stheraven  .
199227825Stheraven  .
200227825Stheraven  .
201232950Stheraven  extern unspecified _Mp;
202227825Stheraven}
203227825Stheraven
204227825Stheraventemplate <class Operation>
205227825Stheravenclass binder1st
206227825Stheraven    : public unary_function<typename Operation::second_argument_type,
207227825Stheraven                            typename Operation::result_type>
208227825Stheraven{
209227825Stheravenprotected:
210227825Stheraven    Operation                               op;
211227825Stheraven    typename Operation::first_argument_type value;
212227825Stheravenpublic:
213227825Stheraven    binder1st(const Operation& x, const typename Operation::first_argument_type y);
214227825Stheraven    typename Operation::result_type operator()(      typename Operation::second_argument_type& x) const;
215227825Stheraven    typename Operation::result_type operator()(const typename Operation::second_argument_type& x) const;
216227825Stheraven};
217227825Stheraven
218227825Stheraventemplate <class Operation, class T>
219227825Stheravenbinder1st<Operation> bind1st(const Operation& op, const T& x);
220227825Stheraven
221227825Stheraventemplate <class Operation>
222227825Stheravenclass binder2nd
223227825Stheraven    : public unary_function<typename Operation::first_argument_type,
224227825Stheraven                            typename Operation::result_type>
225227825Stheraven{
226227825Stheravenprotected:
227227825Stheraven    Operation                                op;
228227825Stheraven    typename Operation::second_argument_type value;
229227825Stheravenpublic:
230227825Stheraven    binder2nd(const Operation& x, const typename Operation::second_argument_type y);
231227825Stheraven    typename Operation::result_type operator()(      typename Operation::first_argument_type& x) const;
232227825Stheraven    typename Operation::result_type operator()(const typename Operation::first_argument_type& x) const;
233227825Stheraven};
234227825Stheraven
235227825Stheraventemplate <class Operation, class T>
236227825Stheravenbinder2nd<Operation> bind2nd(const Operation& op, const T& x);
237227825Stheraven
238227825Stheraventemplate <class Arg, class Result>
239227825Stheravenclass pointer_to_unary_function : public unary_function<Arg, Result>
240227825Stheraven{
241227825Stheravenpublic:
242227825Stheraven    explicit pointer_to_unary_function(Result (*f)(Arg));
243227825Stheraven    Result operator()(Arg x) const;
244227825Stheraven};
245227825Stheraven
246227825Stheraventemplate <class Arg, class Result>
247227825Stheravenpointer_to_unary_function<Arg,Result> ptr_fun(Result (*f)(Arg));
248227825Stheraven
249227825Stheraventemplate <class Arg1, class Arg2, class Result>
250227825Stheravenclass pointer_to_binary_function : public binary_function<Arg1, Arg2, Result>
251227825Stheraven{
252227825Stheravenpublic:
253227825Stheraven    explicit pointer_to_binary_function(Result (*f)(Arg1, Arg2));
254227825Stheraven    Result operator()(Arg1 x, Arg2 y) const;
255227825Stheraven};
256227825Stheraven
257227825Stheraventemplate <class Arg1, class Arg2, class Result>
258227825Stheravenpointer_to_binary_function<Arg1,Arg2,Result> ptr_fun(Result (*f)(Arg1,Arg2));
259227825Stheraven
260227825Stheraventemplate<class S, class T>
261227825Stheravenclass mem_fun_t : public unary_function<T*, S>
262227825Stheraven{
263227825Stheravenpublic:
264227825Stheraven    explicit mem_fun_t(S (T::*p)());
265227825Stheraven    S operator()(T* p) const;
266227825Stheraven};
267227825Stheraven
268227825Stheraventemplate<class S, class T, class A>
269227825Stheravenclass mem_fun1_t : public binary_function<T*, A, S>
270227825Stheraven{
271227825Stheravenpublic:
272227825Stheraven    explicit mem_fun1_t(S (T::*p)(A));
273227825Stheraven    S operator()(T* p, A x) const;
274227825Stheraven};
275227825Stheraven
276227825Stheraventemplate<class S, class T>          mem_fun_t<S,T>    mem_fun(S (T::*f)());
277227825Stheraventemplate<class S, class T, class A> mem_fun1_t<S,T,A> mem_fun(S (T::*f)(A));
278227825Stheraven
279227825Stheraventemplate<class S, class T>
280227825Stheravenclass mem_fun_ref_t : public unary_function<T, S>
281227825Stheraven{
282227825Stheravenpublic:
283227825Stheraven    explicit mem_fun_ref_t(S (T::*p)());
284227825Stheraven    S operator()(T& p) const;
285227825Stheraven};
286227825Stheraven
287227825Stheraventemplate<class S, class T, class A>
288227825Stheravenclass mem_fun1_ref_t : public binary_function<T, A, S>
289227825Stheraven{
290227825Stheravenpublic:
291227825Stheraven    explicit mem_fun1_ref_t(S (T::*p)(A));
292227825Stheraven    S operator()(T& p, A x) const;
293227825Stheraven};
294227825Stheraven
295227825Stheraventemplate<class S, class T>          mem_fun_ref_t<S,T>    mem_fun_ref(S (T::*f)());
296227825Stheraventemplate<class S, class T, class A> mem_fun1_ref_t<S,T,A> mem_fun_ref(S (T::*f)(A));
297227825Stheraven
298227825Stheraventemplate <class S, class T>
299227825Stheravenclass const_mem_fun_t : public unary_function<const T*, S>
300227825Stheraven{
301227825Stheravenpublic:
302227825Stheraven    explicit const_mem_fun_t(S (T::*p)() const);
303227825Stheraven    S operator()(const T* p) const;
304227825Stheraven};
305227825Stheraven
306227825Stheraventemplate <class S, class T, class A>
307227825Stheravenclass const_mem_fun1_t : public binary_function<const T*, A, S>
308227825Stheraven{
309227825Stheravenpublic:
310227825Stheraven    explicit const_mem_fun1_t(S (T::*p)(A) const);
311227825Stheraven    S operator()(const T* p, A x) const;
312227825Stheraven};
313227825Stheraven
314227825Stheraventemplate <class S, class T>          const_mem_fun_t<S,T>    mem_fun(S (T::*f)() const);
315227825Stheraventemplate <class S, class T, class A> const_mem_fun1_t<S,T,A> mem_fun(S (T::*f)(A) const);
316227825Stheraven
317227825Stheraventemplate <class S, class T>
318227825Stheravenclass const_mem_fun_ref_t : public unary_function<T, S>
319227825Stheraven{
320227825Stheravenpublic:
321227825Stheraven    explicit const_mem_fun_ref_t(S (T::*p)() const);
322227825Stheraven    S operator()(const T& p) const;
323227825Stheraven};
324227825Stheraven
325227825Stheraventemplate <class S, class T, class A>
326227825Stheravenclass const_mem_fun1_ref_t : public binary_function<T, A, S>
327227825Stheraven{
328227825Stheravenpublic:
329227825Stheraven    explicit const_mem_fun1_ref_t(S (T::*p)(A) const);
330227825Stheraven    S operator()(const T& p, A x) const;
331227825Stheraven};
332227825Stheraven
333227825Stheraventemplate <class S, class T>          const_mem_fun_ref_t<S,T>    mem_fun_ref(S (T::*f)() const);
334227825Stheraventemplate <class S, class T, class A> const_mem_fun1_ref_t<S,T,A> mem_fun_ref(S (T::*f)(A) const);
335227825Stheraven
336227825Stheraventemplate<class R, class T> unspecified mem_fn(R T::*);
337227825Stheraventemplate<class R, class T, class... Args> unspecified mem_fn(R (T::*)(Args...));
338227825Stheraventemplate<class R, class T, class... Args> unspecified mem_fn(R (T::*)(Args...) const);
339227825Stheraventemplate<class R, class T, class... Args> unspecified mem_fn(R (T::*)(Args...) volatile);
340227825Stheraventemplate<class R, class T, class... Args> unspecified mem_fn(R (T::*)(Args...) const volatile);
341227825Stheraventemplate<class R, class T, class... Args> unspecified mem_fn(R (T::*)(Args...) &);
342227825Stheraventemplate<class R, class T, class... Args> unspecified mem_fn(R (T::*)(Args...) const &);
343227825Stheraventemplate<class R, class T, class... Args> unspecified mem_fn(R (T::*)(Args...) volatile &);
344227825Stheraventemplate<class R, class T, class... Args> unspecified mem_fn(R (T::*)(Args...) const volatile &);
345227825Stheraventemplate<class R, class T, class... Args> unspecified mem_fn(R (T::*)(Args...) &&);
346227825Stheraventemplate<class R, class T, class... Args> unspecified mem_fn(R (T::*)(Args...) const &&);
347227825Stheraventemplate<class R, class T, class... Args> unspecified mem_fn(R (T::*)(Args...) volatile &&);
348227825Stheraventemplate<class R, class T, class... Args> unspecified mem_fn(R (T::*)(Args...) const volatile &&);
349227825Stheraven
350227825Stheravenclass bad_function_call
351227825Stheraven    : public exception
352227825Stheraven{
353227825Stheraven};
354227825Stheraven
355227825Stheraventemplate<class> class function; // undefined
356227825Stheraven
357227825Stheraventemplate<class R, class... ArgTypes>
358227825Stheravenclass function<R(ArgTypes...)>
359227825Stheraven  : public unary_function<T1, R>      // iff sizeof...(ArgTypes) == 1 and
360227825Stheraven                                      // ArgTypes contains T1
361227825Stheraven  : public binary_function<T1, T2, R> // iff sizeof...(ArgTypes) == 2 and
362227825Stheraven                                      // ArgTypes contains T1 and T2
363227825Stheraven{
364227825Stheravenpublic:
365227825Stheraven    typedef R result_type;
366227825Stheraven
367227825Stheraven    // construct/copy/destroy:
368227825Stheraven    function() noexcept;
369227825Stheraven    function(nullptr_t) noexcept;
370227825Stheraven    function(const function&);
371227825Stheraven    function(function&&) noexcept;
372227825Stheraven    template<class F>
373227825Stheraven      function(F);
374227825Stheraven    template<Allocator Alloc>
375227825Stheraven      function(allocator_arg_t, const Alloc&) noexcept;
376227825Stheraven    template<Allocator Alloc>
377227825Stheraven      function(allocator_arg_t, const Alloc&, nullptr_t) noexcept;
378227825Stheraven    template<Allocator Alloc>
379227825Stheraven      function(allocator_arg_t, const Alloc&, const function&);
380227825Stheraven    template<Allocator Alloc>
381227825Stheraven      function(allocator_arg_t, const Alloc&, function&&);
382227825Stheraven    template<class F, Allocator Alloc>
383227825Stheraven      function(allocator_arg_t, const Alloc&, F);
384227825Stheraven
385227825Stheraven    function& operator=(const function&);
386227825Stheraven    function& operator=(function&&) noexcept;
387227825Stheraven    function& operator=(nullptr_t) noexcept;
388227825Stheraven    template<class F>
389227825Stheraven      function& operator=(F&&);
390227825Stheraven    template<class F>
391227825Stheraven      function& operator=(reference_wrapper<F>) noexcept;
392227825Stheraven
393227825Stheraven    ~function();
394227825Stheraven
395227825Stheraven    // function modifiers:
396227825Stheraven    void swap(function&) noexcept;
397227825Stheraven    template<class F, class Alloc>
398227825Stheraven      void assign(F&&, const Alloc&);
399227825Stheraven
400227825Stheraven    // function capacity:
401227825Stheraven    explicit operator bool() const noexcept;
402227825Stheraven
403227825Stheraven    // function invocation:
404227825Stheraven    R operator()(ArgTypes...) const;
405227825Stheraven
406227825Stheraven    // function target access:
407227825Stheraven    const std::type_info& target_type() const noexcept;
408227825Stheraven    template <typename T>       T* target() noexcept;
409227825Stheraven    template <typename T> const T* target() const noexcept;
410227825Stheraven};
411227825Stheraven
412227825Stheraven// Null pointer comparisons:
413227825Stheraventemplate <class R, class ... ArgTypes>
414227825Stheraven  bool operator==(const function<R(ArgTypes...)>&, nullptr_t) noexcept;
415227825Stheraven
416227825Stheraventemplate <class R, class ... ArgTypes>
417227825Stheraven  bool operator==(nullptr_t, const function<R(ArgTypes...)>&) noexcept;
418227825Stheraven
419227825Stheraventemplate <class R, class ... ArgTypes>
420227825Stheraven  bool operator!=(const function<R(ArgTypes...)>&, nullptr_t) noexcept;
421227825Stheraven
422227825Stheraventemplate <class  R, class ... ArgTypes>
423227825Stheraven  bool operator!=(nullptr_t, const function<R(ArgTypes...)>&) noexcept;
424227825Stheraven
425227825Stheraven// specialized algorithms:
426227825Stheraventemplate <class  R, class ... ArgTypes>
427227825Stheraven  void swap(function<R(ArgTypes...)>&, function<R(ArgTypes...)>&) noexcept;
428227825Stheraven
429227825Stheraventemplate <class T> struct hash;
430227825Stheraven
431227825Stheraventemplate <> struct hash<bool>;
432227825Stheraventemplate <> struct hash<char>;
433227825Stheraventemplate <> struct hash<signed char>;
434227825Stheraventemplate <> struct hash<unsigned char>;
435227825Stheraventemplate <> struct hash<char16_t>;
436227825Stheraventemplate <> struct hash<char32_t>;
437227825Stheraventemplate <> struct hash<wchar_t>;
438227825Stheraventemplate <> struct hash<short>;
439227825Stheraventemplate <> struct hash<unsigned short>;
440227825Stheraventemplate <> struct hash<int>;
441227825Stheraventemplate <> struct hash<unsigned int>;
442227825Stheraventemplate <> struct hash<long>;
443227825Stheraventemplate <> struct hash<long long>;
444227825Stheraventemplate <> struct hash<unsigned long>;
445227825Stheraventemplate <> struct hash<unsigned long long>;
446227825Stheraven
447227825Stheraventemplate <> struct hash<float>;
448227825Stheraventemplate <> struct hash<double>;
449227825Stheraventemplate <> struct hash<long double>;
450227825Stheraven
451227825Stheraventemplate<class T> struct hash<T*>;
452227825Stheraven
453227825Stheraven}  // std
454227825Stheraven
455227825StheravenPOLICY:  For non-variadic implementations, the number of arguments is limited
456227825Stheraven         to 3.  It is hoped that the need for non-variadic implementations
457227825Stheraven         will be minimal.
458227825Stheraven
459227825Stheraven*/
460227825Stheraven
461227825Stheraven#include <__config>
462227825Stheraven#include <type_traits>
463227825Stheraven#include <typeinfo>
464227825Stheraven#include <exception>
465227825Stheraven#include <memory>
466227825Stheraven#include <tuple>
467227825Stheraven
468227825Stheraven#include <__functional_base>
469227825Stheraven
470227825Stheraven#if !defined(_LIBCPP_HAS_NO_PRAGMA_SYSTEM_HEADER)
471227825Stheraven#pragma GCC system_header
472227825Stheraven#endif
473227825Stheraven
474227825Stheraven_LIBCPP_BEGIN_NAMESPACE_STD
475227825Stheraven
476227825Stheraventemplate <class _Tp>
477249998Sdimstruct _LIBCPP_TYPE_VIS plus : binary_function<_Tp, _Tp, _Tp>
478227825Stheraven{
479227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Tp operator()(const _Tp& __x, const _Tp& __y) const
480227825Stheraven        {return __x + __y;}
481227825Stheraven};
482227825Stheraven
483227825Stheraventemplate <class _Tp>
484249998Sdimstruct _LIBCPP_TYPE_VIS minus : binary_function<_Tp, _Tp, _Tp>
485227825Stheraven{
486227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Tp operator()(const _Tp& __x, const _Tp& __y) const
487227825Stheraven        {return __x - __y;}
488227825Stheraven};
489227825Stheraven
490227825Stheraventemplate <class _Tp>
491249998Sdimstruct _LIBCPP_TYPE_VIS multiplies : binary_function<_Tp, _Tp, _Tp>
492227825Stheraven{
493227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Tp operator()(const _Tp& __x, const _Tp& __y) const
494227825Stheraven        {return __x * __y;}
495227825Stheraven};
496227825Stheraven
497227825Stheraventemplate <class _Tp>
498249998Sdimstruct _LIBCPP_TYPE_VIS divides : binary_function<_Tp, _Tp, _Tp>
499227825Stheraven{
500227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Tp operator()(const _Tp& __x, const _Tp& __y) const
501227825Stheraven        {return __x / __y;}
502227825Stheraven};
503227825Stheraven
504227825Stheraventemplate <class _Tp>
505249998Sdimstruct _LIBCPP_TYPE_VIS modulus : binary_function<_Tp, _Tp, _Tp>
506227825Stheraven{
507227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Tp operator()(const _Tp& __x, const _Tp& __y) const
508227825Stheraven        {return __x % __y;}
509227825Stheraven};
510227825Stheraven
511227825Stheraventemplate <class _Tp>
512249998Sdimstruct _LIBCPP_TYPE_VIS negate : unary_function<_Tp, _Tp>
513227825Stheraven{
514227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Tp operator()(const _Tp& __x) const
515227825Stheraven        {return -__x;}
516227825Stheraven};
517227825Stheraven
518227825Stheraventemplate <class _Tp>
519249998Sdimstruct _LIBCPP_TYPE_VIS equal_to : binary_function<_Tp, _Tp, bool>
520227825Stheraven{
521227825Stheraven    _LIBCPP_INLINE_VISIBILITY bool operator()(const _Tp& __x, const _Tp& __y) const
522227825Stheraven        {return __x == __y;}
523227825Stheraven};
524227825Stheraven
525227825Stheraventemplate <class _Tp>
526249998Sdimstruct _LIBCPP_TYPE_VIS not_equal_to : binary_function<_Tp, _Tp, bool>
527227825Stheraven{
528227825Stheraven    _LIBCPP_INLINE_VISIBILITY bool operator()(const _Tp& __x, const _Tp& __y) const
529227825Stheraven        {return __x != __y;}
530227825Stheraven};
531227825Stheraven
532227825Stheraventemplate <class _Tp>
533249998Sdimstruct _LIBCPP_TYPE_VIS greater : binary_function<_Tp, _Tp, bool>
534227825Stheraven{
535227825Stheraven    _LIBCPP_INLINE_VISIBILITY bool operator()(const _Tp& __x, const _Tp& __y) const
536227825Stheraven        {return __x > __y;}
537227825Stheraven};
538227825Stheraven
539232950Stheraven// less in <__functional_base>
540227825Stheraven
541227825Stheraventemplate <class _Tp>
542249998Sdimstruct _LIBCPP_TYPE_VIS greater_equal : binary_function<_Tp, _Tp, bool>
543227825Stheraven{
544227825Stheraven    _LIBCPP_INLINE_VISIBILITY bool operator()(const _Tp& __x, const _Tp& __y) const
545227825Stheraven        {return __x >= __y;}
546227825Stheraven};
547227825Stheraven
548227825Stheraventemplate <class _Tp>
549249998Sdimstruct _LIBCPP_TYPE_VIS less_equal : binary_function<_Tp, _Tp, bool>
550227825Stheraven{
551227825Stheraven    _LIBCPP_INLINE_VISIBILITY bool operator()(const _Tp& __x, const _Tp& __y) const
552227825Stheraven        {return __x <= __y;}
553227825Stheraven};
554227825Stheraven
555227825Stheraventemplate <class _Tp>
556249998Sdimstruct _LIBCPP_TYPE_VIS logical_and : binary_function<_Tp, _Tp, bool>
557227825Stheraven{
558227825Stheraven    _LIBCPP_INLINE_VISIBILITY bool operator()(const _Tp& __x, const _Tp& __y) const
559227825Stheraven        {return __x && __y;}
560227825Stheraven};
561227825Stheraven
562227825Stheraventemplate <class _Tp>
563249998Sdimstruct _LIBCPP_TYPE_VIS logical_or : binary_function<_Tp, _Tp, bool>
564227825Stheraven{
565227825Stheraven    _LIBCPP_INLINE_VISIBILITY bool operator()(const _Tp& __x, const _Tp& __y) const
566227825Stheraven        {return __x || __y;}
567227825Stheraven};
568227825Stheraven
569227825Stheraventemplate <class _Tp>
570249998Sdimstruct _LIBCPP_TYPE_VIS logical_not : unary_function<_Tp, bool>
571227825Stheraven{
572227825Stheraven    _LIBCPP_INLINE_VISIBILITY bool operator()(const _Tp& __x) const
573227825Stheraven        {return !__x;}
574227825Stheraven};
575227825Stheraven
576227825Stheraventemplate <class _Tp>
577249998Sdimstruct _LIBCPP_TYPE_VIS bit_and : binary_function<_Tp, _Tp, _Tp>
578227825Stheraven{
579227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Tp operator()(const _Tp& __x, const _Tp& __y) const
580227825Stheraven        {return __x & __y;}
581227825Stheraven};
582227825Stheraven
583227825Stheraventemplate <class _Tp>
584249998Sdimstruct _LIBCPP_TYPE_VIS bit_or : binary_function<_Tp, _Tp, _Tp>
585227825Stheraven{
586227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Tp operator()(const _Tp& __x, const _Tp& __y) const
587227825Stheraven        {return __x | __y;}
588227825Stheraven};
589227825Stheraven
590227825Stheraventemplate <class _Tp>
591249998Sdimstruct _LIBCPP_TYPE_VIS bit_xor : binary_function<_Tp, _Tp, _Tp>
592227825Stheraven{
593227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Tp operator()(const _Tp& __x, const _Tp& __y) const
594227825Stheraven        {return __x ^ __y;}
595227825Stheraven};
596227825Stheraven
597227825Stheraventemplate <class _Predicate>
598249998Sdimclass _LIBCPP_TYPE_VIS unary_negate
599227825Stheraven    : public unary_function<typename _Predicate::argument_type, bool>
600227825Stheraven{
601227825Stheraven    _Predicate __pred_;
602227825Stheravenpublic:
603227825Stheraven    _LIBCPP_INLINE_VISIBILITY explicit unary_negate(const _Predicate& __pred)
604227825Stheraven        : __pred_(__pred) {}
605227825Stheraven    _LIBCPP_INLINE_VISIBILITY bool operator()(const typename _Predicate::argument_type& __x) const
606227825Stheraven        {return !__pred_(__x);}
607227825Stheraven};
608227825Stheraven
609227825Stheraventemplate <class _Predicate>
610227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
611227825Stheravenunary_negate<_Predicate>
612227825Stheravennot1(const _Predicate& __pred) {return unary_negate<_Predicate>(__pred);}
613227825Stheraven
614227825Stheraventemplate <class _Predicate>
615249998Sdimclass _LIBCPP_TYPE_VIS binary_negate
616227825Stheraven    : public binary_function<typename _Predicate::first_argument_type,
617227825Stheraven                             typename _Predicate::second_argument_type,
618227825Stheraven                             bool>
619227825Stheraven{
620227825Stheraven    _Predicate __pred_;
621227825Stheravenpublic:
622227825Stheraven    _LIBCPP_INLINE_VISIBILITY explicit binary_negate(const _Predicate& __pred)
623227825Stheraven        : __pred_(__pred) {}
624227825Stheraven    _LIBCPP_INLINE_VISIBILITY bool operator()(const typename _Predicate::first_argument_type& __x,
625227825Stheraven                    const typename _Predicate::second_argument_type& __y) const
626227825Stheraven        {return !__pred_(__x, __y);}
627227825Stheraven};
628227825Stheraven
629227825Stheraventemplate <class _Predicate>
630227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
631227825Stheravenbinary_negate<_Predicate>
632227825Stheravennot2(const _Predicate& __pred) {return binary_negate<_Predicate>(__pred);}
633227825Stheraven
634227825Stheraventemplate <class __Operation>
635249998Sdimclass _LIBCPP_TYPE_VIS binder1st
636227825Stheraven    : public unary_function<typename __Operation::second_argument_type,
637227825Stheraven                            typename __Operation::result_type>
638227825Stheraven{
639227825Stheravenprotected:
640227825Stheraven    __Operation                               op;
641227825Stheraven    typename __Operation::first_argument_type value;
642227825Stheravenpublic:
643227825Stheraven    _LIBCPP_INLINE_VISIBILITY binder1st(const __Operation& __x,
644227825Stheraven                               const typename __Operation::first_argument_type __y)
645227825Stheraven        : op(__x), value(__y) {}
646227825Stheraven    _LIBCPP_INLINE_VISIBILITY typename __Operation::result_type operator()
647227825Stheraven        (typename __Operation::second_argument_type& __x) const
648227825Stheraven            {return op(value, __x);}
649227825Stheraven    _LIBCPP_INLINE_VISIBILITY typename __Operation::result_type operator()
650227825Stheraven        (const typename __Operation::second_argument_type& __x) const
651227825Stheraven            {return op(value, __x);}
652227825Stheraven};
653227825Stheraven
654227825Stheraventemplate <class __Operation, class _Tp>
655227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
656227825Stheravenbinder1st<__Operation>
657227825Stheravenbind1st(const __Operation& __op, const _Tp& __x)
658227825Stheraven    {return binder1st<__Operation>(__op, __x);}
659227825Stheraven
660227825Stheraventemplate <class __Operation>
661249998Sdimclass _LIBCPP_TYPE_VIS binder2nd
662227825Stheraven    : public unary_function<typename __Operation::first_argument_type,
663227825Stheraven                            typename __Operation::result_type>
664227825Stheraven{
665227825Stheravenprotected:
666227825Stheraven    __Operation                                op;
667227825Stheraven    typename __Operation::second_argument_type value;
668227825Stheravenpublic:
669227825Stheraven    _LIBCPP_INLINE_VISIBILITY
670227825Stheraven    binder2nd(const __Operation& __x, const typename __Operation::second_argument_type __y)
671227825Stheraven        : op(__x), value(__y) {}
672227825Stheraven    _LIBCPP_INLINE_VISIBILITY typename __Operation::result_type operator()
673227825Stheraven        (      typename __Operation::first_argument_type& __x) const
674227825Stheraven            {return op(__x, value);}
675227825Stheraven    _LIBCPP_INLINE_VISIBILITY typename __Operation::result_type operator()
676227825Stheraven        (const typename __Operation::first_argument_type& __x) const
677227825Stheraven            {return op(__x, value);}
678227825Stheraven};
679227825Stheraven
680227825Stheraventemplate <class __Operation, class _Tp>
681227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
682227825Stheravenbinder2nd<__Operation>
683227825Stheravenbind2nd(const __Operation& __op, const _Tp& __x)
684227825Stheraven    {return binder2nd<__Operation>(__op, __x);}
685227825Stheraven
686227825Stheraventemplate <class _Arg, class _Result>
687249998Sdimclass _LIBCPP_TYPE_VIS pointer_to_unary_function
688227825Stheraven    : public unary_function<_Arg, _Result>
689227825Stheraven{
690227825Stheraven    _Result (*__f_)(_Arg);
691227825Stheravenpublic:
692227825Stheraven    _LIBCPP_INLINE_VISIBILITY explicit pointer_to_unary_function(_Result (*__f)(_Arg))
693227825Stheraven        : __f_(__f) {}
694227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Result operator()(_Arg __x) const
695227825Stheraven        {return __f_(__x);}
696227825Stheraven};
697227825Stheraven
698227825Stheraventemplate <class _Arg, class _Result>
699227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
700227825Stheravenpointer_to_unary_function<_Arg,_Result>
701227825Stheravenptr_fun(_Result (*__f)(_Arg))
702227825Stheraven    {return pointer_to_unary_function<_Arg,_Result>(__f);}
703227825Stheraven
704227825Stheraventemplate <class _Arg1, class _Arg2, class _Result>
705249998Sdimclass _LIBCPP_TYPE_VIS pointer_to_binary_function
706227825Stheraven    : public binary_function<_Arg1, _Arg2, _Result>
707227825Stheraven{
708227825Stheraven    _Result (*__f_)(_Arg1, _Arg2);
709227825Stheravenpublic:
710227825Stheraven    _LIBCPP_INLINE_VISIBILITY explicit pointer_to_binary_function(_Result (*__f)(_Arg1, _Arg2))
711227825Stheraven        : __f_(__f) {}
712227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Result operator()(_Arg1 __x, _Arg2 __y) const
713227825Stheraven        {return __f_(__x, __y);}
714227825Stheraven};
715227825Stheraven
716227825Stheraventemplate <class _Arg1, class _Arg2, class _Result>
717227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
718227825Stheravenpointer_to_binary_function<_Arg1,_Arg2,_Result>
719227825Stheravenptr_fun(_Result (*__f)(_Arg1,_Arg2))
720227825Stheraven    {return pointer_to_binary_function<_Arg1,_Arg2,_Result>(__f);}
721227825Stheraven
722227825Stheraventemplate<class _Sp, class _Tp>
723249998Sdimclass _LIBCPP_TYPE_VIS mem_fun_t : public unary_function<_Tp*, _Sp>
724227825Stheraven{
725227825Stheraven    _Sp (_Tp::*__p_)();
726227825Stheravenpublic:
727227825Stheraven    _LIBCPP_INLINE_VISIBILITY explicit mem_fun_t(_Sp (_Tp::*__p)())
728227825Stheraven        : __p_(__p) {}
729227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Sp operator()(_Tp* __p) const
730227825Stheraven        {return (__p->*__p_)();}
731227825Stheraven};
732227825Stheraven
733227825Stheraventemplate<class _Sp, class _Tp, class _Ap>
734249998Sdimclass _LIBCPP_TYPE_VIS mem_fun1_t : public binary_function<_Tp*, _Ap, _Sp>
735227825Stheraven{
736227825Stheraven    _Sp (_Tp::*__p_)(_Ap);
737227825Stheravenpublic:
738227825Stheraven    _LIBCPP_INLINE_VISIBILITY explicit mem_fun1_t(_Sp (_Tp::*__p)(_Ap))
739227825Stheraven        : __p_(__p) {}
740227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Sp operator()(_Tp* __p, _Ap __x) const
741227825Stheraven        {return (__p->*__p_)(__x);}
742227825Stheraven};
743227825Stheraven
744227825Stheraventemplate<class _Sp, class _Tp>
745227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
746227825Stheravenmem_fun_t<_Sp,_Tp>
747227825Stheravenmem_fun(_Sp (_Tp::*__f)())
748227825Stheraven    {return mem_fun_t<_Sp,_Tp>(__f);}
749227825Stheraven
750227825Stheraventemplate<class _Sp, class _Tp, class _Ap>
751227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
752227825Stheravenmem_fun1_t<_Sp,_Tp,_Ap>
753227825Stheravenmem_fun(_Sp (_Tp::*__f)(_Ap))
754227825Stheraven    {return mem_fun1_t<_Sp,_Tp,_Ap>(__f);}
755227825Stheraven
756227825Stheraventemplate<class _Sp, class _Tp>
757249998Sdimclass _LIBCPP_TYPE_VIS mem_fun_ref_t : public unary_function<_Tp, _Sp>
758227825Stheraven{
759227825Stheraven    _Sp (_Tp::*__p_)();
760227825Stheravenpublic:
761227825Stheraven    _LIBCPP_INLINE_VISIBILITY explicit mem_fun_ref_t(_Sp (_Tp::*__p)())
762227825Stheraven        : __p_(__p) {}
763227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Sp operator()(_Tp& __p) const
764227825Stheraven        {return (__p.*__p_)();}
765227825Stheraven};
766227825Stheraven
767227825Stheraventemplate<class _Sp, class _Tp, class _Ap>
768249998Sdimclass _LIBCPP_TYPE_VIS mem_fun1_ref_t : public binary_function<_Tp, _Ap, _Sp>
769227825Stheraven{
770227825Stheraven    _Sp (_Tp::*__p_)(_Ap);
771227825Stheravenpublic:
772227825Stheraven    _LIBCPP_INLINE_VISIBILITY explicit mem_fun1_ref_t(_Sp (_Tp::*__p)(_Ap))
773227825Stheraven        : __p_(__p) {}
774227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Sp operator()(_Tp& __p, _Ap __x) const
775227825Stheraven        {return (__p.*__p_)(__x);}
776227825Stheraven};
777227825Stheraven
778227825Stheraventemplate<class _Sp, class _Tp>
779227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
780227825Stheravenmem_fun_ref_t<_Sp,_Tp>
781227825Stheravenmem_fun_ref(_Sp (_Tp::*__f)())
782227825Stheraven    {return mem_fun_ref_t<_Sp,_Tp>(__f);}
783227825Stheraven
784227825Stheraventemplate<class _Sp, class _Tp, class _Ap>
785227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
786227825Stheravenmem_fun1_ref_t<_Sp,_Tp,_Ap>
787227825Stheravenmem_fun_ref(_Sp (_Tp::*__f)(_Ap))
788227825Stheraven    {return mem_fun1_ref_t<_Sp,_Tp,_Ap>(__f);}
789227825Stheraven
790227825Stheraventemplate <class _Sp, class _Tp>
791249998Sdimclass _LIBCPP_TYPE_VIS const_mem_fun_t : public unary_function<const _Tp*, _Sp>
792227825Stheraven{
793227825Stheraven    _Sp (_Tp::*__p_)() const;
794227825Stheravenpublic:
795227825Stheraven    _LIBCPP_INLINE_VISIBILITY explicit const_mem_fun_t(_Sp (_Tp::*__p)() const)
796227825Stheraven        : __p_(__p) {}
797227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Sp operator()(const _Tp* __p) const
798227825Stheraven        {return (__p->*__p_)();}
799227825Stheraven};
800227825Stheraven
801227825Stheraventemplate <class _Sp, class _Tp, class _Ap>
802249998Sdimclass _LIBCPP_TYPE_VIS const_mem_fun1_t : public binary_function<const _Tp*, _Ap, _Sp>
803227825Stheraven{
804227825Stheraven    _Sp (_Tp::*__p_)(_Ap) const;
805227825Stheravenpublic:
806227825Stheraven    _LIBCPP_INLINE_VISIBILITY explicit const_mem_fun1_t(_Sp (_Tp::*__p)(_Ap) const)
807227825Stheraven        : __p_(__p) {}
808227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Sp operator()(const _Tp* __p, _Ap __x) const
809227825Stheraven        {return (__p->*__p_)(__x);}
810227825Stheraven};
811227825Stheraven
812227825Stheraventemplate <class _Sp, class _Tp>
813227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
814227825Stheravenconst_mem_fun_t<_Sp,_Tp>
815227825Stheravenmem_fun(_Sp (_Tp::*__f)() const)
816227825Stheraven    {return const_mem_fun_t<_Sp,_Tp>(__f);}
817227825Stheraven
818227825Stheraventemplate <class _Sp, class _Tp, class _Ap>
819227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
820227825Stheravenconst_mem_fun1_t<_Sp,_Tp,_Ap>
821227825Stheravenmem_fun(_Sp (_Tp::*__f)(_Ap) const)
822227825Stheraven    {return const_mem_fun1_t<_Sp,_Tp,_Ap>(__f);}
823227825Stheraven
824227825Stheraventemplate <class _Sp, class _Tp>
825249998Sdimclass _LIBCPP_TYPE_VIS const_mem_fun_ref_t : public unary_function<_Tp, _Sp>
826227825Stheraven{
827227825Stheraven    _Sp (_Tp::*__p_)() const;
828227825Stheravenpublic:
829227825Stheraven    _LIBCPP_INLINE_VISIBILITY explicit const_mem_fun_ref_t(_Sp (_Tp::*__p)() const)
830227825Stheraven        : __p_(__p) {}
831227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Sp operator()(const _Tp& __p) const
832227825Stheraven        {return (__p.*__p_)();}
833227825Stheraven};
834227825Stheraven
835227825Stheraventemplate <class _Sp, class _Tp, class _Ap>
836249998Sdimclass _LIBCPP_TYPE_VIS const_mem_fun1_ref_t
837227825Stheraven    : public binary_function<_Tp, _Ap, _Sp>
838227825Stheraven{
839227825Stheraven    _Sp (_Tp::*__p_)(_Ap) const;
840227825Stheravenpublic:
841227825Stheraven    _LIBCPP_INLINE_VISIBILITY explicit const_mem_fun1_ref_t(_Sp (_Tp::*__p)(_Ap) const)
842227825Stheraven        : __p_(__p) {}
843227825Stheraven    _LIBCPP_INLINE_VISIBILITY _Sp operator()(const _Tp& __p, _Ap __x) const
844227825Stheraven        {return (__p.*__p_)(__x);}
845227825Stheraven};
846227825Stheraven
847227825Stheraventemplate <class _Sp, class _Tp>
848227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
849227825Stheravenconst_mem_fun_ref_t<_Sp,_Tp>
850227825Stheravenmem_fun_ref(_Sp (_Tp::*__f)() const)
851227825Stheraven    {return const_mem_fun_ref_t<_Sp,_Tp>(__f);}
852227825Stheraven
853227825Stheraventemplate <class _Sp, class _Tp, class _Ap>
854227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
855227825Stheravenconst_mem_fun1_ref_t<_Sp,_Tp,_Ap>
856227825Stheravenmem_fun_ref(_Sp (_Tp::*__f)(_Ap) const)
857227825Stheraven    {return const_mem_fun1_ref_t<_Sp,_Tp,_Ap>(__f);}
858227825Stheraven
859227825Stheraven#ifdef _LIBCPP_HAS_NO_VARIADICS
860227825Stheraven
861227825Stheraven#include <__functional_03>
862227825Stheraven
863227825Stheraven#else  // _LIBCPP_HAS_NO_VARIADICS
864227825Stheraven
865227825Stheraventemplate <class _Tp>
866227825Stheravenclass __mem_fn
867227825Stheraven    : public __weak_result_type<_Tp>
868227825Stheraven{
869227825Stheravenpublic:
870227825Stheraven    // types
871227825Stheraven    typedef _Tp type;
872227825Stheravenprivate:
873227825Stheraven    type __f_;
874227825Stheraven
875227825Stheravenpublic:
876227825Stheraven    _LIBCPP_INLINE_VISIBILITY __mem_fn(type __f) : __f_(__f) {}
877227825Stheraven
878227825Stheraven    // invoke
879227825Stheraven    template <class... _ArgTypes>
880227825Stheraven       _LIBCPP_INLINE_VISIBILITY
881227825Stheraven       typename __invoke_return<type, _ArgTypes...>::type
882227825Stheraven          operator() (_ArgTypes&&... __args)
883227825Stheraven          {
884227825Stheraven              return __invoke(__f_, _VSTD::forward<_ArgTypes>(__args)...);
885227825Stheraven          }
886227825Stheraven};
887227825Stheraven
888232950Stheraventemplate<class _Rp, class _Tp>
889227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
890232950Stheraven__mem_fn<_Rp _Tp::*>
891232950Stheravenmem_fn(_Rp _Tp::* __pm)
892227825Stheraven{
893232950Stheraven    return __mem_fn<_Rp _Tp::*>(__pm);
894227825Stheraven}
895227825Stheraven
896232950Stheraventemplate<class _Rp, class _Tp, class ..._Args>
897227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
898232950Stheraven__mem_fn<_Rp (_Tp::*)(_Args...)>
899232950Stheravenmem_fn(_Rp (_Tp::* __pm)(_Args...))
900227825Stheraven{
901232950Stheraven    return __mem_fn<_Rp (_Tp::*)(_Args...)>(__pm);
902227825Stheraven}
903227825Stheraven
904232950Stheraventemplate<class _Rp, class _Tp, class ..._Args>
905227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
906232950Stheraven__mem_fn<_Rp (_Tp::*)(_Args...) const>
907232950Stheravenmem_fn(_Rp (_Tp::* __pm)(_Args...) const)
908227825Stheraven{
909232950Stheraven    return __mem_fn<_Rp (_Tp::*)(_Args...) const>(__pm);
910227825Stheraven}
911227825Stheraven
912232950Stheraventemplate<class _Rp, class _Tp, class ..._Args>
913227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
914232950Stheraven__mem_fn<_Rp (_Tp::*)(_Args...) volatile>
915232950Stheravenmem_fn(_Rp (_Tp::* __pm)(_Args...) volatile)
916227825Stheraven{
917232950Stheraven    return __mem_fn<_Rp (_Tp::*)(_Args...) volatile>(__pm);
918227825Stheraven}
919227825Stheraven
920232950Stheraventemplate<class _Rp, class _Tp, class ..._Args>
921227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
922232950Stheraven__mem_fn<_Rp (_Tp::*)(_Args...) const volatile>
923232950Stheravenmem_fn(_Rp (_Tp::* __pm)(_Args...) const volatile)
924227825Stheraven{
925232950Stheraven    return __mem_fn<_Rp (_Tp::*)(_Args...) const volatile>(__pm);
926227825Stheraven}
927227825Stheraven
928227825Stheraven// bad_function_call
929227825Stheraven
930227825Stheravenclass _LIBCPP_EXCEPTION_ABI bad_function_call
931227825Stheraven    : public exception
932227825Stheraven{
933227825Stheraven};
934227825Stheraven
935249998Sdimtemplate<class _Fp> class _LIBCPP_TYPE_VIS function; // undefined
936227825Stheraven
937227825Stheravennamespace __function
938227825Stheraven{
939227825Stheraven
940232950Stheraventemplate<class _Rp, class ..._ArgTypes>
941227825Stheravenstruct __maybe_derive_from_unary_function
942227825Stheraven{
943227825Stheraven};
944227825Stheraven
945232950Stheraventemplate<class _Rp, class _A1>
946232950Stheravenstruct __maybe_derive_from_unary_function<_Rp(_A1)>
947232950Stheraven    : public unary_function<_A1, _Rp>
948227825Stheraven{
949227825Stheraven};
950227825Stheraven
951232950Stheraventemplate<class _Rp, class ..._ArgTypes>
952227825Stheravenstruct __maybe_derive_from_binary_function
953227825Stheraven{
954227825Stheraven};
955227825Stheraven
956232950Stheraventemplate<class _Rp, class _A1, class _A2>
957232950Stheravenstruct __maybe_derive_from_binary_function<_Rp(_A1, _A2)>
958232950Stheraven    : public binary_function<_A1, _A2, _Rp>
959227825Stheraven{
960227825Stheraven};
961227825Stheraven
962227825Stheraventemplate<class _Fp> class __base;
963227825Stheraven
964232950Stheraventemplate<class _Rp, class ..._ArgTypes>
965232950Stheravenclass __base<_Rp(_ArgTypes...)>
966227825Stheraven{
967227825Stheraven    __base(const __base&);
968227825Stheraven    __base& operator=(const __base&);
969227825Stheravenpublic:
970227825Stheraven    _LIBCPP_INLINE_VISIBILITY __base() {}
971227825Stheraven    _LIBCPP_INLINE_VISIBILITY virtual ~__base() {}
972227825Stheraven    virtual __base* __clone() const = 0;
973227825Stheraven    virtual void __clone(__base*) const = 0;
974227825Stheraven    virtual void destroy() _NOEXCEPT = 0;
975227825Stheraven    virtual void destroy_deallocate() _NOEXCEPT = 0;
976232950Stheraven    virtual _Rp operator()(_ArgTypes&& ...) = 0;
977227825Stheraven#ifndef _LIBCPP_NO_RTTI
978227825Stheraven    virtual const void* target(const type_info&) const _NOEXCEPT = 0;
979227825Stheraven    virtual const std::type_info& target_type() const _NOEXCEPT = 0;
980227825Stheraven#endif  // _LIBCPP_NO_RTTI
981227825Stheraven};
982227825Stheraven
983227825Stheraventemplate<class _FD, class _Alloc, class _FB> class __func;
984227825Stheraven
985232950Stheraventemplate<class _Fp, class _Alloc, class _Rp, class ..._ArgTypes>
986232950Stheravenclass __func<_Fp, _Alloc, _Rp(_ArgTypes...)>
987232950Stheraven    : public  __base<_Rp(_ArgTypes...)>
988227825Stheraven{
989232950Stheraven    __compressed_pair<_Fp, _Alloc> __f_;
990227825Stheravenpublic:
991227825Stheraven    _LIBCPP_INLINE_VISIBILITY
992232950Stheraven    explicit __func(_Fp&& __f)
993232950Stheraven        : __f_(piecewise_construct, _VSTD::forward_as_tuple(_VSTD::move(__f)),
994232950Stheraven                                    _VSTD::forward_as_tuple()) {}
995227825Stheraven    _LIBCPP_INLINE_VISIBILITY
996232950Stheraven    explicit __func(const _Fp& __f, const _Alloc& __a)
997232950Stheraven        : __f_(piecewise_construct, _VSTD::forward_as_tuple(__f),
998232950Stheraven                                    _VSTD::forward_as_tuple(__a)) {}
999232950Stheraven
1000232950Stheraven    _LIBCPP_INLINE_VISIBILITY
1001232950Stheraven    explicit __func(const _Fp& __f, _Alloc&& __a)
1002232950Stheraven        : __f_(piecewise_construct, _VSTD::forward_as_tuple(__f),
1003232950Stheraven                                    _VSTD::forward_as_tuple(_VSTD::move(__a))) {}
1004232950Stheraven
1005232950Stheraven    _LIBCPP_INLINE_VISIBILITY
1006232950Stheraven    explicit __func(_Fp&& __f, _Alloc&& __a)
1007232950Stheraven        : __f_(piecewise_construct, _VSTD::forward_as_tuple(_VSTD::move(__f)),
1008232950Stheraven                                    _VSTD::forward_as_tuple(_VSTD::move(__a))) {}
1009232950Stheraven    virtual __base<_Rp(_ArgTypes...)>* __clone() const;
1010232950Stheraven    virtual void __clone(__base<_Rp(_ArgTypes...)>*) const;
1011227825Stheraven    virtual void destroy() _NOEXCEPT;
1012227825Stheraven    virtual void destroy_deallocate() _NOEXCEPT;
1013232950Stheraven    virtual _Rp operator()(_ArgTypes&& ... __arg);
1014227825Stheraven#ifndef _LIBCPP_NO_RTTI
1015227825Stheraven    virtual const void* target(const type_info&) const _NOEXCEPT;
1016227825Stheraven    virtual const std::type_info& target_type() const _NOEXCEPT;
1017227825Stheraven#endif  // _LIBCPP_NO_RTTI
1018227825Stheraven};
1019227825Stheraven
1020232950Stheraventemplate<class _Fp, class _Alloc, class _Rp, class ..._ArgTypes>
1021232950Stheraven__base<_Rp(_ArgTypes...)>*
1022232950Stheraven__func<_Fp, _Alloc, _Rp(_ArgTypes...)>::__clone() const
1023227825Stheraven{
1024232950Stheraven    typedef typename _Alloc::template rebind<__func>::other _Ap;
1025232950Stheraven    _Ap __a(__f_.second());
1026232950Stheraven    typedef __allocator_destructor<_Ap> _Dp;
1027232950Stheraven    unique_ptr<__func, _Dp> __hold(__a.allocate(1), _Dp(__a, 1));
1028227825Stheraven    ::new (__hold.get()) __func(__f_.first(), _Alloc(__a));
1029227825Stheraven    return __hold.release();
1030227825Stheraven}
1031227825Stheraven
1032232950Stheraventemplate<class _Fp, class _Alloc, class _Rp, class ..._ArgTypes>
1033227825Stheravenvoid
1034232950Stheraven__func<_Fp, _Alloc, _Rp(_ArgTypes...)>::__clone(__base<_Rp(_ArgTypes...)>* __p) const
1035227825Stheraven{
1036227825Stheraven    ::new (__p) __func(__f_.first(), __f_.second());
1037227825Stheraven}
1038227825Stheraven
1039232950Stheraventemplate<class _Fp, class _Alloc, class _Rp, class ..._ArgTypes>
1040227825Stheravenvoid
1041232950Stheraven__func<_Fp, _Alloc, _Rp(_ArgTypes...)>::destroy() _NOEXCEPT
1042227825Stheraven{
1043232950Stheraven    __f_.~__compressed_pair<_Fp, _Alloc>();
1044227825Stheraven}
1045227825Stheraven
1046232950Stheraventemplate<class _Fp, class _Alloc, class _Rp, class ..._ArgTypes>
1047227825Stheravenvoid
1048232950Stheraven__func<_Fp, _Alloc, _Rp(_ArgTypes...)>::destroy_deallocate() _NOEXCEPT
1049227825Stheraven{
1050232950Stheraven    typedef typename _Alloc::template rebind<__func>::other _Ap;
1051232950Stheraven    _Ap __a(__f_.second());
1052232950Stheraven    __f_.~__compressed_pair<_Fp, _Alloc>();
1053227825Stheraven    __a.deallocate(this, 1);
1054227825Stheraven}
1055227825Stheraven
1056232950Stheraventemplate<class _Fp, class _Alloc, class _Rp, class ..._ArgTypes>
1057232950Stheraven_Rp
1058232950Stheraven__func<_Fp, _Alloc, _Rp(_ArgTypes...)>::operator()(_ArgTypes&& ... __arg)
1059227825Stheraven{
1060227825Stheraven    return __invoke(__f_.first(), _VSTD::forward<_ArgTypes>(__arg)...);
1061227825Stheraven}
1062227825Stheraven
1063227825Stheraven#ifndef _LIBCPP_NO_RTTI
1064227825Stheraven
1065232950Stheraventemplate<class _Fp, class _Alloc, class _Rp, class ..._ArgTypes>
1066227825Stheravenconst void*
1067232950Stheraven__func<_Fp, _Alloc, _Rp(_ArgTypes...)>::target(const type_info& __ti) const _NOEXCEPT
1068227825Stheraven{
1069232950Stheraven    if (__ti == typeid(_Fp))
1070227825Stheraven        return &__f_.first();
1071227825Stheraven    return (const void*)0;
1072227825Stheraven}
1073227825Stheraven
1074232950Stheraventemplate<class _Fp, class _Alloc, class _Rp, class ..._ArgTypes>
1075227825Stheravenconst std::type_info&
1076232950Stheraven__func<_Fp, _Alloc, _Rp(_ArgTypes...)>::target_type() const _NOEXCEPT
1077227825Stheraven{
1078232950Stheraven    return typeid(_Fp);
1079227825Stheraven}
1080227825Stheraven
1081227825Stheraven#endif  // _LIBCPP_NO_RTTI
1082227825Stheraven
1083227825Stheraven}  // __function
1084227825Stheraven
1085232950Stheraventemplate<class _Rp, class ..._ArgTypes>
1086249998Sdimclass _LIBCPP_TYPE_VIS function<_Rp(_ArgTypes...)>
1087232950Stheraven    : public __function::__maybe_derive_from_unary_function<_Rp(_ArgTypes...)>,
1088232950Stheraven      public __function::__maybe_derive_from_binary_function<_Rp(_ArgTypes...)>
1089227825Stheraven{
1090232950Stheraven    typedef __function::__base<_Rp(_ArgTypes...)> __base;
1091246487Stheraven    typename aligned_storage<3*sizeof(void*)>::type __buf_;
1092227825Stheraven    __base* __f_;
1093227825Stheraven
1094232950Stheraven    template <class _Fp>
1095227825Stheraven        _LIBCPP_INLINE_VISIBILITY
1096232950Stheraven        static bool __not_null(const _Fp&) {return true;}
1097232950Stheraven    template <class _R2, class ..._Ap>
1098227825Stheraven        _LIBCPP_INLINE_VISIBILITY
1099232950Stheraven        static bool __not_null(_R2 (*__p)(_Ap...)) {return __p;}
1100232950Stheraven    template <class _R2, class _Cp, class ..._Ap>
1101227825Stheraven        _LIBCPP_INLINE_VISIBILITY
1102232950Stheraven        static bool __not_null(_R2 (_Cp::*__p)(_Ap...)) {return __p;}
1103232950Stheraven    template <class _R2, class _Cp, class ..._Ap>
1104227825Stheraven        _LIBCPP_INLINE_VISIBILITY
1105232950Stheraven        static bool __not_null(_R2 (_Cp::*__p)(_Ap...) const) {return __p;}
1106232950Stheraven    template <class _R2, class _Cp, class ..._Ap>
1107227825Stheraven        _LIBCPP_INLINE_VISIBILITY
1108232950Stheraven        static bool __not_null(_R2 (_Cp::*__p)(_Ap...) volatile) {return __p;}
1109232950Stheraven    template <class _R2, class _Cp, class ..._Ap>
1110227825Stheraven        _LIBCPP_INLINE_VISIBILITY
1111232950Stheraven        static bool __not_null(_R2 (_Cp::*__p)(_Ap...) const volatile) {return __p;}
1112232950Stheraven    template <class _R2, class ..._Ap>
1113227825Stheraven        _LIBCPP_INLINE_VISIBILITY
1114232950Stheraven        static bool __not_null(const function<_Rp(_Ap...)>& __p) {return __p;}
1115227825Stheraven
1116241903Sdim    template <class _Fp, bool = !is_same<_Fp, function>::value &&
1117241903Sdim                                __invokable<_Fp&, _ArgTypes...>::value>
1118227825Stheraven        struct __callable;
1119232950Stheraven    template <class _Fp>
1120232950Stheraven        struct __callable<_Fp, true>
1121227825Stheraven        {
1122227825Stheraven            static const bool value =
1123232950Stheraven                is_convertible<typename __invoke_of<_Fp&, _ArgTypes...>::type,
1124232950Stheraven                               _Rp>::value;
1125227825Stheraven        };
1126232950Stheraven    template <class _Fp>
1127232950Stheraven        struct __callable<_Fp, false>
1128227825Stheraven        {
1129227825Stheraven            static const bool value = false;
1130227825Stheraven        };
1131227825Stheravenpublic:
1132232950Stheraven    typedef _Rp result_type;
1133227825Stheraven
1134227825Stheraven    // construct/copy/destroy:
1135227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1136227825Stheraven    function() _NOEXCEPT : __f_(0) {}
1137227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1138227825Stheraven    function(nullptr_t) _NOEXCEPT : __f_(0) {}
1139227825Stheraven    function(const function&);
1140227825Stheraven    function(function&&) _NOEXCEPT;
1141232950Stheraven    template<class _Fp>
1142253159Stheraven      function(_Fp, typename enable_if
1143253159Stheraven                                     <
1144253159Stheraven                                        __callable<_Fp>::value &&
1145253159Stheraven                                        !is_same<_Fp, function>::value
1146253159Stheraven                                      >::type* = 0);
1147227825Stheraven
1148227825Stheraven    template<class _Alloc>
1149227825Stheraven      _LIBCPP_INLINE_VISIBILITY
1150227825Stheraven      function(allocator_arg_t, const _Alloc&) _NOEXCEPT : __f_(0) {}
1151227825Stheraven    template<class _Alloc>
1152227825Stheraven      _LIBCPP_INLINE_VISIBILITY
1153227825Stheraven      function(allocator_arg_t, const _Alloc&, nullptr_t) _NOEXCEPT : __f_(0) {}
1154227825Stheraven    template<class _Alloc>
1155227825Stheraven      function(allocator_arg_t, const _Alloc&, const function&);
1156227825Stheraven    template<class _Alloc>
1157227825Stheraven      function(allocator_arg_t, const _Alloc&, function&&);
1158232950Stheraven    template<class _Fp, class _Alloc>
1159232950Stheraven      function(allocator_arg_t, const _Alloc& __a, _Fp __f,
1160232950Stheraven               typename enable_if<__callable<_Fp>::value>::type* = 0);
1161227825Stheraven
1162227825Stheraven    function& operator=(const function&);
1163227825Stheraven    function& operator=(function&&) _NOEXCEPT;
1164227825Stheraven    function& operator=(nullptr_t) _NOEXCEPT;
1165232950Stheraven    template<class _Fp>
1166227825Stheraven      typename enable_if
1167227825Stheraven      <
1168253159Stheraven        __callable<typename decay<_Fp>::type>::value &&
1169253159Stheraven        !is_same<typename remove_reference<_Fp>::type, function>::value,
1170227825Stheraven        function&
1171227825Stheraven      >::type
1172232950Stheraven      operator=(_Fp&&);
1173227825Stheraven
1174227825Stheraven    ~function();
1175227825Stheraven
1176227825Stheraven    // function modifiers:
1177227825Stheraven    void swap(function&) _NOEXCEPT;
1178232950Stheraven    template<class _Fp, class _Alloc>
1179227825Stheraven      _LIBCPP_INLINE_VISIBILITY
1180232950Stheraven      void assign(_Fp&& __f, const _Alloc& __a)
1181232950Stheraven        {function(allocator_arg, __a, _VSTD::forward<_Fp>(__f)).swap(*this);}
1182227825Stheraven
1183227825Stheraven    // function capacity:
1184227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1185232950Stheraven        _LIBCPP_EXPLICIT operator bool() const _NOEXCEPT {return __f_;}
1186227825Stheraven
1187227825Stheraven    // deleted overloads close possible hole in the type system
1188227825Stheraven    template<class _R2, class... _ArgTypes2>
1189227825Stheraven      bool operator==(const function<_R2(_ArgTypes2...)>&) const = delete;
1190227825Stheraven    template<class _R2, class... _ArgTypes2>
1191227825Stheraven      bool operator!=(const function<_R2(_ArgTypes2...)>&) const = delete;
1192227825Stheravenpublic:
1193227825Stheraven    // function invocation:
1194232950Stheraven    _Rp operator()(_ArgTypes...) const;
1195227825Stheraven
1196227825Stheraven#ifndef _LIBCPP_NO_RTTI
1197227825Stheraven    // function target access:
1198227825Stheraven    const std::type_info& target_type() const _NOEXCEPT;
1199232950Stheraven    template <typename _Tp> _Tp* target() _NOEXCEPT;
1200232950Stheraven    template <typename _Tp> const _Tp* target() const _NOEXCEPT;
1201227825Stheraven#endif  // _LIBCPP_NO_RTTI
1202227825Stheraven};
1203227825Stheraven
1204232950Stheraventemplate<class _Rp, class ..._ArgTypes>
1205232950Stheravenfunction<_Rp(_ArgTypes...)>::function(const function& __f)
1206227825Stheraven{
1207227825Stheraven    if (__f.__f_ == 0)
1208227825Stheraven        __f_ = 0;
1209227825Stheraven    else if (__f.__f_ == (const __base*)&__f.__buf_)
1210227825Stheraven    {
1211227825Stheraven        __f_ = (__base*)&__buf_;
1212227825Stheraven        __f.__f_->__clone(__f_);
1213227825Stheraven    }
1214227825Stheraven    else
1215227825Stheraven        __f_ = __f.__f_->__clone();
1216227825Stheraven}
1217227825Stheraven
1218232950Stheraventemplate<class _Rp, class ..._ArgTypes>
1219227825Stheraventemplate <class _Alloc>
1220232950Stheravenfunction<_Rp(_ArgTypes...)>::function(allocator_arg_t, const _Alloc&,
1221227825Stheraven                                     const function& __f)
1222227825Stheraven{
1223227825Stheraven    if (__f.__f_ == 0)
1224227825Stheraven        __f_ = 0;
1225227825Stheraven    else if (__f.__f_ == (const __base*)&__f.__buf_)
1226227825Stheraven    {
1227227825Stheraven        __f_ = (__base*)&__buf_;
1228227825Stheraven        __f.__f_->__clone(__f_);
1229227825Stheraven    }
1230227825Stheraven    else
1231227825Stheraven        __f_ = __f.__f_->__clone();
1232227825Stheraven}
1233227825Stheraven
1234232950Stheraventemplate<class _Rp, class ..._ArgTypes>
1235232950Stheravenfunction<_Rp(_ArgTypes...)>::function(function&& __f) _NOEXCEPT
1236227825Stheraven{
1237227825Stheraven    if (__f.__f_ == 0)
1238227825Stheraven        __f_ = 0;
1239227825Stheraven    else if (__f.__f_ == (__base*)&__f.__buf_)
1240227825Stheraven    {
1241227825Stheraven        __f_ = (__base*)&__buf_;
1242227825Stheraven        __f.__f_->__clone(__f_);
1243227825Stheraven    }
1244227825Stheraven    else
1245227825Stheraven    {
1246227825Stheraven        __f_ = __f.__f_;
1247227825Stheraven        __f.__f_ = 0;
1248227825Stheraven    }
1249227825Stheraven}
1250227825Stheraven
1251232950Stheraventemplate<class _Rp, class ..._ArgTypes>
1252227825Stheraventemplate <class _Alloc>
1253232950Stheravenfunction<_Rp(_ArgTypes...)>::function(allocator_arg_t, const _Alloc&,
1254227825Stheraven                                     function&& __f)
1255227825Stheraven{
1256227825Stheraven    if (__f.__f_ == 0)
1257227825Stheraven        __f_ = 0;
1258227825Stheraven    else if (__f.__f_ == (__base*)&__f.__buf_)
1259227825Stheraven    {
1260227825Stheraven        __f_ = (__base*)&__buf_;
1261227825Stheraven        __f.__f_->__clone(__f_);
1262227825Stheraven    }
1263227825Stheraven    else
1264227825Stheraven    {
1265227825Stheraven        __f_ = __f.__f_;
1266227825Stheraven        __f.__f_ = 0;
1267227825Stheraven    }
1268227825Stheraven}
1269227825Stheraven
1270232950Stheraventemplate<class _Rp, class ..._ArgTypes>
1271232950Stheraventemplate <class _Fp>
1272232950Stheravenfunction<_Rp(_ArgTypes...)>::function(_Fp __f,
1273253159Stheraven                                     typename enable_if
1274253159Stheraven                                     <
1275253159Stheraven                                        __callable<_Fp>::value &&
1276253159Stheraven                                        !is_same<_Fp, function>::value
1277253159Stheraven                                     >::type*)
1278227825Stheraven    : __f_(0)
1279227825Stheraven{
1280227825Stheraven    if (__not_null(__f))
1281227825Stheraven    {
1282232950Stheraven        typedef __function::__func<_Fp, allocator<_Fp>, _Rp(_ArgTypes...)> _FF;
1283232950Stheraven        if (sizeof(_FF) <= sizeof(__buf_) && is_nothrow_copy_constructible<_Fp>::value)
1284227825Stheraven        {
1285227825Stheraven            __f_ = (__base*)&__buf_;
1286227825Stheraven            ::new (__f_) _FF(_VSTD::move(__f));
1287227825Stheraven        }
1288227825Stheraven        else
1289227825Stheraven        {
1290232950Stheraven            typedef allocator<_FF> _Ap;
1291232950Stheraven            _Ap __a;
1292232950Stheraven            typedef __allocator_destructor<_Ap> _Dp;
1293232950Stheraven            unique_ptr<__base, _Dp> __hold(__a.allocate(1), _Dp(__a, 1));
1294232950Stheraven            ::new (__hold.get()) _FF(_VSTD::move(__f), allocator<_Fp>(__a));
1295227825Stheraven            __f_ = __hold.release();
1296227825Stheraven        }
1297227825Stheraven    }
1298227825Stheraven}
1299227825Stheraven
1300232950Stheraventemplate<class _Rp, class ..._ArgTypes>
1301232950Stheraventemplate <class _Fp, class _Alloc>
1302232950Stheravenfunction<_Rp(_ArgTypes...)>::function(allocator_arg_t, const _Alloc& __a0, _Fp __f,
1303232950Stheraven                                     typename enable_if<__callable<_Fp>::value>::type*)
1304227825Stheraven    : __f_(0)
1305227825Stheraven{
1306227825Stheraven    typedef allocator_traits<_Alloc> __alloc_traits;
1307227825Stheraven    if (__not_null(__f))
1308227825Stheraven    {
1309232950Stheraven        typedef __function::__func<_Fp, _Alloc, _Rp(_ArgTypes...)> _FF;
1310232950Stheraven        if (sizeof(_FF) <= sizeof(__buf_) && is_nothrow_copy_constructible<_Fp>::value)
1311227825Stheraven        {
1312227825Stheraven            __f_ = (__base*)&__buf_;
1313227825Stheraven            ::new (__f_) _FF(_VSTD::move(__f));
1314227825Stheraven        }
1315227825Stheraven        else
1316227825Stheraven        {
1317227825Stheraven            typedef typename __alloc_traits::template
1318227825Stheraven#ifndef _LIBCPP_HAS_NO_TEMPLATE_ALIASES
1319227825Stheraven                rebind_alloc<_FF>
1320227825Stheraven#else
1321227825Stheraven                rebind_alloc<_FF>::other
1322227825Stheraven#endif
1323232950Stheraven                                                         _Ap;
1324232950Stheraven            _Ap __a(__a0);
1325232950Stheraven            typedef __allocator_destructor<_Ap> _Dp;
1326232950Stheraven            unique_ptr<__base, _Dp> __hold(__a.allocate(1), _Dp(__a, 1));
1327227825Stheraven            ::new (__hold.get()) _FF(_VSTD::move(__f), _Alloc(__a));
1328227825Stheraven            __f_ = __hold.release();
1329227825Stheraven        }
1330227825Stheraven    }
1331227825Stheraven}
1332227825Stheraven
1333232950Stheraventemplate<class _Rp, class ..._ArgTypes>
1334232950Stheravenfunction<_Rp(_ArgTypes...)>&
1335232950Stheravenfunction<_Rp(_ArgTypes...)>::operator=(const function& __f)
1336227825Stheraven{
1337227825Stheraven    function(__f).swap(*this);
1338227825Stheraven    return *this;
1339227825Stheraven}
1340227825Stheraven
1341232950Stheraventemplate<class _Rp, class ..._ArgTypes>
1342232950Stheravenfunction<_Rp(_ArgTypes...)>&
1343232950Stheravenfunction<_Rp(_ArgTypes...)>::operator=(function&& __f) _NOEXCEPT
1344227825Stheraven{
1345227825Stheraven    if (__f_ == (__base*)&__buf_)
1346227825Stheraven        __f_->destroy();
1347227825Stheraven    else if (__f_)
1348227825Stheraven        __f_->destroy_deallocate();
1349227825Stheraven    __f_ = 0;
1350227825Stheraven    if (__f.__f_ == 0)
1351227825Stheraven        __f_ = 0;
1352227825Stheraven    else if (__f.__f_ == (__base*)&__f.__buf_)
1353227825Stheraven    {
1354227825Stheraven        __f_ = (__base*)&__buf_;
1355227825Stheraven        __f.__f_->__clone(__f_);
1356227825Stheraven    }
1357227825Stheraven    else
1358227825Stheraven    {
1359227825Stheraven        __f_ = __f.__f_;
1360227825Stheraven        __f.__f_ = 0;
1361227825Stheraven    }
1362241903Sdim    return *this;
1363227825Stheraven}
1364227825Stheraven
1365232950Stheraventemplate<class _Rp, class ..._ArgTypes>
1366232950Stheravenfunction<_Rp(_ArgTypes...)>&
1367232950Stheravenfunction<_Rp(_ArgTypes...)>::operator=(nullptr_t) _NOEXCEPT
1368227825Stheraven{
1369227825Stheraven    if (__f_ == (__base*)&__buf_)
1370227825Stheraven        __f_->destroy();
1371227825Stheraven    else if (__f_)
1372227825Stheraven        __f_->destroy_deallocate();
1373227825Stheraven    __f_ = 0;
1374241903Sdim    return *this;
1375227825Stheraven}
1376227825Stheraven
1377232950Stheraventemplate<class _Rp, class ..._ArgTypes>
1378232950Stheraventemplate <class _Fp>
1379227825Stheraventypename enable_if
1380227825Stheraven<
1381253159Stheraven    function<_Rp(_ArgTypes...)>::template __callable<typename decay<_Fp>::type>::value &&
1382253159Stheraven    !is_same<typename remove_reference<_Fp>::type, function<_Rp(_ArgTypes...)>>::value,
1383232950Stheraven    function<_Rp(_ArgTypes...)>&
1384227825Stheraven>::type
1385232950Stheravenfunction<_Rp(_ArgTypes...)>::operator=(_Fp&& __f)
1386227825Stheraven{
1387232950Stheraven    function(_VSTD::forward<_Fp>(__f)).swap(*this);
1388227825Stheraven    return *this;
1389227825Stheraven}
1390227825Stheraven
1391232950Stheraventemplate<class _Rp, class ..._ArgTypes>
1392232950Stheravenfunction<_Rp(_ArgTypes...)>::~function()
1393227825Stheraven{
1394227825Stheraven    if (__f_ == (__base*)&__buf_)
1395227825Stheraven        __f_->destroy();
1396227825Stheraven    else if (__f_)
1397227825Stheraven        __f_->destroy_deallocate();
1398227825Stheraven}
1399227825Stheraven
1400232950Stheraventemplate<class _Rp, class ..._ArgTypes>
1401227825Stheravenvoid
1402232950Stheravenfunction<_Rp(_ArgTypes...)>::swap(function& __f) _NOEXCEPT
1403227825Stheraven{
1404227825Stheraven    if (__f_ == (__base*)&__buf_ && __f.__f_ == (__base*)&__f.__buf_)
1405227825Stheraven    {
1406227825Stheraven        typename aligned_storage<sizeof(__buf_)>::type __tempbuf;
1407227825Stheraven        __base* __t = (__base*)&__tempbuf;
1408227825Stheraven        __f_->__clone(__t);
1409227825Stheraven        __f_->destroy();
1410227825Stheraven        __f_ = 0;
1411227825Stheraven        __f.__f_->__clone((__base*)&__buf_);
1412227825Stheraven        __f.__f_->destroy();
1413227825Stheraven        __f.__f_ = 0;
1414227825Stheraven        __f_ = (__base*)&__buf_;
1415227825Stheraven        __t->__clone((__base*)&__f.__buf_);
1416227825Stheraven        __t->destroy();
1417227825Stheraven        __f.__f_ = (__base*)&__f.__buf_;
1418227825Stheraven    }
1419227825Stheraven    else if (__f_ == (__base*)&__buf_)
1420227825Stheraven    {
1421227825Stheraven        __f_->__clone((__base*)&__f.__buf_);
1422227825Stheraven        __f_->destroy();
1423227825Stheraven        __f_ = __f.__f_;
1424227825Stheraven        __f.__f_ = (__base*)&__f.__buf_;
1425227825Stheraven    }
1426227825Stheraven    else if (__f.__f_ == (__base*)&__f.__buf_)
1427227825Stheraven    {
1428227825Stheraven        __f.__f_->__clone((__base*)&__buf_);
1429227825Stheraven        __f.__f_->destroy();
1430227825Stheraven        __f.__f_ = __f_;
1431227825Stheraven        __f_ = (__base*)&__buf_;
1432227825Stheraven    }
1433227825Stheraven    else
1434227825Stheraven        _VSTD::swap(__f_, __f.__f_);
1435227825Stheraven}
1436227825Stheraven
1437232950Stheraventemplate<class _Rp, class ..._ArgTypes>
1438232950Stheraven_Rp
1439232950Stheravenfunction<_Rp(_ArgTypes...)>::operator()(_ArgTypes... __arg) const
1440227825Stheraven{
1441227825Stheraven#ifndef _LIBCPP_NO_EXCEPTIONS
1442227825Stheraven    if (__f_ == 0)
1443227825Stheraven        throw bad_function_call();
1444227825Stheraven#endif  // _LIBCPP_NO_EXCEPTIONS
1445227825Stheraven    return (*__f_)(_VSTD::forward<_ArgTypes>(__arg)...);
1446227825Stheraven}
1447227825Stheraven
1448227825Stheraven#ifndef _LIBCPP_NO_RTTI
1449227825Stheraven
1450232950Stheraventemplate<class _Rp, class ..._ArgTypes>
1451227825Stheravenconst std::type_info&
1452232950Stheravenfunction<_Rp(_ArgTypes...)>::target_type() const _NOEXCEPT
1453227825Stheraven{
1454227825Stheraven    if (__f_ == 0)
1455227825Stheraven        return typeid(void);
1456227825Stheraven    return __f_->target_type();
1457227825Stheraven}
1458227825Stheraven
1459232950Stheraventemplate<class _Rp, class ..._ArgTypes>
1460232950Stheraventemplate <typename _Tp>
1461232950Stheraven_Tp*
1462232950Stheravenfunction<_Rp(_ArgTypes...)>::target() _NOEXCEPT
1463227825Stheraven{
1464227825Stheraven    if (__f_ == 0)
1465232950Stheraven        return (_Tp*)0;
1466232950Stheraven    return (_Tp*)__f_->target(typeid(_Tp));
1467227825Stheraven}
1468227825Stheraven
1469232950Stheraventemplate<class _Rp, class ..._ArgTypes>
1470232950Stheraventemplate <typename _Tp>
1471232950Stheravenconst _Tp*
1472232950Stheravenfunction<_Rp(_ArgTypes...)>::target() const _NOEXCEPT
1473227825Stheraven{
1474227825Stheraven    if (__f_ == 0)
1475232950Stheraven        return (const _Tp*)0;
1476232950Stheraven    return (const _Tp*)__f_->target(typeid(_Tp));
1477227825Stheraven}
1478227825Stheraven
1479227825Stheraven#endif  // _LIBCPP_NO_RTTI
1480227825Stheraven
1481232950Stheraventemplate <class _Rp, class... _ArgTypes>
1482227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
1483227825Stheravenbool
1484232950Stheravenoperator==(const function<_Rp(_ArgTypes...)>& __f, nullptr_t) _NOEXCEPT {return !__f;}
1485227825Stheraven
1486232950Stheraventemplate <class _Rp, class... _ArgTypes>
1487227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
1488227825Stheravenbool
1489232950Stheravenoperator==(nullptr_t, const function<_Rp(_ArgTypes...)>& __f) _NOEXCEPT {return !__f;}
1490227825Stheraven
1491232950Stheraventemplate <class _Rp, class... _ArgTypes>
1492227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
1493227825Stheravenbool
1494232950Stheravenoperator!=(const function<_Rp(_ArgTypes...)>& __f, nullptr_t) _NOEXCEPT {return (bool)__f;}
1495227825Stheraven
1496232950Stheraventemplate <class _Rp, class... _ArgTypes>
1497227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
1498227825Stheravenbool
1499232950Stheravenoperator!=(nullptr_t, const function<_Rp(_ArgTypes...)>& __f) _NOEXCEPT {return (bool)__f;}
1500227825Stheraven
1501232950Stheraventemplate <class _Rp, class... _ArgTypes>
1502227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
1503227825Stheravenvoid
1504232950Stheravenswap(function<_Rp(_ArgTypes...)>& __x, function<_Rp(_ArgTypes...)>& __y) _NOEXCEPT
1505227825Stheraven{return __x.swap(__y);}
1506227825Stheraven
1507227825Stheraventemplate<class _Tp> struct __is_bind_expression : public false_type {};
1508249998Sdimtemplate<class _Tp> struct _LIBCPP_TYPE_VIS is_bind_expression
1509227825Stheraven    : public __is_bind_expression<typename remove_cv<_Tp>::type> {};
1510227825Stheraven
1511227825Stheraventemplate<class _Tp> struct __is_placeholder : public integral_constant<int, 0> {};
1512249998Sdimtemplate<class _Tp> struct _LIBCPP_TYPE_VIS is_placeholder
1513227825Stheraven    : public __is_placeholder<typename remove_cv<_Tp>::type> {};
1514227825Stheraven
1515227825Stheravennamespace placeholders
1516227825Stheraven{
1517227825Stheraven
1518232950Stheraventemplate <int _Np> struct __ph {};
1519227825Stheraven
1520227825Stheravenextern __ph<1>   _1;
1521227825Stheravenextern __ph<2>   _2;
1522227825Stheravenextern __ph<3>   _3;
1523227825Stheravenextern __ph<4>   _4;
1524227825Stheravenextern __ph<5>   _5;
1525227825Stheravenextern __ph<6>   _6;
1526227825Stheravenextern __ph<7>   _7;
1527227825Stheravenextern __ph<8>   _8;
1528227825Stheravenextern __ph<9>   _9;
1529227825Stheravenextern __ph<10> _10;
1530227825Stheraven
1531227825Stheraven}  // placeholders
1532227825Stheraven
1533232950Stheraventemplate<int _Np>
1534232950Stheravenstruct __is_placeholder<placeholders::__ph<_Np> >
1535232950Stheraven    : public integral_constant<int, _Np> {};
1536227825Stheraven
1537227825Stheraventemplate <class _Tp, class _Uj>
1538227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
1539227825Stheraven_Tp&
1540227825Stheraven__mu(reference_wrapper<_Tp> __t, _Uj&)
1541227825Stheraven{
1542227825Stheraven    return __t.get();
1543227825Stheraven}
1544227825Stheraven
1545227825Stheraventemplate <class _Ti, class ..._Uj, size_t ..._Indx>
1546227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
1547227825Stheraventypename __invoke_of<_Ti&, _Uj...>::type
1548227825Stheraven__mu_expand(_Ti& __ti, tuple<_Uj...>& __uj, __tuple_indices<_Indx...>)
1549227825Stheraven{
1550227825Stheraven    return __ti(_VSTD::forward<_Uj>(get<_Indx>(__uj))...);
1551227825Stheraven}
1552227825Stheraven
1553227825Stheraventemplate <class _Ti, class ..._Uj>
1554227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
1555227825Stheraventypename enable_if
1556227825Stheraven<
1557227825Stheraven    is_bind_expression<_Ti>::value,
1558227825Stheraven    typename __invoke_of<_Ti&, _Uj...>::type
1559227825Stheraven>::type
1560227825Stheraven__mu(_Ti& __ti, tuple<_Uj...>& __uj)
1561227825Stheraven{
1562227825Stheraven    typedef typename __make_tuple_indices<sizeof...(_Uj)>::type __indices;
1563227825Stheraven    return  __mu_expand(__ti, __uj, __indices());
1564227825Stheraven}
1565227825Stheraven
1566227825Stheraventemplate <bool IsPh, class _Ti, class _Uj>
1567227825Stheravenstruct __mu_return2 {};
1568227825Stheraven
1569227825Stheraventemplate <class _Ti, class _Uj>
1570227825Stheravenstruct __mu_return2<true, _Ti, _Uj>
1571227825Stheraven{
1572227825Stheraven    typedef typename tuple_element<is_placeholder<_Ti>::value - 1, _Uj>::type type;
1573227825Stheraven};
1574227825Stheraven
1575227825Stheraventemplate <class _Ti, class _Uj>
1576227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
1577227825Stheraventypename enable_if
1578227825Stheraven<
1579227825Stheraven    0 < is_placeholder<_Ti>::value,
1580227825Stheraven    typename __mu_return2<0 < is_placeholder<_Ti>::value, _Ti, _Uj>::type
1581227825Stheraven>::type
1582227825Stheraven__mu(_Ti&, _Uj& __uj)
1583227825Stheraven{
1584227825Stheraven    const size_t _Indx = is_placeholder<_Ti>::value - 1;
1585227825Stheraven    return _VSTD::forward<typename tuple_element<_Indx, _Uj>::type>(get<_Indx>(__uj));
1586227825Stheraven}
1587227825Stheraven
1588227825Stheraventemplate <class _Ti, class _Uj>
1589227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
1590227825Stheraventypename enable_if
1591227825Stheraven<
1592227825Stheraven    !is_bind_expression<_Ti>::value &&
1593227825Stheraven    is_placeholder<_Ti>::value == 0 &&
1594227825Stheraven    !__is_reference_wrapper<_Ti>::value,
1595227825Stheraven    _Ti&
1596227825Stheraven>::type
1597232950Stheraven__mu(_Ti& __ti, _Uj&)
1598227825Stheraven{
1599227825Stheraven    return __ti;
1600227825Stheraven}
1601227825Stheraven
1602227825Stheraventemplate <class _Ti, bool IsReferenceWrapper, bool IsBindEx, bool IsPh,
1603227825Stheraven          class _TupleUj>
1604227825Stheravenstruct ____mu_return;
1605227825Stheraven
1606253159Stheraventemplate <bool _Invokable, class _Ti, class ..._Uj>
1607253159Stheravenstruct ____mu_return_invokable  // false
1608253159Stheraven{
1609253159Stheraven    typedef __nat type;
1610253159Stheraven};
1611253159Stheraven
1612227825Stheraventemplate <class _Ti, class ..._Uj>
1613253159Stheravenstruct ____mu_return_invokable<true, _Ti, _Uj...>
1614227825Stheraven{
1615227825Stheraven    typedef typename __invoke_of<_Ti&, _Uj...>::type type;
1616227825Stheraven};
1617227825Stheraven
1618253159Stheraventemplate <class _Ti, class ..._Uj>
1619253159Stheravenstruct ____mu_return<_Ti, false, true, false, tuple<_Uj...> >
1620253159Stheraven    : public ____mu_return_invokable<__invokable<_Ti&, _Uj...>::value, _Ti, _Uj...>
1621253159Stheraven{
1622253159Stheraven};
1623253159Stheraven
1624227825Stheraventemplate <class _Ti, class _TupleUj>
1625227825Stheravenstruct ____mu_return<_Ti, false, false, true, _TupleUj>
1626227825Stheraven{
1627227825Stheraven    typedef typename tuple_element<is_placeholder<_Ti>::value - 1,
1628227825Stheraven                                   _TupleUj>::type&& type;
1629227825Stheraven};
1630227825Stheraven
1631227825Stheraventemplate <class _Ti, class _TupleUj>
1632227825Stheravenstruct ____mu_return<_Ti, true, false, false, _TupleUj>
1633227825Stheraven{
1634227825Stheraven    typedef typename _Ti::type& type;
1635227825Stheraven};
1636227825Stheraven
1637227825Stheraventemplate <class _Ti, class _TupleUj>
1638227825Stheravenstruct ____mu_return<_Ti, false, false, false, _TupleUj>
1639227825Stheraven{
1640227825Stheraven    typedef _Ti& type;
1641227825Stheraven};
1642227825Stheraven
1643227825Stheraventemplate <class _Ti, class _TupleUj>
1644227825Stheravenstruct __mu_return
1645227825Stheraven    : public ____mu_return<_Ti,
1646227825Stheraven                           __is_reference_wrapper<_Ti>::value,
1647227825Stheraven                           is_bind_expression<_Ti>::value,
1648249998Sdim                           0 < is_placeholder<_Ti>::value &&
1649249998Sdim                           is_placeholder<_Ti>::value <= tuple_size<_TupleUj>::value,
1650227825Stheraven                           _TupleUj>
1651227825Stheraven{
1652227825Stheraven};
1653227825Stheraven
1654232950Stheraventemplate <class _Fp, class _BoundArgs, class _TupleUj>
1655249998Sdimstruct _is_valid_bind_return
1656249998Sdim{
1657249998Sdim    static const bool value = false;
1658249998Sdim};
1659249998Sdim
1660249998Sdimtemplate <class _Fp, class ..._BoundArgs, class _TupleUj>
1661249998Sdimstruct _is_valid_bind_return<_Fp, tuple<_BoundArgs...>, _TupleUj>
1662249998Sdim{
1663249998Sdim    static const bool value = __invokable<_Fp,
1664249998Sdim                    typename __mu_return<_BoundArgs, _TupleUj>::type...>::value;
1665249998Sdim};
1666249998Sdim
1667249998Sdimtemplate <class _Fp, class ..._BoundArgs, class _TupleUj>
1668249998Sdimstruct _is_valid_bind_return<_Fp, const tuple<_BoundArgs...>, _TupleUj>
1669249998Sdim{
1670249998Sdim    static const bool value = __invokable<_Fp,
1671249998Sdim                    typename __mu_return<const _BoundArgs, _TupleUj>::type...>::value;
1672249998Sdim};
1673249998Sdim
1674249998Sdimtemplate <class _Fp, class _BoundArgs, class _TupleUj,
1675249998Sdim          bool = _is_valid_bind_return<_Fp, _BoundArgs, _TupleUj>::value>
1676227825Stheravenstruct __bind_return;
1677227825Stheraven
1678232950Stheraventemplate <class _Fp, class ..._BoundArgs, class _TupleUj>
1679249998Sdimstruct __bind_return<_Fp, tuple<_BoundArgs...>, _TupleUj, true>
1680227825Stheraven{
1681227825Stheraven    typedef typename __invoke_of
1682227825Stheraven    <
1683232950Stheraven        _Fp&,
1684227825Stheraven        typename __mu_return
1685227825Stheraven        <
1686227825Stheraven            _BoundArgs,
1687227825Stheraven            _TupleUj
1688227825Stheraven        >::type...
1689227825Stheraven    >::type type;
1690227825Stheraven};
1691227825Stheraven
1692232950Stheraventemplate <class _Fp, class ..._BoundArgs, class _TupleUj>
1693249998Sdimstruct __bind_return<_Fp, const tuple<_BoundArgs...>, _TupleUj, true>
1694227825Stheraven{
1695227825Stheraven    typedef typename __invoke_of
1696227825Stheraven    <
1697232950Stheraven        _Fp&,
1698227825Stheraven        typename __mu_return
1699227825Stheraven        <
1700227825Stheraven            const _BoundArgs,
1701227825Stheraven            _TupleUj
1702227825Stheraven        >::type...
1703227825Stheraven    >::type type;
1704227825Stheraven};
1705227825Stheraven
1706232950Stheraventemplate <class _Fp, class _BoundArgs, size_t ..._Indx, class _Args>
1707227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
1708232950Stheraventypename __bind_return<_Fp, _BoundArgs, _Args>::type
1709232950Stheraven__apply_functor(_Fp& __f, _BoundArgs& __bound_args, __tuple_indices<_Indx...>,
1710227825Stheraven                _Args&& __args)
1711227825Stheraven{
1712227825Stheraven    return __invoke(__f, __mu(get<_Indx>(__bound_args), __args)...);
1713227825Stheraven}
1714227825Stheraven
1715232950Stheraventemplate<class _Fp, class ..._BoundArgs>
1716227825Stheravenclass __bind
1717232950Stheraven    : public __weak_result_type<typename decay<_Fp>::type>
1718227825Stheraven{
1719249998Sdimprotected:
1720232950Stheraven    typedef typename decay<_Fp>::type _Fd;
1721227825Stheraven    typedef tuple<typename decay<_BoundArgs>::type...> _Td;
1722249998Sdimprivate:
1723227825Stheraven    _Fd __f_;
1724227825Stheraven    _Td __bound_args_;
1725227825Stheraven
1726227825Stheraven    typedef typename __make_tuple_indices<sizeof...(_BoundArgs)>::type __indices;
1727227825Stheravenpublic:
1728227825Stheraven#ifdef _LIBCPP_HAS_NO_DEFAULTED_FUNCTIONS
1729227825Stheraven
1730227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1731227825Stheraven    __bind(const __bind& __b)
1732227825Stheraven        : __f_(__b.__f_),
1733227825Stheraven          __bound_args_(__b.__bound_args_) {}
1734227825Stheraven
1735227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1736227825Stheraven    __bind& operator=(const __bind& __b)
1737227825Stheraven    {
1738227825Stheraven        __f_ = __b.__f_;
1739227825Stheraven        __bound_args_ = __b.__bound_args_;
1740227825Stheraven        return *this;
1741227825Stheraven    }
1742227825Stheraven
1743227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1744227825Stheraven    __bind(__bind&& __b)
1745227825Stheraven        : __f_(_VSTD::move(__b.__f_)),
1746227825Stheraven          __bound_args_(_VSTD::move(__b.__bound_args_)) {}
1747227825Stheraven
1748227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1749227825Stheraven    __bind& operator=(__bind&& __b)
1750227825Stheraven    {
1751227825Stheraven        __f_ = _VSTD::move(__b.__f_);
1752227825Stheraven        __bound_args_ = _VSTD::move(__b.__bound_args_);
1753227825Stheraven        return *this;
1754227825Stheraven    }
1755227825Stheraven
1756227825Stheraven#endif  // _LIBCPP_HAS_NO_DEFAULTED_FUNCTIONS
1757227825Stheraven
1758241903Sdim    template <class _Gp, class ..._BA,
1759241903Sdim              class = typename enable_if
1760241903Sdim                               <
1761253159Stheraven                                  is_constructible<_Fd, _Gp>::value &&
1762253159Stheraven                                  !is_same<typename remove_reference<_Gp>::type,
1763253159Stheraven                                           __bind>::value
1764241903Sdim                               >::type>
1765227825Stheraven      _LIBCPP_INLINE_VISIBILITY
1766232950Stheraven      explicit __bind(_Gp&& __f, _BA&& ...__bound_args)
1767232950Stheraven        : __f_(_VSTD::forward<_Gp>(__f)),
1768227825Stheraven          __bound_args_(_VSTD::forward<_BA>(__bound_args)...) {}
1769227825Stheraven
1770227825Stheraven    template <class ..._Args>
1771227825Stheraven        _LIBCPP_INLINE_VISIBILITY
1772227825Stheraven        typename __bind_return<_Fd, _Td, tuple<_Args&&...> >::type
1773227825Stheraven        operator()(_Args&& ...__args)
1774227825Stheraven        {
1775227825Stheraven            return __apply_functor(__f_, __bound_args_, __indices(),
1776227825Stheraven                                  tuple<_Args&&...>(_VSTD::forward<_Args>(__args)...));
1777227825Stheraven        }
1778227825Stheraven
1779227825Stheraven    template <class ..._Args>
1780227825Stheraven        _LIBCPP_INLINE_VISIBILITY
1781249998Sdim        typename __bind_return<const _Fd, const _Td, tuple<_Args&&...> >::type
1782227825Stheraven        operator()(_Args&& ...__args) const
1783227825Stheraven        {
1784227825Stheraven            return __apply_functor(__f_, __bound_args_, __indices(),
1785227825Stheraven                                   tuple<_Args&&...>(_VSTD::forward<_Args>(__args)...));
1786227825Stheraven        }
1787227825Stheraven};
1788227825Stheraven
1789232950Stheraventemplate<class _Fp, class ..._BoundArgs>
1790232950Stheravenstruct __is_bind_expression<__bind<_Fp, _BoundArgs...> > : public true_type {};
1791227825Stheraven
1792232950Stheraventemplate<class _Rp, class _Fp, class ..._BoundArgs>
1793227825Stheravenclass __bind_r
1794232950Stheraven    : public __bind<_Fp, _BoundArgs...>
1795227825Stheraven{
1796232950Stheraven    typedef __bind<_Fp, _BoundArgs...> base;
1797249998Sdim    typedef typename base::_Fd _Fd;
1798249998Sdim    typedef typename base::_Td _Td;
1799227825Stheravenpublic:
1800232950Stheraven    typedef _Rp result_type;
1801227825Stheraven
1802227825Stheraven#ifdef _LIBCPP_HAS_NO_DEFAULTED_FUNCTIONS
1803227825Stheraven
1804227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1805227825Stheraven    __bind_r(const __bind_r& __b)
1806227825Stheraven        : base(_VSTD::forward<const base&>(__b)) {}
1807227825Stheraven
1808227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1809227825Stheraven    __bind_r& operator=(const __bind_r& __b)
1810227825Stheraven    {
1811227825Stheraven        base::operator=(_VSTD::forward<const base&>(__b));
1812227825Stheraven        return *this;
1813227825Stheraven    }
1814227825Stheraven
1815227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1816227825Stheraven    __bind_r(__bind_r&& __b)
1817227825Stheraven        : base(_VSTD::forward<base>(__b)) {}
1818227825Stheraven
1819227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1820227825Stheraven    __bind_r& operator=(__bind_r&& __b)
1821227825Stheraven    {
1822227825Stheraven        base::operator=(_VSTD::forward<base>(__b));
1823227825Stheraven        return *this;
1824227825Stheraven    }
1825227825Stheraven
1826227825Stheraven#endif  // _LIBCPP_HAS_NO_DEFAULTED_FUNCTIONS
1827227825Stheraven
1828253159Stheraven    template <class _Gp, class ..._BA,
1829253159Stheraven              class = typename enable_if
1830253159Stheraven                               <
1831253159Stheraven                                  is_constructible<_Fd, _Gp>::value &&
1832253159Stheraven                                  !is_same<typename remove_reference<_Gp>::type,
1833253159Stheraven                                           __bind_r>::value
1834253159Stheraven                               >::type>
1835227825Stheraven      _LIBCPP_INLINE_VISIBILITY
1836232950Stheraven      explicit __bind_r(_Gp&& __f, _BA&& ...__bound_args)
1837232950Stheraven        : base(_VSTD::forward<_Gp>(__f),
1838227825Stheraven               _VSTD::forward<_BA>(__bound_args)...) {}
1839227825Stheraven
1840227825Stheraven    template <class ..._Args>
1841227825Stheraven        _LIBCPP_INLINE_VISIBILITY
1842249998Sdim        typename enable_if
1843249998Sdim        <
1844249998Sdim            is_convertible<typename __bind_return<_Fd, _Td, tuple<_Args&&...> >::type,
1845249998Sdim                           result_type>::value,
1846249998Sdim            result_type
1847249998Sdim        >::type
1848227825Stheraven        operator()(_Args&& ...__args)
1849227825Stheraven        {
1850227825Stheraven            return base::operator()(_VSTD::forward<_Args>(__args)...);
1851227825Stheraven        }
1852227825Stheraven
1853227825Stheraven    template <class ..._Args>
1854227825Stheraven        _LIBCPP_INLINE_VISIBILITY
1855249998Sdim        typename enable_if
1856249998Sdim        <
1857249998Sdim            is_convertible<typename __bind_return<const _Fd, const _Td, tuple<_Args&&...> >::type,
1858249998Sdim                           result_type>::value,
1859249998Sdim            result_type
1860249998Sdim        >::type
1861227825Stheraven        operator()(_Args&& ...__args) const
1862227825Stheraven        {
1863227825Stheraven            return base::operator()(_VSTD::forward<_Args>(__args)...);
1864227825Stheraven        }
1865227825Stheraven};
1866227825Stheraven
1867232950Stheraventemplate<class _Rp, class _Fp, class ..._BoundArgs>
1868232950Stheravenstruct __is_bind_expression<__bind_r<_Rp, _Fp, _BoundArgs...> > : public true_type {};
1869227825Stheraven
1870232950Stheraventemplate<class _Fp, class ..._BoundArgs>
1871227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
1872232950Stheraven__bind<_Fp, _BoundArgs...>
1873232950Stheravenbind(_Fp&& __f, _BoundArgs&&... __bound_args)
1874227825Stheraven{
1875232950Stheraven    typedef __bind<_Fp, _BoundArgs...> type;
1876232950Stheraven    return type(_VSTD::forward<_Fp>(__f), _VSTD::forward<_BoundArgs>(__bound_args)...);
1877227825Stheraven}
1878227825Stheraven
1879232950Stheraventemplate<class _Rp, class _Fp, class ..._BoundArgs>
1880227825Stheraveninline _LIBCPP_INLINE_VISIBILITY
1881232950Stheraven__bind_r<_Rp, _Fp, _BoundArgs...>
1882232950Stheravenbind(_Fp&& __f, _BoundArgs&&... __bound_args)
1883227825Stheraven{
1884232950Stheraven    typedef __bind_r<_Rp, _Fp, _BoundArgs...> type;
1885232950Stheraven    return type(_VSTD::forward<_Fp>(__f), _VSTD::forward<_BoundArgs>(__bound_args)...);
1886227825Stheraven}
1887227825Stheraven
1888227825Stheraven#endif  // _LIBCPP_HAS_NO_VARIADICS
1889227825Stheraven
1890227825Stheraventemplate <>
1891249998Sdimstruct _LIBCPP_TYPE_VIS hash<bool>
1892227825Stheraven    : public unary_function<bool, size_t>
1893227825Stheraven{
1894227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1895227825Stheraven    size_t operator()(bool __v) const _NOEXCEPT {return static_cast<size_t>(__v);}
1896227825Stheraven};
1897227825Stheraven
1898227825Stheraventemplate <>
1899249998Sdimstruct _LIBCPP_TYPE_VIS hash<char>
1900227825Stheraven    : public unary_function<char, size_t>
1901227825Stheraven{
1902227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1903227825Stheraven    size_t operator()(char __v) const _NOEXCEPT {return static_cast<size_t>(__v);}
1904227825Stheraven};
1905227825Stheraven
1906227825Stheraventemplate <>
1907249998Sdimstruct _LIBCPP_TYPE_VIS hash<signed char>
1908227825Stheraven    : public unary_function<signed char, size_t>
1909227825Stheraven{
1910227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1911227825Stheraven    size_t operator()(signed char __v) const _NOEXCEPT {return static_cast<size_t>(__v);}
1912227825Stheraven};
1913227825Stheraven
1914227825Stheraventemplate <>
1915249998Sdimstruct _LIBCPP_TYPE_VIS hash<unsigned char>
1916227825Stheraven    : public unary_function<unsigned char, size_t>
1917227825Stheraven{
1918227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1919227825Stheraven    size_t operator()(unsigned char __v) const _NOEXCEPT {return static_cast<size_t>(__v);}
1920227825Stheraven};
1921227825Stheraven
1922227825Stheraven#ifndef _LIBCPP_HAS_NO_UNICODE_CHARS
1923227825Stheraven
1924227825Stheraventemplate <>
1925249998Sdimstruct _LIBCPP_TYPE_VIS hash<char16_t>
1926227825Stheraven    : public unary_function<char16_t, size_t>
1927227825Stheraven{
1928227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1929227825Stheraven    size_t operator()(char16_t __v) const _NOEXCEPT {return static_cast<size_t>(__v);}
1930227825Stheraven};
1931227825Stheraven
1932227825Stheraventemplate <>
1933249998Sdimstruct _LIBCPP_TYPE_VIS hash<char32_t>
1934227825Stheraven    : public unary_function<char32_t, size_t>
1935227825Stheraven{
1936227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1937227825Stheraven    size_t operator()(char32_t __v) const _NOEXCEPT {return static_cast<size_t>(__v);}
1938227825Stheraven};
1939227825Stheraven
1940227825Stheraven#endif  // _LIBCPP_HAS_NO_UNICODE_CHARS
1941227825Stheraven
1942227825Stheraventemplate <>
1943249998Sdimstruct _LIBCPP_TYPE_VIS hash<wchar_t>
1944227825Stheraven    : public unary_function<wchar_t, size_t>
1945227825Stheraven{
1946227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1947227825Stheraven    size_t operator()(wchar_t __v) const _NOEXCEPT {return static_cast<size_t>(__v);}
1948227825Stheraven};
1949227825Stheraven
1950227825Stheraventemplate <>
1951249998Sdimstruct _LIBCPP_TYPE_VIS hash<short>
1952227825Stheraven    : public unary_function<short, size_t>
1953227825Stheraven{
1954227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1955227825Stheraven    size_t operator()(short __v) const _NOEXCEPT {return static_cast<size_t>(__v);}
1956227825Stheraven};
1957227825Stheraven
1958227825Stheraventemplate <>
1959249998Sdimstruct _LIBCPP_TYPE_VIS hash<unsigned short>
1960227825Stheraven    : public unary_function<unsigned short, size_t>
1961227825Stheraven{
1962227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1963227825Stheraven    size_t operator()(unsigned short __v) const _NOEXCEPT {return static_cast<size_t>(__v);}
1964227825Stheraven};
1965227825Stheraven
1966227825Stheraventemplate <>
1967249998Sdimstruct _LIBCPP_TYPE_VIS hash<int>
1968227825Stheraven    : public unary_function<int, size_t>
1969227825Stheraven{
1970227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1971227825Stheraven    size_t operator()(int __v) const _NOEXCEPT {return static_cast<size_t>(__v);}
1972227825Stheraven};
1973227825Stheraven
1974227825Stheraventemplate <>
1975249998Sdimstruct _LIBCPP_TYPE_VIS hash<unsigned int>
1976227825Stheraven    : public unary_function<unsigned int, size_t>
1977227825Stheraven{
1978227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1979227825Stheraven    size_t operator()(unsigned int __v) const _NOEXCEPT {return static_cast<size_t>(__v);}
1980227825Stheraven};
1981227825Stheraven
1982227825Stheraventemplate <>
1983249998Sdimstruct _LIBCPP_TYPE_VIS hash<long>
1984227825Stheraven    : public unary_function<long, size_t>
1985227825Stheraven{
1986227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1987227825Stheraven    size_t operator()(long __v) const _NOEXCEPT {return static_cast<size_t>(__v);}
1988227825Stheraven};
1989227825Stheraven
1990227825Stheraventemplate <>
1991249998Sdimstruct _LIBCPP_TYPE_VIS hash<unsigned long>
1992227825Stheraven    : public unary_function<unsigned long, size_t>
1993227825Stheraven{
1994227825Stheraven    _LIBCPP_INLINE_VISIBILITY
1995227825Stheraven    size_t operator()(unsigned long __v) const _NOEXCEPT {return static_cast<size_t>(__v);}
1996227825Stheraven};
1997227825Stheraven
1998227825Stheraventemplate <>
1999249998Sdimstruct _LIBCPP_TYPE_VIS hash<long long>
2000232950Stheraven    : public __scalar_hash<long long>
2001227825Stheraven{
2002227825Stheraven};
2003227825Stheraven
2004227825Stheraventemplate <>
2005249998Sdimstruct _LIBCPP_TYPE_VIS hash<unsigned long long>
2006232950Stheraven    : public __scalar_hash<unsigned long long>
2007227825Stheraven{
2008227825Stheraven};
2009227825Stheraven
2010227825Stheraventemplate <>
2011249998Sdimstruct _LIBCPP_TYPE_VIS hash<float>
2012232950Stheraven    : public __scalar_hash<float>
2013227825Stheraven{
2014227825Stheraven    _LIBCPP_INLINE_VISIBILITY
2015227825Stheraven    size_t operator()(float __v) const _NOEXCEPT
2016227825Stheraven    {
2017232950Stheraven        // -0.0 and 0.0 should return same hash
2018232950Stheraven       if (__v == 0)
2019232950Stheraven           return 0;
2020232950Stheraven        return __scalar_hash<float>::operator()(__v);
2021227825Stheraven    }
2022227825Stheraven};
2023227825Stheraven
2024227825Stheraventemplate <>
2025249998Sdimstruct _LIBCPP_TYPE_VIS hash<double>
2026232950Stheraven    : public __scalar_hash<double>
2027227825Stheraven{
2028227825Stheraven    _LIBCPP_INLINE_VISIBILITY
2029227825Stheraven    size_t operator()(double __v) const _NOEXCEPT
2030227825Stheraven    {
2031232950Stheraven        // -0.0 and 0.0 should return same hash
2032232950Stheraven       if (__v == 0)
2033232950Stheraven           return 0;
2034232950Stheraven        return __scalar_hash<double>::operator()(__v);
2035227825Stheraven    }
2036227825Stheraven};
2037227825Stheraven
2038227825Stheraventemplate <>
2039249998Sdimstruct _LIBCPP_TYPE_VIS hash<long double>
2040232950Stheraven    : public __scalar_hash<long double>
2041227825Stheraven{
2042227825Stheraven    _LIBCPP_INLINE_VISIBILITY
2043227825Stheraven    size_t operator()(long double __v) const _NOEXCEPT
2044227825Stheraven    {
2045232950Stheraven        // -0.0 and 0.0 should return same hash
2046227825Stheraven        if (__v == 0)
2047227825Stheraven            return 0;
2048232950Stheraven#if defined(__i386__)
2049232950Stheraven        // Zero out padding bits
2050232950Stheraven        union
2051232950Stheraven        {
2052232950Stheraven            long double __t;
2053232950Stheraven            struct
2054232950Stheraven            {
2055232950Stheraven                size_t __a;
2056232950Stheraven                size_t __b;
2057232950Stheraven                size_t __c;
2058232950Stheraven                size_t __d;
2059232950Stheraven            };
2060232950Stheraven        } __u;
2061232950Stheraven        __u.__a = 0;
2062232950Stheraven        __u.__b = 0;
2063232950Stheraven        __u.__c = 0;
2064232950Stheraven        __u.__d = 0;
2065232950Stheraven        __u.__t = __v;
2066232950Stheraven        return __u.__a ^ __u.__b ^ __u.__c ^ __u.__d;
2067232950Stheraven#elif defined(__x86_64__)
2068232950Stheraven        // Zero out padding bits
2069232950Stheraven        union
2070232950Stheraven        {
2071232950Stheraven            long double __t;
2072232950Stheraven            struct
2073232950Stheraven            {
2074232950Stheraven                size_t __a;
2075232950Stheraven                size_t __b;
2076232950Stheraven            };
2077232950Stheraven        } __u;
2078232950Stheraven        __u.__a = 0;
2079232950Stheraven        __u.__b = 0;
2080232950Stheraven        __u.__t = __v;
2081232950Stheraven        return __u.__a ^ __u.__b;
2082232950Stheraven#else
2083232950Stheraven        return __scalar_hash<long double>::operator()(__v);
2084232950Stheraven#endif
2085227825Stheraven    }
2086227825Stheraven};
2087227825Stheraven
2088227825Stheraven// struct hash<T*> in <memory>
2089227825Stheraven
2090227825Stheraven_LIBCPP_END_NAMESPACE_STD
2091227825Stheraven
2092227825Stheraven#endif  // _LIBCPP_FUNCTIONAL
2093