diff --git a/.github/workflows/ci.yml b/.github/workflows/ci.yml index a7bcbeaf7..f4ad238cf 100644 --- a/.github/workflows/ci.yml +++ b/.github/workflows/ci.yml @@ -17,23 +17,27 @@ jobs: cabal: latest args: --allow-newer=base,template-haskell experimental: true + - ghc: 9.4.1 + cabal: 3.8.1.0 + args: --allow-newer=base,template-haskell + experimental: false - ghc: 9.0.1 cabal: 3.4.0.0 args: --allow-newer=base,template-haskell experimental: false - ghc: 8.10.1 - cabal: 3.2.0.0 + cabal: 3.4.0.0 args: --allow-newer=base,template-haskell experimental: false - ghc: 8.8.3 - cabal: 3.0.0.0 + cabal: 3.4.0.0 args: --allow-newer=base,template-haskell experimental: false - ghc: 8.6.5 - cabal: 2.4.1.0 + cabal: 3.4.0.0 experimental: false - ghc: 8.4.4 - cabal: 2.4.1.0 + cabal: 3.4.0.0 experimental: false continue-on-error: ${{ matrix.versions.experimental }} diff --git a/.github/workflows/listener-build-linux.yml b/.github/workflows/listener-build-linux.yml index 7241d6f8b..cc6749dc0 100644 --- a/.github/workflows/listener-build-linux.yml +++ b/.github/workflows/listener-build-linux.yml @@ -112,16 +112,17 @@ jobs: - name: move executable run: | cp dist-newstyle/build/x86_64-linux/ghc-${{ matrix.ghc }}/tidal-listener-0.1.0.0/x/tidal-listener/build/tidal-listener/tidal-listener tidal-listener/binary/tidal-listener - cp dist-newstyle/build/x86_64-linux/ghc-${{ matrix.ghc }}/tidal-1.7.10/x/tidal/build/tidal/tidal tidal-listener/binary/tidal + cp dist-newstyle/build/x86_64-linux/ghc-${{ matrix.ghc }}/tidal-*/x/tidal/build/tidal/tidal tidal-listener/binary/tidal - name: zip files run: | cd tidal-listener/ - tar cvfj binary.tar binary/* + mv binary tidal + tar cvfj linux.tar tidal/* - uses: actions/upload-artifact@v2 with: - path: tidal-listener/binary.tar + path: tidal-listener/linux.tar release: runs-on: ubuntu-latest @@ -133,4 +134,4 @@ jobs: - uses: softprops/action-gh-release@v1 with: - files: artifact/binary.tar \ No newline at end of file + files: artifact/linux.tar diff --git a/.github/workflows/listener-build-macosx.yml b/.github/workflows/listener-build-macosx.yml index f84c73981..5a963ae56 100644 --- a/.github/workflows/listener-build-macosx.yml +++ b/.github/workflows/listener-build-macosx.yml @@ -101,7 +101,7 @@ jobs: - name: move executables run: | cp -r dist-newstyle/build/x86_64-osx/ghc-${{ matrix.ghc }}/tidal-listener-0.1.0.0/x/tidal-listener/build/tidal-listener/tidal-listener tidal-listener/binary/tidal-listener - cp -r dist-newstyle/build/x86_64-osx/ghc-${{ matrix.ghc }}/tidal-1.7.10/x/tidal/build/tidal/tidal tidal-listener/binary/tidal + cp -r dist-newstyle/build/x86_64-osx/ghc-${{ matrix.ghc }}/tidal-*/x/tidal/build/tidal/tidal tidal-listener/binary/tidal - name: zip files run: | @@ -122,4 +122,4 @@ jobs: - uses: softprops/action-gh-release@v1 with: - files: artifact/macosx.tar \ No newline at end of file + files: artifact/macosx.tar diff --git a/.github/workflows/listener-build-windows.yml b/.github/workflows/listener-build-windows.yml index a5c4b95dd..06cc06174 100644 --- a/.github/workflows/listener-build-windows.yml +++ b/.github/workflows/listener-build-windows.yml @@ -82,7 +82,7 @@ jobs: - name: move executables run: | Copy-Item -Path 'dist-newstyle\build\x86_64-windows\ghc-${{ matrix.ghc }}\tidal-listener-0.1.0.0\x\tidal-listener\build\tidal-listener\tidal-listener.exe' -Recurse -Destination 'tidal-listener\binary\tidal-listener.exe' - Copy-Item -Path 'dist-newstyle\build\x86_64-windows\ghc-${{ matrix.ghc }}\tidal-1.7.10\x\tidal\build\tidal\tidal.exe' -Recurse -Destination 'tidal-listener\binary\tidal.exe' + Copy-Item -Path 'dist-newstyle\build\x86_64-windows\ghc-${{ matrix.ghc }}\tidal-*\x\tidal\build\tidal\tidal.exe' -Recurse -Destination 'tidal-listener\binary\tidal.exe' - name: zip files run: Compress-Archive -LiteralPath 'tidal-listener\binary\' -DestinationPath 'tidal-listener\windows.zip' @@ -101,4 +101,4 @@ jobs: - uses: softprops/action-gh-release@v1 with: - files: artifact/windows.zip \ No newline at end of file + files: artifact/windows.zip diff --git a/BootTidal.hs b/BootTidal.hs index f2d3026eb..49194c2af 100644 --- a/BootTidal.hs +++ b/BootTidal.hs @@ -6,8 +6,7 @@ import Sound.Tidal.Context import System.IO (hSetEncoding, stdout, utf8) hSetEncoding stdout utf8 --- total latency = oLatency + cFrameTimespan -tidal <- startTidal (superdirtTarget {oLatency = 0.1, oAddress = "127.0.0.1", oPort = 57120}) (defaultConfig {cVerbose = True, cFrameTimespan = 1/20}) +tidal <- startTidal (superdirtTarget {oLatency = 0.05, oAddress = "127.0.0.1", oPort = 57120}) (defaultConfig {cVerbose = True, cFrameTimespan = 1/20}) :{ let only = (hush >>) diff --git a/cabal.project b/cabal.project index 0a20fbfb5..34e38b735 100644 --- a/cabal.project +++ b/cabal.project @@ -1 +1 @@ -packages: ./ tidal-parse tidal-listener +packages: ./ tidal-parse tidal-listener tidal-link diff --git a/old/sync/Canute.hs b/old/sync/Canute.hs deleted file mode 100644 index 18cbccfd9..000000000 --- a/old/sync/Canute.hs +++ /dev/null @@ -1,28 +0,0 @@ -import Sound.Tidal.Tempo (Tempo, logicalTime, clocked, clockedTick, bps) - -import Sound.OSC.FD -import Sound.OSC.Datum ---import Sound.OpenSoundControl ---import Sound.OSC.FD -import System.IO -import Control.Concurrent - -mykip = "192.168.178.135"; -mykport = 57120 - -main :: IO () -main = do myk <- openUDP mykip mykport - clockedTick 2 $ onTick myk - -wave n = drop i s ++ take i s - where s = "¸.·´¯`·.´¯`·.¸¸.·´¯`·.¸<º)))><" - i = n `mod` (length s) - -onTick :: UDP -> Tempo -> Int -> IO () -onTick myk current ticks = - do putStr $ "tickmyk " ++ (show ticks) ++ " " ++ (wave ticks) ++ "\r" - hFlush stdout - let m = Message "/sync" [int32 ticks, float ((bps current) * 60)] - forkIO $ do threadDelay $ floor $ 0.075 * 1000000 - sendOSC myk m - return () diff --git a/old/sync/CanuteMIDI.hs b/old/sync/CanuteMIDI.hs deleted file mode 100644 index 29d8d2590..000000000 --- a/old/sync/CanuteMIDI.hs +++ /dev/null @@ -1,62 +0,0 @@ -import qualified Sound.ALSA.Sequencer.Address as Addr -import qualified Sound.ALSA.Sequencer.Client as Client -import qualified Sound.ALSA.Sequencer.Port as Port -import qualified Sound.ALSA.Sequencer.Event as Event -import qualified Sound.ALSA.Sequencer as SndSeq -import qualified Sound.ALSA.Exception as AlsaExc -import qualified Sound.ALSA.Sequencer.Connect as Connect -import Sound.Tidal.Tempo (Tempo, logicalTime, clocked, clockedTick, bps) -import System.Environment (getArgs, ) -import Data.Maybe -import GHC.Word -import GHC.Int - -import Sound.OSC.FD -import Sound.OSC.Datum ---import Sound.OpenSoundControl ---import Sound.OSC.FD -import System.IO -import Control.Concurrent - -channel = Event.Channel 0 - -mykip = "192.168.178.135"; -mykport = 57120 - -main :: IO () -main = do --myk <- openUDP mykip mykport - h <- SndSeq.openDefault SndSeq.Block - Client.setName (h :: SndSeq.T SndSeq.OutputMode) "Tidal" - c <- Client.getId h - p <- Port.createSimple h "out" - (Port.caps [Port.capRead, Port.capSubsRead]) Port.typeMidiGeneric - as <- getArgs - let dev = fromMaybe "28:0" $ listToMaybe as - conn <- Connect.createTo h p =<< Addr.parse h dev - clockedTick 4 $ onTick h conn - -wave n = drop i s ++ take i s - where s = "¸.·´¯`·.´¯`·.¸¸.·´¯`·.¸<" ++ eye ++ ")))><" - i = n `mod` (length s) - eye | n `mod` 4 == 0 = "O" - | otherwise = "º" - ---onTick :: UDP -> Tempo -> Int -> IO () -onTick h conn current ticks = - do putStr $ "tickmyk " ++ (show ticks) ++ " " ++ (wave ticks) ++ "\r" - hFlush stdout - --let m = Message "/sync" [int32 ticks, float ((bps current) * 60)] - forkIO $ do threadDelay $ floor $ 0.179 * 1000000 - Event.outputDirect h $ noteOn conn (fromIntegral $ ticks `mod` 128) 127 - return () - - --sendOSC myk m - return () - -noteOn :: Connect.T -> Word8 -> Word8 -> Event.T -noteOn conn n v = - Event.forConnection conn - $ Event.NoteEv Event.NoteOn - $ Event.simpleNote channel - (Event.Pitch (n)) - (Event.Velocity v) diff --git a/old/sync/Leafcutter.hs b/old/sync/Leafcutter.hs deleted file mode 100644 index 418df68a0..000000000 --- a/old/sync/Leafcutter.hs +++ /dev/null @@ -1,38 +0,0 @@ - -import Sound.Tidal.Tempo (State, Tempo, clocked, cps, ticks) -import Sound.Tidal.Config -import Control.Concurrent.MVar -import Control.Monad (when) - -import Sound.OSC.FD -import Sound.OSC.Datum ---import Sound.OpenSoundControl ---import Sound.OSC.FD -import System.IO - -tpb = 4 - -mykip = "10.0.1.10"; -mykport = 4000 -main :: IO () -main = do myk <- openUDP mykip mykport - tempoMV <- newEmptyMVar - clocked defaultConfig tempoMV $ onTick myk tempoMV - putStrLn "hmm." - return () - -wave n = drop i s ++ take i s - where s = "¸.·´¯`·.´¯`·.¸¸.·´¯`·.¸<º)))><" - i = n `mod` (length s) - -onTick :: UDP -> MVar Tempo -> State -> IO () -onTick myk mtempo current = - do let t = ticks current - when (t `mod` tpb == 0) $ - do tempo <- readMVar mtempo - let b = t `div` tpb - bpm = (cps tempo) * 60 - putStr $ show bpm ++ " : " ++ (show b) ++ " " ++ (wave b) ++ "\r" - hFlush stdout - let m = Message "/sync" [int32 b, float bpm] - sendMessage myk m diff --git a/old/sync/Sync.hs b/old/sync/Sync.hs deleted file mode 100644 index fd37dd6f5..000000000 --- a/old/sync/Sync.hs +++ /dev/null @@ -1,36 +0,0 @@ -import Sound.Tidal.Tempo (Tempo, logicalTime, clocked, clockedTick, bps) - -import Sound.OSC.FD -import Sound.OSC.Datum ---import Sound.OpenSoundControl ---import Sound.OSC.FD -import System.IO - -daveip = "192.168.0.3"; -daveport = 4000 -adeip = "10.0.0.3"; -adeport = 1777; - -tpb = 8 - -main :: IO () -main = do dave <- openUDP daveip daveport - clocked $ onTick dave - -wave n = drop i s ++ take i s - where s = "¸.·´¯`·.´¯`·.¸¸.·´¯`·.¸<º)))><" - i = n `mod` (length s) - -onTick :: UDP -> Tempo -> Int -> IO () -onTick dave current ticks - | ticks `mod` 8 == 0 = - do putStr $ "tickdave " ++ (show ticks) ++ " " ++ (wave ticks) ++ "\r" - hFlush stdout - let m = Message "/sync" [int32 tpb, float ((bps current) * 60)] - sendOSC dave m - | otherwise = return () - --- onTickAde :: UDP -> BpsChange -> Int -> IO () --- onTickAde ade current ticks = --- do let n = Message "/PureEvents/Beat" [Int ticks] --- sendOSC ade n diff --git a/old/sync/serial.hs b/old/sync/serial.hs deleted file mode 100644 index f1699969b..000000000 --- a/old/sync/serial.hs +++ /dev/null @@ -1,31 +0,0 @@ -import Sound.Tidal.Tempo (Tempo, logicalTime, clocked, clockedTick, bps) -import System.Hardware.Serialport -import qualified Data.ByteString.Char8 as B -import Data.Char -import Data.Word - -import Sound.OSC.FD -import Sound.OSC.Datum -import System.IO -import Control.Concurrent - -tpb = 1 - -wave n = drop i s ++ take i s - where s = "¸.·´¯`·.´¯`·.¸¸.·´¯`·.¸<" ++ eye ++ ")))><" - i = n `mod` (length s) - eye | n `mod` 4 == 0 = "O" - | otherwise = "º" - -onTick ard current ticks = - do let message = B.pack [chr $ if (ticks `mod` 4 == 0) then 100 else 50] - forkIO $ do threadDelay $ floor $ 0.09 * 1000000 - send ard message - return () - threadDelay $ floor $ 0.04 * 1000000 - putStr $ "Pulse " ++ (show ticks) ++ " " ++ (wave ticks) ++ "\r" - hFlush stdout - return () - -main = do ard <- openSerial "/dev/serial/by-id/usb-Arduino__www.arduino.cc__Arduino_Uno_64938323231351417131-if00" defaultSerialSettings {commSpeed = CS9600} - clockedTick 4 $ onTick ard diff --git a/src/Sound/Tidal/Carabiner.hs b/src/Sound/Tidal/Carabiner.hs deleted file mode 100644 index 549a24f00..000000000 --- a/src/Sound/Tidal/Carabiner.hs +++ /dev/null @@ -1,83 +0,0 @@ -{-# OPTIONS_GHC -fno-warn-dodgy-imports -fno-warn-name-shadowing #-} -module Sound.Tidal.Carabiner where - -{- - Carabiner.hs - For syncing with the Link protocol over Carabiner. - Copyright (C) 2020, Alex McLean and contributors - - This library is free software: you can redistribute it and/or modify - it under the terms of the GNU General Public License as published by - the Free Software Foundation, either version 3 of the License, or - (at your option) any later version. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the - GNU General Public License for more details. - - You should have received a copy of the GNU General Public License - along with this library. If not, see . --} - -import Network.Socket hiding (send, sendTo, recv, recvFrom) -import Network.Socket.ByteString (send, recv) -import qualified Data.ByteString.Char8 as B8 -import Control.Concurrent (forkIO, takeMVar, putMVar) -import qualified Sound.Tidal.Stream as S -import Sound.Tidal.Tempo -import System.Clock -import Text.Read (readMaybe) -import Control.Monad (when, forever) -import Data.Maybe (isJust, fromJust) -import qualified Sound.OSC.FD as O - -carabiner :: S.Stream -> Int -> Double -> IO Socket -carabiner tidal bpc latency = do sock <- client tidal bpc latency "127.0.0.1" 17000 - sendMsg sock "status\n" - return sock - -client :: S.Stream -> Int -> Double -> String -> Int -> IO Socket -client tidal bpc latency host port = withSocketsDo $ - do addrInfo <- getAddrInfo Nothing (Just host) (Just $ show port) - let serverAddr = head addrInfo - sock <- socket (addrFamily serverAddr) Stream defaultProtocol - connect sock (addrAddress serverAddr) - _ <- forkIO $ listener tidal bpc latency sock - -- sendMsg sock "status\n" - -- threadDelay 10000000 - return sock - -listener :: S.Stream -> Int -> Double -> Socket -> IO () -listener tidal bpc latency sock = - forever $ do rMsg <- recv sock 1024 - let msg = B8.unpack rMsg - (name:_:ws) = words msg - pairs = pairs' ws - pairs' (a:b:xs) = (a,b):pairs' xs - pairs' _ = [] - act tidal bpc latency name pairs - -act :: S.Stream -> Int -> Double -> String -> [(String, String)] -> IO () -act tidal bpc latency "status" pairs - = do let start = (lookup ":start" pairs >>= readMaybe) :: Maybe Integer - bpm = (lookup ":bpm" pairs >>= readMaybe) :: Maybe Double - beat = (lookup ":beat" pairs >>= readMaybe) :: Maybe Double - when (and [isJust start, isJust bpm, isJust beat]) $ do - nowM <- getTime Monotonic - nowO <- O.time - let m = fromIntegral (sec nowM) + (fromIntegral (nsec nowM)/1000000000) - d = nowO - m - start' = fromIntegral (fromJust start) / 1000000 - startO = start' + d - -- cyc = toRational $ (fromJust beat) / (fromIntegral bpc) - tempo <- takeMVar (S.sTempoMV tidal) - let tempo' = tempo {atTime = startO + latency, - atCycle = 0, - cps = (fromJust bpm / 60) / fromIntegral bpc - } - putMVar (S.sTempoMV tidal) tempo' -act _ _ _ name _ = putStr $ "Unhandled thingie " ++ name - -sendMsg :: Socket -> String -> IO () -sendMsg sock msg = do _ <- send sock $ B8.pack msg - return () diff --git a/src/Sound/Tidal/Chords.hs b/src/Sound/Tidal/Chords.hs index 3650c7989..5c94d3dd8 100644 --- a/src/Sound/Tidal/Chords.hs +++ b/src/Sound/Tidal/Chords.hs @@ -274,3 +274,44 @@ chordL p = (\name -> fromMaybe [] $ lookup name chordTable) <$> p chordList :: String chordList = unwords $ map fst (chordTable :: [(String, [Int])]) +data Modifier = Range Int | Drop Int | Invert | Open deriving Eq + +instance Show Modifier where + show (Range i) = "Range " ++ show i + show (Drop i) = "Drop " ++ show i + show Invert = "Invert" + show Open = "Open" + +applyModifier :: (Enum a, Num a) => Modifier -> [a] -> [a] +applyModifier (Range i) ds = take i $ concatMap (\x -> map (+ x) ds) [0,12..] +applyModifier Invert [] = [] +applyModifier Invert (d:ds) = ds ++ [d+12] +applyModifier Open ds = case length ds > 2 of + True -> [ (ds !! 0 - 12), (ds !! 2 - 12), (ds !! 1) ] ++ reverse (take (length ds - 3) (reverse ds)) + False -> ds +applyModifier (Drop i) ds = case length ds < i of + True -> ds + False -> (ds!!s - 12):(xs ++ drop 1 ys) + where (xs,ys) = splitAt s ds + s = length ds - i + +applyModifierPat :: (Num a, Enum a) => Pattern [a] -> Pattern [Modifier] -> Pattern [a] +applyModifierPat pat modsP = do + ch <- pat + ms <- modsP + return $ foldl (flip applyModifier) ch ms + +applyModifierPatSeq :: (Num a, Enum a) => (a -> b) -> Pattern [a] -> [Pattern [Modifier]] -> Pattern [b] +applyModifierPatSeq f pat [] = fmap (map f) pat +applyModifierPatSeq f pat (mP:msP) = applyModifierPatSeq f (applyModifierPat pat mP) msP + +chordToPatSeq :: (Num a, Enum a) => (a -> b) -> Pattern a -> Pattern String -> [Pattern [Modifier]] -> Pattern b +chordToPatSeq f noteP nameP modsP = uncollect $ do + n <- noteP + name <- nameP + let ch = map (+ n) (fromMaybe [0] $ lookup name chordTable) + applyModifierPatSeq f (return ch) modsP + +-- | turns a given pattern of some Num type, a pattern of chord names and a list of patterns of modifiers into a chord pattern +chord :: (Num a, Enum a) => Pattern a -> Pattern String -> [Pattern [Modifier]] -> Pattern a +chord = chordToPatSeq id diff --git a/src/Sound/Tidal/Config.hs b/src/Sound/Tidal/Config.hs index 9f468d421..c9d2e9f00 100644 --- a/src/Sound/Tidal/Config.hs +++ b/src/Sound/Tidal/Config.hs @@ -1,5 +1,9 @@ module Sound.Tidal.Config where +import qualified Sound.Tidal.Link as Link +import Data.Int(Int64) +import Foreign.C.Types (CDouble) + {- Config.hs - For default Tidal configuration values. Copyright (C) 2020, Alex McLean and contributors @@ -23,11 +27,15 @@ data Config = Config {cCtrlListen :: Bool, cCtrlPort :: Int, cCtrlBroadcast :: Bool, cFrameTimespan :: Double, + cEnableLink :: Bool, + cProcessAhead :: Double, cTempoAddr :: String, cTempoPort :: Int, cTempoClientPort :: Int, - cSkipTicks :: Int, - cVerbose :: Bool + cSkipTicks :: Int64, + cVerbose :: Bool, + cQuantum :: CDouble, + cCyclesPerBeat :: CDouble } defaultConfig :: Config @@ -36,9 +44,13 @@ defaultConfig = Config {cCtrlListen = True, cCtrlPort = 6010, cCtrlBroadcast = False, cFrameTimespan = 1/20, + cEnableLink = True, + cProcessAhead = 3/10, cTempoAddr = "127.0.0.1", cTempoPort = 9160, cTempoClientPort = 0, -- choose at random cSkipTicks = 10, - cVerbose = True + cVerbose = True, + cQuantum = 4, + cCyclesPerBeat = 4 } diff --git a/src/Sound/Tidal/Context.hs b/src/Sound/Tidal/Context.hs index c38df24ee..3d78630f5 100644 --- a/src/Sound/Tidal/Context.hs +++ b/src/Sound/Tidal/Context.hs @@ -22,7 +22,6 @@ import Prelude hiding ((<*), (*>)) import Data.Ratio as C -import Sound.Tidal.Carabiner as C import Sound.Tidal.Config as C import Sound.Tidal.Control as C import Sound.Tidal.Core as C @@ -36,4 +35,3 @@ import Sound.Tidal.Stream as C import Sound.Tidal.Transition as C import Sound.Tidal.UI as C import Sound.Tidal.Version as C -import Sound.Tidal.EspGrid as C diff --git a/src/Sound/Tidal/Control.hs b/src/Sound/Tidal/Control.hs index d553166a8..8c265fbca 100644 --- a/src/Sound/Tidal/Control.hs +++ b/src/Sound/Tidal/Control.hs @@ -350,21 +350,21 @@ smash' n xs p = slowcat $ map (`slow` p') xs This adds a bit of echo: @ - d1 $ echo 4 0.5 0.2 $ sound "bd sn" + d1 $ echo 4 0.2 0.5 $ sound "bd sn" @ The above results in 4 echos, each one 50% quieter than the last, with 1/5th of a cycle between them. It is possible to reverse the echo: @ - d1 $ echo 4 0.5 (-0.2) $ sound "bd sn" + d1 $ echo 4 (-0.2) 0.5 $ sound "bd sn" @ -} echo :: Pattern Integer -> Pattern Rational -> Pattern Double -> ControlPattern -> ControlPattern echo = tParam3 _echo _echo :: Integer -> Rational -> Double -> ControlPattern -> ControlPattern -_echo count time feedback p = stack (p:map (\x -> ((x%1)*time) `rotR` (p |* P.gain (pure $ (* feedback) (fromIntegral x)))) [1..(count-1)]) +_echo count time feedback p = _echoWith count time (|* P.gain (pure $ feedback)) p {- | Allows to apply a function for each step and overlays the result delayed by the given time. diff --git a/src/Sound/Tidal/Core.hs b/src/Sound/Tidal/Core.hs index b53dc0400..04592b9d0 100644 --- a/src/Sound/Tidal/Core.hs +++ b/src/Sound/Tidal/Core.hs @@ -150,6 +150,9 @@ a |+| b = (+) <$> a <*> b a |+ b = (+) <$> a <* b ( +|) :: Num a => Pattern a -> Pattern a -> Pattern a a +| b = (+) <$> a *> b +(||+) :: Num a => Pattern a -> Pattern a -> Pattern a +a ||+ b = (+) <$> a <<* b + (|++|) :: Applicative a => a String -> a String -> a String a |++| b = (++) <$> a <*> b @@ -157,6 +160,8 @@ a |++| b = (++) <$> a <*> b a |++ b = (++) <$> a <* b ( ++|) :: Pattern String -> Pattern String -> Pattern String a ++| b = (++) <$> a *> b +(||++) :: Pattern String -> Pattern String -> Pattern String +a ||++ b = (++) <$> a <<* b (|/|) :: (Applicative a, Fractional b) => a b -> a b -> a b a |/| b = (/) <$> a <*> b @@ -164,6 +169,8 @@ a |/| b = (/) <$> a <*> b a |/ b = (/) <$> a <* b ( /|) :: Fractional a => Pattern a -> Pattern a -> Pattern a a /| b = (/) <$> a *> b +(||/) :: Fractional a => Pattern a -> Pattern a -> Pattern a +a ||/ b = (/) <$> a <<* b (|*|) :: (Applicative a, Num b) => a b -> a b -> a b a |*| b = (*) <$> a <*> b @@ -171,6 +178,8 @@ a |*| b = (*) <$> a <*> b a |* b = (*) <$> a <* b ( *|) :: Num a => Pattern a -> Pattern a -> Pattern a a *| b = (*) <$> a *> b +(||*) :: Num a => Pattern a -> Pattern a -> Pattern a +a ||* b = (*) <$> a <<* b (|-|) :: (Applicative a, Num b) => a b -> a b -> a b a |-| b = (-) <$> a <*> b @@ -178,6 +187,8 @@ a |-| b = (-) <$> a <*> b a |- b = (-) <$> a <* b ( -|) :: Num a => Pattern a -> Pattern a -> Pattern a a -| b = (-) <$> a *> b +(||-) :: Num a => Pattern a -> Pattern a -> Pattern a +a ||- b = (-) <$> a <<* b (|%|) :: (Applicative a, Moddable b) => a b -> a b -> a b a |%| b = gmod <$> a <*> b @@ -185,6 +196,8 @@ a |%| b = gmod <$> a <*> b a |% b = gmod <$> a <* b ( %|) :: Moddable a => Pattern a -> Pattern a -> Pattern a a %| b = gmod <$> a *> b +(||%) :: Moddable a => Pattern a -> Pattern a -> Pattern a +a ||% b = gmod <$> a <<* b (|**|) :: (Applicative a, Floating b) => a b -> a b -> a b a |**| b = (**) <$> a <*> b @@ -192,6 +205,8 @@ a |**| b = (**) <$> a <*> b a |** b = (**) <$> a <* b ( **|) :: Floating a => Pattern a -> Pattern a -> Pattern a a **| b = (**) <$> a *> b +(||**) :: Floating a => Pattern a -> Pattern a -> Pattern a +a ||** b = (**) <$> a <<* b (|>|) :: (Applicative a, Unionable b) => a b -> a b -> a b a |>| b = flip union <$> a <*> b @@ -199,6 +214,8 @@ a |>| b = flip union <$> a <*> b a |> b = flip union <$> a <* b ( >|) :: Unionable a => Pattern a -> Pattern a -> Pattern a a >| b = flip union <$> a *> b +(||>) :: Unionable a => Pattern a -> Pattern a -> Pattern a +a ||> b = flip union <$> a <<* b (|<|) :: (Applicative a, Unionable b) => a b -> a b -> a b a |<| b = union <$> a <*> b @@ -206,6 +223,8 @@ a |<| b = union <$> a <*> b a |< b = union <$> a <* b ( <|) :: Unionable a => Pattern a -> Pattern a -> Pattern a a <| b = union <$> a *> b +(||<) :: Unionable a => Pattern a -> Pattern a -> Pattern a +a ||< b = union <$> a <<* b -- Backward compatibility - structure from left, values from right. (#) :: Unionable b => Pattern b -> Pattern b -> Pattern b diff --git a/src/Sound/Tidal/EspGrid.hs b/src/Sound/Tidal/EspGrid.hs deleted file mode 100644 index 05b96985d..000000000 --- a/src/Sound/Tidal/EspGrid.hs +++ /dev/null @@ -1,72 +0,0 @@ -{-# LANGUAGE ScopedTypeVariables #-} - -module Sound.Tidal.EspGrid (tidalEspGridLink,cpsEsp,espgrid) where - -{- - EspGrid.hs - Provides ability to sync via the ESP Grid - Copyright (C) 2020, David Ogborn and contributors - - This library is free software: you can redistribute it and/or modify - it under the terms of the GNU General Public License as published by - the Free Software Foundation, either version 3 of the License, or - (at your option) any later version. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the - GNU General Public License for more details. - - You should have received a copy of the GNU General Public License - along with this library. If not, see . --} - -import Control.Concurrent.MVar -import Control.Concurrent (forkIO,threadDelay) -import Control.Monad (forever) -import Control.Exception -import Sound.OSC.FD -import Sound.Tidal.Tempo -import Sound.Tidal.Stream (Stream, sTempoMV) - -parseEspTempo :: [Datum] -> Maybe (Tempo -> Tempo) -parseEspTempo d = do - on :: Integer <- datum_integral (d!!0) - bpm <- datum_floating (d!!1) - t1 :: Integer <- datum_integral (d!!2) - t2 <- datum_integral (d!!3) - n :: Integer <- datum_integral (d!!4) - let nanos = (t1*1000000000) + t2 - return $ \t -> t { - atTime = ut_to_ntpr $ realToFrac nanos / 1000000000, - atCycle = fromIntegral n, - cps = bpm/60, - paused = on == 0 - } - -changeTempo :: MVar Tempo -> Packet -> IO () -changeTempo t (Packet_Message msg) = - case parseEspTempo (messageDatum msg) of - Just f -> modifyMVarMasked_ t $ \t0 -> return (f t0) - Nothing -> putStrLn "Warning: Unable to parse message from EspGrid as Tempo" -changeTempo _ _ = putStrLn "Serious error: Can only process Packet_Message" - -tidalEspGridLink :: MVar Tempo -> IO () -tidalEspGridLink _ = putStrLn "Function no longer supported, please use 'espgrid tidal' to connect to ESPgrid instead." - -espgrid :: Stream -> IO () -espgrid st = do - let t = sTempoMV st - socket <- openUDP "127.0.0.1" 5510 - _ <- forkIO $ forever $ do - (do - sendMessage socket $ Message "/esp/tempo/q" [] - response <- waitAddress socket "/esp/tempo/r" - Sound.Tidal.EspGrid.changeTempo t response - threadDelay 200000) - `catch` (\e -> putStrLn $ "exception caught in tidalEspGridLink: " ++ show (e :: SomeException)) - return () - -cpsEsp :: Real t => t -> IO () -cpsEsp t = do - socket <- openUDP "127.0.0.1" 5510 - sendMessage socket $ Message "/esp/beat/tempo" [float (t*60)] diff --git a/src/Sound/Tidal/ParseBP.hs b/src/Sound/Tidal/ParseBP.hs index 937f2dee5..479cb3214 100644 --- a/src/Sound/Tidal/ParseBP.hs +++ b/src/Sound/Tidal/ParseBP.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE OverloadedStrings, FlexibleInstances, CPP, DeriveFunctor #-} +{-# LANGUAGE OverloadedStrings, FlexibleInstances, CPP, DeriveFunctor, GADTs, StandaloneDeriving #-} {-# LANGUAGE LambdaCase #-} {-# OPTIONS_GHC -Wall -fno-warn-orphans -fno-warn-unused-do-bind #-} @@ -42,7 +42,7 @@ import qualified Text.Parsec.Prim import Sound.Tidal.Pattern import Sound.Tidal.UI import Sound.Tidal.Core -import Sound.Tidal.Chords (chordTable) +import Sound.Tidal.Chords import Sound.Tidal.Utils (fromRight) data TidalParseError = TidalParseError {parsecError :: ParseError, @@ -62,22 +62,59 @@ type MyParser = Text.Parsec.Prim.Parsec String Int -- | AST representation of patterns -data TPat a = TPat_Atom (Maybe ((Int, Int), (Int, Int))) a - | TPat_Fast (TPat Time) (TPat a) - | TPat_Slow (TPat Time) (TPat a) - | TPat_DegradeBy Int Double (TPat a) - | TPat_CycleChoose Int [TPat a] - | TPat_Euclid (TPat Int) (TPat Int) (TPat Int) (TPat a) - | TPat_Stack [TPat a] - | TPat_Polyrhythm (Maybe (TPat Rational)) [TPat a] - | TPat_Seq [TPat a] - | TPat_Silence - | TPat_Foot - | TPat_Elongate Rational (TPat a) - | TPat_Repeat Int (TPat a) - | TPat_EnumFromTo (TPat a) (TPat a) - | TPat_Var String - deriving (Show, Functor) +data TPat a where + TPat_Atom :: (Maybe ((Int, Int), (Int, Int))) -> a -> (TPat a) + TPat_Fast :: (TPat Time) -> (TPat a) -> (TPat a) + TPat_Slow :: (TPat Time) -> (TPat a) -> (TPat a) + TPat_DegradeBy :: Int -> Double -> (TPat a) -> (TPat a) + TPat_CycleChoose :: Int -> [TPat a] -> (TPat a) + TPat_Euclid :: (TPat Int) -> (TPat Int) -> (TPat Int) -> (TPat a) -> (TPat a) + TPat_Stack :: [TPat a] -> (TPat a) + TPat_Polyrhythm :: (Maybe (TPat Rational)) -> [TPat a] -> (TPat a) + TPat_Seq :: [TPat a] -> (TPat a) + TPat_Silence :: (TPat a) + TPat_Foot :: (TPat a) + TPat_Elongate :: Rational -> (TPat a) -> (TPat a) + TPat_Repeat :: Int -> (TPat a) -> (TPat a) + TPat_EnumFromTo :: (TPat a) -> (TPat a) -> (TPat a) + TPat_Var :: String -> (TPat a) + TPat_Chord :: (Num b, Enum b, Parseable b, Enumerable b) => (b -> a) -> (TPat b) -> (TPat String) -> [TPat [Modifier]] -> (TPat a) + +instance Show a => Show (TPat a) where + show (TPat_Atom c v) = "TPat_Atom (" ++ show c ++ ") (" ++ show v ++ ")" + show (TPat_Fast t v) = "TPat_Fast (" ++ show t ++ ") (" ++ show v ++ ")" + show (TPat_Slow t v) = "TPat_Slow (" ++ show t ++ ") (" ++ show v ++ ")" + show (TPat_DegradeBy x r v) = "TPat_DegradeBy (" ++ show x ++ ") (" ++ show r ++ ") (" ++ show v ++ ")" + show (TPat_CycleChoose x vs) = "TPat_CycleChoose (" ++ show x ++ ") (" ++ show vs ++ ")" + show (TPat_Euclid a b c v) = "TPat_Euclid (" ++ show a ++ ") (" ++ show b ++ ") (" ++ show c ++ ") " ++ show v ++ ")" + show (TPat_Stack vs) = "TPat_Stack " ++ show vs + show (TPat_Polyrhythm mSteprate vs) = "TPat_Polyrhythm (" ++ show mSteprate ++ ") " ++ show vs + show (TPat_Seq vs) = "TPat_Seq " ++ show vs + show TPat_Silence = "TPat_Silence" + show TPat_Foot = "TPat_Foot" + show (TPat_Elongate r v) = "TPat_Elongate (" ++ show r ++ ") (" ++ show v ++ ")" + show (TPat_Repeat r v) = "TPat_Repeat (" ++ show r ++ ") (" ++ show v ++ ")" + show (TPat_EnumFromTo a b) = "TPat_EnumFromTo (" ++ show a ++ ") (" ++ show b ++ ")" + show (TPat_Var s) = "TPat_Var " ++ show s + show (TPat_Chord g iP nP msP) = "TPat_Chord (" ++ (show $ fmap g iP) ++ ") (" ++ show nP ++ ") (" ++ show msP ++ ")" + +instance Functor TPat where + fmap f (TPat_Atom c v) = TPat_Atom c (f v) + fmap f (TPat_Fast t v) = TPat_Fast t (fmap f v) + fmap f (TPat_Slow t v) = TPat_Slow t (fmap f v) + fmap f (TPat_DegradeBy x r v) = TPat_DegradeBy x r (fmap f v) + fmap f (TPat_CycleChoose x vs) = TPat_CycleChoose x (map (fmap f) vs) + fmap f (TPat_Euclid a b c v) = TPat_Euclid a b c (fmap f v) + fmap f (TPat_Stack vs) = TPat_Stack (map (fmap f) vs) + fmap f (TPat_Polyrhythm mSteprate vs) = TPat_Polyrhythm mSteprate (map (fmap f) vs) + fmap f (TPat_Seq vs) = TPat_Seq (map (fmap f) vs) + fmap _ TPat_Silence = TPat_Silence + fmap _ TPat_Foot = TPat_Foot + fmap f (TPat_Elongate r v) = TPat_Elongate r (fmap f v) + fmap f (TPat_Repeat r v) = TPat_Repeat r (fmap f v) + fmap f (TPat_EnumFromTo a b) = TPat_EnumFromTo (fmap f a) (fmap f b) + fmap _ (TPat_Var s) = TPat_Var s + fmap f (TPat_Chord g iP nP msP) = TPat_Chord (f . g) iP nP msP tShowList :: (Show a) => [TPat a] -> String tShowList vs = "[" ++ intercalate "," (map tShow vs) ++ "]" @@ -107,6 +144,7 @@ tShow (TPat_Seq vs) = snd $ steps_seq vs tShow TPat_Silence = "silence" tShow (TPat_EnumFromTo a b) = "unwrap $ fromTo <$> (" ++ tShow a ++ ") <*> (" ++ tShow b ++ ")" tShow (TPat_Var s) = "getControl " ++ s +tShow (TPat_Chord f n name mods) = "chord (" ++ (tShow $ fmap f n) ++ ") (" ++ tShow name ++ ")" ++ tShowList mods tShow a = "can't happen? " ++ show a @@ -132,6 +170,7 @@ toPat = \case | otherwise = pure $ fst $ head pats TPat_Seq xs -> snd $ resolve_seq xs TPat_Var s -> getControl s + TPat_Chord f iP nP mP -> chordToPatSeq f (toPat iP) (toPat nP) (map toPat mP) _ -> silence resolve_tpat :: (Enumerable a, Parseable a) => TPat a -> (Rational, Pattern a) @@ -431,22 +470,28 @@ pChar :: MyParser (TPat Char) pChar = wrapPos $ TPat_Atom Nothing <$> pCharNum pDouble :: MyParser (TPat Double) -pDouble = wrapPos $ do s <- sign - f <- choice [fromRational <$> pRatio, parseNote] "float" - let v = applySign s f - do TPat_Stack . map (TPat_Atom Nothing . (+ v)) <$> parseChord - <|> return (TPat_Atom Nothing v) - <|> - do TPat_Stack . map (TPat_Atom Nothing) <$> parseChord +pDouble = try $ do d <- pDoubleWithoutChord + pChord d <|> return d + <|> pChord (TPat_Atom Nothing 0) + <|> pDoubleWithoutChord + +pDoubleWithoutChord :: MyParser (TPat Double) +pDoubleWithoutChord = pPart $ wrapPos $ do s <- sign + f <- choice [fromRational <$> pRatio, parseNote] "float" + return $ TPat_Atom Nothing (applySign s f) pNote :: MyParser (TPat Note) -pNote = wrapPos $ fmap (fmap Note) $ do s <- sign - f <- choice [intOrFloat, parseNote] "float" - let v = applySign s f - do TPat_Stack . map (TPat_Atom Nothing . (+ v)) <$> parseChord - <|> return (TPat_Atom Nothing v) - <|> do TPat_Stack . map (TPat_Atom Nothing) <$> parseChord - <|> do TPat_Atom Nothing . fromRational <$> pRatio +pNote = try $ do n <- pNoteWithoutChord + pChord n <|> return n + <|> pChord (TPat_Atom Nothing 0) + <|> pNoteWithoutChord + <|> do TPat_Atom Nothing . fromRational <$> pRatio + +pNoteWithoutChord :: MyParser (TPat Note) +pNoteWithoutChord = pPart $ wrapPos $ do s <- sign + f <- choice [intOrFloat, parseNote] "float" + return $ TPat_Atom Nothing (Note $ applySign s f) + pBool :: MyParser (TPat Bool) pBool = wrapPos $ do oneOf "t1" @@ -462,12 +507,14 @@ parseIntNote = do s <- sign then return $ applySign s $ round d else fail "not an integer" -pIntegral :: Integral a => MyParser (TPat a) -pIntegral = wrapPos $ do i <- parseIntNote - do TPat_Stack . map (TPat_Atom Nothing . (+i)) <$> parseChord - <|> return (TPat_Atom Nothing i) - <|> - do TPat_Stack . map (TPat_Atom Nothing) <$> parseChord +pIntegral :: (Integral a, Parseable a, Enumerable a) => MyParser (TPat a) +pIntegral = try $ do i <- pIntegralWithoutChord + pChord i <|> return i + <|> pChord (TPat_Atom Nothing 0) + <|> pIntegralWithoutChord + +pIntegralWithoutChord :: (Integral a, Parseable a, Enumerable a) => MyParser (TPat a) +pIntegralWithoutChord = pPart $ wrapPos $ fmap (TPat_Atom Nothing) parseIntNote parseChord :: (Enum a, Num a) => MyParser [a] parseChord = do char '\'' @@ -607,3 +654,47 @@ pRatioSingleChar c v = try $ do isInt :: RealFrac a => a -> Bool isInt x = x == fromInteger (round x) + +--- + +instance Parseable [Modifier] where + tPatParser = pModifiers + doEuclid = euclidOff + +instance Enumerable [Modifier] where + fromTo a b = fastFromList [a,b] + fromThenTo a b c = fastFromList [a,b,c] + +parseModInv :: MyParser Modifier +parseModInv = char 'i' >> return Invert + +parseModInvNum :: MyParser [Modifier] +parseModInvNum = do + char 'i' + n <- pInteger + return $ replicate (round n) Invert + +parseModDrop :: MyParser [Modifier] +parseModDrop = do + char 'd' + n <- pInteger + return $ [Drop $ round n] + +parseModOpen :: MyParser Modifier +parseModOpen = char 'o' >> return Open + +parseModRange :: MyParser Modifier +parseModRange = parseIntNote >>= \i -> return $ Range $ fromIntegral i + +parseModifiers :: MyParser [Modifier] +parseModifiers = (many1 parseModOpen) <|> parseModDrop <|> (fmap pure parseModRange) <|> try parseModInvNum <|> (many1 parseModInv) "modifier" + +pModifiers :: MyParser (TPat [Modifier]) +pModifiers = wrapPos $ TPat_Atom Nothing <$> parseModifiers + +pChord :: (Enum a, Num a, Parseable a, Enumerable a) => TPat a -> MyParser (TPat a) +pChord i = do + char '\'' + n <- pPart pVocable "chordname" + ms <- option [] $ many1 $ (char '\'' >> pPart pModifiers) + return $ TPat_Chord id i n ms diff --git a/src/Sound/Tidal/Pattern.hs b/src/Sound/Tidal/Pattern.hs index 894b249de..57a50c907 100644 --- a/src/Sound/Tidal/Pattern.hs +++ b/src/Sound/Tidal/Pattern.hs @@ -37,7 +37,7 @@ import Control.DeepSeq (NFData) import Control.Monad ((>=>)) import qualified Data.Map.Strict as Map import Data.Maybe (isJust, fromJust, catMaybes, mapMaybe) -import Data.List (delete, findIndex, sort) +import Data.List (delete, findIndex, (\\)) import Data.Word (Word8) import Data.Data (Data) -- toConstr import Data.Typeable (Typeable) @@ -79,7 +79,11 @@ instance Applicative Pattern where (*>) :: Pattern (a -> b) -> Pattern a -> Pattern b (*>) = applyPatToPatRight -infixl 4 <*, *> +-- | Like <*>, but the 'wholes' come from the left +(<<*) :: Pattern (a -> b) -> Pattern a -> Pattern b +(<<*) = applyPatToPatSqueeze + +infixl 4 <*, *>, <<* applyPatToPat :: (Maybe Arc -> Maybe Arc -> Maybe (Maybe Arc)) -> Pattern (a -> b) -> Pattern a -> Pattern b applyPatToPat combineWholes pf px = Pattern q where q st = catMaybes $ concatMap match $ query pf st @@ -126,6 +130,9 @@ applyPatToPatRight pf px = Pattern q part' <- subArc (part ef) (part ex) return (Event (combineContexts [context ef, context ex]) whole' part' (value ef $ value ex)) +applyPatToPatSqueeze :: Pattern (a -> b) -> Pattern a -> Pattern b +applyPatToPatSqueeze pf px = squeezeJoin $ (\f -> f <$> px) <$> pf + -- * Monad and friends -- Note there are four ways of joining - the default 'unwrap' used by @>>=@, as well @@ -341,7 +348,7 @@ empty :: Pattern a empty = Pattern {query = const []} queryArc :: Pattern a -> Arc -> [Event a] -queryArc p a = query p $ State a Map.empty +queryArc p a = query p $ State a Map.empty -- | Splits queries that span cycles. For example `query p (0.5, 1.5)` would be -- turned into two queries, `(0.5,1)` and `(1,1.5)`, and the results @@ -422,7 +429,7 @@ compressArcTo (Arc s e) = compressArc (Arc (cyclePos s) (e - sam s)) _fastGap :: Time -> Pattern a -> Pattern a _fastGap 0 _ = empty -_fastGap r p = splitQueries $ +_fastGap r p = splitQueries $ withResultArc (\(Arc s e) -> Arc (sam s + ((s - sam s)/r')) (sam s + ((e - sam s)/r')) ) $ p {query = f} @@ -573,11 +580,6 @@ isDigital = not . isAnalog onsetIn :: Arc -> Event a -> Bool onsetIn a e = isIn a (wholeStart e) --- | Compares two lists of events, attempting to combine fragmented events in the process --- for a 'truer' compare -compareDefrag :: (Ord a) => [Event a] -> [Event a] -> Bool -compareDefrag as bs = sort (defragParts as) == sort (defragParts bs) - -- | Returns a list of events, with any adjacent parts of the same whole combined defragParts :: Eq a => [Event a] -> [Event a] defragParts [] = [] @@ -833,3 +835,52 @@ getList _ = Nothing valueToPattern :: Value -> Pattern Value valueToPattern (VPattern pat) = pat valueToPattern v = pure v + +--- functions relating to chords/patterns of lists + + +sameDur :: Event a -> Event a -> Bool +sameDur e1 e2 = (whole e1 == whole e2) && (part e1 == part e2) + +groupEventsBy :: Eq a => (Event a -> Event a -> Bool) -> [Event a] -> [[Event a]] +groupEventsBy _ [] = [] +groupEventsBy f (e:es) = eqs:(groupEventsBy f (es \\ eqs)) + where eqs = e:[x | x <- es, f e x] + +-- assumes that all events in the list have same whole/part +collectEvent :: [Event a] -> Maybe (Event [a]) +collectEvent [] = Nothing +collectEvent l@(e:_) = Just $ e {context = con, value = vs} + where con = unionC $ map context l + vs = map value l + unionC [] = Context [] + unionC ((Context is):cs) = Context (is ++ iss) + where Context iss = unionC cs + +collectEventsBy :: Eq a => (Event a -> Event a -> Bool) -> [Event a] -> [Event [a]] +collectEventsBy f es = remNo $ map collectEvent (groupEventsBy f es) + where + remNo [] = [] + remNo (Nothing:cs) = remNo cs + remNo ((Just c):cs) = c : (remNo cs) + +-- | collects all events satisfying the same constraint into a list +collectBy :: Eq a => (Event a -> Event a -> Bool) -> Pattern a -> Pattern [a] +collectBy f = withEvents (collectEventsBy f) + +-- | collects all events occuring at the exact same time into a list +collect :: Eq a => Pattern a -> Pattern [a] +collect = collectBy sameDur + +uncollectEvent :: Event [a] -> [Event a] +uncollectEvent e = [e {value = (value e)!!i, context = resolveContext i (context e)} | i <-[0..length (value e) - 1]] + where resolveContext i (Context xs) = case length xs <= i of + True -> Context [] + False -> Context [xs!!i] + +uncollectEvents :: [Event [a]] -> [Event a] +uncollectEvents = concatMap uncollectEvent + +-- | merges all values in a list into one pattern by stacking the values +uncollect :: Pattern [a] -> Pattern a +uncollect = withEvents uncollectEvents diff --git a/src/Sound/Tidal/Safe/Context.hs b/src/Sound/Tidal/Safe/Context.hs index 178eb252a..efc2421fe 100644 --- a/src/Sound/Tidal/Safe/Context.hs +++ b/src/Sound/Tidal/Safe/Context.hs @@ -51,7 +51,6 @@ module Sound.Tidal.Safe.Context where import Data.Ratio as C -import Sound.Tidal.Carabiner as C import Sound.Tidal.Config as C import Sound.Tidal.Control as C import Sound.Tidal.Core as C @@ -65,7 +64,6 @@ import Sound.Tidal.Stream -- import Sound.Tidal.Transition as C import Sound.Tidal.UI as C import Sound.Tidal.Version as C -import Sound.Tidal.EspGrid as C import qualified Sound.Tidal.Context as C import Sound.Tidal.Context diff --git a/src/Sound/Tidal/Stream.hs b/src/Sound/Tidal/Stream.hs index 95ac40279..db9577e2d 100644 --- a/src/Sound/Tidal/Stream.hs +++ b/src/Sound/Tidal/Stream.hs @@ -2,7 +2,7 @@ {-# OPTIONS_GHC -fno-warn-missing-fields #-} {-# language DeriveGeneric, StandaloneDeriving #-} -module Sound.Tidal.Stream where +module Sound.Tidal.Stream (module Sound.Tidal.Stream) where {- Stream.hs - Tidal's thingie for turning patterns into OSC streams @@ -26,9 +26,12 @@ import Control.Applicative ((<|>)) import Control.Concurrent.MVar import Control.Concurrent import Control.Monad (forM_, when) +import Data.Coerce (coerce) import qualified Data.Map.Strict as Map import Data.Maybe (fromJust, fromMaybe, catMaybes, isJust) import qualified Control.Exception as E +import Foreign +import Foreign.C.Types import System.IO (hPutStrLn, stderr) import qualified Sound.OSC.FD as O @@ -37,6 +40,7 @@ import qualified Network.Socket as N import Sound.Tidal.Config import Sound.Tidal.Core (stack, silence, (#)) import Sound.Tidal.ID +import qualified Sound.Tidal.Link as Link import Sound.Tidal.Params (pS) import Sound.Tidal.Pattern import qualified Sound.Tidal.Tempo as T @@ -49,19 +53,20 @@ import Data.Word (Word8) import Sound.Tidal.Version +import Sound.Tidal.StreamTypes as Sound.Tidal.Stream + data Stream = Stream {sConfig :: Config, sBusses :: MVar [Int], sStateMV :: MVar ValueMap, -- sOutput :: MVar ControlPattern, + sLink :: Link.AbletonLink, sListen :: Maybe O.UDP, sPMapMV :: MVar PlayMap, - sTempoMV :: MVar T.Tempo, + sActionsMV :: MVar [T.TempoAction], sGlobalFMV :: MVar (ControlPattern -> ControlPattern), sCxs :: [Cx] } -type PatId = String - data Cx = Cx {cxTarget :: Target, cxUDP :: O.UDP, cxOSCs :: [OSC], @@ -99,15 +104,18 @@ data OSC = OSC {path :: String, | OSCContext {path :: String} deriving Show -data PlayState = PlayState {pattern :: ControlPattern, - mute :: Bool, - solo :: Bool, - history :: [ControlPattern] - } - deriving Show - -type PlayMap = Map.Map PatId PlayState - +data ProcessedEvent = + ProcessedEvent { + peHasOnset :: Bool, + peEvent :: Event ValueMap, + peCps :: Link.BPM, + peDelta :: Link.Micros, + peCycle :: Time, + peOnWholeOrPart :: Link.Micros, + peOnWholeOrPartOsc :: O.Time, + peOnPart :: Link.Micros, + peOnPartOsc :: O.Time + } sDefault :: String -> Maybe Value sDefault x = Just $ VS x @@ -186,6 +194,12 @@ dirtShape = OSC "/play" $ ArgList [("cps", fDefault 0), -- ("id", iDefault 0) ] +defaultCps :: O.Time +defaultCps = 0.5625 + +-- Start an instance of Tidal +-- Spawns a thread within Tempo that acts as the clock +-- Spawns a thread that listens to and acts on OSC control messages startStream :: Config -> [(Target, [OSC])] -> IO Stream startStream config oscmap = do sMapMV <- newMVar Map.empty @@ -193,6 +207,7 @@ startStream config oscmap bussesMV <- newMVar [] globalFMV <- newMVar id tempoMV <- newEmptyMVar + actionsMV <- newEmptyMVar tidal_status_string >>= verbose config verbose config $ "Listening for external controls on " ++ cCtrlAddr config ++ ":" ++ show (cCtrlPort config) @@ -208,17 +223,27 @@ startStream config oscmap ) (oAddress target) (oPort target) return $ Cx {cxUDP = u, cxAddr = remote_addr, cxBusAddr = remote_bus_addr, cxTarget = target, cxOSCs = os} ) oscmap + let bpm = (coerce defaultCps) * 60 * (cCyclesPerBeat config) + abletonLink <- Link.create bpm let stream = Stream {sConfig = config, sBusses = bussesMV, sStateMV = sMapMV, + sLink = abletonLink, sListen = listen, sPMapMV = pMapMV, - sTempoMV = tempoMV, + sActionsMV = actionsMV, sGlobalFMV = globalFMV, sCxs = cxs } sendHandshakes stream - _ <- T.clocked config tempoMV $ onTick stream + let ac = T.ActionHandler { + T.onTick = onTick stream, + T.onSingleTick = onSingleTick stream, + T.updatePattern = updatePattern stream + } + -- Spawn a thread that acts as the clock + _ <- T.clocked config sMapMV pMapMV actionsMV ac abletonLink + -- Spawn a thread to handle OSC control messages _ <- forkIO $ ctrlResponder 0 config stream return stream @@ -250,6 +275,7 @@ resolve host port = do let hints = N.defaultHints { N.addrSocketType = N.Stream addr:_ <- N.getAddrInfo (Just hints) (Just host) (Just port) return addr +-- Start an instance of Tidal with superdirt OSC startTidal :: Target -> Config -> IO Stream startTidal target config = startStream config [(target, [superdirtShape])] @@ -314,105 +340,151 @@ playStack pMap = stack $ map pattern active else not (mute pState) ) $ Map.elems pMap -toOSC :: Double -> [Int] -> Event ValueMap -> T.Tempo -> OSC -> [(Double, Bool, O.Message)] -toOSC latency busses e tempo osc@(OSC _ _) +toOSC :: [Int] -> ProcessedEvent -> OSC -> [(Double, Bool, O.Message)] +toOSC busses pe osc@(OSC _ _) = catMaybes (playmsg:busmsgs) - where (playmap, busmap) = Map.partitionWithKey (\k _ -> null k || head k /= '^') $ value e - -- swap in bus ids where needed - playmap' = Map.union (Map.mapKeys tail $ Map.map (\(VI i) -> VS ('c':(show $ toBus i))) busmap) playmap - addExtra = Map.union playmap' extra - playmsg | eventHasOnset e = do vs <- toData osc (e {value = addExtra}) - mungedPath <- substitutePath (path osc) playmap' - return (ts, - False, -- bus message ? - O.Message mungedPath vs - ) - | otherwise = Nothing - toBus n | null busses = n - | otherwise = busses !!! n - busmsgs = map - (\(('^':k), (VI b)) -> do v <- Map.lookup k playmap - return $ (tsPart, - True, -- bus message ? - O.Message "/c_set" [O.int32 b, toDatum v] - ) - ) - (Map.toList busmap) - onPart = sched tempo $ start $ part e - on = sched tempo $ start $ wholeOrPart e - off = sched tempo $ stop $ wholeOrPart e - delta = off - on - -- If there is already cps in the event, the union will preserve that. - extra = Map.fromList [("cps", (VF (T.cps tempo))), - ("delta", VF delta), - ("cycle", VF (fromRational $ start $ wholeOrPart e)) - ] - nudge = fromJust $ getF $ fromMaybe (VF 0) $ Map.lookup "nudge" $ playmap - ts = on + nudge + latency - tsPart = onPart + nudge + latency - -toOSC latency _ e tempo (OSCContext oscpath) - = map cToM $ contextPosition $ context e + -- playmap is a ValueMap where the keys don't start with ^ and are not "" + -- busmap is a ValueMap containing the rest of the keys from the event value + -- The partition is performed in order to have special handling of bus ids. + where + (playmap, busmap) = Map.partitionWithKey (\k _ -> null k || head k /= '^') $ val pe + -- Map in bus ids where needed. + -- + -- Bus ids are integers + -- If busses is empty, the ids to send are directly contained in the the values of the busmap. + -- Otherwise, the ids to send are contained in busses at the indices of the values of the busmap. + -- Both cases require that the values of the busmap are only ever integers, + -- that is, they are Values with constructor VI + -- (but perhaps we should explicitly crash with an error message if it contains something else?). + -- Map.mapKeys tail is used to remove ^ from the keys. + -- In case (value e) has the key "", we will get a crash here. + playmap' = Map.union (Map.mapKeys tail $ Map.map (\(VI i) -> VS ('c':(show $ toBus i))) busmap) playmap + toChannelId (VI i) = VS ('c':(show $ toBus i)) + toChannelId _ = error "All channels IDs should be VI" + val = value . peEvent + -- Only events that start within the current nowArc are included + playmsg | peHasOnset pe = do + -- If there is already cps in the event, the union will preserve that. + let extra = Map.fromList [("cps", (VF (coerce $! peCps pe))), + ("delta", VF (T.addMicrosToOsc (peDelta pe) 0)), + ("cycle", VF (fromRational (peCycle pe))) + ] + addExtra = Map.union playmap' extra + ts = (peOnWholeOrPartOsc pe) + nudge -- + latency + vs <- toData osc ((peEvent pe) {value = addExtra}) + mungedPath <- substitutePath (path osc) playmap' + return (ts, + False, -- bus message ? + O.Message mungedPath vs + ) + | otherwise = Nothing + toBus n | null busses = n + | otherwise = busses !!! n + busmsgs = map + (\(('^':k), (VI b)) -> do v <- Map.lookup k playmap + return $ (tsPart, + True, -- bus message ? + O.Message "/c_set" [O.int32 b, toDatum v] + ) + ) + (Map.toList busmap) + where + tsPart = (peOnPartOsc pe) + nudge -- + latency + nudge = fromJust $ getF $ fromMaybe (VF 0) $ Map.lookup "nudge" $ playmap +toOSC _ pe (OSCContext oscpath) + = map cToM $ contextPosition $ context $ peEvent pe where cToM :: ((Int,Int),(Int,Int)) -> (Double, Bool, O.Message) cToM ((x, y), (x',y')) = (ts, False, -- bus message ? - O.Message oscpath $ (O.string ident):(O.float delta):(O.float cyc):(map O.int32 [x,y,x',y']) + O.Message oscpath $ (O.string ident):(O.float (peDelta pe)):(O.float cyc):(map O.int32 [x,y,x',y']) ) - on = sched tempo $ start $ wholeOrPart e - off = sched tempo $ stop $ wholeOrPart e - delta = off - on cyc :: Double - cyc = fromRational $ start $ wholeOrPart e - nudge = fromMaybe 0 $ Map.lookup "nudge" (value e) >>= getF - ident = fromMaybe "unknown" $ Map.lookup "_id_" (value e) >>= getS - ts = on + nudge + latency - -doCps :: MVar T.Tempo -> (Double, Maybe Value) -> IO () -doCps tempoMV (d, Just (VF cps)) = - do _ <- forkIO $ do threadDelay $ floor $ d * 1000000 - -- hack to stop things from stopping ! - -- TODO is this still needed? - _ <- T.setCps tempoMV (max 0.00001 cps) - return () - return () -doCps _ _ = return () - -onTick :: Stream -> T.State -> IO () -onTick stream st - = do doTick False stream st - -processCps :: T.Tempo -> [Event ValueMap] -> ([(T.Tempo, Event ValueMap)], T.Tempo) -processCps t [] = ([], t) --- If an event has a tempo change, that affects the following events.. -processCps t (e:evs) = (((t', e):es'), t'') - where cps' | eventHasOnset e = do x <- Map.lookup "cps" $ value e - getF x - | otherwise = Nothing - t' = (maybe t (\newCps -> T.changeTempo' t newCps (eventPartStart e)) cps') - (es', t'') = processCps t' evs + cyc = fromRational $ peCycle pe + nudge = fromMaybe 0 $ Map.lookup "nudge" (value $ peEvent pe) >>= getF + ident = fromMaybe "unknown" $ Map.lookup "_id_" (value $ peEvent pe) >>= getS + ts = (peOnWholeOrPartOsc pe) + nudge -- + latency + +-- Used for Tempo callback +updatePattern :: Stream -> ID -> ControlPattern -> IO () +updatePattern stream k pat = do + let x = queryArc pat (Arc 0 0) + pMap <- seq x $ takeMVar (sPMapMV stream) + let playState = updatePS $ Map.lookup (fromID k) pMap + putMVar (sPMapMV stream) $ Map.insert (fromID k) playState pMap + where updatePS (Just playState) = do playState {pattern = pat', history = pat:(history playState)} + updatePS Nothing = PlayState pat' False False [pat'] + pat' = pat # pS "_id_" (pure $ fromID k) +processCps :: T.LinkOperations -> [Event ValueMap] -> IO [ProcessedEvent] +processCps ops = mapM processEvent + where + processEvent :: Event ValueMap -> IO ProcessedEvent + processEvent e = do + let wope = wholeOrPart e + partStartCycle = start $ part e + partStartBeat = (T.cyclesToBeat ops) (realToFrac partStartCycle) + onCycle = start wope + onBeat = (T.cyclesToBeat ops) (realToFrac onCycle) + offCycle = stop wope + offBeat = (T.cyclesToBeat ops) (realToFrac offCycle) + on <- (T.timeAtBeat ops) onBeat + onPart <- (T.timeAtBeat ops) partStartBeat + when (eventHasOnset e) (do + let cps' = Map.lookup "cps" (value e) >>= getF + maybe (return ()) (\newCps -> (T.setTempo ops) ((T.cyclesToBeat ops) (newCps * 60)) on) $ coerce cps' + ) + off <- (T.timeAtBeat ops) offBeat + bpm <- (T.getTempo ops) + let cps = ((T.beatToCycles ops) bpm) / 60 + let delta = off - on + return $! ProcessedEvent { + peHasOnset = eventHasOnset e, + peEvent = e, + peCps = cps, + peDelta = delta, + peCycle = onCycle, + peOnWholeOrPart = on, + peOnWholeOrPartOsc = (T.linkToOscTime ops) on, + peOnPart = onPart, + peOnPartOsc = (T.linkToOscTime ops) onPart + } + + +-- streamFirst but with random cycle instead of always first cicle streamOnce :: Stream -> ControlPattern -> IO () streamOnce st p = do i <- getStdRandom $ randomR (0, 8192) streamFirst st $ rotL (toRational (i :: Int)) p +-- here let's do modifyMVar_ on actions streamFirst :: Stream -> ControlPattern -> IO () -streamFirst stream pat = do now <- O.time - tempo <- readMVar (sTempoMV stream) - pMapMV <- newMVar $ Map.singleton "fake" - (PlayState {pattern = pat, - mute = False, - solo = False, - history = [] - } - ) - let cps = T.cps tempo - state = T.State {T.ticks = 0, - T.start = now, - T.nowTimespan = (now, now + (1/cps)), - T.starting = True, -- really? - T.nowArc = (Arc 0 1) - } - doTick True (stream {sPMapMV = pMapMV}) state +streamFirst stream pat = modifyMVar_ (sActionsMV stream) (\actions -> return $ (T.SingleTick pat) : actions) + +-- Used for Tempo callback +onTick :: Stream -> TickState -> T.LinkOperations -> ValueMap -> IO ValueMap +onTick stream st ops s + = doTick stream st ops s + +-- Used for Tempo callback +-- Tempo changes will be applied. +-- However, since the full arc is processed at once and since Link does not support +-- scheduling, tempo change may affect scheduling of events that happen earlier +-- in the normal stream (the one handled by onTick). +onSingleTick :: Stream -> Link.Micros -> T.LinkOperations -> ValueMap -> ControlPattern -> IO ValueMap +onSingleTick stream now ops s pat = do + pMapMV <- newMVar $ Map.singleton "fake" + (PlayState {pattern = pat, + mute = False, + solo = False, + history = [] + } + ) + bpm <- (T.getTempo ops) + let cps = realToFrac $ ((T.beatToCycles ops) bpm) / 60 + + -- The nowArc is a full cycle + let state = TickState {tickArc = (Arc 0 1), tickNudge = 0} + doTick (stream {sPMapMV = pMapMV}) state ops s + -- | Query the current pattern (contained in argument @stream :: Stream@) -- for the events in the current arc (contained in argument @st :: T.State@), @@ -427,62 +499,43 @@ streamFirst stream pat = do now <- O.time -- this function prints a warning and resets the current pattern -- to the previous one (or to silence if there isn't one) and continues, -- because the likely reason is that something is wrong with the current pattern. -doTick :: Bool -> Stream -> T.State -> IO () -doTick fake stream st = +doTick :: Stream -> TickState -> T.LinkOperations -> ValueMap -> IO ValueMap +doTick stream st ops sMap = E.handle (\ (e :: E.SomeException) -> do hPutStrLn stderr $ "Failed to Stream.doTick: " ++ show e hPutStrLn stderr $ "Return to previous pattern." setPreviousPatternOrSilence stream - ) $ - modifyState $ \(tempo, sMap) -> do - pMap <- readMVar (sPMapMV stream) - busses <- readMVar (sBusses stream) - sGlobalF <- readMVar (sGlobalFMV stream) - -- putStrLn $ show st - let config = sConfig stream - cxs = sCxs stream - cycleNow = T.timeToCycles tempo $ T.start st - patstack = sGlobalF $ playStack pMap - -- If a 'fake' tick, it'll be aligned with cycle zero - pat | fake = withResultTime (+ cycleNow) patstack - | otherwise = patstack - frameEnd = snd $ T.nowTimespan st - -- add cps to state - sMap' = Map.insert "_cps" (VF (T.cps tempo)) sMap - --filterOns = filter eventHasOnset - extraLatency | fake = 0 - | otherwise = cFrameTimespan config + T.nudged tempo - -- First the state is used to query the pattern - es = sortOn (start . part) $ query pat (State {arc = T.nowArc st, + return sMap) (do + pMap <- readMVar (sPMapMV stream) + busses <- readMVar (sBusses stream) + sGlobalF <- readMVar (sGlobalFMV stream) + bpm <- (T.getTempo ops) + let + config = sConfig stream + cxs = sCxs stream + patstack = sGlobalF $ playStack pMap + cps = ((T.beatToCycles ops) bpm) / 60 + sMap' = Map.insert "_cps" (VF $ coerce cps) sMap + extraLatency = tickNudge st + -- First the state is used to query the pattern + es = sortOn (start . part) $ query patstack (State {arc = tickArc st, controls = sMap' - } + } ) -- Then it's passed through the events - (sMap'', es') = resolveState sMap' es - - -- TODO onset is calculated in toOSC as well.. - on e tempo'' = (sched tempo'' $ start $ wholeOrPart e) - (tes, tempo') = processCps tempo $ es' - forM_ cxs $ \cx@(Cx target _ oscs _ _) -> do - let latency = oLatency target + extraLatency - ms = concatMap (\(t, e) -> - if (fake || (on e t) < frameEnd) - then concatMap (toOSC latency busses e t) oscs - else [] - ) tes - forM_ ms $ \ m -> send (sListen stream) cx m `E.catch` \ (e :: E.SomeException) -> do - hPutStrLn stderr $ "Failed to send. Is the '" ++ oName target ++ "' target running? " ++ show e - - when (tempo /= tempo') $ T.sendTempo tempo' - - (tempo', sMap'') `seq` return (tempo', sMap'') - where modifyState :: ((T.Tempo, ValueMap) -> IO (T.Tempo, ValueMap)) -> IO () - modifyState io = E.mask $ \restore -> do - s <- takeMVar (sStateMV stream) - t <- takeMVar (sTempoMV stream) - (t', s') <- restore (io (t, s)) `E.onException` (do {putMVar (sStateMV stream) s; putMVar (sTempoMV stream) t; return ()}) - putMVar (sStateMV stream) s' - putMVar (sTempoMV stream) t' + (sMap'', es') = resolveState sMap' es + tes <- processCps ops es' + -- For each OSC target + forM_ cxs $ \cx@(Cx target _ oscs _ _) -> do + -- Latency is configurable per target. + -- Latency is only used when sending events live. + let latency = oLatency target + ms = concatMap (\e -> concatMap (toOSC busses e) oscs) tes + -- send the events to the OSC target + forM_ ms $ \ m -> (do + send (sListen stream) cx latency extraLatency m) `E.catch` \ (e :: E.SomeException) -> do + hPutStrLn stderr $ "Failed to send. Is the '" ++ oName target ++ "' target running? " ++ show e + sMap'' `seq` return sMap'') setPreviousPatternOrSilence :: Stream -> IO () setPreviousPatternOrSilence stream = @@ -491,36 +544,35 @@ setPreviousPatternOrSilence stream = _:p:ps -> pMap { pattern = p, history = p:ps } _ -> pMap { pattern = silence, history = [silence] } ) - -send :: Maybe O.UDP -> Cx -> (Double, Bool, O.Message) -> IO () -send listen cx (time, isBusMsg, m) - | oSchedule target == Pre BundleStamp = sendBndl isBusMsg listen cx $ O.Bundle time [m] + +-- send has three modes: +-- Send events early using timestamp in the OSC bundle - used by Superdirt +-- Send events early by adding timestamp to the OSC message - used by Dirt +-- Send events live by delaying the thread +send :: Maybe O.UDP -> Cx -> Double -> Double -> (Double, Bool, O.Message) -> IO () +send listen cx latency extraLatency (time, isBusMsg, m) + | oSchedule target == Pre BundleStamp = sendBndl isBusMsg listen cx $ O.Bundle timeWithLatency [m] | oSchedule target == Pre MessageStamp = sendO isBusMsg listen cx $ addtime m - | otherwise = do _ <- forkIO $ do now <- O.time - threadDelay $ floor $ (time - now) * 1000000 + | otherwise = do _ <- forkOS $ do now <- O.time + threadDelay $ floor $ (timeWithLatency - now) * 1000000 sendO isBusMsg listen cx m return () where addtime (O.Message mpath params) = O.Message mpath ((O.int32 sec):((O.int32 usec):params)) - ut = O.ntpr_to_ut time + ut = O.ntpr_to_ut timeWithLatency sec :: Int sec = floor ut usec :: Int usec = floor $ 1000000 * (ut - (fromIntegral sec)) target = cxTarget cx - -sched :: T.Tempo -> Rational -> Double -sched tempo c = ((fromRational $ c - (T.atCycle tempo)) / T.cps tempo) - + (T.atTime tempo) + timeWithLatency = time - latency + extraLatency -- Interaction streamNudgeAll :: Stream -> Double -> IO () -streamNudgeAll s nudge = do tempo <- takeMVar $ sTempoMV s - putMVar (sTempoMV s) $ tempo {T.nudged = nudge} +streamNudgeAll s nudge = T.setNudge (sActionsMV s) nudge streamResetCycles :: Stream -> IO () -streamResetCycles s = do _ <- T.resetCycles (sTempoMV s) - return () +streamResetCycles s =T.resetCycles (sActionsMV s) hasSolo :: Map.Map k PlayState -> Bool hasSolo = (>= 1) . length . filter solo . Map.elems @@ -539,25 +591,7 @@ streamList s = do pMap <- readMVar (sPMapMV s) streamReplace :: Stream -> ID -> ControlPattern -> IO () streamReplace s k !pat - = E.catch (do let x = queryArc pat (Arc 0 0) - tempo <- readMVar $ sTempoMV s - input <- takeMVar $ sStateMV s - -- put pattern id and change time in control input - now <- O.time - let cyc = T.timeToCycles tempo now - putMVar (sStateMV s) $ - Map.insert ("_t_all") (VR cyc) $ Map.insert ("_t_" ++ fromID k) (VR cyc) input - -- update the pattern itself - pMap <- seq x $ takeMVar $ sPMapMV s - let playState = updatePS $ Map.lookup (fromID k) pMap - putMVar (sPMapMV s) $ Map.insert (fromID k) playState pMap - return () - ) - (\(e :: E.SomeException) -> hPutStrLn stderr $ "Error in pattern: " ++ show e - ) - where updatePS (Just playState) = do playState {pattern = pat', history = pat:(history playState)} - updatePS Nothing = PlayState pat' False False [pat'] - pat' = pat # pS "_id_" (pure $ fromID k) + = modifyMVar_ (sActionsMV s) (\actions -> return $ (T.StreamReplace k pat) : actions) streamMute :: Stream -> ID -> IO () streamMute s k = withPatIds s [k] (\x -> x {mute = True}) @@ -638,6 +672,7 @@ openListener c catchAny :: IO a -> (E.SomeException -> IO a) -> IO a catchAny = E.catch +-- Listen to and act on OSC control messages ctrlResponder :: Int -> Config -> Stream -> IO () ctrlResponder waits c (stream@(Stream {sListen = Just sock})) = do ms <- recvMessagesTimeout 2 sock @@ -699,20 +734,24 @@ ctrlResponder waits c (stream@(Stream {sListen = Just sock})) withID _ _ = return () ctrlResponder _ _ _ = return () - verbose :: Config -> String -> IO () verbose c s = when (cVerbose c) $ putStrLn s recvMessagesTimeout :: (O.Transport t) => Double -> t -> IO [O.Message] recvMessagesTimeout n sock = fmap (maybe [] O.packetMessages) $ O.recvPacketTimeout n sock - -streamGetcps :: Stream -> IO O.Time -streamGetcps s = do tempo <- readMVar $ sTempoMV s - return $ T.cps tempo +streamGetcps :: Stream -> IO Double +streamGetcps s = do + let config = sConfig s + now <- Link.clock (sLink s) + ss <- Link.createAndCaptureAppSessionState (sLink s) + bpm <- Link.getTempo ss + return $! coerce $ bpm / (cCyclesPerBeat config) / 60 streamGetnow :: Stream -> IO Double -streamGetnow s = do tempo <- readMVar $ sTempoMV s - now <- O.time - return $ fromRational $ T.timeToCycles tempo now - +streamGetnow s = do + let config = sConfig s + ss <- Link.createAndCaptureAppSessionState (sLink s) + now <- Link.clock (sLink s) + beat <- Link.beatAtTime ss now (cQuantum config) + return $! coerce $ beat / (cCyclesPerBeat config) diff --git a/src/Sound/Tidal/StreamTypes.hs b/src/Sound/Tidal/StreamTypes.hs new file mode 100644 index 000000000..6088b9d32 --- /dev/null +++ b/src/Sound/Tidal/StreamTypes.hs @@ -0,0 +1,22 @@ +module Sound.Tidal.StreamTypes where + +import qualified Data.Map.Strict as Map +import Sound.Tidal.Pattern +import Sound.Tidal.Show () +import qualified Sound.Tidal.Link as Link + +data PlayState = PlayState {pattern :: ControlPattern, + mute :: Bool, + solo :: Bool, + history :: [ControlPattern] + } + deriving Show + +type PatId = String +type PlayMap = Map.Map PatId PlayState + +data TickState = TickState { + tickArc :: Arc, + tickNudge :: Double + } + deriving Show diff --git a/src/Sound/Tidal/Tempo.hs b/src/Sound/Tidal/Tempo.hs index ca3c82976..cb32a83d6 100644 --- a/src/Sound/Tidal/Tempo.hs +++ b/src/Sound/Tidal/Tempo.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE ConstraintKinds, GeneralizedNewtypeDeriving, FlexibleContexts, ScopedTypeVariables, BangPatterns #-} {-# OPTIONS_GHC -fno-warn-incomplete-uni-patterns -fno-warn-orphans #-} @@ -6,13 +7,21 @@ module Sound.Tidal.Tempo where import Control.Concurrent.MVar import qualified Sound.Tidal.Pattern as P import qualified Sound.OSC.FD as O -import qualified Network.Socket as N import Control.Concurrent (forkIO, ThreadId, threadDelay) -import Control.Monad (forever, when, foldM) -import Data.List (nub) +import Control.Monad (when) +import qualified Data.Map.Strict as Map import qualified Control.Exception as E +import Sound.Tidal.ID import Sound.Tidal.Config import Sound.Tidal.Utils (writeError) +import qualified Sound.Tidal.Link as Link +import Foreign.C.Types (CDouble(..)) +import Data.Coerce (coerce) +import System.IO (hPutStrLn, stderr) +import Data.Int(Int64) + +import Sound.Tidal.StreamTypes +import Sound.Tidal.Core (silence) {- Tempo.hs - Tidal's scheduler @@ -35,210 +44,259 @@ import Sound.Tidal.Utils (writeError) instance Show O.UDP where show _ = "-unshowable-" -data Tempo = Tempo {atTime :: O.Time, - atCycle :: Rational, - cps :: O.Time, - paused :: Bool, - nudged :: Double, - localUDP :: O.UDP, - remoteAddr :: N.SockAddr, - synched :: Bool - } - deriving Show +type TransitionMapper = P.Time -> [P.ControlPattern] -> P.ControlPattern -instance Eq Tempo where - (==) t t' = and [(atTime t) == (atTime t'), - (atCycle t) == (atCycle t'), - (cps t) == (cps t'), - (paused t) == (paused t'), - (nudged t) == (nudged t') - ] - -data State = State {ticks :: Int, - start :: O.Time, - nowTimespan :: (O.Time, O.Time), - nowArc :: P.Arc, - starting :: Bool +data TempoAction = + ResetCycles + | SingleTick P.ControlPattern + | SetNudge Double + | StreamReplace ID P.ControlPattern + | Transition Bool TransitionMapper ID P.ControlPattern + +data State = State {ticks :: Int64, + start :: Link.Micros, + nowEnd :: Link.Micros, + nowArc :: P.Arc, + nudged :: Double } deriving Show -changeTempo :: MVar Tempo -> (O.Time -> Tempo -> Tempo) -> IO Tempo -changeTempo tempoMV f = do t <- O.time - tempo <- takeMVar tempoMV - let tempo' = f t tempo - sendTempo tempo' - putMVar tempoMV tempo' - return tempo' - -changeTempo' :: Tempo -> O.Time -> Rational -> Tempo -changeTempo' tempo newCps cyc = tempo {atTime = cyclesToTime tempo cyc, - cps = newCps, - atCycle = cyc - } - -resetCycles :: MVar Tempo -> IO Tempo -resetCycles tempoMV = changeTempo tempoMV (\t tempo -> tempo {atTime = t, atCycle = 0}) - -setCps :: MVar Tempo -> O.Time -> IO Tempo -setCps tempoMV newCps = changeTempo tempoMV (\t tempo -> tempo {atTime = t, - atCycle = timeToCycles tempo t, - cps = newCps - }) - -defaultCps :: O.Time -defaultCps = 0.5625 - -defaultTempo :: O.Time -> O.UDP -> N.SockAddr -> Tempo -defaultTempo t local remote = Tempo {atTime = t, - atCycle = 0, - cps = defaultCps, - paused = False, - nudged = 0, - localUDP = local, - remoteAddr = remote, - synched = False - } - --- | Returns the given time in terms of --- cycles relative to metrical grid of a given Tempo -timeToCycles :: Tempo -> O.Time -> Rational -timeToCycles tempo t = atCycle tempo + toRational cycleDelta - where delta = t - atTime tempo - cycleDelta = realToFrac (cps tempo) * delta - -cyclesToTime :: Tempo -> Rational -> O.Time -cyclesToTime tempo cyc = atTime tempo + fromRational timeDelta - where cycleDelta = cyc - atCycle tempo - timeDelta = cycleDelta / toRational (cps tempo) +data ActionHandler = + ActionHandler { + onTick :: TickState -> LinkOperations -> P.ValueMap -> IO P.ValueMap, + onSingleTick :: Link.Micros -> LinkOperations -> P.ValueMap -> P.ControlPattern -> IO P.ValueMap, + updatePattern :: ID -> P.ControlPattern -> IO () + } -{- -getCurrentCycle :: MVar Tempo -> IO Rational -getCurrentCycle t = (readMVar t) >>= (cyclesNow) >>= (return . toRational) --} +data LinkOperations = + LinkOperations { + timeAtBeat :: Link.Beat -> IO Link.Micros, + timeToCycles :: Link.Micros -> IO P.Time, + getTempo :: IO Link.BPM, + setTempo :: Link.BPM -> Link.Micros -> IO (), + linkToOscTime :: Link.Micros -> O.Time, + beatToCycles :: CDouble -> CDouble, + cyclesToBeat :: CDouble -> CDouble + } -clocked :: Config -> MVar Tempo -> (State -> IO ()) -> IO [ThreadId] -clocked config tempoMV callback - = do s <- O.time - -- TODO - do something with thread id - _ <- serverListen config - listenTid <- clientListen config tempoMV s - let st = State {ticks = 0, - start = s, - nowTimespan = (s, s + frameTimespan), +resetCycles :: MVar [TempoAction] -> IO () +resetCycles actionsMV = modifyMVar_ actionsMV (\actions -> return $ ResetCycles : actions) + +setNudge :: MVar [TempoAction] -> Double -> IO () +setNudge actionsMV nudge = modifyMVar_ actionsMV (\actions -> return $ SetNudge nudge : actions) + +timeToCycles' :: Config -> Link.SessionState -> Link.Micros -> IO P.Time +timeToCycles' config ss time = do + beat <- Link.beatAtTime ss time (cQuantum config) + return $! (toRational beat) / (toRational (cCyclesPerBeat config)) + +cyclesToTime :: Config -> Link.SessionState -> P.Time -> IO Link.Micros +cyclesToTime config ss cyc = do + let beat = (fromRational cyc) * (cCyclesPerBeat config) + Link.timeAtBeat ss beat (cQuantum config) + +addMicrosToOsc :: Link.Micros -> O.Time -> O.Time +addMicrosToOsc m t = ((fromIntegral m) / 1000000) + t + +-- clocked assumes tempoMV is empty +clocked :: Config -> MVar P.ValueMap -> MVar PlayMap -> MVar [TempoAction] -> ActionHandler -> Link.AbletonLink -> IO [ThreadId] +clocked config stateMV mapMV actionsMV ac abletonLink + = do -- TODO - do something with thread id + clockTid <- forkIO $ loopInit + return $! [clockTid] + where frameTimespan :: Link.Micros + frameTimespan = round $ (cFrameTimespan config) * 1000000 + quantum :: CDouble + quantum = cQuantum config + cyclesPerBeat :: CDouble + cyclesPerBeat = cCyclesPerBeat config + loopInit :: IO a + loopInit = + do + when (cEnableLink config) $ Link.enable abletonLink + sessionState <- Link.createAndCaptureAppSessionState abletonLink + now <- Link.clock abletonLink + let startAt = now + processAhead + Link.requestBeatAtTime sessionState 0 startAt quantum + Link.commitAppSessionState abletonLink sessionState + putMVar actionsMV [] + let st = State {ticks = 0, + start = now, + nowEnd = logicalTime now 1, nowArc = P.Arc 0 0, - starting = True + nudged = 0 } - clockTid <- forkIO $ loop st - return [listenTid, clockTid] - where frameTimespan :: Double - frameTimespan = cFrameTimespan config - loop st = - do -- putStrLn $ show $ nowArc ts - tempo <- readMVar tempoMV - t <- O.time - let logicalT ticks' = start st + fromIntegral ticks' * frameTimespan - logicalNow = logicalT $ ticks st + 1 - -- Wait maximum of two frames - delta = min (frameTimespan * 2) (logicalNow - t) - e = timeToCycles tempo logicalNow - s = if starting st && synched tempo - then timeToCycles tempo (logicalT $ ticks st) - else P.stop $ nowArc st - when (t < logicalNow) $ threadDelay (floor $ delta * 1000000) - t' <- O.time - let actualTick = floor $ (t' - start st) / frameTimespan - -- reset ticks if ahead/behind by skipTicks or more - ahead = abs (actualTick - ticks st) > cSkipTicks config - newTick | ahead = actualTick - | otherwise = ticks st + 1 - st' = st {ticks = newTick, - nowArc = P.Arc s e, - nowTimespan = (logicalNow, logicalNow + frameTimespan), - starting = not (synched tempo) - } - when ahead $ writeError $ "skip: " ++ show (actualTick - ticks st) - callback st' - {-putStrLn ("actual tick: " ++ show actualTick - ++ " old tick: " ++ show (ticks st) - ++ " new tick: " ++ show newTick - )-} - loop st' - -clientListen :: Config -> MVar Tempo -> O.Time -> IO ThreadId -clientListen config tempoMV s = - do -- Listen on random port - let tempoClientPort = cTempoClientPort config - hostname = cTempoAddr config - port = cTempoPort config - (remote_addr:_) <- N.getAddrInfo Nothing (Just hostname) Nothing - local <- O.udpServer "0.0.0.0" tempoClientPort - let (N.SockAddrInet _ a) = N.addrAddress remote_addr - remote = N.SockAddrInet (fromIntegral port) a - t = defaultTempo s local remote - putMVar tempoMV t - -- Send to clock port from same port that's listened to - O.sendTo local (O.p_message "/hello" []) remote - -- Make tempo mvar - -- Listen to tempo changes - forkIO $ listenTempo local tempoMV - -sendTempo :: Tempo -> IO () -sendTempo tempo = O.sendTo (localUDP tempo) (O.p_bundle (atTime tempo) [m]) (remoteAddr tempo) - where m = O.Message "/transmit/cps/cycle" [O.Float $ fromRational $ atCycle tempo, - O.Float $ realToFrac $ cps tempo, - O.Int32 $ if paused tempo then 1 else 0 - ] - -listenTempo :: O.UDP -> MVar Tempo -> IO () -listenTempo udp tempoMV = forever $ do pkt <- O.recvPacket udp - act Nothing pkt - return () - where act _ (O.Packet_Bundle (O.Bundle ts ms)) = mapM_ (act (Just ts) . O.Packet_Message) ms - act (Just ts) (O.Packet_Message (O.Message "/cps/cycle" [O.Float atCycle', - O.Float cps', - O.Int32 paused' - ] - ) - ) = - do tempo <- takeMVar tempoMV - putMVar tempoMV $ tempo {atTime = ts, - atCycle = realToFrac atCycle', - cps = realToFrac cps', - paused = paused' == 1, - synched = True - } - act _ pkt = writeError $ "Unknown packet (client): " ++ show pkt - -serverListen :: Config -> IO (Maybe ThreadId) -serverListen config = catchAny run (\_ -> return Nothing) -- probably just already running) - where run = do let port = cTempoPort config - -- iNADDR_ANY deprecated - what's the right way to do this? - udp <- O.udpServer "0.0.0.0" port - cpsMessage <- defaultCpsMessage - tid <- forkIO $ loop udp ([], cpsMessage) - return $ Just tid - loop udp (cs, msg) = do (pkt,c) <- O.recvFrom udp - (cs', msg') <- act udp c Nothing (cs,msg) pkt - loop udp (cs', msg') - act :: O.UDP -> N.SockAddr -> Maybe O.Time -> ([N.SockAddr], O.Packet) -> O.Packet -> IO ([N.SockAddr], O.Packet) - act udp c _ (cs,msg) (O.Packet_Bundle (O.Bundle ts ms)) = foldM (act udp c (Just ts)) (cs,msg) $ map O.Packet_Message ms - act udp c _ (cs,msg) (O.Packet_Message (O.Message "/hello" [])) - = do O.sendTo udp msg c - return (nub (c:cs),msg) - act udp _ (Just ts) (cs,_) (O.Packet_Message (O.Message "/transmit/cps/cycle" params)) = - do let path' = "/cps/cycle" - msg' = O.p_bundle ts [O.Message path' params] - mapM_ (O.sendTo udp msg') cs - return (cs, msg') - act _ x _ (cs,msg) pkt = do writeError $ "Unknown packet (serv): " ++ show pkt ++ " / " ++ show x - return (cs,msg) - catchAny :: IO a -> (E.SomeException -> IO a) -> IO a - catchAny = E.catch - defaultCpsMessage = do ts <- O.time - return $ O.p_bundle ts [O.Message "/cps/cycle" [O.Float 0, - O.Float $ realToFrac defaultCps, - O.Int32 0 - ] - ] - + checkArc $! st + -- Time is processed at a fixed rate according to configuration + -- logicalTime gives the time when a tick starts based on when + -- processing first started. + logicalTime :: Link.Micros -> Int64 -> Link.Micros + logicalTime startTime ticks' = startTime + ticks' * frameTimespan + -- tick moves the logical time forward or recalculates the ticks in case + -- the logical time is out of sync with Link time. + -- tick delays the thread when logical time is ahead of Link time. + tick :: State -> IO a + tick st = do + now <- Link.clock abletonLink + let preferredNewTick = ticks st + 1 + logicalNow = logicalTime (start st) preferredNewTick + aheadOfNow = now + processAhead + actualTick = (aheadOfNow - start st) `div` frameTimespan + drifted = abs (actualTick - preferredNewTick) > cSkipTicks config + newTick | drifted = actualTick + | otherwise = preferredNewTick + st' = st {ticks = newTick} + delta = min frameTimespan (logicalNow - aheadOfNow) + if drifted + then writeError $ "skip: " ++ (show (actualTick - ticks st)) + else when (delta > 0) $ threadDelay $ fromIntegral delta + checkArc st' + -- The reference time Link uses, + -- is the time the audio for a certain beat hits the speaker. + -- Processing of the nowArc should happen early enough for + -- all events in the nowArc to hit the speaker, but not too early. + -- Processing thus needs to happen a short while before the start + -- of nowArc. How far ahead is controlled by cProcessAhead. + processAhead :: Link.Micros + processAhead = round $ (cProcessAhead config) * 1000000 + checkArc :: State -> IO a + checkArc st = do + actions <- swapMVar actionsMV [] + st' <- processActions st actions + let logicalEnd = logicalTime (start st') $ ticks st' + 1 + nextArcStartCycle = P.stop $ nowArc st' + ss <- Link.createAndCaptureAppSessionState abletonLink + arcStartTime <- cyclesToTime config ss nextArcStartCycle + Link.destroySessionState ss + if (arcStartTime < logicalEnd) + then processArc st' + else tick st' + processArc :: State -> IO a + processArc st = + do + streamState <- takeMVar stateMV + let logicalEnd = logicalTime (start st) $ ticks st + 1 + startCycle = P.stop $ nowArc st + sessionState <- Link.createAndCaptureAppSessionState abletonLink + endCycle <- timeToCycles' config sessionState logicalEnd + let st' = st {nowArc = P.Arc startCycle endCycle, + nowEnd = logicalEnd + } + nowOsc <- O.time + nowLink <- Link.clock abletonLink + let ops = LinkOperations { + timeAtBeat = \beat -> Link.timeAtBeat sessionState beat quantum , + timeToCycles = timeToCycles' config sessionState, + getTempo = Link.getTempo sessionState, + setTempo = Link.setTempo sessionState, + linkToOscTime = \lt -> addMicrosToOsc (lt - nowLink) nowOsc, + beatToCycles = btc, + cyclesToBeat = ctb + } + let state = TickState { + tickArc = nowArc st', + tickNudge = nudged st' + } + streamState' <- (onTick ac) state ops streamState + Link.commitAndDestroyAppSessionState abletonLink sessionState + putMVar stateMV streamState' + tick st' + btc :: CDouble -> CDouble + btc beat = beat / cyclesPerBeat + ctb :: CDouble -> CDouble + ctb cyc = cyc * cyclesPerBeat + processActions :: State -> [TempoAction] -> IO State + processActions st [] = return $! st + processActions st actions = do + streamState <- takeMVar stateMV + (st', streamState') <- handleActions st actions streamState + putMVar stateMV streamState' + return $! st' + handleActions :: State -> [TempoAction] -> P.ValueMap -> IO (State, P.ValueMap) + handleActions st [] streamState = return (st, streamState) + handleActions st (ResetCycles : otherActions) streamState = + do + (st', streamState') <- handleActions st otherActions streamState + sessionState <- Link.createAndCaptureAppSessionState abletonLink + let logicalEnd = logicalTime (start st') $ ticks st' + 1 + st'' = st' { + nowArc = P.Arc 0 0, + nowEnd = logicalEnd + frameTimespan + } + now <- Link.clock abletonLink + Link.requestBeatAtTime sessionState 0 now quantum + Link.commitAndDestroyAppSessionState abletonLink sessionState + return (st'', streamState') + handleActions st (SingleTick pat : otherActions) streamState = + do + (st', streamState') <- handleActions st otherActions streamState + -- onSingleTick assumes it runs at beat 0. + -- The best way to achieve that is to use forceBeatAtTime. + -- But using forceBeatAtTime means we can not commit its session state. + -- Another session state, which we will commit, + -- is introduced to keep track of tempo changes. + sessionState <- Link.createAndCaptureAppSessionState abletonLink + zeroedSessionState <- Link.createAndCaptureAppSessionState abletonLink + nowOsc <- O.time + nowLink <- Link.clock abletonLink + Link.forceBeatAtTime zeroedSessionState 0 (nowLink + processAhead) quantum + let ops = LinkOperations { + timeAtBeat = \beat -> Link.timeAtBeat zeroedSessionState beat quantum, + timeToCycles = timeToCycles' config zeroedSessionState, + getTempo = Link.getTempo zeroedSessionState, + setTempo = \bpm micros -> + Link.setTempo zeroedSessionState bpm micros >> + Link.setTempo sessionState bpm micros, + linkToOscTime = \lt -> addMicrosToOsc (lt - nowLink) nowOsc, + beatToCycles = btc, + cyclesToBeat = ctb + } + streamState'' <- (onSingleTick ac) nowLink ops streamState' pat + Link.commitAndDestroyAppSessionState abletonLink sessionState + Link.destroySessionState zeroedSessionState + return (st', streamState'') + handleActions st (SetNudge nudge : otherActions) streamState = + do + (st', streamState') <- handleActions st otherActions streamState + let st'' = st' {nudged = nudge} + return (st'', streamState') + handleActions st (StreamReplace k pat : otherActions) streamState = + do + (st', streamState') <- handleActions st otherActions streamState + E.catch ( + do + now <- Link.clock abletonLink + sessionState <- Link.createAndCaptureAppSessionState abletonLink + cyc <- timeToCycles' config sessionState now + Link.destroySessionState sessionState + -- put pattern id and change time in control input + let streamState'' = Map.insert ("_t_all") (P.VR $! cyc) $ Map.insert ("_t_" ++ fromID k) (P.VR $! cyc) streamState' + (updatePattern ac) k pat + return (st', streamState'') + ) + (\(e :: E.SomeException) -> do + hPutStrLn stderr $ "Error in pattern: " ++ show e + return (st', streamState') + ) + handleActions st (Transition historyFlag f patId pat : otherActions) streamState = + do + (st', streamState') <- handleActions st otherActions streamState + let + appendPat flag = if flag then (pat:) else id + updatePS (Just playState) = playState {history = (appendPat historyFlag) (history playState)} + updatePS Nothing = PlayState {pattern = silence, + mute = False, + solo = False, + history = (appendPat historyFlag) (silence:[]) + } + transition' pat' = do now <- Link.clock abletonLink + ss <- Link.createAndCaptureAppSessionState abletonLink + c <- timeToCycles' config ss now + return $! f c pat' + pMap <- readMVar mapMV + let playState = updatePS $ Map.lookup (fromID patId) pMap + pat' <- transition' $ appendPat (not historyFlag) (history playState) + let pMap' = Map.insert (fromID patId) (playState {pattern = pat'}) pMap + _ <- swapMVar mapMV pMap' + return (st', streamState') diff --git a/src/Sound/Tidal/Transition.hs b/src/Sound/Tidal/Transition.hs index 38f937052..b4fda7014 100644 --- a/src/Sound/Tidal/Transition.hs +++ b/src/Sound/Tidal/Transition.hs @@ -4,7 +4,7 @@ module Sound.Tidal.Transition where import Prelude hiding ((<*), (*>)) -import Control.Concurrent.MVar (readMVar, swapMVar) +import Control.Concurrent.MVar (readMVar, swapMVar, modifyMVar_) import qualified Sound.OSC.FD as O import qualified Data.Map.Strict as Map @@ -16,7 +16,7 @@ import Sound.Tidal.ID import Sound.Tidal.Params (gain, pan) import Sound.Tidal.Pattern import Sound.Tidal.Stream -import Sound.Tidal.Tempo (timeToCycles) +import Sound.Tidal.Tempo as T import Sound.Tidal.UI (fadeOutFrom, fadeInFrom) import Sound.Tidal.Utils (enumerate) @@ -42,24 +42,7 @@ import Sound.Tidal.Utils (enumerate) -- the "historyFlag" determines if the new pattern should be placed on the history stack or not transition :: Stream -> Bool -> (Time -> [ControlPattern] -> ControlPattern) -> ID -> ControlPattern -> IO () transition stream historyFlag f patId !pat = - do pMap <- readMVar (sPMapMV stream) - let playState = updatePS $ Map.lookup (fromID patId) pMap - pat' <- transition' $ appendPat (not historyFlag) (history playState) - let pMap' = Map.insert (fromID patId) (playState {pattern = pat'}) pMap - _ <- swapMVar (sPMapMV stream) pMap' - return () - where - appendPat flag = if flag then (pat:) else id - updatePS (Just playState) = playState {history = (appendPat historyFlag) (history playState)} - updatePS Nothing = PlayState {pattern = silence, - mute = False, - solo = False, - history = (appendPat historyFlag) (silence:[]) - } - transition' pat' = do tempo <- readMVar $ sTempoMV stream - now <- O.time - let c = timeToCycles tempo now - return $ f c pat' + modifyMVar_ (sActionsMV stream) (\actions -> return $! (T.Transition historyFlag f patId pat) : actions) mortalOverlay :: Time -> Time -> [Pattern a] -> Pattern a mortalOverlay _ _ [] = silence diff --git a/src/Sound/Tidal/UI.hs b/src/Sound/Tidal/UI.hs index 369bbf122..c598977c2 100644 --- a/src/Sound/Tidal/UI.hs +++ b/src/Sound/Tidal/UI.hs @@ -110,7 +110,7 @@ rand :: Fractional a => Pattern a rand = Pattern (\(State a@(Arc s e) _) -> [Event (Context []) Nothing a (realToFrac $ (timeToRand ((e + s)/2) :: Double))]) -- | Boolean rand - a continuous stream of true/false values, with a 50/50 chance. -brand :: Pattern Bool +brand :: Pattern Bool brand = _brandBy 0.5 -- | Boolean rand with probability as input, e.g. brandBy 0.25 is 25% chance of being true. @@ -718,6 +718,8 @@ In the above, three sounds are picked from the pattern on the right according to the structure given by the `e 3 8`. It ends up picking two `bd` sounds, a `cp` and missing the `sn` entirely. +A negative first argument provides the inverse of the euclidean pattern. + These types of sequences use "Bjorklund's algorithm", which wasn't made for music but for an application in nuclear physics, which is exciting. More exciting still is that it is very similar in structure to the one of the first @@ -755,7 +757,8 @@ euclid :: Pattern Int -> Pattern Int -> Pattern a -> Pattern a euclid = tParam2 _euclid _euclid :: Int -> Int -> Pattern a -> Pattern a -_euclid n k a = fastcat $ fmap (bool silence a) $ bjorklund (n,k) +_euclid n k a | n >= 0 = fastcat $ fmap (bool silence a) $ bjorklund (n,k) + | otherwise = fastcat $ fmap (bool a silence) $ bjorklund (-n,k) {- | `euclidfull n k pa pb` stacks @e n k pa@ with @einv n k pb@ -} euclidFull :: Pattern Int -> Pattern Int -> Pattern a -> Pattern a -> Pattern a @@ -809,7 +812,7 @@ euclidInv :: Pattern Int -> Pattern Int -> Pattern a -> Pattern a euclidInv = tParam2 _euclidInv _euclidInv :: Int -> Int -> Pattern a -> Pattern a -_euclidInv n k a = fastcat $ fmap (bool a silence) $ bjorklund (n,k) +_euclidInv n k a = _euclid (-n) k a index :: Real b => b -> Pattern b -> Pattern c -> Pattern c index sz indexpat pat = @@ -960,7 +963,7 @@ discretise = segment -- | @randcat ps@: does a @slowcat@ on the list of patterns @ps@ but -- randomises the order in which they are played. randcat :: [Pattern a] -> Pattern a -randcat ps = spread' rotL (_segment 1 $ (%1) . fromIntegral <$> (_irand (length ps) :: Pattern Int)) (slowcat ps) +randcat ps = spread' rotL (_segment 1 $ (% 1) . fromIntegral <$> (_irand (length ps) :: Pattern Int)) (slowcat ps) wrandcat :: [(Pattern a, Double)] -> Pattern a wrandcat ps = unwrap $ wchooseBy (segment 1 rand) ps @@ -1228,33 +1231,32 @@ fit' cyc n from to p = squeezeJoin $ _fit n mapMasks to p' = density cyc p from' = density cyc from -{-| @chunk n f p@ treats the given pattern @p@ as having @n@ chunks, and applies the function @f@ to one of those sections per cycle, running from left to right. - -@ -d1 $ chunk 4 (density 4) $ sound "cp sn arpy [mt lt]" -@ +{-| + Treats the given pattern @p@ as having @n@ chunks, and applies the function @f@ to one of those sections per cycle. + Running: + - from left to right if chunk number is positive + - from right to left if chunk number is negative + + @ + d1 $ chunk 4 (fast 4) $ sound "cp sn arpy [mt lt]" + @ -} -_chunk :: Int -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b -_chunk n f p = cat [withinArc (Arc (i % fromIntegral n) ((i+1) % fromIntegral n)) f p | i <- [0 .. fromIntegral n - 1]] - - chunk :: Pattern Int -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b -chunk npat f p = innerJoin $ (\n -> _chunk n f p) <$> npat - --- deprecated (renamed to chunk) -runWith :: Int -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b -runWith = _chunk +chunk npat f p = innerJoin $ (\n -> _chunk n f p) <$> npat -{-| @chunk'@ works much the same as `chunk`, but runs from right to left. --} --- this was throwing a parse error when I ran it in tidal whenever I changed the function name.. -_chunk' :: Integral a => a -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b -_chunk' n f p = do i <- _slow (toRational n) $ rev $ run (fromIntegral n) - withinArc (Arc (i % fromIntegral n) ((i+)1 % fromIntegral n)) f p +_chunk :: Integral a => a -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b +_chunk n f p | n >= 0 = cat [withinArc (Arc (i % fromIntegral n) ((i+1) % fromIntegral n)) f p | i <- [0 .. fromIntegral n - 1]] + | otherwise = do i <- _slow (toRational (-n)) $ rev $ run (fromIntegral (-n)) + withinArc (Arc (i % fromIntegral (-n)) ((i+1) % fromIntegral (-n))) f p +-- | DEPRECATED, use 'chunk' with negative numbers instead chunk' :: Integral a1 => Pattern a1 -> (Pattern a2 -> Pattern a2) -> Pattern a2 -> Pattern a2 chunk' npat f p = innerJoin $ (\n -> _chunk' n f p) <$> npat +-- | DEPRECATED, use '_chunk' with negative numbers instead +_chunk' :: Integral a => a -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b +_chunk' n f p = _chunk (-n) f p + _inside :: Time -> (Pattern a1 -> Pattern a) -> Pattern a1 -> Pattern a _inside n f p = _fast n $ f (_slow n p) @@ -1468,7 +1470,7 @@ rolledBy "<1 -0.5 0.25 -0.125>" $ note "c'maj9" # s "superpiano" rolledWith :: Ratio Integer -> Pattern a -> Pattern a rolledWith t = withEvents aux where aux es = concatMap (steppityIn) (groupBy (\a b -> whole a == whole b) $ ((isRev t) es)) - isRev b = (\x -> if x > 0 then id else reverse ) b + isRev b = (\x -> if x > 0 then id else reverse ) b steppityIn xs = mapMaybe (\(n, ev) -> (timeguard n xs ev t)) $ enumerate xs timeguard _ _ ev 0 = return ev timeguard n xs ev _ = (shiftIt n (length xs) ev) diff --git a/src/Sound/Tidal/Version.hs b/src/Sound/Tidal/Version.hs index e26ffdafa..82bb265db 100644 --- a/src/Sound/Tidal/Version.hs +++ b/src/Sound/Tidal/Version.hs @@ -21,7 +21,7 @@ import Paths_tidal -} tidal_version :: String -tidal_version = "1.8.0" +tidal_version = "1.9.0" tidal_status :: IO () tidal_status = tidal_status_string >>= putStrLn diff --git a/stack.yaml b/stack.yaml index 8867f79c2..c933842f4 100644 --- a/stack.yaml +++ b/stack.yaml @@ -3,6 +3,7 @@ resolver: lts-16.31 packages: - '.' - 'tidal-parse' + - 'tidal-link' extra-deps: - hosc-0.18.1 diff --git a/test/Sound/Tidal/ControlTest.hs b/test/Sound/Tidal/ControlTest.hs index 7c0f879ca..4a5b4aa67 100644 --- a/test/Sound/Tidal/ControlTest.hs +++ b/test/Sound/Tidal/ControlTest.hs @@ -18,15 +18,23 @@ run = describe "echo" $ do it "should echo the event by the specified time and multiply the gain factor" $ do - compareP (Arc 0 1) - (echo 2 0.25 0.5 $ s "bd" # gain "1") - (stack [rotR 0 "bd" # gain 1, rotR 0.25 "bd" # gain 0.5]) + comparePD (Arc 0 1) + (echo 3 0.2 0.5 $ s "bd" # gain "1") + (stack [ + rotR 0 $ s "bd" # gain 1, + rotR 0.2 $ s "bd" # gain 0.5, + rotR 0.4 $ s "bd" # gain 0.25 + ]) describe "echoWith" $ do it "should echo the event by the specified time and apply the specified function" $ do - compareP (Arc 0 1) - (echoWith 2 0.25 (|* speed 2) $ s "bd" # speed "1") - (stack [rotR 0 "bd" # speed 1, rotR 0.25 "bd" # speed 2]) + comparePD (Arc 0 1) + (echoWith 3 0.25 (|* speed 2) $ s "bd" # speed "1") + (stack [ + rotR 0 $ s "bd" # speed 1, + rotR 0.25 $ s "bd" # speed 2, + rotR 0.5 $ s "bd" # speed 4 + ]) describe "stutWith" $ do it "can mimic stut" $ do diff --git a/test/Sound/Tidal/ParseTest.hs b/test/Sound/Tidal/ParseTest.hs index 55a26c5a7..5448f37c9 100644 --- a/test/Sound/Tidal/ParseTest.hs +++ b/test/Sound/Tidal/ParseTest.hs @@ -160,6 +160,42 @@ run = compareP (Arc 0 2) ("c'major c'minor" :: Pattern Note) ("'major 'minor") + it "can invert chords" $ do + compareP (Arc 0 2) + ("c'major'i" :: Pattern Note) + ("[4,7,12]") + it "can invert chords using a number" $ do + compareP (Arc 0 2) + ("c'major'i2" :: Pattern Note) + ("[7,12,16]") + it "spread chords over a range" $ do + compareP (Arc 0 2) + ("c'major'5 e'min7'5" :: Pattern Note) + ("[0,4,7,12,16] [4,7,11,14,16]") + it "can open chords" $ do + compareP (Arc 0 2) + ("c'major'o" :: Pattern Note) + ("[-12,-5,4]") + it "can drop notes in a chord" $ do + compareP (Arc 0 2) + ("c'major'd1" :: Pattern Note) + ("[-5,0,4]") + it "can apply multiple modifiers" $ do + compareP (Arc 0 2) + ("c'major'i'5" :: Pattern Note) + ("[4,7,12,16,19]") + it "can pattern modifiers" $ do + compareP (Arc 0 2) + ("c'major'" :: Pattern Note) + ("<[4,7,12] [0,4,7,12,16]>") + it "can pattern chord names" $ do + compareP (Arc 0 2) + ("c''i" :: Pattern Note) + ("<[4,7,12] [3,7,12]>") + it "can pattern chord notes" $ do + compareP (Arc 0 2) + ("''i" :: Pattern Note) + ("<[4,7,12] [7,11,16]>") it "handle trailing and leading whitespaces" $ do compareP (Arc 0 1) (" bd " :: Pattern String) diff --git a/test/Sound/Tidal/PatternTest.hs b/test/Sound/Tidal/PatternTest.hs index 951cee61d..898a135b3 100644 --- a/test/Sound/Tidal/PatternTest.hs +++ b/test/Sound/Tidal/PatternTest.hs @@ -428,17 +428,6 @@ run = let res = defragParts [(Event (Context []) (Just $ Arc 1 2) (Arc 3 4) 5), (Event (Context []) (Just $ Arc 7 8) (Arc 4 3) (5 :: Int))] property $ [Event (Context []) (Just $ Arc 1 2) (Arc 3 4) 5, Event (Context []) (Just $ Arc 7 8) (Arc 4 3) (5 :: Int)] === res - describe "compareDefrag" $ do - it "compare list with Events with empty list of Events" $ do - let res = compareDefrag [Event (Context []) (Just $ Arc 1 2) (Arc 3 4) (5 :: Int), Event (Context []) (Just $ Arc 1 2) (Arc 4 3) (5 :: Int)] [] - property $ False === res - it "compare lists containing same Events but of different length" $ do - let res = compareDefrag [Event (Context []) (Just $ Arc 1 2) (Arc 3 4) (5 :: Int), Event (Context []) (Just $ Arc 1 2) (Arc 4 3) 5] [Event (Context []) (Just $ Arc 1 2) (Arc 3 4) (5 :: Int)] - property $ True === res - it "compare lists of same length with same Events" $ do - let res = compareDefrag [Event (Context []) (Just $ Arc 1 2) (Arc 3 4) (5 :: Int)] [Event (Context []) (Just $ Arc 1 2) (Arc 3 4) (5 :: Int)] - property $ True === res - describe "sect" $ do it "take two Arcs and return - Arc (max of two starts) (min of two ends)" $ do let res = sect (Arc 2.2 3) (Arc 2 2.9) diff --git a/test/Sound/Tidal/UITest.hs b/test/Sound/Tidal/UITest.hs index 4a22e7717..71a3f0980 100644 --- a/test/Sound/Tidal/UITest.hs +++ b/test/Sound/Tidal/UITest.hs @@ -306,6 +306,15 @@ run = (euclid 11 24 "x", "x ~ ~ x ~ x ~ x ~ x ~ x ~ ~ x ~ x ~ x ~ x ~ x ~"), (euclid 13 24 "x", "x ~ x x ~ x ~ x ~ x ~ x ~ x x ~ x ~ x ~ x ~ x ~") ] :: [(Pattern String, String)]) + it "can be called with a negative first value to give the inverse" $ do + compareP (Arc 0 1) + (euclid (-3) 8 ("bd" :: Pattern String)) + (euclidInv 3 8 ("bd" :: Pattern String)) + it "can be called with a negative first value to give the inverse (patternable)" $ do + compareP (Arc 0 1) + (euclid (-3) 8 ("bd" :: Pattern String)) + ("bd(-3,8)" :: Pattern String) + describe "wedge" $ do it "should not freeze tidal amount is 1" $ do @@ -360,6 +369,10 @@ run = compareP (Arc 0 4) (chunk 2 (fast 2) $ "a b" :: Pattern String) (slow 2 $ "a b b _ a _ a b" :: Pattern String) + it "should chunk backward with a negative number" $ do + compareP (Arc 0 4) + (chunk (-2) (rev) $ ("a b c d" :: Pattern String)) + (slow 2 $ "a b b a d c c d" :: Pattern String) describe "binary" $ do it "converts a number to a pattern of boolean" $ do diff --git a/test/TestUtils.hs b/test/TestUtils.hs index 7bbd1940f..eb9928af5 100644 --- a/test/TestUtils.hs +++ b/test/TestUtils.hs @@ -36,13 +36,17 @@ instance TolerantEq (Event ValueMap) where -- | Compare the events of two patterns using the given arc compareP :: (Ord a, Show a) => Arc -> Pattern a -> Pattern a -> Property -compareP a p p' = (sort $ query (stripContext p) $ State a Map.empty) `shouldBe` (sort $ query (stripContext p') $ State a Map.empty) +compareP a p p' = + (sort $ queryArc (stripContext p) a) + `shouldBe` + (sort $ queryArc (stripContext p') a) -- | Like @compareP@, but tries to 'defragment' the events -comparePD :: (Ord a) => Arc -> Pattern a -> Pattern a -> Bool -comparePD a p p' = compareDefrag es es' - where es = query (stripContext p) (State a Map.empty) - es' = query (stripContext p') (State a Map.empty) +comparePD :: (Ord a, Show a) => Arc -> Pattern a -> Pattern a -> Property +comparePD a p p' = + (sort $ defragParts $ queryArc (stripContext p) a) + `shouldBe` + (sort $ defragParts $ queryArc (stripContext p') a) -- | Like @compareP@, but for control patterns, with some tolerance for floating point error compareTol :: Arc -> ControlPattern -> ControlPattern -> Bool diff --git a/tidal-link/LICENSE b/tidal-link/LICENSE new file mode 100644 index 000000000..f288702d2 --- /dev/null +++ b/tidal-link/LICENSE @@ -0,0 +1,674 @@ + GNU GENERAL PUBLIC LICENSE + Version 3, 29 June 2007 + + Copyright (C) 2007 Free Software Foundation, Inc. + Everyone is permitted to copy and distribute verbatim copies + of this license document, but changing it is not allowed. + + Preamble + + The GNU General Public License is a free, copyleft license for +software and other kinds of works. + + The licenses for most software and other practical works are designed +to take away your freedom to share and change the works. By contrast, +the GNU General Public License is intended to guarantee your freedom to +share and change all versions of a program--to make sure it remains free +software for all its users. We, the Free Software Foundation, use the +GNU General Public License for most of our software; it applies also to +any other work released this way by its authors. You can apply it to +your programs, too. + + When we speak of free software, we are referring to freedom, not +price. Our General Public Licenses are designed to make sure that you +have the freedom to distribute copies of free software (and charge for +them if you wish), that you receive source code or can get it if you +want it, that you can change the software or use pieces of it in new +free programs, and that you know you can do these things. + + To protect your rights, we need to prevent others from denying you +these rights or asking you to surrender the rights. Therefore, you have +certain responsibilities if you distribute copies of the software, or if +you modify it: responsibilities to respect the freedom of others. + + For example, if you distribute copies of such a program, whether +gratis or for a fee, you must pass on to the recipients the same +freedoms that you received. You must make sure that they, too, receive +or can get the source code. And you must show them these terms so they +know their rights. + + Developers that use the GNU GPL protect your rights with two steps: +(1) assert copyright on the software, and (2) offer you this License +giving you legal permission to copy, distribute and/or modify it. + + For the developers' and authors' protection, the GPL clearly explains +that there is no warranty for this free software. For both users' and +authors' sake, the GPL requires that modified versions be marked as +changed, so that their problems will not be attributed erroneously to +authors of previous versions. + + Some devices are designed to deny users access to install or run +modified versions of the software inside them, although the manufacturer +can do so. This is fundamentally incompatible with the aim of +protecting users' freedom to change the software. The systematic +pattern of such abuse occurs in the area of products for individuals to +use, which is precisely where it is most unacceptable. Therefore, we +have designed this version of the GPL to prohibit the practice for those +products. If such problems arise substantially in other domains, we +stand ready to extend this provision to those domains in future versions +of the GPL, as needed to protect the freedom of users. + + Finally, every program is threatened constantly by software patents. +States should not allow patents to restrict development and use of +software on general-purpose computers, but in those that do, we wish to +avoid the special danger that patents applied to a free program could +make it effectively proprietary. To prevent this, the GPL assures that +patents cannot be used to render the program non-free. + + The precise terms and conditions for copying, distribution and +modification follow. + + TERMS AND CONDITIONS + + 0. Definitions. + + "This License" refers to version 3 of the GNU General Public License. + + "Copyright" also means copyright-like laws that apply to other kinds of +works, such as semiconductor masks. + + "The Program" refers to any copyrightable work licensed under this +License. Each licensee is addressed as "you". "Licensees" and +"recipients" may be individuals or organizations. + + To "modify" a work means to copy from or adapt all or part of the work +in a fashion requiring copyright permission, other than the making of an +exact copy. The resulting work is called a "modified version" of the +earlier work or a work "based on" the earlier work. + + A "covered work" means either the unmodified Program or a work based +on the Program. + + To "propagate" a work means to do anything with it that, without +permission, would make you directly or secondarily liable for +infringement under applicable copyright law, except executing it on a +computer or modifying a private copy. Propagation includes copying, +distribution (with or without modification), making available to the +public, and in some countries other activities as well. + + To "convey" a work means any kind of propagation that enables other +parties to make or receive copies. Mere interaction with a user through +a computer network, with no transfer of a copy, is not conveying. + + An interactive user interface displays "Appropriate Legal Notices" +to the extent that it includes a convenient and prominently visible +feature that (1) displays an appropriate copyright notice, and (2) +tells the user that there is no warranty for the work (except to the +extent that warranties are provided), that licensees may convey the +work under this License, and how to view a copy of this License. If +the interface presents a list of user commands or options, such as a +menu, a prominent item in the list meets this criterion. + + 1. Source Code. + + The "source code" for a work means the preferred form of the work +for making modifications to it. "Object code" means any non-source +form of a work. + + A "Standard Interface" means an interface that either is an official +standard defined by a recognized standards body, or, in the case of +interfaces specified for a particular programming language, one that +is widely used among developers working in that language. + + The "System Libraries" of an executable work include anything, other +than the work as a whole, that (a) is included in the normal form of +packaging a Major Component, but which is not part of that Major +Component, and (b) serves only to enable use of the work with that +Major Component, or to implement a Standard Interface for which an +implementation is available to the public in source code form. A +"Major Component", in this context, means a major essential component +(kernel, window system, and so on) of the specific operating system +(if any) on which the executable work runs, or a compiler used to +produce the work, or an object code interpreter used to run it. + + The "Corresponding Source" for a work in object code form means all +the source code needed to generate, install, and (for an executable +work) run the object code and to modify the work, including scripts to +control those activities. However, it does not include the work's +System Libraries, or general-purpose tools or generally available free +programs which are used unmodified in performing those activities but +which are not part of the work. For example, Corresponding Source +includes interface definition files associated with source files for +the work, and the source code for shared libraries and dynamically +linked subprograms that the work is specifically designed to require, +such as by intimate data communication or control flow between those +subprograms and other parts of the work. + + The Corresponding Source need not include anything that users +can regenerate automatically from other parts of the Corresponding +Source. + + The Corresponding Source for a work in source code form is that +same work. + + 2. Basic Permissions. + + All rights granted under this License are granted for the term of +copyright on the Program, and are irrevocable provided the stated +conditions are met. This License explicitly affirms your unlimited +permission to run the unmodified Program. The output from running a +covered work is covered by this License only if the output, given its +content, constitutes a covered work. This License acknowledges your +rights of fair use or other equivalent, as provided by copyright law. + + You may make, run and propagate covered works that you do not +convey, without conditions so long as your license otherwise remains +in force. You may convey covered works to others for the sole purpose +of having them make modifications exclusively for you, or provide you +with facilities for running those works, provided that you comply with +the terms of this License in conveying all material for which you do +not control copyright. Those thus making or running the covered works +for you must do so exclusively on your behalf, under your direction +and control, on terms that prohibit them from making any copies of +your copyrighted material outside their relationship with you. + + Conveying under any other circumstances is permitted solely under +the conditions stated below. Sublicensing is not allowed; section 10 +makes it unnecessary. + + 3. Protecting Users' Legal Rights From Anti-Circumvention Law. + + No covered work shall be deemed part of an effective technological +measure under any applicable law fulfilling obligations under article +11 of the WIPO copyright treaty adopted on 20 December 1996, or +similar laws prohibiting or restricting circumvention of such +measures. + + When you convey a covered work, you waive any legal power to forbid +circumvention of technological measures to the extent such circumvention +is effected by exercising rights under this License with respect to +the covered work, and you disclaim any intention to limit operation or +modification of the work as a means of enforcing, against the work's +users, your or third parties' legal rights to forbid circumvention of +technological measures. + + 4. Conveying Verbatim Copies. + + You may convey verbatim copies of the Program's source code as you +receive it, in any medium, provided that you conspicuously and +appropriately publish on each copy an appropriate copyright notice; +keep intact all notices stating that this License and any +non-permissive terms added in accord with section 7 apply to the code; +keep intact all notices of the absence of any warranty; and give all +recipients a copy of this License along with the Program. + + You may charge any price or no price for each copy that you convey, +and you may offer support or warranty protection for a fee. + + 5. Conveying Modified Source Versions. + + You may convey a work based on the Program, or the modifications to +produce it from the Program, in the form of source code under the +terms of section 4, provided that you also meet all of these conditions: + + a) The work must carry prominent notices stating that you modified + it, and giving a relevant date. + + b) The work must carry prominent notices stating that it is + released under this License and any conditions added under section + 7. This requirement modifies the requirement in section 4 to + "keep intact all notices". + + c) You must license the entire work, as a whole, under this + License to anyone who comes into possession of a copy. This + License will therefore apply, along with any applicable section 7 + additional terms, to the whole of the work, and all its parts, + regardless of how they are packaged. This License gives no + permission to license the work in any other way, but it does not + invalidate such permission if you have separately received it. + + d) If the work has interactive user interfaces, each must display + Appropriate Legal Notices; however, if the Program has interactive + interfaces that do not display Appropriate Legal Notices, your + work need not make them do so. + + A compilation of a covered work with other separate and independent +works, which are not by their nature extensions of the covered work, +and which are not combined with it such as to form a larger program, +in or on a volume of a storage or distribution medium, is called an +"aggregate" if the compilation and its resulting copyright are not +used to limit the access or legal rights of the compilation's users +beyond what the individual works permit. Inclusion of a covered work +in an aggregate does not cause this License to apply to the other +parts of the aggregate. + + 6. Conveying Non-Source Forms. + + You may convey a covered work in object code form under the terms +of sections 4 and 5, provided that you also convey the +machine-readable Corresponding Source under the terms of this License, +in one of these ways: + + a) Convey the object code in, or embodied in, a physical product + (including a physical distribution medium), accompanied by the + Corresponding Source fixed on a durable physical medium + customarily used for software interchange. + + b) Convey the object code in, or embodied in, a physical product + (including a physical distribution medium), accompanied by a + written offer, valid for at least three years and valid for as + long as you offer spare parts or customer support for that product + model, to give anyone who possesses the object code either (1) a + copy of the Corresponding Source for all the software in the + product that is covered by this License, on a durable physical + medium customarily used for software interchange, for a price no + more than your reasonable cost of physically performing this + conveying of source, or (2) access to copy the + Corresponding Source from a network server at no charge. + + c) Convey individual copies of the object code with a copy of the + written offer to provide the Corresponding Source. This + alternative is allowed only occasionally and noncommercially, and + only if you received the object code with such an offer, in accord + with subsection 6b. + + d) Convey the object code by offering access from a designated + place (gratis or for a charge), and offer equivalent access to the + Corresponding Source in the same way through the same place at no + further charge. You need not require recipients to copy the + Corresponding Source along with the object code. If the place to + copy the object code is a network server, the Corresponding Source + may be on a different server (operated by you or a third party) + that supports equivalent copying facilities, provided you maintain + clear directions next to the object code saying where to find the + Corresponding Source. Regardless of what server hosts the + Corresponding Source, you remain obligated to ensure that it is + available for as long as needed to satisfy these requirements. + + e) Convey the object code using peer-to-peer transmission, provided + you inform other peers where the object code and Corresponding + Source of the work are being offered to the general public at no + charge under subsection 6d. + + A separable portion of the object code, whose source code is excluded +from the Corresponding Source as a System Library, need not be +included in conveying the object code work. + + A "User Product" is either (1) a "consumer product", which means any +tangible personal property which is normally used for personal, family, +or household purposes, or (2) anything designed or sold for incorporation +into a dwelling. In determining whether a product is a consumer product, +doubtful cases shall be resolved in favor of coverage. For a particular +product received by a particular user, "normally used" refers to a +typical or common use of that class of product, regardless of the status +of the particular user or of the way in which the particular user +actually uses, or expects or is expected to use, the product. A product +is a consumer product regardless of whether the product has substantial +commercial, industrial or non-consumer uses, unless such uses represent +the only significant mode of use of the product. + + "Installation Information" for a User Product means any methods, +procedures, authorization keys, or other information required to install +and execute modified versions of a covered work in that User Product from +a modified version of its Corresponding Source. The information must +suffice to ensure that the continued functioning of the modified object +code is in no case prevented or interfered with solely because +modification has been made. + + If you convey an object code work under this section in, or with, or +specifically for use in, a User Product, and the conveying occurs as +part of a transaction in which the right of possession and use of the +User Product is transferred to the recipient in perpetuity or for a +fixed term (regardless of how the transaction is characterized), the +Corresponding Source conveyed under this section must be accompanied +by the Installation Information. But this requirement does not apply +if neither you nor any third party retains the ability to install +modified object code on the User Product (for example, the work has +been installed in ROM). + + The requirement to provide Installation Information does not include a +requirement to continue to provide support service, warranty, or updates +for a work that has been modified or installed by the recipient, or for +the User Product in which it has been modified or installed. Access to a +network may be denied when the modification itself materially and +adversely affects the operation of the network or violates the rules and +protocols for communication across the network. + + Corresponding Source conveyed, and Installation Information provided, +in accord with this section must be in a format that is publicly +documented (and with an implementation available to the public in +source code form), and must require no special password or key for +unpacking, reading or copying. + + 7. Additional Terms. + + "Additional permissions" are terms that supplement the terms of this +License by making exceptions from one or more of its conditions. +Additional permissions that are applicable to the entire Program shall +be treated as though they were included in this License, to the extent +that they are valid under applicable law. If additional permissions +apply only to part of the Program, that part may be used separately +under those permissions, but the entire Program remains governed by +this License without regard to the additional permissions. + + When you convey a copy of a covered work, you may at your option +remove any additional permissions from that copy, or from any part of +it. (Additional permissions may be written to require their own +removal in certain cases when you modify the work.) You may place +additional permissions on material, added by you to a covered work, +for which you have or can give appropriate copyright permission. + + Notwithstanding any other provision of this License, for material you +add to a covered work, you may (if authorized by the copyright holders of +that material) supplement the terms of this License with terms: + + a) Disclaiming warranty or limiting liability differently from the + terms of sections 15 and 16 of this License; or + + b) Requiring preservation of specified reasonable legal notices or + author attributions in that material or in the Appropriate Legal + Notices displayed by works containing it; or + + c) Prohibiting misrepresentation of the origin of that material, or + requiring that modified versions of such material be marked in + reasonable ways as different from the original version; or + + d) Limiting the use for publicity purposes of names of licensors or + authors of the material; or + + e) Declining to grant rights under trademark law for use of some + trade names, trademarks, or service marks; or + + f) Requiring indemnification of licensors and authors of that + material by anyone who conveys the material (or modified versions of + it) with contractual assumptions of liability to the recipient, for + any liability that these contractual assumptions directly impose on + those licensors and authors. + + All other non-permissive additional terms are considered "further +restrictions" within the meaning of section 10. If the Program as you +received it, or any part of it, contains a notice stating that it is +governed by this License along with a term that is a further +restriction, you may remove that term. If a license document contains +a further restriction but permits relicensing or conveying under this +License, you may add to a covered work material governed by the terms +of that license document, provided that the further restriction does +not survive such relicensing or conveying. + + If you add terms to a covered work in accord with this section, you +must place, in the relevant source files, a statement of the +additional terms that apply to those files, or a notice indicating +where to find the applicable terms. + + Additional terms, permissive or non-permissive, may be stated in the +form of a separately written license, or stated as exceptions; +the above requirements apply either way. + + 8. Termination. + + You may not propagate or modify a covered work except as expressly +provided under this License. Any attempt otherwise to propagate or +modify it is void, and will automatically terminate your rights under +this License (including any patent licenses granted under the third +paragraph of section 11). + + However, if you cease all violation of this License, then your +license from a particular copyright holder is reinstated (a) +provisionally, unless and until the copyright holder explicitly and +finally terminates your license, and (b) permanently, if the copyright +holder fails to notify you of the violation by some reasonable means +prior to 60 days after the cessation. + + Moreover, your license from a particular copyright holder is +reinstated permanently if the copyright holder notifies you of the +violation by some reasonable means, this is the first time you have +received notice of violation of this License (for any work) from that +copyright holder, and you cure the violation prior to 30 days after +your receipt of the notice. + + Termination of your rights under this section does not terminate the +licenses of parties who have received copies or rights from you under +this License. If your rights have been terminated and not permanently +reinstated, you do not qualify to receive new licenses for the same +material under section 10. + + 9. Acceptance Not Required for Having Copies. + + You are not required to accept this License in order to receive or +run a copy of the Program. Ancillary propagation of a covered work +occurring solely as a consequence of using peer-to-peer transmission +to receive a copy likewise does not require acceptance. However, +nothing other than this License grants you permission to propagate or +modify any covered work. These actions infringe copyright if you do +not accept this License. Therefore, by modifying or propagating a +covered work, you indicate your acceptance of this License to do so. + + 10. Automatic Licensing of Downstream Recipients. + + Each time you convey a covered work, the recipient automatically +receives a license from the original licensors, to run, modify and +propagate that work, subject to this License. You are not responsible +for enforcing compliance by third parties with this License. + + An "entity transaction" is a transaction transferring control of an +organization, or substantially all assets of one, or subdividing an +organization, or merging organizations. If propagation of a covered +work results from an entity transaction, each party to that +transaction who receives a copy of the work also receives whatever +licenses to the work the party's predecessor in interest had or could +give under the previous paragraph, plus a right to possession of the +Corresponding Source of the work from the predecessor in interest, if +the predecessor has it or can get it with reasonable efforts. + + You may not impose any further restrictions on the exercise of the +rights granted or affirmed under this License. For example, you may +not impose a license fee, royalty, or other charge for exercise of +rights granted under this License, and you may not initiate litigation +(including a cross-claim or counterclaim in a lawsuit) alleging that +any patent claim is infringed by making, using, selling, offering for +sale, or importing the Program or any portion of it. + + 11. Patents. + + A "contributor" is a copyright holder who authorizes use under this +License of the Program or a work on which the Program is based. The +work thus licensed is called the contributor's "contributor version". + + A contributor's "essential patent claims" are all patent claims +owned or controlled by the contributor, whether already acquired or +hereafter acquired, that would be infringed by some manner, permitted +by this License, of making, using, or selling its contributor version, +but do not include claims that would be infringed only as a +consequence of further modification of the contributor version. For +purposes of this definition, "control" includes the right to grant +patent sublicenses in a manner consistent with the requirements of +this License. + + Each contributor grants you a non-exclusive, worldwide, royalty-free +patent license under the contributor's essential patent claims, to +make, use, sell, offer for sale, import and otherwise run, modify and +propagate the contents of its contributor version. + + In the following three paragraphs, a "patent license" is any express +agreement or commitment, however denominated, not to enforce a patent +(such as an express permission to practice a patent or covenant not to +sue for patent infringement). To "grant" such a patent license to a +party means to make such an agreement or commitment not to enforce a +patent against the party. + + If you convey a covered work, knowingly relying on a patent license, +and the Corresponding Source of the work is not available for anyone +to copy, free of charge and under the terms of this License, through a +publicly available network server or other readily accessible means, +then you must either (1) cause the Corresponding Source to be so +available, or (2) arrange to deprive yourself of the benefit of the +patent license for this particular work, or (3) arrange, in a manner +consistent with the requirements of this License, to extend the patent +license to downstream recipients. "Knowingly relying" means you have +actual knowledge that, but for the patent license, your conveying the +covered work in a country, or your recipient's use of the covered work +in a country, would infringe one or more identifiable patents in that +country that you have reason to believe are valid. + + If, pursuant to or in connection with a single transaction or +arrangement, you convey, or propagate by procuring conveyance of, a +covered work, and grant a patent license to some of the parties +receiving the covered work authorizing them to use, propagate, modify +or convey a specific copy of the covered work, then the patent license +you grant is automatically extended to all recipients of the covered +work and works based on it. + + A patent license is "discriminatory" if it does not include within +the scope of its coverage, prohibits the exercise of, or is +conditioned on the non-exercise of one or more of the rights that are +specifically granted under this License. You may not convey a covered +work if you are a party to an arrangement with a third party that is +in the business of distributing software, under which you make payment +to the third party based on the extent of your activity of conveying +the work, and under which the third party grants, to any of the +parties who would receive the covered work from you, a discriminatory +patent license (a) in connection with copies of the covered work +conveyed by you (or copies made from those copies), or (b) primarily +for and in connection with specific products or compilations that +contain the covered work, unless you entered into that arrangement, +or that patent license was granted, prior to 28 March 2007. + + Nothing in this License shall be construed as excluding or limiting +any implied license or other defenses to infringement that may +otherwise be available to you under applicable patent law. + + 12. No Surrender of Others' Freedom. + + If conditions are imposed on you (whether by court order, agreement or +otherwise) that contradict the conditions of this License, they do not +excuse you from the conditions of this License. If you cannot convey a +covered work so as to satisfy simultaneously your obligations under this +License and any other pertinent obligations, then as a consequence you may +not convey it at all. For example, if you agree to terms that obligate you +to collect a royalty for further conveying from those to whom you convey +the Program, the only way you could satisfy both those terms and this +License would be to refrain entirely from conveying the Program. + + 13. Use with the GNU Affero General Public License. + + Notwithstanding any other provision of this License, you have +permission to link or combine any covered work with a work licensed +under version 3 of the GNU Affero General Public License into a single +combined work, and to convey the resulting work. The terms of this +License will continue to apply to the part which is the covered work, +but the special requirements of the GNU Affero General Public License, +section 13, concerning interaction through a network will apply to the +combination as such. + + 14. Revised Versions of this License. + + The Free Software Foundation may publish revised and/or new versions of +the GNU General Public License from time to time. Such new versions will +be similar in spirit to the present version, but may differ in detail to +address new problems or concerns. + + Each version is given a distinguishing version number. If the +Program specifies that a certain numbered version of the GNU General +Public License "or any later version" applies to it, you have the +option of following the terms and conditions either of that numbered +version or of any later version published by the Free Software +Foundation. If the Program does not specify a version number of the +GNU General Public License, you may choose any version ever published +by the Free Software Foundation. + + If the Program specifies that a proxy can decide which future +versions of the GNU General Public License can be used, that proxy's +public statement of acceptance of a version permanently authorizes you +to choose that version for the Program. + + Later license versions may give you additional or different +permissions. However, no additional obligations are imposed on any +author or copyright holder as a result of your choosing to follow a +later version. + + 15. Disclaimer of Warranty. + + THERE IS NO WARRANTY FOR THE PROGRAM, TO THE EXTENT PERMITTED BY +APPLICABLE LAW. EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT +HOLDERS AND/OR OTHER PARTIES PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY +OF ANY KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, +THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +PURPOSE. THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF THE PROGRAM +IS WITH YOU. SHOULD THE PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF +ALL NECESSARY SERVICING, REPAIR OR CORRECTION. + + 16. Limitation of Liability. + + IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING +WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MODIFIES AND/OR CONVEYS +THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, INCLUDING ANY +GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING OUT OF THE +USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED TO LOSS OF +DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD +PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER PROGRAMS), +EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF +SUCH DAMAGES. + + 17. Interpretation of Sections 15 and 16. + + If the disclaimer of warranty and limitation of liability provided +above cannot be given local legal effect according to their terms, +reviewing courts shall apply local law that most closely approximates +an absolute waiver of all civil liability in connection with the +Program, unless a warranty or assumption of liability accompanies a +copy of the Program in return for a fee. + + END OF TERMS AND CONDITIONS + + How to Apply These Terms to Your New Programs + + If you develop a new program, and you want it to be of the greatest +possible use to the public, the best way to achieve this is to make it +free software which everyone can redistribute and change under these terms. + + To do so, attach the following notices to the program. It is safest +to attach them to the start of each source file to most effectively +state the exclusion of warranty; and each file should have at least +the "copyright" line and a pointer to where the full notice is found. + + + Copyright (C) + + This program is free software: you can redistribute it and/or modify + it under the terms of the GNU General Public License as published by + the Free Software Foundation, either version 3 of the License, or + (at your option) any later version. + + This program is distributed in the hope that it will be useful, + but WITHOUT ANY WARRANTY; without even the implied warranty of + MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + GNU General Public License for more details. + + You should have received a copy of the GNU General Public License + along with this program. If not, see . + +Also add information on how to contact you by electronic and paper mail. + + If the program does terminal interaction, make it output a short +notice like this when it starts in an interactive mode: + + Copyright (C) + This program comes with ABSOLUTELY NO WARRANTY; for details type `show w'. + This is free software, and you are welcome to redistribute it + under certain conditions; type `show c' for details. + +The hypothetical commands `show w' and `show c' should show the appropriate +parts of the General Public License. Of course, your program's commands +might be different; for a GUI interface, you would use an "about box". + + You should also get your employer (if you work as a programmer) or school, +if any, to sign a "copyright disclaimer" for the program, if necessary. +For more information on this, and how to apply and follow the GNU GPL, see +. + + The GNU General Public License does not permit incorporating your program +into proprietary programs. If your program is a subroutine library, you +may consider it more useful to permit linking proprietary applications with +the library. If this is what you want to do, use the GNU Lesser General +Public License instead of this License. But first, please read +. diff --git a/tidal-link/README.md b/tidal-link/README.md new file mode 100644 index 000000000..fcebd905d --- /dev/null +++ b/tidal-link/README.md @@ -0,0 +1,6 @@ +# tidal-link + +Ableton Link integration for Tidal + +Requires fixes to GHC on Windows (see https://gitlab.haskell.org/ghc/ghc/-/issues/20918) +which are available from GHC 9.2.4. diff --git a/tidal-link/link/.appveyor.yml b/tidal-link/link/.appveyor.yml new file mode 100644 index 000000000..27214e28d --- /dev/null +++ b/tidal-link/link/.appveyor.yml @@ -0,0 +1,146 @@ +clone_depth: 50 + +branches: + only: + - master + +environment: + matrix: + - APPVEYOR_BUILD_WORKER_IMAGE: macos-mojave + CONFIGURATION: Release + XCODE_VERSION: 9.4.1 + - APPVEYOR_BUILD_WORKER_IMAGE: macos-catalina + CONFIGURATION: Release + XCODE_VERSION: 11.7 + - APPVEYOR_BUILD_WORKER_IMAGE: macos-catalina + CONFIGURATION: Debug + XCODE_VERSION: 12.3 + - APPVEYOR_BUILD_WORKER_IMAGE: macos-monterey + CONFIGURATION: Release + XCODE_VERSION: 12.5.1 + - APPVEYOR_BUILD_WORKER_IMAGE: macos-monterey + CONFIGURATION: Release + XCODE_VERSION: 13.2.1 + - APPVEYOR_BUILD_WORKER_IMAGE: Ubuntu2004 + AUDIO_DRIVER: Jack + CONFIGURATION: Debug + GENERATOR: Ninja + CXX: clang++-11 + - APPVEYOR_BUILD_WORKER_IMAGE: Ubuntu2004 + AUDIO_DRIVER: Alsa + CONFIGURATION: Release + GENERATOR: Ninja + CXX: clang++-10 + - APPVEYOR_BUILD_WORKER_IMAGE: Ubuntu2004 + AUDIO_DRIVER: Jack + CONFIGURATION: Debug + GENERATOR: Ninja + CXX: clang++-9 + - APPVEYOR_BUILD_WORKER_IMAGE: Ubuntu2004 + AUDIO_DRIVER: Alsa + CONFIGURATION: Release + GENERATOR: Ninja + CXX: g++-9 + - APPVEYOR_BUILD_WORKER_IMAGE: Ubuntu2004 + AUDIO_DRIVER: Jack + CONFIGURATION: Debug + GENERATOR: Ninja + CXX: g++-8 + - APPVEYOR_BUILD_WORKER_IMAGE: Ubuntu2004 + AUDIO_DRIVER: Alsa + CONFIGURATION: Release + GENERATOR: Ninja + CXX: g++-7 + - APPVEYOR_BUILD_WORKER_IMAGE: Visual Studio 2015 + AUDIO_DRIVER: Asio + THREAD_DESCRIPTION: OFF + CONFIGURATION: Release + GENERATOR: Visual Studio 14 2015 + - APPVEYOR_BUILD_WORKER_IMAGE: Visual Studio 2015 + AUDIO_DRIVER: Asio + THREAD_DESCRIPTION: OFF + CONFIGURATION: Debug + GENERATOR: Visual Studio 14 2015 Win64 + - APPVEYOR_BUILD_WORKER_IMAGE: Visual Studio 2015 + AUDIO_DRIVER: Asio + THREAD_DESCRIPTION: OFF + CONFIGURATION: Release + GENERATOR: Visual Studio 14 2015 Win64 + - APPVEYOR_BUILD_WORKER_IMAGE: Visual Studio 2015 + AUDIO_DRIVER: Wasapi + THREAD_DESCRIPTION: OFF + CONFIGURATION: Release + GENERATOR: Visual Studio 14 2015 Win64 + - APPVEYOR_BUILD_WORKER_IMAGE: Visual Studio 2017 + AUDIO_DRIVER: Asio + THREAD_DESCRIPTION: OFF + CONFIGURATION: Release + GENERATOR: Visual Studio 15 2017 Win64 + - APPVEYOR_BUILD_WORKER_IMAGE: Visual Studio 2019 + AUDIO_DRIVER: Asio + THREAD_DESCRIPTION: ON + CONFIGURATION: Release + GENERATOR: Visual Studio 16 2019 + - APPVEYOR_BUILD_WORKER_IMAGE: Visual Studio 2022 + AUDIO_DRIVER: Wasapi + THREAD_DESCRIPTION: ON + CONFIGURATION: Debug + GENERATOR: Visual Studio 17 2022 + - APPVEYOR_BUILD_WORKER_IMAGE: Ubuntu2004 + ESP_IDF: true + IDF_RELEASE: v4.3.1 + - APPVEYOR_BUILD_WORKER_IMAGE: Ubuntu2004 + FORMATTING: true + +install: + - git submodule update --init --recursive + +for: + - matrix: + only: + - APPVEYOR_BUILD_WORKER_IMAGE: macos-mojave + - APPVEYOR_BUILD_WORKER_IMAGE: macos-catalina + - APPVEYOR_BUILD_WORKER_IMAGE: macos-monterey + build_script: + - sudo xcode-select -s /Applications/Xcode-$XCODE_VERSION.app + - python3 ci/configure.py --generator Xcode + - python3 ci/build.py --configuration $CONFIGURATION + test_script: + - python3 ci/run-tests.py --target LinkCoreTest + - python3 ci/run-tests.py --target LinkDiscoveryTest + - matrix: + only: + # Ubuntu2004 but not ESP_IDF or FORMATTING + - GENERATOR: Ninja + install: + - git submodule update --init --recursive + - sudo apt-get update + - sudo apt-get install -y libjack-dev portaudio19-dev valgrind + build_script: + - python3 ci/configure.py --audio-driver $AUDIO_DRIVER --generator "$GENERATOR" --configuration $CONFIGURATION + - python3 ci/build.py + test_script: + - python3 ci/run-tests.py --target LinkCoreTest --valgrind + - python3 ci/run-tests.py --target LinkDiscoveryTest --valgrind + - matrix: + only: + - APPVEYOR_BUILD_WORKER_IMAGE: Visual Studio 2015 + - APPVEYOR_BUILD_WORKER_IMAGE: Visual Studio 2017 + - APPVEYOR_BUILD_WORKER_IMAGE: Visual Studio 2019 + - APPVEYOR_BUILD_WORKER_IMAGE: Visual Studio 2022 + build_script: + - py -3 ci/configure.py --audio-driver %AUDIO_DRIVER% --thread-description %THREAD_DESCRIPTION% --generator "%GENERATOR%" --flags="-DCMAKE_SYSTEM_VERSION=10.0.18362.0" + - py -3 ci/build.py --configuration %CONFIGURATION% + test_script: + - py -3 ci/run-tests.py --target LinkCoreTest + - py -3 ci/run-tests.py --target LinkDiscoveryTest + - matrix: + only: + - ESP_IDF: true + build_script: + - docker run --rm -v $APPVEYOR_BUILD_FOLDER:/link -w /link/examples/esp32 -e LC_ALL=C.UTF-8 espressif/idf:$IDF_RELEASE idf.py build + - matrix: + only: + - FORMATTING: true + build_script: + - docker run -v $APPVEYOR_BUILD_FOLDER:/link dalg24/clang-format:18.04.0 python /link/ci/check-formatting.py -c /usr/bin/clang-format-6.0 diff --git a/tidal-link/link/.clang-format b/tidal-link/link/.clang-format new file mode 100644 index 000000000..ac03c4e31 --- /dev/null +++ b/tidal-link/link/.clang-format @@ -0,0 +1,50 @@ +Language: Cpp + +AccessModifierOffset: -2 +AlignAfterOpenBracket: DontAlign +AlignEscapedNewlinesLeft: false +AlignOperands: true +AlignTrailingComments: true +AllowAllParametersOfDeclarationOnNextLine: true +AllowShortBlocksOnASingleLine: false +AllowShortCaseLabelsOnASingleLine: false +AllowShortFunctionsOnASingleLine: None +AllowShortIfStatementsOnASingleLine: false +AllowShortLoopsOnASingleLine: false +AlwaysBreakAfterDefinitionReturnType: None +AlwaysBreakAfterReturnType: None +AlwaysBreakBeforeMultilineStrings: true +AlwaysBreakTemplateDeclarations: true +BinPackArguments: true +BinPackParameters: false +BreakBeforeBinaryOperators: NonAssignment +BreakBeforeBraces: Allman +BreakBeforeTernaryOperators: true +BreakConstructorInitializersBeforeComma: true +ColumnLimit: 90 +ConstructorInitializerAllOnOneLineOrOnePerLine: false +ConstructorInitializerIndentWidth: 2 +ContinuationIndentWidth: 2 +Cpp11BracedListStyle: true +DerivePointerAlignment: false +IndentCaseLabels: false +IndentFunctionDeclarationAfterType: false +IndentWidth: 2 +IndentWrappedFunctionNames: false +KeepEmptyLinesAtTheStartOfBlocks: true +MaxEmptyLinesToKeep: 2 +NamespaceIndentation: None +PenaltyBreakBeforeFirstCallParameter: 0 +PenaltyReturnTypeOnItsOwnLine: 1000 +PointerAlignment: Left +SpaceAfterCStyleCast: false +SpaceBeforeAssignmentOperators: true +SpaceBeforeParens: ControlStatements +SpaceInEmptyParentheses: false +SpacesBeforeTrailingComments: 1 +SpacesInAngles: false +SpacesInCStyleCastParentheses: false +SpacesInParentheses: false +SpacesInSquareBrackets: false +Standard: Cpp11 +UseTab: Never diff --git a/tidal-link/link/.gitignore b/tidal-link/link/.gitignore new file mode 100644 index 000000000..bcdff6af1 --- /dev/null +++ b/tidal-link/link/.gitignore @@ -0,0 +1,33 @@ +# IDE generated files and build outputs +/build/ +/ide/ +/output/ +/logs/ +.idea/* + +# System temporary files +.DS_Store +*~ +*.swp + +# Compiled Object files +*.slo +*.lo +*.o +*.obj + +# Compiled Dynamic libraries +*.so +*.dylib +*.dll + +# Compiled Static libraries +*.lai +*.la +*.a +*.lib + +# Executables +*.exe +*.out +*.app diff --git a/tidal-link/link/AbletonLinkConfig.cmake b/tidal-link/link/AbletonLinkConfig.cmake new file mode 100644 index 000000000..43b66e7d3 --- /dev/null +++ b/tidal-link/link/AbletonLinkConfig.cmake @@ -0,0 +1,50 @@ +if(CMAKE_VERSION VERSION_LESS 3.0) + message(FATAL_ERROR "CMake 3.0 or greater is required") +endif() + +add_library(Ableton::Link IMPORTED INTERFACE) +set_property(TARGET Ableton::Link APPEND PROPERTY + INTERFACE_INCLUDE_DIRECTORIES + ${CMAKE_CURRENT_LIST_DIR}/include +) + +# Force C++11 support for consuming targets +set_property(TARGET Ableton::Link APPEND PROPERTY + INTERFACE_COMPILE_FEATURES + cxx_generalized_initializers +) + +if(UNIX) + set_property(TARGET Ableton::Link APPEND PROPERTY + INTERFACE_COMPILE_DEFINITIONS + LINK_PLATFORM_UNIX=1 + ) +endif() + +if(APPLE) + set_property(TARGET Ableton::Link APPEND PROPERTY + INTERFACE_COMPILE_DEFINITIONS + LINK_PLATFORM_MACOSX=1 + ) +elseif(WIN32) + set_property(TARGET Ableton::Link APPEND PROPERTY + INTERFACE_COMPILE_DEFINITIONS + LINK_PLATFORM_WINDOWS=1 + ) +elseif(CMAKE_SYSTEM_NAME MATCHES "Linux|kFreeBSD|GNU") + set_property(TARGET Ableton::Link APPEND PROPERTY + INTERFACE_COMPILE_DEFINITIONS + LINK_PLATFORM_LINUX=1 + ) +endif() + +include(${CMAKE_CURRENT_LIST_DIR}/cmake_include/AsioStandaloneConfig.cmake) +set_property(TARGET Ableton::Link APPEND PROPERTY + INTERFACE_LINK_LIBRARIES + AsioStandalone::AsioStandalone +) + +set_property(TARGET Ableton::Link APPEND PROPERTY + INTERFACE_SOURCES + ${CMAKE_CURRENT_LIST_DIR}/include/ableton/Link.hpp +) diff --git a/tidal-link/link/CMakeLists.txt b/tidal-link/link/CMakeLists.txt new file mode 100644 index 000000000..5924722da --- /dev/null +++ b/tidal-link/link/CMakeLists.txt @@ -0,0 +1,65 @@ +cmake_minimum_required(VERSION 3.0) +project(Link) + +set(CMAKE_RUNTIME_OUTPUT_DIRECTORY ${CMAKE_BINARY_DIR}/bin) + +# ___ _ _ +# / _ \ _ __ | |_(_) ___ _ __ ___ +# | | | | '_ \| __| |/ _ \| '_ \/ __| +# | |_| | |_) | |_| | (_) | | | \__ \ +# \___/| .__/ \__|_|\___/|_| |_|___/ +# |_| + +# Note: Please use the LINK_* prefix for all project-specific options + +if(UNIX) + option(LINK_ENABLE_ASAN "Build with Address Sanitizier (ASan)" OFF) + option(LINK_BUILD_JACK "Build example applications with JACK support" OFF) +endif() + +if(WIN32) + option(LINK_BUILD_ASIO "Build example applications with ASIO driver" ON) + option(LINK_BUILD_VLD "Build with VLD support (VLD must be installed separately)" OFF) +endif() + +# ____ _ _ +# | _ \ __ _| |_| |__ ___ +# | |_) / _` | __| '_ \/ __| +# | __/ (_| | |_| | | \__ \ +# |_| \__,_|\__|_| |_|___/ +# + +# Other CMake files must be included only after declaring build options +include(cmake_include/ConfigureCompileFlags.cmake) +include(cmake_include/CatchConfig.cmake) +include(AbletonLinkConfig.cmake) +include(extensions/abl_link/abl_link.cmake) + +add_subdirectory(include) +add_subdirectory(src) +add_subdirectory(examples) +add_subdirectory(extensions/abl_link) + +# ____ +# / ___| _ _ _ __ ___ _ __ ___ __ _ _ __ _ _ +# \___ \| | | | '_ ` _ \| '_ ` _ \ / _` | '__| | | | +# ___) | |_| | | | | | | | | | | | (_| | | | |_| | +# |____/ \__,_|_| |_| |_|_| |_| |_|\__,_|_| \__, | +# |___/ + +message(STATUS "Build options") + +get_cmake_property(all_variables VARIABLES) +string(REGEX MATCHALL "(^|;)LINK_[A-Z_]+" link_variables "${all_variables}") +foreach(variable ${link_variables}) + message(" ${variable}: ${${variable}}") +endforeach() + +message(STATUS "Build configuration") + +if(CMAKE_BUILD_TYPE) + message(" Build type: ${CMAKE_BUILD_TYPE}") +else() + message(" Build type: Set by IDE") +endif() + diff --git a/tidal-link/link/CONTRIBUTING.md b/tidal-link/link/CONTRIBUTING.md new file mode 100644 index 000000000..c4a0fd5e1 --- /dev/null +++ b/tidal-link/link/CONTRIBUTING.md @@ -0,0 +1,63 @@ +Bug Reports +=========== + +If you've found a bug in Link itself, then please file a new issue here at GitHub. If you +have found a bug in a Link-enabled app, it might be wiser to reach out to the developer of +the app before filing an issue here. + +Any and all information that you can provide regarding the bug will help in our being able +to find it. Specifically, that could include: + + - Stacktraces, in the event of a crash + - Versions of the software used, and the underlying operating system + - Steps to reproduce + - Screenshots, in the case of a bug which results in a visual error + + +Pull Requests +============= + +We are happy to accept pull requests from the GitHub community, assuming that they meet +the following criteria: + + - You have signed and returned Ableton's [CLA][cla] + - The [tests pass](#testing) + - The PR passes all CI service checks + - The code is [well-formatted](#code-formatting) + - The git commit messages comply to [the commonly accepted standards][git-commit-msgs] + +Testing +------- + +Link ships with unit tests that are run on [Travis CI][travis] and [AppVeyor][appveyor] for +all PRs. There are two test suites: `LinkCoreTest`, which tests the core Link +functionality, and `LinkDiscoverTest`, which tests the network discovery feature of Link. +A third virtual target, `LinkAllTest` is provided by the CMake project as a convenience +to run all tests at once. + +The unit tests are run on every platform which Link is officially supported on, and also +are run through [Valgrind][valgrind] on Linux to check for memory corruption and leaks. If +valgrind detects any memory errors when running the tests, it will fail the build. + +If you are submitting a PR which fixes a bug or introduces new functionality, please add a +test which helps to verify the correctness of the code in the PR. + +Code Formatting +--------------- + +Link uses [clang-format][clang-format] to enforce our preferred code style. At the moment, +we use **clang-format version 6.0**. Note that other versions may format code differently. + +Any PRs submitted to Link are also checked with clang-format by the Travis CI service. If +you get a build failure, then you can format your code by running the following command: + +``` +clang-format -style=file -i (filename) +``` + +[cla]: http://ableton.github.io/cla/ +[git-commit-msgs]: http://tbaggery.com/2008/04/19/a-note-about-git-commit-messages.html +[clang-format]: http://llvm.org/builds +[valgrind]: http://valgrind.org +[travis]: http://travis-ci.com +[appveyor]: http://appveyor.com diff --git a/tidal-link/link/GNU-GPL-v2.0.md b/tidal-link/link/GNU-GPL-v2.0.md new file mode 100644 index 000000000..0daa04150 --- /dev/null +++ b/tidal-link/link/GNU-GPL-v2.0.md @@ -0,0 +1,336 @@ +GNU General Public License +========================== + +_Version 2, June 1991_ +_Copyright © 1989, 1991 Free Software Foundation, Inc.,_ +_51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA_ + +Everyone is permitted to copy and distribute verbatim copies +of this license document, but changing it is not allowed. + +### Preamble + +The licenses for most software are designed to take away your +freedom to share and change it. By contrast, the GNU General Public +License is intended to guarantee your freedom to share and change free +software--to make sure the software is free for all its users. This +General Public License applies to most of the Free Software +Foundation's software and to any other program whose authors commit to +using it. (Some other Free Software Foundation software is covered by +the GNU Lesser General Public License instead.) You can apply it to +your programs, too. + +When we speak of free software, we are referring to freedom, not +price. Our General Public Licenses are designed to make sure that you +have the freedom to distribute copies of free software (and charge for +this service if you wish), that you receive source code or can get it +if you want it, that you can change the software or use pieces of it +in new free programs; and that you know you can do these things. + +To protect your rights, we need to make restrictions that forbid +anyone to deny you these rights or to ask you to surrender the rights. +These restrictions translate to certain responsibilities for you if you +distribute copies of the software, or if you modify it. + +For example, if you distribute copies of such a program, whether +gratis or for a fee, you must give the recipients all the rights that +you have. You must make sure that they, too, receive or can get the +source code. And you must show them these terms so they know their +rights. + +We protect your rights with two steps: **(1)** copyright the software, and +**(2)** offer you this license which gives you legal permission to copy, +distribute and/or modify the software. + +Also, for each author's protection and ours, we want to make certain +that everyone understands that there is no warranty for this free +software. If the software is modified by someone else and passed on, we +want its recipients to know that what they have is not the original, so +that any problems introduced by others will not reflect on the original +authors' reputations. + +Finally, any free program is threatened constantly by software +patents. We wish to avoid the danger that redistributors of a free +program will individually obtain patent licenses, in effect making the +program proprietary. To prevent this, we have made it clear that any +patent must be licensed for everyone's free use or not licensed at all. + +The precise terms and conditions for copying, distribution and +modification follow. + +### TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION + +**0.** This License applies to any program or other work which contains +a notice placed by the copyright holder saying it may be distributed +under the terms of this General Public License. The “Program”, below, +refers to any such program or work, and a “work based on the Program” +means either the Program or any derivative work under copyright law: +that is to say, a work containing the Program or a portion of it, +either verbatim or with modifications and/or translated into another +language. (Hereinafter, translation is included without limitation in +the term “modification”.) Each licensee is addressed as “you”. + +Activities other than copying, distribution and modification are not +covered by this License; they are outside its scope. The act of +running the Program is not restricted, and the output from the Program +is covered only if its contents constitute a work based on the +Program (independent of having been made by running the Program). +Whether that is true depends on what the Program does. + +**1.** You may copy and distribute verbatim copies of the Program's +source code as you receive it, in any medium, provided that you +conspicuously and appropriately publish on each copy an appropriate +copyright notice and disclaimer of warranty; keep intact all the +notices that refer to this License and to the absence of any warranty; +and give any other recipients of the Program a copy of this License +along with the Program. + +You may charge a fee for the physical act of transferring a copy, and +you may at your option offer warranty protection in exchange for a fee. + +**2.** You may modify your copy or copies of the Program or any portion +of it, thus forming a work based on the Program, and copy and +distribute such modifications or work under the terms of Section 1 +above, provided that you also meet all of these conditions: + +* **a)** You must cause the modified files to carry prominent notices +stating that you changed the files and the date of any change. +* **b)** You must cause any work that you distribute or publish, that in +whole or in part contains or is derived from the Program or any +part thereof, to be licensed as a whole at no charge to all third +parties under the terms of this License. +* **c)** If the modified program normally reads commands interactively +when run, you must cause it, when started running for such +interactive use in the most ordinary way, to print or display an +announcement including an appropriate copyright notice and a +notice that there is no warranty (or else, saying that you provide +a warranty) and that users may redistribute the program under +these conditions, and telling the user how to view a copy of this +License. (Exception: if the Program itself is interactive but +does not normally print such an announcement, your work based on +the Program is not required to print an announcement.) + +These requirements apply to the modified work as a whole. If +identifiable sections of that work are not derived from the Program, +and can be reasonably considered independent and separate works in +themselves, then this License, and its terms, do not apply to those +sections when you distribute them as separate works. But when you +distribute the same sections as part of a whole which is a work based +on the Program, the distribution of the whole must be on the terms of +this License, whose permissions for other licensees extend to the +entire whole, and thus to each and every part regardless of who wrote it. + +Thus, it is not the intent of this section to claim rights or contest +your rights to work written entirely by you; rather, the intent is to +exercise the right to control the distribution of derivative or +collective works based on the Program. + +In addition, mere aggregation of another work not based on the Program +with the Program (or with a work based on the Program) on a volume of +a storage or distribution medium does not bring the other work under +the scope of this License. + +**3.** You may copy and distribute the Program (or a work based on it, +under Section 2) in object code or executable form under the terms of +Sections 1 and 2 above provided that you also do one of the following: + +* **a)** Accompany it with the complete corresponding machine-readable +source code, which must be distributed under the terms of Sections +1 and 2 above on a medium customarily used for software interchange; or, +* **b)** Accompany it with a written offer, valid for at least three +years, to give any third party, for a charge no more than your +cost of physically performing source distribution, a complete +machine-readable copy of the corresponding source code, to be +distributed under the terms of Sections 1 and 2 above on a medium +customarily used for software interchange; or, +* **c)** Accompany it with the information you received as to the offer +to distribute corresponding source code. (This alternative is +allowed only for noncommercial distribution and only if you +received the program in object code or executable form with such +an offer, in accord with Subsection b above.) + +The source code for a work means the preferred form of the work for +making modifications to it. For an executable work, complete source +code means all the source code for all modules it contains, plus any +associated interface definition files, plus the scripts used to +control compilation and installation of the executable. However, as a +special exception, the source code distributed need not include +anything that is normally distributed (in either source or binary +form) with the major components (compiler, kernel, and so on) of the +operating system on which the executable runs, unless that component +itself accompanies the executable. + +If distribution of executable or object code is made by offering +access to copy from a designated place, then offering equivalent +access to copy the source code from the same place counts as +distribution of the source code, even though third parties are not +compelled to copy the source along with the object code. + +**4.** You may not copy, modify, sublicense, or distribute the Program +except as expressly provided under this License. Any attempt +otherwise to copy, modify, sublicense or distribute the Program is +void, and will automatically terminate your rights under this License. +However, parties who have received copies, or rights, from you under +this License will not have their licenses terminated so long as such +parties remain in full compliance. + +**5.** You are not required to accept this License, since you have not +signed it. However, nothing else grants you permission to modify or +distribute the Program or its derivative works. These actions are +prohibited by law if you do not accept this License. Therefore, by +modifying or distributing the Program (or any work based on the +Program), you indicate your acceptance of this License to do so, and +all its terms and conditions for copying, distributing or modifying +the Program or works based on it. + +**6.** Each time you redistribute the Program (or any work based on the +Program), the recipient automatically receives a license from the +original licensor to copy, distribute or modify the Program subject to +these terms and conditions. You may not impose any further +restrictions on the recipients' exercise of the rights granted herein. +You are not responsible for enforcing compliance by third parties to +this License. + +**7.** If, as a consequence of a court judgment or allegation of patent +infringement or for any other reason (not limited to patent issues), +conditions are imposed on you (whether by court order, agreement or +otherwise) that contradict the conditions of this License, they do not +excuse you from the conditions of this License. If you cannot +distribute so as to satisfy simultaneously your obligations under this +License and any other pertinent obligations, then as a consequence you +may not distribute the Program at all. For example, if a patent +license would not permit royalty-free redistribution of the Program by +all those who receive copies directly or indirectly through you, then +the only way you could satisfy both it and this License would be to +refrain entirely from distribution of the Program. + +If any portion of this section is held invalid or unenforceable under +any particular circumstance, the balance of the section is intended to +apply and the section as a whole is intended to apply in other +circumstances. + +It is not the purpose of this section to induce you to infringe any +patents or other property right claims or to contest validity of any +such claims; this section has the sole purpose of protecting the +integrity of the free software distribution system, which is +implemented by public license practices. Many people have made +generous contributions to the wide range of software distributed +through that system in reliance on consistent application of that +system; it is up to the author/donor to decide if he or she is willing +to distribute software through any other system and a licensee cannot +impose that choice. + +This section is intended to make thoroughly clear what is believed to +be a consequence of the rest of this License. + +**8.** If the distribution and/or use of the Program is restricted in +certain countries either by patents or by copyrighted interfaces, the +original copyright holder who places the Program under this License +may add an explicit geographical distribution limitation excluding +those countries, so that distribution is permitted only in or among +countries not thus excluded. In such case, this License incorporates +the limitation as if written in the body of this License. + +**9.** The Free Software Foundation may publish revised and/or new versions +of the General Public License from time to time. Such new versions will +be similar in spirit to the present version, but may differ in detail to +address new problems or concerns. + +Each version is given a distinguishing version number. If the Program +specifies a version number of this License which applies to it and “any +later version”, you have the option of following the terms and conditions +either of that version or of any later version published by the Free +Software Foundation. If the Program does not specify a version number of +this License, you may choose any version ever published by the Free Software +Foundation. + +**10.** If you wish to incorporate parts of the Program into other free +programs whose distribution conditions are different, write to the author +to ask for permission. For software which is copyrighted by the Free +Software Foundation, write to the Free Software Foundation; we sometimes +make exceptions for this. Our decision will be guided by the two goals +of preserving the free status of all derivatives of our free software and +of promoting the sharing and reuse of software generally. + +### NO WARRANTY + +**11.** BECAUSE THE PROGRAM IS LICENSED FREE OF CHARGE, THERE IS NO WARRANTY +FOR THE PROGRAM, TO THE EXTENT PERMITTED BY APPLICABLE LAW. EXCEPT WHEN +OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES +PROVIDE THE PROGRAM “AS IS” WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED +OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF +MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE RISK AS +TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU. SHOULD THE +PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING, +REPAIR OR CORRECTION. + +**12.** IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING +WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR +REDISTRIBUTE THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, +INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING +OUT OF THE USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED +TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY +YOU OR THIRD PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER +PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE +POSSIBILITY OF SUCH DAMAGES. + +END OF TERMS AND CONDITIONS + +### How to Apply These Terms to Your New Programs + +If you develop a new program, and you want it to be of the greatest +possible use to the public, the best way to achieve this is to make it +free software which everyone can redistribute and change under these terms. + +To do so, attach the following notices to the program. It is safest +to attach them to the start of each source file to most effectively +convey the exclusion of warranty; and each file should have at least +the “copyright” line and a pointer to where the full notice is found. + + + Copyright (C) + + This program is free software; you can redistribute it and/or modify + it under the terms of the GNU General Public License as published by + the Free Software Foundation; either version 2 of the License, or + (at your option) any later version. + + This program is distributed in the hope that it will be useful, + but WITHOUT ANY WARRANTY; without even the implied warranty of + MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + GNU General Public License for more details. + + You should have received a copy of the GNU General Public License along + with this program; if not, write to the Free Software Foundation, Inc., + 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA. + +Also add information on how to contact you by electronic and paper mail. + +If the program is interactive, make it output a short notice like this +when it starts in an interactive mode: + + Gnomovision version 69, Copyright (C) year name of author + Gnomovision comes with ABSOLUTELY NO WARRANTY; for details type `show w'. + This is free software, and you are welcome to redistribute it + under certain conditions; type `show c' for details. + +The hypothetical commands `show w` and `show c` should show the appropriate +parts of the General Public License. Of course, the commands you use may +be called something other than `show w` and `show c`; they could even be +mouse-clicks or menu items--whatever suits your program. + +You should also get your employer (if you work as a programmer) or your +school, if any, to sign a “copyright disclaimer” for the program, if +necessary. Here is a sample; alter the names: + + Yoyodyne, Inc., hereby disclaims all copyright interest in the program + `Gnomovision' (which makes passes at compilers) written by James Hacker. + + , 1 April 1989 + Ty Coon, President of Vice + +This General Public License does not permit incorporating your program into +proprietary programs. If your program is a subroutine library, you may +consider it more useful to permit linking proprietary applications with the +library. If this is what you want to do, use the GNU Lesser General +Public License instead of this License. diff --git a/tidal-link/link/LICENSE.md b/tidal-link/link/LICENSE.md new file mode 100644 index 000000000..75fc05464 --- /dev/null +++ b/tidal-link/link/LICENSE.md @@ -0,0 +1,19 @@ +# License + +Copyright 2016, Ableton AG, Berlin. All rights reserved. + +This program is free software: you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation, either version 2 of the License, or +(at your option) any later version. + +This program is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with this program. If not, see . + +If you would like to incorporate Link into a proprietary software application, +please contact . diff --git a/tidal-link/link/README.md b/tidal-link/link/README.md new file mode 100644 index 000000000..ee2c6b1d9 --- /dev/null +++ b/tidal-link/link/README.md @@ -0,0 +1,156 @@ +# Ableton Link + +This is the codebase for Ableton Link, a technology that synchronizes musical beat, tempo, +and phase across multiple applications running on one or more devices. Applications on +devices connected to a local network discover each other automatically and form a musical +session in which each participant can perform independently: anyone can start or stop +while still staying in time. Anyone can change the tempo, the others will follow. Anyone +can join or leave without disrupting the session. + +# License + +Ableton Link is dual [licensed][license] under GPLv2+ and a proprietary license. If you +would like to incorporate Link into a proprietary software application, please contact +. + +# Building and Running Link Examples + +Link relies on `asio-standalone` as a submodule. After checking out the +main repositories, those submodules have to be loaded using + +``` +git submodule update --init --recursive +``` + +Link uses [CMake][cmake] to generate build files for the [Catch][catch]-based +unit-tests and the example applications. + +``` +$ mkdir build +$ cd build +$ cmake .. +$ cmake --build . +``` + +The output binaries for the example applications and the unit-tests will be placed in a +`bin` subdirectory of the CMake binary directory. + +# Integrating Link in your Application + +## Test Plan + +To make sure users have the best possible experience using Link it is important all apps +supporting Link behave consistently. This includes for example playing in sync with other +apps as well as not hijacking a jams tempo when joining. To make sure your app behaves as +intended make sure it complies to the [Test Plan](TEST-PLAN.md). + +## Building Link + +Link is a header-only library, so it should be straightforward to integrate into your +application. + +### CMake-based Projects + +If you are using CMake, then you can simply add the following to your CMakeLists.txt file: + +```cmake +include($PATH_TO_LINK/AbletonLinkConfig.cmake) +target_link_libraries($YOUR_TARGET Ableton::Link) + +``` + +You can optionally have your build target depend on `${link_HEADERS}`, which will make +the Link headers visible in your IDE. This variable exported to the `PARENT_SCOPE` by +Link's CMakeLists.txt. + +### Other Build Systems + +To include the Link library in your non CMake project, you must do the following: + + - Add the `link/include` and `modules/asio-standalone/asio/include` directories to your + list of include paths + - Define `LINK_PLATFORM_MACOSX=1`, `LINK_PLATFORM_LINUX=1`, or `LINK_PLATFORM_WINDOWS=1`, + depending on which platform you are building on. + +If you get any compiler errors/warnings, have a look at +[compile-flags.cmake](cmake_include/ConfigureCompileFlags.cmake), which might provide some +insight as to the compiler flags needed to build Link. + +### Build Requirements + +| Platform | Minimum Required | Optional (only required for examples) | +|----------|----------------------|---------------------------------------| +| Windows | MSVC 2015 | Steinberg ASIO SDK 2.3 | +| Mac | Xcode 9.4.1 | | +| Linux | Clang 3.6 or GCC 5.2 | libportaudio19-dev | + + +Other compilers with good C++11 support should work, but are not verified. + +iOS developers should not use this repo. See http://ableton.github.io/linkkit for +information on the LinkKit SDK for iOS. + +# Documentation + +An overview of Link concepts can be found at http://ableton.github.io/link. Those that +are new to Link should start there. The [Link.hpp](include/ableton/Link.hpp) header +contains the full Link public interface. See the LinkHut projects in this repo for an +example usage of the `Link` type. + +## Time and Clocks + +Link works by calculating a relationship between the system clocks of devices in a session. +Since the mechanism for obtaining a system time value and the unit of these values differ +across platforms, Link defines a `Clock` abstraction with platform-specific +implementations. Please see: +- `Link::clock()` method in [Link.hpp](include/ableton/Link.hpp) +- OSX and iOS clock implementation in +[platforms/darwin/Clock.hpp](include/ableton/platforms/darwin/Clock.hpp) +- Windows clock implementation in +[platforms/windows/Clock.hpp](include/ableton/platforms/windows/Clock.hpp) +- C++ standard library `std::chrono::high_resolution_clock`-based implementation in +[platforms/stl/Clock.hpp](include/ableton/platforms/stl/Clock.hpp) + +Using the system time correctly in the context of an audio callback gets a little +complicated. Audio devices generally have a sample clock that is independent of the system +Clock. Link maintains a mapping between system time and beat time and therefore can't use +the sample time provided by the audio system directly. + +On OSX and iOS, the CoreAudio render callback is passed an `AudioTimeStamp` structure with +a `mHostTime` member that represents the system time at which the audio buffer will be +passed to the audio hardware. This is precisely the information needed to derive the beat +time values corresponding to samples in the buffer using Link. Unfortunately, not all +platforms provide this data to the audio callback. + +When a system timestamp is not provided with the audio buffer, the best a client can do in +the audio callback is to get the current system time and filter it based on the provided +sample time. Filtering is necessary because the audio callback will not be invoked at a +perfectly regular interval and therefore the queried system time will exhibit jitter +relative to the sample clock. The Link library provides a +[HostTimeFilter](include/ableton/link/HostTimeFilter.hpp) utility class that performs a +linear regression between system time and sample time in order to improve the accuracy of +system time values used in an audio callback. See the audio callback implementations for +the various [platforms](examples/linkaudio) used in the examples to see how this is used +in practice. Note that for Windows-based systems, we recommend using the [ASIO][asio] +audio driver. + +## Latency Compensation + +As discussed in the previous section, the system time that a client is provided in an +audio callback either represents the time at which the buffer will be submitted to the +audio hardware (for OSX/iOS) or the time at which the callback was invoked (when the +code in the callback queries the system time). Note that neither of these is what we +actually want to synchronize between devices in order to play in time. + +In order for multiple devices to play in time, we need to synchronize the moment at which +their signals hit the speaker or output cable. If this compensation is not performed, +the output signals from devices with different output latencies will exhibit a persistent +offset from each other. For this reason, the audio system's output latency should be added +to system time values before passing them to Link methods. Examples of this latency +compensation can be found in the [platform](examples/linkaudio) implementations of the +example apps. + +[asio]: https://www.steinberg.net/en/company/developers.html +[catch]: https://github.com/philsquared/Catch +[cmake]: https://www.cmake.org +[license]: LICENSE.md diff --git a/tidal-link/link/TEST-PLAN.md b/tidal-link/link/TEST-PLAN.md new file mode 100644 index 000000000..5a6de3782 --- /dev/null +++ b/tidal-link/link/TEST-PLAN.md @@ -0,0 +1,99 @@ +# Test Plan + +Below are a set of user interactions that are expected to work consistently across all +Link-enabled apps. In order to provide the best user experience, it's important that apps +behave consistently with respect to these test cases. + +## Tempo Changes + +### TEMPO-1: Tempo changes should be transmitted between connected apps. + +- Open LinkHut, press **Play** and **enable** Link. +- Open App and **enable** Link. +- Without starting to play, change tempo in App **⇒** LinkHut clicks should speed up or slow down to match the tempo specified in +the App. +- Start playing in the App **⇒** App and LinkHut should be in sync +- Change tempo in App and in LinkHut **⇒** App and LinkHut should remain in sync + +### TEMPO-2: Opening an app with Link enabled should not change the tempo of an existing Link session. + +- Open App and **enable** Link. +- Set App tempo to 100bpm. +- Terminate App. +- Open LinkHut, press **Play** and **enable** Link. +- Set LinkHut tempo to 130bpm. +- Open App and **enable** Link. **⇒** Link should be connected (“1 Link”) and the App and +LinkHut’s tempo should both be 130bpm. + +### TEMPO-3: When connected, loading a new document should not change the Link session tempo. + +- Open LinkHut, press **Play** and **enable** Link. +- Set LinkHut tempo to 130bpm. +- Open App and **enable** Link **⇒** LinkHut’s tempo should not change. +- Load new Song/Set/Session with a tempo other than 130bpm **⇒** App and LinkHut tempo should both be 130bpm. + +### TEMPO-4: Tempo range handling. + +- Open LinkHut, press **Play**, enable Link. +- Open App, start Audio, and **enable** Link. +- Change tempo in LinkHut to **20bpm** **⇒** App and LinkHut should stay in sync. +- Change Tempo in LinkHut to **999bpm** **⇒** App and LinkHut should stay in sync. +- If App does not support the full range of tempos supported by Link, it should stay in sync by switching to a multiple of the Link session tempo. + +### TEMPO-5: Enabling Link does not change app's tempo if there is no Link session to join. +- Open App, start playing. +- Change App tempo to something other than the default. +- **Enable** Link **⇒** App's tempo should not change. +- Change App tempo to a new value (not the default). +- **Disable** Link **⇒** App's tempo should not change. + +## Beat Time + +These cases verify the continuity of beat time across Link operations. + +### BEATTIME-1: Enabling Link does not change app's beat time if there is no Link session to join. +- Open App, start playing. +- **Enable** Link **⇒** No beat time jump or audible discontinuity should occur. +- **Disable** Link **⇒** No beat time jump or audible discontinuity should occur. + +### BEATTIME-2: App's beat time does not change if another participant joins its session. +- Open App and **enable** Link. +- Start playing. +- Open LinkHut and **enable** Link **⇒** No beat time jump or audible discontinuity should occur in the App. + +**Note**: When joining an existing Link session, an app should adjust to the existing +session's tempo and phase, which will usually result in a beat time jump. Apps that are +already in a session should never have any kind of beat time or audio discontinuity when +a new participant joins the session. + +## Start Stop States + +### STARTSTOPSTATE-1: Listening to start/stop commands from other peers. +- Open App, set Link and Start Stop Sync to **Enabled**. +- Open LinkHut, **enable** Link and Start Stop Sync and press **Play** **⇒** App should start playing according to its quantization. +- Stop playback in LinkHut **⇒** App should stop playing. + +### STARTSTOPSTATE-2: Sending start/stop commands to other peers. +- Open LinkHut, **enable** Link and Start Stop Sync and press **Play**. +- Open App, set Link and Start Stop Sync to **Enabled** **⇒** App should not be +playing while LinkHut continues playing. +- Start playback in App **⇒** App should join playing according to its quantization. +- Stop playback in App **⇒** App and LinkHut should stop playing. +- Start playback in App **⇒** App and LinkHut should start playing according to +their quantizations. + +## Audio Engine + +These cases verify the correct implementation of latency compensation within an app's +audio engine. + +### AUDIOENGINE-1: Correct alignment of app audio with shared session + +- Connect the audio out of your computer to the audio in. Alternatively use +[SoundFlower](https://github.com/mattingalls/Soundflower) to be able to record the output +of your app and LinkHut. +- Open LinkHut, **enable** Link and press **Play**. +- Open App and **enable** Link. +- Start playing audio (preferably a short, click-like sample) with notes on the same beats as LinkHut. +- Record audio within application of choice. +- Validate whether onset of the sample aligns with the pulse generated by LinkHut (tolerance: less than 3 ms). diff --git a/tidal-link/link/assets/Ableton_Link_Badge-Black.eps b/tidal-link/link/assets/Ableton_Link_Badge-Black.eps new file mode 100644 index 000000000..082662fc9 Binary files /dev/null and b/tidal-link/link/assets/Ableton_Link_Badge-Black.eps differ diff --git a/tidal-link/link/assets/Ableton_Link_Badge-White.eps b/tidal-link/link/assets/Ableton_Link_Badge-White.eps new file mode 100644 index 000000000..1bc5e7ad3 Binary files /dev/null and b/tidal-link/link/assets/Ableton_Link_Badge-White.eps differ diff --git a/tidal-link/link/assets/Ableton_Link_Button_disabled.eps b/tidal-link/link/assets/Ableton_Link_Button_disabled.eps new file mode 100644 index 000000000..885a4a037 Binary files /dev/null and b/tidal-link/link/assets/Ableton_Link_Button_disabled.eps differ diff --git a/tidal-link/link/assets/Ableton_Link_Button_enabled.eps b/tidal-link/link/assets/Ableton_Link_Button_enabled.eps new file mode 100644 index 000000000..e90e40476 Binary files /dev/null and b/tidal-link/link/assets/Ableton_Link_Button_enabled.eps differ diff --git a/tidal-link/link/ci/build.py b/tidal-link/link/ci/build.py new file mode 100644 index 000000000..2413071cf --- /dev/null +++ b/tidal-link/link/ci/build.py @@ -0,0 +1,72 @@ +#!/usr/bin/env python + +import argparse +import logging +import os +import sys + +from distutils.spawn import find_executable +from subprocess import call + + +def parse_args(): + arg_parser = argparse.ArgumentParser() + + arg_parser.add_argument( + '--cmake', + default=find_executable("cmake"), + help='Path to CMake executable (default: %(default)s)') + + arg_parser.add_argument( + '-c', '--configuration', + help='Build configuration to use (not supported by IDE generators)') + + arg_parser.add_argument( + '-a', '--arguments', + help='Arguments to pass to builder') + + return arg_parser.parse_args(sys.argv[1:]) + + +def build_cmake_args(args, build_dir): + if args.cmake is None: + logging.error('CMake not found, please use the --cmake option') + return None + + cmake_args = [] + cmake_args.append(args.cmake) + cmake_args.append('--build') + cmake_args.append(build_dir) + + if args.configuration is not None: + cmake_args.append('--config') + cmake_args.append(args.configuration) + + if args.arguments is not None: + cmake_args.append('--') + for arg in args.arguments.split(): + cmake_args.append(arg) + + return cmake_args + + +def build(args): + scripts_dir = os.path.dirname(os.path.realpath(__file__)) + root_dir = os.path.join(scripts_dir, os.pardir) + build_dir = os.path.join(root_dir, 'build') + if not os.path.exists(build_dir): + logging.error( + 'Build directory not found, did you forget to run the configure.py script?') + return 2 + + cmake_args = build_cmake_args(args, build_dir) + if cmake_args is None: + return 1 + + logging.info('Running CMake') + return call(cmake_args) + + +if __name__ == '__main__': + logging.basicConfig(format='%(message)s', level=logging.INFO, stream=sys.stdout) + sys.exit(build(parse_args())) diff --git a/tidal-link/link/ci/check-formatting.py b/tidal-link/link/ci/check-formatting.py new file mode 100644 index 000000000..d95eb1000 --- /dev/null +++ b/tidal-link/link/ci/check-formatting.py @@ -0,0 +1,92 @@ +#!/usr/bin/env python + +import argparse +import logging +import os +import subprocess +import sys + + +def parse_args(): + arg_parser = argparse.ArgumentParser() + + arg_parser.add_argument( + '-c', '--clang-format', + default='clang-format-6.0', + help='Path to clang-format executable') + + arg_parser.add_argument( + '-f', '--fix', action='store_true', + help='Automatically fix all files with formatting errors') + + return arg_parser.parse_args(sys.argv[1:]) + + +def parse_clang_xml(xml): + for line in xml.splitlines(): + if line.startswith(b' < +# \___/|_| |_|_/_/\_\ +# + +if(UNIX) + # Common flags for all Unix compilers + set(build_flags_DEBUG_LIST + "-DDEBUG=1" + ) + set(build_flags_RELEASE_LIST + "-DNDEBUG=1" + ) + + # Clang-specific flags + if(${CMAKE_CXX_COMPILER_ID} MATCHES Clang) + set(build_flags_COMMON_LIST + ${build_flags_COMMON_LIST} + "-Weverything" + "-Werror" + "-Wno-c++98-compat" + "-Wno-c++98-compat-pedantic" + "-Wno-deprecated" + "-Wno-disabled-macro-expansion" + "-Wno-exit-time-destructors" + "-Wno-padded" + "-Wno-poison-system-directories" + "-Wno-reserved-id-macro" + "-Wno-unknown-warning-option" + "-Wno-unused-member-function" + ) + + # GCC-specific flags + # Unfortunately, we can't use -Werror on GCC, since there is no way to suppress the + # warnings generated by -fpermissive. + elseif(${CMAKE_CXX_COMPILER_ID} STREQUAL GNU) + set(build_flags_COMMON_LIST + ${build_flags_COMMON_LIST} + "-Werror" + "-Wno-multichar" + ) + endif() + + # ASan support + if(LINK_ENABLE_ASAN) + set(build_flags_COMMON_LIST + ${build_flags_COMMON_LIST} + "-fsanitize=address" + "-fno-omit-frame-pointer" + ) + endif() + +# __ ___ _ +# \ \ / (_)_ __ __| | _____ _____ +# \ \ /\ / /| | '_ \ / _` |/ _ \ \ /\ / / __| +# \ V V / | | | | | (_| | (_) \ V V /\__ \ +# \_/\_/ |_|_| |_|\__,_|\___/ \_/\_/ |___/ +# + +elseif(${CMAKE_CXX_COMPILER_ID} STREQUAL MSVC) + add_definitions("/D_SCL_SECURE_NO_WARNINGS") + if(LINK_BUILD_VLD) + add_definitions("/DLINK_BUILD_VLD=1") + else() + add_definitions("/DLINK_BUILD_VLD=0") + endif() + if(LINK_WINDOWS_SETTHREADDESCRIPTION) + add_definitions("/DLINK_WINDOWS_SETTHREADDESCRIPTION") + endif() + + set(build_flags_DEBUG_LIST + "/DDEBUG=1" + ) + set(build_flags_RELEASE_LIST + "/DNDEBUG=1" + ) + + set(build_flags_COMMON_LIST + ${build_flags_COMMON_LIST} + "/MP" + "/Wall" + "/WX" + "/EHsc" + + ############################# + # Ignored compiler warnings # + ############################# + "/wd4061" # Enumerator 'identifier' in switch of enum 'enumeration' is not explicitly handled by a case label + "/wd4265" # 'Class' : class has virtual functions, but destructor is not virtual + "/wd4350" # Behavior change: 'member1' called instead of 'member2' + "/wd4355" # 'This' : used in base member initializer list + "/wd4365" # 'Action': conversion from 'type_1' to 'type_2', signed/unsigned mismatch + "/wd4371" # Layout of class may have changed from a previous version of the compiler due to better packing of member 'member' + "/wd4503" # 'Identifier': decorated name length exceeded, name was truncated + "/wd4510" # 'Class': default constructor could not be generated + "/wd4512" # 'Class': assignment operator could not be generated + "/wd4514" # 'Function' : unreferenced inline function has been removed + "/wd4571" # Informational: catch(...) semantics changed since Visual C++ 7.1; structured exceptions (SEH) are no longer caught + "/wd4610" # 'Class': can never be instantiated - user defined constructor required + "/wd4625" # 'Derived class' : copy constructor was implicitly defined as deleted because a base class copy constructor is inaccessible or deleted + "/wd4626" # 'Derived class' : assignment operator was implicitly defined as deleted because a base class assignment operator is inaccessible or deleted + "/wd4628" # digraphs not supported with -Ze. Character sequence 'digraph' not interpreted as alternate token for 'char' + "/wd4640" # 'Instance': construction of local static object is not thread-safe + "/wd4710" # 'Function': function not inlined + "/wd4711" # Function 'function' selected for inline expansion + "/wd4723" # potential divide by 0 + "/wd4738" # Storing 32-bit float result in memory, possible loss of performance + "/wd4820" # 'Bytes': bytes padding added after construct 'member_name' + "/wd4996" # Your code uses a function, class member, variable, or typedef that's marked deprecated + "/wd5045" # Compiler will insert Spectre mitigation for memory load if /Qspectre switch specified + "/wd5204" # 'class' : class has virtual functions, but destructor is not virtual + ) + + if(MSVC_VERSION VERSION_GREATER 1800) + set(build_flags_COMMON_LIST + ${build_flags_COMMON_LIST} + "/wd4464" # Relative include path contains '..' + "/wd4548" # Expression before comma has no effect; expected expression with side-effect + "/wd4623" # 'Derived class': default constructor could not be generated because a base class default constructor is inaccessible + "/wd4868" # Compiler may not enforce left-to-right evaluation order in braced initializer list + "/wd5026" # Move constructor was implicitly defined as deleted + "/wd5027" # Move assignment operator was implicitly defined as deleted + ) + endif() + + if(MSVC_VERSION VERSION_GREATER 1900) + set(build_flags_COMMON_LIST + ${build_flags_COMMON_LIST} + "/wd4987" # nonstandard extension used: 'throw (...)' + "/wd4774" # 'printf_s' : format string expected in argument 1 is not a string literal + "/wd5039" # "pointer or reference to potentially throwing function passed to extern C function under -EHc. Undefined behavior may occur if this function throws an exception." + ) + endif() + + if(NOT LINK_BUILD_ASIO) + set(build_flags_COMMON_LIST + ${build_flags_COMMON_LIST} + "/wd4917" # 'Symbol': a GUID can only be associated with a class, interface or namespace + # This compiler warning is generated by Microsoft's own ocidl.h, which is + # used when building the WASAPI driver. + ) + endif() +endif() + +# ____ _ __ _ +# / ___| ___| |_ / _| | __ _ __ _ ___ +# \___ \ / _ \ __| | |_| |/ _` |/ _` / __| +# ___) | __/ |_ | _| | (_| | (_| \__ \ +# |____/ \___|\__| |_| |_|\__,_|\__, |___/ +# |___/ + +# Translate lists to strings +string(REPLACE ";" " " build_flags_COMMON "${build_flags_COMMON_LIST}") +string(REPLACE ";" " " build_flags_DEBUG "${build_flags_DEBUG_LIST}") +string(REPLACE ";" " " build_flags_RELEASE "${build_flags_RELEASE_LIST}") + +# Set flags for different build types +set(CMAKE_CXX_FLAGS "${CMAKE_CXX_FLAGS} ${build_flags_COMMON}") +set(CMAKE_CXX_FLAGS_DEBUG "${CMAKE_CXX_FLAGS_DEBUG} ${build_flags_DEBUG}") +set(CMAKE_CXX_FLAGS_RELEASE "${CMAKE_CXX_FLAGS_RELEASE} ${build_flags_RELEASE}") diff --git a/tidal-link/link/examples/CMakeLists.txt b/tidal-link/link/examples/CMakeLists.txt new file mode 100644 index 000000000..f75b00b1b --- /dev/null +++ b/tidal-link/link/examples/CMakeLists.txt @@ -0,0 +1,223 @@ +cmake_minimum_required(VERSION 3.0) +project(LinkExamples) + +# _ ____ ___ ___ +# / \ / ___|_ _/ _ \ +# / _ \ \___ \| | | | | +# / ___ \ ___) | | |_| | +# /_/ \_\____/___\___/ +# + +if(WIN32) + function(configure_asio asio_sdk_path_OUT) + # ASIO-related path/file variables + set(asio_download_root "https:/download.steinberg.net/sdk_downloads") + set(asio_file_name "asiosdk_2.3.3_2019-06-14.zip") + set(asio_dir_name "asiosdk_2.3.3_2019-06-14") + set(asio_working_dir "${CMAKE_BINARY_DIR}/modules") + set(asio_output_path "${asio_working_dir}/${asio_file_name}") + + message(STATUS "Downloading ASIO SDK") + file(DOWNLOAD "${asio_download_root}/${asio_file_name}" ${asio_output_path}) + file(SHA1 ${asio_output_path} asio_zip_hash) + message(" ASIO SDK SHA1: ${asio_zip_hash}") + + message(" Extracting ASIO SDK") + execute_process(COMMAND ${CMAKE_COMMAND} -E tar "xf" ${asio_output_path} --format=zip + WORKING_DIRECTORY ${asio_working_dir} + INPUT_FILE ${asio_output_path} + ) + + # Set the ASIO SDK path for the caller + set(${asio_sdk_path_OUT} "${asio_working_dir}/${asio_dir_name}" PARENT_SCOPE) + endfunction() +endif() + +# _ _ _ +# / \ _ _ __| (_) ___ +# / _ \| | | |/ _` | |/ _ \ +# / ___ \ |_| | (_| | | (_) | +# /_/ \_\__,_|\__,_|_|\___/ +# + +set(linkhut_audio_SOURCES) + +if(APPLE) + set(linkhut_audio_SOURCES + linkaudio/AudioPlatform_CoreAudio.hpp + linkaudio/AudioPlatform_CoreAudio.cpp + ) +elseif(WIN32) + if(LINK_BUILD_ASIO) + configure_asio(asio_sdk_path) + + include_directories(${asio_sdk_path}/common) + include_directories(${asio_sdk_path}/host) + include_directories(${asio_sdk_path}/host/pc) + + set(linkhut_audio_SOURCES + ${asio_sdk_path}/common/asio.cpp + ${asio_sdk_path}/host/asiodrivers.cpp + ${asio_sdk_path}/host/pc/asiolist.cpp + linkaudio/AudioPlatform_Asio.hpp + linkaudio/AudioPlatform_Asio.cpp + ) + else() + message(WARNING "LinkHut has been configured to be built with the WASAPI audio " + "driver. This driver is considered experimental and has problems with low-latency " + "playback. Please consider using the ASIO driver instead.") + set(linkhut_audio_SOURCES + linkaudio/AudioPlatform_Wasapi.hpp + linkaudio/AudioPlatform_Wasapi.cpp + ) + endif() +elseif(CMAKE_SYSTEM_NAME MATCHES "Linux|kFreeBSD|GNU") + if(LINK_BUILD_JACK) + set(linkhut_audio_SOURCES + linkaudio/AudioPlatform_Jack.hpp + linkaudio/AudioPlatform_Jack.cpp + ) + else() + set(linkhut_audio_SOURCES + linkaudio/AudioPlatform_Portaudio.hpp + linkaudio/AudioPlatform_Portaudio.cpp + ) + endif() +endif() + +include_directories(linkaudio) +source_group("Audio Sources" FILES ${linkhut_audio_SOURCES}) + +# ____ +# / ___|___ _ __ ___ _ __ ___ ___ _ __ +# | | / _ \| '_ ` _ \| '_ ` _ \ / _ \| '_ \ +# | |__| (_) | | | | | | | | | | | (_) | | | | +# \____\___/|_| |_| |_|_| |_| |_|\___/|_| |_| +# + +function(configure_linkhut_executable target) + if(CMAKE_SYSTEM_NAME MATCHES "Linux|kFreeBSD|GNU") + target_link_libraries(${target} atomic pthread) + endif() + + target_link_libraries(${target} Ableton::Link) +endfunction() + +function(configure_linkhut_audio_sources target) + if(APPLE) + target_link_libraries(${target} "-framework AudioUnit") + target_compile_definitions(${target} PRIVATE + -DLINKHUT_AUDIO_PLATFORM_COREAUDIO=1 + ) + elseif(CMAKE_SYSTEM_NAME MATCHES "Linux|kFreeBSD|GNU") + if(LINK_BUILD_JACK) + target_link_libraries(${target} jack) + target_compile_definitions(${target} PRIVATE + -DLINKHUT_AUDIO_PLATFORM_JACK=1 + ) + else() + target_link_libraries(${target} asound portaudio) + target_compile_definitions(${target} PRIVATE + -DLINKHUT_AUDIO_PLATFORM_PORTAUDIO=1 + ) + endif() + elseif(WIN32) + if(LINK_BUILD_ASIO) + # ASIO uses lots of old-school string APIs from the C stdlib + add_definitions("/D_CRT_SECURE_NO_WARNINGS") + target_compile_definitions(${target} PRIVATE + -DLINKHUT_AUDIO_PLATFORM_ASIO=1 + ) + else() + target_compile_definitions(${target} PRIVATE + -DLINKHUT_AUDIO_PLATFORM_WASAPI=1 + ) + endif() + + target_link_libraries(${target} winmm) + endif() + +endfunction() + +if(WIN32) + # When building LinkHut, additional warnings are generated from third-party frameworks + set(extra_ignored_warnings_LIST + "/wd4127" # conditional expression is constant + "/wd4242" # 'identifier' : conversion from 'type1' to 'type2', possible loss of data + "/wd4619" # #pragma warning : there is no warning number 'number' + "/wd4668" # 'symbol' is not defined as a preprocessor macro, replacing with '0' for 'directives' + "/wd4702" # unreachable code + "/wd4946" # reinterpret_cast used between related classes: 'class1' and 'class2' + ) + if(LINK_BUILD_ASIO) + set(extra_ignored_warnings_LIST + ${extra_ignored_warnings_LIST} + "/wd4267" # 'argument': conversion from '?' to '?', possible loss of data + "/wd4477" # 'printf': format string '%?' requires an argument of type '?' + ) + else() + set(extra_ignored_warnings_LIST + ${extra_ignored_warnings_LIST} + "/wd4191" # 'operator/operation' : unsafe conversion from 'type of expression' to 'type required' + ) + endif() + string(REPLACE ";" " " extra_ignored_warnings "${extra_ignored_warnings_LIST}") + set(CMAKE_CXX_FLAGS "${CMAKE_CXX_FLAGS} ${extra_ignored_warnings}") +endif() + +# _ _ _ _ _ _ +# | | (_)_ __ | | _| | | |_ _| |_ +# | | | | '_ \| |/ / |_| | | | | __| +# | |___| | | | | <| _ | |_| | |_ +# |_____|_|_| |_|_|\_\_| |_|\__,_|\__| +# + +set(linkhut_HEADERS + linkaudio/AudioEngine.hpp + linkaudio/AudioPlatform.hpp + ${link_HEADERS} +) + +set(linkhut_SOURCES + linkaudio/AudioEngine.cpp + linkhut/main.cpp +) + +add_executable(LinkHut + ${linkhut_HEADERS} + ${linkhut_SOURCES} + ${linkhut_audio_SOURCES} +) +configure_linkhut_audio_sources(LinkHut) +configure_linkhut_executable(LinkHut) +source_group("LinkHut" FILES ${linkhut_HEADERS} ${linkhut_SOURCES}) + +# _ _ _ _ _ _ ____ _ _ _ +# | | (_)_ __ | | _| | | |_ _| |_/ ___|(_) | ___ _ __ | |_ +# | | | | '_ \| |/ / |_| | | | | __\___ \| | |/ _ \ '_ \| __| +# | |___| | | | | <| _ | |_| | |_ ___) | | | __/ | | | |_ +# |_____|_|_| |_|_|\_\_| |_|\__,_|\__|____/|_|_|\___|_| |_|\__| +# + +set(linkhutsilent_HEADERS + linkaudio/AudioEngine.hpp + linkaudio/AudioPlatform_Dummy.hpp + ${link_HEADERS} +) + +set(linkhutsilent_SOURCES + linkaudio/AudioEngine.cpp + linkhut/main.cpp +) + +add_executable(LinkHutSilent + ${linkhutsilent_HEADERS} + ${linkhutsilent_SOURCES} +) + +target_compile_definitions(LinkHutSilent PRIVATE + -DLINKHUT_AUDIO_PLATFORM_DUMMY=1 +) + +configure_linkhut_executable(LinkHutSilent) +source_group("LinkHutSilent" FILES ${linkhutsilent_HEADERS} ${linkhutsilent_SOURCES}) diff --git a/tidal-link/link/examples/esp32/.gitignore b/tidal-link/link/examples/esp32/.gitignore new file mode 100644 index 000000000..d054d8439 --- /dev/null +++ b/tidal-link/link/examples/esp32/.gitignore @@ -0,0 +1,3 @@ +build +sdkconfig +sdkconfig.old diff --git a/tidal-link/link/examples/esp32/CMakeLists.txt b/tidal-link/link/examples/esp32/CMakeLists.txt new file mode 100644 index 000000000..b6d956d74 --- /dev/null +++ b/tidal-link/link/examples/esp32/CMakeLists.txt @@ -0,0 +1,6 @@ +cmake_minimum_required(VERSION 3.5) + +set(EXTRA_COMPONENT_DIRS $ENV{IDF_PATH}/examples/common_components/protocol_examples_common) + +include($ENV{IDF_PATH}/tools/cmake/project.cmake) +project(link_esp32_example) \ No newline at end of file diff --git a/tidal-link/link/examples/esp32/README.md b/tidal-link/link/examples/esp32/README.md new file mode 100644 index 000000000..3379db627 --- /dev/null +++ b/tidal-link/link/examples/esp32/README.md @@ -0,0 +1,12 @@ +# *E X P E R I M E N T A L* + +*Tested with esp-idf [v4.3.1](https://github.com/espressif/esp-idf/releases/tag/v4.3.1)* + +## Building and Running the Example + +* Setup esp-idf as described in [the documentation](https://docs.espressif.com/projects/esp-idf/en/latest/get-started/index.html) +* Run `idf.py menuconfig` and setup WiFi credentials under +`Example Connection Configuration` +``` +idf.py build +idf.py -p ${ESP32_SERIAL_PORT} flash diff --git a/tidal-link/link/examples/esp32/main/CMakeLists.txt b/tidal-link/link/examples/esp32/main/CMakeLists.txt new file mode 100644 index 000000000..64756eed6 --- /dev/null +++ b/tidal-link/link/examples/esp32/main/CMakeLists.txt @@ -0,0 +1,11 @@ +idf_component_register(SRCS main.cpp) + +if(NOT DEFINED LINK_ESP_TASK_CORE_ID) + set(LINK_ESP_TASK_CORE_ID tskNO_AFFINITY) +endif() +target_compile_definitions(${COMPONENT_LIB} PRIVATE LINK_ESP_TASK_CORE_ID=${LINK_ESP_TASK_CORE_ID}) + +target_compile_options(${COMPONENT_LIB} PRIVATE -fexceptions) + +include(../../../AbletonLinkConfig.cmake) +target_link_libraries(${COMPONENT_TARGET} Ableton::Link) diff --git a/tidal-link/link/examples/esp32/main/main.cpp b/tidal-link/link/examples/esp32/main/main.cpp new file mode 100644 index 000000000..b44f45923 --- /dev/null +++ b/tidal-link/link/examples/esp32/main/main.cpp @@ -0,0 +1,109 @@ +#include +#include +#include +#include +#include +#include +#include +#include +#include + +#define LED GPIO_NUM_2 +#define PRINT_LINK_STATE false + +unsigned int if_nametoindex(const char* ifName) +{ + return 0; +} + +char* if_indextoname(unsigned int ifIndex, char* ifName) +{ + return nullptr; +} + +void IRAM_ATTR timer_group0_isr(void* userParam) +{ + static BaseType_t xHigherPriorityTaskWoken = pdFALSE; + + TIMERG0.int_clr_timers.t0 = 1; + TIMERG0.hw_timer[0].config.alarm_en = 1; + + xSemaphoreGiveFromISR(userParam, &xHigherPriorityTaskWoken); + if (xHigherPriorityTaskWoken) + { + portYIELD_FROM_ISR(); + } +} + +void timerGroup0Init(int timerPeriodUS, void* userParam) +{ + timer_config_t config = {.alarm_en = TIMER_ALARM_EN, + .counter_en = TIMER_PAUSE, + .intr_type = TIMER_INTR_LEVEL, + .counter_dir = TIMER_COUNT_UP, + .auto_reload = TIMER_AUTORELOAD_EN, + .divider = 80}; + + timer_init(TIMER_GROUP_0, TIMER_0, &config); + timer_set_counter_value(TIMER_GROUP_0, TIMER_0, 0); + timer_set_alarm_value(TIMER_GROUP_0, TIMER_0, timerPeriodUS); + timer_enable_intr(TIMER_GROUP_0, TIMER_0); + timer_isr_register(TIMER_GROUP_0, TIMER_0, &timer_group0_isr, userParam, 0, nullptr); + + timer_start(TIMER_GROUP_0, TIMER_0); +} + +void printTask(void* userParam) +{ + auto link = static_cast(userParam); + const auto quantum = 4.0; + + while (true) + { + const auto sessionState = link->captureAppSessionState(); + const auto numPeers = link->numPeers(); + const auto time = link->clock().micros(); + const auto beats = sessionState.beatAtTime(time, quantum); + std::cout << std::defaultfloat << "| peers: " << numPeers << " | " + << "tempo: " << sessionState.tempo() << " | " << std::fixed + << "beats: " << beats << " |" << std::endl; + vTaskDelay(800 / portTICK_PERIOD_MS); + } +} + +void tickTask(void* userParam) +{ + SemaphoreHandle_t handle = static_cast(userParam); + ableton::Link link(120.0f); + link.enable(true); + + if (PRINT_LINK_STATE) + { + xTaskCreate(printTask, "print", 8192, &link, 1, nullptr); + } + + gpio_set_direction(LED, GPIO_MODE_OUTPUT); + + while (true) + { + xSemaphoreTake(handle, portMAX_DELAY); + + const auto state = link.captureAudioSessionState(); + const auto phase = state.phaseAtTime(link.clock().micros(), 1.); + gpio_set_level(LED, fmodf(phase, 1.) < 0.1); + portYIELD(); + } +} + +extern "C" void app_main() +{ + ESP_ERROR_CHECK(nvs_flash_init()); + esp_netif_init(); + ESP_ERROR_CHECK(esp_event_loop_create_default()); + ESP_ERROR_CHECK(example_connect()); + + SemaphoreHandle_t tickSemphr = xSemaphoreCreateBinary(); + timerGroup0Init(100, tickSemphr); + + xTaskCreate(tickTask, "tick", 8192, tickSemphr, configMAX_PRIORITIES - 1, nullptr); +} diff --git a/tidal-link/link/examples/esp32/sdkconfig.defaults b/tidal-link/link/examples/esp32/sdkconfig.defaults new file mode 100644 index 000000000..75ebeae1c --- /dev/null +++ b/tidal-link/link/examples/esp32/sdkconfig.defaults @@ -0,0 +1 @@ +CONFIG_COMPILER_CXX_EXCEPTIONS=y diff --git a/tidal-link/link/examples/linkaudio/AudioEngine.cpp b/tidal-link/link/examples/linkaudio/AudioEngine.cpp new file mode 100644 index 000000000..45df3a26e --- /dev/null +++ b/tidal-link/link/examples/linkaudio/AudioEngine.cpp @@ -0,0 +1,240 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#include "AudioEngine.hpp" + +// Make sure to define this before is included for Windows +#ifdef LINK_PLATFORM_WINDOWS +#define _USE_MATH_DEFINES +#endif +#include +#include + +namespace ableton +{ +namespace linkaudio +{ + +AudioEngine::AudioEngine(Link& link) + : mLink(link) + , mSampleRate(44100.) + , mOutputLatency(std::chrono::microseconds{0}) + , mSharedEngineData({0., false, false, 4., false}) + , mLockfreeEngineData(mSharedEngineData) + , mTimeAtLastClick{} + , mIsPlaying(false) +{ + if (!mOutputLatency.is_lock_free()) + { + std::cout << "WARNING: AudioEngine::mOutputLatency is not lock free!" << std::endl; + } +} + +void AudioEngine::startPlaying() +{ + std::lock_guard lock(mEngineDataGuard); + mSharedEngineData.requestStart = true; +} + +void AudioEngine::stopPlaying() +{ + std::lock_guard lock(mEngineDataGuard); + mSharedEngineData.requestStop = true; +} + +bool AudioEngine::isPlaying() const +{ + return mLink.captureAppSessionState().isPlaying(); +} + +double AudioEngine::beatTime() const +{ + const auto sessionState = mLink.captureAppSessionState(); + return sessionState.beatAtTime(mLink.clock().micros(), mSharedEngineData.quantum); +} + +void AudioEngine::setTempo(double tempo) +{ + std::lock_guard lock(mEngineDataGuard); + mSharedEngineData.requestedTempo = tempo; +} + +double AudioEngine::quantum() const +{ + return mSharedEngineData.quantum; +} + +void AudioEngine::setQuantum(double quantum) +{ + std::lock_guard lock(mEngineDataGuard); + mSharedEngineData.quantum = quantum; +} + +bool AudioEngine::isStartStopSyncEnabled() const +{ + return mLink.isStartStopSyncEnabled(); +} + +void AudioEngine::setStartStopSyncEnabled(const bool enabled) +{ + mLink.enableStartStopSync(enabled); +} + +void AudioEngine::setBufferSize(std::size_t size) +{ + mBuffer = std::vector(size, 0.); +} + +void AudioEngine::setSampleRate(double sampleRate) +{ + mSampleRate = sampleRate; +} + +AudioEngine::EngineData AudioEngine::pullEngineData() +{ + auto engineData = EngineData{}; + if (mEngineDataGuard.try_lock()) + { + engineData.requestedTempo = mSharedEngineData.requestedTempo; + mSharedEngineData.requestedTempo = 0; + engineData.requestStart = mSharedEngineData.requestStart; + mSharedEngineData.requestStart = false; + engineData.requestStop = mSharedEngineData.requestStop; + mSharedEngineData.requestStop = false; + + mLockfreeEngineData.quantum = mSharedEngineData.quantum; + mLockfreeEngineData.startStopSyncOn = mSharedEngineData.startStopSyncOn; + + mEngineDataGuard.unlock(); + } + engineData.quantum = mLockfreeEngineData.quantum; + + return engineData; +} + +void AudioEngine::renderMetronomeIntoBuffer(const Link::SessionState sessionState, + const double quantum, + const std::chrono::microseconds beginHostTime, + const std::size_t numSamples) +{ + using namespace std::chrono; + + // Metronome frequencies + static const double highTone = 1567.98; + static const double lowTone = 1108.73; + // 100ms click duration + static const auto clickDuration = duration{0.1}; + + // The number of microseconds that elapse between samples + const auto microsPerSample = 1e6 / mSampleRate; + + for (std::size_t i = 0; i < numSamples; ++i) + { + double amplitude = 0.; + // Compute the host time for this sample and the last. + const auto hostTime = + beginHostTime + microseconds(llround(static_cast(i) * microsPerSample)); + const auto lastSampleHostTime = hostTime - microseconds(llround(microsPerSample)); + + // Only make sound for positive beat magnitudes. Negative beat + // magnitudes are count-in beats. + if (sessionState.beatAtTime(hostTime, quantum) >= 0.) + { + // If the phase wraps around between the last sample and the + // current one with respect to a 1 beat quantum, then a click + // should occur. + if (sessionState.phaseAtTime(hostTime, 1) + < sessionState.phaseAtTime(lastSampleHostTime, 1)) + { + mTimeAtLastClick = hostTime; + } + + const auto secondsAfterClick = + duration_cast>(hostTime - mTimeAtLastClick); + + // If we're within the click duration of the last beat, render + // the click tone into this sample + if (secondsAfterClick < clickDuration) + { + // If the phase of the last beat with respect to the current + // quantum was zero, then it was at a quantum boundary and we + // want to use the high tone. For other beats within the + // quantum, use the low tone. + const auto freq = + floor(sessionState.phaseAtTime(hostTime, quantum)) == 0 ? highTone : lowTone; + + // Simple cosine synth + amplitude = cos(2 * M_PI * secondsAfterClick.count() * freq) + * (1 - sin(5 * M_PI * secondsAfterClick.count())); + } + } + mBuffer[i] = amplitude; + } +} + +void AudioEngine::audioCallback( + const std::chrono::microseconds hostTime, const std::size_t numSamples) +{ + const auto engineData = pullEngineData(); + + auto sessionState = mLink.captureAudioSessionState(); + + // Clear the buffer + std::fill(mBuffer.begin(), mBuffer.end(), 0); + + if (engineData.requestStart) + { + sessionState.setIsPlaying(true, hostTime); + } + + if (engineData.requestStop) + { + sessionState.setIsPlaying(false, hostTime); + } + + if (!mIsPlaying && sessionState.isPlaying()) + { + // Reset the timeline so that beat 0 corresponds to the time when transport starts + sessionState.requestBeatAtStartPlayingTime(0, engineData.quantum); + mIsPlaying = true; + } + else if (mIsPlaying && !sessionState.isPlaying()) + { + mIsPlaying = false; + } + + if (engineData.requestedTempo > 0) + { + // Set the newly requested tempo from the beginning of this buffer + sessionState.setTempo(engineData.requestedTempo, hostTime); + } + + // Timeline modifications are complete, commit the results + mLink.commitAudioSessionState(sessionState); + + if (mIsPlaying) + { + // As long as the engine is playing, generate metronome clicks in + // the buffer at the appropriate beats. + renderMetronomeIntoBuffer(sessionState, engineData.quantum, hostTime, numSamples); + } +} + +} // namespace linkaudio +} // namespace ableton diff --git a/tidal-link/link/examples/linkaudio/AudioEngine.hpp b/tidal-link/link/examples/linkaudio/AudioEngine.hpp new file mode 100644 index 000000000..f9c94d51c --- /dev/null +++ b/tidal-link/link/examples/linkaudio/AudioEngine.hpp @@ -0,0 +1,81 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +// Make sure to define this before is included for Windows +#define _USE_MATH_DEFINES +#include +#include +#include + +namespace ableton +{ +namespace linkaudio +{ + +class AudioEngine +{ +public: + AudioEngine(Link& link); + void startPlaying(); + void stopPlaying(); + bool isPlaying() const; + double beatTime() const; + void setTempo(double tempo); + double quantum() const; + void setQuantum(double quantum); + bool isStartStopSyncEnabled() const; + void setStartStopSyncEnabled(bool enabled); + +private: + struct EngineData + { + double requestedTempo; + bool requestStart; + bool requestStop; + double quantum; + bool startStopSyncOn; + }; + + void setBufferSize(std::size_t size); + void setSampleRate(double sampleRate); + EngineData pullEngineData(); + void renderMetronomeIntoBuffer(Link::SessionState sessionState, + double quantum, + std::chrono::microseconds beginHostTime, + std::size_t numSamples); + void audioCallback(const std::chrono::microseconds hostTime, std::size_t numSamples); + + Link& mLink; + double mSampleRate; + std::atomic mOutputLatency; + std::vector mBuffer; + EngineData mSharedEngineData; + EngineData mLockfreeEngineData; + std::chrono::microseconds mTimeAtLastClick; + bool mIsPlaying; + std::mutex mEngineDataGuard; + + friend class AudioPlatform; +}; + + +} // namespace linkaudio +} // namespace ableton diff --git a/tidal-link/link/examples/linkaudio/AudioPlatform.hpp b/tidal-link/link/examples/linkaudio/AudioPlatform.hpp new file mode 100644 index 000000000..9ebc24830 --- /dev/null +++ b/tidal-link/link/examples/linkaudio/AudioPlatform.hpp @@ -0,0 +1,44 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#if defined(LINKHUT_AUDIO_PLATFORM_ASIO) +#include "AudioPlatform_Asio.hpp" +#endif + +#if defined(LINKHUT_AUDIO_PLATFORM_COREAUDIO) +#include "AudioPlatform_CoreAudio.hpp" +#endif + +#if defined(LINKHUT_AUDIO_PLATFORM_DUMMY) +#include "AudioPlatform_Dummy.hpp" +#endif + +#if defined(LINKHUT_AUDIO_PLATFORM_JACK) +#include "AudioPlatform_Jack.hpp" +#endif + +#if defined(LINKHUT_AUDIO_PLATFORM_PORTAUDIO) +#include "AudioPlatform_Portaudio.hpp" +#endif + +#if defined(LINKHUT_AUDIO_PLATFORM_WASAPI) +#include "AudioPlatform_Wasapi.hpp" +#endif diff --git a/tidal-link/link/examples/linkaudio/AudioPlatform_Asio.cpp b/tidal-link/link/examples/linkaudio/AudioPlatform_Asio.cpp new file mode 100644 index 000000000..8e22845c8 --- /dev/null +++ b/tidal-link/link/examples/linkaudio/AudioPlatform_Asio.cpp @@ -0,0 +1,315 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#include "AudioPlatform_Asio.hpp" + +namespace ableton +{ +namespace linkaudio +{ + +void fatalError(const ASIOError result, const std::string& function) +{ + std::cerr << "Call to ASIO function " << function << " failed"; + if (result != ASE_OK) + { + std::cerr << " (ASIO error code " << result << ")"; + } + std::cerr << std::endl; + std::terminate(); +} + +double asioSamplesToDouble(const ASIOSamples& samples) +{ + return samples.lo + samples.hi * std::pow(2, 32); +} + +// ASIO processing callbacks +ASIOTime* bufferSwitchTimeInfo(ASIOTime* timeInfo, long index, ASIOBool) +{ + AudioPlatform* platform = AudioPlatform::singleton(); + if (platform) + { + platform->audioCallback(timeInfo, index); + } + return nullptr; +} + +void bufferSwitch(long index, ASIOBool processNow) +{ + ASIOTime timeInfo{}; + ASIOError result = ASIOGetSamplePosition( + &timeInfo.timeInfo.samplePosition, &timeInfo.timeInfo.systemTime); + if (result != ASE_OK) + { + std::cerr << "ASIOGetSamplePosition failed with ASIO error: " << result << std::endl; + } + else + { + timeInfo.timeInfo.flags = kSystemTimeValid | kSamplePositionValid; + } + + bufferSwitchTimeInfo(&timeInfo, index, processNow); +} + +AudioPlatform* AudioPlatform::_singleton = nullptr; + +AudioPlatform* AudioPlatform::singleton() +{ + return _singleton; +} + +void AudioPlatform::setSingleton(AudioPlatform* platform) +{ + _singleton = platform; +} + +AudioPlatform::AudioPlatform(Link& link) + : mEngine(link) +{ + initialize(); + mEngine.setBufferSize(mDriverInfo.preferredSize); + mEngine.setSampleRate(mDriverInfo.sampleRate); + setSingleton(this); + start(); +} + +AudioPlatform::~AudioPlatform() +{ + stop(); + ASIODisposeBuffers(); + ASIOExit(); + if (asioDrivers != nullptr) + { + asioDrivers->removeCurrentDriver(); + } + + setSingleton(nullptr); +} + +void AudioPlatform::audioCallback(ASIOTime* timeInfo, long index) +{ + auto hostTime = std::chrono::microseconds(0); + if (timeInfo->timeInfo.flags & kSystemTimeValid) + { + hostTime = mHostTimeFilter.sampleTimeToHostTime( + asioSamplesToDouble(timeInfo->timeInfo.samplePosition)); + } + + const auto bufferBeginAtOutput = hostTime + mEngine.mOutputLatency.load(); + + ASIOBufferInfo* bufferInfos = mDriverInfo.bufferInfos; + const long numSamples = mDriverInfo.preferredSize; + const long numChannels = mDriverInfo.numBuffers; + const double maxAmp = std::numeric_limits::max(); + + mEngine.audioCallback(bufferBeginAtOutput, numSamples); + + for (long i = 0; i < numSamples; ++i) + { + for (long j = 0; j < numChannels; ++j) + { + int* buffer = static_cast(bufferInfos[j].buffers[index]); + buffer[i] = static_cast(mEngine.mBuffer[i] * maxAmp); + } + } + + if (mDriverInfo.outputReady) + { + ASIOOutputReady(); + } +} + +void AudioPlatform::createAsioBuffers() +{ + DriverInfo& driverInfo = mDriverInfo; + ASIOBufferInfo* bufferInfo = driverInfo.bufferInfos; + driverInfo.numBuffers = 0; + + // Prepare input channels. Though this is not necessarily required, the opened input + // channels will not work. + int numInputBuffers; + if (driverInfo.inputChannels > LINK_ASIO_INPUT_CHANNELS) + { + numInputBuffers = LINK_ASIO_INPUT_CHANNELS; + } + else + { + numInputBuffers = driverInfo.inputChannels; + } + + for (long i = 0; i < numInputBuffers; ++i, ++bufferInfo) + { + bufferInfo->isInput = ASIOTrue; + bufferInfo->channelNum = i; + bufferInfo->buffers[0] = bufferInfo->buffers[1] = nullptr; + } + + // Prepare output channels + int numOutputBuffers; + if (driverInfo.outputChannels > LINK_ASIO_OUTPUT_CHANNELS) + { + numOutputBuffers = LINK_ASIO_OUTPUT_CHANNELS; + } + else + { + numOutputBuffers = driverInfo.outputChannels; + } + + for (long i = 0; i < numOutputBuffers; i++, bufferInfo++) + { + bufferInfo->isInput = ASIOFalse; + bufferInfo->channelNum = i; + bufferInfo->buffers[0] = bufferInfo->buffers[1] = nullptr; + } + + driverInfo.numBuffers = numInputBuffers + numOutputBuffers; + ASIOError result = ASIOCreateBuffers(driverInfo.bufferInfos, driverInfo.numBuffers, + driverInfo.preferredSize, &(mAsioCallbacks)); + if (result != ASE_OK) + { + fatalError(result, "ASIOCreateBuffers"); + } + + // Now get all buffer details, sample word length, name, word clock group and latency + for (long i = 0; i < driverInfo.numBuffers; ++i) + { + driverInfo.channelInfos[i].channel = driverInfo.bufferInfos[i].channelNum; + driverInfo.channelInfos[i].isInput = driverInfo.bufferInfos[i].isInput; + + result = ASIOGetChannelInfo(&driverInfo.channelInfos[i]); + if (result != ASE_OK) + { + fatalError(result, "ASIOGetChannelInfo"); + } + + std::clog << "ASIOGetChannelInfo successful, type: " + << (driverInfo.bufferInfos[i].isInput ? "input" : "output") + << ", channel: " << i + << ", sample type: " << driverInfo.channelInfos[i].type << std::endl; + + if (driverInfo.channelInfos[i].type != ASIOSTInt32LSB) + { + fatalError(ASE_OK, "Unsupported sample type!"); + } + } + + long inputLatency, outputLatency; + result = ASIOGetLatencies(&inputLatency, &outputLatency); + if (result != ASE_OK) + { + fatalError(result, "ASIOGetLatencies"); + } + std::clog << "Driver input latency: " << inputLatency << "usec" + << ", output latency: " << outputLatency << "usec" << std::endl; + + const double bufferSize = driverInfo.preferredSize / driverInfo.sampleRate; + auto outputLatencyMicros = + std::chrono::microseconds(llround(outputLatency / driverInfo.sampleRate)); + outputLatencyMicros += std::chrono::microseconds(llround(1.0e6 * bufferSize)); + + mEngine.mOutputLatency.store(outputLatencyMicros); + + std::clog << "Total latency: " << outputLatencyMicros.count() << "usec" << std::endl; +} + +void AudioPlatform::initializeDriverInfo() +{ + ASIOError result = + ASIOGetChannels(&mDriverInfo.inputChannels, &mDriverInfo.outputChannels); + if (result != ASE_OK) + { + fatalError(result, "ASIOGetChannels"); + } + std::clog << "ASIOGetChannels succeeded, inputs:" << mDriverInfo.inputChannels + << ", outputs: " << mDriverInfo.outputChannels << std::endl; + + long minSize, maxSize, granularity; + result = + ASIOGetBufferSize(&minSize, &maxSize, &mDriverInfo.preferredSize, &granularity); + if (result != ASE_OK) + { + fatalError(result, "ASIOGetBufferSize"); + } + std::clog << "ASIOGetBufferSize succeeded, min: " << minSize << ", max: " << maxSize + << ", preferred: " << mDriverInfo.preferredSize + << ", granularity: " << granularity << std::endl; + + result = ASIOGetSampleRate(&mDriverInfo.sampleRate); + if (result != ASE_OK) + { + fatalError(result, "ASIOGetSampleRate"); + } + std::clog << "ASIOGetSampleRate succeeded, sampleRate: " << mDriverInfo.sampleRate + << "Hz" << std::endl; + + // Check wether the driver requires the ASIOOutputReady() optimization, which can be + // used by the driver to reduce output latency by one block + mDriverInfo.outputReady = (ASIOOutputReady() == ASE_OK); + std::clog << "ASIOOutputReady optimization is " + << (mDriverInfo.outputReady ? "enabled" : "disabled") << std::endl; +} + +void AudioPlatform::initialize() +{ + if (!loadAsioDriver(LINK_ASIO_DRIVER_NAME)) + { + std::cerr << "Failed opening ASIO driver for device named '" << LINK_ASIO_DRIVER_NAME + << "', is the driver installed?" << std::endl; + std::terminate(); + } + + ASIOError result = ASIOInit(&mDriverInfo.driverInfo); + if (result != ASE_OK) + { + fatalError(result, "ASIOInit"); + } + + std::clog << "ASIOInit succeeded, asioVersion: " << mDriverInfo.driverInfo.asioVersion + << ", driverVersion: " << mDriverInfo.driverInfo.driverVersion + << ", name: " << mDriverInfo.driverInfo.name << std::endl; + + initializeDriverInfo(); + + ASIOCallbacks* callbacks = &(mAsioCallbacks); + callbacks->bufferSwitch = &bufferSwitch; + callbacks->bufferSwitchTimeInfo = &bufferSwitchTimeInfo; + createAsioBuffers(); +} + +void AudioPlatform::start() +{ + ASIOError result = ASIOStart(); + if (result != ASE_OK) + { + fatalError(result, "ASIOStart"); + } +} + +void AudioPlatform::stop() +{ + ASIOError result = ASIOStop(); + if (result != ASE_OK) + { + fatalError(result, "ASIOStop"); + } +} + +} // namespace linkaudio +} // namespace ableton diff --git a/tidal-link/link/examples/linkaudio/AudioPlatform_Asio.hpp b/tidal-link/link/examples/linkaudio/AudioPlatform_Asio.hpp new file mode 100644 index 000000000..b3286744c --- /dev/null +++ b/tidal-link/link/examples/linkaudio/AudioPlatform_Asio.hpp @@ -0,0 +1,103 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include "AudioEngine.hpp" + +#include +#include + +#include "asiosys.h" // Should be included before asio.h + +#include "asio.h" +#include "asiodrivers.h" + +// External functions in the ASIO SDK which aren't declared in the SDK headers +extern AsioDrivers* asioDrivers; +bool loadAsioDriver(char* name); + +namespace ableton +{ +namespace linkaudio +{ + +#ifndef LINK_ASIO_DRIVER_NAME +#define LINK_ASIO_DRIVER_NAME "ASIO4ALL v2" +#endif +#ifndef LINK_ASIO_INPUT_CHANNELS +#define LINK_ASIO_INPUT_CHANNELS 0 +#endif +#ifndef LINK_ASIO_OUTPUT_CHANNELS +#define LINK_ASIO_OUTPUT_CHANNELS 2 +#endif + +struct DriverInfo +{ + ASIODriverInfo driverInfo; + long inputChannels; + long outputChannels; + long preferredSize; + ASIOSampleRate sampleRate; + bool outputReady; + long numBuffers; + ASIOBufferInfo bufferInfos[LINK_ASIO_INPUT_CHANNELS + LINK_ASIO_OUTPUT_CHANNELS]; + ASIOChannelInfo channelInfos[LINK_ASIO_INPUT_CHANNELS + LINK_ASIO_OUTPUT_CHANNELS]; +}; + +// Helper functions + +// Convenience function to print out an ASIO error code along with the function called +void fatalError(const ASIOError result, const std::string& function); +double asioSamplesToDouble(const ASIOSamples& samples); + +ASIOTime* bufferSwitchTimeInfo(ASIOTime* timeInfo, long index, ASIOBool); +void bufferSwitch(long index, ASIOBool processNow); + +class AudioPlatform +{ +public: + AudioPlatform(Link& link); + ~AudioPlatform(); + + void audioCallback(ASIOTime* timeInfo, long index); + + AudioEngine mEngine; + + // Unfortunately, the ASIO SDK does not allow passing void* user data to callback + // functions, so we need to keep a singleton instance of the audio engine + static AudioPlatform* singleton(); + static void setSingleton(AudioPlatform* platform); + +private: + void createAsioBuffers(); + void initializeDriverInfo(); + void initialize(); + void start(); + void stop(); + + DriverInfo mDriverInfo; + ASIOCallbacks mAsioCallbacks; + link::HostTimeFilter mHostTimeFilter; + + static AudioPlatform* _singleton; +}; + +} // namespace linkaudio +} // namespace ableton diff --git a/tidal-link/link/examples/linkaudio/AudioPlatform_CoreAudio.cpp b/tidal-link/link/examples/linkaudio/AudioPlatform_CoreAudio.cpp new file mode 100644 index 000000000..d4b4552b8 --- /dev/null +++ b/tidal-link/link/examples/linkaudio/AudioPlatform_CoreAudio.cpp @@ -0,0 +1,214 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#include "AudioPlatform_CoreAudio.hpp" +#include +#include +#include + +namespace ableton +{ +namespace linkaudio +{ + +AudioPlatform::AudioPlatform(Link& link) + : mEngine(link) +{ + initialize(); + start(); +} + +AudioPlatform::~AudioPlatform() +{ + stop(); + uninitialize(); +} + +OSStatus AudioPlatform::audioCallback(void* inRefCon, + AudioUnitRenderActionFlags*, + const AudioTimeStamp* inTimeStamp, + UInt32, + UInt32 inNumberFrames, + AudioBufferList* ioData) +{ + AudioEngine* engine = static_cast(inRefCon); + + const auto bufferBeginAtOutput = + engine->mLink.clock().ticksToMicros(inTimeStamp->mHostTime) + + engine->mOutputLatency.load(); + + engine->audioCallback(bufferBeginAtOutput, inNumberFrames); + + for (std::size_t i = 0; i < inNumberFrames; ++i) + { + for (UInt32 j = 0; j < ioData->mNumberBuffers; ++j) + { + SInt16* bufData = static_cast(ioData->mBuffers[j].mData); + bufData[i] = static_cast(32761. * engine->mBuffer[i]); + } + } + + return noErr; +} + +void AudioPlatform::initialize() +{ + AudioComponentDescription cd = {}; + cd.componentManufacturer = kAudioUnitManufacturer_Apple; + cd.componentFlags = 0; + cd.componentFlagsMask = 0; + cd.componentType = kAudioUnitType_Output; + cd.componentSubType = kAudioUnitSubType_DefaultOutput; + + AudioComponent component = AudioComponentFindNext(nullptr, &cd); + OSStatus result = AudioComponentInstanceNew(component, &mIoUnit); + if (result) + { + std::cerr << "Could not get Audio Unit. " << result << std::endl; + std::terminate(); + } + + UInt32 size = sizeof(mEngine.mSampleRate); + result = AudioUnitGetProperty(mIoUnit, kAudioUnitProperty_SampleRate, + kAudioUnitScope_Output, 0, &mEngine.mSampleRate, &size); + if (result) + { + std::cerr << "Could not get sample rate. " << result << std::endl; + std::terminate(); + } + std::clog << "SAMPLE RATE: " << mEngine.mSampleRate << std::endl; + + AudioStreamBasicDescription asbd = {}; + asbd.mFormatID = kAudioFormatLinearPCM; + asbd.mFormatFlags = kAudioFormatFlagIsSignedInteger | kAudioFormatFlagIsPacked + | kAudioFormatFlagsNativeEndian | kAudioFormatFlagIsNonInterleaved; + asbd.mChannelsPerFrame = 2; + asbd.mBytesPerPacket = sizeof(SInt16); + asbd.mFramesPerPacket = 1; + asbd.mBytesPerFrame = sizeof(SInt16); + asbd.mBitsPerChannel = 8 * sizeof(SInt16); + asbd.mSampleRate = mEngine.mSampleRate; + + result = AudioUnitSetProperty(mIoUnit, kAudioUnitProperty_StreamFormat, + kAudioUnitScope_Input, 0, &asbd, sizeof(asbd)); + if (result) + { + std::cerr << "Could not set stream format. " << result << std::endl; + } + + char deviceName[512]; + size = sizeof(deviceName); + result = AudioUnitGetProperty(mIoUnit, kAudioDevicePropertyDeviceName, + kAudioUnitScope_Global, 0, &deviceName, &size); + if (result) + { + std::cerr << "Could not get device name. " << result << std::endl; + std::terminate(); + } + std::clog << "DEVICE NAME: " << deviceName << std::endl; + + UInt32 bufferSize = 512; + size = sizeof(bufferSize); + result = AudioUnitSetProperty(mIoUnit, kAudioDevicePropertyBufferFrameSize, + kAudioUnitScope_Global, 0, &bufferSize, size); + if (result) + { + std::cerr << "Could not set buffer size. " << result << std::endl; + std::terminate(); + } + mEngine.setBufferSize(bufferSize); + + UInt32 propertyResult = 0; + size = sizeof(propertyResult); + result = AudioUnitGetProperty(mIoUnit, kAudioDevicePropertyBufferFrameSize, + kAudioUnitScope_Global, 0, &propertyResult, &size); + if (result) + { + std::cerr << "Could not get buffer size. " << result << std::endl; + std::terminate(); + } + std::clog << "BUFFER SIZE: " << propertyResult << " samples, " + << propertyResult / mEngine.mSampleRate * 1e3 << " ms." << std::endl; + + // the buffer, stream and safety-offset latencies are part of inTimeStamp->mHostTime + // within the audio callback. + UInt32 deviceLatency = 0; + size = sizeof(deviceLatency); + result = AudioUnitGetProperty(mIoUnit, kAudioDevicePropertyLatency, + kAudioUnitScope_Output, 0, &deviceLatency, &size); + if (result) + { + std::cerr << "Could not get output device latency. " << result << std::endl; + std::terminate(); + } + std::clog << "OUTPUT DEVICE LATENCY: " << deviceLatency << " samples, " + << deviceLatency / mEngine.mSampleRate * 1e3 << " ms." << std::endl; + + using namespace std::chrono; + const double latency = static_cast(deviceLatency) / mEngine.mSampleRate; + mEngine.mOutputLatency.store(duration_cast(duration{latency})); + + AURenderCallbackStruct ioRemoteInput; + ioRemoteInput.inputProc = audioCallback; + ioRemoteInput.inputProcRefCon = &mEngine; + + result = AudioUnitSetProperty(mIoUnit, kAudioUnitProperty_SetRenderCallback, + kAudioUnitScope_Input, 0, &ioRemoteInput, sizeof(ioRemoteInput)); + if (result) + { + std::cerr << "Could not set render callback. " << result << std::endl; + } + + result = AudioUnitInitialize(mIoUnit); + if (result) + { + std::cerr << "Could not initialize audio unit. " << result << std::endl; + } +} + +void AudioPlatform::uninitialize() +{ + OSStatus result = AudioUnitUninitialize(mIoUnit); + if (result) + { + std::cerr << "Could not uninitialize Audio Unit. " << result << std::endl; + } +} + +void AudioPlatform::start() +{ + OSStatus result = AudioOutputUnitStart(mIoUnit); + if (result) + { + std::cerr << "Could not start Audio Unit. " << result << std::endl; + std::terminate(); + } +} + +void AudioPlatform::stop() +{ + OSStatus result = AudioOutputUnitStop(mIoUnit); + if (result) + { + std::cerr << "Could not stop Audio Unit. " << result << std::endl; + } +} + +} // namespace linkaudio +} // namespace ableton diff --git a/tidal-link/link/examples/linkaudio/AudioPlatform_CoreAudio.hpp b/tidal-link/link/examples/linkaudio/AudioPlatform_CoreAudio.hpp new file mode 100644 index 000000000..7e2600fb3 --- /dev/null +++ b/tidal-link/link/examples/linkaudio/AudioPlatform_CoreAudio.hpp @@ -0,0 +1,54 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include "AudioEngine.hpp" +#include + +namespace ableton +{ +namespace linkaudio +{ + +class AudioPlatform +{ +public: + AudioPlatform(Link& link); + ~AudioPlatform(); + AudioEngine mEngine; + +private: + static OSStatus audioCallback(void* inRefCon, + AudioUnitRenderActionFlags*, + const AudioTimeStamp* inTimeStamp, + UInt32, + UInt32 inNumberFrames, + AudioBufferList* ioData); + + void initialize(); + void uninitialize(); + void start(); + void stop(); + + AudioUnit mIoUnit; +}; + +} // namespace linkaudio +} // namespace ableton diff --git a/tidal-link/link/examples/linkaudio/AudioPlatform_Dummy.hpp b/tidal-link/link/examples/linkaudio/AudioPlatform_Dummy.hpp new file mode 100644 index 000000000..b5ff745ca --- /dev/null +++ b/tidal-link/link/examples/linkaudio/AudioPlatform_Dummy.hpp @@ -0,0 +1,112 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include + +namespace ableton +{ +namespace linkaudio +{ + +class AudioPlatform +{ + class AudioEngine + { + public: + AudioEngine(Link& link) + : mLink(link) + , mQuantum(4.) + { + } + + void startPlaying() + { + auto sessionState = mLink.captureAppSessionState(); + sessionState.setIsPlayingAndRequestBeatAtTime(true, now(), 0., mQuantum); + mLink.commitAppSessionState(sessionState); + } + + void stopPlaying() + { + auto sessionState = mLink.captureAppSessionState(); + sessionState.setIsPlaying(false, now()); + mLink.commitAppSessionState(sessionState); + } + + bool isPlaying() const + { + return mLink.captureAppSessionState().isPlaying(); + } + + double beatTime() const + { + auto sessionState = mLink.captureAppSessionState(); + return sessionState.beatAtTime(now(), mQuantum); + } + + void setTempo(double tempo) + { + auto sessionState = mLink.captureAppSessionState(); + sessionState.setTempo(tempo, now()); + mLink.commitAppSessionState(sessionState); + } + + double quantum() const + { + return mQuantum; + } + + void setQuantum(double quantum) + { + mQuantum = quantum; + } + + bool isStartStopSyncEnabled() const + { + return mLink.isStartStopSyncEnabled(); + } + + void setStartStopSyncEnabled(bool enabled) + { + mLink.enableStartStopSync(enabled); + } + + private: + std::chrono::microseconds now() const + { + return mLink.clock().micros(); + } + + Link& mLink; + double mQuantum; + }; + +public: + AudioPlatform(Link& link) + : mEngine(link) + { + } + + AudioEngine mEngine; +}; + +} // namespace linkaudio +} // namespace ableton diff --git a/tidal-link/link/examples/linkaudio/AudioPlatform_Jack.cpp b/tidal-link/link/examples/linkaudio/AudioPlatform_Jack.cpp new file mode 100644 index 000000000..76a778d8a --- /dev/null +++ b/tidal-link/link/examples/linkaudio/AudioPlatform_Jack.cpp @@ -0,0 +1,188 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#include "AudioPlatform_Jack.hpp" +#include +#include +#include + +namespace ableton +{ +namespace linkaudio +{ + +AudioPlatform::AudioPlatform(Link& link) + : mEngine(link) + , mSampleTime(0.) + , mpJackClient(nullptr) + , mpJackPorts(nullptr) +{ + initialize(); + start(); +} + +AudioPlatform::~AudioPlatform() +{ + stop(); + uninitialize(); +} + +int AudioPlatform::audioCallback(jack_nframes_t nframes, void* pvUserData) +{ + AudioPlatform* pAudioPlatform = static_cast(pvUserData); + return pAudioPlatform->audioCallback(nframes); +} + +void AudioPlatform::latencyCallback(jack_latency_callback_mode_t, void* pvUserData) +{ + AudioPlatform* pAudioPlatform = static_cast(pvUserData); + pAudioPlatform->updateLatency(); +} + +void AudioPlatform::updateLatency() +{ + jack_latency_range_t latencyRange; + jack_port_get_latency_range(mpJackPorts[0], JackPlaybackLatency, &latencyRange); + mEngine.mOutputLatency.store( + std::chrono::microseconds(llround(1.0e6 * latencyRange.max / mEngine.mSampleRate))); +} + +int AudioPlatform::audioCallback(jack_nframes_t nframes) +{ + using namespace std::chrono; + AudioEngine& engine = mEngine; + + const auto hostTime = mHostTimeFilter.sampleTimeToHostTime(mSampleTime); + + mSampleTime += nframes; + + const auto bufferBeginAtOutput = hostTime + engine.mOutputLatency.load(); + + engine.audioCallback(bufferBeginAtOutput, nframes); + + for (int k = 0; k < 2; ++k) + { + float* buffer = static_cast(jack_port_get_buffer(mpJackPorts[k], nframes)); + for (unsigned long i = 0; i < nframes; ++i) + buffer[i] = static_cast(engine.mBuffer[i]); + } + + return 0; +} + +void AudioPlatform::initialize() +{ + jack_status_t status = JackFailure; + mpJackClient = jack_client_open("LinkHut", JackNullOption, &status); + if (mpJackClient == nullptr) + { + std::cerr << "Could not initialize Audio Engine. "; + std::cerr << "JACK: " << std::endl; + if (status & JackFailure) + std::cerr << "Overall operation failed." << std::endl; + if (status & JackInvalidOption) + std::cerr << "Invalid or unsupported option." << std::endl; + if (status & JackNameNotUnique) + std::cerr << "Client name not unique." << std::endl; + if (status & JackServerStarted) + std::cerr << "Server is started." << std::endl; + if (status & JackServerFailed) + std::cerr << "Unable to connect to server." << std::endl; + if (status & JackServerError) + std::cerr << "Server communication error." << std::endl; + if (status & JackNoSuchClient) + std::cerr << "Client does not exist." << std::endl; + if (status & JackLoadFailure) + std::cerr << "Unable to load internal client." << std::endl; + if (status & JackInitFailure) + std::cerr << "Unable to initialize client." << std::endl; + if (status & JackShmFailure) + std::cerr << "Unable to access shared memory." << std::endl; + if (status & JackVersionError) + std::cerr << "Client protocol version mismatch." << std::endl; + std::cerr << std::endl; + std::terminate(); + } + + const double bufferSize = jack_get_buffer_size(mpJackClient); + const double sampleRate = jack_get_sample_rate(mpJackClient); + mEngine.setBufferSize(static_cast(bufferSize)); + mEngine.setSampleRate(sampleRate); + + jack_set_latency_callback(mpJackClient, AudioPlatform::latencyCallback, this); + + mpJackPorts = new jack_port_t*[2]; + + for (int k = 0; k < 2; ++k) + { + const std::string port_name = "out_" + std::to_string(k + 1); + mpJackPorts[k] = jack_port_register( + mpJackClient, port_name.c_str(), JACK_DEFAULT_AUDIO_TYPE, JackPortIsOutput, 0); + if (mpJackPorts[k] == nullptr) + { + std::cerr << "Could not get Audio Device. " << std::endl; + jack_client_close(mpJackClient); + std::terminate(); + } + } + + jack_set_process_callback(mpJackClient, AudioPlatform::audioCallback, this); +} + +void AudioPlatform::uninitialize() +{ + for (int k = 0; k < 2; ++k) + { + jack_port_unregister(mpJackClient, mpJackPorts[k]); + mpJackPorts[k] = nullptr; + } + delete[] mpJackPorts; + mpJackPorts = nullptr; + + jack_client_close(mpJackClient); + mpJackClient = nullptr; +} + +void AudioPlatform::start() +{ + jack_activate(mpJackClient); + + const char** playback_ports = jack_get_ports( + mpJackClient, nullptr, JACK_DEFAULT_AUDIO_TYPE, JackPortIsInput | JackPortIsPhysical); + + if (playback_ports) + { + const std::string client_name = jack_get_client_name(mpJackClient); + for (int k = 0; k < 2; ++k) + { + const std::string port_name = "out_" + std::to_string(k + 1); + const std::string client_port = client_name + ':' + port_name; + jack_connect(mpJackClient, client_port.c_str(), playback_ports[k]); + } + jack_free(playback_ports); + } +} + +void AudioPlatform::stop() +{ + jack_deactivate(mpJackClient); +} + +} // namespace linkaudio +} // namespace ableton diff --git a/tidal-link/link/examples/linkaudio/AudioPlatform_Jack.hpp b/tidal-link/link/examples/linkaudio/AudioPlatform_Jack.hpp new file mode 100644 index 000000000..0b7999c37 --- /dev/null +++ b/tidal-link/link/examples/linkaudio/AudioPlatform_Jack.hpp @@ -0,0 +1,58 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include "AudioEngine.hpp" +#include +#include +#include + +namespace ableton +{ +namespace linkaudio +{ + +class AudioPlatform +{ +public: + AudioPlatform(Link& link); + ~AudioPlatform(); + + AudioEngine mEngine; + +private: + static int audioCallback(jack_nframes_t nframes, void* pvUserData); + int audioCallback(jack_nframes_t nframes); + static void latencyCallback(jack_latency_callback_mode_t mode, void* pvUserData); + void updateLatency(); + + void initialize(); + void uninitialize(); + void start(); + void stop(); + + link::HostTimeFilter mHostTimeFilter; + double mSampleTime; + jack_client_t* mpJackClient; + jack_port_t** mpJackPorts; +}; + +} // namespace linkaudio +} // namespace ableton diff --git a/tidal-link/link/examples/linkaudio/AudioPlatform_Portaudio.cpp b/tidal-link/link/examples/linkaudio/AudioPlatform_Portaudio.cpp new file mode 100644 index 000000000..c35f1008f --- /dev/null +++ b/tidal-link/link/examples/linkaudio/AudioPlatform_Portaudio.cpp @@ -0,0 +1,156 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#include "AudioPlatform_Portaudio.hpp" +#include +#include + +namespace ableton +{ +namespace linkaudio +{ + +AudioPlatform::AudioPlatform(Link& link) + : mEngine(link) + , mSampleTime(0.) +{ + mEngine.setSampleRate(44100.); + mEngine.setBufferSize(512); + initialize(); + start(); +} + +AudioPlatform::~AudioPlatform() +{ + stop(); + uninitialize(); +} + +int AudioPlatform::audioCallback(const void* /*inputBuffer*/, + void* outputBuffer, + unsigned long inNumFrames, + const PaStreamCallbackTimeInfo* /*timeInfo*/, + PaStreamCallbackFlags /*statusFlags*/, + void* userData) +{ + using namespace std::chrono; + float* buffer = static_cast(outputBuffer); + AudioPlatform& platform = *static_cast(userData); + AudioEngine& engine = platform.mEngine; + + const auto hostTime = + platform.mHostTimeFilter.sampleTimeToHostTime(platform.mSampleTime); + + platform.mSampleTime += static_cast(inNumFrames); + + const auto bufferBeginAtOutput = hostTime + engine.mOutputLatency.load(); + + engine.audioCallback(bufferBeginAtOutput, inNumFrames); + + for (unsigned long i = 0; i < inNumFrames; ++i) + { + buffer[i * 2] = static_cast(engine.mBuffer[i]); + buffer[i * 2 + 1] = static_cast(engine.mBuffer[i]); + } + + return paContinue; +} + +void AudioPlatform::initialize() +{ + PaError result = Pa_Initialize(); + if (result) + { + std::cerr << "Could not initialize Audio Engine. " << result << std::endl; + std::terminate(); + } + + PaStreamParameters outputParameters; + outputParameters.device = Pa_GetDefaultOutputDevice(); + if (outputParameters.device == paNoDevice) + { + std::cerr << "Could not get Audio Device. " << std::endl; + std::terminate(); + } + + outputParameters.channelCount = 2; + outputParameters.sampleFormat = paFloat32; + outputParameters.suggestedLatency = + Pa_GetDeviceInfo(outputParameters.device)->defaultLowOutputLatency; + outputParameters.hostApiSpecificStreamInfo = nullptr; + mEngine.mOutputLatency.store( + std::chrono::microseconds(llround(outputParameters.suggestedLatency * 1.0e6))); + result = Pa_OpenStream(&pStream, nullptr, &outputParameters, mEngine.mSampleRate, + mEngine.mBuffer.size(), paClipOff, &audioCallback, this); + + if (result) + { + std::cerr << "Could not open stream. " << result << std::endl; + std::terminate(); + } + + if (!pStream) + { + std::cerr << "No valid audio stream." << std::endl; + std::terminate(); + } +} + +void AudioPlatform::uninitialize() +{ + PaError result = Pa_CloseStream(pStream); + if (result) + { + std::cerr << "Could not close Audio Stream. " << result << std::endl; + } + Pa_Terminate(); + + if (!pStream) + { + std::cerr << "No valid audio stream." << std::endl; + std::terminate(); + } +} + +void AudioPlatform::start() +{ + PaError result = Pa_StartStream(pStream); + if (result) + { + std::cerr << "Could not start Audio Stream. " << result << std::endl; + } +} + +void AudioPlatform::stop() +{ + if (pStream == nullptr) + { + return; + } + + PaError result = Pa_StopStream(pStream); + if (result) + { + std::cerr << "Could not stop Audio Stream. " << result << std::endl; + std::terminate(); + } +} + +} // namespace linkaudio +} // namespace ableton diff --git a/tidal-link/link/examples/linkaudio/AudioPlatform_Portaudio.hpp b/tidal-link/link/examples/linkaudio/AudioPlatform_Portaudio.hpp new file mode 100644 index 000000000..032d14793 --- /dev/null +++ b/tidal-link/link/examples/linkaudio/AudioPlatform_Portaudio.hpp @@ -0,0 +1,59 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include "AudioEngine.hpp" +#include +#include +#include + +namespace ableton +{ +namespace linkaudio +{ + +class AudioPlatform +{ +public: + AudioPlatform(Link& link); + ~AudioPlatform(); + + AudioEngine mEngine; + +private: + static int audioCallback(const void* inputBuffer, + void* outputBuffer, + unsigned long inNumFrames, + const PaStreamCallbackTimeInfo* timeInfo, + PaStreamCallbackFlags statusFlags, + void* userData); + + void initialize(); + void uninitialize(); + void start(); + void stop(); + + link::HostTimeFilter mHostTimeFilter; + double mSampleTime; + PaStream* pStream; +}; + +} // namespace linkaudio +} // namespace ableton diff --git a/tidal-link/link/examples/linkaudio/AudioPlatform_Wasapi.cpp b/tidal-link/link/examples/linkaudio/AudioPlatform_Wasapi.cpp new file mode 100644 index 000000000..efb73f8bd --- /dev/null +++ b/tidal-link/link/examples/linkaudio/AudioPlatform_Wasapi.cpp @@ -0,0 +1,331 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#include "AudioPlatform_Wasapi.hpp" +#include +#include + +// WARNING: This file provides an audio driver for Windows using WASAPI. This driver is +// considered experimental and has problems with low-latency playback. Please consider +// using the ASIO driver instead. + +namespace ableton +{ +namespace linkaudio +{ + +// GUID identifiers used to when looking up COM enumerators and devices +static const IID kMMDeviceEnumeratorId = __uuidof(MMDeviceEnumerator); +static const IID kIMMDeviceEnumeratorId = __uuidof(IMMDeviceEnumerator); +static const IID kAudioClientId = __uuidof(IAudioClient); +static const IID kAudioRenderClientId = __uuidof(IAudioRenderClient); + +// Controls how large the driver's ring buffer will be, expressed in terms of +// 100-nanosecond units. This value also influences the overall driver latency. +static const REFERENCE_TIME kBufferDuration = 1000000; + +// How long to block the runloop while waiting for an event callback. +static const DWORD kWaitTimeoutInMs = 2000; + +void fatalError(HRESULT result, LPCTSTR context) +{ + if (result > 0) + { + _com_error error(result); + LPCTSTR errorMessage = error.ErrorMessage(); + std::cerr << context << ": " << errorMessage << std::endl; + } + else + { + std::cerr << context << std::endl; + } + + std::terminate(); +} + +DWORD renderAudioRunloop(LPVOID lpParam) +{ + AudioPlatform* platform = static_cast(lpParam); + return platform->audioRunloop(); +} + +AudioPlatform::AudioPlatform(Link& link) + : mEngine(link) + , mSampleTime(0) + , mDevice(nullptr) + , mAudioClient(nullptr) + , mRenderClient(nullptr) + , mStreamFormat(nullptr) + , mEventHandle(nullptr) + , mAudioThreadHandle(nullptr) + , mIsRunning(false) +{ + initialize(); + mEngine.setBufferSize(bufferSize()); + mEngine.setSampleRate(mStreamFormat->nSamplesPerSec); + start(); +} + +AudioPlatform::~AudioPlatform() +{ + // WARNING: Here be dragons! + // The WASAPI driver is not thread-safe, and crashes may occur when shutting down due + // to these fields being concurrently accessed in the audio thread. Introducing a mutex + // in the audio thread is not an appropriate solution to fix this race condition; a more + // robust solution needs to be considered instead. + + if (mDevice != nullptr) + { + mDevice->Release(); + } + if (mAudioClient != nullptr) + { + mAudioClient->Release(); + } + if (mRenderClient != nullptr) + { + mRenderClient->Release(); + } + CoTaskMemFree(mStreamFormat); +} + +UINT32 AudioPlatform::bufferSize() +{ + UINT32 bufferSize; + HRESULT result = mAudioClient->GetBufferSize(&bufferSize); + if (FAILED(result)) + { + fatalError(result, "Could not get buffer size"); + return 0; // not reached + } + + return bufferSize; +} + +void AudioPlatform::initialize() +{ + HRESULT result = CoInitialize(nullptr); + if (FAILED(result)) + { + fatalError(result, "Could not initialize COM library"); + } + + IMMDeviceEnumerator* enumerator = nullptr; + result = CoCreateInstance(kMMDeviceEnumeratorId, nullptr, CLSCTX_ALL, + kIMMDeviceEnumeratorId, (void**)&enumerator); + if (FAILED(result)) + { + fatalError(result, "Could not create device instance"); + } + + result = enumerator->GetDefaultAudioEndpoint(eRender, eConsole, &(mDevice)); + if (FAILED(result)) + { + fatalError(result, "Could not get default audio endpoint"); + } + else + { + enumerator->Release(); + enumerator = nullptr; + } + + result = + mDevice->Activate(kAudioClientId, CLSCTX_ALL, nullptr, (void**)&(mAudioClient)); + if (FAILED(result)) + { + fatalError(result, "Could not activate audio device"); + } + + result = mAudioClient->GetMixFormat(&(mStreamFormat)); + if (FAILED(result)) + { + fatalError(result, "Could not get mix format"); + } + + if (mStreamFormat->wFormatTag == WAVE_FORMAT_EXTENSIBLE) + { + WAVEFORMATEXTENSIBLE* streamFormatEx = + reinterpret_cast(mStreamFormat); + if (streamFormatEx->SubFormat != KSDATAFORMAT_SUBTYPE_IEEE_FLOAT) + { + fatalError(0, "Sorry, only IEEE floating point streams are supported"); + } + } + else + { + fatalError(0, "Sorry, only extensible wave streams are supported"); + } + + result = mAudioClient->Initialize(AUDCLNT_SHAREMODE_SHARED, + AUDCLNT_STREAMFLAGS_EVENTCALLBACK, kBufferDuration, 0, mStreamFormat, nullptr); + if (FAILED(result)) + { + fatalError(result, "Could not initialize audio device"); + } + + mEventHandle = CreateEvent(nullptr, false, false, nullptr); + if (mEventHandle == nullptr) + { + fatalError(result, "Could not create event handle"); + } + + result = mAudioClient->GetService(kAudioRenderClientId, (void**)&(mRenderClient)); + if (FAILED(result)) + { + fatalError(result, "Could not get audio render service"); + } + + mIsRunning = true; + LPTHREAD_START_ROUTINE threadEntryPoint = + reinterpret_cast(renderAudioRunloop); + mAudioThreadHandle = CreateThread(nullptr, 0, threadEntryPoint, this, 0, nullptr); + if (mAudioThreadHandle == nullptr) + { + fatalError(GetLastError(), "Could not create audio thread"); + } +} + +void AudioPlatform::start() +{ + UINT32 bufSize = bufferSize(); + BYTE* buffer; + HRESULT result = mRenderClient->GetBuffer(bufSize, &buffer); + if (FAILED(result)) + { + fatalError(result, "Could not get render client buffer (in start audio engine)"); + } + + result = mRenderClient->ReleaseBuffer(bufSize, 0); + if (FAILED(result)) + { + fatalError(result, "Could not release buffer"); + } + + result = mAudioClient->SetEventHandle(mEventHandle); + if (FAILED(result)) + { + fatalError(result, "Could not set event handle to audio client"); + } + + REFERENCE_TIME latency; + result = mAudioClient->GetStreamLatency(&latency); + if (FAILED(result)) + { + fatalError(result, "Could not get stream latency"); + } + + result = mAudioClient->Start(); + if (FAILED(result)) + { + fatalError(result, "Could not start audio client"); + } +} + +DWORD AudioPlatform::audioRunloop() +{ + while (mIsRunning) + { + DWORD wait = WaitForSingleObject(mEventHandle, kWaitTimeoutInMs); + if (wait != WAIT_OBJECT_0) + { + mIsRunning = false; + mAudioClient->Stop(); + return wait; + } + + // Get the amount of padding, which basically is the amount of data in the driver's + // ring buffer that is filled with unread data. Thus, subtracting this amount from + // the buffer size gives the effective buffer size, which is the amount of frames + // that can be safely written to the driver. + UINT32 paddingFrames; + HRESULT result = mAudioClient->GetCurrentPadding(&paddingFrames); + if (FAILED(result)) + { + fatalError(result, "Could not get number of padding frames"); + } + + const UINT32 numSamples = bufferSize() - paddingFrames; + + BYTE* buffer; + result = mRenderClient->GetBuffer(numSamples, &buffer); + if (FAILED(result)) + { + fatalError(result, "Could not get render client buffer (in callback)"); + } + + const double sampleRate = static_cast(mStreamFormat->nSamplesPerSec); + using namespace std::chrono; + const auto bufferDuration = + duration_cast(duration{numSamples / sampleRate}); + + const auto hostTime = mHostTimeFilter.sampleTimeToHostTime(mSampleTime); + + mSampleTime += numSamples; + + const auto bufferBeginAtOutput = hostTime + mEngine.mOutputLatency.load(); + + mEngine.audioCallback(bufferBeginAtOutput, numSamples); + + float* floatBuffer = reinterpret_cast(buffer); + for (WORD i = 0; i < numSamples; ++i) + { + if (i >= mEngine.mBuffer.size()) + { + break; + } + for (WORD j = 0; j < mStreamFormat->nChannels; ++j) + { + floatBuffer[j + (i * mStreamFormat->nChannels)] = + static_cast(mEngine.mBuffer[i]); + } + } + + // Write the buffer to the audio driver and subsequently free the buffer memory + result = mRenderClient->ReleaseBuffer(numSamples, 0); + if (FAILED(result)) + { + fatalError(result, "Error rendering data"); + } + } // end of runloop + + mIsRunning = false; + return 0; +} + + +// void fillBuffer(MetronomeSynth& metronome, +// const UINT32 startFrame, +// const UINT32 numSamples, +// const UINT32 numChannels, +// BYTE* buffer) +//{ +// float* floatBuffer = reinterpret_cast(buffer); +// UINT32 frame = startFrame; +// while (frame < numSamples * numChannels) +// { +// const float sample = static_cast(metronome.getSample()); +// for (UINT32 channel = 0; channel < numChannels; ++channel) +// { +// floatBuffer[frame++] = sample; +// } +// } +//} + +} // namespace linkaudio +} // namespace ableton diff --git a/tidal-link/link/examples/linkaudio/AudioPlatform_Wasapi.hpp b/tidal-link/link/examples/linkaudio/AudioPlatform_Wasapi.hpp new file mode 100644 index 000000000..9fa61be94 --- /dev/null +++ b/tidal-link/link/examples/linkaudio/AudioPlatform_Wasapi.hpp @@ -0,0 +1,72 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include "AudioEngine.hpp" +#include +#include +#include +#include + +// WARNING: This file provides an audio driver for Windows using WASAPI. This driver is +// considered experimental and has problems with low-latency playback. Please consider +// using the ASIO driver instead. + +namespace ableton +{ +namespace linkaudio +{ + +// Convenience function to look up the human-readable WinAPI error code, print it out, +// and then terminate the application. +void fatalError(HRESULT result, LPCTSTR context); + +DWORD renderAudioRunloop(LPVOID); + +class AudioPlatform +{ +public: + AudioPlatform(Link& link); + ~AudioPlatform(); + + DWORD audioRunloop(); + + AudioEngine mEngine; + +private: + UINT32 bufferSize(); + + void initialize(); + void start(); + + link::HostTimeFilter mHostTimeFilter; + double mSampleTime; + + IMMDevice* mDevice; + IAudioClient* mAudioClient; + IAudioRenderClient* mRenderClient; + WAVEFORMATEX* mStreamFormat; + HANDLE mEventHandle; + HANDLE mAudioThreadHandle; + std::atomic mIsRunning; +}; + +} // namespace linkaudio +} // namespace ableton diff --git a/tidal-link/link/examples/linkhut/main.cpp b/tidal-link/link/examples/linkhut/main.cpp new file mode 100644 index 000000000..92cb504b6 --- /dev/null +++ b/tidal-link/link/examples/linkhut/main.cpp @@ -0,0 +1,208 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#include "AudioPlatform.hpp" + +#include +#include +#include +#include +#include +#include +#if defined(LINK_PLATFORM_UNIX) +#include +#endif + +namespace +{ + +struct State +{ + std::atomic running; + ableton::Link link; + ableton::linkaudio::AudioPlatform audioPlatform; + + State() + : running(true) + , link(120.) + , audioPlatform(link) + { + } +}; + +void disableBufferedInput() +{ +#if defined(LINK_PLATFORM_UNIX) + termios t; + tcgetattr(STDIN_FILENO, &t); + t.c_lflag &= static_cast(~ICANON); + tcsetattr(STDIN_FILENO, TCSANOW, &t); +#endif +} + +void enableBufferedInput() +{ +#if defined(LINK_PLATFORM_UNIX) + termios t; + tcgetattr(STDIN_FILENO, &t); + t.c_lflag |= ICANON; + tcsetattr(STDIN_FILENO, TCSANOW, &t); +#endif +} + +void clearLine() +{ + std::cout << " \r" << std::flush; + std::cout.fill(' '); +} + +void printHelp() +{ + std::cout << std::endl << " < L I N K H U T >" << std::endl << std::endl; + std::cout << "usage:" << std::endl; + std::cout << " enable / disable Link: a" << std::endl; + std::cout << " start / stop: space" << std::endl; + std::cout << " decrease / increase tempo: w / e" << std::endl; + std::cout << " decrease / increase quantum: r / t" << std::endl; + std::cout << " enable / disable start stop sync: s" << std::endl; + std::cout << " quit: q" << std::endl << std::endl; +} + +void printStateHeader() +{ + std::cout + << "enabled | num peers | quantum | start stop sync | tempo | beats | metro" + << std::endl; +} + +void printState(const std::chrono::microseconds time, + const ableton::Link::SessionState sessionState, + const bool linkEnabled, + const std::size_t numPeers, + const double quantum, + const bool startStopSyncOn) +{ + using namespace std; + const auto enabled = linkEnabled ? "yes" : "no"; + const auto beats = sessionState.beatAtTime(time, quantum); + const auto phase = sessionState.phaseAtTime(time, quantum); + const auto startStop = startStopSyncOn ? "yes" : "no"; + const auto isPlaying = sessionState.isPlaying() ? "[playing]" : "[stopped]"; + cout << defaultfloat << left << setw(7) << enabled << " | " << setw(9) << numPeers + << " | " << setw(7) << quantum << " | " << setw(3) << startStop << " " << setw(11) + << isPlaying << " | " << fixed << setw(7) << sessionState.tempo() << " | " << fixed + << setprecision(2) << setw(7) << beats << " | "; + for (int i = 0; i < ceil(quantum); ++i) + { + if (i < phase) + { + std::cout << 'X'; + } + else + { + std::cout << 'O'; + } + } + clearLine(); +} + +void input(State& state) +{ + char in; + + for (;;) + { +#if defined(LINK_PLATFORM_WINDOWS) + HANDLE stdinHandle = GetStdHandle(STD_INPUT_HANDLE); + DWORD numCharsRead; + INPUT_RECORD inputRecord; + do + { + ReadConsoleInput(stdinHandle, &inputRecord, 1, &numCharsRead); + } while ((inputRecord.EventType != KEY_EVENT) || inputRecord.Event.KeyEvent.bKeyDown); + in = inputRecord.Event.KeyEvent.uChar.AsciiChar; +#elif defined(LINK_PLATFORM_UNIX) + in = static_cast(std::cin.get()); +#endif + + const auto tempo = state.link.captureAppSessionState().tempo(); + auto& engine = state.audioPlatform.mEngine; + + switch (in) + { + case 'q': + state.running = false; + clearLine(); + return; + case 'a': + state.link.enable(!state.link.isEnabled()); + break; + case 'w': + engine.setTempo(tempo - 1); + break; + case 'e': + engine.setTempo(tempo + 1); + break; + case 'r': + engine.setQuantum(engine.quantum() - 1); + break; + case 't': + engine.setQuantum(std::max(1., engine.quantum() + 1)); + break; + case 's': + engine.setStartStopSyncEnabled(!engine.isStartStopSyncEnabled()); + break; + case ' ': + if (engine.isPlaying()) + { + engine.stopPlaying(); + } + else + { + engine.startPlaying(); + } + break; + } + } +} + +} // namespace + +int main(int, char**) +{ + State state; + printHelp(); + printStateHeader(); + std::thread thread(input, std::ref(state)); + disableBufferedInput(); + + while (state.running) + { + const auto time = state.link.clock().micros(); + auto sessionState = state.link.captureAppSessionState(); + printState(time, sessionState, state.link.isEnabled(), state.link.numPeers(), + state.audioPlatform.mEngine.quantum(), + state.audioPlatform.mEngine.isStartStopSyncEnabled()); + std::this_thread::sleep_for(std::chrono::milliseconds(10)); + } + + enableBufferedInput(); + thread.join(); + return 0; +} diff --git a/tidal-link/link/extensions/abl_link/.clang-format b/tidal-link/link/extensions/abl_link/.clang-format new file mode 100644 index 000000000..8fb4cfc56 --- /dev/null +++ b/tidal-link/link/extensions/abl_link/.clang-format @@ -0,0 +1,44 @@ +AccessModifierOffset: -2 +AlignAfterOpenBracket: DontAlign +AlignEscapedNewlinesLeft: false +AlignOperands: true +AlignTrailingComments: true +AllowAllParametersOfDeclarationOnNextLine: true +AllowShortBlocksOnASingleLine: false +AllowShortCaseLabelsOnASingleLine: false +AllowShortFunctionsOnASingleLine: None +AllowShortIfStatementsOnASingleLine: false +AllowShortLoopsOnASingleLine: false +AlwaysBreakAfterDefinitionReturnType: None +AlwaysBreakAfterReturnType: None +AlwaysBreakBeforeMultilineStrings: true +AlwaysBreakTemplateDeclarations: true +BinPackArguments: true +BinPackParameters: false +BreakBeforeBinaryOperators: NonAssignment +BreakBeforeBraces: Allman +BreakBeforeTernaryOperators: true +ColumnLimit: 90 +ConstructorInitializerAllOnOneLineOrOnePerLine: false +ConstructorInitializerIndentWidth: 2 +ContinuationIndentWidth: 2 +DerivePointerAlignment: false +IndentCaseLabels: false +IndentFunctionDeclarationAfterType: false +IndentWidth: 2 +IndentWrappedFunctionNames: false +KeepEmptyLinesAtTheStartOfBlocks: true +MaxEmptyLinesToKeep: 2 +PenaltyBreakBeforeFirstCallParameter: 0 +PenaltyReturnTypeOnItsOwnLine: 1000 +PointerAlignment: Right +SpaceAfterCStyleCast: false +SpaceBeforeAssignmentOperators: true +SpaceBeforeParens: ControlStatements +SpaceInEmptyParentheses: false +SpacesBeforeTrailingComments: 1 +SpacesInAngles: false +SpacesInCStyleCastParentheses: false +SpacesInParentheses: false +SpacesInSquareBrackets: false +UseTab: Never diff --git a/tidal-link/link/extensions/abl_link/CMakeLists.txt b/tidal-link/link/extensions/abl_link/CMakeLists.txt new file mode 100644 index 000000000..bccb5971d --- /dev/null +++ b/tidal-link/link/extensions/abl_link/CMakeLists.txt @@ -0,0 +1,19 @@ +# _ _ _ _ _ +# | (_)_ __ | | __ | |__ _ _| |_ +# | | | '_ \| |/ / | '_ \| | | | __| +# | | | | | | < | | | | |_| | |_ +# |_|_|_| |_|_|\_\___|_| |_|\__,_|\__| +# |_____| + +set(link_hut_SOURCES + ${CMAKE_CURRENT_LIST_DIR}/examples/link_hut/main.c +) + +source_group("link_hut" FILES ${link_hut_SOURCES}) + +add_executable(link_hut ${link_hut_SOURCES}) + +set_property(TARGET link_hut PROPERTY C_STANDARD 11) + +target_link_libraries(link_hut abl_link) + diff --git a/tidal-link/link/extensions/abl_link/README.md b/tidal-link/link/extensions/abl_link/README.md new file mode 100644 index 000000000..70f60a267 --- /dev/null +++ b/tidal-link/link/extensions/abl_link/README.md @@ -0,0 +1,17 @@ +# abl_link + +Plain C 11 wrapper for Ableton Link. + +# Building and Running abl_link Examples + +The `abl_link` library and the `link_hut` example application are built as part of the main CMake project in this repository. + +# Integrating abl_link into CMake-based Projects + +If you are using CMake, you can integrate `abl_link` by including both, the `Ableton::Link` and the `abl_link` configs: + +```cmake +include($PATH_TO_LINK/AbletonLinkConfig.cmake) +include($PATH_TO_LINK/extensions/abl_link/abl_link.cmake) +target_link_libraries($YOUR_TARGET abl_link) +``` diff --git a/tidal-link/link/extensions/abl_link/abl_link.cmake b/tidal-link/link/extensions/abl_link/abl_link.cmake new file mode 100644 index 000000000..00efd1ee2 --- /dev/null +++ b/tidal-link/link/extensions/abl_link/abl_link.cmake @@ -0,0 +1,19 @@ +if(CMAKE_VERSION VERSION_LESS 3.0) + message(FATAL_ERROR "CMake 3.0 or greater is required") +endif() + +add_library(abl_link STATIC + ${CMAKE_CURRENT_LIST_DIR}/src/abl_link.cpp +) + +target_include_directories(abl_link PUBLIC + ${CMAKE_CURRENT_LIST_DIR}/include +) + +set_property(TARGET abl_link PROPERTY C_STANDARD 11) + +target_link_libraries(abl_link Ableton::Link) + +if(CMAKE_SYSTEM_NAME MATCHES "Linux|kFreeBSD|GNU") + target_link_libraries(abl_link atomic pthread) +endif() diff --git a/tidal-link/link/extensions/abl_link/examples/link_hut/main.c b/tidal-link/link/extensions/abl_link/examples/link_hut/main.c new file mode 100644 index 000000000..df7d9d810 --- /dev/null +++ b/tidal-link/link/extensions/abl_link/examples/link_hut/main.c @@ -0,0 +1,269 @@ +/* Copyright 2021, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#include +#include +#include +#include +#include +#if defined(LINK_PLATFORM_UNIX) +#include +#include +#include +#elif defined(LINK_PLATFORM_WINDOWS) +#pragma warning(push, 0) +#pragma warning(disable : 4255) // 'no function prototype given' in winuser.h +#pragma warning(disable : 4668) // undefined preprocessor macro in winioctl.h +#pragma warning(disable : 5105) // "/wd5105" # "macro expansion producing 'defined' has + // undefined behavior" in winbase.h +#include +#pragma warning(pop) +#pragma warning(disable : 4100) // unreferenced formal parameter in main +#endif + +#include + +typedef struct state +{ + abl_link link; + abl_link_session_state session_state; + bool running; + double quantum; +} state; + +struct state *new_state(void) +{ + struct state *s = malloc(sizeof(state)); + s->link = abl_link_create(120); + s->session_state = abl_link_create_session_state(); + s->running = true; + s->quantum = 4; + return s; +} + +void delete_state(state *state) +{ + abl_link_destroy_session_state(state->session_state); + abl_link_destroy(state->link); + free(state); +} + +void disable_buffered_input(void) +{ +#if defined(LINK_PLATFORM_UNIX) + struct termios t; + tcgetattr(STDIN_FILENO, &t); + t.c_lflag &= ~ICANON; + tcsetattr(STDIN_FILENO, TCSANOW, &t); +#endif +} + +void enable_buffered_input(void) +{ +#if defined(LINK_PLATFORM_UNIX) + struct termios t; + tcgetattr(STDIN_FILENO, &t); + t.c_lflag |= ICANON; + tcsetattr(STDIN_FILENO, TCSANOW, &t); +#endif +} + +bool wait_for_input(void) +{ +#if defined(LINK_PLATFORM_UNIX) + fd_set selectset; + struct timeval timeout = {0, 50000}; + int ret; + FD_ZERO(&selectset); + FD_SET(0, &selectset); + ret = select(1, &selectset, NULL, NULL, &timeout); + if (ret > 0) + { + return true; + } +#elif (LINK_PLATFORM_WINDOWS) + HANDLE handle = GetStdHandle(STD_INPUT_HANDLE); + if (WaitForSingleObject(handle, 50) == WAIT_OBJECT_0) + { + return true; + } +#else +#error "Missing implementation" +#endif + return false; +} + +void clear_line(void) +{ + printf(" \r"); + fflush(stdout); +} + +void clear_input(void) +{ +#if defined(LINK_PLATFORM_WINDOWS) + { + HANDLE handle = GetStdHandle(STD_INPUT_HANDLE); + INPUT_RECORD r[512]; + DWORD read; + ReadConsoleInput(handle, r, 512, &read); + } +#endif +} + +void print_help(void) +{ + printf("\n\n < L I N K H U T >\n\n"); + printf("usage:\n"); + printf(" enable / disable Link: a\n"); + printf(" start / stop: space\n"); + printf(" decrease / increase tempo: w / e\n"); + printf(" decrease / increase quantum: r / t\n"); + printf(" enable / disable start stop sync: s\n"); + printf(" quit: q\n"); +} + +void print_state_header(void) +{ + printf( + "\nenabled | num peers | quantum | start stop sync | tempo | beats | metro\n"); +} + +void print_state(state *state) +{ + abl_link_capture_app_session_state(state->link, state->session_state); + const uint64_t time = abl_link_clock_micros(state->link); + const char *enabled = abl_link_is_enabled(state->link) ? "yes" : "no"; + const uint64_t num_peers = abl_link_num_peers(state->link); + const char *start_stop = + abl_link_is_start_stop_sync_enabled(state->link) ? "yes" : " no"; + const char *playing = + abl_link_is_playing(state->session_state) ? "[playing]" : "[stopped]"; + const double tempo = abl_link_tempo(state->session_state); + const double beats = abl_link_beat_at_time(state->session_state, time, state->quantum); + const double phase = abl_link_phase_at_time(state->session_state, time, state->quantum); + printf("%7s | ", enabled); + printf("%9" PRIu64 " | ", num_peers); + printf("%7.f | ", state->quantum); + printf("%3s %11s | ", start_stop, playing); + printf("%7.2f | ", tempo); + printf("%7.2f | ", beats); + for (int i = 0; i < ceil(state->quantum); ++i) + { + if (i < phase) + { + printf("X"); + } + else + { + printf("O"); + } + } +} + +void input(state *state) +{ + char in; + +#if defined(LINK_PLATFORM_UNIX) + in = (char)fgetc(stdin); +#elif defined(LINK_PLATFORM_WINDOWS) + HANDLE stdinHandle = GetStdHandle(STD_INPUT_HANDLE); + DWORD numCharsRead; + INPUT_RECORD inputRecord; + do + { + ReadConsoleInput(stdinHandle, &inputRecord, 1, &numCharsRead); + } while ((inputRecord.EventType != KEY_EVENT) || inputRecord.Event.KeyEvent.bKeyDown); + in = inputRecord.Event.KeyEvent.uChar.AsciiChar; +#else +#error "Missing implementation" +#endif + + abl_link_capture_app_session_state(state->link, state->session_state); + const double tempo = abl_link_tempo(state->session_state); + const uint64_t timestamp = abl_link_clock_micros(state->link); + const bool enabled = abl_link_is_enabled(state->link); + switch (in) + { + case 'q': + state->running = false; + clear_line(); + return; + case 'a': + abl_link_enable(state->link, !enabled); + break; + case 'w': + abl_link_set_tempo(state->session_state, tempo - 1, timestamp); + break; + case 'e': + abl_link_set_tempo(state->session_state, tempo + 1, timestamp); + break; + case 'r': + state->quantum -= 1; + break; + case 't': + state->quantum += 1; + break; + case 's': + abl_link_enable_start_stop_sync( + state->link, !abl_link_is_start_stop_sync_enabled(state->link)); + break; + case ' ': + if (abl_link_is_playing(state->session_state)) + { + abl_link_set_is_playing( + state->session_state, false, abl_link_clock_micros(state->link)); + } + else + { + abl_link_set_is_playing_and_request_beat_at_time(state->session_state, true, + abl_link_clock_micros(state->link), 0, state->quantum); + } + break; + } + abl_link_commit_app_session_state(state->link, state->session_state); +} + +int main(int nargs, char **args) +{ + state *state = new_state(); + + print_help(); + print_state_header(); + disable_buffered_input(); + clear_input(); + + while (state->running) + { + clear_line(); + if (wait_for_input()) + { + input(state); + } + else + { + print_state(state); + } + } + + enable_buffered_input(); + delete_state(state); + return 0; +} diff --git a/tidal-link/link/extensions/abl_link/include/abl_link.h b/tidal-link/link/extensions/abl_link/include/abl_link.h new file mode 100644 index 000000000..34ac71b0f --- /dev/null +++ b/tidal-link/link/extensions/abl_link/include/abl_link.h @@ -0,0 +1,352 @@ +/* Copyright 2021, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#include +#include + +#ifdef __cplusplus +extern "C" +{ +#endif // __cplusplus + + /*! + * @discussion Each abl_link instance has its own session state which + * represents a beat timeline and a transport start/stop state. The + * timeline starts running from beat 0 at the initial tempo when + * constructed. The timeline always advances at a speed defined by + * its current tempo, even if transport is stopped. Synchronizing to the + * transport start/stop state of Link is optional for every peer. + * The transport start/stop state is only shared with other peers when + * start/stop synchronization is enabled. + * + * An abl_link instance is initially disabled after construction, which + * means that it will not communicate on the network. Once enabled, + * an abl_link instance initiates network communication in an effort to + * discover other peers. When peers are discovered, they immediately + * become part of a shared Link session. + * + * Each function documents its thread-safety and + * realtime-safety properties. When a function is marked thread-safe, + * it means it is safe to call from multiple threads + * concurrently. When a function is marked realtime-safe, it means that + * it does not block and is appropriate for use in the thread that + * performs audio IO. + * + * One session state capture/commit function pair for use + * in the audio thread and one for all other application contexts is provided. + * In general, modifying the session state should be done in the audio + * thread for the most accurate timing results. The ability to modify + * the session state from application threads should only be used in + * cases where an application's audio thread is not actively running + * or if it doesn't generate audio at all. Modifying the Link session + * state from both the audio thread and an application thread + * concurrently is not advised and will potentially lead to unexpected + * behavior. + */ + + /*! @brief The representation of an abl_link instance*/ + typedef struct abl_link + { + void *impl; + } abl_link; + + /*! @brief Construct a new abl_link instance with an initial tempo. + * Thread-safe: yes + * Realtime-safe: no + */ + abl_link abl_link_create(double bpm); + + /*! @brief Delete an abl_link instance. + * Thread-safe: yes + * Realtime-safe: no + */ + void abl_link_destroy(abl_link link); + + /*! @brief Is Link currently enabled? + * Thread-safe: yes + * Realtime-safe: yes + */ + bool abl_link_is_enabled(abl_link link); + + /*! @brief Enable/disable Link. + * Thread-safe: yes + * Realtime-safe: no + */ + void abl_link_enable(abl_link link, bool enable); + + /*! @brief: Is start/stop synchronization enabled? + * Thread-safe: yes + * Realtime-safe: no + */ + bool abl_link_is_start_stop_sync_enabled(abl_link link); + + /*! @brief: Enable start/stop synchronization. + * Thread-safe: yes + * Realtime-safe: no + */ + void abl_link_enable_start_stop_sync(abl_link link, bool enabled); + + /*! @brief How many peers are currently connected in a Link session? + * Thread-safe: yes + * Realtime-safe: yes + */ + uint64_t abl_link_num_peers(abl_link link); + + /*! @brief Register a callback to be notified when the number of + * peers in the Link session changes. + * Thread-safe: yes + * Realtime-safe: no + * + * @discussion The callback is invoked on a Link-managed thread. + */ + typedef void (*abl_link_num_peers_callback)(uint64_t num_peers, void *context); + void abl_link_set_num_peers_callback( + abl_link link, abl_link_num_peers_callback callback, void *context); + + /*! @brief Register a callback to be notified when the session + * tempo changes. + * Thread-safe: yes + * Realtime-safe: no + * + * @discussion The callback is invoked on a Link-managed thread. + */ + typedef void (*abl_link_tempo_callback)(double tempo, void *context); + void abl_link_set_tempo_callback( + abl_link link, abl_link_tempo_callback callback, void *context); + + /*! brief: Register a callback to be notified when the state of + * start/stop isPlaying changes. + * Thread-safe: yes + * Realtime-safe: no + * + * @discussion The callback is invoked on a Link-managed thread. + */ + typedef void (*abl_link_start_stop_callback)(bool is_playing, void *context); + void abl_link_set_start_stop_callback( + abl_link link, abl_link_start_stop_callback callback, void *context); + + /*! brief: Get the current link clock time in microseconds. + * Thread-safe: yes + * Realtime-safe: yes + */ + int64_t abl_link_clock_micros(abl_link link); + + /*! @brief The representation of the current local state of a client in a Link Session + * + * @discussion A session state represents a timeline and the start/stop + * state. The timeline is a representation of a mapping between time and + * beats for varying quanta. The start/stop state represents the user + * intention to start or stop transport at a specific time. Start stop + * synchronization is an optional feature that allows to share the user + * request to start or stop transport between a subgroup of peers in a + * Link session. When observing a change of start/stop state, audio + * playback of a peer should be started or stopped the same way it would + * have happened if the user had requested that change at the according + * time locally. The start/stop state can only be changed by the user. + * This means that the current local start/stop state persists when + * joining or leaving a Link session. After joining a Link session + * start/stop change requests will be communicated to all connected peers. + */ + typedef struct abl_link_session_state + { + void *impl; + } abl_link_session_state; + + /*! @brief Create a new session_state instance. + * Thread-safe: yes + * Realtime-safe: no + * + * @discussion The session_state is to be used with the abl_link_capture... and + * abl_link_commit... functions to capture snapshots of the current link state and pass + * changes to the link session. + */ + abl_link_session_state abl_link_create_session_state(void); + + /*! @brief Delete a session_state instance. + * Thread-safe: yes + * Realtime-safe: no + */ + void abl_link_destroy_session_state(abl_link_session_state abl_link_session_state); + + /*! @brief Capture the current Link Session State from the audio thread. + * Thread-safe: no + * Realtime-safe: yes + * + * @discussion This function should ONLY be called in the audio thread and must not be + * accessed from any other threads. After capturing the session_state holds a snapshot + * of the current Link Session State, so it should be used in a local scope. The + * session_state should not be created on the audio thread. + */ + void abl_link_capture_audio_session_state( + abl_link link, abl_link_session_state session_state); + + /*! @brief Commit the given Session State to the Link session from the + * audio thread. + * Thread-safe: no + * Realtime-safe: yes + * + * @discussion This function should ONLY be called in the audio thread. The given + * session_state will replace the current Link state. Modifications will be + * communicated to other peers in the session. + */ + void abl_link_commit_audio_session_state( + abl_link link, abl_link_session_state session_state); + + /*! @brief Capture the current Link Session State from an application thread. + * Thread-safe: no + * Realtime-safe: yes + * + * @discussion Provides a mechanism for capturing the Link Session State from an + * application thread (other than the audio thread). After capturing the session_state + * contains a snapshot of the current Link state, so it should be used in a local + * scope. + */ + void abl_link_capture_app_session_state( + abl_link link, abl_link_session_state session_state); + + /*! @brief Commit the given Session State to the Link session from an + * application thread. + * Thread-safe: yes + * Realtime-safe: no + * + * @discussion The given session_state will replace the current Link Session State. + * Modifications of the Session State will be communicated to other peers in the + * session. + */ + void abl_link_commit_app_session_state( + abl_link link, abl_link_session_state session_state); + + /*! @brief: The tempo of the timeline, in Beats Per Minute. + * + * @discussion This is a stable value that is appropriate for display to the user. Beat + * time progress will not necessarily match this tempo exactly because of clock drift + * compensation. + */ + double abl_link_tempo(abl_link_session_state session_state); + + /*! @brief: Set the timeline tempo to the given bpm value, taking effect at the given + * time. + */ + void abl_link_set_tempo( + abl_link_session_state session_state, double bpm, int64_t at_time); + + /*! @brief: Get the beat value corresponding to the given time for the given quantum. + * + * @discussion: The magnitude of the resulting beat value is unique to this Link + * client, but its phase with respect to the provided quantum is shared among all + * session peers. For non-negative beat values, the following property holds: + * fmod(beatAtTime(t, q), q) == phaseAtTime(t, q) + */ + double abl_link_beat_at_time( + abl_link_session_state session_state, int64_t time, double quantum); + + /*! @brief: Get the session phase at the given time for the given quantum. + * + * @discussion: The result is in the interval [0, quantum). The result is equivalent to + * fmod(beatAtTime(t, q), q) for non-negative beat values. This function is convenient + * if the client application is only interested in the phase and not the beat + * magnitude. Also, unlike fmod, it handles negative beat values correctly. + */ + double abl_link_phase_at_time( + abl_link_session_state session_state, int64_t time, double quantum); + + /*! @brief: Get the time at which the given beat occurs for the given quantum. + * + * @discussion: The inverse of beatAtTime, assuming a constant tempo. + * beatAtTime(timeAtBeat(b, q), q) === b. + */ + int64_t abl_link_time_at_beat( + abl_link_session_state session_state, double beat, double quantum); + + /*! @brief: Attempt to map the given beat to the given time in the context of the given + * quantum. + * + * @discussion: This function behaves differently depending on the state of the + * session. If no other peers are connected, then this abl_link instance is in a + * session by itself and is free to re-map the beat/time relationship whenever it + * pleases. In this case, beatAtTime(time, quantum) == beat after this funtion has been + * called. + * + * If there are other peers in the session, this abl_link instance should not abruptly + * re-map the beat/time relationship in the session because that would lead to beat + * discontinuities among the other peers. In this case, the given beat will be mapped + * to the next time value greater than the given time with the same phase as the given + * beat. + * + * This function is specifically designed to enable the concept of "quantized launch" + * in client applications. If there are no other peers in the session, then an event + * (such as starting transport) happens immediately when it is requested. If there are + * other peers, however, we wait until the next time at which the session phase matches + * the phase of the event, thereby executing the event in-phase with the other peers in + * the session. The client application only needs to invoke this function to achieve + * this behavior and should not need to explicitly check the number of peers. + */ + void abl_link_request_beat_at_time( + abl_link_session_state session_state, double beat, int64_t time, double quantum); + + /*! @brief: Rudely re-map the beat/time relationship for all peers in a session. + * + * @discussion: DANGER: This function should only be needed in certain special + * circumstances. Most applications should not use it. It is very similar to + * requestBeatAtTime except that it does not fall back to the quantizing behavior when + * it is in a session with other peers. Calling this function will unconditionally map + * the given beat to the given time and broadcast the result to the session. This is + * very anti-social behavior and should be avoided. + * + * One of the few legitimate uses of this function is to synchronize a Link session + * with an external clock source. By periodically forcing the beat/time mapping + * according to an external clock source, a peer can effectively bridge that clock into + * a Link session. Much care must be taken at the application layer when implementing + * such a feature so that users do not accidentally disrupt Link sessions that they may + * join. + */ + void abl_link_force_beat_at_time( + abl_link_session_state session_state, double beat, uint64_t time, double quantum); + + /*! @brief: Set if transport should be playing or stopped, taking effect at the given + * time. + */ + void abl_link_set_is_playing( + abl_link_session_state session_state, bool is_playing, uint64_t time); + + /*! @brief: Is transport playing? */ + bool abl_link_is_playing(abl_link_session_state session_state); + + /*! @brief: Get the time at which a transport start/stop occurs */ + uint64_t abl_link_time_for_is_playing(abl_link_session_state session_state); + + /*! @brief: Convenience function to attempt to map the given beat to the time + * when transport is starting to play in context of the given quantum. + * This function evaluates to a no-op if abl_link_is_playing equals false. + */ + void abl_link_request_beat_at_start_playing_time( + abl_link_session_state session_state, double beat, double quantum); + + /*! @brief: Convenience function to start or stop transport at a given time and attempt + * to map the given beat to this time in context of the given quantum. */ + void abl_link_set_is_playing_and_request_beat_at_time( + abl_link_session_state session_state, + bool is_playing, + uint64_t time, + double beat, + double quantum); + +#ifdef __cplusplus +} // extern "C" +#endif // __cplusplus diff --git a/tidal-link/link/extensions/abl_link/src/abl_link.cpp b/tidal-link/link/extensions/abl_link/src/abl_link.cpp new file mode 100644 index 000000000..e34f6b522 --- /dev/null +++ b/tidal-link/link/extensions/abl_link/src/abl_link.cpp @@ -0,0 +1,214 @@ +/* Copyright 2021, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#include +#include + +extern "C" +{ + abl_link abl_link_create(double bpm) + { + return abl_link{reinterpret_cast(new ableton::Link(bpm))}; + } + + void abl_link_destroy(abl_link link) + { + delete reinterpret_cast(link.impl); + } + + bool abl_link_is_enabled(abl_link link) + { + return reinterpret_cast(link.impl)->isEnabled(); + } + + void abl_link_enable(abl_link link, bool enabled) + { + reinterpret_cast(link.impl)->enable(enabled); + } + + bool abl_link_is_start_stop_sync_enabled(abl_link link) + { + return reinterpret_cast(link.impl)->isStartStopSyncEnabled(); + } + + void abl_link_enable_start_stop_sync(abl_link link, bool enabled) + { + reinterpret_cast(link.impl)->enableStartStopSync(enabled); + } + + uint64_t abl_link_num_peers(abl_link link) + { + return reinterpret_cast(link.impl)->numPeers(); + } + + void abl_link_set_num_peers_callback( + abl_link link, abl_link_num_peers_callback callback, void *context) + { + reinterpret_cast(link.impl)->setNumPeersCallback( + [callback, context]( + std::size_t numPeers) { (*callback)(static_cast(numPeers), context); }); + } + + void abl_link_set_tempo_callback( + abl_link link, abl_link_tempo_callback callback, void *context) + { + reinterpret_cast(link.impl)->setTempoCallback( + [callback, context](double tempo) { (*callback)(tempo, context); }); + } + + void abl_link_set_start_stop_callback( + abl_link link, abl_link_start_stop_callback callback, void *context) + { + reinterpret_cast(link.impl)->setStartStopCallback( + [callback, context](bool isPlaying) { (*callback)(isPlaying, context); }); + } + + int64_t abl_link_clock_micros(abl_link link) + { + return reinterpret_cast(link.impl)->clock().micros().count(); + } + + abl_link_session_state abl_link_create_session_state(void) + { + return abl_link_session_state{reinterpret_cast( + new ableton::Link::SessionState{ableton::link::ApiState{}, {}})}; + } + + void abl_link_destroy_session_state(abl_link_session_state session_state) + { + delete reinterpret_cast(session_state.impl); + } + + void abl_link_capture_app_session_state( + abl_link link, abl_link_session_state session_state) + { + *reinterpret_cast(session_state.impl) = + reinterpret_cast(link.impl)->captureAppSessionState(); + } + + void abl_link_commit_app_session_state( + abl_link link, abl_link_session_state session_state) + { + reinterpret_cast(link.impl)->commitAppSessionState( + *reinterpret_cast(session_state.impl)); + } + + void abl_link_capture_audio_session_state( + abl_link link, abl_link_session_state session_state) + { + *reinterpret_cast(session_state.impl) = + reinterpret_cast(link.impl)->captureAudioSessionState(); + } + + void abl_link_commit_audio_session_state( + abl_link link, abl_link_session_state session_state) + { + reinterpret_cast(link.impl)->commitAudioSessionState( + *reinterpret_cast(session_state.impl)); + } + + double abl_link_tempo(abl_link_session_state session_state) + { + return reinterpret_cast(session_state.impl)->tempo(); + } + + void abl_link_set_tempo( + abl_link_session_state session_state, double bpm, int64_t at_time) + { + reinterpret_cast(session_state.impl) + ->setTempo(bpm, std::chrono::microseconds{at_time}); + } + + double abl_link_beat_at_time( + abl_link_session_state session_state, int64_t time, double quantum) + { + auto micros = std::chrono::microseconds{time}; + return reinterpret_cast(session_state.impl) + ->beatAtTime(micros, quantum); + } + + double abl_link_phase_at_time( + abl_link_session_state session_state, int64_t time, double quantum) + { + return reinterpret_cast(session_state.impl) + ->phaseAtTime(std::chrono::microseconds{time}, quantum); + } + + int64_t abl_link_time_at_beat( + abl_link_session_state session_state, double beat, double quantum) + { + return reinterpret_cast(session_state.impl) + ->timeAtBeat(beat, quantum) + .count(); + } + + void abl_link_request_beat_at_time( + abl_link_session_state session_state, double beat, int64_t time, double quantum) + { + reinterpret_cast(session_state.impl) + ->requestBeatAtTime(beat, std::chrono::microseconds{time}, quantum); + } + + void abl_link_force_beat_at_time( + abl_link_session_state session_state, double beat, uint64_t time, double quantum) + { + reinterpret_cast(session_state.impl) + ->forceBeatAtTime(beat, std::chrono::microseconds{time}, quantum); + } + + void abl_link_set_is_playing( + abl_link_session_state session_state, bool is_playing, uint64_t time) + { + reinterpret_cast(session_state.impl) + ->setIsPlaying(is_playing, std::chrono::microseconds(time)); + } + + bool abl_link_is_playing(abl_link_session_state session_state) + { + return reinterpret_cast(session_state.impl) + ->isPlaying(); + } + + uint64_t abl_link_time_for_is_playing(abl_link_session_state session_state) + { + return static_cast( + reinterpret_cast(session_state.impl) + ->timeForIsPlaying() + .count()); + } + + void abl_link_request_beat_at_start_playing_time( + abl_link_session_state session_state, double beat, double quantum) + { + reinterpret_cast(session_state.impl) + ->requestBeatAtStartPlayingTime(beat, quantum); + } + + void abl_link_set_is_playing_and_request_beat_at_time( + abl_link_session_state session_state, + bool is_playing, + uint64_t time, + double beat, + double quantum) + { + reinterpret_cast(session_state.impl) + ->setIsPlayingAndRequestBeatAtTime( + is_playing, std::chrono::microseconds{time}, beat, quantum); + } +} diff --git a/tidal-link/link/include/CMakeLists.txt b/tidal-link/link/include/CMakeLists.txt new file mode 100644 index 000000000..1c7b5ed96 --- /dev/null +++ b/tidal-link/link/include/CMakeLists.txt @@ -0,0 +1,186 @@ +cmake_minimum_required(VERSION 3.0) +project(LinkCore) + +# ____ +# / ___|___ _ __ ___ +# | | / _ \| '__/ _ \ +# | |__| (_) | | | __/ +# \____\___/|_| \___| +# + +set(link_core_DIR ${CMAKE_CURRENT_SOURCE_DIR}/ableton/link) +set(link_core_HEADERS + ${link_core_DIR}/Beats.hpp + ${link_core_DIR}/ClientSessionTimelines.hpp + ${link_core_DIR}/Controller.hpp + ${link_core_DIR}/Gateway.hpp + ${link_core_DIR}/GhostXForm.hpp + ${link_core_DIR}/HostTimeFilter.hpp + ${link_core_DIR}/LinearRegression.hpp + ${link_core_DIR}/Measurement.hpp + ${link_core_DIR}/MeasurementEndpointV4.hpp + ${link_core_DIR}/MeasurementService.hpp + ${link_core_DIR}/Median.hpp + ${link_core_DIR}/NodeId.hpp + ${link_core_DIR}/NodeState.hpp + ${link_core_DIR}/PayloadEntries.hpp + ${link_core_DIR}/Optional.hpp + ${link_core_DIR}/Peers.hpp + ${link_core_DIR}/PeerState.hpp + ${link_core_DIR}/Phase.hpp + ${link_core_DIR}/PingResponder.hpp + ${link_core_DIR}/SessionId.hpp + ${link_core_DIR}/SessionState.hpp + ${link_core_DIR}/Sessions.hpp + ${link_core_DIR}/StartStopState.hpp + ${link_core_DIR}/Tempo.hpp + ${link_core_DIR}/Timeline.hpp + ${link_core_DIR}/TripleBuffer.hpp + ${link_core_DIR}/v1/Messages.hpp + PARENT_SCOPE +) + +# ____ _ +# | _ \(_)___ ___ _____ _____ _ __ _ _ +# | | | | / __|/ __/ _ \ \ / / _ \ '__| | | | +# | |_| | \__ \ (_| (_) \ V / __/ | | |_| | +# |____/|_|___/\___\___/ \_/ \___|_| \__, | +# |___/ + +set(link_discovery_DIR ${CMAKE_CURRENT_SOURCE_DIR}/ableton/discovery) +set(link_discovery_HEADERS + ${link_discovery_DIR}/InterfaceScanner.hpp + ${link_discovery_DIR}/IpV4Interface.hpp + ${link_discovery_DIR}/MessageTypes.hpp + ${link_discovery_DIR}/NetworkByteStreamSerializable.hpp + ${link_discovery_DIR}/Payload.hpp + ${link_discovery_DIR}/PeerGateway.hpp + ${link_discovery_DIR}/PeerGateways.hpp + ${link_discovery_DIR}/Service.hpp + ${link_discovery_DIR}/UdpMessenger.hpp + ${link_discovery_DIR}/v1/Messages.hpp + PARENT_SCOPE +) + +# ____ _ _ __ +# | _ \| | __ _| |_ / _| ___ _ __ _ __ ___ +# | |_) | |/ _` | __| |_ / _ \| '__| '_ ` _ \ +# | __/| | (_| | |_| _| (_) | | | | | | | | +# |_| |_|\__,_|\__|_| \___/|_| |_| |_| |_| +# + +set(link_platform_DIR ${CMAKE_CURRENT_SOURCE_DIR}/ableton/platforms) +set(link_platform_HEADERS + ${link_platform_DIR}/Config.hpp + ${link_platform_DIR}/asio/AsioTimer.hpp + ${link_platform_DIR}/asio/AsioWrapper.hpp + ${link_platform_DIR}/asio/Context.hpp + ${link_platform_DIR}/asio/LockFreeCallbackDispatcher.hpp + ${link_platform_DIR}/asio/Socket.hpp + ${link_platform_DIR}/asio/Util.hpp +) + +if(ESP_PLATFORM) + set(link_platform_HEADERS + ${link_platform_HEADERS} + ${link_platform_DIR}/esp32/Clock.hpp + ${link_platform_DIR}/esp32/Context.hpp + ${link_platform_DIR}/esp32/Esp32.hpp + ${link_platform_DIR}/esp32/Random.hpp + ${link_platform_DIR}/esp32/ScanIpIfAddrs.hpp + ) +elseif(UNIX) + set(link_platform_HEADERS + ${link_platform_HEADERS} + ${link_platform_DIR}/posix/ScanIpIfAddrs.hpp + ) + + if(APPLE) + set(link_platform_HEADERS + ${link_platform_HEADERS} + ${link_platform_DIR}/darwin/Clock.hpp + ${link_platform_DIR}/darwin/Darwin.hpp + ${link_platform_DIR}/darwin/ThreadFactory.hpp + ${link_platform_DIR}/stl/Random.hpp + ) + elseif(CMAKE_SYSTEM_NAME MATCHES "Linux|kFreeBSD|GNU") + set(link_platform_HEADERS + ${link_platform_HEADERS} + ${link_platform_DIR}/linux/Clock.hpp + ${link_platform_DIR}/linux/Linux.hpp + ${link_platform_DIR}/stl/Clock.hpp + ${link_platform_DIR}/stl/Random.hpp + ) + if(${CMAKE_SYSTEM_NAME} MATCHES "Linux") + set(link_platform_HEADERS + ${link_platform_HEADERS} + ${link_platform_DIR}/linux/ThreadFactory.hpp + ) + endif() + endif() +elseif(WIN32) + set(link_platform_HEADERS + ${link_platform_HEADERS} + ${link_platform_DIR}/stl/Random.hpp + ${link_platform_DIR}/windows/Clock.hpp + ${link_platform_DIR}/windows/ScanIpIfAddrs.hpp + ${link_platform_DIR}/windows/ThreadFactory.hpp + ${link_platform_DIR}/windows/Windows.hpp + ) +endif() +set(link_platform_HEADERS + ${link_platform_HEADERS} + PARENT_SCOPE +) + +# _ _ _ _ _ +# | | | | |_(_) | +# | | | | __| | | +# | |_| | |_| | | +# \___/ \__|_|_| +# + +set(link_util_DIR ${CMAKE_CURRENT_SOURCE_DIR}/ableton/util) +set(link_util_HEADERS + ${link_util_DIR}/Injected.hpp + ${link_util_DIR}/Log.hpp + ${link_util_DIR}/SafeAsyncHandler.hpp + ${link_util_DIR}/SampleTiming.hpp + PARENT_SCOPE +) + +# _____ _ _ +# | ____|_ ___ __ ___ _ __| |_ ___ __| | +# | _| \ \/ / '_ \ / _ \| '__| __/ _ \/ _` | +# | |___ > <| |_) | (_) | | | || __/ (_| | +# |_____/_/\_\ .__/ \___/|_| \__\___|\__,_| +# |_| + +# This list contains all of the headers needed by most Link projects. +# Usually, just adding this variable to your linker targets will place +# all relevant Link headers in your project. +set(link_DIR ${CMAKE_CURRENT_SOURCE_DIR}/ableton) +set(link_HEADERS + ${link_core_HEADERS} + ${link_discovery_HEADERS} + ${link_platform_HEADERS} + ${link_util_HEADERS} + ${link_DIR}/Link.hpp + ${link_DIR}/Link.ipp + PARENT_SCOPE +) + +set(link_test_DIR ${CMAKE_CURRENT_SOURCE_DIR}/ableton/test) +set(link_test_HEADERS + ${link_discovery_DIR}/test/Interface.hpp + ${link_discovery_DIR}/test/PayloadEntries.hpp + ${link_discovery_DIR}/test/Socket.hpp + ${link_util_DIR}/test/IoService.hpp + ${link_util_DIR}/test/Timer.hpp + ${link_test_DIR}/CatchWrapper.hpp + ${link_test_DIR}/serial_io/Context.hpp + ${link_test_DIR}/serial_io/Fixture.hpp + ${link_test_DIR}/serial_io/SchedulerTree.hpp + ${link_test_DIR}/serial_io/Timer.hpp + PARENT_SCOPE +) diff --git a/tidal-link/link/include/ableton/Link.hpp b/tidal-link/link/include/ableton/Link.hpp new file mode 100644 index 000000000..8b915977e --- /dev/null +++ b/tidal-link/link/include/ableton/Link.hpp @@ -0,0 +1,403 @@ +/*! @file Link.hpp + * @copyright 2016, Ableton AG, Berlin. All rights reserved. + * @brief Library for cross-device shared tempo and quantized beat grid + * + * @license: + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ + +/*! @class Link and BasicLink + * @brief Classes representing a participant in a Link session. + * The BasicLink type allows to customize the clock. The Link type + * uses the recommended platform-dependent representation of the + * system clock as defined in platforms/Config.hpp. + * It's preferred to use Link instead of BasicLink. + * + * @discussion Each Link instance has its own session state which + * represents a beat timeline and a transport start/stop state. The + * timeline starts running from beat 0 at the initial tempo when + * constructed. The timeline always advances at a speed defined by + * its current tempo, even if transport is stopped. Synchronizing to the + * transport start/stop state of Link is optional for every peer. + * The transport start/stop state is only shared with other peers when + * start/stop synchronization is enabled. + * + * A Link instance is initially disabled after construction, which + * means that it will not communicate on the network. Once enabled, + * a Link instance initiates network communication in an effort to + * discover other peers. When peers are discovered, they immediately + * become part of a shared Link session. + * + * Each method of the Link type documents its thread-safety and + * realtime-safety properties. When a method is marked thread-safe, + * it means it is safe to call from multiple threads + * concurrently. When a method is marked realtime-safe, it means that + * it does not block and is appropriate for use in the thread that + * performs audio IO. + * + * Link provides one session state capture/commit method pair for use + * in the audio thread and one for all other application contexts. In + * general, modifying the session state should be done in the audio + * thread for the most accurate timing results. The ability to modify + * the session state from application threads should only be used in + * cases where an application's audio thread is not actively running + * or if it doesn't generate audio at all. Modifying the Link session + * state from both the audio thread and an application thread + * concurrently is not advised and will potentially lead to unexpected + * behavior. + * + * Only use the BasicLink class if the default platform clock does not + * fulfill other requirements of the client application. Please note this + * will require providing a custom Clock implementation. See the clock() + * documentation for details. + */ +template +class BasicLink +{ +public: + class SessionState; + + /*! @brief Construct with an initial tempo. */ + BasicLink(double bpm); + + /*! @brief Link instances cannot be copied or moved */ + BasicLink(const BasicLink&) = delete; + BasicLink& operator=(const BasicLink&) = delete; + BasicLink(BasicLink&&) = delete; + BasicLink& operator=(BasicLink&&) = delete; + + /*! @brief Is Link currently enabled? + * Thread-safe: yes + * Realtime-safe: yes + */ + bool isEnabled() const; + + /*! @brief Enable/disable Link. + * Thread-safe: yes + * Realtime-safe: no + */ + void enable(bool bEnable); + + /*! @brief: Is start/stop synchronization enabled? + * Thread-safe: yes + * Realtime-safe: no + */ + bool isStartStopSyncEnabled() const; + + /*! @brief: Enable start/stop synchronization. + * Thread-safe: yes + * Realtime-safe: no + */ + void enableStartStopSync(bool bEnable); + + /*! @brief How many peers are currently connected in a Link session? + * Thread-safe: yes + * Realtime-safe: yes + */ + std::size_t numPeers() const; + + /*! @brief Register a callback to be notified when the number of + * peers in the Link session changes. + * Thread-safe: yes + * Realtime-safe: no + * + * @discussion The callback is invoked on a Link-managed thread. + * + * @param callback The callback signature is: + * void (std::size_t numPeers) + */ + template + void setNumPeersCallback(Callback callback); + + /*! @brief Register a callback to be notified when the session + * tempo changes. + * Thread-safe: yes + * Realtime-safe: no + * + * @discussion The callback is invoked on a Link-managed thread. + * + * @param callback The callback signature is: void (double bpm) + */ + template + void setTempoCallback(Callback callback); + + /*! brief: Register a callback to be notified when the state of + * start/stop isPlaying changes. + * Thread-safe: yes + * Realtime-safe: no + * + * @discussion The callback is invoked on a Link-managed thread. + * + * @param callback The callback signature is: + * void (bool isPlaying) + */ + template + void setStartStopCallback(Callback callback); + + /*! @brief The clock used by Link. + * Thread-safe: yes + * Realtime-safe: yes + * + * @discussion The Clock type is a platform-dependent representation + * of the system clock. It exposes a micros() method, which is a + * normalized representation of the current system time in + * std::chrono::microseconds. + */ + Clock clock() const; + + /*! @brief Capture the current Link Session State from the audio thread. + * Thread-safe: no + * Realtime-safe: yes + * + * @discussion This method should ONLY be called in the audio thread + * and must not be accessed from any other threads. The returned + * object stores a snapshot of the current Link Session State, so it + * should be captured and used in a local scope. Storing the + * Session State for later use in a different context is not advised + * because it will provide an outdated view. + */ + SessionState captureAudioSessionState() const; + + /*! @brief Commit the given Session State to the Link session from the + * audio thread. + * Thread-safe: no + * Realtime-safe: yes + * + * @discussion This method should ONLY be called in the audio + * thread. The given Session State will replace the current Link + * state. Modifications will be communicated to other peers in the + * session. + */ + void commitAudioSessionState(SessionState state); + + /*! @brief Capture the current Link Session State from an application + * thread. + * Thread-safe: yes + * Realtime-safe: no + * + * @discussion Provides a mechanism for capturing the Link Session + * State from an application thread (other than the audio thread). + * The returned Session State stores a snapshot of the current Link + * state, so it should be captured and used in a local scope. + * Storing the it for later use in a different context is not + * advised because it will provide an outdated view. + */ + SessionState captureAppSessionState() const; + + /*! @brief Commit the given Session State to the Link session from an + * application thread. + * Thread-safe: yes + * Realtime-safe: no + * + * @discussion The given Session State will replace the current Link + * Session State. Modifications of the Session State will be + * communicated to other peers in the session. + */ + void commitAppSessionState(SessionState state); + + /*! @class SessionState + * @brief Representation of a timeline and the start/stop state + * + * @discussion A SessionState object is intended for use in a local scope within + * a single thread - none of its methods are thread-safe. All of its methods are + * non-blocking, so it is safe to use from a realtime thread. + * It provides functions to observe and manipulate the timeline and start/stop + * state. + * + * The timeline is a representation of a mapping between time and beats for varying + * quanta. + * The start/stop state represents the user intention to start or stop transport at + * a specific time. Start stop synchronization is an optional feature that allows to + * share the user request to start or stop transport between a subgroup of peers in + * a Link session. When observing a change of start/stop state, audio playback of a + * peer should be started or stopped the same way it would have happened if the user + * had requested that change at the according time locally. The start/stop state can + * only be changed by the user. This means that the current local start/stop state + * persists when joining or leaving a Link session. After joining a Link session + * start/stop change requests will be communicated to all connected peers. + */ + class SessionState + { + public: + SessionState(const link::ApiState state, const bool bRespectQuantum); + + /*! @brief: The tempo of the timeline, in Beats Per Minute. + * + * @discussion This is a stable value that is appropriate for display + * to the user. Beat time progress will not necessarily match this tempo + * exactly because of clock drift compensation. + */ + double tempo() const; + + /*! @brief: Set the timeline tempo to the given bpm value, taking + * effect at the given time. + */ + void setTempo(double bpm, std::chrono::microseconds atTime); + + /*! @brief: Get the beat value corresponding to the given time + * for the given quantum. + * + * @discussion: The magnitude of the resulting beat value is + * unique to this Link instance, but its phase with respect to + * the provided quantum is shared among all session + * peers. For non-negative beat values, the following + * property holds: fmod(beatAtTime(t, q), q) == phaseAtTime(t, q) + */ + double beatAtTime(std::chrono::microseconds time, double quantum) const; + + /*! @brief: Get the session phase at the given time for the given + * quantum. + * + * @discussion: The result is in the interval [0, quantum). The + * result is equivalent to fmod(beatAtTime(t, q), q) for + * non-negative beat values. This method is convenient if the + * client is only interested in the phase and not the beat + * magnitude. Also, unlike fmod, it handles negative beat values + * correctly. + */ + double phaseAtTime(std::chrono::microseconds time, double quantum) const; + + /*! @brief: Get the time at which the given beat occurs for the + * given quantum. + * + * @discussion: The inverse of beatAtTime, assuming a constant + * tempo. beatAtTime(timeAtBeat(b, q), q) === b. + */ + std::chrono::microseconds timeAtBeat(double beat, double quantum) const; + + /*! @brief: Attempt to map the given beat to the given time in the + * context of the given quantum. + * + * @discussion: This method behaves differently depending on the + * state of the session. If no other peers are connected, + * then this instance is in a session by itself and is free to + * re-map the beat/time relationship whenever it pleases. In this + * case, beatAtTime(time, quantum) == beat after this method has + * been called. + * + * If there are other peers in the session, this instance + * should not abruptly re-map the beat/time relationship in the + * session because that would lead to beat discontinuities among + * the other peers. In this case, the given beat will be mapped + * to the next time value greater than the given time with the + * same phase as the given beat. + * + * This method is specifically designed to enable the concept of + * "quantized launch" in client applications. If there are no other + * peers in the session, then an event (such as starting + * transport) happens immediately when it is requested. If there + * are other peers, however, we wait until the next time at which + * the session phase matches the phase of the event, thereby + * executing the event in-phase with the other peers in the + * session. The client only needs to invoke this method to + * achieve this behavior and should not need to explicitly check + * the number of peers. + */ + void requestBeatAtTime(double beat, std::chrono::microseconds time, double quantum); + + /*! @brief: Rudely re-map the beat/time relationship for all peers + * in a session. + * + * @discussion: DANGER: This method should only be needed in + * certain special circumstances. Most applications should not + * use it. It is very similar to requestBeatAtTime except that it + * does not fall back to the quantizing behavior when it is in a + * session with other peers. Calling this method will + * unconditionally map the given beat to the given time and + * broadcast the result to the session. This is very anti-social + * behavior and should be avoided. + * + * One of the few legitimate uses of this method is to + * synchronize a Link session with an external clock source. By + * periodically forcing the beat/time mapping according to an + * external clock source, a peer can effectively bridge that + * clock into a Link session. Much care must be taken at the + * application layer when implementing such a feature so that + * users do not accidentally disrupt Link sessions that they may + * join. + */ + void forceBeatAtTime(double beat, std::chrono::microseconds time, double quantum); + + /*! @brief: Set if transport should be playing or stopped, taking effect + * at the given time. + */ + void setIsPlaying(bool isPlaying, std::chrono::microseconds time); + + /*! @brief: Is transport playing? */ + bool isPlaying() const; + + /*! @brief: Get the time at which a transport start/stop occurs */ + std::chrono::microseconds timeForIsPlaying() const; + + /*! @brief: Convenience function to attempt to map the given beat to the time + * when transport is starting to play in context of the given quantum. + * This function evaluates to a no-op if isPlaying() equals false. + */ + void requestBeatAtStartPlayingTime(double beat, double quantum); + + /*! @brief: Convenience function to start or stop transport at a given time and + * attempt to map the given beat to this time in context of the given quantum. + */ + void setIsPlayingAndRequestBeatAtTime( + bool isPlaying, std::chrono::microseconds time, double beat, double quantum); + + private: + friend BasicLink; + link::ApiState mOriginalState; + link::ApiState mState; + bool mbRespectQuantum; + }; + +private: + using Controller = ableton::link::Controller; + + std::mutex mCallbackMutex; + link::PeerCountCallback mPeerCountCallback = [](std::size_t) {}; + link::TempoCallback mTempoCallback = [](link::Tempo) {}; + link::StartStopStateCallback mStartStopCallback = [](bool) {}; + Clock mClock; + Controller mController; +}; + +class Link : public BasicLink +{ +public: + using Clock = link::platform::Clock; + + Link(double bpm) + : BasicLink(bpm) + { + } +}; + +} // namespace ableton + +#include diff --git a/tidal-link/link/include/ableton/Link.ipp b/tidal-link/link/include/ableton/Link.ipp new file mode 100644 index 000000000..f8cbce832 --- /dev/null +++ b/tidal-link/link/include/ableton/Link.ipp @@ -0,0 +1,280 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include + +namespace ableton +{ +namespace detail +{ + +template +inline typename BasicLink::SessionState toSessionState( + const link::ClientState& state, const bool isConnected) +{ + return {{state.timeline, {state.startStopState.isPlaying, state.startStopState.time}}, + isConnected}; +} + +inline link::IncomingClientState toIncomingClientState(const link::ApiState& state, + const link::ApiState& originalState, + const std::chrono::microseconds timestamp) +{ + const auto timeline = originalState.timeline != state.timeline + ? link::OptionalTimeline{state.timeline} + : link::OptionalTimeline{}; + const auto startStopState = + originalState.startStopState != state.startStopState + ? link::OptionalClientStartStopState{{state.startStopState.isPlaying, + state.startStopState.time, timestamp}} + : link::OptionalClientStartStopState{}; + return {timeline, startStopState, timestamp}; +} + +} // namespace detail + +template +inline BasicLink::BasicLink(const double bpm) + : mController(link::Tempo(bpm), + [this](const std::size_t peers) { + std::lock_guard lock(mCallbackMutex); + mPeerCountCallback(peers); + }, + [this](const link::Tempo tempo) { + std::lock_guard lock(mCallbackMutex); + mTempoCallback(tempo); + }, + [this](const bool isPlaying) { + std::lock_guard lock(mCallbackMutex); + mStartStopCallback(isPlaying); + }, + mClock) +{ +} + +template +inline bool BasicLink::isEnabled() const +{ + return mController.isEnabled(); +} + +template +inline void BasicLink::enable(const bool bEnable) +{ + mController.enable(bEnable); +} + +template +inline bool BasicLink::isStartStopSyncEnabled() const +{ + return mController.isStartStopSyncEnabled(); +} + +template +inline void BasicLink::enableStartStopSync(bool bEnable) +{ + mController.enableStartStopSync(bEnable); +} + +template +inline std::size_t BasicLink::numPeers() const +{ + return mController.numPeers(); +} + +template +template +void BasicLink::setNumPeersCallback(Callback callback) +{ + std::lock_guard lock(mCallbackMutex); + mPeerCountCallback = [callback](const std::size_t numPeers) { callback(numPeers); }; +} + +template +template +void BasicLink::setTempoCallback(Callback callback) +{ + std::lock_guard lock(mCallbackMutex); + mTempoCallback = [callback](const link::Tempo tempo) { callback(tempo.bpm()); }; +} + +template +template +void BasicLink::setStartStopCallback(Callback callback) +{ + std::lock_guard lock(mCallbackMutex); + mStartStopCallback = callback; +} + +template +inline Clock BasicLink::clock() const +{ + return mClock; +} + +template +inline typename BasicLink::SessionState BasicLink< + Clock>::captureAudioSessionState() const +{ + return detail::toSessionState(mController.clientStateRtSafe(), numPeers() > 0); +} + +template +inline void BasicLink::commitAudioSessionState( + const typename BasicLink::SessionState state) +{ + mController.setClientStateRtSafe( + detail::toIncomingClientState(state.mState, state.mOriginalState, mClock.micros())); +} + +template +inline typename BasicLink::SessionState BasicLink::captureAppSessionState() + const +{ + return detail::toSessionState(mController.clientState(), numPeers() > 0); +} + +template +inline void BasicLink::commitAppSessionState( + const typename BasicLink::SessionState state) +{ + mController.setClientState( + detail::toIncomingClientState(state.mState, state.mOriginalState, mClock.micros())); +} + +// Link::SessionState + +template +inline BasicLink::SessionState::SessionState( + const link::ApiState state, const bool bRespectQuantum) + : mOriginalState(state) + , mState(state) + , mbRespectQuantum(bRespectQuantum) +{ +} + +template +inline double BasicLink::SessionState::tempo() const +{ + return mState.timeline.tempo.bpm(); +} + +template +inline void BasicLink::SessionState::setTempo( + const double bpm, const std::chrono::microseconds atTime) +{ + const auto desiredTl = link::clampTempo( + link::Timeline{link::Tempo(bpm), mState.timeline.toBeats(atTime), atTime}); + mState.timeline.tempo = desiredTl.tempo; + mState.timeline.timeOrigin = desiredTl.fromBeats(mState.timeline.beatOrigin); +} + +template +inline double BasicLink::SessionState::beatAtTime( + const std::chrono::microseconds time, const double quantum) const +{ + return link::toPhaseEncodedBeats(mState.timeline, time, link::Beats{quantum}) + .floating(); +} + +template +inline double BasicLink::SessionState::phaseAtTime( + const std::chrono::microseconds time, const double quantum) const +{ + return link::phase(link::Beats{beatAtTime(time, quantum)}, link::Beats{quantum}) + .floating(); +} + +template +inline std::chrono::microseconds BasicLink::SessionState::timeAtBeat( + const double beat, const double quantum) const +{ + return link::fromPhaseEncodedBeats( + mState.timeline, link::Beats{beat}, link::Beats{quantum}); +} + +template +inline void BasicLink::SessionState::requestBeatAtTime( + const double beat, std::chrono::microseconds time, const double quantum) +{ + if (mbRespectQuantum) + { + time = timeAtBeat(link::nextPhaseMatch(link::Beats{beatAtTime(time, quantum)}, + link::Beats{beat}, link::Beats{quantum}) + .floating(), + quantum); + } + forceBeatAtTime(beat, time, quantum); +} + +template +inline void BasicLink::SessionState::forceBeatAtTime( + const double beat, const std::chrono::microseconds time, const double quantum) +{ + // There are two components to the beat adjustment: a phase shift + // and a beat magnitude adjustment. + const auto curBeatAtTime = link::Beats{beatAtTime(time, quantum)}; + const auto closestInPhase = + link::closestPhaseMatch(curBeatAtTime, link::Beats{beat}, link::Beats{quantum}); + mState.timeline = shiftClientTimeline(mState.timeline, closestInPhase - curBeatAtTime); + // Now adjust the magnitude + mState.timeline.beatOrigin = + mState.timeline.beatOrigin + (link::Beats{beat} - closestInPhase); +} + +template +inline void BasicLink::SessionState::setIsPlaying( + const bool isPlaying, const std::chrono::microseconds time) +{ + mState.startStopState = {isPlaying, time}; +} + +template +inline bool BasicLink::SessionState::isPlaying() const +{ + return mState.startStopState.isPlaying; +} + +template +inline std::chrono::microseconds BasicLink::SessionState::timeForIsPlaying() const +{ + return mState.startStopState.time; +} + +template +inline void BasicLink::SessionState::requestBeatAtStartPlayingTime( + const double beat, const double quantum) +{ + if (isPlaying()) + { + requestBeatAtTime(beat, mState.startStopState.time, quantum); + } +} + +template +inline void BasicLink::SessionState::setIsPlayingAndRequestBeatAtTime( + bool isPlaying, std::chrono::microseconds time, double beat, double quantum) +{ + mState.startStopState = {isPlaying, time}; + requestBeatAtStartPlayingTime(beat, quantum); +} + +} // namespace ableton diff --git a/tidal-link/link/include/ableton/discovery/InterfaceScanner.hpp b/tidal-link/link/include/ableton/discovery/InterfaceScanner.hpp new file mode 100644 index 000000000..cb3adad56 --- /dev/null +++ b/tidal-link/link/include/ableton/discovery/InterfaceScanner.hpp @@ -0,0 +1,102 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include + +namespace ableton +{ +namespace discovery +{ + +// Callback takes a range of asio::ip:address which is +// guaranteed to be sorted and unique +template +class InterfaceScanner +{ +public: + using Timer = typename util::Injected::type::Timer; + + InterfaceScanner(const std::chrono::seconds period, + util::Injected callback, + util::Injected io) + : mPeriod(period) + , mCallback(std::move(callback)) + , mIo(std::move(io)) + , mTimer(mIo->makeTimer()) + { + } + + void enable(const bool bEnable) + { + if (bEnable) + { + scan(); + } + else + { + mTimer.cancel(); + } + } + + void scan() + { + using namespace std; + debug(mIo->log()) << "Scanning network interfaces"; + // Rescan the hardware for available network interface addresses + vector addrs = mIo->scanNetworkInterfaces(); + // Sort and unique them to guarantee consistent comparison + sort(begin(addrs), end(addrs)); + addrs.erase(unique(begin(addrs), end(addrs)), end(addrs)); + // Pass them to the callback + (*mCallback)(std::move(addrs)); + // setup the next scanning + mTimer.expires_from_now(mPeriod); + using ErrorCode = typename Timer::ErrorCode; + mTimer.async_wait([this](const ErrorCode e) { + if (!e) + { + scan(); + } + }); + } + +private: + const std::chrono::seconds mPeriod; + util::Injected mCallback; + util::Injected mIo; + Timer mTimer; +}; + +// Factory function +template +InterfaceScanner makeInterfaceScanner( + const std::chrono::seconds period, + util::Injected callback, + util::Injected io) +{ + return {period, std::move(callback), std::move(io)}; +} + +} // namespace discovery +} // namespace ableton diff --git a/tidal-link/link/include/ableton/discovery/IpV4Interface.hpp b/tidal-link/link/include/ableton/discovery/IpV4Interface.hpp new file mode 100644 index 000000000..9967f5125 --- /dev/null +++ b/tidal-link/link/include/ableton/discovery/IpV4Interface.hpp @@ -0,0 +1,123 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include + +namespace ableton +{ +namespace discovery +{ + +inline asio::ip::udp::endpoint multicastEndpoint() +{ + return {asio::ip::address_v4::from_string("224.76.78.75"), 20808}; +} + +// Type tags for dispatching between unicast and multicast packets +struct MulticastTag +{ +}; +struct UnicastTag +{ +}; + +template +class IpV4Interface +{ +public: + using Socket = typename util::Injected::type::template Socket; + + IpV4Interface(util::Injected io, const asio::ip::address_v4& addr) + : mIo(std::move(io)) + , mMulticastReceiveSocket(mIo->template openMulticastSocket(addr)) + , mSendSocket(mIo->template openUnicastSocket(addr)) + { + } + + IpV4Interface(const IpV4Interface&) = delete; + IpV4Interface& operator=(const IpV4Interface&) = delete; + + IpV4Interface(IpV4Interface&& rhs) + : mIo(std::move(rhs.mIo)) + , mMulticastReceiveSocket(std::move(rhs.mMulticastReceiveSocket)) + , mSendSocket(std::move(rhs.mSendSocket)) + { + } + + + std::size_t send( + const uint8_t* const pData, const size_t numBytes, const asio::ip::udp::endpoint& to) + { + return mSendSocket.send(pData, numBytes, to); + } + + template + void receive(Handler handler, UnicastTag) + { + mSendSocket.receive(SocketReceiver{std::move(handler)}); + } + + template + void receive(Handler handler, MulticastTag) + { + mMulticastReceiveSocket.receive( + SocketReceiver(std::move(handler))); + } + + asio::ip::udp::endpoint endpoint() const + { + return mSendSocket.endpoint(); + } + +private: + template + struct SocketReceiver + { + SocketReceiver(Handler handler) + : mHandler(std::move(handler)) + { + } + + template + void operator()( + const asio::ip::udp::endpoint& from, const It messageBegin, const It messageEnd) + { + mHandler(Tag{}, from, messageBegin, messageEnd); + } + + Handler mHandler; + }; + + util::Injected mIo; + Socket mMulticastReceiveSocket; + Socket mSendSocket; +}; + +template +IpV4Interface makeIpV4Interface( + util::Injected io, const asio::ip::address_v4& addr) +{ + return {std::move(io), addr}; +} + +} // namespace discovery +} // namespace ableton diff --git a/tidal-link/link/include/ableton/discovery/MessageTypes.hpp b/tidal-link/link/include/ableton/discovery/MessageTypes.hpp new file mode 100644 index 000000000..e6941a2be --- /dev/null +++ b/tidal-link/link/include/ableton/discovery/MessageTypes.hpp @@ -0,0 +1,50 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +namespace ableton +{ +namespace discovery +{ + +// Message types used in the Ableton service discovery protocol. There +// are two logical messages: a state dump and a bye bye. +// +// A state dump provides all relevant information about the peer's +// current state as well as a Time To Live (TTL) value that indicates +// how many seconds this state should be considered valid. +// +// The bye bye indicates that the sender is leaving the session. + +template +struct PeerState +{ + NodeState peerState; + int ttl; +}; + +template +struct ByeBye +{ + NodeId peerId; +}; + +} // namespace discovery +} // namespace ableton diff --git a/tidal-link/link/include/ableton/discovery/NetworkByteStreamSerializable.hpp b/tidal-link/link/include/ableton/discovery/NetworkByteStreamSerializable.hpp new file mode 100644 index 000000000..49a119530 --- /dev/null +++ b/tidal-link/link/include/ableton/discovery/NetworkByteStreamSerializable.hpp @@ -0,0 +1,462 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#if defined(LINK_PLATFORM_MACOSX) +#include +#elif defined(LINK_PLATFORM_LINUX) +#include +#elif defined(LINK_PLATFORM_WINDOWS) +#include +#elif defined(ESP_PLATFORM) +#include +#endif + +#include +#include +#include +#include +#include + +#if defined(LINK_PLATFORM_WINDOWS) +#include +#include +#include +#endif + +namespace ableton +{ +namespace discovery +{ + +// Concept: NetworkByteStreamSerializable +// +// A type that can be encoded to a stream of bytes and decoded from a +// stream of bytes in network byte order. The following type is for +// documentation purposes only. + +struct NetworkByteStreamSerializable +{ + friend std::uint32_t sizeInByteStream(const NetworkByteStreamSerializable&); + + // The byte stream pointed to by 'out' must have sufficient space to + // hold this object, as defined by sizeInByteStream. + template + friend It toNetworkByteStream(const NetworkByteStreamSerializable&, It out); +}; + +// Deserialization aspect of the concept. Outside of the demonstration +// type above because clients must specify the type +// explicitly. Default implementation just defers to a class static +// method on T. For types that can't provide such a method, specialize +// this template. +template +struct Deserialize +{ + // Throws std::runtime_exception if parsing the type from the given + // byte range fails. Returns a pair of the correctly parsed value + // and an iterator to the next byte to parse. + template + static std::pair fromNetworkByteStream(It begin, It end) + { + return T::fromNetworkByteStream(std::move(begin), std::move(end)); + } +}; + + +// Default size implementation. Works for primitive types. + +template ::value>::type* = nullptr> +std::uint32_t sizeInByteStream(T) +{ + return sizeof(T); +} + +namespace detail +{ + +// utilities for implementing concept for primitive types + +template +It copyToByteStream(T t, It out) +{ + using namespace std; + return copy_n( + reinterpret_cast::pointer>(&t), sizeof(t), out); +} + +template +std::pair copyFromByteStream(It begin, const It end) +{ + using namespace std; + using ItDiff = typename iterator_traits::difference_type; + + if (distance(begin, end) < static_cast(sizeof(T))) + { + throw range_error("Parsing type from byte stream failed"); + } + else + { + T t; + const auto n = sizeof(t); + copy_n(begin, n, reinterpret_cast(&t)); + return make_pair(t, begin + n); + } +} + +} // namespace detail + + +// Model the concept for unsigned integral types + +// uint8_t +template +It toNetworkByteStream(const uint8_t byte, It out) +{ + return detail::copyToByteStream(byte, std::move(out)); +} + +template <> +struct Deserialize +{ + template + static std::pair fromNetworkByteStream(It begin, It end) + { + return detail::copyFromByteStream(std::move(begin), std::move(end)); + } +}; + +// uint16_t +template +It toNetworkByteStream(uint16_t s, It out) +{ + return detail::copyToByteStream(htons(s), std::move(out)); +} + +template <> +struct Deserialize +{ + template + static std::pair fromNetworkByteStream(It begin, It end) + { + auto result = detail::copyFromByteStream(std::move(begin), std::move(end)); + result.first = ntohs(result.first); + return result; + } +}; + +// uint32_t +template +It toNetworkByteStream(uint32_t l, It out) +{ + return detail::copyToByteStream(htonl(l), std::move(out)); +} + +template <> +struct Deserialize +{ + template + static std::pair fromNetworkByteStream(It begin, It end) + { + auto result = detail::copyFromByteStream(std::move(begin), std::move(end)); + result.first = ntohl(result.first); + return result; + } +}; + +// int32_t in terms of uint32_t +template +It toNetworkByteStream(int32_t l, It out) +{ + return toNetworkByteStream(reinterpret_cast(l), std::move(out)); +} + +template <> +struct Deserialize +{ + template + static std::pair fromNetworkByteStream(It begin, It end) + { + auto result = + Deserialize::fromNetworkByteStream(std::move(begin), std::move(end)); + return std::make_pair(reinterpret_cast(result.first), result.second); + } +}; + +// uint64_t +template +It toNetworkByteStream(uint64_t ll, It out) +{ + return detail::copyToByteStream(htonll(ll), std::move(out)); +} + +template <> +struct Deserialize +{ + template + static std::pair fromNetworkByteStream(It begin, It end) + { + auto result = detail::copyFromByteStream(std::move(begin), std::move(end)); + result.first = ntohll(result.first); + return result; + } +}; + +// int64_t in terms of uint64_t +template +It toNetworkByteStream(int64_t ll, It out) +{ + return toNetworkByteStream(reinterpret_cast(ll), std::move(out)); +} + +template <> +struct Deserialize +{ + template + static std::pair fromNetworkByteStream(It begin, It end) + { + auto result = + Deserialize::fromNetworkByteStream(std::move(begin), std::move(end)); + return std::make_pair(reinterpret_cast(result.first), result.second); + } +}; + +// bool +inline std::uint32_t sizeInByteStream(bool) +{ + return sizeof(uint8_t); +} + +template +It toNetworkByteStream(bool bl, It out) +{ + return toNetworkByteStream(static_cast(bl), std::move(out)); +} + +template <> +struct Deserialize +{ + template + static std::pair fromNetworkByteStream(It begin, It end) + { + auto result = + Deserialize::fromNetworkByteStream(std::move(begin), std::move(end)); + return std::make_pair(result.first != 0, result.second); + } +}; + +// std::chrono::microseconds +inline std::uint32_t sizeInByteStream(const std::chrono::microseconds micros) +{ + return sizeInByteStream(micros.count()); +} + +template +It toNetworkByteStream(const std::chrono::microseconds micros, It out) +{ + static_assert(sizeof(int64_t) == sizeof(std::chrono::microseconds::rep), + "The size of microseconds::rep must matche the size of int64_t."); + return toNetworkByteStream(static_cast(micros.count()), std::move(out)); +} + +template <> +struct Deserialize +{ + template + static std::pair fromNetworkByteStream(It begin, It end) + { + using namespace std; + auto result = + Deserialize::fromNetworkByteStream(std::move(begin), std::move(end)); + return make_pair(chrono::microseconds{result.first}, result.second); + } +}; + +namespace detail +{ + +// Generic serialize/deserialize utilities for containers + +template +std::uint32_t containerSizeInByteStream(const Container& container) +{ + std::uint32_t totalSize = 0; + for (const auto& val : container) + { + totalSize += sizeInByteStream(val); + } + return totalSize; +} + +template +It containerToNetworkByteStream(const Container& container, It out) +{ + for (const auto& val : container) + { + out = toNetworkByteStream(val, out); + } + return out; +} + +template +BytesIt deserializeContainer(BytesIt bytesBegin, + const BytesIt bytesEnd, + InsertIt contBegin, + const std::uint32_t maxElements) +{ + using namespace std; + std::uint32_t numElements = 0; + while (bytesBegin < bytesEnd && numElements < maxElements) + { + T newVal; + tie(newVal, bytesBegin) = Deserialize::fromNetworkByteStream(bytesBegin, bytesEnd); + *contBegin++ = newVal; + ++numElements; + } + return bytesBegin; +} + +} // namespace detail + +// Need specific overloads for each container type, but use above +// utilities for common implementation + +// array +template +std::uint32_t sizeInByteStream(const std::array& arr) +{ + return detail::containerSizeInByteStream(arr); +} + +template +It toNetworkByteStream(const std::array& arr, It out) +{ + return detail::containerToNetworkByteStream(arr, std::move(out)); +} + +template +struct Deserialize> +{ + template + static std::pair, It> fromNetworkByteStream(It begin, It end) + { + using namespace std; + array result{}; + auto resultIt = detail::deserializeContainer( + std::move(begin), std::move(end), std::move(result.begin()), Size); + return make_pair(std::move(result), std::move(resultIt)); + } +}; + +// vector +template +std::uint32_t sizeInByteStream(const std::vector& vec) +{ + return sizeof(uint32_t) + detail::containerSizeInByteStream(vec); +} + +template +It toNetworkByteStream(const std::vector& vec, It out) +{ + out = toNetworkByteStream(static_cast(vec.size()), out); + return detail::containerToNetworkByteStream(vec, std::move(out)); +} + +template +struct Deserialize> +{ + template + static std::pair, It> fromNetworkByteStream( + It bytesBegin, It bytesEnd) + { + using namespace std; + auto result_size = + Deserialize::fromNetworkByteStream(std::move(bytesBegin), bytesEnd); + vector result; + auto resultIt = detail::deserializeContainer(std::move(result_size.second), + std::move(bytesEnd), back_inserter(result), result_size.first); + return make_pair(std::move(result), std::move(resultIt)); + } +}; + +// 2-tuple +template +std::uint32_t sizeInByteStream(const std::tuple& tup) +{ + return sizeInByteStream(std::get<0>(tup)) + sizeInByteStream(std::get<1>(tup)); +} + +template +It toNetworkByteStream(const std::tuple& tup, It out) +{ + return toNetworkByteStream( + std::get<1>(tup), toNetworkByteStream(std::get<0>(tup), std::move(out))); +} + +template +struct Deserialize> +{ + template + static std::pair, It> fromNetworkByteStream(It begin, It end) + { + using namespace std; + auto xres = Deserialize::fromNetworkByteStream(begin, end); + auto yres = Deserialize::fromNetworkByteStream(xres.second, end); + return make_pair( + make_tuple(std::move(xres.first), std::move(yres.first)), std::move(yres.second)); + } +}; + +// 3-tuple +template +std::uint32_t sizeInByteStream(const std::tuple& tup) +{ + return sizeInByteStream(std::get<0>(tup)) + sizeInByteStream(std::get<1>(tup)) + + sizeInByteStream(std::get<2>(tup)); +} + +template +It toNetworkByteStream(const std::tuple& tup, It out) +{ + return toNetworkByteStream( + std::get<2>(tup), toNetworkByteStream(std::get<1>(tup), + toNetworkByteStream(std::get<0>(tup), std::move(out)))); +} + +template +struct Deserialize> +{ + template + static std::pair, It> fromNetworkByteStream(It begin, It end) + { + using namespace std; + auto xres = Deserialize::fromNetworkByteStream(begin, end); + auto yres = Deserialize::fromNetworkByteStream(xres.second, end); + auto zres = Deserialize::fromNetworkByteStream(yres.second, end); + return make_pair( + make_tuple(std::move(xres.first), std::move(yres.first), std::move(zres.first)), + std::move(zres.second)); + } +}; + +} // namespace discovery +} // namespace ableton diff --git a/tidal-link/link/include/ableton/discovery/Payload.hpp b/tidal-link/link/include/ableton/discovery/Payload.hpp new file mode 100644 index 000000000..1d48caa7e --- /dev/null +++ b/tidal-link/link/include/ableton/discovery/Payload.hpp @@ -0,0 +1,296 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include + +namespace ableton +{ +namespace discovery +{ + +struct PayloadEntryHeader +{ + using Key = std::uint32_t; + using Size = std::uint32_t; + + Key key; + Size size; + + friend Size sizeInByteStream(const PayloadEntryHeader& header) + { + return sizeInByteStream(header.key) + sizeInByteStream(header.size); + } + + template + friend It toNetworkByteStream(const PayloadEntryHeader& header, It out) + { + return toNetworkByteStream( + header.size, toNetworkByteStream(header.key, std::move(out))); + } + + template + static std::pair fromNetworkByteStream(It begin, const It end) + { + using namespace std; + Key key; + Size size; + tie(key, begin) = Deserialize::fromNetworkByteStream(begin, end); + tie(size, begin) = Deserialize::fromNetworkByteStream(begin, end); + return make_pair( + PayloadEntryHeader{std::move(key), std::move(size)}, std::move(begin)); + } +}; + +template +struct PayloadEntry +{ + PayloadEntry(EntryType entryVal) + : value(std::move(entryVal)) + { + header = {EntryType::key, sizeInByteStream(value)}; + } + + PayloadEntryHeader header; + EntryType value; + + friend std::uint32_t sizeInByteStream(const PayloadEntry& entry) + { + return sizeInByteStream(entry.header) + sizeInByteStream(entry.value); + } + + template + friend It toNetworkByteStream(const PayloadEntry& entry, It out) + { + return toNetworkByteStream( + entry.value, toNetworkByteStream(entry.header, std::move(out))); + } +}; + +namespace detail +{ + +template +using HandlerMap = + std::unordered_map>; + +// Given an index of handlers and a byte range, parse the bytes as a +// sequence of payload entries and invoke the appropriate handler for +// each entry type. Entries that are encountered that do not have a +// corresponding handler in the map are ignored. Throws +// std::runtime_error if parsing fails for any entry. Note that if an +// exception is thrown, some of the handlers may have already been called. +template +void parseByteStream(HandlerMap& map, It bsBegin, const It bsEnd) +{ + using namespace std; + + while (bsBegin < bsEnd) + { + // Try to parse an entry header at this location in the byte stream + PayloadEntryHeader header; + It valueBegin; + tie(header, valueBegin) = + Deserialize::fromNetworkByteStream(bsBegin, bsEnd); + + // Ensure that the reported size of the entry does not exceed the + // length of the byte stream + It valueEnd = valueBegin + header.size; + if (bsEnd < valueEnd) + { + throw range_error("Payload with incorrect size."); + } + + // The next entry will start at the end of this one + bsBegin = valueEnd; + + // Use the appropriate handler for this entry, if available + auto handlerIt = map.find(header.key); + if (handlerIt != end(map)) + { + handlerIt->second(std::move(valueBegin), std::move(valueEnd)); + } + } +} + +} // namespace detail + + +// Payload encoding +template +struct Payload; + +template +struct Payload +{ + Payload(First first, Rest rest) + : mFirst(std::move(first)) + , mRest(std::move(rest)) + { + } + + Payload(PayloadEntry first, Rest rest) + : mFirst(std::move(first)) + , mRest(std::move(rest)) + { + } + + template + using PayloadSum = + Payload>; + + // Concatenate payloads together into a single payload + template + friend PayloadSum operator+( + Payload lhs, Payload rhs) + { + return {std::move(lhs.mFirst), std::move(lhs.mRest) + std::move(rhs)}; + } + + friend std::size_t sizeInByteStream(const Payload& payload) + { + return sizeInByteStream(payload.mFirst) + sizeInByteStream(payload.mRest); + } + + template + friend It toNetworkByteStream(const Payload& payload, It streamIt) + { + return toNetworkByteStream( + payload.mRest, toNetworkByteStream(payload.mFirst, std::move(streamIt))); + } + + PayloadEntry mFirst; + Rest mRest; +}; + +template <> +struct Payload<> +{ + template + using PayloadSum = Payload; + + template + friend PayloadSum operator+(Payload, Payload rhs) + { + return rhs; + } + + friend std::size_t sizeInByteStream(const Payload&) + { + return 0; + } + + template + friend It toNetworkByteStream(const Payload&, It streamIt) + { + return streamIt; + } +}; + +template +struct PayloadBuilder; + +// Payload factory function +template +auto makePayload(Entries... entries) + -> decltype(PayloadBuilder{}(std::move(entries)...)) +{ + return PayloadBuilder{}(std::move(entries)...); +} + +template +struct PayloadBuilder +{ + auto operator()(First first, Rest... rest) + -> Payload + { + return {std::move(first), makePayload(std::move(rest)...)}; + } +}; + +template <> +struct PayloadBuilder<> +{ + Payload<> operator()() + { + return {}; + } +}; + +// Parse payloads to values +template +struct ParsePayload; + +template +struct ParsePayload +{ + template + static void parse(It begin, It end, Handlers... handlers) + { + detail::HandlerMap map; + collectHandlers(map, std::move(handlers)...); + detail::parseByteStream(map, std::move(begin), std::move(end)); + } + + template + static void collectHandlers( + detail::HandlerMap& map, FirstHandler handler, RestHandlers... rest) + { + using namespace std; + map[First::key] = [handler](const It begin, const It end) { + const auto res = First::fromNetworkByteStream(begin, end); + if (res.second != end) + { + std::ostringstream stringStream; + stringStream << "Parsing payload entry " << First::key + << " did not consume the expected number of bytes. " + << " Expected: " << distance(begin, end) + << ", Actual: " << distance(begin, res.second); + throw range_error(stringStream.str()); + } + handler(res.first); + }; + + ParsePayload::collectHandlers(map, std::move(rest)...); + } +}; + +template <> +struct ParsePayload<> +{ + template + static void collectHandlers(detail::HandlerMap&) + { + } +}; + +template +void parsePayload(It begin, It end, Handlers... handlers) +{ + using namespace std; + ParsePayload::parse( + std::move(begin), std::move(end), std::move(handlers)...); +} + +} // namespace discovery +} // namespace ableton diff --git a/tidal-link/link/include/ableton/discovery/PeerGateway.hpp b/tidal-link/link/include/ableton/discovery/PeerGateway.hpp new file mode 100644 index 000000000..db434394c --- /dev/null +++ b/tidal-link/link/include/ableton/discovery/PeerGateway.hpp @@ -0,0 +1,251 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include + +namespace ableton +{ +namespace discovery +{ + +template +class PeerGateway +{ +public: + // The peer types are defined by the observer but must match with those + // used by the Messenger + using ObserverT = typename util::Injected::type; + using NodeState = typename ObserverT::GatewayObserverNodeState; + using NodeId = typename ObserverT::GatewayObserverNodeId; + using Timer = typename util::Injected::type::Timer; + using TimerError = typename Timer::ErrorCode; + + PeerGateway(util::Injected messenger, + util::Injected observer, + util::Injected io) + : mpImpl(new Impl(std::move(messenger), std::move(observer), std::move(io))) + { + mpImpl->listen(); + } + + PeerGateway(const PeerGateway&) = delete; + PeerGateway& operator=(const PeerGateway&) = delete; + + PeerGateway(PeerGateway&& rhs) + : mpImpl(std::move(rhs.mpImpl)) + { + } + + void updateState(NodeState state) + { + mpImpl->updateState(std::move(state)); + } + +private: + using PeerTimeout = std::pair; + using PeerTimeouts = std::vector; + + struct Impl : std::enable_shared_from_this + { + Impl(util::Injected messenger, + util::Injected observer, + util::Injected io) + : mMessenger(std::move(messenger)) + , mObserver(std::move(observer)) + , mIo(std::move(io)) + , mPruneTimer(mIo->makeTimer()) + { + } + + void updateState(NodeState state) + { + mMessenger->updateState(std::move(state)); + try + { + mMessenger->broadcastState(); + } + catch (const std::runtime_error& err) + { + info(mIo->log()) << "State broadcast failed on gateway: " << err.what(); + } + } + + void listen() + { + mMessenger->receive(util::makeAsyncSafe(this->shared_from_this())); + } + + // Operators for handling incoming messages + void operator()(const PeerState& msg) + { + onPeerState(msg.peerState, msg.ttl); + listen(); + } + + void operator()(const ByeBye& msg) + { + onByeBye(msg.peerId); + listen(); + } + + void onPeerState(const NodeState& nodeState, const int ttl) + { + using namespace std; + const auto peerId = nodeState.ident(); + const auto existing = findPeer(peerId); + if (existing != end(mPeerTimeouts)) + { + // If the peer is already present in our timeout list, remove it + // as it will be re-inserted below. + mPeerTimeouts.erase(existing); + } + + auto newTo = make_pair(mPruneTimer.now() + std::chrono::seconds(ttl), peerId); + mPeerTimeouts.insert( + upper_bound(begin(mPeerTimeouts), end(mPeerTimeouts), newTo, TimeoutCompare{}), + std::move(newTo)); + + sawPeer(*mObserver, nodeState); + scheduleNextPruning(); + } + + void onByeBye(const NodeId& peerId) + { + const auto it = findPeer(peerId); + if (it != mPeerTimeouts.end()) + { + peerLeft(*mObserver, it->second); + mPeerTimeouts.erase(it); + } + } + + void pruneExpiredPeers() + { + using namespace std; + + const auto test = make_pair(mPruneTimer.now(), NodeId{}); + debug(mIo->log()) << "pruning peers @ " << test.first.time_since_epoch().count(); + + const auto endExpired = + lower_bound(begin(mPeerTimeouts), end(mPeerTimeouts), test, TimeoutCompare{}); + + for_each(begin(mPeerTimeouts), endExpired, [this](const PeerTimeout& pto) { + info(mIo->log()) << "pruning peer " << pto.second; + peerTimedOut(*mObserver, pto.second); + }); + mPeerTimeouts.erase(begin(mPeerTimeouts), endExpired); + scheduleNextPruning(); + } + + void scheduleNextPruning() + { + // Find the next peer to expire and set the timer based on it + if (!mPeerTimeouts.empty()) + { + // Add a second of padding to the timer to avoid over-eager timeouts + const auto t = mPeerTimeouts.front().first + std::chrono::seconds(1); + + debug(mIo->log()) << "scheduling next pruning for " + << t.time_since_epoch().count() << " because of peer " + << mPeerTimeouts.front().second; + + mPruneTimer.expires_at(t); + mPruneTimer.async_wait([this](const TimerError e) { + if (!e) + { + pruneExpiredPeers(); + } + }); + } + } + + struct TimeoutCompare + { + bool operator()(const PeerTimeout& lhs, const PeerTimeout& rhs) const + { + return lhs.first < rhs.first; + } + }; + + typename PeerTimeouts::iterator findPeer(const NodeId& peerId) + { + return std::find_if(begin(mPeerTimeouts), end(mPeerTimeouts), + [&peerId](const PeerTimeout& pto) { return pto.second == peerId; }); + } + + util::Injected mMessenger; + util::Injected mObserver; + util::Injected mIo; + Timer mPruneTimer; + PeerTimeouts mPeerTimeouts; // Invariant: sorted by time_point + }; + + std::shared_ptr mpImpl; +}; + +template +PeerGateway makePeerGateway( + util::Injected messenger, + util::Injected observer, + util::Injected io) +{ + return {std::move(messenger), std::move(observer), std::move(io)}; +} + +// IpV4 gateway types +template +using IpV4Messenger = UdpMessenger< + IpV4Interface::type&, v1::kMaxMessageSize>, + StateQuery, + IoContext>; + +template +using IpV4Gateway = + PeerGateway::type&>, + PeerObserver, + IoContext>; + +// Factory function to bind a PeerGateway to an IpV4Interface with the given address. +template +IpV4Gateway makeIpV4Gateway( + util::Injected io, + const asio::ip::address_v4& addr, + util::Injected observer, + NodeState state) +{ + using namespace std; + using namespace util; + + const uint8_t ttl = 5; + const uint8_t ttlRatio = 20; + + auto iface = makeIpV4Interface(injectRef(*io), addr); + + auto messenger = makeUdpMessenger( + injectVal(std::move(iface)), std::move(state), injectRef(*io), ttl, ttlRatio); + return {injectVal(std::move(messenger)), std::move(observer), std::move(io)}; +} + +} // namespace discovery +} // namespace ableton diff --git a/tidal-link/link/include/ableton/discovery/PeerGateways.hpp b/tidal-link/link/include/ableton/discovery/PeerGateways.hpp new file mode 100644 index 000000000..bdefbaef2 --- /dev/null +++ b/tidal-link/link/include/ableton/discovery/PeerGateways.hpp @@ -0,0 +1,182 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace discovery +{ + +// GatewayFactory must have an operator()(NodeState, IoRef, asio::ip::address) +// that constructs a new PeerGateway on a given interface address. +template +class PeerGateways +{ +public: + using IoType = typename util::Injected::type; + using Gateway = typename std::result_of, asio::ip::address)>::type; + using GatewayMap = std::map; + + PeerGateways(const std::chrono::seconds rescanPeriod, + NodeState state, + GatewayFactory factory, + util::Injected io) + : mIo(std::move(io)) + { + mpScannerCallback = + std::make_shared(std::move(state), std::move(factory), *mIo); + mpScanner = std::make_shared( + rescanPeriod, util::injectShared(mpScannerCallback), util::injectRef(*mIo)); + } + + ~PeerGateways() + { + mpScanner.reset(); + mpScannerCallback.reset(); + } + + PeerGateways(const PeerGateways&) = delete; + PeerGateways& operator=(const PeerGateways&) = delete; + + PeerGateways(PeerGateways&&) = delete; + PeerGateways& operator=(PeerGateways&&) = delete; + + void enable(const bool bEnable) + { + mpScannerCallback->mGateways.clear(); + mpScanner->enable(bEnable); + } + + template + void withGateways(Handler handler) + { + handler(mpScannerCallback->mGateways.begin(), mpScannerCallback->mGateways.end()); + } + + void updateNodeState(const NodeState& state) + { + mpScannerCallback->mState = state; + for (const auto& entry : mpScannerCallback->mGateways) + { + entry.second->updateNodeState(state); + } + } + + // If a gateway has become non-responsive or is throwing exceptions, + // this method can be invoked to either fix it or discard it. + void repairGateway(const asio::ip::address& gatewayAddr) + { + if (mpScannerCallback->mGateways.erase(gatewayAddr)) + { + // If we erased a gateway, rescan again immediately so that + // we will re-initialize it if it's still present + mpScanner->scan(); + } + } + +private: + struct Callback + { + Callback(NodeState state, GatewayFactory factory, IoType& io) + : mState(std::move(state)) + , mFactory(std::move(factory)) + , mIo(io) + { + } + + template + void operator()(const AddrRange& range) + { + using namespace std; + // Get the set of current addresses. + vector curAddrs; + curAddrs.reserve(mGateways.size()); + transform(std::begin(mGateways), std::end(mGateways), back_inserter(curAddrs), + [](const typename GatewayMap::value_type& vt) { return vt.first; }); + + // Now use set_difference to determine the set of addresses that + // are new and the set of cur addresses that are no longer there + vector newAddrs; + set_difference(std::begin(range), std::end(range), std::begin(curAddrs), + std::end(curAddrs), back_inserter(newAddrs)); + + vector staleAddrs; + set_difference(std::begin(curAddrs), std::end(curAddrs), std::begin(range), + std::end(range), back_inserter(staleAddrs)); + + // Remove the stale addresses + for (const auto& addr : staleAddrs) + { + mGateways.erase(addr); + } + + // Add the new addresses + for (const auto& addr : newAddrs) + { + try + { + // Only handle v4 for now + if (addr.is_v4()) + { + info(mIo.log()) << "initializing peer gateway on interface " << addr; + mGateways.emplace(addr, mFactory(mState, util::injectRef(mIo), addr.to_v4())); + } + } + catch (const runtime_error& e) + { + warning(mIo.log()) << "failed to init gateway on interface " << addr + << " reason: " << e.what(); + } + } + } + + NodeState mState; + GatewayFactory mFactory; + IoType& mIo; + GatewayMap mGateways; + }; + + using Scanner = InterfaceScanner, IoType&>; + std::shared_ptr mpScannerCallback; + std::shared_ptr mpScanner; + util::Injected mIo; +}; + +// Factory function +template +std::unique_ptr> makePeerGateways( + const std::chrono::seconds rescanPeriod, + NodeState state, + GatewayFactory factory, + util::Injected io) +{ + using namespace std; + using Gateways = PeerGateways; + return unique_ptr{ + new Gateways{rescanPeriod, std::move(state), std::move(factory), std::move(io)}}; +} + +} // namespace discovery +} // namespace ableton diff --git a/tidal-link/link/include/ableton/discovery/Service.hpp b/tidal-link/link/include/ableton/discovery/Service.hpp new file mode 100644 index 000000000..8898fce43 --- /dev/null +++ b/tidal-link/link/include/ableton/discovery/Service.hpp @@ -0,0 +1,72 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include + +namespace ableton +{ +namespace discovery +{ + +template +class Service +{ +public: + using ServicePeerGateways = PeerGateways; + + Service(NodeState state, GatewayFactory factory, util::Injected io) + : mGateways( + std::chrono::seconds(5), std::move(state), std::move(factory), std::move(io)) + { + } + + void enable(const bool bEnable) + { + mGateways.enable(bEnable); + } + + // Asynchronously operate on the current set of peer gateways. The + // handler will be invoked in the service's io context. + template + void withGateways(Handler handler) + { + mGateways.withGateways(std::move(handler)); + } + + void updateNodeState(const NodeState& state) + { + mGateways.updateNodeState(state); + } + + // Repair the gateway with the given address if possible. Its + // sockets may have been closed, for example, and the gateway needs + // to be regenerated. + void repairGateway(const asio::ip::address& gatewayAddr) + { + mGateways.repairGateway(gatewayAddr); + } + +private: + ServicePeerGateways mGateways; +}; + +} // namespace discovery +} // namespace ableton diff --git a/tidal-link/link/include/ableton/discovery/UdpMessenger.hpp b/tidal-link/link/include/ableton/discovery/UdpMessenger.hpp new file mode 100644 index 000000000..c15c6943a --- /dev/null +++ b/tidal-link/link/include/ableton/discovery/UdpMessenger.hpp @@ -0,0 +1,330 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include +#include +#include +#include +#include + +namespace ableton +{ +namespace discovery +{ + +// An exception thrown when sending a udp message fails. Stores the +// interface through which the sending failed. +struct UdpSendException : std::runtime_error +{ + UdpSendException(const std::runtime_error& e, asio::ip::address ifAddr) + : std::runtime_error(e.what()) + , interfaceAddr(std::move(ifAddr)) + { + } + + asio::ip::address interfaceAddr; +}; + +// Throws UdpSendException +template +void sendUdpMessage(Interface& iface, + NodeId from, + const uint8_t ttl, + const v1::MessageType messageType, + const Payload& payload, + const asio::ip::udp::endpoint& to) +{ + using namespace std; + v1::MessageBuffer buffer; + const auto messageBegin = begin(buffer); + const auto messageEnd = + v1::detail::encodeMessage(std::move(from), ttl, messageType, payload, messageBegin); + const auto numBytes = static_cast(distance(messageBegin, messageEnd)); + try + { + iface.send(buffer.data(), numBytes, to); + } + catch (const std::runtime_error& err) + { + throw UdpSendException{err, iface.endpoint().address()}; + } +} + +// UdpMessenger uses a "shared_ptr pImpl" pattern to make it movable +// and to support safe async handler callbacks when receiving messages +// on the given interface. +template +class UdpMessenger +{ +public: + using NodeState = NodeStateT; + using NodeId = typename NodeState::IdType; + using Timer = typename util::Injected::type::Timer; + using TimerError = typename Timer::ErrorCode; + using TimePoint = typename Timer::TimePoint; + + UdpMessenger(util::Injected iface, + NodeState state, + util::Injected io, + const uint8_t ttl, + const uint8_t ttlRatio) + : mpImpl(std::make_shared( + std::move(iface), std::move(state), std::move(io), ttl, ttlRatio)) + { + // We need to always listen for incoming traffic in order to + // respond to peer state broadcasts + mpImpl->listen(MulticastTag{}); + mpImpl->listen(UnicastTag{}); + mpImpl->broadcastState(); + } + + UdpMessenger(const UdpMessenger&) = delete; + UdpMessenger& operator=(const UdpMessenger&) = delete; + + UdpMessenger(UdpMessenger&& rhs) + : mpImpl(std::move(rhs.mpImpl)) + { + } + + ~UdpMessenger() + { + if (mpImpl != nullptr) + { + try + { + mpImpl->sendByeBye(); + } + catch (const UdpSendException& err) + { + debug(mpImpl->mIo->log()) << "Failed to send bye bye message: " << err.what(); + } + } + } + + void updateState(NodeState state) + { + mpImpl->updateState(std::move(state)); + } + + // Broadcast the current state of the system to all peers. May throw + // std::runtime_error if assembling a broadcast message fails or if + // there is an error at the transport layer. Throws on failure. + void broadcastState() + { + mpImpl->broadcastState(); + } + + // Asynchronous receive function for incoming messages from peers. Will + // return immediately and the handler will be invoked when a message + // is received. Handler must have operator() overloads for PeerState and + // ByeBye messages. + template + void receive(Handler handler) + { + mpImpl->setReceiveHandler(std::move(handler)); + } + +private: + struct Impl : std::enable_shared_from_this + { + Impl(util::Injected iface, + NodeState state, + util::Injected io, + const uint8_t ttl, + const uint8_t ttlRatio) + : mIo(std::move(io)) + , mInterface(std::move(iface)) + , mState(std::move(state)) + , mTimer(mIo->makeTimer()) + , mLastBroadcastTime{} + , mTtl(ttl) + , mTtlRatio(ttlRatio) + , mPeerStateHandler([](PeerState) {}) + , mByeByeHandler([](ByeBye) {}) + { + } + + template + void setReceiveHandler(Handler handler) + { + mPeerStateHandler = [handler]( + PeerState state) { handler(std::move(state)); }; + + mByeByeHandler = [handler](ByeBye byeBye) { handler(std::move(byeBye)); }; + } + + void sendByeBye() + { + sendUdpMessage( + *mInterface, mState.ident(), 0, v1::kByeBye, makePayload(), multicastEndpoint()); + } + + void updateState(NodeState state) + { + mState = std::move(state); + } + + void broadcastState() + { + using namespace std::chrono; + + const auto minBroadcastPeriod = milliseconds{50}; + const auto nominalBroadcastPeriod = milliseconds(mTtl * 1000 / mTtlRatio); + const auto timeSinceLastBroadcast = + duration_cast(mTimer.now() - mLastBroadcastTime); + + // The rate is limited to maxBroadcastRate to prevent flooding the network. + const auto delay = minBroadcastPeriod - timeSinceLastBroadcast; + + // Schedule the next broadcast before we actually send the + // message so that if sending throws an exception we are still + // scheduled to try again. We want to keep trying at our + // interval as long as this instance is alive. + mTimer.expires_from_now(delay > milliseconds{0} ? delay : nominalBroadcastPeriod); + mTimer.async_wait([this](const TimerError e) { + if (!e) + { + broadcastState(); + } + }); + + // If we're not delaying, broadcast now + if (delay < milliseconds{1}) + { + debug(mIo->log()) << "Broadcasting state"; + sendPeerState(v1::kAlive, multicastEndpoint()); + } + } + + void sendPeerState( + const v1::MessageType messageType, const asio::ip::udp::endpoint& to) + { + sendUdpMessage( + *mInterface, mState.ident(), mTtl, messageType, toPayload(mState), to); + mLastBroadcastTime = mTimer.now(); + } + + void sendResponse(const asio::ip::udp::endpoint& to) + { + sendPeerState(v1::kResponse, to); + } + + template + void listen(Tag tag) + { + mInterface->receive(util::makeAsyncSafe(this->shared_from_this()), tag); + } + + template + void operator()(Tag tag, + const asio::ip::udp::endpoint& from, + const It messageBegin, + const It messageEnd) + { + auto result = v1::parseMessageHeader(messageBegin, messageEnd); + + const auto& header = result.first; + // Ignore messages from self and other groups + if (header.ident != mState.ident() && header.groupId == 0) + { + debug(mIo->log()) << "Received message type " + << static_cast(header.messageType) << " from peer " + << header.ident; + + switch (header.messageType) + { + case v1::kAlive: + sendResponse(from); + receivePeerState(std::move(result.first), result.second, messageEnd); + break; + case v1::kResponse: + receivePeerState(std::move(result.first), result.second, messageEnd); + break; + case v1::kByeBye: + receiveByeBye(std::move(result.first.ident)); + break; + default: + info(mIo->log()) << "Unknown message received of type: " << header.messageType; + } + } + listen(tag); + } + + template + void receivePeerState( + v1::MessageHeader header, It payloadBegin, It payloadEnd) + { + try + { + auto state = NodeState::fromPayload( + std::move(header.ident), std::move(payloadBegin), std::move(payloadEnd)); + + // Handlers must only be called once + auto handler = std::move(mPeerStateHandler); + mPeerStateHandler = [](PeerState) {}; + handler(PeerState{std::move(state), header.ttl}); + } + catch (const std::runtime_error& err) + { + info(mIo->log()) << "Ignoring peer state message: " << err.what(); + } + } + + void receiveByeBye(NodeId nodeId) + { + // Handlers must only be called once + auto byeByeHandler = std::move(mByeByeHandler); + mByeByeHandler = [](ByeBye) {}; + byeByeHandler(ByeBye{std::move(nodeId)}); + } + + util::Injected mIo; + util::Injected mInterface; + NodeState mState; + Timer mTimer; + TimePoint mLastBroadcastTime; + uint8_t mTtl; + uint8_t mTtlRatio; + std::function)> mPeerStateHandler; + std::function)> mByeByeHandler; + }; + + std::shared_ptr mpImpl; +}; + +// Factory function +template +UdpMessenger makeUdpMessenger( + util::Injected iface, + NodeState state, + util::Injected io, + const uint8_t ttl, + const uint8_t ttlRatio) +{ + return UdpMessenger{ + std::move(iface), std::move(state), std::move(io), ttl, ttlRatio}; +} + +} // namespace discovery +} // namespace ableton diff --git a/tidal-link/link/include/ableton/discovery/test/Interface.hpp b/tidal-link/link/include/ableton/discovery/test/Interface.hpp new file mode 100644 index 000000000..f538856ff --- /dev/null +++ b/tidal-link/link/include/ableton/discovery/test/Interface.hpp @@ -0,0 +1,75 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include + +namespace ableton +{ +namespace discovery +{ +namespace test +{ + +class Interface +{ +public: + void send(const uint8_t* const bytes, + const size_t numBytes, + const asio::ip::udp::endpoint& endpoint) + { + sentMessages.push_back( + std::make_pair(std::vector{bytes, bytes + numBytes}, endpoint)); + } + + template + void receive(Callback callback, Tag tag) + { + mCallback = [callback, tag](const asio::ip::udp::endpoint& from, + const std::vector& buffer) { + callback(tag, from, begin(buffer), end(buffer)); + }; + } + + template + void incomingMessage( + const asio::ip::udp::endpoint& from, It messageBegin, It messageEnd) + { + std::vector buffer{messageBegin, messageEnd}; + mCallback(from, buffer); + } + + asio::ip::udp::endpoint endpoint() const + { + return asio::ip::udp::endpoint({}, 0); + } + + using SentMessage = std::pair, asio::ip::udp::endpoint>; + std::vector sentMessages; + +private: + using ReceiveCallback = + std::function&)>; + ReceiveCallback mCallback; +}; + +} // namespace test +} // namespace discovery +} // namespace ableton diff --git a/tidal-link/link/include/ableton/discovery/test/PayloadEntries.hpp b/tidal-link/link/include/ableton/discovery/test/PayloadEntries.hpp new file mode 100644 index 000000000..1962dad99 --- /dev/null +++ b/tidal-link/link/include/ableton/discovery/test/PayloadEntries.hpp @@ -0,0 +1,133 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include + +namespace ableton +{ +namespace discovery +{ +namespace test +{ + +// Test payload entries + +// A fixed-size entry type +struct Foo +{ + static const std::int32_t key = '_foo'; + static_assert(key == 0x5f666f6f, "Unexpected byte order"); + + std::int32_t fooVal; + + friend std::uint32_t sizeInByteStream(const Foo& foo) + { + // Namespace qualification is needed to avoid ambiguous function definitions + return discovery::sizeInByteStream(foo.fooVal); + } + + template + friend It toNetworkByteStream(const Foo& foo, It out) + { + return discovery::toNetworkByteStream(foo.fooVal, std::move(out)); + } + + template + static std::pair fromNetworkByteStream(It begin, It end) + { + auto result = Deserialize::fromNetworkByteStream( + std::move(begin), std::move(end)); + return std::make_pair(Foo{std::move(result.first)}, std::move(result.second)); + } +}; + +// A variable-size entry type +struct Bar +{ + static const std::int32_t key = '_bar'; + static_assert(key == 0x5f626172, "Unexpected byte order"); + + std::vector barVals; + + friend std::uint32_t sizeInByteStream(const Bar& bar) + { + return discovery::sizeInByteStream(bar.barVals); + } + + template + friend It toNetworkByteStream(const Bar& bar, It out) + { + return discovery::toNetworkByteStream(bar.barVals, out); + } + + template + static std::pair fromNetworkByteStream(It begin, It end) + { + auto result = Deserialize::fromNetworkByteStream( + std::move(begin), std::move(end)); + return std::make_pair(Bar{std::move(result.first)}, std::move(result.second)); + } +}; + +// An entry type with two vectors +struct Foobar +{ + static const std::int32_t key = 'fbar'; + static_assert(key == 0x66626172, "Unexpected byte order"); + + using FoobarVector = std::vector; + using FoobarTuple = std::tuple; + + FoobarVector fooVals; + FoobarVector barVals; + + friend std::uint32_t sizeInByteStream(const Foobar& foobar) + { + return discovery::sizeInByteStream(foobar.asTuple()); + } + + template + friend It toNetworkByteStream(const Foobar& foobar, It out) + { + return discovery::toNetworkByteStream(foobar.asTuple(), out); + } + + template + static std::pair fromNetworkByteStream(It begin, It end) + { + const auto result = + Deserialize::fromNetworkByteStream(std::move(begin), std::move(end)); + const auto foobar = Foobar{std::get<0>(result.first), std::get<1>(result.first)}; + return std::make_pair(std::move(foobar), std::move(result.second)); + } + + FoobarTuple asTuple() const + { + return std::make_tuple(fooVals, barVals); + } +}; + +} // namespace test +} // namespace discovery +} // namespace ableton diff --git a/tidal-link/link/include/ableton/discovery/test/Socket.hpp b/tidal-link/link/include/ableton/discovery/test/Socket.hpp new file mode 100644 index 000000000..2983bcefb --- /dev/null +++ b/tidal-link/link/include/ableton/discovery/test/Socket.hpp @@ -0,0 +1,85 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace discovery +{ +namespace test +{ + +class Socket +{ +public: + Socket(util::test::IoService&) + { + } + + friend void configureUnicastSocket(Socket&, const asio::ip::address_v4&) + { + } + + std::size_t send( + const uint8_t* const pData, const size_t numBytes, const asio::ip::udp::endpoint& to) + { + sentMessages.push_back( + std::make_pair(std::vector{pData, pData + numBytes}, to)); + return numBytes; + } + + template + void receive(Handler handler) + { + mCallback = [handler](const asio::ip::udp::endpoint& from, + const std::vector& buffer) { + handler(from, begin(buffer), end(buffer)); + }; + } + + template + void incomingMessage( + const asio::ip::udp::endpoint& from, It messageBegin, It messageEnd) + { + std::vector buffer{messageBegin, messageEnd}; + mCallback(from, buffer); + } + + asio::ip::udp::endpoint endpoint() const + { + return asio::ip::udp::endpoint({}, 0); + } + + using SentMessage = std::pair, asio::ip::udp::endpoint>; + std::vector sentMessages; + +private: + using ReceiveCallback = + std::function&)>; + ReceiveCallback mCallback; +}; + +} // namespace test +} // namespace discovery +} // namespace ableton diff --git a/tidal-link/link/include/ableton/discovery/v1/Messages.hpp b/tidal-link/link/include/ableton/discovery/v1/Messages.hpp new file mode 100644 index 000000000..1707b8e80 --- /dev/null +++ b/tidal-link/link/include/ableton/discovery/v1/Messages.hpp @@ -0,0 +1,168 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include + +namespace ableton +{ +namespace discovery +{ +namespace v1 +{ + +// The maximum size of a message, in bytes +const std::size_t kMaxMessageSize = 512; +// Utility typedef for an array of bytes of maximum message size +using MessageBuffer = std::array; + +using MessageType = uint8_t; +using SessionGroupId = uint16_t; + +const MessageType kInvalid = 0; +const MessageType kAlive = 1; +const MessageType kResponse = 2; +const MessageType kByeBye = 3; + +template +struct MessageHeader +{ + MessageType messageType; + uint8_t ttl; + SessionGroupId groupId; + NodeId ident; + + friend std::uint32_t sizeInByteStream(const MessageHeader& header) + { + return discovery::sizeInByteStream(header.messageType) + + discovery::sizeInByteStream(header.ttl) + + discovery::sizeInByteStream(header.groupId) + + discovery::sizeInByteStream(header.ident); + } + + template + friend It toNetworkByteStream(const MessageHeader& header, It out) + { + return discovery::toNetworkByteStream(header.ident, + discovery::toNetworkByteStream(header.groupId, + discovery::toNetworkByteStream(header.ttl, + discovery::toNetworkByteStream(header.messageType, std::move(out))))); + } + + template + static std::pair fromNetworkByteStream(It begin, const It end) + { + using namespace std; + + MessageHeader header; + tie(header.messageType, begin) = + Deserialize::fromNetworkByteStream(begin, end); + tie(header.ttl, begin) = + Deserialize::fromNetworkByteStream(begin, end); + tie(header.groupId, begin) = + Deserialize::fromNetworkByteStream(begin, end); + tie(header.ident, begin) = + Deserialize::fromNetworkByteStream(begin, end); + + return make_pair(std::move(header), std::move(begin)); + } +}; + +namespace detail +{ + +// Types that are only used in the sending/parsing of messages, not +// publicly exposed. +using ProtocolHeader = std::array; +const ProtocolHeader kProtocolHeader = {{'_', 'a', 's', 'd', 'p', '_', 'v', 1}}; + +// Must have at least kMaxMessageSize bytes available in the output stream +template +It encodeMessage(NodeId from, + const uint8_t ttl, + const MessageType messageType, + const Payload& payload, + It out) +{ + using namespace std; + const MessageHeader header = {messageType, ttl, 0, std::move(from)}; + const auto messageSize = + kProtocolHeader.size() + sizeInByteStream(header) + sizeInByteStream(payload); + + if (messageSize < kMaxMessageSize) + { + return toNetworkByteStream( + payload, toNetworkByteStream(header, + copy(begin(kProtocolHeader), end(kProtocolHeader), std::move(out)))); + } + else + { + throw range_error("Exceeded maximum message size"); + } +} + +} // namespace detail + +template +It aliveMessage(NodeId from, const uint8_t ttl, const Payload& payload, It out) +{ + return detail::encodeMessage(std::move(from), ttl, kAlive, payload, std::move(out)); +} + +template +It responseMessage(NodeId from, const uint8_t ttl, const Payload& payload, It out) +{ + return detail::encodeMessage(std::move(from), ttl, kResponse, payload, std::move(out)); +} + +template +It byeByeMessage(NodeId from, It out) +{ + return detail::encodeMessage( + std::move(from), 0, kByeBye, makePayload(), std::move(out)); +} + +template +std::pair, It> parseMessageHeader(It bytesBegin, const It bytesEnd) +{ + using namespace std; + using ItDiff = typename iterator_traits::difference_type; + + MessageHeader header = {}; + const auto protocolHeaderSize = discovery::sizeInByteStream(detail::kProtocolHeader); + const auto minMessageSize = + static_cast(protocolHeaderSize + sizeInByteStream(header)); + + // If there are enough bytes in the stream to make a header and if + // the first bytes in the stream are the protocol header, then + // proceed to parse the stream. + if (distance(bytesBegin, bytesEnd) >= minMessageSize + && equal(begin(detail::kProtocolHeader), end(detail::kProtocolHeader), bytesBegin)) + { + tie(header, bytesBegin) = MessageHeader::fromNetworkByteStream( + bytesBegin + protocolHeaderSize, bytesEnd); + } + return make_pair(std::move(header), std::move(bytesBegin)); +} + +} // namespace v1 +} // namespace discovery +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/Beats.hpp b/tidal-link/link/include/ableton/link/Beats.hpp new file mode 100644 index 000000000..de8ec89f0 --- /dev/null +++ b/tidal-link/link/include/ableton/link/Beats.hpp @@ -0,0 +1,125 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +struct Beats +{ + Beats() = default; + + explicit Beats(const double beats) + : mValue(std::llround(beats * 1e6)) + { + } + + explicit Beats(const std::int64_t microBeats) + : mValue(microBeats) + { + } + + double floating() const + { + return static_cast(mValue) / 1e6; + } + + std::int64_t microBeats() const + { + return mValue; + } + + Beats operator-() const + { + return Beats{-mValue}; + } + + friend Beats abs(const Beats b) + { + return Beats{std::abs(b.mValue)}; + } + + friend Beats operator+(const Beats lhs, const Beats rhs) + { + return Beats{lhs.mValue + rhs.mValue}; + } + + friend Beats operator-(const Beats lhs, const Beats rhs) + { + return Beats{lhs.mValue - rhs.mValue}; + } + + friend Beats operator%(const Beats lhs, const Beats rhs) + { + return Beats{rhs.mValue == 0 ? 0 : (lhs.mValue % rhs.mValue)}; + } + + friend bool operator<(const Beats lhs, const Beats rhs) + { + return lhs.mValue < rhs.mValue; + } + + friend bool operator>(const Beats lhs, const Beats rhs) + { + return lhs.mValue > rhs.mValue; + } + + friend bool operator==(const Beats lhs, const Beats rhs) + { + return lhs.mValue == rhs.mValue; + } + + friend bool operator!=(const Beats lhs, const Beats rhs) + { + return lhs.mValue != rhs.mValue; + } + + // Model the NetworkByteStreamSerializable concept + friend std::uint32_t sizeInByteStream(const Beats beats) + { + return discovery::sizeInByteStream(beats.microBeats()); + } + + template + friend It toNetworkByteStream(const Beats beats, It out) + { + return discovery::toNetworkByteStream(beats.microBeats(), std::move(out)); + } + + template + static std::pair fromNetworkByteStream(It begin, It end) + { + auto result = discovery::Deserialize::fromNetworkByteStream( + std::move(begin), std::move(end)); + return std::make_pair(Beats{result.first}, std::move(result.second)); + } + +private: + std::int64_t mValue = 0; +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/ClientSessionTimelines.hpp b/tidal-link/link/include/ableton/link/ClientSessionTimelines.hpp new file mode 100644 index 000000000..345cd18b7 --- /dev/null +++ b/tidal-link/link/include/ableton/link/ClientSessionTimelines.hpp @@ -0,0 +1,115 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include + +namespace ableton +{ +namespace link +{ + +// Clamp the tempo of the given timeline to the valid Link range +inline Timeline clampTempo(const Timeline timeline) +{ + const double kMinBpm = 20.0; + const double kMaxBpm = 999.0; + return {Tempo{(std::min)((std::max)(timeline.tempo.bpm(), kMinBpm), kMaxBpm)}, + timeline.beatOrigin, timeline.timeOrigin}; +} + +// Given an existing client timeline, a session timeline, and the +// global host transform of the session, return a new version of the client +// timeline. The resulting new client timeline is continuous with the +// previous timeline so that curClient.toBeats(atTime) == +// result.toBeats(atTime). +inline Timeline updateClientTimelineFromSession(const Timeline curClient, + const Timeline session, + const std::chrono::microseconds atTime, + const GhostXForm xform) +{ + // An intermediate timeline representing the continuation of the + // existing client timeline with the tempo from the session timeline. + const auto tempTl = Timeline{session.tempo, curClient.toBeats(atTime), atTime}; + // The host time corresponding to beat 0 on the session + // timeline. Beat 0 on the session timeline is important because it + // serves as the origin of the quantization grid for all participants. + const auto hostBeatZero = xform.ghostToHost(session.fromBeats(Beats{INT64_C(0)})); + // The new client timeline becomes the result of sliding the + // intermediate timeline back so that it's anchor corresponds to + // beat zero on the session timeline. The result preserves the + // magnitude of beats on the client timeline while encoding the + // quantization reference point in the time and beatOrigins. + return {tempTl.tempo, tempTl.toBeats(hostBeatZero), hostBeatZero}; +} + + +inline Timeline updateSessionTimelineFromClient(const Timeline curSession, + const Timeline client, + const std::chrono::microseconds atTime, + const GhostXForm xform) +{ + // The client timeline was constructed so that it's timeOrigin + // corresponds to beat 0 on the session timeline. + const auto ghostBeat0 = xform.hostToGhost(client.timeOrigin); + + const auto zero = Beats{INT64_C(0)}; + // If beat 0 was not shifted and there is not a new tempo, an update + // of the session timeline is not required. Don't create an + // equivalent timeline with different anchor points if not needed as + // this will trigger other unnecessary changes. + if (curSession.toBeats(ghostBeat0) == zero && client.tempo == curSession.tempo) + { + return curSession; + } + else + { + // An intermediate timeline representing the new tempo, the + // effective time, and a possibly adjusted origin. + const auto tempTl = Timeline{client.tempo, zero, ghostBeat0}; + // The final session timeline must have the beat corresponding to + // atTime on the old session timeline as its beatOrigin because this is + // used for prioritization of timelines among peers - we can't let a + // modification applied by the client artificially increase or + // reduce the timeline's priority in the session. The new beat + // origin should be as close as possible to lining up with atTime, + // but we must also make sure that it's > curSession.beatOrigin + // because otherwise it will get ignored. + const auto newBeatOrigin = (std::max)(curSession.toBeats(xform.hostToGhost(atTime)), + curSession.beatOrigin + Beats{INT64_C(1)}); + return {client.tempo, newBeatOrigin, tempTl.fromBeats(newBeatOrigin)}; + } +} + +// Shift timeline so result.toBeats(t) == client.toBeats(t) + +// shift. This takes into account the fact that the timeOrigin +// corresponds to beat 0 on the session timeline. Using this function +// and then setting the session timeline with the result will change +// the phase of the session by the given shift amount. +inline Timeline shiftClientTimeline(Timeline client, const Beats shift) +{ + const auto timeDelta = client.fromBeats(shift) - client.fromBeats(Beats{INT64_C(0)}); + client.timeOrigin = client.timeOrigin - timeDelta; + return client; +} + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/Controller.hpp b/tidal-link/link/include/ableton/link/Controller.hpp new file mode 100644 index 000000000..2922f46f0 --- /dev/null +++ b/tidal-link/link/include/ableton/link/Controller.hpp @@ -0,0 +1,792 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include +#include +#include +#include +#include +#include +#include +#include +#include + +namespace ableton +{ +namespace link +{ +namespace detail +{ + +template +GhostXForm initXForm(const Clock& clock) +{ + // Make the current time map to a ghost time of 0 with ghost time + // increasing at the same rate as clock time + return {1.0, -clock.micros()}; +} + +template +inline SessionState initSessionState(const Tempo tempo, const Clock& clock) +{ + using namespace std::chrono; + return {clampTempo(Timeline{tempo, Beats{0.}, microseconds{0}}), + StartStopState{false, Beats{0.}, microseconds{0}}, initXForm(clock)}; +} + +inline ClientState initClientState(const SessionState& sessionState) +{ + const auto hostTime = sessionState.ghostXForm.ghostToHost(std::chrono::microseconds{0}); + return { + Timeline{sessionState.timeline.tempo, sessionState.timeline.beatOrigin, hostTime}, + ClientStartStopState{sessionState.startStopState.isPlaying, hostTime, hostTime}}; +} + +inline RtClientState initRtClientState(const ClientState& clientState) +{ + using namespace std::chrono; + return { + clientState.timeline, clientState.startStopState, microseconds{0}, microseconds{0}}; +} + +// The timespan in which local modifications to the timeline will be +// preferred over any modifications coming from the network. +const auto kLocalModGracePeriod = std::chrono::milliseconds(1000); +const auto kRtHandlerFallbackPeriod = kLocalModGracePeriod / 2; + +inline ClientStartStopState selectPreferredStartStopState( + const ClientStartStopState currentStartStopState, + const ClientStartStopState startStopState) +{ + return startStopState.timestamp > currentStartStopState.timestamp + ? startStopState + : currentStartStopState; +} + +inline ClientStartStopState mapStartStopStateFromSessionToClient( + const StartStopState& sessionStartStopState, + const Timeline& sessionTimeline, + const GhostXForm& xForm) +{ + const auto time = + xForm.ghostToHost(sessionTimeline.fromBeats(sessionStartStopState.beats)); + const auto timestamp = xForm.ghostToHost(sessionStartStopState.timestamp); + return ClientStartStopState{sessionStartStopState.isPlaying, time, timestamp}; +} + +inline StartStopState mapStartStopStateFromClientToSession( + const ClientStartStopState& clientStartStopState, + const Timeline& sessionTimeline, + const GhostXForm& xForm) +{ + const auto sessionBeats = + sessionTimeline.toBeats(xForm.hostToGhost(clientStartStopState.time)); + const auto timestamp = xForm.hostToGhost(clientStartStopState.timestamp); + return StartStopState{clientStartStopState.isPlaying, sessionBeats, timestamp}; +} + +} // namespace detail + +// function types corresponding to the Controller callback type params +using PeerCountCallback = std::function; +using TempoCallback = std::function; +using StartStopStateCallback = std::function; + + +// The main Link controller +template +class Controller +{ +public: + Controller(Tempo tempo, + PeerCountCallback peerCallback, + TempoCallback tempoCallback, + StartStopStateCallback startStopStateCallback, + Clock clock) + : mTempoCallback(std::move(tempoCallback)) + , mStartStopStateCallback(std::move(startStopStateCallback)) + , mClock(std::move(clock)) + , mNodeId(NodeId::random()) + , mSessionId(mNodeId) + , mSessionState(detail::initSessionState(tempo, mClock)) + , mClientState(detail::initClientState(mSessionState)) + , mLastIsPlayingForStartStopStateCallback(false) + , mRtClientState(detail::initRtClientState(mClientState.get())) + , mHasPendingRtClientStates(false) + , mSessionPeerCounter(*this, std::move(peerCallback)) + , mEnabled(false) + , mStartStopSyncEnabled(false) + , mIo(IoContext{UdpSendExceptionHandler{this}}) + , mRtClientStateSetter(*this) + , mPeers(util::injectRef(*mIo), + std::ref(mSessionPeerCounter), + SessionTimelineCallback{*this}, + SessionStartStopStateCallback{*this}) + , mSessions( + {mSessionId, mSessionState.timeline, {mSessionState.ghostXForm, mClock.micros()}}, + util::injectRef(mPeers), + MeasurePeer{*this}, + JoinSessionCallback{*this}, + util::injectRef(*mIo), + mClock) + , mDiscovery(std::make_pair(NodeState{mNodeId, mSessionId, mSessionState.timeline, + mSessionState.startStopState}, + mSessionState.ghostXForm), + GatewayFactory{*this}, + util::injectRef(*mIo)) + { + } + + Controller(const Controller&) = delete; + Controller(Controller&&) = delete; + + Controller& operator=(const Controller&) = delete; + Controller& operator=(Controller&&) = delete; + + ~Controller() + { + std::mutex mutex; + std::condition_variable condition; + auto stopped = false; + + mIo->async([this, &mutex, &condition, &stopped]() { + enable(false); + std::unique_lock lock(mutex); + stopped = true; + condition.notify_one(); + }); + + std::unique_lock lock(mutex); + condition.wait(lock, [&stopped] { return stopped; }); + + mIo->stop(); + } + + void enable(const bool bEnable) + { + const bool bWasEnabled = mEnabled.exchange(bEnable); + if (bWasEnabled != bEnable) + { + mIo->async([this, bEnable] { + if (bEnable) + { + // Process the pending client states to make sure we don't push one after we + // have joined a running session + mRtClientStateSetter.processPendingClientStates(); + // Always reset when first enabling to avoid hijacking + // tempo in existing sessions + resetState(); + } + mDiscovery.enable(bEnable); + }); + } + } + + bool isEnabled() const + { + return mEnabled; + } + + void enableStartStopSync(const bool bEnable) + { + mStartStopSyncEnabled = bEnable; + } + + bool isStartStopSyncEnabled() const + { + return mStartStopSyncEnabled; + } + + std::size_t numPeers() const + { + return mSessionPeerCounter.mSessionPeerCount; + } + + // Get the current Link client state. Thread-safe but may block, so + // it cannot be used from audio thread. + ClientState clientState() const + { + return mClientState.get(); + } + + // Set the client state to be used, starting at the given time. + // Thread-safe but may block, so it cannot be used from audio thread. + void setClientState(IncomingClientState newClientState) + { + mClientState.update([&](ClientState& clientState) { + if (newClientState.timeline) + { + *newClientState.timeline = clampTempo(*newClientState.timeline); + clientState.timeline = *newClientState.timeline; + } + if (newClientState.startStopState) + { + // Prevent updating client start stop state with an outdated start stop state + *newClientState.startStopState = detail::selectPreferredStartStopState( + clientState.startStopState, *newClientState.startStopState); + clientState.startStopState = *newClientState.startStopState; + } + }); + mIo->async([this, newClientState] { handleClientState(newClientState); }); + } + + // Non-blocking client state access for a realtime context. NOT + // thread-safe. Must not be called from multiple threads + // concurrently and must not be called concurrently with setClientStateRtSafe. + ClientState clientStateRtSafe() const + { + // Respect the session state guard and the client state guard but don't + // block on them. If we can't access one or both because of concurrent modification + // we fall back to our cached version of the timeline and/or start stop state. + + if (!mHasPendingRtClientStates) + { + const auto now = mClock.micros(); + const auto timelineGracePeriodOver = + now - mRtClientState.timelineTimestamp > detail::kLocalModGracePeriod; + const auto startStopStateGracePeriodOver = + now - mRtClientState.startStopStateTimestamp > detail::kLocalModGracePeriod; + + if (timelineGracePeriodOver || startStopStateGracePeriodOver) + { + const auto clientState = mClientState.getRt(); + + if (timelineGracePeriodOver && clientState.timeline != mRtClientState.timeline) + { + mRtClientState.timeline = clientState.timeline; + } + + if (startStopStateGracePeriodOver + && clientState.startStopState != mRtClientState.startStopState) + { + mRtClientState.startStopState = clientState.startStopState; + } + } + } + + return {mRtClientState.timeline, mRtClientState.startStopState}; + } + + // should only be called from the audio thread + void setClientStateRtSafe(IncomingClientState newClientState) + { + if (!newClientState.timeline && !newClientState.startStopState) + { + return; + } + + if (newClientState.timeline) + { + *newClientState.timeline = clampTempo(*newClientState.timeline); + } + + if (newClientState.startStopState) + { + // Prevent updating client start stop state with an outdated start stop state + *newClientState.startStopState = detail::selectPreferredStartStopState( + mRtClientState.startStopState, *newClientState.startStopState); + } + + // This flag ensures that mRtClientState is only updated after all incoming + // client states were processed + mHasPendingRtClientStates = true; + mRtClientStateSetter.push(newClientState); + const auto now = mClock.micros(); + // Cache the new timeline and StartStopState for serving back to the client + if (newClientState.timeline) + { + // Cache the new timeline and StartStopState for serving back to the client + mRtClientState.timeline = *newClientState.timeline; + mRtClientState.timelineTimestamp = makeRtTimestamp(now); + } + if (newClientState.startStopState) + { + mRtClientState.startStopState = *newClientState.startStopState; + mRtClientState.startStopStateTimestamp = makeRtTimestamp(now); + } + } + +private: + std::chrono::microseconds makeRtTimestamp(const std::chrono::microseconds now) const + { + return isEnabled() ? now : std::chrono::microseconds(0); + } + + void invokeStartStopStateCallbackIfChanged() + { + bool shouldInvokeCallback = false; + + mClientState.update([&](ClientState& clientState) { + shouldInvokeCallback = + mLastIsPlayingForStartStopStateCallback != clientState.startStopState.isPlaying; + mLastIsPlayingForStartStopStateCallback = clientState.startStopState.isPlaying; + }); + + if (shouldInvokeCallback) + { + mStartStopStateCallback(mLastIsPlayingForStartStopStateCallback); + } + } + + void updateDiscovery() + { + // Push the change to the discovery service + mDiscovery.updateNodeState( + std::make_pair(NodeState{mNodeId, mSessionId, mSessionState.timeline, + mSessionState.startStopState}, + mSessionState.ghostXForm)); + } + + void updateSessionTiming(Timeline newTimeline, const GhostXForm newXForm) + { + // Clamp the session tempo because it may slightly overshoot (999 bpm is + // transferred as 60606 us/beat and received as 999.000999... bpm). + newTimeline = clampTempo(newTimeline); + const auto oldTimeline = mSessionState.timeline; + const auto oldXForm = mSessionState.ghostXForm; + + if (oldTimeline != newTimeline || oldXForm != newXForm) + { + { + std::lock_guard lock(mSessionStateGuard); + mSessionState.timeline = newTimeline; + mSessionState.ghostXForm = newXForm; + } + + // Update the client timeline and start stop state based on the new session timing + mClientState.update([&](ClientState& clientState) { + clientState.timeline = updateClientTimelineFromSession(clientState.timeline, + mSessionState.timeline, mClock.micros(), mSessionState.ghostXForm); + // Don't pass the start stop state to the client when start stop sync is disabled + // or when we have a default constructed start stop state + if (mStartStopSyncEnabled && mSessionState.startStopState != StartStopState{}) + { + std::lock_guard startStopStateLock(mSessionStateGuard); + clientState.startStopState = + detail::mapStartStopStateFromSessionToClient(mSessionState.startStopState, + mSessionState.timeline, mSessionState.ghostXForm); + } + }); + + if (oldTimeline.tempo != newTimeline.tempo) + { + mTempoCallback(newTimeline.tempo); + } + } + } + + void handleTimelineFromSession(SessionId id, Timeline timeline) + { + debug(mIo->log()) << "Received timeline with tempo: " << timeline.tempo.bpm() + << " for session: " << id; + updateSessionTiming(mSessions.sawSessionTimeline(std::move(id), std::move(timeline)), + mSessionState.ghostXForm); + updateDiscovery(); + } + + void resetSessionStartStopState() + { + mSessionState.startStopState = StartStopState{}; + } + + void handleStartStopStateFromSession(SessionId sessionId, StartStopState startStopState) + { + debug(mIo->log()) << "Received start stop state. isPlaying: " + << startStopState.isPlaying + << ", beats: " << startStopState.beats.floating() + << ", time: " << startStopState.timestamp.count() + << " for session: " << sessionId; + if (sessionId == mSessionId + && startStopState.timestamp > mSessionState.startStopState.timestamp) + { + mSessionState.startStopState = startStopState; + + // Always propagate the session start stop state so even a client that doesn't have + // the feature enabled can function as a relay. + updateDiscovery(); + + if (mStartStopSyncEnabled) + { + mClientState.update([&](ClientState& clientState) { + clientState.startStopState = detail::mapStartStopStateFromSessionToClient( + startStopState, mSessionState.timeline, mSessionState.ghostXForm); + }); + invokeStartStopStateCallbackIfChanged(); + } + } + } + + void handleClientState(const IncomingClientState clientState) + { + auto mustUpdateDiscovery = false; + + if (clientState.timeline) + { + auto sessionTimeline = updateSessionTimelineFromClient(mSessionState.timeline, + *clientState.timeline, clientState.timelineTimestamp, mSessionState.ghostXForm); + + mSessions.resetTimeline(sessionTimeline); + mPeers.setSessionTimeline(mSessionId, sessionTimeline); + updateSessionTiming(std::move(sessionTimeline), mSessionState.ghostXForm); + + mustUpdateDiscovery = true; + } + + if (mStartStopSyncEnabled && clientState.startStopState) + { + // Prevent updating with an outdated start stop state + const auto newGhostTime = + mSessionState.ghostXForm.hostToGhost(clientState.startStopState->timestamp); + if (newGhostTime > mSessionState.startStopState.timestamp) + { + mClientState.update([&](ClientState& currentClientState) { + mSessionState.startStopState = + detail::mapStartStopStateFromClientToSession(*clientState.startStopState, + mSessionState.timeline, mSessionState.ghostXForm); + currentClientState.startStopState = *clientState.startStopState; + }); + + mustUpdateDiscovery = true; + } + } + + if (mustUpdateDiscovery) + { + updateDiscovery(); + } + + invokeStartStopStateCallbackIfChanged(); + } + + void handleRtClientState(IncomingClientState clientState) + { + mClientState.update([&](ClientState& currentClientState) { + if (clientState.timeline) + { + currentClientState.timeline = *clientState.timeline; + } + if (clientState.startStopState) + { + // Prevent updating client start stop state with an outdated start stop state + *clientState.startStopState = detail::selectPreferredStartStopState( + currentClientState.startStopState, *clientState.startStopState); + currentClientState.startStopState = *clientState.startStopState; + } + }); + + handleClientState(clientState); + mHasPendingRtClientStates = false; + } + + void joinSession(const Session& session) + { + const bool sessionIdChanged = mSessionId != session.sessionId; + mSessionId = session.sessionId; + + // Prevent passing the state of the previous session to the new one. + if (sessionIdChanged) + { + mRtClientStateSetter.processPendingClientStates(); + resetSessionStartStopState(); + } + + updateSessionTiming(session.timeline, session.measurement.xform); + updateDiscovery(); + + if (sessionIdChanged) + { + debug(mIo->log()) << "Joining session " << session.sessionId << " with tempo " + << session.timeline.tempo.bpm(); + mSessionPeerCounter(); + } + } + + void resetState() + { + mNodeId = NodeId::random(); + mSessionId = mNodeId; + + const auto xform = detail::initXForm(mClock); + const auto hostTime = -xform.intercept; + // When creating the new timeline, make it continuous by finding + // the beat on the old session timeline corresponding to the + // current host time and mapping it to the new ghost time + // representation of the current host time. + const auto newTl = Timeline{mSessionState.timeline.tempo, + mSessionState.timeline.toBeats(mSessionState.ghostXForm.hostToGhost(hostTime)), + xform.hostToGhost(hostTime)}; + + resetSessionStartStopState(); + + updateSessionTiming(newTl, xform); + updateDiscovery(); + + mSessions.resetSession({mNodeId, newTl, {xform, hostTime}}); + mPeers.resetPeers(); + } + + struct SessionTimelineCallback + { + void operator()(SessionId id, Timeline timeline) + { + mController.handleTimelineFromSession(std::move(id), std::move(timeline)); + } + + Controller& mController; + }; + + struct RtClientStateSetter + { + using CallbackDispatcher = + typename IoContext::template LockFreeCallbackDispatcher, + std::chrono::milliseconds>; + + RtClientStateSetter(Controller& controller) + : mController(controller) + , mCallbackDispatcher( + [this] { mController.mIo->async([this]() { processPendingClientStates(); }); }, + detail::kRtHandlerFallbackPeriod) + { + } + + void push(const IncomingClientState clientState) + { + if (clientState.timeline) + { + mTimelineBuffer.write( + std::make_pair(clientState.timelineTimestamp, *clientState.timeline)); + } + + if (clientState.startStopState) + { + mStartStopStateBuffer.write(*clientState.startStopState); + } + + if (clientState.timeline || clientState.startStopState) + { + mCallbackDispatcher.invoke(); + } + } + + void processPendingClientStates() + { + const auto clientState = buildMergedPendingClientState(); + mController.handleRtClientState(clientState); + } + + private: + IncomingClientState buildMergedPendingClientState() + { + auto clientState = IncomingClientState{}; + if (auto tl = mTimelineBuffer.readNew()) + { + clientState.timelineTimestamp = (*tl).first; + clientState.timeline = OptionalTimeline{(*tl).second}; + } + if (auto sss = mStartStopStateBuffer.readNew()) + { + clientState.startStopState = sss; + } + return clientState; + } + + Controller& mController; + // Use separate TripleBuffers for the Timeline and the StartStopState so we read the + // latest set value from either optional. + TripleBuffer> mTimelineBuffer; + TripleBuffer mStartStopStateBuffer; + CallbackDispatcher mCallbackDispatcher; + }; + + struct SessionStartStopStateCallback + { + void operator()(SessionId sessionId, StartStopState startStopState) + { + mController.handleStartStopStateFromSession(sessionId, startStopState); + } + + Controller& mController; + }; + + struct SessionPeerCounter + { + SessionPeerCounter(Controller& controller, PeerCountCallback callback) + : mController(controller) + , mCallback(std::move(callback)) + , mSessionPeerCount(0) + { + } + + void operator()() + { + const auto count = + mController.mPeers.uniqueSessionPeerCount(mController.mSessionId); + const auto oldCount = mSessionPeerCount.exchange(count); + if (oldCount != count) + { + if (count == 0) + { + // When the count goes down to zero, completely reset the + // state, effectively founding a new session + mController.mIo->async([this] { mController.resetState(); }); + } + mCallback(count); + } + } + + Controller& mController; + PeerCountCallback mCallback; + std::atomic mSessionPeerCount; + }; + + struct MeasurePeer + { + template + void operator()(Peer peer, Handler handler) + { + using It = typename Discovery::ServicePeerGateways::GatewayMap::iterator; + using ValueType = typename Discovery::ServicePeerGateways::GatewayMap::value_type; + mController.mDiscovery.withGateways([peer, handler](It begin, const It end) { + const auto addr = peer.second; + const auto it = std::find_if( + begin, end, [&addr](const ValueType& vt) { return vt.first == addr; }); + if (it != end) + { + it->second->measurePeer(std::move(peer.first), std::move(handler)); + } + else + { + // invoke the handler with an empty result if we couldn't + // find the peer's gateway + handler(GhostXForm{}); + } + }); + } + + Controller& mController; + }; + + struct JoinSessionCallback + { + void operator()(Session session) + { + mController.joinSession(std::move(session)); + } + + Controller& mController; + }; + + using IoType = typename util::Injected::type; + + using ControllerPeers = Peers, + SessionTimelineCallback, + SessionStartStopStateCallback>; + + using ControllerGateway = + Gateway; + using GatewayPtr = std::shared_ptr; + + struct GatewayFactory + { + GatewayPtr operator()(std::pair state, + util::Injected io, + const asio::ip::address& addr) + { + if (addr.is_v4()) + { + return GatewayPtr{new ControllerGateway{std::move(io), addr.to_v4(), + util::injectVal(makeGatewayObserver(mController.mPeers, addr)), + std::move(state.first), std::move(state.second), mController.mClock}}; + } + else + { + throw std::runtime_error("Could not create peer gateway on non-ipV4 address"); + } + } + + Controller& mController; + }; + + struct UdpSendExceptionHandler + { + using Exception = discovery::UdpSendException; + + void operator()(const Exception exception) + { + mpController->mIo->async([this, exception] { + mpController->mDiscovery.repairGateway(exception.interfaceAddr); + }); + } + + Controller* mpController; + }; + + TempoCallback mTempoCallback; + StartStopStateCallback mStartStopStateCallback; + Clock mClock; + NodeId mNodeId; + SessionId mSessionId; + + mutable std::mutex mSessionStateGuard; + SessionState mSessionState; + + ControllerClientState mClientState; + bool mLastIsPlayingForStartStopStateCallback; + + mutable RtClientState mRtClientState; + std::atomic mHasPendingRtClientStates; + + SessionPeerCounter mSessionPeerCounter; + + std::atomic mEnabled; + + std::atomic mStartStopSyncEnabled; + + util::Injected mIo; + + RtClientStateSetter mRtClientStateSetter; + + ControllerPeers mPeers; + + using ControllerSessions = Sessions::type&, + Clock>; + ControllerSessions mSessions; + + using Discovery = discovery::Service, + GatewayFactory, + typename util::Injected::type&>; + Discovery mDiscovery; +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/Gateway.hpp b/tidal-link/link/include/ableton/link/Gateway.hpp new file mode 100644 index 000000000..16d6abdea --- /dev/null +++ b/tidal-link/link/include/ableton/link/Gateway.hpp @@ -0,0 +1,93 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +template +class Gateway +{ +public: + Gateway(util::Injected io, + asio::ip::address_v4 addr, + util::Injected observer, + NodeState nodeState, + GhostXForm ghostXForm, + Clock clock) + : mIo(std::move(io)) + , mMeasurement(addr, + nodeState.sessionId, + std::move(ghostXForm), + std::move(clock), + util::injectRef(*mIo)) + , mPeerGateway(discovery::makeIpV4Gateway(util::injectRef(*mIo), + std::move(addr), + std::move(observer), + PeerState{std::move(nodeState), mMeasurement.endpoint()})) + { + } + + Gateway(const Gateway& rhs) = delete; + Gateway& operator=(const Gateway& rhs) = delete; + + Gateway(Gateway&& rhs) + : mIo(std::move(rhs.mIo)) + , mMeasurement(std::move(rhs.mMeasurement)) + , mPeerGateway(std::move(rhs.mPeerGateway)) + { + } + + Gateway& operator=(Gateway&& rhs) + { + mIo = std::move(rhs.mIo); + mMeasurement = std::move(rhs.mMeasurement); + mPeerGateway = std::move(rhs.mPeerGateway); + return *this; + } + + void updateNodeState(std::pair state) + { + mMeasurement.updateNodeState(state.first.sessionId, state.second); + mPeerGateway.updateState(PeerState{std::move(state.first), mMeasurement.endpoint()}); + } + + template + void measurePeer(const PeerState& peer, Handler handler) + { + mMeasurement.measurePeer(peer, std::move(handler)); + } + +private: + util::Injected mIo; + MeasurementService::type&> mMeasurement; + discovery:: + IpV4Gateway::type&> + mPeerGateway; +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/GhostXForm.hpp b/tidal-link/link/include/ableton/link/GhostXForm.hpp new file mode 100644 index 000000000..2971d7bb4 --- /dev/null +++ b/tidal-link/link/include/ableton/link/GhostXForm.hpp @@ -0,0 +1,61 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include + +namespace ableton +{ +namespace link +{ + +using std::chrono::microseconds; + +struct GhostXForm +{ + microseconds hostToGhost(const microseconds hostTime) const + { + return microseconds{llround(slope * static_cast(hostTime.count()))} + + intercept; + } + + microseconds ghostToHost(const microseconds ghostTime) const + { + return microseconds{ + llround(static_cast((ghostTime - intercept).count()) / slope)}; + } + + friend bool operator==(const GhostXForm lhs, const GhostXForm rhs) + { + return lhs.slope == rhs.slope && lhs.intercept == rhs.intercept; + } + + friend bool operator!=(const GhostXForm lhs, const GhostXForm rhs) + { + return !(lhs == rhs); + } + + double slope; + microseconds intercept; +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/HostTimeFilter.hpp b/tidal-link/link/include/ableton/link/HostTimeFilter.hpp new file mode 100644 index 000000000..3cf0b1b9d --- /dev/null +++ b/tidal-link/link/include/ableton/link/HostTimeFilter.hpp @@ -0,0 +1,86 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +template +class BasicHostTimeFilter +{ + using Points = std::vector>; + using PointIt = typename Points::iterator; + +public: + BasicHostTimeFilter() + : mIndex(0) + { + mPoints.reserve(kNumPoints); + } + + ~BasicHostTimeFilter() = default; + + void reset() + { + mIndex = 0; + mPoints.clear(); + } + + std::chrono::microseconds sampleTimeToHostTime(const NumberType sampleTime) + { + const auto micros = static_cast(mHostTimeSampler.micros().count()); + const auto point = std::make_pair(sampleTime, micros); + + if (mPoints.size() < kNumPoints) + { + mPoints.push_back(point); + } + else + { + mPoints[mIndex] = point; + } + mIndex = (mIndex + 1) % kNumPoints; + + const auto result = linearRegression(mPoints.begin(), mPoints.end()); + + const auto hostTime = (result.first * sampleTime) + result.second; + + return std::chrono::microseconds(llround(hostTime)); + } + +private: + std::size_t mIndex; + Points mPoints; + Clock mHostTimeSampler; +}; + +template +using HostTimeFilter = BasicHostTimeFilter; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/LinearRegression.hpp b/tidal-link/link/include/ableton/link/LinearRegression.hpp new file mode 100644 index 000000000..adc26edf7 --- /dev/null +++ b/tidal-link/link/include/ableton/link/LinearRegression.hpp @@ -0,0 +1,61 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +template +typename std::iterator_traits::value_type linearRegression(It begin, It end) +{ + using NumberType = + typename std::tuple_element<0, typename std::iterator_traits::value_type>::type; + + NumberType sumX = 0.0; + NumberType sumXX = 0.0; + NumberType sumXY = 0.0; + NumberType sumY = 0.0; + for (auto i = begin; i != end; ++i) + { + sumX += i->first; + sumXX += i->first * i->first; + sumXY += i->first * i->second; + sumY += i->second; + } + + const NumberType numPoints = static_cast(distance(begin, end)); + assert(numPoints > 0); + const NumberType denominator = numPoints * sumXX - sumX * sumX; + const NumberType slope = denominator == NumberType{0} + ? NumberType{0} + : (numPoints * sumXY - sumX * sumY) / denominator; + const NumberType intercept = (sumY - slope * sumX) / numPoints; + + return std::make_pair(slope, intercept); +} + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/Measurement.hpp b/tidal-link/link/include/ableton/link/Measurement.hpp new file mode 100644 index 000000000..299ca24b6 --- /dev/null +++ b/tidal-link/link/include/ableton/link/Measurement.hpp @@ -0,0 +1,250 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include +#include +#include +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +template +struct Measurement +{ + using Callback = std::function&)>; + using Micros = std::chrono::microseconds; + + static const std::size_t kNumberDataPoints = 100; + static const std::size_t kNumberMeasurements = 5; + + Measurement(const PeerState& state, + Callback callback, + asio::ip::address_v4 address, + Clock clock, + util::Injected io) + : mIo(std::move(io)) + , mpImpl(std::make_shared( + std::move(state), std::move(callback), std::move(address), std::move(clock), mIo)) + { + mpImpl->listen(); + } + + Measurement(const Measurement&) = delete; + Measurement& operator=(Measurement&) = delete; + Measurement(const Measurement&&) = delete; + Measurement& operator=(Measurement&&) = delete; + + struct Impl : std::enable_shared_from_this + { + using Socket = + typename util::Injected::type::template Socket; + using Timer = typename util::Injected::type::Timer; + using Log = typename util::Injected::type::Log; + + Impl(const PeerState& state, + Callback callback, + asio::ip::address_v4 address, + Clock clock, + util::Injected io) + : mSocket(io->template openUnicastSocket(address)) + , mSessionId(state.nodeState.sessionId) + , mEndpoint(state.endpoint) + , mCallback(std::move(callback)) + , mClock(std::move(clock)) + , mTimer(io->makeTimer()) + , mMeasurementsStarted(0) + , mLog(channel(io->log(), "Measurement on gateway@" + address.to_string())) + , mSuccess(false) + { + const auto ht = HostTime{mClock.micros()}; + sendPing(mEndpoint, discovery::makePayload(ht)); + resetTimer(); + } + + void resetTimer() + { + mTimer.cancel(); + mTimer.expires_from_now(std::chrono::milliseconds(50)); + mTimer.async_wait([this](const typename Timer::ErrorCode e) { + if (!e) + { + if (mMeasurementsStarted < kNumberMeasurements) + { + const auto ht = HostTime{mClock.micros()}; + sendPing(mEndpoint, discovery::makePayload(ht)); + ++mMeasurementsStarted; + resetTimer(); + } + else + { + fail(); + } + } + }); + } + + void listen() + { + mSocket.receive(util::makeAsyncSafe(this->shared_from_this())); + } + + // Operator to handle incoming messages on the interface + template + void operator()( + const asio::ip::udp::endpoint& from, const It messageBegin, const It messageEnd) + { + using namespace std; + const auto result = v1::parseMessageHeader(messageBegin, messageEnd); + const auto& header = result.first; + const auto payloadBegin = result.second; + + if (header.messageType == v1::kPong) + { + debug(mLog) << "Received Pong message from " << from; + + // parse for all entries + SessionId sessionId{}; + std::chrono::microseconds ghostTime{0}; + std::chrono::microseconds prevGHostTime{0}; + std::chrono::microseconds prevHostTime{0}; + + try + { + discovery::parsePayload( + payloadBegin, messageEnd, + [&sessionId](const SessionMembership& sms) { sessionId = sms.sessionId; }, + [&ghostTime](GHostTime gt) { ghostTime = std::move(gt.time); }, + [&prevGHostTime](PrevGHostTime gt) { prevGHostTime = std::move(gt.time); }, + [&prevHostTime](HostTime ht) { prevHostTime = std::move(ht.time); }); + } + catch (const std::runtime_error& err) + { + warning(mLog) << "Failed parsing payload, caught exception: " << err.what(); + listen(); + return; + } + + if (mSessionId == sessionId) + { + const auto hostTime = mClock.micros(); + + const auto payload = + discovery::makePayload(HostTime{hostTime}, PrevGHostTime{ghostTime}); + + sendPing(from, payload); + listen(); + + + if (ghostTime != Micros{0} && prevHostTime != Micros{0}) + { + mData.push_back( + static_cast(ghostTime.count()) + - (static_cast((hostTime + prevHostTime).count()) * 0.5)); + + if (prevGHostTime != Micros{0}) + { + mData.push_back( + (static_cast((ghostTime + prevGHostTime).count()) * 0.5) + - static_cast(prevHostTime.count())); + } + } + + if (mData.size() > kNumberDataPoints) + { + finish(); + } + else + { + resetTimer(); + } + } + else + { + fail(); + } + } + else + { + debug(mLog) << "Received invalid message from " << from; + listen(); + } + } + + template + void sendPing(asio::ip::udp::endpoint to, const Payload& payload) + { + v1::MessageBuffer buffer; + const auto msgBegin = std::begin(buffer); + const auto msgEnd = v1::pingMessage(payload, msgBegin); + const auto numBytes = static_cast(std::distance(msgBegin, msgEnd)); + + try + { + mSocket.send(buffer.data(), numBytes, to); + } + catch (const std::runtime_error& err) + { + info(mLog) << "Failed to send Ping to " << to.address().to_string() << ": " + << err.what(); + } + } + + void finish() + { + mTimer.cancel(); + mSuccess = true; + debug(mLog) << "Measuring " << mEndpoint << " done."; + mCallback(mData); + } + + void fail() + { + mData.clear(); + debug(mLog) << "Measuring " << mEndpoint << " failed."; + mCallback(mData); + } + + Socket mSocket; + SessionId mSessionId; + asio::ip::udp::endpoint mEndpoint; + std::vector mData; + Callback mCallback; + Clock mClock; + Timer mTimer; + std::size_t mMeasurementsStarted; + Log mLog; + bool mSuccess; + }; + + util::Injected mIo; + std::shared_ptr mpImpl; +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/MeasurementEndpointV4.hpp b/tidal-link/link/include/ableton/link/MeasurementEndpointV4.hpp new file mode 100644 index 000000000..958aad958 --- /dev/null +++ b/tidal-link/link/include/ableton/link/MeasurementEndpointV4.hpp @@ -0,0 +1,69 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include + +namespace ableton +{ +namespace link +{ + +struct MeasurementEndpointV4 +{ + static const std::int32_t key = 'mep4'; + static_assert(key == 0x6d657034, "Unexpected byte order"); + + // Model the NetworkByteStreamSerializable concept + friend std::uint32_t sizeInByteStream(const MeasurementEndpointV4 mep) + { + return discovery::sizeInByteStream( + static_cast(mep.ep.address().to_v4().to_ulong())) + + discovery::sizeInByteStream(mep.ep.port()); + } + + template + friend It toNetworkByteStream(const MeasurementEndpointV4 mep, It out) + { + return discovery::toNetworkByteStream(mep.ep.port(), + discovery::toNetworkByteStream( + static_cast(mep.ep.address().to_v4().to_ulong()), std::move(out))); + } + + template + static std::pair fromNetworkByteStream(It begin, It end) + { + using namespace std; + auto addrRes = + discovery::Deserialize::fromNetworkByteStream(std::move(begin), end); + auto portRes = discovery::Deserialize::fromNetworkByteStream( + std::move(addrRes.second), end); + return make_pair( + MeasurementEndpointV4{ + {asio::ip::address_v4{std::move(addrRes.first)}, std::move(portRes.first)}}, + std::move(portRes.second)); + } + + asio::ip::udp::endpoint ep; +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/MeasurementService.hpp b/tidal-link/link/include/ableton/link/MeasurementService.hpp new file mode 100644 index 000000000..22bf46d52 --- /dev/null +++ b/tidal-link/link/include/ableton/link/MeasurementService.hpp @@ -0,0 +1,144 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include +#include +#include +#include +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +template +class MeasurementService +{ +public: + using IoType = util::Injected; + using MeasurementInstance = Measurement; + + MeasurementService(asio::ip::address_v4 address, + SessionId sessionId, + GhostXForm ghostXForm, + Clock clock, + IoType io) + : mClock(std::move(clock)) + , mIo(std::move(io)) + , mPingResponder(std::move(address), + std::move(sessionId), + std::move(ghostXForm), + mClock, + util::injectRef(*mIo)) + { + } + + MeasurementService(const MeasurementService&) = delete; + MeasurementService(MeasurementService&&) = delete; + + void updateNodeState(const SessionId& sessionId, const GhostXForm& xform) + { + mPingResponder.updateNodeState(sessionId, xform); + } + + asio::ip::udp::endpoint endpoint() const + { + return mPingResponder.endpoint(); + } + + // Measure the peer and invoke the handler with a GhostXForm + template + void measurePeer(const PeerState& state, const Handler handler) + { + using namespace std; + + const auto nodeId = state.nodeState.nodeId; + auto addr = mPingResponder.endpoint().address().to_v4(); + auto callback = CompletionCallback{*this, nodeId, handler}; + + try + { + mMeasurementMap[nodeId] = + std::unique_ptr(new MeasurementInstance{ + state, std::move(callback), std::move(addr), mClock, mIo}); + } + catch (const runtime_error& err) + { + info(mIo->log()) << "gateway@" + addr.to_string() + << " Failed to measure. Reason: " << err.what(); + handler(GhostXForm{}); + } + } + +private: + template + struct CompletionCallback + { + void operator()(std::vector& data) + { + using namespace std; + using std::chrono::microseconds; + + // Post this to the measurement service's IoContext so that we + // don't delete the measurement object in its stack. Capture all + // needed data separately from this, since this object may be + // gone by the time the block gets executed. + auto nodeId = mNodeId; + auto handler = mHandler; + auto& measurementMap = mMeasurementService.mMeasurementMap; + const auto it = measurementMap.find(nodeId); + if (it != measurementMap.end()) + { + if (data.empty()) + { + handler(GhostXForm{}); + } + else + { + handler(GhostXForm{1, microseconds(llround(median(data.begin(), data.end())))}); + } + measurementMap.erase(it); + } + } + + MeasurementService& mMeasurementService; + NodeId mNodeId; + Handler mHandler; + }; + + // Make sure the measurement map outlives the IoContext so that the rest of + // the members are guaranteed to be valid when any final handlers + // are begin run. + using MeasurementMap = std::map>; + MeasurementMap mMeasurementMap; + Clock mClock; + IoType mIo; + PingResponder mPingResponder; +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/Median.hpp b/tidal-link/link/include/ableton/link/Median.hpp new file mode 100644 index 000000000..ddc7faf25 --- /dev/null +++ b/tidal-link/link/include/ableton/link/Median.hpp @@ -0,0 +1,50 @@ +/* Copyright 2021, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +template +double median(It begin, It end) +{ + const auto n = std::distance(begin, end); + assert(n > 2); + if (n % 2 == 0) + { + std::nth_element(begin, begin + n / 2, end); + std::nth_element(begin, begin + (n - 1) / 2, end); + return (*(begin + (n / 2)) + *(begin + (n - 1) / 2)) / 2.0; + } + else + { + std::nth_element(begin, begin + n / 2, end); + return *(begin + (n / 2)); + } +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/NodeId.hpp b/tidal-link/link/include/ableton/link/NodeId.hpp new file mode 100644 index 000000000..ef4f7981c --- /dev/null +++ b/tidal-link/link/include/ableton/link/NodeId.hpp @@ -0,0 +1,78 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +using NodeIdArray = std::array; + +struct NodeId : NodeIdArray +{ + NodeId() = default; + + NodeId(NodeIdArray rhs) + : NodeIdArray(std::move(rhs)) + { + } + + template + static NodeId random() + { + using namespace std; + NodeId nodeId; + + Random random; + generate(nodeId.begin(), nodeId.end(), [&] { return random(); }); + + return nodeId; + } + + friend std::ostream& operator<<(std::ostream& stream, const NodeId& id) + { + return stream << std::string{id.cbegin(), id.cend()}; + } + + template + friend It toNetworkByteStream(const NodeId& nodeId, It out) + { + return discovery::toNetworkByteStream(nodeId, std::move(out)); + } + + template + static std::pair fromNetworkByteStream(It begin, It end) + { + using namespace std; + auto result = discovery::Deserialize::fromNetworkByteStream( + std::move(begin), std::move(end)); + return make_pair(NodeId(std::move(result.first)), std::move(result.second)); + } +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/NodeState.hpp b/tidal-link/link/include/ableton/link/NodeState.hpp new file mode 100644 index 000000000..787fbda00 --- /dev/null +++ b/tidal-link/link/include/ableton/link/NodeState.hpp @@ -0,0 +1,77 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +struct NodeState +{ + using Payload = + decltype(discovery::makePayload(Timeline{}, SessionMembership{}, StartStopState{})); + + NodeId ident() const + { + return nodeId; + } + + friend bool operator==(const NodeState& lhs, const NodeState& rhs) + { + return std::tie(lhs.nodeId, lhs.sessionId, lhs.timeline, lhs.startStopState) + == std::tie(rhs.nodeId, rhs.sessionId, rhs.timeline, rhs.startStopState); + } + + friend Payload toPayload(const NodeState& state) + { + return discovery::makePayload( + state.timeline, SessionMembership{state.sessionId}, state.startStopState); + } + + template + static NodeState fromPayload(NodeId nodeId, It begin, It end) + { + using namespace std; + auto nodeState = NodeState{std::move(nodeId), {}, {}, {}}; + discovery::parsePayload(std::move(begin), + std::move(end), [&nodeState](Timeline tl) { nodeState.timeline = std::move(tl); }, + [&nodeState](SessionMembership membership) { + nodeState.sessionId = std::move(membership.sessionId); + }, + [&nodeState]( + StartStopState ststst) { nodeState.startStopState = std::move(ststst); }); + return nodeState; + } + + NodeId nodeId; + SessionId sessionId; + Timeline timeline; + StartStopState startStopState; +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/Optional.hpp b/tidal-link/link/include/ableton/link/Optional.hpp new file mode 100644 index 000000000..01b35ed10 --- /dev/null +++ b/tidal-link/link/include/ableton/link/Optional.hpp @@ -0,0 +1,97 @@ +/* Copyright 2017, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include + +namespace ableton +{ +namespace link +{ + +// Subset of the C++ 17 std::optional API. T has to be default constructible. +template +struct Optional +{ + Optional() + : mHasValue(false) + { + } + + explicit Optional(T value) + : mValue(std::move(value)) + , mHasValue(true) + { + } + + Optional(const Optional&) = default; + + Optional(Optional&& other) + : mValue(std::move(other.mValue)) + , mHasValue(other.mHasValue) + { + } + + Optional& operator=(const Optional&) = default; + + Optional& operator=(Optional&& other) + { + mValue = std::move(other.mValue); + mHasValue = other.mHasValue; + return *this; + } + + explicit operator bool() const + { + return mHasValue; + } + + const T& operator*() const + { + assert(mHasValue); + return mValue; + } + + T& operator*() + { + assert(mHasValue); + return mValue; + } + + const T* operator->() const + { + assert(mHasValue); + return &mValue; + } + + T* operator->() + { + assert(mHasValue); + return &mValue; + } + +private: + T mValue; + bool mHasValue; +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/PayloadEntries.hpp b/tidal-link/link/include/ableton/link/PayloadEntries.hpp new file mode 100644 index 000000000..cefd35f26 --- /dev/null +++ b/tidal-link/link/include/ableton/link/PayloadEntries.hpp @@ -0,0 +1,140 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +struct HostTime +{ + static const std::int32_t key = '__ht'; + static_assert(key == 0x5f5f6874, "Unexpected byte order"); + + HostTime() = default; + + HostTime(const std::chrono::microseconds tm) + : time(tm) + { + } + + // Model the NetworkByteStreamSerializable concept + friend std::uint32_t sizeInByteStream(const HostTime& sht) + { + return discovery::sizeInByteStream(std::move(sht.time)); + } + + template + friend It toNetworkByteStream(const HostTime& sht, It out) + { + return discovery::toNetworkByteStream(std::move(sht.time), std::move(out)); + } + + template + static std::pair fromNetworkByteStream(It begin, It end) + { + using namespace std; + auto result = discovery::Deserialize::fromNetworkByteStream( + std::move(begin), std::move(end)); + return make_pair(HostTime{std::move(result.first)}, std::move(result.second)); + } + + std::chrono::microseconds time; +}; + +struct GHostTime +{ + static const std::int32_t key = '__gt'; + static_assert(key == 0x5f5f6774, "Unexpected byte order"); + + GHostTime() = default; + + GHostTime(const std::chrono::microseconds tm) + : time(tm) + { + } + + // Model the NetworkByteStreamSerializable concept + friend std::uint32_t sizeInByteStream(const GHostTime& dgt) + { + return discovery::sizeInByteStream(std::move(dgt.time)); + } + + template + friend It toNetworkByteStream(const GHostTime& dgt, It out) + { + return discovery::toNetworkByteStream(std::move(dgt.time), std::move(out)); + } + + template + static std::pair fromNetworkByteStream(It begin, It end) + { + using namespace std; + auto result = discovery::Deserialize::fromNetworkByteStream( + std::move(begin), std::move(end)); + return make_pair(GHostTime{std::move(result.first)}, std::move(result.second)); + } + + std::chrono::microseconds time; +}; + +struct PrevGHostTime +{ + static const std::int32_t key = '_pgt'; + static_assert(key == 0x5f706774, "Unexpected byte order"); + + PrevGHostTime() = default; + + PrevGHostTime(const std::chrono::microseconds tm) + : time(tm) + { + } + + // Model the NetworkByteStreamSerializable concept + friend std::uint32_t sizeInByteStream(const PrevGHostTime& dgt) + { + return discovery::sizeInByteStream(std::move(dgt.time)); + } + + template + friend It toNetworkByteStream(const PrevGHostTime& pdgt, It out) + { + return discovery::toNetworkByteStream(std::move(pdgt.time), std::move(out)); + } + + template + static std::pair fromNetworkByteStream(It begin, It end) + { + using namespace std; + auto result = discovery::Deserialize::fromNetworkByteStream( + std::move(begin), std::move(end)); + return make_pair(PrevGHostTime{std::move(result.first)}, std::move(result.second)); + } + + std::chrono::microseconds time; +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/PeerState.hpp b/tidal-link/link/include/ableton/link/PeerState.hpp new file mode 100644 index 000000000..291c27891 --- /dev/null +++ b/tidal-link/link/include/ableton/link/PeerState.hpp @@ -0,0 +1,90 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +// A state type for peers. PeerState stores the normal NodeState plus +// additional information (the remote endpoint at which to find its +// ping/pong measurement server). + +struct PeerState +{ + using IdType = NodeId; + + IdType ident() const + { + return nodeState.ident(); + } + + SessionId sessionId() const + { + return nodeState.sessionId; + } + + Timeline timeline() const + { + return nodeState.timeline; + } + + StartStopState startStopState() const + { + return nodeState.startStopState; + } + + friend bool operator==(const PeerState& lhs, const PeerState& rhs) + { + return lhs.nodeState == rhs.nodeState && lhs.endpoint == rhs.endpoint; + } + + friend auto toPayload(const PeerState& state) + -> decltype(std::declval() + + discovery::makePayload(MeasurementEndpointV4{{}})) + { + return toPayload(state.nodeState) + + discovery::makePayload(MeasurementEndpointV4{state.endpoint}); + } + + template + static PeerState fromPayload(NodeId id, It begin, It end) + { + using namespace std; + auto peerState = PeerState{NodeState::fromPayload(std::move(id), begin, end), {}}; + + discovery::parsePayload( + std::move(begin), std::move(end), [&peerState](MeasurementEndpointV4 me4) { + peerState.endpoint = std::move(me4.ep); + }); + return peerState; + } + + NodeState nodeState; + asio::ip::udp::endpoint endpoint; +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/Peers.hpp b/tidal-link/link/include/ableton/link/Peers.hpp new file mode 100644 index 000000000..b633ec363 --- /dev/null +++ b/tidal-link/link/include/ableton/link/Peers.hpp @@ -0,0 +1,368 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +// SessionMembershipCallback is invoked when any change to session +// membership occurs (when any peer joins or leaves a session) +// +// SessionTimelineCallback is invoked with a session id and a timeline +// whenever a new combination of these values is seen +// +// SessionStartStopStateCallback is invoked with a session id and a startStopState +// whenever a new combination of these values is seen + +template +class Peers +{ + // non-movable private implementation type + struct Impl; + +public: + using Peer = std::pair; + + Peers(util::Injected io, + SessionMembershipCallback membership, + SessionTimelineCallback timeline, + SessionStartStopStateCallback startStop) + : mpImpl(std::make_shared( + std::move(io), std::move(membership), std::move(timeline), std::move(startStop))) + { + } + + // The set of peers for a given session, ordered by (peerId, addr). + // The result will possibly contain multiple entries for the same + // peer if it is visible through multiple gateways. + std::vector sessionPeers(const SessionId& sid) const + { + using namespace std; + vector result; + auto& peerVec = mpImpl->mPeers; + copy_if(begin(peerVec), end(peerVec), back_inserter(result), SessionMemberPred{sid}); + return result; + } + + // Number of individual for a given session. + std::size_t uniqueSessionPeerCount(const SessionId& sid) const + { + using namespace std; + auto peerVec = sessionPeers(sid); + auto last = unique(begin(peerVec), end(peerVec), + [](const Peer& a, const Peer& b) { return a.first.ident() == b.first.ident(); }); + return static_cast(distance(begin(peerVec), last)); + } + + void setSessionTimeline(const SessionId& sid, const Timeline& tl) + { + // Set the cached timeline for all peers to a new client-specified + // timeline. When we make a timeline change, we do so + // optimistically and clients assume that all peers in a session + // have adopted the newly specified timeline. We must represent + // this in our cache or else we risk failing to notify about a + // higher-priority peer timeline that was already seen. + for (auto& peer : mpImpl->mPeers) + { + if (peer.first.sessionId() == sid) + { + peer.first.nodeState.timeline = tl; + } + } + } + + // Purge all cached peers that are members of the given session + void forgetSession(const SessionId& sid) + { + using namespace std; + auto& peerVec = mpImpl->mPeers; + peerVec.erase( + remove_if(begin(peerVec), end(peerVec), SessionMemberPred{sid}), end(peerVec)); + } + + void resetPeers() + { + mpImpl->mPeers.clear(); + } + + // Observer type that monitors peer discovery on a particular + // gateway and relays the information to a Peers instance. + // Models the PeerObserver concept from the discovery module. + struct GatewayObserver + { + using GatewayObserverNodeState = PeerState; + using GatewayObserverNodeId = NodeId; + + GatewayObserver(std::shared_ptr pImpl, asio::ip::address addr) + : mpImpl(std::move(pImpl)) + , mAddr(std::move(addr)) + { + } + GatewayObserver(const GatewayObserver&) = delete; + + GatewayObserver(GatewayObserver&& rhs) + : mpImpl(std::move(rhs.mpImpl)) + , mAddr(std::move(rhs.mAddr)) + { + } + + ~GatewayObserver() + { + // Check to handle the moved from case + if (mpImpl) + { + mpImpl->gatewayClosed(mAddr); + } + } + + // model the PeerObserver concept from discovery + friend void sawPeer(GatewayObserver& observer, const PeerState& state) + { + auto pImpl = observer.mpImpl; + auto addr = observer.mAddr; + assert(pImpl); + pImpl->sawPeerOnGateway(std::move(state), std::move(addr)); + } + + friend void peerLeft(GatewayObserver& observer, const NodeId& id) + { + auto pImpl = observer.mpImpl; + auto addr = observer.mAddr; + pImpl->peerLeftGateway(std::move(id), std::move(addr)); + } + + friend void peerTimedOut(GatewayObserver& observer, const NodeId& id) + { + auto pImpl = observer.mpImpl; + auto addr = observer.mAddr; + pImpl->peerLeftGateway(std::move(id), std::move(addr)); + } + + std::shared_ptr mpImpl; + asio::ip::address mAddr; + }; + + // Factory function for the gateway observer + friend GatewayObserver makeGatewayObserver(Peers& peers, asio::ip::address addr) + { + return GatewayObserver{peers.mpImpl, std::move(addr)}; + } + +private: + struct Impl + { + Impl(util::Injected io, + SessionMembershipCallback membership, + SessionTimelineCallback timeline, + SessionStartStopStateCallback startStop) + : mIo(std::move(io)) + , mSessionMembershipCallback(std::move(membership)) + , mSessionTimelineCallback(std::move(timeline)) + , mSessionStartStopStateCallback(std::move(startStop)) + { + } + + void sawPeerOnGateway(PeerState peerState, asio::ip::address gatewayAddr) + { + using namespace std; + + const auto peerSession = peerState.sessionId(); + const auto peerTimeline = peerState.timeline(); + const auto peerStartStopState = peerState.startStopState(); + + bool isNewSessionTimeline = !sessionTimelineExists(peerSession, peerTimeline); + bool isNewSessionStartStopState = + !sessionStartStopStateExists(peerSession, peerStartStopState); + + auto peer = make_pair(std::move(peerState), std::move(gatewayAddr)); + const auto idRange = equal_range(begin(mPeers), end(mPeers), peer, PeerIdComp{}); + + bool didSessionMembershipChange = false; + if (idRange.first == idRange.second) + { + // This peer is not currently known on any gateway + didSessionMembershipChange = true; + mPeers.insert(std::move(idRange.first), std::move(peer)); + } + else + { + // We've seen this peer before... does it have a new session? + didSessionMembershipChange = + all_of(idRange.first, idRange.second, [&peerSession](const Peer& test) { + return test.first.sessionId() != peerSession; + }); + + // was it on this gateway? + const auto addrRange = + equal_range(idRange.first, idRange.second, peer, AddrComp{}); + + if (addrRange.first == addrRange.second) + { + // First time on this gateway, add it + mPeers.insert(std::move(addrRange.first), std::move(peer)); + } + else + { + // We have an entry for this peer on this gateway, update it + *addrRange.first = std::move(peer); + } + } + + // Invoke callbacks outside the critical section + if (isNewSessionTimeline) + { + mSessionTimelineCallback(peerSession, peerTimeline); + } + + // Pass the start stop state to the Controller after it processed the timeline. + // A new timeline can cause a session Id change which will prevent processing the + // new start stop state. By handling the start stop state after the timeline we + // assure that the start stop state is processed with the correct session Id. + if (isNewSessionStartStopState) + { + mSessionStartStopStateCallback(peerSession, peerStartStopState); + } + + if (didSessionMembershipChange) + { + mSessionMembershipCallback(); + } + } + + void peerLeftGateway(const NodeId& nodeId, const asio::ip::address& gatewayAddr) + { + using namespace std; + + auto it = find_if(begin(mPeers), end(mPeers), [&](const Peer& peer) { + return peer.first.ident() == nodeId && peer.second == gatewayAddr; + }); + + bool didSessionMembershipChange = false; + if (it != end(mPeers)) + { + mPeers.erase(std::move(it)); + didSessionMembershipChange = true; + } + + if (didSessionMembershipChange) + { + mSessionMembershipCallback(); + } + } + + void gatewayClosed(const asio::ip::address& gatewayAddr) + { + using namespace std; + + mPeers.erase( + remove_if(begin(mPeers), end(mPeers), + [&gatewayAddr](const Peer& peer) { return peer.second == gatewayAddr; }), + end(mPeers)); + + mSessionMembershipCallback(); + } + + template + bool hasPeerWith(const SessionId& sessionId, Predicate predicate) + { + using namespace std; + return find_if(begin(mPeers), end(mPeers), [&](const Peer& peer) { + return peer.first.sessionId() == sessionId && predicate(peer.first); + }) != end(mPeers); + } + + bool sessionTimelineExists(const SessionId& session, const Timeline& timeline) + { + return hasPeerWith(session, + [&](const PeerState& peerState) { return peerState.timeline() == timeline; }); + } + + bool sessionStartStopStateExists( + const SessionId& sessionId, const StartStopState& startStopState) + { + return hasPeerWith(sessionId, [&](const PeerState& peerState) { + return peerState.startStopState() == startStopState; + }); + } + + struct PeerIdComp + { + bool operator()(const Peer& lhs, const Peer& rhs) const + { + return lhs.first.ident() < rhs.first.ident(); + } + }; + + struct AddrComp + { + bool operator()(const Peer& lhs, const Peer& rhs) const + { + return lhs.second < rhs.second; + } + }; + + util::Injected mIo; + SessionMembershipCallback mSessionMembershipCallback; + SessionTimelineCallback mSessionTimelineCallback; + SessionStartStopStateCallback mSessionStartStopStateCallback; + std::vector mPeers; // sorted by peerId, unique by (peerId, addr) + }; + + struct SessionMemberPred + { + bool operator()(const Peer& peer) const + { + return peer.first.sessionId() == sid; + } + + const SessionId& sid; + }; + + std::shared_ptr mpImpl; +}; + +template +Peers +makePeers(util::Injected io, + SessionMembershipCallback membershipCallback, + SessionTimelineCallback timelineCallback, + SessionStartStopStateCallback startStopStateCallback) +{ + return {std::move(io), std::move(membershipCallback), std::move(timelineCallback), + std::move(startStopStateCallback)}; +} + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/Phase.hpp b/tidal-link/link/include/ableton/link/Phase.hpp new file mode 100644 index 000000000..7268a62e8 --- /dev/null +++ b/tidal-link/link/include/ableton/link/Phase.hpp @@ -0,0 +1,100 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +// Returns a value in the range [0,quantum) corresponding to beats % +// quantum except that negative beat values are handled correctly. +// If the given quantum is zero, returns zero. +inline Beats phase(const Beats beats, const Beats quantum) +{ + if (quantum == Beats{INT64_C(0)}) + { + return Beats{INT64_C(0)}; + } + else + { + // Handle negative beat values by doing the computation relative to an + // origin that is on the nearest quantum boundary less than -(abs(x)) + const auto quantumMicros = quantum.microBeats(); + const auto quantumBins = (llabs(beats.microBeats()) + quantumMicros) / quantumMicros; + const std::int64_t quantumBeats{quantumBins * quantumMicros}; + return (beats + Beats{quantumBeats}) % quantum; + } +} + +// Return the least value greater than x that matches the phase of +// target with respect to the given quantum. If the given quantum +// quantum is 0, x is returned. +inline Beats nextPhaseMatch(const Beats x, const Beats target, const Beats quantum) +{ + const auto desiredPhase = phase(target, quantum); + const auto xPhase = phase(x, quantum); + const auto phaseDiff = (desiredPhase - xPhase + quantum) % quantum; + return x + phaseDiff; +} + +// Return the closest value to x that matches the phase of the target +// with respect to the given quantum. The result deviates from x by at +// most quantum/2, but may be less than x. +inline Beats closestPhaseMatch(const Beats x, const Beats target, const Beats quantum) +{ + return nextPhaseMatch(x - Beats{0.5 * quantum.floating()}, target, quantum); +} + +// Interprets the given timeline as encoding a quantum boundary at its +// origin. Given such a timeline, returns a phase-encoded beat value +// relative to the given quantum that corresponds to the given +// time. The phase of the resulting beat value can be calculated with +// phase(beats, quantum). The result will deviate by up to +- +// (quantum/2) beats compared to the result of tl.toBeats(time). +inline Beats toPhaseEncodedBeats( + const Timeline& tl, const std::chrono::microseconds time, const Beats quantum) +{ + const auto beat = tl.toBeats(time); + return closestPhaseMatch(beat, beat - tl.beatOrigin, quantum); +} + +// The inverse of toPhaseEncodedBeats. Given a phase encoded beat +// value from the given timeline and quantum, find the time value that +// it maps to. +inline std::chrono::microseconds fromPhaseEncodedBeats( + const Timeline& tl, const Beats beat, const Beats quantum) +{ + const auto fromOrigin = beat - tl.beatOrigin; + const auto originOffset = fromOrigin - phase(fromOrigin, quantum); + // invert the phase calculation so that it always rounds up in the + // middle instead of down like closestPhaseMatch. Otherwise we'll + // end up rounding down twice when a value is at phase quantum/2. + const auto inversePhaseOffset = closestPhaseMatch( + quantum - phase(fromOrigin, quantum), quantum - phase(beat, quantum), quantum); + return tl.fromBeats(tl.beatOrigin + originOffset + quantum - inversePhaseOffset); +} + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/PingResponder.hpp b/tidal-link/link/include/ableton/link/PingResponder.hpp new file mode 100644 index 000000000..a8f455fe5 --- /dev/null +++ b/tidal-link/link/include/ableton/link/PingResponder.hpp @@ -0,0 +1,171 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include +#include +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +template +class PingResponder +{ + using IoType = util::Injected; + using Socket = typename IoType::type::template Socket; + +public: + PingResponder(asio::ip::address_v4 address, + SessionId sessionId, + GhostXForm ghostXForm, + Clock clock, + IoType io) + : mIo(io) + , mpImpl(std::make_shared(std::move(address), + std::move(sessionId), + std::move(ghostXForm), + std::move(clock), + std::move(io))) + { + mpImpl->listen(); + } + + PingResponder(const PingResponder&) = delete; + PingResponder(PingResponder&&) = delete; + + void updateNodeState(const SessionId& sessionId, const GhostXForm& xform) + { + mpImpl->mSessionId = std::move(sessionId); + mpImpl->mGhostXForm = std::move(xform); + } + + asio::ip::udp::endpoint endpoint() const + { + return mpImpl->mSocket.endpoint(); + } + + asio::ip::address address() const + { + return endpoint().address(); + } + + Socket socket() const + { + return mpImpl->mSocket; + } + +private: + struct Impl : std::enable_shared_from_this + { + Impl(asio::ip::address_v4 address, + SessionId sessionId, + GhostXForm ghostXForm, + Clock clock, + IoType io) + : mSessionId(std::move(sessionId)) + , mGhostXForm(std::move(ghostXForm)) + , mClock(std::move(clock)) + , mLog(channel(io->log(), "gateway@" + address.to_string())) + , mSocket(io->template openUnicastSocket(address)) + { + } + + void listen() + { + mSocket.receive(util::makeAsyncSafe(this->shared_from_this())); + } + + // Operator to handle incoming messages on the interface + template + void operator()(const asio::ip::udp::endpoint& from, const It begin, const It end) + { + using namespace discovery; + + // Decode Ping Message + const auto result = link::v1::parseMessageHeader(begin, end); + const auto& header = result.first; + const auto payloadBegin = result.second; + + // Check Payload size + const auto payloadSize = static_cast(std::distance(payloadBegin, end)); + const auto maxPayloadSize = + sizeInByteStream(makePayload(HostTime{}, PrevGHostTime{})); + if (header.messageType == v1::kPing && payloadSize <= maxPayloadSize) + { + debug(mLog) << " Received ping message from " << from; + + try + { + reply(std::move(payloadBegin), std::move(end), from); + } + catch (const std::runtime_error& err) + { + info(mLog) << " Failed to send pong to " << from << ". Reason: " << err.what(); + } + } + else + { + info(mLog) << " Received invalid Message from " << from << "."; + } + listen(); + } + + template + void reply(It begin, It end, const asio::ip::udp::endpoint& to) + { + using namespace discovery; + + // Encode Pong Message + const auto id = SessionMembership{mSessionId}; + const auto currentGt = GHostTime{mGhostXForm.hostToGhost(mClock.micros())}; + const auto pongPayload = makePayload(id, currentGt); + + v1::MessageBuffer pongBuffer; + const auto pongMsgBegin = std::begin(pongBuffer); + auto pongMsgEnd = v1::pongMessage(pongPayload, pongMsgBegin); + // Append ping payload to pong message. + pongMsgEnd = std::copy(begin, end, pongMsgEnd); + + const auto numBytes = + static_cast(std::distance(pongMsgBegin, pongMsgEnd)); + mSocket.send(pongBuffer.data(), numBytes, to); + } + + SessionId mSessionId; + GhostXForm mGhostXForm; + Clock mClock; + typename IoType::type::Log mLog; + Socket mSocket; + }; + + IoType mIo; + std::shared_ptr mpImpl; +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/SessionId.hpp b/tidal-link/link/include/ableton/link/SessionId.hpp new file mode 100644 index 000000000..7881e2010 --- /dev/null +++ b/tidal-link/link/include/ableton/link/SessionId.hpp @@ -0,0 +1,63 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include + +namespace ableton +{ +namespace link +{ + +// SessionIds occupy the same value space as NodeIds and are +// identified by their founding node. +using SessionId = NodeId; + +// A payload entry indicating membership in a particular session +struct SessionMembership +{ + static const std::int32_t key = 'sess'; + static_assert(key == 0x73657373, "Unexpected byte order"); + + // Model the NetworkByteStreamSerializable concept + friend std::uint32_t sizeInByteStream(const SessionMembership& sm) + { + return discovery::sizeInByteStream(sm.sessionId); + } + + template + friend It toNetworkByteStream(const SessionMembership& sm, It out) + { + return discovery::toNetworkByteStream(sm.sessionId, std::move(out)); + } + + template + static std::pair fromNetworkByteStream(It begin, It end) + { + using namespace std; + auto idRes = SessionId::fromNetworkByteStream(std::move(begin), std::move(end)); + return make_pair(SessionMembership{std::move(idRes.first)}, std::move(idRes.second)); + } + + SessionId sessionId; +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/SessionState.hpp b/tidal-link/link/include/ableton/link/SessionState.hpp new file mode 100644 index 000000000..183c8a9c6 --- /dev/null +++ b/tidal-link/link/include/ableton/link/SessionState.hpp @@ -0,0 +1,115 @@ +/* Copyright 2017, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +using OptionalTimeline = Optional; +using OptionalStartStopState = Optional; +using OptionalClientStartStopState = Optional; + +struct SessionState +{ + Timeline timeline; + StartStopState startStopState; + GhostXForm ghostXForm; +}; + +struct ClientState +{ + friend bool operator==(const ClientState& lhs, const ClientState& rhs) + { + return std::tie(lhs.timeline, lhs.startStopState) + == std::tie(rhs.timeline, rhs.startStopState); + } + + friend bool operator!=(const ClientState& lhs, const ClientState& rhs) + { + return !(lhs == rhs); + } + + Timeline timeline; + ClientStartStopState startStopState; +}; + +struct ControllerClientState +{ + ControllerClientState(ClientState state) + : mState(state) + , mRtState(state) + { + } + + template + void update(Fn fn) + { + std::unique_lock lock(mMutex); + fn(mState); + mRtState.write(mState); + } + + ClientState get() const + { + std::unique_lock lock(mMutex); + return mState; + } + + ClientState getRt() const + { + return mRtState.read(); + } + +private: + mutable std::mutex mMutex; + ClientState mState; + mutable TripleBuffer mRtState; +}; + +struct RtClientState +{ + Timeline timeline; + ClientStartStopState startStopState; + std::chrono::microseconds timelineTimestamp; + std::chrono::microseconds startStopStateTimestamp; +}; + +struct IncomingClientState +{ + OptionalTimeline timeline; + OptionalClientStartStopState startStopState; + std::chrono::microseconds timelineTimestamp; +}; + +struct ApiState +{ + Timeline timeline; + ApiStartStopState startStopState; +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/Sessions.hpp b/tidal-link/link/include/ableton/link/Sessions.hpp new file mode 100644 index 000000000..14ea54af3 --- /dev/null +++ b/tidal-link/link/include/ableton/link/Sessions.hpp @@ -0,0 +1,301 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +struct SessionMeasurement +{ + GhostXForm xform; + std::chrono::microseconds timestamp; +}; + +struct Session +{ + SessionId sessionId; + Timeline timeline; + SessionMeasurement measurement; +}; + +template +class Sessions +{ +public: + using Timer = typename util::Injected::type::Timer; + + Sessions(Session init, + util::Injected peers, + MeasurePeer measure, + JoinSessionCallback join, + util::Injected io, + Clock clock) + : mPeers(std::move(peers)) + , mMeasure(std::move(measure)) + , mCallback(std::move(join)) + , mCurrent(std::move(init)) + , mIo(std::move(io)) + , mTimer(mIo->makeTimer()) + , mClock(std::move(clock)) + { + } + + void resetSession(Session session) + { + mCurrent = std::move(session); + mOtherSessions.clear(); + } + + void resetTimeline(Timeline timeline) + { + mCurrent.timeline = std::move(timeline); + } + + // Consider the observed session/timeline pair and return a possibly + // new timeline that should be used going forward. + Timeline sawSessionTimeline(SessionId sid, Timeline timeline) + { + using namespace std; + if (sid == mCurrent.sessionId) + { + // matches our current session, update the timeline if necessary + updateTimeline(mCurrent, std::move(timeline)); + } + else + { + auto session = Session{std::move(sid), std::move(timeline), {}}; + const auto range = + equal_range(begin(mOtherSessions), end(mOtherSessions), session, SessionIdComp{}); + if (range.first == range.second) + { + // brand new session, insert it into our list of known + // sessions and launch a measurement + launchSessionMeasurement(session); + mOtherSessions.insert(range.first, std::move(session)); + } + else + { + // we've seen this session before, update its timeline if necessary + updateTimeline(*range.first, std::move(timeline)); + } + } + return mCurrent.timeline; + } + +private: + void launchSessionMeasurement(Session& session) + { + using namespace std; + auto peers = mPeers->sessionPeers(session.sessionId); + if (!peers.empty()) + { + // first criteria: always prefer the founding peer + const auto it = find_if(begin(peers), end(peers), + [&session](const Peer& peer) { return session.sessionId == peer.first.ident(); }); + // TODO: second criteria should be degree. We don't have that + // represented yet so just use the first peer for now + auto peer = it == end(peers) ? peers.front() : *it; + // mark that a session is in progress by clearing out the + // session's timestamp + session.measurement.timestamp = {}; + mMeasure(std::move(peer), MeasurementResultsHandler{*this, session.sessionId}); + } + } + + void handleSuccessfulMeasurement(const SessionId& id, GhostXForm xform) + { + using namespace std; + + debug(mIo->log()) << "Session " << id << " measurement completed with result " + << "(" << xform.slope << ", " << xform.intercept.count() << ")"; + + auto measurement = SessionMeasurement{std::move(xform), mClock.micros()}; + + if (mCurrent.sessionId == id) + { + mCurrent.measurement = std::move(measurement); + mCallback(mCurrent); + } + else + { + const auto range = equal_range( + begin(mOtherSessions), end(mOtherSessions), Session{id, {}, {}}, SessionIdComp{}); + + if (range.first != range.second) + { + const auto SESSION_EPS = chrono::microseconds{500000}; + // should we join this session? + const auto hostTime = mClock.micros(); + const auto curGhost = mCurrent.measurement.xform.hostToGhost(hostTime); + const auto newGhost = measurement.xform.hostToGhost(hostTime); + // update the measurement for the session entry + range.first->measurement = std::move(measurement); + // If session times too close - fall back to session id order + const auto ghostDiff = newGhost - curGhost; + if (ghostDiff > SESSION_EPS + || (std::abs(ghostDiff.count()) < SESSION_EPS.count() + && id < mCurrent.sessionId)) + { + // The new session wins, switch over to it + auto current = mCurrent; + mCurrent = std::move(*range.first); + mOtherSessions.erase(range.first); + // Put the old current session back into our list of known + // sessions so that we won't re-measure it + const auto it = upper_bound( + begin(mOtherSessions), end(mOtherSessions), current, SessionIdComp{}); + mOtherSessions.insert(it, std::move(current)); + // And notify that we have a new session and make sure that + // we remeasure it periodically. + mCallback(mCurrent); + scheduleRemeasurement(); + } + } + } + } + + void scheduleRemeasurement() + { + // set a timer to re-measure the active session after a period + mTimer.expires_from_now(std::chrono::microseconds{30000000}); + mTimer.async_wait([this](const typename Timer::ErrorCode e) { + if (!e) + { + launchSessionMeasurement(mCurrent); + scheduleRemeasurement(); + } + }); + } + + void handleFailedMeasurement(const SessionId& id) + { + using namespace std; + + debug(mIo->log()) << "Session " << id << " measurement failed."; + + // if we failed to measure for our current session, schedule a + // retry in the future. Otherwise, remove the session from our set + // of known sessions (if it is seen again it will be measured as + // if new). + if (mCurrent.sessionId == id) + { + scheduleRemeasurement(); + } + else + { + const auto range = equal_range( + begin(mOtherSessions), end(mOtherSessions), Session{id, {}, {}}, SessionIdComp{}); + if (range.first != range.second) + { + mOtherSessions.erase(range.first); + mPeers->forgetSession(id); + } + } + } + + void updateTimeline(Session& session, Timeline timeline) + { + // We use beat origin magnitude to prioritize sessions. + if (timeline.beatOrigin > session.timeline.beatOrigin) + { + debug(mIo->log()) << "Adopting peer timeline (" << timeline.tempo.bpm() << ", " + << timeline.beatOrigin.floating() << ", " + << timeline.timeOrigin.count() << ")"; + + session.timeline = std::move(timeline); + } + else + { + debug(mIo->log()) << "Rejecting peer timeline with beat origin: " + << timeline.beatOrigin.floating() + << ". Current timeline beat origin: " + << session.timeline.beatOrigin.floating(); + } + } + + struct MeasurementResultsHandler + { + void operator()(GhostXForm xform) const + { + Sessions& sessions = mSessions; + const SessionId& sessionId = mSessionId; + if (xform == GhostXForm{}) + { + sessions.handleFailedMeasurement(std::move(sessionId)); + } + else + { + sessions.handleSuccessfulMeasurement(std::move(sessionId), std::move(xform)); + } + } + + Sessions& mSessions; + SessionId mSessionId; + }; + + struct SessionIdComp + { + bool operator()(const Session& lhs, const Session& rhs) const + { + return lhs.sessionId < rhs.sessionId; + } + }; + + using Peer = typename util::Injected::type::Peer; + util::Injected mPeers; + MeasurePeer mMeasure; + JoinSessionCallback mCallback; + Session mCurrent; + util::Injected mIo; + Timer mTimer; + Clock mClock; + std::vector mOtherSessions; // sorted/unique by session id +}; + +template +Sessions makeSessions( + Session init, + util::Injected peers, + MeasurePeer measure, + JoinSessionCallback join, + util::Injected io, + Clock clock) +{ + using namespace std; + return {std::move(init), std::move(peers), std::move(measure), std::move(join), + std::move(io), std::move(clock)}; +} + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/StartStopState.hpp b/tidal-link/link/include/ableton/link/StartStopState.hpp new file mode 100644 index 000000000..1caad99bf --- /dev/null +++ b/tidal-link/link/include/ableton/link/StartStopState.hpp @@ -0,0 +1,152 @@ +/* Copyright 2017, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +// A tuple of (isPlaying, time) that represents the playing state +// with an according timestamp in microseconds. It also serves as a +// payload entry. + +struct StartStopState +{ + static const std::int32_t key = 'stst'; + static_assert(key == 0x73747374, "Unexpected byte order"); + + using StartStopStateTuple = std::tuple; + + StartStopState() = default; + + StartStopState( + const bool aIsPlaying, const Beats aBeats, const std::chrono::microseconds aTimestamp) + : isPlaying(aIsPlaying) + , beats(aBeats) + , timestamp(aTimestamp) + { + } + + friend bool operator==(const StartStopState& lhs, const StartStopState& rhs) + { + return std::tie(lhs.isPlaying, lhs.beats, lhs.timestamp) + == std::tie(rhs.isPlaying, rhs.beats, rhs.timestamp); + } + + friend bool operator!=(const StartStopState& lhs, const StartStopState& rhs) + { + return !(lhs == rhs); + } + + // Model the NetworkByteStreamSerializable concept + friend std::uint32_t sizeInByteStream(const StartStopState& state) + { + return discovery::sizeInByteStream(state.asTuple()); + } + + template + friend It toNetworkByteStream(const StartStopState& state, It out) + { + return discovery::toNetworkByteStream(state.asTuple(), std::move(out)); + } + + template + static std::pair fromNetworkByteStream(It begin, It end) + { + using namespace std; + using namespace discovery; + auto result = Deserialize::fromNetworkByteStream( + std::move(begin), std::move(end)); + auto state = + StartStopState{get<0>(result.first), get<1>(result.first), get<2>(result.first)}; + return make_pair(std::move(state), std::move(result.second)); + } + + bool isPlaying{false}; + Beats beats{0.}; + std::chrono::microseconds timestamp{0}; + +private: + StartStopStateTuple asTuple() const + { + return std::make_tuple(isPlaying, beats, timestamp); + } +}; + +struct ClientStartStopState +{ + ClientStartStopState() = default; + + ClientStartStopState(const bool aIsPlaying, + const std::chrono::microseconds aTime, + const std::chrono::microseconds aTimestamp) + : isPlaying(aIsPlaying) + , time(aTime) + , timestamp(aTimestamp) + { + } + + friend bool operator==(const ClientStartStopState& lhs, const ClientStartStopState& rhs) + { + return std::tie(lhs.isPlaying, lhs.time, lhs.timestamp) + == std::tie(rhs.isPlaying, rhs.time, rhs.timestamp); + } + + friend bool operator!=(const ClientStartStopState& lhs, const ClientStartStopState& rhs) + { + return !(lhs == rhs); + } + + bool isPlaying{false}; + std::chrono::microseconds time{0}; + std::chrono::microseconds timestamp{0}; +}; + +struct ApiStartStopState +{ + ApiStartStopState() = default; + + ApiStartStopState(const bool aIsPlaying, const std::chrono::microseconds aTime) + : isPlaying(aIsPlaying) + , time(aTime) + { + } + + friend bool operator==(const ApiStartStopState& lhs, const ApiStartStopState& rhs) + { + return std::tie(lhs.isPlaying, lhs.time) == std::tie(rhs.isPlaying, rhs.time); + } + + friend bool operator!=(const ApiStartStopState& lhs, const ApiStartStopState& rhs) + { + return !(lhs == rhs); + } + + bool isPlaying{false}; + std::chrono::microseconds time{0}; +}; +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/Tempo.hpp b/tidal-link/link/include/ableton/link/Tempo.hpp new file mode 100644 index 000000000..69beb9c91 --- /dev/null +++ b/tidal-link/link/include/ableton/link/Tempo.hpp @@ -0,0 +1,125 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include + +namespace ableton +{ +namespace link +{ + +struct Tempo +{ + Tempo() = default; + + // Beats per minute + explicit Tempo(const double bpm) + : mValue(bpm) + { + } + + Tempo(const std::chrono::microseconds microsPerBeat) + : mValue(60. * 1e6 / static_cast(microsPerBeat.count())) + { + } + + double bpm() const + { + return mValue; + } + + std::chrono::microseconds microsPerBeat() const + { + return std::chrono::microseconds{std::llround(60. * 1e6 / bpm())}; + } + + // Given the tempo, convert a time to a beat value + Beats microsToBeats(const std::chrono::microseconds micros) const + { + return Beats{ + static_cast(micros.count()) / static_cast(microsPerBeat().count())}; + } + + // Given the tempo, convert a beat to a time value + std::chrono::microseconds beatsToMicros(const Beats beats) const + { + return std::chrono::microseconds{ + std::llround(beats.floating() * static_cast(microsPerBeat().count()))}; + } + + // Model the NetworkByteStreamSerializable concept + friend std::uint32_t sizeInByteStream(const Tempo tempo) + { + return discovery::sizeInByteStream(tempo.microsPerBeat()); + } + + template + friend It toNetworkByteStream(const Tempo tempo, It out) + { + return discovery::toNetworkByteStream(tempo.microsPerBeat(), std::move(out)); + } + + template + static std::pair fromNetworkByteStream(It begin, It end) + { + auto result = + discovery::Deserialize::fromNetworkByteStream( + std::move(begin), std::move(end)); + return std::make_pair(Tempo{std::move(result.first)}, std::move(result.second)); + } + + friend bool operator==(const Tempo lhs, const Tempo rhs) + { + return lhs.mValue == rhs.mValue; + } + + friend bool operator!=(const Tempo lhs, const Tempo rhs) + { + return lhs.mValue != rhs.mValue; + } + + friend bool operator<(const Tempo lhs, const Tempo rhs) + { + return lhs.mValue < rhs.mValue; + } + + friend bool operator>(const Tempo lhs, const Tempo rhs) + { + return lhs.mValue > rhs.mValue; + } + + friend bool operator<=(const Tempo lhs, const Tempo rhs) + { + return lhs.mValue <= rhs.mValue; + } + + friend bool operator>=(const Tempo lhs, const Tempo rhs) + { + return lhs.mValue >= rhs.mValue; + } + +private: + double mValue = 0; +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/Timeline.hpp b/tidal-link/link/include/ableton/link/Timeline.hpp new file mode 100644 index 000000000..9fa3a4541 --- /dev/null +++ b/tidal-link/link/include/ableton/link/Timeline.hpp @@ -0,0 +1,98 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +// A tuple of (tempo, beats, time), with integral units +// based on microseconds. This type establishes a bijection between +// beats and wall time, given a valid tempo. It also serves as a +// payload entry. + +struct Timeline +{ + static const std::int32_t key = 'tmln'; + static_assert(key == 0x746d6c6e, "Unexpected byte order"); + + Beats toBeats(const std::chrono::microseconds time) const + { + return beatOrigin + tempo.microsToBeats(time - timeOrigin); + } + + std::chrono::microseconds fromBeats(const Beats beats) const + { + return timeOrigin + tempo.beatsToMicros(beats - beatOrigin); + } + + friend bool operator==(const Timeline& lhs, const Timeline& rhs) + { + return std::tie(lhs.tempo, lhs.beatOrigin, lhs.timeOrigin) + == std::tie(rhs.tempo, rhs.beatOrigin, rhs.timeOrigin); + } + + friend bool operator!=(const Timeline& lhs, const Timeline& rhs) + { + return !(lhs == rhs); + } + + // Model the NetworkByteStreamSerializable concept + friend std::uint32_t sizeInByteStream(const Timeline& tl) + { + return discovery::sizeInByteStream(std::tie(tl.tempo, tl.beatOrigin, tl.timeOrigin)); + } + + template + friend It toNetworkByteStream(const Timeline& tl, It out) + { + return discovery::toNetworkByteStream( + std::tie(tl.tempo, tl.beatOrigin, tl.timeOrigin), std::move(out)); + } + + template + static std::pair fromNetworkByteStream(It begin, It end) + { + using namespace std; + using namespace discovery; + Timeline timeline; + auto result = + Deserialize>::fromNetworkByteStream( + std::move(begin), std::move(end)); + tie(timeline.tempo, timeline.beatOrigin, timeline.timeOrigin) = + std::move(result.first); + return make_pair(std::move(timeline), std::move(result.second)); + } + + Tempo tempo; + Beats beatOrigin; + std::chrono::microseconds timeOrigin; +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/TripleBuffer.hpp b/tidal-link/link/include/ableton/link/TripleBuffer.hpp new file mode 100644 index 000000000..10a83c1be --- /dev/null +++ b/tidal-link/link/include/ableton/link/TripleBuffer.hpp @@ -0,0 +1,121 @@ +/* Copyright 2022, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + + +#pragma once + +#include + +#include +#include +#include +#include + +namespace ableton +{ +namespace link +{ + +template +struct TripleBuffer +{ +public: + TripleBuffer() + : mBuffers{{{}, {}, {}}} + { + assert(mState.is_lock_free()); + } + + explicit TripleBuffer(const T& initial) + : mBuffers{{initial, initial, initial}} + { + assert(mState.is_lock_free()); + } + + TripleBuffer(const TripleBuffer&) = delete; + TripleBuffer& operator=(const TripleBuffer&) = delete; + + T read() noexcept + { + loadReadBuffer(); + return mBuffers[mReadIndex]; + } + + Optional readNew() + { + if (loadReadBuffer()) + { + return Optional(mBuffers[mReadIndex]); + } + return {}; + } + + template + void write(U&& value) + { + mBuffers[mWriteIndex] = std::forward(value); + + const auto prevState = + mState.exchange(makeState(mWriteIndex, true), std::memory_order_acq_rel); + + mWriteIndex = backIndex(prevState); + } + +private: + bool loadReadBuffer() + { + auto state = mState.load(std::memory_order_acquire); + auto isNew = isNewWrite(state); + if (isNew) + { + const auto prevState = + mState.exchange(makeState(mReadIndex, false), std::memory_order_acq_rel); + + mReadIndex = backIndex(prevState); + } + return isNew; + } + + using BackingState = uint32_t; + + static constexpr bool isNewWrite(const BackingState state) + { + return (state & 0x0000FFFFu) != 0; + } + + static constexpr uint32_t backIndex(const BackingState state) + { + return state >> 16; + } + + static constexpr BackingState makeState( + const uint32_t backBufferIndex, const bool isWrite) + { + return (backBufferIndex << 16) | uint32_t(isWrite); + } + + std::atomic mState{makeState(1u, false)}; // Reader and writer + uint32_t mReadIndex = 0u; // Reader only + uint32_t mWriteIndex = 2u; // Writer only + + std::array mBuffers{}; +}; + +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/link/v1/Messages.hpp b/tidal-link/link/include/ableton/link/v1/Messages.hpp new file mode 100644 index 000000000..a0e0ee323 --- /dev/null +++ b/tidal-link/link/include/ableton/link/v1/Messages.hpp @@ -0,0 +1,138 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include + +namespace ableton +{ +namespace link +{ +namespace v1 +{ + +// The maximum size of a message, in bytes +const std::size_t kMaxMessageSize = 512; +// Utility typedef for an array of bytes of maximum message size +using MessageBuffer = std::array; + +using MessageType = uint8_t; + +const MessageType kPing = 1; +const MessageType kPong = 2; + +struct MessageHeader +{ + MessageType messageType; + + friend std::uint32_t sizeInByteStream(const MessageHeader& header) + { + return discovery::sizeInByteStream(header.messageType); + } + + template + friend It toNetworkByteStream(const MessageHeader& header, It out) + { + return discovery::toNetworkByteStream(header.messageType, std::move(out)); + } + + template + static std::pair fromNetworkByteStream(It begin, const It end) + { + using namespace discovery; + + MessageHeader header; + std::tie(header.messageType, begin) = + Deserialize::fromNetworkByteStream(begin, end); + + return std::make_pair(std::move(header), std::move(begin)); + } +}; + +namespace detail +{ + +// Types that are only used in the sending/parsing of messages, not +// publicly exposed. +using ProtocolHeader = std::array; +const ProtocolHeader kProtocolHeader = {{'_', 'l', 'i', 'n', 'k', '_', 'v', 1}}; + +// Must have at least kMaxMessageSize bytes available in the output stream +template +It encodeMessage(const MessageType messageType, const Payload& payload, It out) +{ + using namespace std; + const MessageHeader header = {messageType}; + const auto messageSize = + kProtocolHeader.size() + sizeInByteStream(header) + sizeInByteStream(payload); + + if (messageSize < kMaxMessageSize) + { + return toNetworkByteStream( + payload, toNetworkByteStream(header, + copy(begin(kProtocolHeader), end(kProtocolHeader), std::move(out)))); + } + else + { + throw range_error("Exceeded maximum message size"); + } +} + +} // namespace detail + +template +It pingMessage(const Payload& payload, It out) +{ + return detail::encodeMessage(kPing, payload, std::move(out)); +} + +template +It pongMessage(const Payload& payload, It out) +{ + return detail::encodeMessage(kPong, payload, std::move(out)); +} + +template +std::pair parseMessageHeader(It bytesBegin, const It bytesEnd) +{ + using ItDiff = typename std::iterator_traits::difference_type; + + MessageHeader header = {}; + const auto protocolHeaderSize = discovery::sizeInByteStream(detail::kProtocolHeader); + const auto minMessageSize = + static_cast(protocolHeaderSize + sizeInByteStream(header)); + + // If there are enough bytes in the stream to make a header and if + // the first bytes in the stream are the protocol header, then + // proceed to parse the stream. + if (std::distance(bytesBegin, bytesEnd) >= minMessageSize + && std::equal( + begin(detail::kProtocolHeader), end(detail::kProtocolHeader), bytesBegin)) + { + std::tie(header, bytesBegin) = + MessageHeader::fromNetworkByteStream(bytesBegin + protocolHeaderSize, bytesEnd); + } + return std::make_pair(std::move(header), std::move(bytesBegin)); +} + +} // namespace v1 +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/Config.hpp b/tidal-link/link/include/ableton/platforms/Config.hpp new file mode 100644 index 000000000..9deba58bd --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/Config.hpp @@ -0,0 +1,101 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include + +#if defined(LINK_PLATFORM_WINDOWS) +#include +#include +#include +#include +#if defined(LINK_WINDOWS_SETTHREADDESCRIPTION) +#include +#endif +#elif defined(LINK_PLATFORM_MACOSX) +#include +#include +#include +#include +#include +#elif defined(LINK_PLATFORM_LINUX) +#include +#include +#include +#include +#ifdef __linux__ +#include +#endif +#elif defined(ESP_PLATFORM) +#include +#include +#include +#include +#endif + +namespace ableton +{ +namespace link +{ +namespace platform +{ + +#if defined(LINK_PLATFORM_WINDOWS) +using Clock = platforms::windows::Clock; +using Random = platforms::stl::Random; +#if defined(LINK_WINDOWS_SETTHREADDESCRIPTION) +using IoContext = platforms::asio::Context; +#else +using IoContext = + platforms::asio::Context; +#endif + +#elif defined(LINK_PLATFORM_MACOSX) +using Clock = platforms::darwin::Clock; +using IoContext = platforms::asio::Context; +using Random = platforms::stl::Random; + +#elif defined(LINK_PLATFORM_LINUX) +using Clock = platforms::linux::ClockMonotonicRaw; +using Random = platforms::stl::Random; +#ifdef __linux__ +using IoContext = platforms::asio::Context; +#else +using IoContext = + platforms::asio::Context; +#endif + +#elif defined(ESP_PLATFORM) +using Clock = platforms::esp32::Clock; +using IoContext = + platforms::esp32::Context; +using Random = platforms::esp32::Random; +#endif + +} // namespace platform +} // namespace link +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/asio/AsioTimer.hpp b/tidal-link/link/include/ableton/platforms/asio/AsioTimer.hpp new file mode 100644 index 000000000..e2c71b011 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/asio/AsioTimer.hpp @@ -0,0 +1,132 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace platforms +{ +namespace asio +{ + +// This implementation is based on the boost::asio::system_timer concept. +// Since boost::system_timer doesn't support move semantics, we create a wrapper +// with a unique_ptr to get a movable type. It also handles an inconvenient +// aspect of asio timers, which is that you must explicitly guard against the +// handler firing after cancellation. We handle this by use of the SafeAsyncHandler +// utility. AsioTimer therefore guarantees that a handler will not be called after +// the destruction of the timer, or after the timer has been canceled. + +class AsioTimer +{ +public: + using ErrorCode = ::asio::error_code; + using TimePoint = std::chrono::system_clock::time_point; + + AsioTimer(::asio::io_service& io) + : mpTimer(new ::asio::system_timer(io)) + , mpAsyncHandler(std::make_shared()) + { + } + + ~AsioTimer() + { + // The timer may not be valid anymore if this instance was moved from + if (mpTimer != nullptr) + { + // Ignore errors during cancellation + cancel(); + } + } + + AsioTimer(const AsioTimer&) = delete; + AsioTimer& operator=(const AsioTimer&) = delete; + + // Enable move construction but not move assignment. Move assignment + // would get weird - would have to handle outstanding handlers + AsioTimer(AsioTimer&& rhs) + : mpTimer(std::move(rhs.mpTimer)) + , mpAsyncHandler(std::move(rhs.mpAsyncHandler)) + { + } + + void expires_at(std::chrono::system_clock::time_point tp) + { + mpTimer->expires_at(std::move(tp)); + } + + template + void expires_from_now(T duration) + { + mpTimer->expires_from_now(std::move(duration)); + } + + ErrorCode cancel() + { + ErrorCode ec; + mpTimer->cancel(ec); + mpAsyncHandler->mpHandler = nullptr; + return ec; + } + + template + void async_wait(Handler handler) + { + *mpAsyncHandler = std::move(handler); + mpTimer->async_wait(util::makeAsyncSafe(mpAsyncHandler)); + } + + TimePoint now() const + { + return std::chrono::system_clock::now(); + } + +private: + struct AsyncHandler + { + template + AsyncHandler& operator=(Handler handler) + { + mpHandler = [handler](ErrorCode ec) { handler(std::move(ec)); }; + return *this; + } + + void operator()(ErrorCode ec) + { + if (mpHandler) + { + mpHandler(std::move(ec)); + } + } + + std::function mpHandler; + }; + + std::unique_ptr<::asio::system_timer> mpTimer; + std::shared_ptr mpAsyncHandler; +}; + +} // namespace asio +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/asio/AsioWrapper.hpp b/tidal-link/link/include/ableton/platforms/asio/AsioWrapper.hpp new file mode 100644 index 000000000..1f3dc4d4e --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/asio/AsioWrapper.hpp @@ -0,0 +1,90 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +/*! + * \brief Wrapper file for AsioStandalone library + * + * This file includes all necessary headers from the AsioStandalone library which are used + * by Link. + */ + +#if !defined(ESP_PLATFORM) +#pragma push_macro("ASIO_STANDALONE") +#define ASIO_STANDALONE 1 + +#pragma push_macro("ASIO_NO_TYPEID") +#define ASIO_NO_TYPEID 1 +#endif + +#if defined(LINK_PLATFORM_WINDOWS) +#pragma push_macro("INCL_EXTRA_HTON_FUNCTIONS") +#define INCL_EXTRA_HTON_FUNCTIONS 1 +#endif + +#if defined(WIN32) || defined(_WIN32) +#if !defined(_WIN32_WINNT) +#define _WIN32_WINNT 0x0501 +#endif +#endif + +#if defined(__clang__) +#pragma clang diagnostic push +#if __has_warning("-Wcomma") +#pragma clang diagnostic ignored "-Wcomma" +#endif +#if __has_warning("-Wshorten-64-to-32") +#pragma clang diagnostic ignored "-Wshorten-64-to-32" +#endif +#if __has_warning("-Wunused-local-typedef") +#pragma clang diagnostic ignored "-Wunused-local-typedef" +#endif +#endif + +#if defined(_MSC_VER) +#define _SCL_SECURE_NO_WARNINGS 1 +#pragma warning(push, 0) +#pragma warning(disable : 4242) +#pragma warning(disable : 4668) +#pragma warning(disable : 4702) +#pragma warning(disable : 5204) +#pragma warning(disable : 5220) +#endif + +#include +#include + +#if defined(LINK_PLATFORM_WINDOWS) +#pragma pop_macro("INCL_EXTRA_HTON_FUNCTIONS") +#endif + +#if !defined(ESP_PLATFORM) +#pragma pop_macro("ASIO_STANDALONE") +#pragma pop_macro("ASIO_NO_TYPEID") +#endif + +#if defined(_MSC_VER) +#pragma warning(pop) +#undef _SCL_SECURE_NO_WARNINGS +#endif + +#if defined(__clang__) +#pragma clang diagnostic pop +#endif diff --git a/tidal-link/link/include/ableton/platforms/asio/Context.hpp b/tidal-link/link/include/ableton/platforms/asio/Context.hpp new file mode 100644 index 000000000..7c10a4bc5 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/asio/Context.hpp @@ -0,0 +1,196 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include +#include +#include +#include + +namespace ableton +{ +namespace platforms +{ +namespace asio +{ +namespace +{ + +struct ThreadFactory +{ + template + static std::thread makeThread(std::string, Callable&& f, Args&&... args) + { + return std::thread(std::forward(f), std::forward(args)...); + } +}; + +} // namespace + +template +class Context +{ +public: + using Timer = AsioTimer; + using Log = LogT; + + template + using LockFreeCallbackDispatcher = + LockFreeCallbackDispatcher; + + template + using Socket = asio::Socket; + + Context() + : Context(DefaultHandler{}) + { + } + + template + explicit Context(ExceptionHandler exceptHandler) + : mpService(new ::asio::io_service()) + , mpWork(new ::asio::io_service::work(*mpService)) + { + mThread = ThreadFactoryT::makeThread("Link Main", + [](::asio::io_service& service, ExceptionHandler handler) { + for (;;) + { + try + { + service.run(); + break; + } + catch (const typename ExceptionHandler::Exception& exception) + { + handler(exception); + } + } + }, + std::ref(*mpService), std::move(exceptHandler)); + } + + Context(const Context&) = delete; + + Context(Context&& rhs) + : mpService(std::move(rhs.mpService)) + , mpWork(std::move(rhs.mpWork)) + , mThread(std::move(rhs.mThread)) + , mLog(std::move(rhs.mLog)) + , mScanIpIfAddrs(std::move(rhs.mScanIpIfAddrs)) + { + } + + ~Context() + { + if (mpService && mpWork) + { + mpWork.reset(); + mThread.join(); + } + } + + void stop() + { + if (mpService && mpWork) + { + mpWork.reset(); + mpService->stop(); + mThread.join(); + } + } + + + template + Socket openUnicastSocket(const ::asio::ip::address_v4& addr) + { + auto socket = Socket{*mpService}; + socket.mpImpl->mSocket.set_option( + ::asio::ip::multicast::enable_loopback(addr.is_loopback())); + socket.mpImpl->mSocket.set_option(::asio::ip::multicast::outbound_interface(addr)); + socket.mpImpl->mSocket.bind(::asio::ip::udp::endpoint{addr, 0}); + return socket; + } + + template + Socket openMulticastSocket(const ::asio::ip::address_v4& addr) + { + auto socket = Socket{*mpService}; + socket.mpImpl->mSocket.set_option(::asio::ip::udp::socket::reuse_address(true)); + socket.mpImpl->mSocket.set_option( + ::asio::socket_base::broadcast(!addr.is_loopback())); + socket.mpImpl->mSocket.set_option( + ::asio::ip::multicast::enable_loopback(addr.is_loopback())); + socket.mpImpl->mSocket.set_option(::asio::ip::multicast::outbound_interface(addr)); + socket.mpImpl->mSocket.bind({::asio::ip::address::from_string("0.0.0.0"), + discovery::multicastEndpoint().port()}); + socket.mpImpl->mSocket.set_option(::asio::ip::multicast::join_group( + discovery::multicastEndpoint().address().to_v4(), addr)); + return socket; + } + + std::vector<::asio::ip::address> scanNetworkInterfaces() + { + return mScanIpIfAddrs(); + } + + Timer makeTimer() const + { + return {*mpService}; + } + + Log& log() + { + return mLog; + } + + template + void async(Handler handler) + { + mpService->post(std::move(handler)); + } + +private: + // Default handler is hidden and defines a hidden exception type + // that will never be thrown by other code, so it effectively does + // not catch. + struct DefaultHandler + { + struct Exception + { + }; + + void operator()(const Exception&) + { + } + }; + + std::unique_ptr<::asio::io_service> mpService; + std::unique_ptr<::asio::io_service::work> mpWork; + std::thread mThread; + Log mLog; + ScanIpIfAddrs mScanIpIfAddrs; +}; + +} // namespace asio +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/asio/LockFreeCallbackDispatcher.hpp b/tidal-link/link/include/ableton/platforms/asio/LockFreeCallbackDispatcher.hpp new file mode 100644 index 000000000..189a6f7ce --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/asio/LockFreeCallbackDispatcher.hpp @@ -0,0 +1,88 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace platforms +{ +namespace asio +{ + +// Utility to signal invocation of a callback on another thread in a lock free manner. +// The callback is evoked on a thread owned by the instance of this class. +// +// A condition variable is used to notify a waiting thread, but only if the required +// lock can be acquired immediately. If that fails, we fall back on signaling +// after a timeout. This gives us a guaranteed minimum signaling rate which is defined +// by the fallbackPeriod parameter. + +template +class LockFreeCallbackDispatcher +{ +public: + LockFreeCallbackDispatcher(Callback callback, Duration fallbackPeriod) + : mCallback(std::move(callback)) + , mFallbackPeriod(std::move(fallbackPeriod)) + , mRunning(true) + , mThread(ThreadFactory::makeThread("Link Dispatcher", [this] { run(); })) + { + } + + ~LockFreeCallbackDispatcher() + { + mRunning = false; + mCondition.notify_one(); + mThread.join(); + } + + void invoke() + { + mCondition.notify_one(); + } + +private: + void run() + { + while (mRunning.load()) + { + { + std::unique_lock lock(mMutex); + mCondition.wait_for(lock, mFallbackPeriod); + } + mCallback(); + } + } + + Callback mCallback; + Duration mFallbackPeriod; + std::atomic mRunning; + std::mutex mMutex; + std::condition_variable mCondition; + std::thread mThread; +}; + +} // namespace asio +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/asio/Socket.hpp b/tidal-link/link/include/ableton/platforms/asio/Socket.hpp new file mode 100644 index 000000000..8992f6d00 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/asio/Socket.hpp @@ -0,0 +1,110 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include + +namespace ableton +{ +namespace platforms +{ +namespace asio +{ + +template +struct Socket +{ + Socket(::asio::io_service& io) + : mpImpl(std::make_shared(io)) + { + } + + Socket(const Socket&) = delete; + Socket& operator=(const Socket&) = delete; + + Socket(Socket&& rhs) + : mpImpl(std::move(rhs.mpImpl)) + { + } + + std::size_t send(const uint8_t* const pData, + const size_t numBytes, + const ::asio::ip::udp::endpoint& to) + { + assert(numBytes < MaxPacketSize); + return mpImpl->mSocket.send_to(::asio::buffer(pData, numBytes), to); + } + + template + void receive(Handler handler) + { + mpImpl->mHandler = std::move(handler); + mpImpl->mSocket.async_receive_from( + ::asio::buffer(mpImpl->mReceiveBuffer, MaxPacketSize), mpImpl->mSenderEndpoint, + util::makeAsyncSafe(mpImpl)); + } + + ::asio::ip::udp::endpoint endpoint() const + { + return mpImpl->mSocket.local_endpoint(); + } + + struct Impl + { + Impl(::asio::io_service& io) + : mSocket(io, ::asio::ip::udp::v4()) + { + } + + ~Impl() + { + // Ignore error codes in shutdown and close as the socket may + // have already been forcibly closed + ::asio::error_code ec; + mSocket.shutdown(::asio::ip::udp::socket::shutdown_both, ec); + mSocket.close(ec); + } + + void operator()(const ::asio::error_code& error, const std::size_t numBytes) + { + if (!error && numBytes > 0 && numBytes <= MaxPacketSize) + { + const auto bufBegin = begin(mReceiveBuffer); + mHandler(mSenderEndpoint, bufBegin, bufBegin + static_cast(numBytes)); + } + } + + ::asio::ip::udp::socket mSocket; + ::asio::ip::udp::endpoint mSenderEndpoint; + using Buffer = std::array; + Buffer mReceiveBuffer; + using ByteIt = typename Buffer::const_iterator; + std::function mHandler; + }; + + std::shared_ptr mpImpl; +}; + +} // namespace asio +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/asio/Util.hpp b/tidal-link/link/include/ableton/platforms/asio/Util.hpp new file mode 100644 index 000000000..b974c10cc --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/asio/Util.hpp @@ -0,0 +1,43 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include + +namespace ableton +{ +namespace platforms +{ +namespace asio +{ + +// Utility for making v4 or v6 ip addresses from raw bytes in network byte-order +template +AsioAddrType makeAddress(const char* pAddr) +{ + using namespace std; + typename AsioAddrType::bytes_type bytes; + copy(pAddr, pAddr + bytes.size(), begin(bytes)); + return AsioAddrType{bytes}; +} + +} // namespace asio +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/darwin/Clock.hpp b/tidal-link/link/include/ableton/platforms/darwin/Clock.hpp new file mode 100644 index 000000000..dd40ff4b2 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/darwin/Clock.hpp @@ -0,0 +1,70 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include + +namespace ableton +{ +namespace platforms +{ +namespace darwin +{ + +struct Clock +{ + using Ticks = std::uint64_t; + using Micros = std::chrono::microseconds; + + Clock() + { + mach_timebase_info_data_t timeInfo; + mach_timebase_info(&timeInfo); + // numer / denom gives nanoseconds, we want microseconds + mTicksToMicros = timeInfo.numer / (timeInfo.denom * 1000.); + } + + Micros ticksToMicros(const Ticks ticks) const + { + return Micros{llround(mTicksToMicros * ticks)}; + } + + Ticks microsToTicks(const Micros micros) const + { + return static_cast(micros.count() / mTicksToMicros); + } + + Ticks ticks() const + { + return mach_absolute_time(); + } + + std::chrono::microseconds micros() const + { + return ticksToMicros(ticks()); + } + + double mTicksToMicros; +}; + +} // namespace darwin +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/darwin/Darwin.hpp b/tidal-link/link/include/ableton/platforms/darwin/Darwin.hpp new file mode 100644 index 000000000..c645db037 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/darwin/Darwin.hpp @@ -0,0 +1,30 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +// ntohll and htonll are not defined in 10.7 SDK, so we provide a compatibility macro here + +#ifndef ntohll +#define ntohll(x) __DARWIN_OSSwapInt64(x) +#endif + +#ifndef htonll +#define htonll(x) __DARWIN_OSSwapInt64(x) +#endif diff --git a/tidal-link/link/include/ableton/platforms/darwin/ThreadFactory.hpp b/tidal-link/link/include/ableton/platforms/darwin/ThreadFactory.hpp new file mode 100644 index 000000000..22c3162cc --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/darwin/ThreadFactory.hpp @@ -0,0 +1,48 @@ +/* Copyright 2021, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace platforms +{ +namespace darwin +{ + +struct ThreadFactory +{ + template + static std::thread makeThread(std::string name, Callable&& f, Args&&... args) + { + return std::thread{[](std::string name, Callable&& f, Args&&... args) { + pthread_setname_np(name.c_str()); + f(args...); + }, + std::move(name), std::forward(f), std::forward(args)...}; + } +}; + +} // namespace darwin +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/esp32/Clock.hpp b/tidal-link/link/include/ableton/platforms/esp32/Clock.hpp new file mode 100644 index 000000000..5cfaf0b49 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/esp32/Clock.hpp @@ -0,0 +1,36 @@ +/* Copyright 2019, Mathias Bredholt, Torso Electronics, Copenhagen. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + */ + +#pragma once + +#include "esp_timer.h" + +namespace ableton +{ +namespace platforms +{ +namespace esp32 +{ +struct Clock +{ + std::chrono::microseconds micros() const + { + return static_cast(esp_timer_get_time()); + } +}; +} // namespace esp32 +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/esp32/Context.hpp b/tidal-link/link/include/ableton/platforms/esp32/Context.hpp new file mode 100644 index 000000000..0c1cd00b5 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/esp32/Context.hpp @@ -0,0 +1,228 @@ +/* Copyright 2020, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include +#include +#include +#include +#include + +namespace ableton +{ +namespace platforms +{ +namespace esp32 +{ + +template +class Context +{ + class ServiceRunner + { + + static void run(void* userParams) + { + auto runner = static_cast(userParams); + for (;;) + { + try + { + ulTaskNotifyTake(pdTRUE, portMAX_DELAY); + runner->mpService->poll_one(); + } + catch (...) + { + } + } + } + + static void IRAM_ATTR timerIsr(void* userParam) + { + static BaseType_t xHigherPriorityTaskWoken = pdFALSE; + + timer_group_clr_intr_status_in_isr(TIMER_GROUP_0, TIMER_1); + timer_group_enable_alarm_in_isr(TIMER_GROUP_0, TIMER_1); + + vTaskNotifyGiveFromISR(userParam, &xHigherPriorityTaskWoken); + if (xHigherPriorityTaskWoken) + { + portYIELD_FROM_ISR(); + } + } + + public: + ServiceRunner() + : mpService(new ::asio::io_service()) + , mpWork(new ::asio::io_service::work(*mpService)) + { + xTaskCreatePinnedToCore(run, "link", 8192, this, 2 | portPRIVILEGE_BIT, + &mTaskHandle, LINK_ESP_TASK_CORE_ID); + + timer_config_t config = {.alarm_en = TIMER_ALARM_EN, + .counter_en = TIMER_PAUSE, + .intr_type = TIMER_INTR_LEVEL, + .counter_dir = TIMER_COUNT_UP, + .auto_reload = TIMER_AUTORELOAD_EN, + .divider = 80}; + + timer_init(TIMER_GROUP_0, TIMER_1, &config); + timer_set_counter_value(TIMER_GROUP_0, TIMER_1, 0); + timer_set_alarm_value(TIMER_GROUP_0, TIMER_1, 100); + timer_enable_intr(TIMER_GROUP_0, TIMER_1); + timer_isr_register(TIMER_GROUP_0, TIMER_1, &timerIsr, mTaskHandle, 0, nullptr); + + timer_start(TIMER_GROUP_0, TIMER_1); + } + + ~ServiceRunner() + { + vTaskDelete(mTaskHandle); + } + + template + void async(Handler handler) + { + mpService->post(std::move(handler)); + } + + ::asio::io_service& service() const + { + return *mpService; + } + + private: + TaskHandle_t mTaskHandle; + std::unique_ptr<::asio::io_service> mpService; + std::unique_ptr<::asio::io_service::work> mpWork; + }; + +public: + using Timer = ::ableton::platforms::asio::AsioTimer; + using Log = LogT; + + template + using LockFreeCallbackDispatcher = LockFreeCallbackDispatcher; + + template + using Socket = asio::Socket; + + Context() + : Context(DefaultHandler{}) + { + } + + template + explicit Context(ExceptionHandler exceptHandler) + { + } + + Context(const Context&) = delete; + + Context(Context&& rhs) + : mLog(std::move(rhs.mLog)) + , mScanIpIfAddrs(std::move(rhs.mScanIpIfAddrs)) + { + } + + void stop() + { + } + + template + Socket openUnicastSocket(const ::asio::ip::address_v4& addr) + { + auto socket = Socket{serviceRunner().service()}; + socket.mpImpl->mSocket.set_option( + ::asio::ip::multicast::enable_loopback(addr.is_loopback())); + socket.mpImpl->mSocket.set_option(::asio::ip::multicast::outbound_interface(addr)); + socket.mpImpl->mSocket.bind(::asio::ip::udp::endpoint{addr, 0}); + return socket; + } + + template + Socket openMulticastSocket(const ::asio::ip::address_v4& addr) + { + auto socket = Socket{serviceRunner().service()}; + socket.mpImpl->mSocket.set_option(::asio::ip::udp::socket::reuse_address(true)); + socket.mpImpl->mSocket.set_option( + ::asio::socket_base::broadcast(!addr.is_loopback())); + socket.mpImpl->mSocket.set_option( + ::asio::ip::multicast::enable_loopback(addr.is_loopback())); + socket.mpImpl->mSocket.set_option(::asio::ip::multicast::outbound_interface(addr)); + socket.mpImpl->mSocket.bind({::asio::ip::address::from_string("0.0.0.0"), + discovery::multicastEndpoint().port()}); + socket.mpImpl->mSocket.set_option(::asio::ip::multicast::join_group( + discovery::multicastEndpoint().address().to_v4(), addr)); + return socket; + } + + std::vector<::asio::ip::address> scanNetworkInterfaces() + { + return mScanIpIfAddrs(); + } + + Timer makeTimer() const + { + return {serviceRunner().service()}; + } + + Log& log() + { + return mLog; + } + + template + void async(Handler handler) + { + serviceRunner().service().post(std::move(handler)); + } + +private: + // Default handler is hidden and defines a hidden exception type + // that will never be thrown by other code, so it effectively does + // not catch. + struct DefaultHandler + { + struct Exception + { + }; + + void operator()(const Exception&) + { + } + }; + + static ServiceRunner& serviceRunner() + { + static ServiceRunner runner; + return runner; + } + + Log mLog; + ScanIpIfAddrs mScanIpIfAddrs; +}; + +} // namespace esp32 +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/esp32/Esp32.hpp b/tidal-link/link/include/ableton/platforms/esp32/Esp32.hpp new file mode 100644 index 000000000..9762ef432 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/esp32/Esp32.hpp @@ -0,0 +1,27 @@ +/* Copyright 2019, Mathias Bredholt, Torso Electronics, Copenhagen. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + */ + +#pragma once + +#include + +#ifndef ntohll +#define ntohll(x) bswap64(x) +#endif + +#ifndef htonll +#define htonll(x) bswap64(x) +#endif diff --git a/tidal-link/link/include/ableton/platforms/esp32/LockFreeCallbackDispatcher.hpp b/tidal-link/link/include/ableton/platforms/esp32/LockFreeCallbackDispatcher.hpp new file mode 100644 index 000000000..1d7d12088 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/esp32/LockFreeCallbackDispatcher.hpp @@ -0,0 +1,94 @@ +/* Copyright 2020, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace platforms +{ +namespace esp32 +{ + +// Utility to signal invocation of a callback on another thread in a lock free manner. +// The callback is evoked on a thread owned by the instance of this class. +// +// A condition variable is used to notify a waiting thread, but only if the required +// lock can be acquired immediately. If that fails, we fall back on signaling +// after a timeout. This gives us a guaranteed minimum signaling rate which is defined +// by the fallbackPeriod parameter. + +template +class LockFreeCallbackDispatcher +{ +public: + LockFreeCallbackDispatcher(Callback callback, Duration fallbackPeriod) + : mCallback(std::move(callback)) + , mFallbackPeriod(std::move(fallbackPeriod)) + , mRunning(true) + { + xTaskCreate(run, "link", 4096, this, tskIDLE_PRIORITY, &mTaskHandle); + } + + ~LockFreeCallbackDispatcher() + { + mRunning = false; + mCondition.notify_one(); + vTaskDelete(mTaskHandle); + } + + void invoke() + { + if (mMutex.try_lock()) + { + mCondition.notify_one(); + mMutex.unlock(); + } + } + +private: + static void run(void* userData) + { + auto dispatcher = static_cast(userData); + while (dispatcher->mRunning.load()) + { + { + std::unique_lock lock(dispatcher->mMutex); + dispatcher->mCondition.wait_for(lock, dispatcher->mFallbackPeriod); + } + dispatcher->mCallback(); + vTaskDelay(1); + } + } + + Callback mCallback; + Duration mFallbackPeriod; + std::atomic mRunning; + std::mutex mMutex; + std::condition_variable mCondition; + TaskHandle_t mTaskHandle; +}; + +} // namespace esp32 +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/esp32/Random.hpp b/tidal-link/link/include/ableton/platforms/esp32/Random.hpp new file mode 100644 index 000000000..adca04913 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/esp32/Random.hpp @@ -0,0 +1,36 @@ +/* Copyright 2019, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + */ + +#pragma once + +namespace ableton +{ +namespace platforms +{ +namespace esp32 +{ + +struct Random +{ + uint8_t operator()() + { + return static_cast((esp_random() % 93) + 33); // printable ascii chars + } +}; + +} // namespace esp32 +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/esp32/ScanIpIfAddrs.hpp b/tidal-link/link/include/ableton/platforms/esp32/ScanIpIfAddrs.hpp new file mode 100644 index 000000000..527d080a5 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/esp32/ScanIpIfAddrs.hpp @@ -0,0 +1,59 @@ +/* Copyright 2020, Ableton AG, Berlin and 2019, Mathias Bredholt, Torso Electronics, + * Copenhagen. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + */ + +#pragma once + +#include +#include +#include +#include +#include + +namespace ableton +{ +namespace platforms +{ +namespace esp32 +{ + +// ESP32 implementation of ip interface address scanner +struct ScanIpIfAddrs +{ + std::vector<::asio::ip::address> operator()() + { + std::vector<::asio::ip::address> addrs; + // Get first network interface + esp_netif_t* esp_netif = esp_netif_next(NULL); + while (esp_netif) + { + // Check if interface is active + if (esp_netif_is_netif_up(esp_netif)) + { + esp_netif_ip_info_t ip_info; + esp_netif_get_ip_info(esp_netif, &ip_info); + addrs.emplace_back(::asio::ip::address_v4(ntohl(ip_info.ip.addr))); + } + // Get next network interface + esp_netif = esp_netif_next(esp_netif); + } + return addrs; + } +}; + +} // namespace esp32 +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/linux/Clock.hpp b/tidal-link/link/include/ableton/platforms/linux/Clock.hpp new file mode 100644 index 000000000..accfe4720 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/linux/Clock.hpp @@ -0,0 +1,60 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace platforms +{ + +#ifdef linux +#undef linux +#endif + +#if defined(__FreeBSD_kernel__) +#define CLOCK_MONOTONIC_RAW CLOCK_MONOTONIC +#endif + +namespace linux +{ + +template +class Clock +{ +public: + std::chrono::microseconds micros() const + { + ::timespec ts; + ::clock_gettime(CLOCK, &ts); + std::uint64_t ns = ts.tv_sec * 1000000000ULL + ts.tv_nsec; + return std::chrono::microseconds(ns / 1000ULL); + } +}; + +using ClockMonotonic = Clock; +using ClockMonotonicRaw = Clock; + +} // namespace linux +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/linux/Linux.hpp b/tidal-link/link/include/ableton/platforms/linux/Linux.hpp new file mode 100644 index 000000000..07da43626 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/linux/Linux.hpp @@ -0,0 +1,30 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include + +#ifndef ntohll +#define ntohll(x) bswap_64(x) +#endif + +#ifndef htonll +#define htonll(x) bswap_64(x) +#endif diff --git a/tidal-link/link/include/ableton/platforms/linux/ThreadFactory.hpp b/tidal-link/link/include/ableton/platforms/linux/ThreadFactory.hpp new file mode 100644 index 000000000..81988f90b --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/linux/ThreadFactory.hpp @@ -0,0 +1,45 @@ +/* Copyright 2021, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include + +namespace ableton +{ +namespace platforms +{ +namespace linux +{ + +struct ThreadFactory +{ + template + static std::thread makeThread(std::string name, Callable&& f, Args&&... args) + { + auto thread = std::thread(std::forward(f), std::forward(args)...); + pthread_setname_np(thread.native_handle(), name.c_str()); + return thread; + } +}; + +} // namespace linux +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/posix/ScanIpIfAddrs.hpp b/tidal-link/link/include/ableton/platforms/posix/ScanIpIfAddrs.hpp new file mode 100644 index 000000000..8d24bc2f4 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/posix/ScanIpIfAddrs.hpp @@ -0,0 +1,110 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include +#include +#include + +namespace ableton +{ +namespace platforms +{ +namespace posix +{ +namespace detail +{ + +// RAII type to make [get,free]ifaddrs function pairs exception safe +class GetIfAddrs +{ +public: + GetIfAddrs() + { + if (getifaddrs(&interfaces)) // returns 0 on success + { + interfaces = NULL; + } + } + ~GetIfAddrs() + { + if (interfaces) + freeifaddrs(interfaces); + } + + // RAII must not copy + GetIfAddrs(GetIfAddrs&) = delete; + GetIfAddrs& operator=(GetIfAddrs&) = delete; + + template + void withIfAddrs(Function f) + { + if (interfaces) + f(*interfaces); + } + +private: + struct ifaddrs* interfaces = NULL; +}; + +} // namespace detail + + +// Posix implementation of ip interface address scanner +struct ScanIpIfAddrs +{ + // Scan active network interfaces and return corresponding addresses + // for all ip-based interfaces. + std::vector<::asio::ip::address> operator()() + { + std::vector<::asio::ip::address> addrs; + + detail::GetIfAddrs getIfAddrs; + getIfAddrs.withIfAddrs([&addrs](const struct ifaddrs& interfaces) { + const struct ifaddrs* interface; + for (interface = &interfaces; interface; interface = interface->ifa_next) + { + auto addr = reinterpret_cast(interface->ifa_addr); + if (addr && interface->ifa_flags & IFF_UP) + { + if (addr->sin_family == AF_INET) + { + auto bytes = reinterpret_cast(&addr->sin_addr); + addrs.emplace_back(asio::makeAddress<::asio::ip::address_v4>(bytes)); + } + else if (addr->sin_family == AF_INET6) + { + auto addr6 = reinterpret_cast(addr); + auto bytes = reinterpret_cast(&addr6->sin6_addr); + addrs.emplace_back(asio::makeAddress<::asio::ip::address_v6>(bytes)); + } + } + } + }); + return addrs; + } +}; + +} // namespace posix +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/stl/Clock.hpp b/tidal-link/link/include/ableton/platforms/stl/Clock.hpp new file mode 100644 index 000000000..9015dda5e --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/stl/Clock.hpp @@ -0,0 +1,43 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include + +namespace ableton +{ +namespace platforms +{ +namespace stl +{ + +struct Clock +{ + std::chrono::microseconds micros() const + { + using namespace std::chrono; + auto nowInMicros = time_point_cast(steady_clock::now()); + return nowInMicros.time_since_epoch(); + } +}; + +} // namespace stl +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/stl/Random.hpp b/tidal-link/link/include/ableton/platforms/stl/Random.hpp new file mode 100644 index 000000000..18fb1a361 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/stl/Random.hpp @@ -0,0 +1,51 @@ +/* Copyright 2019, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include + +namespace ableton +{ +namespace platforms +{ +namespace stl +{ + +struct Random +{ + Random() + : gen(rd()) + , dist(33, 126) // printable ascii chars + { + } + + uint8_t operator()() + { + return static_cast(dist(gen)); + } + + std::random_device rd; + std::mt19937 gen; + std::uniform_int_distribution dist; +}; + +} // namespace stl +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/windows/Clock.hpp b/tidal-link/link/include/ableton/platforms/windows/Clock.hpp new file mode 100644 index 000000000..b8f9029a8 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/windows/Clock.hpp @@ -0,0 +1,71 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include + +namespace ableton +{ +namespace platforms +{ +namespace windows +{ + +struct Clock +{ + using Ticks = std::int64_t; + using Micros = std::chrono::microseconds; + + Clock() + { + LARGE_INTEGER frequency; + QueryPerformanceFrequency(&frequency); + mTicksToMicros = 1.0e6 / static_cast(frequency.QuadPart); + } + + Micros ticksToMicros(const Ticks ticks) const + { + return Micros{llround(mTicksToMicros * static_cast(ticks))}; + } + + Ticks microsToTicks(const Micros micros) const + { + return static_cast(static_cast(micros.count()) / mTicksToMicros); + } + + Ticks ticks() const + { + LARGE_INTEGER count; + QueryPerformanceCounter(&count); + return count.QuadPart; + } + + std::chrono::microseconds micros() const + { + return ticksToMicros(ticks()); + } + + double mTicksToMicros; +}; + +} // namespace windows +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/windows/ScanIpIfAddrs.hpp b/tidal-link/link/include/ableton/platforms/windows/ScanIpIfAddrs.hpp new file mode 100644 index 000000000..e2b6f8459 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/windows/ScanIpIfAddrs.hpp @@ -0,0 +1,140 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include +#include +#include +#include + +#pragma comment(lib, "iphlpapi.lib") +#pragma comment(lib, "ws2_32.lib") + +namespace ableton +{ +namespace platforms +{ +namespace windows +{ +namespace detail +{ +// RAII type to make [get,free]ifaddrs function pairs exception safe +class GetIfAddrs +{ +public: + GetIfAddrs() + { + const int MAX_TRIES = 3; // MSFT recommendation + const int WORKING_BUFFER_SIZE = 15000; // MSFT recommendation + + DWORD adapter_addrs_buffer_size = WORKING_BUFFER_SIZE; + for (int i = 0; i < MAX_TRIES; i++) + { + adapter_addrs = (IP_ADAPTER_ADDRESSES*)malloc(adapter_addrs_buffer_size); + assert(adapter_addrs); + + DWORD error = ::GetAdaptersAddresses(AF_UNSPEC, + GAA_FLAG_SKIP_ANYCAST | GAA_FLAG_SKIP_MULTICAST | GAA_FLAG_SKIP_DNS_SERVER + | GAA_FLAG_SKIP_FRIENDLY_NAME, + NULL, adapter_addrs, &adapter_addrs_buffer_size); + + if (error == ERROR_SUCCESS) + { + break; + } + // if buffer too small, use new buffer size in next iteration + if (error == ERROR_BUFFER_OVERFLOW) + { + free(adapter_addrs); + adapter_addrs = NULL; + continue; + } + } + } + ~GetIfAddrs() + { + if (adapter_addrs) + free(adapter_addrs); + } + + // RAII must not copy + GetIfAddrs(GetIfAddrs&) = delete; + GetIfAddrs& operator=(GetIfAddrs&) = delete; + + template + void withIfAddrs(Function f) + { + if (adapter_addrs) + f(*adapter_addrs); + } + +private: + IP_ADAPTER_ADDRESSES* adapter_addrs; + IP_ADAPTER_ADDRESSES* adapter; +}; + +} // namespace detail + +struct ScanIpIfAddrs +{ + // Scan active network interfaces and return corresponding addresses + // for all ip-based interfaces. + std::vector<::asio::ip::address> operator()() + { + std::vector<::asio::ip::address> addrs; + + detail::GetIfAddrs getIfAddrs; + getIfAddrs.withIfAddrs([&addrs](const IP_ADAPTER_ADDRESSES& interfaces) { + const IP_ADAPTER_ADDRESSES* networkInterface; + for (networkInterface = &interfaces; networkInterface; + networkInterface = networkInterface->Next) + { + for (IP_ADAPTER_UNICAST_ADDRESS* address = networkInterface->FirstUnicastAddress; + NULL != address; address = address->Next) + { + auto family = address->Address.lpSockaddr->sa_family; + if (AF_INET == family) + { + // IPv4 + SOCKADDR_IN* addr4 = + reinterpret_cast(address->Address.lpSockaddr); + auto bytes = reinterpret_cast(&addr4->sin_addr); + addrs.emplace_back(asio::makeAddress<::asio::ip::address_v4>(bytes)); + } + else if (AF_INET6 == family) + { + SOCKADDR_IN6* addr6 = + reinterpret_cast(address->Address.lpSockaddr); + auto bytes = reinterpret_cast(&addr6->sin6_addr); + addrs.emplace_back(asio::makeAddress<::asio::ip::address_v6>(bytes)); + } + } + } + }); + return addrs; + } +}; + +} // namespace windows +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/windows/ThreadFactory.hpp b/tidal-link/link/include/ableton/platforms/windows/ThreadFactory.hpp new file mode 100644 index 000000000..1fc1a0573 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/windows/ThreadFactory.hpp @@ -0,0 +1,52 @@ +/* Copyright 2021, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace platforms +{ +namespace windows +{ + +struct ThreadFactory +{ + template + static std::thread makeThread(std::string name, Callable&& f, Args&&... args) + { + return std::thread( + [](std::string name, Callable&& f, Args&&... args) { + assert(name.length() < 20); + wchar_t nativeName[20]; + mbstowcs(nativeName, name.c_str(), name.length() + 1); + SetThreadDescription(GetCurrentThread(), nativeName); + f(args...); + }, + std::move(name), std::forward(f), std::forward(args)...); + } +}; + +} // namespace windows +} // namespace platforms +} // namespace ableton diff --git a/tidal-link/link/include/ableton/platforms/windows/Windows.hpp b/tidal-link/link/include/ableton/platforms/windows/Windows.hpp new file mode 100644 index 000000000..5e8bd90b2 --- /dev/null +++ b/tidal-link/link/include/ableton/platforms/windows/Windows.hpp @@ -0,0 +1,32 @@ +/* Copyright 2020, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +// ntohll and htonll are not defined for MinGW + +#ifdef __MINGW32__ +#if __BIG_ENDIAN__ +#define htonll(x) (x) +#define ntohll(x) (x) +#else +#define htonll(x) (((uint64_t)htonl((x)&0xFFFFFFFF) << 32) | htonl((x) >> 32)) +#define ntohll(x) (((uint64_t)ntohl((x)&0xFFFFFFFF) << 32) | ntohl((x) >> 32)) +#endif +#endif diff --git a/tidal-link/link/include/ableton/test/CatchWrapper.hpp b/tidal-link/link/include/ableton/test/CatchWrapper.hpp new file mode 100644 index 000000000..997da91e1 --- /dev/null +++ b/tidal-link/link/include/ableton/test/CatchWrapper.hpp @@ -0,0 +1,42 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +/*! + * \brief Wrapper file for Catch library + * + * This file includes the Catch header for Link, and also disables some compiler warnings + * which are specific to that library. + */ + +#if defined(_MSC_VER) +#pragma warning(push, 0) +#pragma warning(disable : 4242) +#pragma warning(disable : 4244) +#pragma warning(disable : 4668) +#pragma warning(disable : 4702) +#pragma warning(disable : 5220) +#endif + +#include + +#if defined(_MSC_VER) +#pragma warning(pop) +#endif diff --git a/tidal-link/link/include/ableton/test/serial_io/Context.hpp b/tidal-link/link/include/ableton/test/serial_io/Context.hpp new file mode 100644 index 000000000..f450fbb79 --- /dev/null +++ b/tidal-link/link/include/ableton/test/serial_io/Context.hpp @@ -0,0 +1,109 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include +#include +#include + +namespace ableton +{ +namespace test +{ +namespace serial_io +{ + +class Context +{ +public: + Context(const SchedulerTree::TimePoint& now, + const std::vector<::asio::ip::address>& ifAddrs, + std::shared_ptr pScheduler) + : mNow(now) + , mIfAddrs(ifAddrs) + , mpScheduler(std::move(pScheduler)) + , mNextTimerId(0) + { + } + + ~Context() + { + if (mpScheduler != nullptr) + { + // Finish any pending tasks before shutting down + mpScheduler->run(); + } + } + + Context(const Context&) = delete; + Context& operator=(const Context&) = delete; + + Context(Context&& rhs) + : mNow(rhs.mNow) + , mIfAddrs(rhs.mIfAddrs) + , mpScheduler(std::move(rhs.mpScheduler)) + , mLog(std::move(rhs.mLog)) + , mNextTimerId(rhs.mNextTimerId) + { + } + + void stop() + { + } + + template + void async(Handler handler) + { + mpScheduler->async(std::move(handler)); + } + + using Timer = serial_io::Timer; + + Timer makeTimer() + { + return {mNextTimerId++, mNow, mpScheduler}; + } + + using Log = util::NullLog; + + Log& log() + { + return mLog; + } + + std::vector<::asio::ip::address> scanNetworkInterfaces() + { + return mIfAddrs; + } + +private: + const SchedulerTree::TimePoint& mNow; + const std::vector<::asio::ip::address>& mIfAddrs; + std::shared_ptr mpScheduler; + Log mLog; + SchedulerTree::TimerId mNextTimerId; +}; + +} // namespace serial_io +} // namespace test +} // namespace ableton diff --git a/tidal-link/link/include/ableton/test/serial_io/Fixture.hpp b/tidal-link/link/include/ableton/test/serial_io/Fixture.hpp new file mode 100644 index 000000000..316c44d0c --- /dev/null +++ b/tidal-link/link/include/ableton/test/serial_io/Fixture.hpp @@ -0,0 +1,92 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include + +namespace ableton +{ +namespace test +{ +namespace serial_io +{ + +class Fixture +{ +public: + Fixture() + : mpScheduler(std::make_shared()) + , mNow(std::chrono::milliseconds{123456789}) + { + } + + ~Fixture() + { + flush(); + } + + Fixture(const Fixture&) = delete; + Fixture& operator=(const Fixture&) = delete; + Fixture(Fixture&&) = delete; + Fixture& operator=(Fixture&&) = delete; + + void setNetworkInterfaces(std::vector<::asio::ip::address> ifAddrs) + { + mIfAddrs = std::move(ifAddrs); + } + + Context makeIoContext() + { + return {mNow, mIfAddrs, mpScheduler}; + } + + void flush() + { + mpScheduler->run(); + } + + template + void advanceTime(std::chrono::duration duration) + { + const auto target = mNow + duration; + mpScheduler->run(); + auto nextTimer = mpScheduler->nextTimerExpiration(); + while (nextTimer <= target) + { + mNow = nextTimer; + mpScheduler->triggerTimersUntil(mNow); + mpScheduler->run(); + nextTimer = mpScheduler->nextTimerExpiration(); + } + mNow = target; + } + +private: + std::shared_ptr mpScheduler; + SchedulerTree::TimePoint mNow; + std::vector<::asio::ip::address> mIfAddrs; +}; + +} // namespace serial_io +} // namespace test +} // namespace ableton diff --git a/tidal-link/link/include/ableton/test/serial_io/SchedulerTree.hpp b/tidal-link/link/include/ableton/test/serial_io/SchedulerTree.hpp new file mode 100644 index 000000000..6b854786b --- /dev/null +++ b/tidal-link/link/include/ableton/test/serial_io/SchedulerTree.hpp @@ -0,0 +1,104 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include +#include +#include +#include + +namespace ableton +{ +namespace test +{ +namespace serial_io +{ + +class SchedulerTree +{ +public: + using TimePoint = std::chrono::system_clock::time_point; + using TimerId = std::size_t; + using TimerErrorCode = int; + + void run(); + + std::shared_ptr makeChild(); + + template + void async(Handler handler) + { + mPendingHandlers.push_back(std::move(handler)); + } + + template + void setTimer(const TimerId timerId, const TimePoint expiration, Handler handler) + { + using namespace std; + mTimers[make_pair(std::move(expiration), timerId)] = std::move(handler); + } + + void cancelTimer(const TimerId timerId); + + // returns the time that the next timer in the subtree expires + TimePoint nextTimerExpiration(); + + // triggers all timers in the subtree that expire at time t or before + void triggerTimersUntil(const TimePoint t); + +private: + // returns true if some work was done, false if there was none to do + bool handlePending(); + + // returns the time that the next timer from this node expires + TimePoint nextOwnTimerExpiration(); + + // Traversal function over children that cleans up children that + // have been destroyed. + template + void withChildren(Fn fn) + { + auto it = begin(mChildren); + while (it != end(mChildren)) + { + const auto childIt = it++; + auto pChild = childIt->lock(); + if (pChild) + { + fn(*pChild); + } + else + { + mChildren.erase(childIt); + } + } + } + + using TimerHandler = std::function; + using TimerMap = std::map, TimerHandler>; + TimerMap mTimers; + std::list> mPendingHandlers; + std::list> mChildren; +}; + +} // namespace serial_io +} // namespace test +} // namespace ableton diff --git a/tidal-link/link/include/ableton/test/serial_io/Timer.hpp b/tidal-link/link/include/ableton/test/serial_io/Timer.hpp new file mode 100644 index 000000000..1bf2b7288 --- /dev/null +++ b/tidal-link/link/include/ableton/test/serial_io/Timer.hpp @@ -0,0 +1,110 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include + +namespace ableton +{ +namespace test +{ +namespace serial_io +{ + +struct Timer +{ + using ErrorCode = SchedulerTree::TimerErrorCode; + using TimePoint = SchedulerTree::TimePoint; + + Timer(const SchedulerTree::TimerId timerId, + const TimePoint& now, + std::shared_ptr pScheduler) + : mId(timerId) + , mNow(now) + , mpScheduler(std::move(pScheduler)) + { + } + + ~Timer() + { + if (!mbMovedFrom) + { + cancel(); + } + } + + Timer(const Timer&) = delete; + + Timer(Timer&& rhs) + : mId(rhs.mId) + , mNow(rhs.mNow) + , mExpiration(std::move(rhs.mExpiration)) + , mpScheduler(std::move(rhs.mpScheduler)) + { + rhs.mbMovedFrom = true; + } + + void expires_at(const TimePoint t) + { + if (t < mNow) + { + throw std::runtime_error("Setting timer in the past"); + } + else + { + cancel(); + mExpiration = t; + } + } + + template + void expires_from_now(std::chrono::duration duration) + { + expires_at(mNow + duration); + } + + void cancel() + { + auto pScheduler = mpScheduler.lock(); + pScheduler->cancelTimer(mId); + } + + template + void async_wait(Handler handler) + { + auto pScheduler = mpScheduler.lock(); + pScheduler->setTimer(mId, mExpiration, std::move(handler)); + } + + TimePoint now() const + { + return mNow; + } + + const SchedulerTree::TimerId mId; + const TimePoint& mNow; + TimePoint mExpiration; + std::weak_ptr mpScheduler; + bool mbMovedFrom = false; +}; + +} // namespace serial_io +} // namespace test +} // namespace ableton diff --git a/tidal-link/link/include/ableton/util/Injected.hpp b/tidal-link/link/include/ableton/util/Injected.hpp new file mode 100644 index 000000000..5f4449988 --- /dev/null +++ b/tidal-link/link/include/ableton/util/Injected.hpp @@ -0,0 +1,254 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include + +namespace ableton +{ +namespace util +{ + +// Utility type for aiding in dependency injection. + +// Base template and implementation for injected valued +template +struct Injected +{ + using type = T; + + Injected() = default; + + explicit Injected(T t) + : val(std::move(t)) + { + } + + Injected(const Injected&) = default; + Injected& operator=(const Injected&) = default; + + Injected(Injected&& rhs) + : val(std::move(rhs.val)) + { + } + + Injected& operator=(Injected&& rhs) + { + val = std::move(rhs.val); + return *this; + } + + T* operator->() + { + return &val; + } + + const T* operator->() const + { + return &val; + } + + T& operator*() + { + return val; + } + + const T& operator*() const + { + return val; + } + + T val; +}; + +// Utility function for injecting values +template +Injected injectVal(T t) +{ + return Injected(std::move(t)); +} + +// Specialization for injected references +template +struct Injected +{ + using type = T; + + explicit Injected(T& t) + : ref(std::ref(t)) + { + } + + Injected(const Injected&) = default; + Injected& operator=(const Injected&) = default; + + Injected(Injected&& rhs) + : ref(std::move(rhs.ref)) + { + } + + Injected& operator=(Injected&& rhs) + { + ref = std::move(rhs.ref); + return *this; + } + + T* operator->() + { + return &ref.get(); + } + + const T* operator->() const + { + return &ref.get(); + } + + T& operator*() + { + return ref; + } + + const T& operator*() const + { + return ref; + } + + std::reference_wrapper ref; +}; + +// Utility function for injecting references +template +Injected injectRef(T& t) +{ + return Injected(t); +} + +// Specialization for injected shared_ptr +template +struct Injected> +{ + using type = T; + + explicit Injected(std::shared_ptr pT) + : shared(std::move(pT)) + { + } + + Injected(const Injected&) = default; + Injected& operator=(const Injected&) = default; + + Injected(Injected&& rhs) + : shared(std::move(rhs.shared)) + { + } + + Injected& operator=(Injected&& rhs) + { + shared = std::move(rhs.shared); + return *this; + } + + T* operator->() + { + return shared.get(); + } + + const T* operator->() const + { + return shared.get(); + } + + T& operator*() + { + return *shared; + } + + const T& operator*() const + { + return *shared; + } + + std::shared_ptr shared; +}; + +// Utility function for injected shared_ptr +template +Injected> injectShared(std::shared_ptr shared) +{ + return Injected>(std::move(shared)); +} + +// Specialization for injected unique_ptr +template +struct Injected> +{ + using type = T; + + explicit Injected(std::unique_ptr pT) + : unique(std::move(pT)) + { + } + + Injected(const Injected&) = default; + Injected& operator=(const Injected&) = default; + + Injected(Injected&& rhs) + : unique(std::move(rhs.unique)) + { + } + + Injected& operator=(Injected&& rhs) + { + unique = std::move(rhs.unique); + return *this; + } + + T* operator->() + { + return unique.get(); + } + + const T* operator->() const + { + return unique.get(); + } + + T& operator*() + { + return *unique; + } + + const T& operator*() const + { + return *unique; + } + + std::unique_ptr unique; +}; + +// Utility function for injected unique_ptr +template +Injected> injectUnique(std::unique_ptr unique) +{ + return Injected>(std::move(unique)); +} + +} // namespace util +} // namespace ableton diff --git a/tidal-link/link/include/ableton/util/Log.hpp b/tidal-link/link/include/ableton/util/Log.hpp new file mode 100644 index 000000000..6b70c16b3 --- /dev/null +++ b/tidal-link/link/include/ableton/util/Log.hpp @@ -0,0 +1,176 @@ +// Copyright: 2014, Ableton AG, Berlin, all rights reserved + +#pragma once + +#include +#include +#include + +namespace ableton +{ +namespace util +{ + +// Null object for the Log concept +struct NullLog +{ + template + friend const NullLog& operator<<(const NullLog& log, const T&) + { + return log; + } + + friend const NullLog& debug(const NullLog& log) + { + return log; + } + + friend const NullLog& info(const NullLog& log) + { + return log; + } + + friend const NullLog& warning(const NullLog& log) + { + return log; + } + + friend const NullLog& error(const NullLog& log) + { + return log; + } + + friend NullLog channel(const NullLog&, std::string) + { + return {}; + } +}; + +// std streams-based log +struct StdLog +{ + StdLog(std::string channelName = "") + : mChannelName(std::move(channelName)) + { + } + + // Stream type used by std log to prepend the channel name to log messages + struct StdLogStream + { + StdLogStream(std::ostream& ioStream, const std::string& channelName) + : mpIoStream(&ioStream) + , mChannelName(channelName) + { + ioStream << "[" << mChannelName << "] "; + } + + StdLogStream(StdLogStream&& rhs) + : mpIoStream(rhs.mpIoStream) + , mChannelName(rhs.mChannelName) + { + rhs.mpIoStream = nullptr; + } + + ~StdLogStream() + { + if (mpIoStream) + { + (*mpIoStream) << "\n"; + } + } + + template + std::ostream& operator<<(const T& rhs) + { + (*mpIoStream) << rhs; + return *mpIoStream; + } + + std::ostream* mpIoStream; + const std::string& mChannelName; + }; + + friend StdLogStream debug(const StdLog& log) + { + return {std::clog, log.mChannelName}; + } + + friend StdLogStream info(const StdLog& log) + { + return {std::clog, log.mChannelName}; + } + + friend StdLogStream warning(const StdLog& log) + { + return {std::clog, log.mChannelName}; + } + + friend StdLogStream error(const StdLog& log) + { + return {std::cerr, log.mChannelName}; + } + + friend StdLog channel(const StdLog& log, const std::string& channelName) + { + auto compositeName = + log.mChannelName.empty() ? channelName : log.mChannelName + "::" + channelName; + return {std::move(compositeName)}; + } + + std::string mChannelName; +}; + +// Log adapter that adds timestamps +template +struct Timestamped +{ + using InnerLog = typename util::Injected::type; + + Timestamped() = default; + + Timestamped(util::Injected log) + : mLog(std::move(log)) + { + } + + util::Injected mLog; + + friend decltype(debug(std::declval())) debug(const Timestamped& log) + { + return log.logTimestamp(debug(*log.mLog)); + } + + friend decltype(info(std::declval())) info(const Timestamped& log) + { + return log.logTimestamp(info(*log.mLog)); + } + + friend decltype(warning(std::declval())) warning(const Timestamped& log) + { + return log.logTimestamp(warning(*log.mLog)); + } + + friend decltype(error(std::declval())) error(const Timestamped& log) + { + return log.logTimestamp(error(*log.mLog)); + } + + friend Timestamped channel(const Timestamped& log, const std::string& channelName) + { + return {channel(*log.mLog, channelName)}; + } + + template + Stream logTimestamp(Stream&& streamRef) const + { + using namespace std::chrono; + Stream stream = std::forward(streamRef); + stream << "|" + << duration_cast(system_clock::now().time_since_epoch()).count() + << "ms| "; + return stream; + } +}; + +} // namespace util +} // namespace ableton diff --git a/tidal-link/link/include/ableton/util/SafeAsyncHandler.hpp b/tidal-link/link/include/ableton/util/SafeAsyncHandler.hpp new file mode 100644 index 000000000..f83316dde --- /dev/null +++ b/tidal-link/link/include/ableton/util/SafeAsyncHandler.hpp @@ -0,0 +1,66 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include + +namespace ableton +{ +namespace util +{ + +// A utility handler for passing to async functions that may call the +// handler past the lifetime of the wrapped delegate object. +// The need for this is particularly driven by boost::asio timer +// objects, which explicitly document that they may be called without +// an error code after they have been cancelled. This has led to +// several crashes. This handler wrapper implements a useful idiom for +// avoiding this problem. + +template +struct SafeAsyncHandler +{ + SafeAsyncHandler(const std::shared_ptr& pDelegate) + : mpDelegate(pDelegate) + { + } + + template + void operator()(T&&... t) const + { + std::shared_ptr pDelegate = mpDelegate.lock(); + if (pDelegate) + { + (*pDelegate)(std::forward(t)...); + } + } + + std::weak_ptr mpDelegate; +}; + +// Factory function for easily wrapping a shared_ptr to a handler +template +SafeAsyncHandler makeAsyncSafe(const std::shared_ptr& pDelegate) +{ + return {pDelegate}; +} + +} // namespace util +} // namespace ableton diff --git a/tidal-link/link/include/ableton/util/SampleTiming.hpp b/tidal-link/link/include/ableton/util/SampleTiming.hpp new file mode 100644 index 000000000..fbd5c1ee0 --- /dev/null +++ b/tidal-link/link/include/ableton/util/SampleTiming.hpp @@ -0,0 +1,52 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include + +namespace ableton +{ +namespace util +{ + +/*! Utility type to convert between time and sample index given the + * time at the beginning of a buffer and the sample rate. + */ +struct SampleTiming +{ + double sampleAtTime(std::chrono::microseconds time) const + { + using namespace std::chrono; + return duration_cast>(time - mBufferBegin).count() * mSampleRate; + } + + std::chrono::microseconds timeAtSample(const double sample) const + { + using namespace std::chrono; + return mBufferBegin + + duration_cast(duration{sample / mSampleRate}); + } + + std::chrono::microseconds mBufferBegin; + double mSampleRate; +}; + +} // namespace util +} // namespace ableton diff --git a/tidal-link/link/include/ableton/util/test/IoService.hpp b/tidal-link/link/include/ableton/util/test/IoService.hpp new file mode 100644 index 000000000..278f1d2b5 --- /dev/null +++ b/tidal-link/link/include/ableton/util/test/IoService.hpp @@ -0,0 +1,114 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include + +namespace ableton +{ +namespace util +{ +namespace test +{ + +struct IoService +{ + // Wrapper around the internal util::test::Timer in the list + struct Timer + { + using ErrorCode = test::Timer::ErrorCode; + using TimePoint = test::Timer::TimePoint; + + Timer(util::test::Timer* pTimer) + : mpTimer(pTimer) + { + } + + void expires_at(std::chrono::system_clock::time_point t) + { + mpTimer->expires_at(t); + } + + template + void expires_from_now(std::chrono::duration duration) + { + mpTimer->expires_from_now(duration); + } + + ErrorCode cancel() + { + return mpTimer->cancel(); + } + + template + void async_wait(Handler handler) + { + mpTimer->async_wait(std::move(handler)); + } + + TimePoint now() const + { + return mpTimer->now(); + } + + util::test::Timer* mpTimer; + }; + + IoService() = default; + + Timer makeTimer() + { + mTimers.emplace_back(); + return Timer{&mTimers.back()}; + } + + template + void post(Handler handler) + { + mHandlers.emplace_back(std::move(handler)); + } + + template + void advance(std::chrono::duration duration) + { + runHandlers(); + + for (auto& timer : mTimers) + { + timer.advance(duration); + } + } + + void runHandlers() + { + for (auto& handler : mHandlers) + { + handler(); + } + mHandlers.clear(); + } + + std::vector> mHandlers; + std::vector mTimers; +}; + +} // namespace test +} // namespace util +} // namespace ableton diff --git a/tidal-link/link/include/ableton/util/test/Timer.hpp b/tidal-link/link/include/ableton/util/test/Timer.hpp new file mode 100644 index 000000000..e0918a537 --- /dev/null +++ b/tidal-link/link/include/ableton/util/test/Timer.hpp @@ -0,0 +1,96 @@ +/* Copyright 2016, Ableton AG, Berlin. All rights reserved. + * + * This program is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, either version 2 of the License, or + * (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with this program. If not, see . + * + * If you would like to incorporate Link into a proprietary software application, + * please contact . + */ + +#pragma once + +#include +#include + +namespace ableton +{ +namespace util +{ +namespace test +{ + +struct Timer +{ + using ErrorCode = int; + using TimePoint = std::chrono::system_clock::time_point; + + // Initialize timer with an arbitrary large value to simulate the + // time_since_epoch of a real clock. + Timer() + : mNow{std::chrono::milliseconds{123456789}} + { + } + + void expires_at(std::chrono::system_clock::time_point t) + { + cancel(); + mFireAt = std::move(t); + } + + template + void expires_from_now(std::chrono::duration duration) + { + cancel(); + mFireAt = now() + duration; + } + + ErrorCode cancel() + { + if (mHandler) + { + mHandler(1); // call existing handler with truthy error code + } + mHandler = nullptr; + return 0; + } + + template + void async_wait(Handler handler) + { + mHandler = [handler](ErrorCode ec) { handler(ec); }; + } + + std::chrono::system_clock::time_point now() const + { + return mNow; + } + + template + void advance(std::chrono::duration duration) + { + mNow += duration; + if (mHandler && mFireAt < mNow) + { + mHandler(0); + mHandler = nullptr; + } + } + + std::function mHandler; + std::chrono::system_clock::time_point mFireAt; + std::chrono::system_clock::time_point mNow; +}; + +} // namespace test +} // namespace util +} // namespace ableton diff --git a/tidal-link/link/modules/asio-standalone/.appveyor.yml b/tidal-link/link/modules/asio-standalone/.appveyor.yml new file mode 100644 index 000000000..d7865c5a2 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/.appveyor.yml @@ -0,0 +1,139 @@ +version: "{branch} (#{build})" + +image: + - Visual Studio 2013 + - Visual Studio 2015 + - Visual Studio 2017 + - Visual Studio 2019 + +environment: + DEBUG: 1 + WARNINGS: 1 + matrix: + - STANDALONE: 1 + HEADER_ONLY: 1 + MSVC: 1 + - STANDALONE: 1 + SEPARATE_COMPILATION: 1 + MSVC: 1 + - STANDALONE: 1 + SEPARATE_COMPILATION: 1 + MINGW: 1 + - STANDALONE: 1 + CXXLATEST: 1 + MSVC: 1 + - STANDALONE: 1 + HEADER_ONLY: 1 + WIN9X: 1 + MSVC: 1 + - STANDALONE: 1 + SEPARATE_COMPILATION: 1 + WIN9X: 1 + MSVC: 1 + - USING_BOOST: 1 + HEADER_ONLY: 1 + MSVC: 1 + - USING_BOOST: 1 + SEPARATE_COMPILATION: 1 + MSVC: 1 + - USING_BOOST: 1 + SEPARATE_COMPILATION: 1 + MINGW: 1 + +for: + - + matrix: + only: + - image: Visual Studio 2013 + environment: + BOOSTDIR: C:\Libraries\boost_1_58_0 + build_script: + - call "C:\Program Files\Microsoft SDKs\Windows\v7.1\Bin\SetEnv.cmd" /x86 + - call "C:\Program Files (x86)\Microsoft Visual Studio 12.0\VC\vcvarsall.bat" x86 + - cd asio\src + - nmake -f Makefile.msc + - nmake -f Makefile.msc check + - + matrix: + only: + - image: Visual Studio 2015 + MSVC: 1 + environment: + BOOSTDIR: C:\Libraries\boost_1_63_0 + build_script: + - call "C:\Program Files\Microsoft SDKs\Windows\v7.1\Bin\SetEnv.cmd" /x64 + - call "C:\Program Files (x86)\Microsoft Visual Studio 14.0\VC\vcvarsall.bat" x86_amd64 + - cd asio\src + - nmake -f Makefile.msc + - nmake -f Makefile.msc check + - + matrix: + only: + - image: Visual Studio 2015 + MINGW: 1 + environment: + BOOSTDIR: C:/Libraries/boost_1_63_0 + build_script: + - PATH=C:\mingw-w64\x86_64-8.1.0-posix-seh-rt_v6-rev0\mingw64\bin;C:\msys64\usr\bin;%PATH% + - cd asio\src + - mingw32-make -f Makefile.mgw + - mingw32-make -f Makefile.mgw check + - + matrix: + only: + - image: Visual Studio 2017 + environment: + BOOSTDIR: C:\Libraries\boost_1_69_0 + _WIN32_WINNT: 0x0603 + build_script: + - call "C:\Program Files (x86)\Microsoft Visual Studio\2017\Community\VC\Auxiliary\Build\vcvarsall.bat" x86_amd64 + - cd asio\src + - nmake -f Makefile.msc + - nmake -f Makefile.msc check + - + matrix: + only: + - image: Visual Studio 2019 + environment: + BOOSTDIR: C:\Libraries\boost_1_71_0 + _WIN32_WINNT: 0x0A00 + build_script: + - call "C:\Program Files (x86)\Microsoft Visual Studio\2019\Community\VC\Auxiliary\Build\vcvarsall.bat" x86_amd64 + - cd asio\src + - nmake -f Makefile.msc + - nmake -f Makefile.msc check + +matrix: + exclude: + - image: Visual Studio 2013 + SEPARATE_COMPILATION: 1 + - image: Visual Studio 2013 + CXXLATEST: 1 + - image: Visual Studio 2013 + USING_BOOST: 1 + - image: Visual Studio 2013 + MINGW: 1 + - image: Visual Studio 2015 + HEADER_ONLY: 1 + - image: Visual Studio 2015 + CXXLATEST: 1 + - image: Visual Studio 2015 + WIN9X: 1 + - image: Visual Studio 2017 + SEPARATE_COMPILATION: 1 + - image: Visual Studio 2017 + CXXLATEST: 1 + - image: Visual Studio 2017 + WIN9X: 1 + - image: Visual Studio 2017 + USING_BOOST: 1 + - image: Visual Studio 2017 + MINGW: 1 + - image: Visual Studio 2019 + HEADER_ONLY: 1 + - image: Visual Studio 2019 + WIN9X: 1 + - image: Visual Studio 2019 + USING_BOOST: 1 + - image: Visual Studio 2019 + MINGW: 1 diff --git a/tidal-link/link/modules/asio-standalone/.cirrus.yml b/tidal-link/link/modules/asio-standalone/.cirrus.yml new file mode 100644 index 000000000..3a7dafc39 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/.cirrus.yml @@ -0,0 +1,16 @@ +freebsd_instance: + image_family: freebsd-12-1 + cpu: 1 + +env: + CXXFLAGS: -std=c++14 -Wall -Wextra -O2 + +task: + install_script: + - pkg install -y autoconf automake + build_script: + - cd asio + - ./autogen.sh + - ./configure --with-boost=no + - make + - make check diff --git a/tidal-link/link/modules/asio-standalone/.gitignore b/tidal-link/link/modules/asio-standalone/.gitignore new file mode 100644 index 000000000..e6c8ff1c2 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/.gitignore @@ -0,0 +1,3 @@ +/*.cpp +/*.hpp +/boost diff --git a/tidal-link/link/modules/asio-standalone/.travis.yml b/tidal-link/link/modules/asio-standalone/.travis.yml new file mode 100644 index 000000000..06fb4b9a7 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/.travis.yml @@ -0,0 +1,372 @@ +language: cpp +os: linux +dist: xenial + +cache: + directories: + - ${TRAVIS_BUILD_DIR}/boost_1_64_0 + - ${TRAVIS_BUILD_DIR}/boost_1_73_0 + +matrix: + include: + # + #--------------------------------------------------------------------------- + # Linux / g++-9 + #--------------------------------------------------------------------------- + # + # Linux / g++-9 -std=c++2a / -O2 / standalone + # + - os: linux + dist: bionic + addons: + apt: + sources: + - ubuntu-toolchain-r-test + packages: + - g++-9 + env: + - CXXFLAGS="-std=c++2a -fconcepts -Wall -Wextra -O2" + - CONFIGFLAGS="--with-boost=no" + - MATRIX_EVAL="CC=gcc-9 CXX=g++-9" + compiler: gcc + # + # Linux / g++-9 -std=c++17 / -O2 / boost 1.73 + # + - os: linux + dist: bionic + addons: + apt: + sources: + - ubuntu-toolchain-r-test + packages: + - g++-9 + env: + - BOOST_DIR="boost_1_73_0" + - BOOST_URL="https://sourceforge.net/projects/boost/files/boost/1.73.0/boost_1_73_0.tar.bz2/download" + - CXXFLAGS="-std=c++17 -Wall -Wextra -O2" + - CONFIGFLAGS="--with-boost=$PWD/$BOOST_DIR" + - MATRIX_EVAL="CC=gcc-9 CXX=g++-9" + compiler: gcc + # + # Linux / g++-9 -std=c++14 / -O0 / standalone / separate compilation + # + - os: linux + dist: bionic + addons: + apt: + sources: + - ubuntu-toolchain-r-test + packages: + - g++-9 + env: + - CXXFLAGS="-std=c++14 -Wall -Wextra -O0 -fno-inline" + - CONFIGFLAGS="--with-boost=no --enable-separate-compilation" + - MATRIX_EVAL="CC=gcc-9 CXX=g++-9" + compiler: gcc + # + #--------------------------------------------------------------------------- + # Linux / g++-6 + #--------------------------------------------------------------------------- + # + # Linux / g++-6 / -O2 / standalone + # + - os: linux + addons: + apt: + sources: + - ubuntu-toolchain-r-test + packages: + - g++-6 + env: + - CXXFLAGS="-Wall -Wextra -O2" + - CONFIGFLAGS="--with-boost=no" + - MATRIX_EVAL="CC=gcc-6 CXX=g++-6" + compiler: gcc + # + # Linux / g++-6 / -O0 / standalone / handler tracking + # + - os: linux + addons: + apt: + sources: + - ubuntu-toolchain-r-test + packages: + - g++-6 + env: + - CXXFLAGS="-Wall -Wextra -O0 -fno-inline -DASIO_ENABLE_HANDLER_TRACKING" + - CONFIGFLAGS="--with-boost=no" + - MATRIX_EVAL="CC=gcc-6 CXX=g++-6" + compiler: gcc + # + # Linux / g++-6 / -O0 / standalone / epoll disabled + # + - os: linux + addons: + apt: + sources: + - ubuntu-toolchain-r-test + packages: + - g++-6 + env: + - CXXFLAGS="-Wall -Wextra -O0 -fno-inline -DASIO_DISABLE_EPOLL" + - CONFIGFLAGS="--with-boost=no" + - MATRIX_EVAL="CC=gcc-6 CXX=g++-6" + compiler: gcc + # + # Linux / g++-6 / -O0 / standalone / separate compilation / handler tracking + # + - os: linux + addons: + apt: + sources: + - ubuntu-toolchain-r-test + packages: + - g++-6 + env: + - CXXFLAGS="-Wall -Wextra -O0 -fno-inline -DASIO_ENABLE_HANDLER_TRACKING" + - CONFIGFLAGS="--with-boost=no --enable-separate-compilation" + - MATRIX_EVAL="CC=gcc-6 CXX=g++-6" + compiler: gcc + # + # Linux / g++-6 / -O0 / standalone / separate compilation / epoll disabled + # + - os: linux + addons: + apt: + sources: + - ubuntu-toolchain-r-test + packages: + - g++-6 + env: + - CXXFLAGS="-Wall -Wextra -O0 -fno-inline -DASIO_DISABLE_EPOLL" + - CONFIGFLAGS="--with-boost=no --enable-separate-compilation" + - MATRIX_EVAL="CC=gcc-6 CXX=g++-6" + compiler: gcc + # + # Linux / g++-6 / -O2 / boost 1.64 + # + - os: linux + addons: + apt: + sources: + - ubuntu-toolchain-r-test + packages: + - g++-6 + env: + - BOOST_DIR="boost_1_64_0" + - BOOST_URL="https://sourceforge.net/projects/boost/files/boost/1.64.0/boost_1_64_0.tar.bz2/download" + - CXXFLAGS="-Wall -Wextra -O2" + - CONFIGFLAGS="" + - MATRIX_EVAL="CC=gcc-6 CXX=g++-6" + compiler: gcc + # + # Linux / g++-6 / -O0 / boost 1.64 / epoll disabled + # + - os: linux + addons: + apt: + sources: + - ubuntu-toolchain-r-test + packages: + - g++-6 + env: + - BOOST_DIR="boost_1_64_0" + - BOOST_URL="https://sourceforge.net/projects/boost/files/boost/1.64.0/boost_1_64_0.tar.bz2/download" + - CXXFLAGS="-Wall -Wextra -O0 -fno-inline -DASIO_DISABLE_EPOLL" + - CONFIGFLAGS="" + - MATRIX_EVAL="CC=gcc-6 CXX=g++-6" + compiler: gcc + # + # Linux / g++-6 / -O0 / boost 1.64 / separate compilation + # + - os: linux + addons: + apt: + sources: + - ubuntu-toolchain-r-test + packages: + - g++-6 + env: + - BOOST_DIR="boost_1_64_0" + - BOOST_URL="https://sourceforge.net/projects/boost/files/boost/1.64.0/boost_1_64_0.tar.bz2/download" + - CXXFLAGS="-Wall -Wextra -O0 -fno-inline" + - CONFIGFLAGS="--enable-separate-compilation" + - MATRIX_EVAL="CC=gcc-6 CXX=g++-6" + compiler: gcc + # + #--------------------------------------------------------------------------- + # Linux / g++-4.8 + #--------------------------------------------------------------------------- + # + # Linux / g++-4.8 / -O2 / standalone + # + - os: linux + addons: + apt: + sources: + - ubuntu-toolchain-r-test + packages: + - g++-4.8 + env: + - CXXFLAGS="-Wall -Wextra -O2" + - CONFIGFLAGS="--with-boost=no" + - MATRIX_EVAL="CC=gcc-4.8 CXX=g++-4.8" + compiler: gcc + # + # Linux / g++-4.8 / -O0 / standalone / separate compilation + # + - os: linux + addons: + apt: + sources: + - ubuntu-toolchain-r-test + packages: + - g++-4.8 + env: + - CXXFLAGS="-Wall -Wextra -O0 -fno-inline" + - CONFIGFLAGS="--with-boost=no --enable-separate-compilation" + - MATRIX_EVAL="CC=gcc-4.8 CXX=g++-4.8" + compiler: gcc + # + # Linux / g++-4.8 / -O2 / boost 1.64 + # + - os: linux + addons: + apt: + sources: + - ubuntu-toolchain-r-test + packages: + - g++-4.8 + env: + - BOOST_DIR="boost_1_64_0" + - BOOST_URL="https://sourceforge.net/projects/boost/files/boost/1.64.0/boost_1_64_0.tar.bz2/download" + - CXXFLAGS="-Wall -Wextra -O2" + - CONFIGFLAGS="" + - MATRIX_EVAL="CC=gcc-4.8 CXX=g++-4.8" + compiler: gcc + # + # Linux / g++-4.8 -std=c++11 / -O2 / boost 1.64 + # + - os: linux + addons: + apt: + sources: + - ubuntu-toolchain-r-test + packages: + - g++-4.8 + env: + - BOOST_DIR="boost_1_64_0" + - BOOST_URL="https://sourceforge.net/projects/boost/files/boost/1.64.0/boost_1_64_0.tar.bz2/download" + - CXXFLAGS="-std=c++11 -Wall -Wextra -O2" + - CONFIGFLAGS="" + - MATRIX_EVAL="CC=gcc-4.8 CXX=g++-4.8" + compiler: gcc + # + #--------------------------------------------------------------------------- + # Linux / clang-3.8 + #--------------------------------------------------------------------------- + # + # Linux / clang-3.8 / -O2 / standalone" + # + - os: linux + addons: + apt: + sources: + - ubuntu-toolchain-r-test + - llvm-toolchain-precise-3.8 + packages: + - clang-3.8 + env: + - CXXFLAGS="-Wall -Wextra -O2" + - CONFIGFLAGS="--with-boost=no" + - MATRIX_EVAL="CC=clang-3.8 CXX=clang++-3.8" + compiler: clang + # + # Linux / clang-3.8 / -O0 / standalone / separate compilation + # + - os: linux + addons: + apt: + sources: + - ubuntu-toolchain-r-test + - llvm-toolchain-precise-3.8 + packages: + - clang-3.8 + env: + - CXXFLAGS="-Wall -Wextra -O0 -fno-inline" + - CONFIGFLAGS="--with-boost=no --enable-separate-compilation" + - MATRIX_EVAL="CC=clang-3.8 CXX=clang++-3.8" + compiler: clang + # + #--------------------------------------------------------------------------- + # macOS / xcode10.1 + #--------------------------------------------------------------------------- + # + # macOS / xcode10.1 / -std=c++2a -fcoroutines-ts -O2 / standalone + # + - os: osx + env: + - CXXFLAGS="-std=c++2a -fcoroutines-ts -Wall -Wextra -O0 -fno-inline" + - CONFIGFLAGS="--with-boost=no" + osx_image: xcode10.1 + # + # macOS / xcode10.1 / -O2 / standalone + # + - os: osx + env: + - CXXFLAGS="-Wall -Wextra -O0 -fno-inline" + - CONFIGFLAGS="--with-boost=no" + osx_image: xcode10.1 + # + # macOS / xcode10.1 / -O0 / standalone / kqueue disabled + # + - os: osx + env: + - CXXFLAGS="-Wall -Wextra -O0 -fno-inline -DASIO_DISABLE_KQUEUE" + - CONFIGFLAGS="--with-boost=no" + osx_image: xcode10.1 + # + # macOS / xcode10.1 / -O0 / standalone / separate compilation + # + - os: osx + env: + - CXXFLAGS="-Wall -Wextra -O0 -fno-inline" + - CONFIGFLAGS="--with-boost=no --enable-separate-compilation" + osx_image: xcode10.1 + # + # macOS / xcode10.1 / -O2 / boost 1.64 + # + - os: osx + env: + - BOOST_DIR="boost_1_64_0" + - BOOST_URL="https://sourceforge.net/projects/boost/files/boost/1.64.0/boost_1_64_0.tar.bz2/download" + - CXXFLAGS="-Wall -Wextra -O2" + - CONFIGFLAGS="" + osx_image: xcode10.1 + # + # macOS / xcode10.1 / -O0 / boost 1.64 / separate compilation + # + - os: osx + env: + - BOOST_DIR="boost_1_64_0" + - BOOST_URL="https://sourceforge.net/projects/boost/files/boost/1.64.0/boost_1_64_0.tar.bz2/download" + - CXXFLAGS="-Wall -Wextra -O0 -fno-inline" + - CONFIGFLAGS="--enable-separate-compilation" + osx_image: xcode10.1 + +before_install: + - eval "${MATRIX_EVAL}" + +install: + - | + if [[ "${BOOST_URL}" != "" ]]; then + if [[ -z "$(ls -A ${BOOST_DIR})" ]]; then + { travis_retry wget --quiet -O - ${BOOST_URL} | tar -xj; } || exit 1 + fi + fi + +script: + - cd asio && ./autogen.sh && ./configure $CONFIGFLAGS && make && make check + +notifications: + email: false diff --git a/tidal-link/link/modules/asio-standalone/asio/.gitignore b/tidal-link/link/modules/asio-standalone/asio/.gitignore new file mode 100644 index 000000000..55db11878 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/.gitignore @@ -0,0 +1,23 @@ +Makefile +Makefile.in +aclocal.m4 +autom4te.cache +compile +config.guess +config.log +config.status +config.sub +configure +depcomp +install-sh +missing +test-driver +/doc +/lib +/boostified +/tsified +*.gz +*.bz2 +*.zip +/*.cpp +/*.hpp diff --git a/tidal-link/link/modules/asio-standalone/asio/COPYING b/tidal-link/link/modules/asio-standalone/asio/COPYING new file mode 100644 index 000000000..2bb5eb20d --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/COPYING @@ -0,0 +1,4 @@ +Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) + +Distributed under the Boost Software License, Version 1.0. (See accompanying +file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) diff --git a/tidal-link/link/modules/asio-standalone/asio/INSTALL b/tidal-link/link/modules/asio-standalone/asio/INSTALL new file mode 100644 index 000000000..f045678c4 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/INSTALL @@ -0,0 +1,5 @@ +See doc/index.html for information on: + - External dependencies + - Using asio + - Supported platforms + - How to build the tests and examples diff --git a/tidal-link/link/modules/asio-standalone/asio/LICENSE_1_0.txt b/tidal-link/link/modules/asio-standalone/asio/LICENSE_1_0.txt new file mode 100644 index 000000000..36b7cd93c --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/LICENSE_1_0.txt @@ -0,0 +1,23 @@ +Boost Software License - Version 1.0 - August 17th, 2003 + +Permission is hereby granted, free of charge, to any person or organization +obtaining a copy of the software and accompanying documentation covered by +this license (the "Software") to use, reproduce, display, distribute, +execute, and transmit the Software, and to prepare derivative works of the +Software, and to permit third-parties to whom the Software is furnished to +do so, all subject to the following: + +The copyright notices in the Software and this entire statement, including +the above license grant, this restriction and the following disclaimer, +must be included in all copies of the Software, in whole or in part, and +all derivative works of the Software, unless such copies or derivative +works are solely in the form of machine-executable object code generated by +a source language processor. + +THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR +IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, +FITNESS FOR A PARTICULAR PURPOSE, TITLE AND NON-INFRINGEMENT. IN NO EVENT +SHALL THE COPYRIGHT HOLDERS OR ANYONE DISTRIBUTING THE SOFTWARE BE LIABLE +FOR ANY DAMAGES OR OTHER LIABILITY, WHETHER IN CONTRACT, TORT OR OTHERWISE, +ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER +DEALINGS IN THE SOFTWARE. diff --git a/tidal-link/link/modules/asio-standalone/asio/Makefile.am b/tidal-link/link/modules/asio-standalone/asio/Makefile.am new file mode 100644 index 000000000..0acdc02d9 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/Makefile.am @@ -0,0 +1,19 @@ +AUTOMAKE_OPTIONS = foreign dist-bzip2 dist-zip + +SUBDIRS = include src + +MAINTAINERCLEANFILES = \ + $(srcdir)/aclocal.m4 \ + $(srcdir)/configure \ + $(srcdir)/config.guess \ + $(srcdir)/config.sub \ + $(srcdir)/depcomp \ + $(srcdir)/install-sh \ + $(srcdir)/missing \ + $(srcdir)/mkinstalldirs \ + $(srcdir)/Makefile.in \ + asio-*.tar.gz + +EXTRA_DIST = \ + LICENSE_1_0.txt \ + doc diff --git a/tidal-link/link/modules/asio-standalone/asio/README b/tidal-link/link/modules/asio-standalone/asio/README new file mode 100644 index 000000000..92472f52e --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/README @@ -0,0 +1,4 @@ +asio version 1.17.0 +Released Friday, 10 July 2020. + +See doc/index.html for API documentation and a tutorial. diff --git a/tidal-link/link/modules/asio-standalone/asio/asio.manifest b/tidal-link/link/modules/asio-standalone/asio/asio.manifest new file mode 100644 index 000000000..440b974eb --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/asio.manifest @@ -0,0 +1,5658 @@ +/ +/aclocal.m4 +/compile +/config.guess +/config.sub +/configure +/configure.ac +/COPYING +/depcomp +/doc/ +/doc/asio/ +/doc/asio/examples/ +/doc/asio/examples/cpp03_examples.html +/doc/asio/examples/cpp11_examples.html +/doc/asio/examples/cpp14_examples.html +/doc/asio/examples/cpp17_examples.html +/doc/asio/examples.html +/doc/asio/history.html +/doc/asio/index.html +/doc/asio/net_ts.html +/doc/asio/overview/ +/doc/asio/overview/core/ +/doc/asio/overview/core/allocation.html +/doc/asio/overview/core/async.html +/doc/asio/overview/core/basics.html +/doc/asio/overview/core/buffers.html +/doc/asio/overview/core/concurrency_hint.html +/doc/asio/overview/core/coroutine.html +/doc/asio/overview/core/coroutines_ts.html +/doc/asio/overview/core/handler_tracking.html +/doc/asio/overview/core.html +/doc/asio/overview/core/line_based.html +/doc/asio/overview/core/reactor.html +/doc/asio/overview/core/spawn.html +/doc/asio/overview/core/strands.html +/doc/asio/overview/core/streams.html +/doc/asio/overview/core/threads.html +/doc/asio/overview/cpp2011/ +/doc/asio/overview/cpp2011/array.html +/doc/asio/overview/cpp2011/atomic.html +/doc/asio/overview/cpp2011/chrono.html +/doc/asio/overview/cpp2011/futures.html +/doc/asio/overview/cpp2011.html +/doc/asio/overview/cpp2011/move_handlers.html +/doc/asio/overview/cpp2011/move_objects.html +/doc/asio/overview/cpp2011/shared_ptr.html +/doc/asio/overview/cpp2011/system_error.html +/doc/asio/overview/cpp2011/variadic.html +/doc/asio/overview.html +/doc/asio/overview/implementation.html +/doc/asio/overview/networking/ +/doc/asio/overview/networking/bsd_sockets.html +/doc/asio/overview/networking.html +/doc/asio/overview/networking/iostreams.html +/doc/asio/overview/networking/other_protocols.html +/doc/asio/overview/networking/protocols.html +/doc/asio/overview/posix/ +/doc/asio/overview/posix/fork.html +/doc/asio/overview/posix.html +/doc/asio/overview/posix/local.html +/doc/asio/overview/posix/stream_descriptor.html +/doc/asio/overview/rationale.html +/doc/asio/overview/serial_ports.html +/doc/asio/overview/signals.html +/doc/asio/overview/ssl.html +/doc/asio/overview/timers.html +/doc/asio/overview/windows/ +/doc/asio/overview/windows.html +/doc/asio/overview/windows/object_handle.html +/doc/asio/overview/windows/random_access_handle.html +/doc/asio/overview/windows/stream_handle.html +/doc/asio.png +/doc/asio/reference/ +/doc/asio/reference/AcceptableProtocol.html +/doc/asio/reference/AcceptHandler.html +/doc/asio/reference/any_io_executor.html +/doc/asio/reference/asio_handler_allocate.html +/doc/asio/reference/asio_handler_deallocate.html +/doc/asio/reference/asio_handler_invoke/ +/doc/asio/reference/asio_handler_invoke.html +/doc/asio/reference/asio_handler_invoke/overload1.html +/doc/asio/reference/asio_handler_invoke/overload2.html +/doc/asio/reference/asio_handler_is_continuation.html +/doc/asio/reference/associated_allocator/ +/doc/asio/reference/associated_allocator/get.html +/doc/asio/reference/associated_allocator.html +/doc/asio/reference/associated_allocator/type.html +/doc/asio/reference/associated_executor/ +/doc/asio/reference/associated_executor/get.html +/doc/asio/reference/associated_executor.html +/doc/asio/reference/associated_executor/type.html +/doc/asio/reference/async_completion/ +/doc/asio/reference/async_completion/async_completion.html +/doc/asio/reference/async_completion/completion_handler.html +/doc/asio/reference/async_completion/completion_handler_type.html +/doc/asio/reference/async_completion.html +/doc/asio/reference/async_completion/result.html +/doc/asio/reference/async_compose.html +/doc/asio/reference/async_connect/ +/doc/asio/reference/async_connect.html +/doc/asio/reference/async_connect/overload1.html +/doc/asio/reference/async_connect/overload2.html +/doc/asio/reference/async_connect/overload3.html +/doc/asio/reference/async_connect/overload4.html +/doc/asio/reference/async_connect/overload5.html +/doc/asio/reference/async_connect/overload6.html +/doc/asio/reference/asynchronous_operations.html +/doc/asio/reference/asynchronous_socket_operations.html +/doc/asio/reference/async_initiate.html +/doc/asio/reference/AsyncRandomAccessReadDevice.html +/doc/asio/reference/AsyncRandomAccessWriteDevice.html +/doc/asio/reference/async_read/ +/doc/asio/reference/async_read_at/ +/doc/asio/reference/async_read_at.html +/doc/asio/reference/async_read_at/overload1.html +/doc/asio/reference/async_read_at/overload2.html +/doc/asio/reference/async_read_at/overload3.html +/doc/asio/reference/async_read_at/overload4.html +/doc/asio/reference/async_read.html +/doc/asio/reference/async_read/overload1.html +/doc/asio/reference/async_read/overload2.html +/doc/asio/reference/async_read/overload3.html +/doc/asio/reference/async_read/overload4.html +/doc/asio/reference/async_read/overload5.html +/doc/asio/reference/async_read/overload6.html +/doc/asio/reference/async_read/overload7.html +/doc/asio/reference/async_read/overload8.html +/doc/asio/reference/AsyncReadStream.html +/doc/asio/reference/async_read_until/ +/doc/asio/reference/async_read_until.html +/doc/asio/reference/async_read_until/overload10.html +/doc/asio/reference/async_read_until/overload11.html +/doc/asio/reference/async_read_until/overload12.html +/doc/asio/reference/async_read_until/overload1.html +/doc/asio/reference/async_read_until/overload2.html +/doc/asio/reference/async_read_until/overload3.html +/doc/asio/reference/async_read_until/overload4.html +/doc/asio/reference/async_read_until/overload5.html +/doc/asio/reference/async_read_until/overload6.html +/doc/asio/reference/async_read_until/overload7.html +/doc/asio/reference/async_read_until/overload8.html +/doc/asio/reference/async_read_until/overload9.html +/doc/asio/reference/async_result/ +/doc/asio/reference/async_result/async_result.html +/doc/asio/reference/async_result/completion_handler_type.html +/doc/asio/reference/async_result/get.html +/doc/asio/reference/async_result.html +/doc/asio/reference/async_result/initiate.html +/doc/asio/reference/async_result_lt__std__packaged_task_lt__Result_lp_Args_ellipsis__rp__gt__comma__Signature__gt_/ +/doc/asio/reference/async_result_lt__std__packaged_task_lt__Result_lp_Args_ellipsis__rp__gt__comma__Signature__gt_/async_result.html +/doc/asio/reference/async_result_lt__std__packaged_task_lt__Result_lp_Args_ellipsis__rp__gt__comma__Signature__gt_/completion_handler_type.html +/doc/asio/reference/async_result_lt__std__packaged_task_lt__Result_lp_Args_ellipsis__rp__gt__comma__Signature__gt_/get.html +/doc/asio/reference/async_result_lt__std__packaged_task_lt__Result_lp_Args_ellipsis__rp__gt__comma__Signature__gt_.html +/doc/asio/reference/async_result_lt__std__packaged_task_lt__Result_lp_Args_ellipsis__rp__gt__comma__Signature__gt_/return_type.html +/doc/asio/reference/async_result/return_type.html +/doc/asio/reference/async_write/ +/doc/asio/reference/async_write_at/ +/doc/asio/reference/async_write_at.html +/doc/asio/reference/async_write_at/overload1.html +/doc/asio/reference/async_write_at/overload2.html +/doc/asio/reference/async_write_at/overload3.html +/doc/asio/reference/async_write_at/overload4.html +/doc/asio/reference/async_write.html +/doc/asio/reference/async_write/overload1.html +/doc/asio/reference/async_write/overload2.html +/doc/asio/reference/async_write/overload3.html +/doc/asio/reference/async_write/overload4.html +/doc/asio/reference/async_write/overload5.html +/doc/asio/reference/async_write/overload6.html +/doc/asio/reference/async_write/overload7.html +/doc/asio/reference/async_write/overload8.html +/doc/asio/reference/AsyncWriteStream.html +/doc/asio/reference/awaitable/ +/doc/asio/reference/awaitable/awaitable/ +/doc/asio/reference/awaitable/_awaitable.html +/doc/asio/reference/awaitable/awaitable.html +/doc/asio/reference/awaitable/awaitable/overload1.html +/doc/asio/reference/awaitable/awaitable/overload2.html +/doc/asio/reference/awaitable/executor_type.html +/doc/asio/reference/awaitable.html +/doc/asio/reference/awaitable/valid.html +/doc/asio/reference/awaitable/value_type.html +/doc/asio/reference/bad_executor/ +/doc/asio/reference/bad_executor/bad_executor.html +/doc/asio/reference/bad_executor.html +/doc/asio/reference/bad_executor/what.html +/doc/asio/reference/basic_datagram_socket/ +/doc/asio/reference/basic_datagram_socket/assign/ +/doc/asio/reference/basic_datagram_socket/assign.html +/doc/asio/reference/basic_datagram_socket/assign/overload1.html +/doc/asio/reference/basic_datagram_socket/assign/overload2.html +/doc/asio/reference/basic_datagram_socket/async_connect.html +/doc/asio/reference/basic_datagram_socket/async_receive/ +/doc/asio/reference/basic_datagram_socket/async_receive_from/ +/doc/asio/reference/basic_datagram_socket/async_receive_from.html +/doc/asio/reference/basic_datagram_socket/async_receive_from/overload1.html +/doc/asio/reference/basic_datagram_socket/async_receive_from/overload2.html +/doc/asio/reference/basic_datagram_socket/async_receive.html +/doc/asio/reference/basic_datagram_socket/async_receive/overload1.html +/doc/asio/reference/basic_datagram_socket/async_receive/overload2.html +/doc/asio/reference/basic_datagram_socket/async_send/ +/doc/asio/reference/basic_datagram_socket/async_send.html +/doc/asio/reference/basic_datagram_socket/async_send/overload1.html +/doc/asio/reference/basic_datagram_socket/async_send/overload2.html +/doc/asio/reference/basic_datagram_socket/async_send_to/ +/doc/asio/reference/basic_datagram_socket/async_send_to.html +/doc/asio/reference/basic_datagram_socket/async_send_to/overload1.html +/doc/asio/reference/basic_datagram_socket/async_send_to/overload2.html +/doc/asio/reference/basic_datagram_socket/async_wait.html +/doc/asio/reference/basic_datagram_socket/at_mark/ +/doc/asio/reference/basic_datagram_socket/at_mark.html +/doc/asio/reference/basic_datagram_socket/at_mark/overload1.html +/doc/asio/reference/basic_datagram_socket/at_mark/overload2.html +/doc/asio/reference/basic_datagram_socket/available/ +/doc/asio/reference/basic_datagram_socket/available.html +/doc/asio/reference/basic_datagram_socket/available/overload1.html +/doc/asio/reference/basic_datagram_socket/available/overload2.html +/doc/asio/reference/basic_datagram_socket/basic_datagram_socket/ +/doc/asio/reference/basic_datagram_socket/_basic_datagram_socket.html +/doc/asio/reference/basic_datagram_socket/basic_datagram_socket.html +/doc/asio/reference/basic_datagram_socket/basic_datagram_socket/overload10.html +/doc/asio/reference/basic_datagram_socket/basic_datagram_socket/overload1.html +/doc/asio/reference/basic_datagram_socket/basic_datagram_socket/overload2.html +/doc/asio/reference/basic_datagram_socket/basic_datagram_socket/overload3.html +/doc/asio/reference/basic_datagram_socket/basic_datagram_socket/overload4.html +/doc/asio/reference/basic_datagram_socket/basic_datagram_socket/overload5.html +/doc/asio/reference/basic_datagram_socket/basic_datagram_socket/overload6.html +/doc/asio/reference/basic_datagram_socket/basic_datagram_socket/overload7.html +/doc/asio/reference/basic_datagram_socket/basic_datagram_socket/overload8.html +/doc/asio/reference/basic_datagram_socket/basic_datagram_socket/overload9.html +/doc/asio/reference/basic_datagram_socket/bind/ +/doc/asio/reference/basic_datagram_socket/bind.html +/doc/asio/reference/basic_datagram_socket/bind/overload1.html +/doc/asio/reference/basic_datagram_socket/bind/overload2.html +/doc/asio/reference/basic_datagram_socket/broadcast.html +/doc/asio/reference/basic_datagram_socket/bytes_readable.html +/doc/asio/reference/basic_datagram_socket/cancel/ +/doc/asio/reference/basic_datagram_socket/cancel.html +/doc/asio/reference/basic_datagram_socket/cancel/overload1.html +/doc/asio/reference/basic_datagram_socket/cancel/overload2.html +/doc/asio/reference/basic_datagram_socket/close/ +/doc/asio/reference/basic_datagram_socket/close.html +/doc/asio/reference/basic_datagram_socket/close/overload1.html +/doc/asio/reference/basic_datagram_socket/close/overload2.html +/doc/asio/reference/basic_datagram_socket/connect/ +/doc/asio/reference/basic_datagram_socket/connect.html +/doc/asio/reference/basic_datagram_socket/connect/overload1.html +/doc/asio/reference/basic_datagram_socket/connect/overload2.html +/doc/asio/reference/basic_datagram_socket/debug.html +/doc/asio/reference/basic_datagram_socket/do_not_route.html +/doc/asio/reference/basic_datagram_socket/enable_connection_aborted.html +/doc/asio/reference/basic_datagram_socket/endpoint_type.html +/doc/asio/reference/basic_datagram_socket/executor_type.html +/doc/asio/reference/basic_datagram_socket/get_executor.html +/doc/asio/reference/basic_datagram_socket/get_option/ +/doc/asio/reference/basic_datagram_socket/get_option.html +/doc/asio/reference/basic_datagram_socket/get_option/overload1.html +/doc/asio/reference/basic_datagram_socket/get_option/overload2.html +/doc/asio/reference/basic_datagram_socket.html +/doc/asio/reference/basic_datagram_socket/impl_.html +/doc/asio/reference/basic_datagram_socket/io_control/ +/doc/asio/reference/basic_datagram_socket/io_control.html +/doc/asio/reference/basic_datagram_socket/io_control/overload1.html +/doc/asio/reference/basic_datagram_socket/io_control/overload2.html +/doc/asio/reference/basic_datagram_socket/is_open.html +/doc/asio/reference/basic_datagram_socket/keep_alive.html +/doc/asio/reference/basic_datagram_socket/linger.html +/doc/asio/reference/basic_datagram_socket/local_endpoint/ +/doc/asio/reference/basic_datagram_socket/local_endpoint.html +/doc/asio/reference/basic_datagram_socket/local_endpoint/overload1.html +/doc/asio/reference/basic_datagram_socket/local_endpoint/overload2.html +/doc/asio/reference/basic_datagram_socket/lowest_layer/ +/doc/asio/reference/basic_datagram_socket/lowest_layer.html +/doc/asio/reference/basic_datagram_socket/lowest_layer/overload1.html +/doc/asio/reference/basic_datagram_socket/lowest_layer/overload2.html +/doc/asio/reference/basic_datagram_socket/lowest_layer_type.html +/doc/asio/reference/basic_datagram_socket/max_connections.html +/doc/asio/reference/basic_datagram_socket/max_listen_connections.html +/doc/asio/reference/basic_datagram_socket/message_do_not_route.html +/doc/asio/reference/basic_datagram_socket/message_end_of_record.html +/doc/asio/reference/basic_datagram_socket/message_flags.html +/doc/asio/reference/basic_datagram_socket/message_out_of_band.html +/doc/asio/reference/basic_datagram_socket/message_peek.html +/doc/asio/reference/basic_datagram_socket/native_handle.html +/doc/asio/reference/basic_datagram_socket/native_handle_type.html +/doc/asio/reference/basic_datagram_socket/native_non_blocking/ +/doc/asio/reference/basic_datagram_socket/native_non_blocking.html +/doc/asio/reference/basic_datagram_socket/native_non_blocking/overload1.html +/doc/asio/reference/basic_datagram_socket/native_non_blocking/overload2.html +/doc/asio/reference/basic_datagram_socket/native_non_blocking/overload3.html +/doc/asio/reference/basic_datagram_socket/non_blocking/ +/doc/asio/reference/basic_datagram_socket/non_blocking.html +/doc/asio/reference/basic_datagram_socket/non_blocking/overload1.html +/doc/asio/reference/basic_datagram_socket/non_blocking/overload2.html +/doc/asio/reference/basic_datagram_socket/non_blocking/overload3.html +/doc/asio/reference/basic_datagram_socket/open/ +/doc/asio/reference/basic_datagram_socket/open.html +/doc/asio/reference/basic_datagram_socket/open/overload1.html +/doc/asio/reference/basic_datagram_socket/open/overload2.html +/doc/asio/reference/basic_datagram_socket/operator_eq_/ +/doc/asio/reference/basic_datagram_socket/operator_eq_.html +/doc/asio/reference/basic_datagram_socket/operator_eq_/overload1.html +/doc/asio/reference/basic_datagram_socket/operator_eq_/overload2.html +/doc/asio/reference/basic_datagram_socket/out_of_band_inline.html +/doc/asio/reference/basic_datagram_socket/protocol_type.html +/doc/asio/reference/basic_datagram_socket__rebind_executor/ +/doc/asio/reference/basic_datagram_socket__rebind_executor.html +/doc/asio/reference/basic_datagram_socket__rebind_executor/other.html +/doc/asio/reference/basic_datagram_socket/receive/ +/doc/asio/reference/basic_datagram_socket/receive_buffer_size.html +/doc/asio/reference/basic_datagram_socket/receive_from/ +/doc/asio/reference/basic_datagram_socket/receive_from.html +/doc/asio/reference/basic_datagram_socket/receive_from/overload1.html +/doc/asio/reference/basic_datagram_socket/receive_from/overload2.html +/doc/asio/reference/basic_datagram_socket/receive_from/overload3.html +/doc/asio/reference/basic_datagram_socket/receive.html +/doc/asio/reference/basic_datagram_socket/receive_low_watermark.html +/doc/asio/reference/basic_datagram_socket/receive/overload1.html +/doc/asio/reference/basic_datagram_socket/receive/overload2.html +/doc/asio/reference/basic_datagram_socket/receive/overload3.html +/doc/asio/reference/basic_datagram_socket/release/ +/doc/asio/reference/basic_datagram_socket/release.html +/doc/asio/reference/basic_datagram_socket/release/overload1.html +/doc/asio/reference/basic_datagram_socket/release/overload2.html +/doc/asio/reference/basic_datagram_socket/remote_endpoint/ +/doc/asio/reference/basic_datagram_socket/remote_endpoint.html +/doc/asio/reference/basic_datagram_socket/remote_endpoint/overload1.html +/doc/asio/reference/basic_datagram_socket/remote_endpoint/overload2.html +/doc/asio/reference/basic_datagram_socket/reuse_address.html +/doc/asio/reference/basic_datagram_socket/send/ +/doc/asio/reference/basic_datagram_socket/send_buffer_size.html +/doc/asio/reference/basic_datagram_socket/send.html +/doc/asio/reference/basic_datagram_socket/send_low_watermark.html +/doc/asio/reference/basic_datagram_socket/send/overload1.html +/doc/asio/reference/basic_datagram_socket/send/overload2.html +/doc/asio/reference/basic_datagram_socket/send/overload3.html +/doc/asio/reference/basic_datagram_socket/send_to/ +/doc/asio/reference/basic_datagram_socket/send_to.html +/doc/asio/reference/basic_datagram_socket/send_to/overload1.html +/doc/asio/reference/basic_datagram_socket/send_to/overload2.html +/doc/asio/reference/basic_datagram_socket/send_to/overload3.html +/doc/asio/reference/basic_datagram_socket/set_option/ +/doc/asio/reference/basic_datagram_socket/set_option.html +/doc/asio/reference/basic_datagram_socket/set_option/overload1.html +/doc/asio/reference/basic_datagram_socket/set_option/overload2.html +/doc/asio/reference/basic_datagram_socket/shutdown/ +/doc/asio/reference/basic_datagram_socket/shutdown.html +/doc/asio/reference/basic_datagram_socket/shutdown/overload1.html +/doc/asio/reference/basic_datagram_socket/shutdown/overload2.html +/doc/asio/reference/basic_datagram_socket/shutdown_type.html +/doc/asio/reference/basic_datagram_socket/wait/ +/doc/asio/reference/basic_datagram_socket/wait.html +/doc/asio/reference/basic_datagram_socket/wait/overload1.html +/doc/asio/reference/basic_datagram_socket/wait/overload2.html +/doc/asio/reference/basic_datagram_socket/wait_type.html +/doc/asio/reference/basic_deadline_timer/ +/doc/asio/reference/basic_deadline_timer/async_wait.html +/doc/asio/reference/basic_deadline_timer/basic_deadline_timer/ +/doc/asio/reference/basic_deadline_timer/_basic_deadline_timer.html +/doc/asio/reference/basic_deadline_timer/basic_deadline_timer.html +/doc/asio/reference/basic_deadline_timer/basic_deadline_timer/overload1.html +/doc/asio/reference/basic_deadline_timer/basic_deadline_timer/overload2.html +/doc/asio/reference/basic_deadline_timer/basic_deadline_timer/overload3.html +/doc/asio/reference/basic_deadline_timer/basic_deadline_timer/overload4.html +/doc/asio/reference/basic_deadline_timer/basic_deadline_timer/overload5.html +/doc/asio/reference/basic_deadline_timer/basic_deadline_timer/overload6.html +/doc/asio/reference/basic_deadline_timer/basic_deadline_timer/overload7.html +/doc/asio/reference/basic_deadline_timer/cancel/ +/doc/asio/reference/basic_deadline_timer/cancel.html +/doc/asio/reference/basic_deadline_timer/cancel_one/ +/doc/asio/reference/basic_deadline_timer/cancel_one.html +/doc/asio/reference/basic_deadline_timer/cancel_one/overload1.html +/doc/asio/reference/basic_deadline_timer/cancel_one/overload2.html +/doc/asio/reference/basic_deadline_timer/cancel/overload1.html +/doc/asio/reference/basic_deadline_timer/cancel/overload2.html +/doc/asio/reference/basic_deadline_timer/duration_type.html +/doc/asio/reference/basic_deadline_timer/executor_type.html +/doc/asio/reference/basic_deadline_timer/expires_at/ +/doc/asio/reference/basic_deadline_timer/expires_at.html +/doc/asio/reference/basic_deadline_timer/expires_at/overload1.html +/doc/asio/reference/basic_deadline_timer/expires_at/overload2.html +/doc/asio/reference/basic_deadline_timer/expires_at/overload3.html +/doc/asio/reference/basic_deadline_timer/expires_from_now/ +/doc/asio/reference/basic_deadline_timer/expires_from_now.html +/doc/asio/reference/basic_deadline_timer/expires_from_now/overload1.html +/doc/asio/reference/basic_deadline_timer/expires_from_now/overload2.html +/doc/asio/reference/basic_deadline_timer/expires_from_now/overload3.html +/doc/asio/reference/basic_deadline_timer/get_executor.html +/doc/asio/reference/basic_deadline_timer.html +/doc/asio/reference/basic_deadline_timer/operator_eq_.html +/doc/asio/reference/basic_deadline_timer__rebind_executor/ +/doc/asio/reference/basic_deadline_timer__rebind_executor.html +/doc/asio/reference/basic_deadline_timer__rebind_executor/other.html +/doc/asio/reference/basic_deadline_timer/time_type.html +/doc/asio/reference/basic_deadline_timer/traits_type.html +/doc/asio/reference/basic_deadline_timer/wait/ +/doc/asio/reference/basic_deadline_timer/wait.html +/doc/asio/reference/basic_deadline_timer/wait/overload1.html +/doc/asio/reference/basic_deadline_timer/wait/overload2.html +/doc/asio/reference/basic_io_object/ +/doc/asio/reference/basic_io_object/basic_io_object/ +/doc/asio/reference/basic_io_object/_basic_io_object.html +/doc/asio/reference/basic_io_object/basic_io_object.html +/doc/asio/reference/basic_io_object/basic_io_object/overload1.html +/doc/asio/reference/basic_io_object/basic_io_object/overload2.html +/doc/asio/reference/basic_io_object/basic_io_object/overload3.html +/doc/asio/reference/basic_io_object/executor_type.html +/doc/asio/reference/basic_io_object/get_executor.html +/doc/asio/reference/basic_io_object/get_implementation/ +/doc/asio/reference/basic_io_object/get_implementation.html +/doc/asio/reference/basic_io_object/get_implementation/overload1.html +/doc/asio/reference/basic_io_object/get_implementation/overload2.html +/doc/asio/reference/basic_io_object/get_io_context.html +/doc/asio/reference/basic_io_object/get_io_service.html +/doc/asio/reference/basic_io_object/get_service/ +/doc/asio/reference/basic_io_object/get_service.html +/doc/asio/reference/basic_io_object/get_service/overload1.html +/doc/asio/reference/basic_io_object/get_service/overload2.html +/doc/asio/reference/basic_io_object.html +/doc/asio/reference/basic_io_object/implementation_type.html +/doc/asio/reference/basic_io_object/operator_eq_.html +/doc/asio/reference/basic_io_object/service_type.html +/doc/asio/reference/basic_raw_socket/ +/doc/asio/reference/basic_raw_socket/assign/ +/doc/asio/reference/basic_raw_socket/assign.html +/doc/asio/reference/basic_raw_socket/assign/overload1.html +/doc/asio/reference/basic_raw_socket/assign/overload2.html +/doc/asio/reference/basic_raw_socket/async_connect.html +/doc/asio/reference/basic_raw_socket/async_receive/ +/doc/asio/reference/basic_raw_socket/async_receive_from/ +/doc/asio/reference/basic_raw_socket/async_receive_from.html +/doc/asio/reference/basic_raw_socket/async_receive_from/overload1.html +/doc/asio/reference/basic_raw_socket/async_receive_from/overload2.html +/doc/asio/reference/basic_raw_socket/async_receive.html +/doc/asio/reference/basic_raw_socket/async_receive/overload1.html +/doc/asio/reference/basic_raw_socket/async_receive/overload2.html +/doc/asio/reference/basic_raw_socket/async_send/ +/doc/asio/reference/basic_raw_socket/async_send.html +/doc/asio/reference/basic_raw_socket/async_send/overload1.html +/doc/asio/reference/basic_raw_socket/async_send/overload2.html +/doc/asio/reference/basic_raw_socket/async_send_to/ +/doc/asio/reference/basic_raw_socket/async_send_to.html +/doc/asio/reference/basic_raw_socket/async_send_to/overload1.html +/doc/asio/reference/basic_raw_socket/async_send_to/overload2.html +/doc/asio/reference/basic_raw_socket/async_wait.html +/doc/asio/reference/basic_raw_socket/at_mark/ +/doc/asio/reference/basic_raw_socket/at_mark.html +/doc/asio/reference/basic_raw_socket/at_mark/overload1.html +/doc/asio/reference/basic_raw_socket/at_mark/overload2.html +/doc/asio/reference/basic_raw_socket/available/ +/doc/asio/reference/basic_raw_socket/available.html +/doc/asio/reference/basic_raw_socket/available/overload1.html +/doc/asio/reference/basic_raw_socket/available/overload2.html +/doc/asio/reference/basic_raw_socket/basic_raw_socket/ +/doc/asio/reference/basic_raw_socket/_basic_raw_socket.html +/doc/asio/reference/basic_raw_socket/basic_raw_socket.html +/doc/asio/reference/basic_raw_socket/basic_raw_socket/overload10.html +/doc/asio/reference/basic_raw_socket/basic_raw_socket/overload1.html +/doc/asio/reference/basic_raw_socket/basic_raw_socket/overload2.html +/doc/asio/reference/basic_raw_socket/basic_raw_socket/overload3.html +/doc/asio/reference/basic_raw_socket/basic_raw_socket/overload4.html +/doc/asio/reference/basic_raw_socket/basic_raw_socket/overload5.html +/doc/asio/reference/basic_raw_socket/basic_raw_socket/overload6.html +/doc/asio/reference/basic_raw_socket/basic_raw_socket/overload7.html +/doc/asio/reference/basic_raw_socket/basic_raw_socket/overload8.html +/doc/asio/reference/basic_raw_socket/basic_raw_socket/overload9.html +/doc/asio/reference/basic_raw_socket/bind/ +/doc/asio/reference/basic_raw_socket/bind.html +/doc/asio/reference/basic_raw_socket/bind/overload1.html +/doc/asio/reference/basic_raw_socket/bind/overload2.html +/doc/asio/reference/basic_raw_socket/broadcast.html +/doc/asio/reference/basic_raw_socket/bytes_readable.html +/doc/asio/reference/basic_raw_socket/cancel/ +/doc/asio/reference/basic_raw_socket/cancel.html +/doc/asio/reference/basic_raw_socket/cancel/overload1.html +/doc/asio/reference/basic_raw_socket/cancel/overload2.html +/doc/asio/reference/basic_raw_socket/close/ +/doc/asio/reference/basic_raw_socket/close.html +/doc/asio/reference/basic_raw_socket/close/overload1.html +/doc/asio/reference/basic_raw_socket/close/overload2.html +/doc/asio/reference/basic_raw_socket/connect/ +/doc/asio/reference/basic_raw_socket/connect.html +/doc/asio/reference/basic_raw_socket/connect/overload1.html +/doc/asio/reference/basic_raw_socket/connect/overload2.html +/doc/asio/reference/basic_raw_socket/debug.html +/doc/asio/reference/basic_raw_socket/do_not_route.html +/doc/asio/reference/basic_raw_socket/enable_connection_aborted.html +/doc/asio/reference/basic_raw_socket/endpoint_type.html +/doc/asio/reference/basic_raw_socket/executor_type.html +/doc/asio/reference/basic_raw_socket/get_executor.html +/doc/asio/reference/basic_raw_socket/get_option/ +/doc/asio/reference/basic_raw_socket/get_option.html +/doc/asio/reference/basic_raw_socket/get_option/overload1.html +/doc/asio/reference/basic_raw_socket/get_option/overload2.html +/doc/asio/reference/basic_raw_socket.html +/doc/asio/reference/basic_raw_socket/impl_.html +/doc/asio/reference/basic_raw_socket/io_control/ +/doc/asio/reference/basic_raw_socket/io_control.html +/doc/asio/reference/basic_raw_socket/io_control/overload1.html +/doc/asio/reference/basic_raw_socket/io_control/overload2.html +/doc/asio/reference/basic_raw_socket/is_open.html +/doc/asio/reference/basic_raw_socket/keep_alive.html +/doc/asio/reference/basic_raw_socket/linger.html +/doc/asio/reference/basic_raw_socket/local_endpoint/ +/doc/asio/reference/basic_raw_socket/local_endpoint.html +/doc/asio/reference/basic_raw_socket/local_endpoint/overload1.html +/doc/asio/reference/basic_raw_socket/local_endpoint/overload2.html +/doc/asio/reference/basic_raw_socket/lowest_layer/ +/doc/asio/reference/basic_raw_socket/lowest_layer.html +/doc/asio/reference/basic_raw_socket/lowest_layer/overload1.html +/doc/asio/reference/basic_raw_socket/lowest_layer/overload2.html +/doc/asio/reference/basic_raw_socket/lowest_layer_type.html +/doc/asio/reference/basic_raw_socket/max_connections.html +/doc/asio/reference/basic_raw_socket/max_listen_connections.html +/doc/asio/reference/basic_raw_socket/message_do_not_route.html +/doc/asio/reference/basic_raw_socket/message_end_of_record.html +/doc/asio/reference/basic_raw_socket/message_flags.html +/doc/asio/reference/basic_raw_socket/message_out_of_band.html +/doc/asio/reference/basic_raw_socket/message_peek.html +/doc/asio/reference/basic_raw_socket/native_handle.html +/doc/asio/reference/basic_raw_socket/native_handle_type.html +/doc/asio/reference/basic_raw_socket/native_non_blocking/ +/doc/asio/reference/basic_raw_socket/native_non_blocking.html +/doc/asio/reference/basic_raw_socket/native_non_blocking/overload1.html +/doc/asio/reference/basic_raw_socket/native_non_blocking/overload2.html +/doc/asio/reference/basic_raw_socket/native_non_blocking/overload3.html +/doc/asio/reference/basic_raw_socket/non_blocking/ +/doc/asio/reference/basic_raw_socket/non_blocking.html +/doc/asio/reference/basic_raw_socket/non_blocking/overload1.html +/doc/asio/reference/basic_raw_socket/non_blocking/overload2.html +/doc/asio/reference/basic_raw_socket/non_blocking/overload3.html +/doc/asio/reference/basic_raw_socket/open/ +/doc/asio/reference/basic_raw_socket/open.html +/doc/asio/reference/basic_raw_socket/open/overload1.html +/doc/asio/reference/basic_raw_socket/open/overload2.html +/doc/asio/reference/basic_raw_socket/operator_eq_/ +/doc/asio/reference/basic_raw_socket/operator_eq_.html +/doc/asio/reference/basic_raw_socket/operator_eq_/overload1.html +/doc/asio/reference/basic_raw_socket/operator_eq_/overload2.html +/doc/asio/reference/basic_raw_socket/out_of_band_inline.html +/doc/asio/reference/basic_raw_socket/protocol_type.html +/doc/asio/reference/basic_raw_socket__rebind_executor/ +/doc/asio/reference/basic_raw_socket__rebind_executor.html +/doc/asio/reference/basic_raw_socket__rebind_executor/other.html +/doc/asio/reference/basic_raw_socket/receive/ +/doc/asio/reference/basic_raw_socket/receive_buffer_size.html +/doc/asio/reference/basic_raw_socket/receive_from/ +/doc/asio/reference/basic_raw_socket/receive_from.html +/doc/asio/reference/basic_raw_socket/receive_from/overload1.html +/doc/asio/reference/basic_raw_socket/receive_from/overload2.html +/doc/asio/reference/basic_raw_socket/receive_from/overload3.html +/doc/asio/reference/basic_raw_socket/receive.html +/doc/asio/reference/basic_raw_socket/receive_low_watermark.html +/doc/asio/reference/basic_raw_socket/receive/overload1.html +/doc/asio/reference/basic_raw_socket/receive/overload2.html +/doc/asio/reference/basic_raw_socket/receive/overload3.html +/doc/asio/reference/basic_raw_socket/release/ +/doc/asio/reference/basic_raw_socket/release.html +/doc/asio/reference/basic_raw_socket/release/overload1.html +/doc/asio/reference/basic_raw_socket/release/overload2.html +/doc/asio/reference/basic_raw_socket/remote_endpoint/ +/doc/asio/reference/basic_raw_socket/remote_endpoint.html +/doc/asio/reference/basic_raw_socket/remote_endpoint/overload1.html +/doc/asio/reference/basic_raw_socket/remote_endpoint/overload2.html +/doc/asio/reference/basic_raw_socket/reuse_address.html +/doc/asio/reference/basic_raw_socket/send/ +/doc/asio/reference/basic_raw_socket/send_buffer_size.html +/doc/asio/reference/basic_raw_socket/send.html +/doc/asio/reference/basic_raw_socket/send_low_watermark.html +/doc/asio/reference/basic_raw_socket/send/overload1.html +/doc/asio/reference/basic_raw_socket/send/overload2.html +/doc/asio/reference/basic_raw_socket/send/overload3.html +/doc/asio/reference/basic_raw_socket/send_to/ +/doc/asio/reference/basic_raw_socket/send_to.html +/doc/asio/reference/basic_raw_socket/send_to/overload1.html +/doc/asio/reference/basic_raw_socket/send_to/overload2.html +/doc/asio/reference/basic_raw_socket/send_to/overload3.html +/doc/asio/reference/basic_raw_socket/set_option/ +/doc/asio/reference/basic_raw_socket/set_option.html +/doc/asio/reference/basic_raw_socket/set_option/overload1.html +/doc/asio/reference/basic_raw_socket/set_option/overload2.html +/doc/asio/reference/basic_raw_socket/shutdown/ +/doc/asio/reference/basic_raw_socket/shutdown.html +/doc/asio/reference/basic_raw_socket/shutdown/overload1.html +/doc/asio/reference/basic_raw_socket/shutdown/overload2.html +/doc/asio/reference/basic_raw_socket/shutdown_type.html +/doc/asio/reference/basic_raw_socket/wait/ +/doc/asio/reference/basic_raw_socket/wait.html +/doc/asio/reference/basic_raw_socket/wait/overload1.html +/doc/asio/reference/basic_raw_socket/wait/overload2.html +/doc/asio/reference/basic_raw_socket/wait_type.html +/doc/asio/reference/basic_seq_packet_socket/ +/doc/asio/reference/basic_seq_packet_socket/assign/ +/doc/asio/reference/basic_seq_packet_socket/assign.html +/doc/asio/reference/basic_seq_packet_socket/assign/overload1.html +/doc/asio/reference/basic_seq_packet_socket/assign/overload2.html +/doc/asio/reference/basic_seq_packet_socket/async_connect.html +/doc/asio/reference/basic_seq_packet_socket/async_receive/ +/doc/asio/reference/basic_seq_packet_socket/async_receive.html +/doc/asio/reference/basic_seq_packet_socket/async_receive/overload1.html +/doc/asio/reference/basic_seq_packet_socket/async_receive/overload2.html +/doc/asio/reference/basic_seq_packet_socket/async_send.html +/doc/asio/reference/basic_seq_packet_socket/async_wait.html +/doc/asio/reference/basic_seq_packet_socket/at_mark/ +/doc/asio/reference/basic_seq_packet_socket/at_mark.html +/doc/asio/reference/basic_seq_packet_socket/at_mark/overload1.html +/doc/asio/reference/basic_seq_packet_socket/at_mark/overload2.html +/doc/asio/reference/basic_seq_packet_socket/available/ +/doc/asio/reference/basic_seq_packet_socket/available.html +/doc/asio/reference/basic_seq_packet_socket/available/overload1.html +/doc/asio/reference/basic_seq_packet_socket/available/overload2.html +/doc/asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/ +/doc/asio/reference/basic_seq_packet_socket/_basic_seq_packet_socket.html +/doc/asio/reference/basic_seq_packet_socket/basic_seq_packet_socket.html +/doc/asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload10.html +/doc/asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload1.html +/doc/asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload2.html +/doc/asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload3.html +/doc/asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload4.html +/doc/asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload5.html +/doc/asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload6.html +/doc/asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload7.html +/doc/asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload8.html +/doc/asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload9.html +/doc/asio/reference/basic_seq_packet_socket/bind/ +/doc/asio/reference/basic_seq_packet_socket/bind.html +/doc/asio/reference/basic_seq_packet_socket/bind/overload1.html +/doc/asio/reference/basic_seq_packet_socket/bind/overload2.html +/doc/asio/reference/basic_seq_packet_socket/broadcast.html +/doc/asio/reference/basic_seq_packet_socket/bytes_readable.html +/doc/asio/reference/basic_seq_packet_socket/cancel/ +/doc/asio/reference/basic_seq_packet_socket/cancel.html +/doc/asio/reference/basic_seq_packet_socket/cancel/overload1.html +/doc/asio/reference/basic_seq_packet_socket/cancel/overload2.html +/doc/asio/reference/basic_seq_packet_socket/close/ +/doc/asio/reference/basic_seq_packet_socket/close.html +/doc/asio/reference/basic_seq_packet_socket/close/overload1.html +/doc/asio/reference/basic_seq_packet_socket/close/overload2.html +/doc/asio/reference/basic_seq_packet_socket/connect/ +/doc/asio/reference/basic_seq_packet_socket/connect.html +/doc/asio/reference/basic_seq_packet_socket/connect/overload1.html +/doc/asio/reference/basic_seq_packet_socket/connect/overload2.html +/doc/asio/reference/basic_seq_packet_socket/debug.html +/doc/asio/reference/basic_seq_packet_socket/do_not_route.html +/doc/asio/reference/basic_seq_packet_socket/enable_connection_aborted.html +/doc/asio/reference/basic_seq_packet_socket/endpoint_type.html +/doc/asio/reference/basic_seq_packet_socket/executor_type.html +/doc/asio/reference/basic_seq_packet_socket/get_executor.html +/doc/asio/reference/basic_seq_packet_socket/get_option/ +/doc/asio/reference/basic_seq_packet_socket/get_option.html +/doc/asio/reference/basic_seq_packet_socket/get_option/overload1.html +/doc/asio/reference/basic_seq_packet_socket/get_option/overload2.html +/doc/asio/reference/basic_seq_packet_socket.html +/doc/asio/reference/basic_seq_packet_socket/impl_.html +/doc/asio/reference/basic_seq_packet_socket/io_control/ +/doc/asio/reference/basic_seq_packet_socket/io_control.html +/doc/asio/reference/basic_seq_packet_socket/io_control/overload1.html +/doc/asio/reference/basic_seq_packet_socket/io_control/overload2.html +/doc/asio/reference/basic_seq_packet_socket/is_open.html +/doc/asio/reference/basic_seq_packet_socket/keep_alive.html +/doc/asio/reference/basic_seq_packet_socket/linger.html +/doc/asio/reference/basic_seq_packet_socket/local_endpoint/ +/doc/asio/reference/basic_seq_packet_socket/local_endpoint.html +/doc/asio/reference/basic_seq_packet_socket/local_endpoint/overload1.html +/doc/asio/reference/basic_seq_packet_socket/local_endpoint/overload2.html +/doc/asio/reference/basic_seq_packet_socket/lowest_layer/ +/doc/asio/reference/basic_seq_packet_socket/lowest_layer.html +/doc/asio/reference/basic_seq_packet_socket/lowest_layer/overload1.html +/doc/asio/reference/basic_seq_packet_socket/lowest_layer/overload2.html +/doc/asio/reference/basic_seq_packet_socket/lowest_layer_type.html +/doc/asio/reference/basic_seq_packet_socket/max_connections.html +/doc/asio/reference/basic_seq_packet_socket/max_listen_connections.html +/doc/asio/reference/basic_seq_packet_socket/message_do_not_route.html +/doc/asio/reference/basic_seq_packet_socket/message_end_of_record.html +/doc/asio/reference/basic_seq_packet_socket/message_flags.html +/doc/asio/reference/basic_seq_packet_socket/message_out_of_band.html +/doc/asio/reference/basic_seq_packet_socket/message_peek.html +/doc/asio/reference/basic_seq_packet_socket/native_handle.html +/doc/asio/reference/basic_seq_packet_socket/native_handle_type.html +/doc/asio/reference/basic_seq_packet_socket/native_non_blocking/ +/doc/asio/reference/basic_seq_packet_socket/native_non_blocking.html +/doc/asio/reference/basic_seq_packet_socket/native_non_blocking/overload1.html +/doc/asio/reference/basic_seq_packet_socket/native_non_blocking/overload2.html +/doc/asio/reference/basic_seq_packet_socket/native_non_blocking/overload3.html +/doc/asio/reference/basic_seq_packet_socket/non_blocking/ +/doc/asio/reference/basic_seq_packet_socket/non_blocking.html +/doc/asio/reference/basic_seq_packet_socket/non_blocking/overload1.html +/doc/asio/reference/basic_seq_packet_socket/non_blocking/overload2.html +/doc/asio/reference/basic_seq_packet_socket/non_blocking/overload3.html +/doc/asio/reference/basic_seq_packet_socket/open/ +/doc/asio/reference/basic_seq_packet_socket/open.html +/doc/asio/reference/basic_seq_packet_socket/open/overload1.html +/doc/asio/reference/basic_seq_packet_socket/open/overload2.html +/doc/asio/reference/basic_seq_packet_socket/operator_eq_/ +/doc/asio/reference/basic_seq_packet_socket/operator_eq_.html +/doc/asio/reference/basic_seq_packet_socket/operator_eq_/overload1.html +/doc/asio/reference/basic_seq_packet_socket/operator_eq_/overload2.html +/doc/asio/reference/basic_seq_packet_socket/out_of_band_inline.html +/doc/asio/reference/basic_seq_packet_socket/protocol_type.html +/doc/asio/reference/basic_seq_packet_socket__rebind_executor/ +/doc/asio/reference/basic_seq_packet_socket__rebind_executor.html +/doc/asio/reference/basic_seq_packet_socket__rebind_executor/other.html +/doc/asio/reference/basic_seq_packet_socket/receive/ +/doc/asio/reference/basic_seq_packet_socket/receive_buffer_size.html +/doc/asio/reference/basic_seq_packet_socket/receive.html +/doc/asio/reference/basic_seq_packet_socket/receive_low_watermark.html +/doc/asio/reference/basic_seq_packet_socket/receive/overload1.html +/doc/asio/reference/basic_seq_packet_socket/receive/overload2.html +/doc/asio/reference/basic_seq_packet_socket/receive/overload3.html +/doc/asio/reference/basic_seq_packet_socket/release/ +/doc/asio/reference/basic_seq_packet_socket/release.html +/doc/asio/reference/basic_seq_packet_socket/release/overload1.html +/doc/asio/reference/basic_seq_packet_socket/release/overload2.html +/doc/asio/reference/basic_seq_packet_socket/remote_endpoint/ +/doc/asio/reference/basic_seq_packet_socket/remote_endpoint.html +/doc/asio/reference/basic_seq_packet_socket/remote_endpoint/overload1.html +/doc/asio/reference/basic_seq_packet_socket/remote_endpoint/overload2.html +/doc/asio/reference/basic_seq_packet_socket/reuse_address.html +/doc/asio/reference/basic_seq_packet_socket/send/ +/doc/asio/reference/basic_seq_packet_socket/send_buffer_size.html +/doc/asio/reference/basic_seq_packet_socket/send.html +/doc/asio/reference/basic_seq_packet_socket/send_low_watermark.html +/doc/asio/reference/basic_seq_packet_socket/send/overload1.html +/doc/asio/reference/basic_seq_packet_socket/send/overload2.html +/doc/asio/reference/basic_seq_packet_socket/set_option/ +/doc/asio/reference/basic_seq_packet_socket/set_option.html +/doc/asio/reference/basic_seq_packet_socket/set_option/overload1.html +/doc/asio/reference/basic_seq_packet_socket/set_option/overload2.html +/doc/asio/reference/basic_seq_packet_socket/shutdown/ +/doc/asio/reference/basic_seq_packet_socket/shutdown.html +/doc/asio/reference/basic_seq_packet_socket/shutdown/overload1.html +/doc/asio/reference/basic_seq_packet_socket/shutdown/overload2.html +/doc/asio/reference/basic_seq_packet_socket/shutdown_type.html +/doc/asio/reference/basic_seq_packet_socket/wait/ +/doc/asio/reference/basic_seq_packet_socket/wait.html +/doc/asio/reference/basic_seq_packet_socket/wait/overload1.html +/doc/asio/reference/basic_seq_packet_socket/wait/overload2.html +/doc/asio/reference/basic_seq_packet_socket/wait_type.html +/doc/asio/reference/basic_serial_port/ +/doc/asio/reference/basic_serial_port/assign/ +/doc/asio/reference/basic_serial_port/assign.html +/doc/asio/reference/basic_serial_port/assign/overload1.html +/doc/asio/reference/basic_serial_port/assign/overload2.html +/doc/asio/reference/basic_serial_port/async_read_some.html +/doc/asio/reference/basic_serial_port/async_write_some.html +/doc/asio/reference/basic_serial_port/basic_serial_port/ +/doc/asio/reference/basic_serial_port/_basic_serial_port.html +/doc/asio/reference/basic_serial_port/basic_serial_port.html +/doc/asio/reference/basic_serial_port/basic_serial_port/overload1.html +/doc/asio/reference/basic_serial_port/basic_serial_port/overload2.html +/doc/asio/reference/basic_serial_port/basic_serial_port/overload3.html +/doc/asio/reference/basic_serial_port/basic_serial_port/overload4.html +/doc/asio/reference/basic_serial_port/basic_serial_port/overload5.html +/doc/asio/reference/basic_serial_port/basic_serial_port/overload6.html +/doc/asio/reference/basic_serial_port/basic_serial_port/overload7.html +/doc/asio/reference/basic_serial_port/basic_serial_port/overload8.html +/doc/asio/reference/basic_serial_port/basic_serial_port/overload9.html +/doc/asio/reference/basic_serial_port/cancel/ +/doc/asio/reference/basic_serial_port/cancel.html +/doc/asio/reference/basic_serial_port/cancel/overload1.html +/doc/asio/reference/basic_serial_port/cancel/overload2.html +/doc/asio/reference/basic_serial_port/close/ +/doc/asio/reference/basic_serial_port/close.html +/doc/asio/reference/basic_serial_port/close/overload1.html +/doc/asio/reference/basic_serial_port/close/overload2.html +/doc/asio/reference/basic_serial_port/executor_type.html +/doc/asio/reference/basic_serial_port/get_executor.html +/doc/asio/reference/basic_serial_port/get_option/ +/doc/asio/reference/basic_serial_port/get_option.html +/doc/asio/reference/basic_serial_port/get_option/overload1.html +/doc/asio/reference/basic_serial_port/get_option/overload2.html +/doc/asio/reference/basic_serial_port.html +/doc/asio/reference/basic_serial_port/is_open.html +/doc/asio/reference/basic_serial_port/lowest_layer/ +/doc/asio/reference/basic_serial_port/lowest_layer.html +/doc/asio/reference/basic_serial_port/lowest_layer/overload1.html +/doc/asio/reference/basic_serial_port/lowest_layer/overload2.html +/doc/asio/reference/basic_serial_port/lowest_layer_type.html +/doc/asio/reference/basic_serial_port/native_handle.html +/doc/asio/reference/basic_serial_port/native_handle_type.html +/doc/asio/reference/basic_serial_port/open/ +/doc/asio/reference/basic_serial_port/open.html +/doc/asio/reference/basic_serial_port/open/overload1.html +/doc/asio/reference/basic_serial_port/open/overload2.html +/doc/asio/reference/basic_serial_port/operator_eq_.html +/doc/asio/reference/basic_serial_port/read_some/ +/doc/asio/reference/basic_serial_port/read_some.html +/doc/asio/reference/basic_serial_port/read_some/overload1.html +/doc/asio/reference/basic_serial_port/read_some/overload2.html +/doc/asio/reference/basic_serial_port__rebind_executor/ +/doc/asio/reference/basic_serial_port__rebind_executor.html +/doc/asio/reference/basic_serial_port__rebind_executor/other.html +/doc/asio/reference/basic_serial_port/send_break/ +/doc/asio/reference/basic_serial_port/send_break.html +/doc/asio/reference/basic_serial_port/send_break/overload1.html +/doc/asio/reference/basic_serial_port/send_break/overload2.html +/doc/asio/reference/basic_serial_port/set_option/ +/doc/asio/reference/basic_serial_port/set_option.html +/doc/asio/reference/basic_serial_port/set_option/overload1.html +/doc/asio/reference/basic_serial_port/set_option/overload2.html +/doc/asio/reference/basic_serial_port/write_some/ +/doc/asio/reference/basic_serial_port/write_some.html +/doc/asio/reference/basic_serial_port/write_some/overload1.html +/doc/asio/reference/basic_serial_port/write_some/overload2.html +/doc/asio/reference/basic_signal_set/ +/doc/asio/reference/basic_signal_set/add/ +/doc/asio/reference/basic_signal_set/add.html +/doc/asio/reference/basic_signal_set/add/overload1.html +/doc/asio/reference/basic_signal_set/add/overload2.html +/doc/asio/reference/basic_signal_set/async_wait.html +/doc/asio/reference/basic_signal_set/basic_signal_set/ +/doc/asio/reference/basic_signal_set/_basic_signal_set.html +/doc/asio/reference/basic_signal_set/basic_signal_set.html +/doc/asio/reference/basic_signal_set/basic_signal_set/overload1.html +/doc/asio/reference/basic_signal_set/basic_signal_set/overload2.html +/doc/asio/reference/basic_signal_set/basic_signal_set/overload3.html +/doc/asio/reference/basic_signal_set/basic_signal_set/overload4.html +/doc/asio/reference/basic_signal_set/basic_signal_set/overload5.html +/doc/asio/reference/basic_signal_set/basic_signal_set/overload6.html +/doc/asio/reference/basic_signal_set/basic_signal_set/overload7.html +/doc/asio/reference/basic_signal_set/basic_signal_set/overload8.html +/doc/asio/reference/basic_signal_set/cancel/ +/doc/asio/reference/basic_signal_set/cancel.html +/doc/asio/reference/basic_signal_set/cancel/overload1.html +/doc/asio/reference/basic_signal_set/cancel/overload2.html +/doc/asio/reference/basic_signal_set/clear/ +/doc/asio/reference/basic_signal_set/clear.html +/doc/asio/reference/basic_signal_set/clear/overload1.html +/doc/asio/reference/basic_signal_set/clear/overload2.html +/doc/asio/reference/basic_signal_set/executor_type.html +/doc/asio/reference/basic_signal_set/get_executor.html +/doc/asio/reference/basic_signal_set.html +/doc/asio/reference/basic_signal_set__rebind_executor/ +/doc/asio/reference/basic_signal_set__rebind_executor.html +/doc/asio/reference/basic_signal_set__rebind_executor/other.html +/doc/asio/reference/basic_signal_set/remove/ +/doc/asio/reference/basic_signal_set/remove.html +/doc/asio/reference/basic_signal_set/remove/overload1.html +/doc/asio/reference/basic_signal_set/remove/overload2.html +/doc/asio/reference/basic_socket/ +/doc/asio/reference/basic_socket_acceptor/ +/doc/asio/reference/basic_socket_acceptor/accept/ +/doc/asio/reference/basic_socket_acceptor/accept.html +/doc/asio/reference/basic_socket_acceptor/accept/overload10.html +/doc/asio/reference/basic_socket_acceptor/accept/overload11.html +/doc/asio/reference/basic_socket_acceptor/accept/overload12.html +/doc/asio/reference/basic_socket_acceptor/accept/overload13.html +/doc/asio/reference/basic_socket_acceptor/accept/overload14.html +/doc/asio/reference/basic_socket_acceptor/accept/overload15.html +/doc/asio/reference/basic_socket_acceptor/accept/overload16.html +/doc/asio/reference/basic_socket_acceptor/accept/overload1.html +/doc/asio/reference/basic_socket_acceptor/accept/overload2.html +/doc/asio/reference/basic_socket_acceptor/accept/overload3.html +/doc/asio/reference/basic_socket_acceptor/accept/overload4.html +/doc/asio/reference/basic_socket_acceptor/accept/overload5.html +/doc/asio/reference/basic_socket_acceptor/accept/overload6.html +/doc/asio/reference/basic_socket_acceptor/accept/overload7.html +/doc/asio/reference/basic_socket_acceptor/accept/overload8.html +/doc/asio/reference/basic_socket_acceptor/accept/overload9.html +/doc/asio/reference/basic_socket_acceptor/assign/ +/doc/asio/reference/basic_socket_acceptor/assign.html +/doc/asio/reference/basic_socket_acceptor/assign/overload1.html +/doc/asio/reference/basic_socket_acceptor/assign/overload2.html +/doc/asio/reference/basic_socket_acceptor/async_accept/ +/doc/asio/reference/basic_socket_acceptor/async_accept.html +/doc/asio/reference/basic_socket_acceptor/async_accept/overload1.html +/doc/asio/reference/basic_socket_acceptor/async_accept/overload2.html +/doc/asio/reference/basic_socket_acceptor/async_accept/overload3.html +/doc/asio/reference/basic_socket_acceptor/async_accept/overload4.html +/doc/asio/reference/basic_socket_acceptor/async_accept/overload5.html +/doc/asio/reference/basic_socket_acceptor/async_accept/overload6.html +/doc/asio/reference/basic_socket_acceptor/async_accept/overload7.html +/doc/asio/reference/basic_socket_acceptor/async_accept/overload8.html +/doc/asio/reference/basic_socket_acceptor/async_wait.html +/doc/asio/reference/basic_socket_acceptor/basic_socket_acceptor/ +/doc/asio/reference/basic_socket_acceptor/_basic_socket_acceptor.html +/doc/asio/reference/basic_socket_acceptor/basic_socket_acceptor.html +/doc/asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload10.html +/doc/asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload1.html +/doc/asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload2.html +/doc/asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload3.html +/doc/asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload4.html +/doc/asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload5.html +/doc/asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload6.html +/doc/asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload7.html +/doc/asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload8.html +/doc/asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload9.html +/doc/asio/reference/basic_socket_acceptor/bind/ +/doc/asio/reference/basic_socket_acceptor/bind.html +/doc/asio/reference/basic_socket_acceptor/bind/overload1.html +/doc/asio/reference/basic_socket_acceptor/bind/overload2.html +/doc/asio/reference/basic_socket_acceptor/broadcast.html +/doc/asio/reference/basic_socket_acceptor/bytes_readable.html +/doc/asio/reference/basic_socket_acceptor/cancel/ +/doc/asio/reference/basic_socket_acceptor/cancel.html +/doc/asio/reference/basic_socket_acceptor/cancel/overload1.html +/doc/asio/reference/basic_socket_acceptor/cancel/overload2.html +/doc/asio/reference/basic_socket_acceptor/close/ +/doc/asio/reference/basic_socket_acceptor/close.html +/doc/asio/reference/basic_socket_acceptor/close/overload1.html +/doc/asio/reference/basic_socket_acceptor/close/overload2.html +/doc/asio/reference/basic_socket_acceptor/debug.html +/doc/asio/reference/basic_socket_acceptor/do_not_route.html +/doc/asio/reference/basic_socket_acceptor/enable_connection_aborted.html +/doc/asio/reference/basic_socket_acceptor/endpoint_type.html +/doc/asio/reference/basic_socket_acceptor/executor_type.html +/doc/asio/reference/basic_socket_acceptor/get_executor.html +/doc/asio/reference/basic_socket_acceptor/get_option/ +/doc/asio/reference/basic_socket_acceptor/get_option.html +/doc/asio/reference/basic_socket_acceptor/get_option/overload1.html +/doc/asio/reference/basic_socket_acceptor/get_option/overload2.html +/doc/asio/reference/basic_socket_acceptor.html +/doc/asio/reference/basic_socket_acceptor/io_control/ +/doc/asio/reference/basic_socket_acceptor/io_control.html +/doc/asio/reference/basic_socket_acceptor/io_control/overload1.html +/doc/asio/reference/basic_socket_acceptor/io_control/overload2.html +/doc/asio/reference/basic_socket_acceptor/is_open.html +/doc/asio/reference/basic_socket_acceptor/keep_alive.html +/doc/asio/reference/basic_socket_acceptor/linger.html +/doc/asio/reference/basic_socket_acceptor/listen/ +/doc/asio/reference/basic_socket_acceptor/listen.html +/doc/asio/reference/basic_socket_acceptor/listen/overload1.html +/doc/asio/reference/basic_socket_acceptor/listen/overload2.html +/doc/asio/reference/basic_socket_acceptor/local_endpoint/ +/doc/asio/reference/basic_socket_acceptor/local_endpoint.html +/doc/asio/reference/basic_socket_acceptor/local_endpoint/overload1.html +/doc/asio/reference/basic_socket_acceptor/local_endpoint/overload2.html +/doc/asio/reference/basic_socket_acceptor/max_connections.html +/doc/asio/reference/basic_socket_acceptor/max_listen_connections.html +/doc/asio/reference/basic_socket_acceptor/message_do_not_route.html +/doc/asio/reference/basic_socket_acceptor/message_end_of_record.html +/doc/asio/reference/basic_socket_acceptor/message_flags.html +/doc/asio/reference/basic_socket_acceptor/message_out_of_band.html +/doc/asio/reference/basic_socket_acceptor/message_peek.html +/doc/asio/reference/basic_socket_acceptor/native_handle.html +/doc/asio/reference/basic_socket_acceptor/native_handle_type.html +/doc/asio/reference/basic_socket_acceptor/native_non_blocking/ +/doc/asio/reference/basic_socket_acceptor/native_non_blocking.html +/doc/asio/reference/basic_socket_acceptor/native_non_blocking/overload1.html +/doc/asio/reference/basic_socket_acceptor/native_non_blocking/overload2.html +/doc/asio/reference/basic_socket_acceptor/native_non_blocking/overload3.html +/doc/asio/reference/basic_socket_acceptor/non_blocking/ +/doc/asio/reference/basic_socket_acceptor/non_blocking.html +/doc/asio/reference/basic_socket_acceptor/non_blocking/overload1.html +/doc/asio/reference/basic_socket_acceptor/non_blocking/overload2.html +/doc/asio/reference/basic_socket_acceptor/non_blocking/overload3.html +/doc/asio/reference/basic_socket_acceptor/open/ +/doc/asio/reference/basic_socket_acceptor/open.html +/doc/asio/reference/basic_socket_acceptor/open/overload1.html +/doc/asio/reference/basic_socket_acceptor/open/overload2.html +/doc/asio/reference/basic_socket_acceptor/operator_eq_/ +/doc/asio/reference/basic_socket_acceptor/operator_eq_.html +/doc/asio/reference/basic_socket_acceptor/operator_eq_/overload1.html +/doc/asio/reference/basic_socket_acceptor/operator_eq_/overload2.html +/doc/asio/reference/basic_socket_acceptor/out_of_band_inline.html +/doc/asio/reference/basic_socket_acceptor/protocol_type.html +/doc/asio/reference/basic_socket_acceptor__rebind_executor/ +/doc/asio/reference/basic_socket_acceptor__rebind_executor.html +/doc/asio/reference/basic_socket_acceptor__rebind_executor/other.html +/doc/asio/reference/basic_socket_acceptor/receive_buffer_size.html +/doc/asio/reference/basic_socket_acceptor/receive_low_watermark.html +/doc/asio/reference/basic_socket_acceptor/release/ +/doc/asio/reference/basic_socket_acceptor/release.html +/doc/asio/reference/basic_socket_acceptor/release/overload1.html +/doc/asio/reference/basic_socket_acceptor/release/overload2.html +/doc/asio/reference/basic_socket_acceptor/reuse_address.html +/doc/asio/reference/basic_socket_acceptor/send_buffer_size.html +/doc/asio/reference/basic_socket_acceptor/send_low_watermark.html +/doc/asio/reference/basic_socket_acceptor/set_option/ +/doc/asio/reference/basic_socket_acceptor/set_option.html +/doc/asio/reference/basic_socket_acceptor/set_option/overload1.html +/doc/asio/reference/basic_socket_acceptor/set_option/overload2.html +/doc/asio/reference/basic_socket_acceptor/shutdown_type.html +/doc/asio/reference/basic_socket_acceptor/wait/ +/doc/asio/reference/basic_socket_acceptor/wait.html +/doc/asio/reference/basic_socket_acceptor/wait/overload1.html +/doc/asio/reference/basic_socket_acceptor/wait/overload2.html +/doc/asio/reference/basic_socket_acceptor/wait_type.html +/doc/asio/reference/basic_socket/assign/ +/doc/asio/reference/basic_socket/assign.html +/doc/asio/reference/basic_socket/assign/overload1.html +/doc/asio/reference/basic_socket/assign/overload2.html +/doc/asio/reference/basic_socket/async_connect.html +/doc/asio/reference/basic_socket/async_wait.html +/doc/asio/reference/basic_socket/at_mark/ +/doc/asio/reference/basic_socket/at_mark.html +/doc/asio/reference/basic_socket/at_mark/overload1.html +/doc/asio/reference/basic_socket/at_mark/overload2.html +/doc/asio/reference/basic_socket/available/ +/doc/asio/reference/basic_socket/available.html +/doc/asio/reference/basic_socket/available/overload1.html +/doc/asio/reference/basic_socket/available/overload2.html +/doc/asio/reference/basic_socket/basic_socket/ +/doc/asio/reference/basic_socket/_basic_socket.html +/doc/asio/reference/basic_socket/basic_socket.html +/doc/asio/reference/basic_socket/basic_socket/overload10.html +/doc/asio/reference/basic_socket/basic_socket/overload1.html +/doc/asio/reference/basic_socket/basic_socket/overload2.html +/doc/asio/reference/basic_socket/basic_socket/overload3.html +/doc/asio/reference/basic_socket/basic_socket/overload4.html +/doc/asio/reference/basic_socket/basic_socket/overload5.html +/doc/asio/reference/basic_socket/basic_socket/overload6.html +/doc/asio/reference/basic_socket/basic_socket/overload7.html +/doc/asio/reference/basic_socket/basic_socket/overload8.html +/doc/asio/reference/basic_socket/basic_socket/overload9.html +/doc/asio/reference/basic_socket/bind/ +/doc/asio/reference/basic_socket/bind.html +/doc/asio/reference/basic_socket/bind/overload1.html +/doc/asio/reference/basic_socket/bind/overload2.html +/doc/asio/reference/basic_socket/broadcast.html +/doc/asio/reference/basic_socket/bytes_readable.html +/doc/asio/reference/basic_socket/cancel/ +/doc/asio/reference/basic_socket/cancel.html +/doc/asio/reference/basic_socket/cancel/overload1.html +/doc/asio/reference/basic_socket/cancel/overload2.html +/doc/asio/reference/basic_socket/close/ +/doc/asio/reference/basic_socket/close.html +/doc/asio/reference/basic_socket/close/overload1.html +/doc/asio/reference/basic_socket/close/overload2.html +/doc/asio/reference/basic_socket/connect/ +/doc/asio/reference/basic_socket/connect.html +/doc/asio/reference/basic_socket/connect/overload1.html +/doc/asio/reference/basic_socket/connect/overload2.html +/doc/asio/reference/basic_socket/debug.html +/doc/asio/reference/basic_socket/do_not_route.html +/doc/asio/reference/basic_socket/enable_connection_aborted.html +/doc/asio/reference/basic_socket/endpoint_type.html +/doc/asio/reference/basic_socket/executor_type.html +/doc/asio/reference/basic_socket/get_executor.html +/doc/asio/reference/basic_socket/get_option/ +/doc/asio/reference/basic_socket/get_option.html +/doc/asio/reference/basic_socket/get_option/overload1.html +/doc/asio/reference/basic_socket/get_option/overload2.html +/doc/asio/reference/basic_socket.html +/doc/asio/reference/basic_socket/impl_.html +/doc/asio/reference/basic_socket/io_control/ +/doc/asio/reference/basic_socket/io_control.html +/doc/asio/reference/basic_socket/io_control/overload1.html +/doc/asio/reference/basic_socket/io_control/overload2.html +/doc/asio/reference/basic_socket_iostream/ +/doc/asio/reference/basic_socket_iostream/basic_socket_iostream/ +/doc/asio/reference/basic_socket_iostream/basic_socket_iostream.html +/doc/asio/reference/basic_socket_iostream/basic_socket_iostream/overload1.html +/doc/asio/reference/basic_socket_iostream/basic_socket_iostream/overload2.html +/doc/asio/reference/basic_socket_iostream/basic_socket_iostream/overload3.html +/doc/asio/reference/basic_socket_iostream/basic_socket_iostream/overload4.html +/doc/asio/reference/basic_socket_iostream/clock_type.html +/doc/asio/reference/basic_socket_iostream/close.html +/doc/asio/reference/basic_socket_iostream/connect.html +/doc/asio/reference/basic_socket_iostream/duration.html +/doc/asio/reference/basic_socket_iostream/duration_type.html +/doc/asio/reference/basic_socket_iostream/endpoint_type.html +/doc/asio/reference/basic_socket_iostream/error.html +/doc/asio/reference/basic_socket_iostream/expires_after.html +/doc/asio/reference/basic_socket_iostream/expires_at/ +/doc/asio/reference/basic_socket_iostream/expires_at.html +/doc/asio/reference/basic_socket_iostream/expires_at/overload1.html +/doc/asio/reference/basic_socket_iostream/expires_at/overload2.html +/doc/asio/reference/basic_socket_iostream/expires_from_now/ +/doc/asio/reference/basic_socket_iostream/expires_from_now.html +/doc/asio/reference/basic_socket_iostream/expires_from_now/overload1.html +/doc/asio/reference/basic_socket_iostream/expires_from_now/overload2.html +/doc/asio/reference/basic_socket_iostream/expiry.html +/doc/asio/reference/basic_socket_iostream.html +/doc/asio/reference/basic_socket_iostream/operator_eq_.html +/doc/asio/reference/basic_socket_iostream/protocol_type.html +/doc/asio/reference/basic_socket_iostream/rdbuf.html +/doc/asio/reference/basic_socket_iostream/socket.html +/doc/asio/reference/basic_socket_iostream/time_point.html +/doc/asio/reference/basic_socket_iostream/time_type.html +/doc/asio/reference/basic_socket/is_open.html +/doc/asio/reference/basic_socket/keep_alive.html +/doc/asio/reference/basic_socket/linger.html +/doc/asio/reference/basic_socket/local_endpoint/ +/doc/asio/reference/basic_socket/local_endpoint.html +/doc/asio/reference/basic_socket/local_endpoint/overload1.html +/doc/asio/reference/basic_socket/local_endpoint/overload2.html +/doc/asio/reference/basic_socket/lowest_layer/ +/doc/asio/reference/basic_socket/lowest_layer.html +/doc/asio/reference/basic_socket/lowest_layer/overload1.html +/doc/asio/reference/basic_socket/lowest_layer/overload2.html +/doc/asio/reference/basic_socket/lowest_layer_type.html +/doc/asio/reference/basic_socket/max_connections.html +/doc/asio/reference/basic_socket/max_listen_connections.html +/doc/asio/reference/basic_socket/message_do_not_route.html +/doc/asio/reference/basic_socket/message_end_of_record.html +/doc/asio/reference/basic_socket/message_flags.html +/doc/asio/reference/basic_socket/message_out_of_band.html +/doc/asio/reference/basic_socket/message_peek.html +/doc/asio/reference/basic_socket/native_handle.html +/doc/asio/reference/basic_socket/native_handle_type.html +/doc/asio/reference/basic_socket/native_non_blocking/ +/doc/asio/reference/basic_socket/native_non_blocking.html +/doc/asio/reference/basic_socket/native_non_blocking/overload1.html +/doc/asio/reference/basic_socket/native_non_blocking/overload2.html +/doc/asio/reference/basic_socket/native_non_blocking/overload3.html +/doc/asio/reference/basic_socket/non_blocking/ +/doc/asio/reference/basic_socket/non_blocking.html +/doc/asio/reference/basic_socket/non_blocking/overload1.html +/doc/asio/reference/basic_socket/non_blocking/overload2.html +/doc/asio/reference/basic_socket/non_blocking/overload3.html +/doc/asio/reference/basic_socket/open/ +/doc/asio/reference/basic_socket/open.html +/doc/asio/reference/basic_socket/open/overload1.html +/doc/asio/reference/basic_socket/open/overload2.html +/doc/asio/reference/basic_socket/operator_eq_/ +/doc/asio/reference/basic_socket/operator_eq_.html +/doc/asio/reference/basic_socket/operator_eq_/overload1.html +/doc/asio/reference/basic_socket/operator_eq_/overload2.html +/doc/asio/reference/basic_socket/out_of_band_inline.html +/doc/asio/reference/basic_socket/protocol_type.html +/doc/asio/reference/basic_socket__rebind_executor/ +/doc/asio/reference/basic_socket__rebind_executor.html +/doc/asio/reference/basic_socket__rebind_executor/other.html +/doc/asio/reference/basic_socket/receive_buffer_size.html +/doc/asio/reference/basic_socket/receive_low_watermark.html +/doc/asio/reference/basic_socket/release/ +/doc/asio/reference/basic_socket/release.html +/doc/asio/reference/basic_socket/release/overload1.html +/doc/asio/reference/basic_socket/release/overload2.html +/doc/asio/reference/basic_socket/remote_endpoint/ +/doc/asio/reference/basic_socket/remote_endpoint.html +/doc/asio/reference/basic_socket/remote_endpoint/overload1.html +/doc/asio/reference/basic_socket/remote_endpoint/overload2.html +/doc/asio/reference/basic_socket/reuse_address.html +/doc/asio/reference/basic_socket/send_buffer_size.html +/doc/asio/reference/basic_socket/send_low_watermark.html +/doc/asio/reference/basic_socket/set_option/ +/doc/asio/reference/basic_socket/set_option.html +/doc/asio/reference/basic_socket/set_option/overload1.html +/doc/asio/reference/basic_socket/set_option/overload2.html +/doc/asio/reference/basic_socket/shutdown/ +/doc/asio/reference/basic_socket/shutdown.html +/doc/asio/reference/basic_socket/shutdown/overload1.html +/doc/asio/reference/basic_socket/shutdown/overload2.html +/doc/asio/reference/basic_socket/shutdown_type.html +/doc/asio/reference/basic_socket_streambuf/ +/doc/asio/reference/basic_socket_streambuf/basic_socket_streambuf/ +/doc/asio/reference/basic_socket_streambuf/_basic_socket_streambuf.html +/doc/asio/reference/basic_socket_streambuf/basic_socket_streambuf.html +/doc/asio/reference/basic_socket_streambuf/basic_socket_streambuf/overload1.html +/doc/asio/reference/basic_socket_streambuf/basic_socket_streambuf/overload2.html +/doc/asio/reference/basic_socket_streambuf/basic_socket_streambuf/overload3.html +/doc/asio/reference/basic_socket_streambuf/clock_type.html +/doc/asio/reference/basic_socket_streambuf/close.html +/doc/asio/reference/basic_socket_streambuf/connect/ +/doc/asio/reference/basic_socket_streambuf/connect.html +/doc/asio/reference/basic_socket_streambuf/connect/overload1.html +/doc/asio/reference/basic_socket_streambuf/connect/overload2.html +/doc/asio/reference/basic_socket_streambuf/duration.html +/doc/asio/reference/basic_socket_streambuf/duration_type.html +/doc/asio/reference/basic_socket_streambuf/endpoint_type.html +/doc/asio/reference/basic_socket_streambuf/error.html +/doc/asio/reference/basic_socket_streambuf/expires_after.html +/doc/asio/reference/basic_socket_streambuf/expires_at/ +/doc/asio/reference/basic_socket_streambuf/expires_at.html +/doc/asio/reference/basic_socket_streambuf/expires_at/overload1.html +/doc/asio/reference/basic_socket_streambuf/expires_at/overload2.html +/doc/asio/reference/basic_socket_streambuf/expires_from_now/ +/doc/asio/reference/basic_socket_streambuf/expires_from_now.html +/doc/asio/reference/basic_socket_streambuf/expires_from_now/overload1.html +/doc/asio/reference/basic_socket_streambuf/expires_from_now/overload2.html +/doc/asio/reference/basic_socket_streambuf/expiry.html +/doc/asio/reference/basic_socket_streambuf.html +/doc/asio/reference/basic_socket_streambuf/operator_eq_.html +/doc/asio/reference/basic_socket_streambuf/overflow.html +/doc/asio/reference/basic_socket_streambuf/protocol_type.html +/doc/asio/reference/basic_socket_streambuf/puberror.html +/doc/asio/reference/basic_socket_streambuf/setbuf.html +/doc/asio/reference/basic_socket_streambuf/socket.html +/doc/asio/reference/basic_socket_streambuf/sync.html +/doc/asio/reference/basic_socket_streambuf/time_point.html +/doc/asio/reference/basic_socket_streambuf/time_type.html +/doc/asio/reference/basic_socket_streambuf/underflow.html +/doc/asio/reference/basic_socket/wait/ +/doc/asio/reference/basic_socket/wait.html +/doc/asio/reference/basic_socket/wait/overload1.html +/doc/asio/reference/basic_socket/wait/overload2.html +/doc/asio/reference/basic_socket/wait_type.html +/doc/asio/reference/basic_streambuf/ +/doc/asio/reference/basic_streambuf/basic_streambuf.html +/doc/asio/reference/basic_streambuf/capacity.html +/doc/asio/reference/basic_streambuf/commit.html +/doc/asio/reference/basic_streambuf/const_buffers_type.html +/doc/asio/reference/basic_streambuf/consume.html +/doc/asio/reference/basic_streambuf/data.html +/doc/asio/reference/basic_streambuf.html +/doc/asio/reference/basic_streambuf/max_size.html +/doc/asio/reference/basic_streambuf/mutable_buffers_type.html +/doc/asio/reference/basic_streambuf/overflow.html +/doc/asio/reference/basic_streambuf/prepare.html +/doc/asio/reference/basic_streambuf_ref/ +/doc/asio/reference/basic_streambuf_ref/basic_streambuf_ref/ +/doc/asio/reference/basic_streambuf_ref/basic_streambuf_ref.html +/doc/asio/reference/basic_streambuf_ref/basic_streambuf_ref/overload1.html +/doc/asio/reference/basic_streambuf_ref/basic_streambuf_ref/overload2.html +/doc/asio/reference/basic_streambuf_ref/basic_streambuf_ref/overload3.html +/doc/asio/reference/basic_streambuf_ref/capacity.html +/doc/asio/reference/basic_streambuf_ref/commit.html +/doc/asio/reference/basic_streambuf_ref/const_buffers_type.html +/doc/asio/reference/basic_streambuf_ref/consume.html +/doc/asio/reference/basic_streambuf_ref/data.html +/doc/asio/reference/basic_streambuf_ref.html +/doc/asio/reference/basic_streambuf_ref/max_size.html +/doc/asio/reference/basic_streambuf_ref/mutable_buffers_type.html +/doc/asio/reference/basic_streambuf_ref/prepare.html +/doc/asio/reference/basic_streambuf_ref/size.html +/doc/asio/reference/basic_streambuf/reserve.html +/doc/asio/reference/basic_streambuf/size.html +/doc/asio/reference/basic_streambuf/underflow.html +/doc/asio/reference/basic_stream_socket/ +/doc/asio/reference/basic_stream_socket/assign/ +/doc/asio/reference/basic_stream_socket/assign.html +/doc/asio/reference/basic_stream_socket/assign/overload1.html +/doc/asio/reference/basic_stream_socket/assign/overload2.html +/doc/asio/reference/basic_stream_socket/async_connect.html +/doc/asio/reference/basic_stream_socket/async_read_some.html +/doc/asio/reference/basic_stream_socket/async_receive/ +/doc/asio/reference/basic_stream_socket/async_receive.html +/doc/asio/reference/basic_stream_socket/async_receive/overload1.html +/doc/asio/reference/basic_stream_socket/async_receive/overload2.html +/doc/asio/reference/basic_stream_socket/async_send/ +/doc/asio/reference/basic_stream_socket/async_send.html +/doc/asio/reference/basic_stream_socket/async_send/overload1.html +/doc/asio/reference/basic_stream_socket/async_send/overload2.html +/doc/asio/reference/basic_stream_socket/async_wait.html +/doc/asio/reference/basic_stream_socket/async_write_some.html +/doc/asio/reference/basic_stream_socket/at_mark/ +/doc/asio/reference/basic_stream_socket/at_mark.html +/doc/asio/reference/basic_stream_socket/at_mark/overload1.html +/doc/asio/reference/basic_stream_socket/at_mark/overload2.html +/doc/asio/reference/basic_stream_socket/available/ +/doc/asio/reference/basic_stream_socket/available.html +/doc/asio/reference/basic_stream_socket/available/overload1.html +/doc/asio/reference/basic_stream_socket/available/overload2.html +/doc/asio/reference/basic_stream_socket/basic_stream_socket/ +/doc/asio/reference/basic_stream_socket/_basic_stream_socket.html +/doc/asio/reference/basic_stream_socket/basic_stream_socket.html +/doc/asio/reference/basic_stream_socket/basic_stream_socket/overload10.html +/doc/asio/reference/basic_stream_socket/basic_stream_socket/overload1.html +/doc/asio/reference/basic_stream_socket/basic_stream_socket/overload2.html +/doc/asio/reference/basic_stream_socket/basic_stream_socket/overload3.html +/doc/asio/reference/basic_stream_socket/basic_stream_socket/overload4.html +/doc/asio/reference/basic_stream_socket/basic_stream_socket/overload5.html +/doc/asio/reference/basic_stream_socket/basic_stream_socket/overload6.html +/doc/asio/reference/basic_stream_socket/basic_stream_socket/overload7.html +/doc/asio/reference/basic_stream_socket/basic_stream_socket/overload8.html +/doc/asio/reference/basic_stream_socket/basic_stream_socket/overload9.html +/doc/asio/reference/basic_stream_socket/bind/ +/doc/asio/reference/basic_stream_socket/bind.html +/doc/asio/reference/basic_stream_socket/bind/overload1.html +/doc/asio/reference/basic_stream_socket/bind/overload2.html +/doc/asio/reference/basic_stream_socket/broadcast.html +/doc/asio/reference/basic_stream_socket/bytes_readable.html +/doc/asio/reference/basic_stream_socket/cancel/ +/doc/asio/reference/basic_stream_socket/cancel.html +/doc/asio/reference/basic_stream_socket/cancel/overload1.html +/doc/asio/reference/basic_stream_socket/cancel/overload2.html +/doc/asio/reference/basic_stream_socket/close/ +/doc/asio/reference/basic_stream_socket/close.html +/doc/asio/reference/basic_stream_socket/close/overload1.html +/doc/asio/reference/basic_stream_socket/close/overload2.html +/doc/asio/reference/basic_stream_socket/connect/ +/doc/asio/reference/basic_stream_socket/connect.html +/doc/asio/reference/basic_stream_socket/connect/overload1.html +/doc/asio/reference/basic_stream_socket/connect/overload2.html +/doc/asio/reference/basic_stream_socket/debug.html +/doc/asio/reference/basic_stream_socket/do_not_route.html +/doc/asio/reference/basic_stream_socket/enable_connection_aborted.html +/doc/asio/reference/basic_stream_socket/endpoint_type.html +/doc/asio/reference/basic_stream_socket/executor_type.html +/doc/asio/reference/basic_stream_socket/get_executor.html +/doc/asio/reference/basic_stream_socket/get_option/ +/doc/asio/reference/basic_stream_socket/get_option.html +/doc/asio/reference/basic_stream_socket/get_option/overload1.html +/doc/asio/reference/basic_stream_socket/get_option/overload2.html +/doc/asio/reference/basic_stream_socket.html +/doc/asio/reference/basic_stream_socket/impl_.html +/doc/asio/reference/basic_stream_socket/io_control/ +/doc/asio/reference/basic_stream_socket/io_control.html +/doc/asio/reference/basic_stream_socket/io_control/overload1.html +/doc/asio/reference/basic_stream_socket/io_control/overload2.html +/doc/asio/reference/basic_stream_socket/is_open.html +/doc/asio/reference/basic_stream_socket/keep_alive.html +/doc/asio/reference/basic_stream_socket/linger.html +/doc/asio/reference/basic_stream_socket/local_endpoint/ +/doc/asio/reference/basic_stream_socket/local_endpoint.html +/doc/asio/reference/basic_stream_socket/local_endpoint/overload1.html +/doc/asio/reference/basic_stream_socket/local_endpoint/overload2.html +/doc/asio/reference/basic_stream_socket/lowest_layer/ +/doc/asio/reference/basic_stream_socket/lowest_layer.html +/doc/asio/reference/basic_stream_socket/lowest_layer/overload1.html +/doc/asio/reference/basic_stream_socket/lowest_layer/overload2.html +/doc/asio/reference/basic_stream_socket/lowest_layer_type.html +/doc/asio/reference/basic_stream_socket/max_connections.html +/doc/asio/reference/basic_stream_socket/max_listen_connections.html +/doc/asio/reference/basic_stream_socket/message_do_not_route.html +/doc/asio/reference/basic_stream_socket/message_end_of_record.html +/doc/asio/reference/basic_stream_socket/message_flags.html +/doc/asio/reference/basic_stream_socket/message_out_of_band.html +/doc/asio/reference/basic_stream_socket/message_peek.html +/doc/asio/reference/basic_stream_socket/native_handle.html +/doc/asio/reference/basic_stream_socket/native_handle_type.html +/doc/asio/reference/basic_stream_socket/native_non_blocking/ +/doc/asio/reference/basic_stream_socket/native_non_blocking.html +/doc/asio/reference/basic_stream_socket/native_non_blocking/overload1.html +/doc/asio/reference/basic_stream_socket/native_non_blocking/overload2.html +/doc/asio/reference/basic_stream_socket/native_non_blocking/overload3.html +/doc/asio/reference/basic_stream_socket/non_blocking/ +/doc/asio/reference/basic_stream_socket/non_blocking.html +/doc/asio/reference/basic_stream_socket/non_blocking/overload1.html +/doc/asio/reference/basic_stream_socket/non_blocking/overload2.html +/doc/asio/reference/basic_stream_socket/non_blocking/overload3.html +/doc/asio/reference/basic_stream_socket/open/ +/doc/asio/reference/basic_stream_socket/open.html +/doc/asio/reference/basic_stream_socket/open/overload1.html +/doc/asio/reference/basic_stream_socket/open/overload2.html +/doc/asio/reference/basic_stream_socket/operator_eq_/ +/doc/asio/reference/basic_stream_socket/operator_eq_.html +/doc/asio/reference/basic_stream_socket/operator_eq_/overload1.html +/doc/asio/reference/basic_stream_socket/operator_eq_/overload2.html +/doc/asio/reference/basic_stream_socket/out_of_band_inline.html +/doc/asio/reference/basic_stream_socket/protocol_type.html +/doc/asio/reference/basic_stream_socket/read_some/ +/doc/asio/reference/basic_stream_socket/read_some.html +/doc/asio/reference/basic_stream_socket/read_some/overload1.html +/doc/asio/reference/basic_stream_socket/read_some/overload2.html +/doc/asio/reference/basic_stream_socket__rebind_executor/ +/doc/asio/reference/basic_stream_socket__rebind_executor.html +/doc/asio/reference/basic_stream_socket__rebind_executor/other.html +/doc/asio/reference/basic_stream_socket/receive/ +/doc/asio/reference/basic_stream_socket/receive_buffer_size.html +/doc/asio/reference/basic_stream_socket/receive.html +/doc/asio/reference/basic_stream_socket/receive_low_watermark.html +/doc/asio/reference/basic_stream_socket/receive/overload1.html +/doc/asio/reference/basic_stream_socket/receive/overload2.html +/doc/asio/reference/basic_stream_socket/receive/overload3.html +/doc/asio/reference/basic_stream_socket/release/ +/doc/asio/reference/basic_stream_socket/release.html +/doc/asio/reference/basic_stream_socket/release/overload1.html +/doc/asio/reference/basic_stream_socket/release/overload2.html +/doc/asio/reference/basic_stream_socket/remote_endpoint/ +/doc/asio/reference/basic_stream_socket/remote_endpoint.html +/doc/asio/reference/basic_stream_socket/remote_endpoint/overload1.html +/doc/asio/reference/basic_stream_socket/remote_endpoint/overload2.html +/doc/asio/reference/basic_stream_socket/reuse_address.html +/doc/asio/reference/basic_stream_socket/send/ +/doc/asio/reference/basic_stream_socket/send_buffer_size.html +/doc/asio/reference/basic_stream_socket/send.html +/doc/asio/reference/basic_stream_socket/send_low_watermark.html +/doc/asio/reference/basic_stream_socket/send/overload1.html +/doc/asio/reference/basic_stream_socket/send/overload2.html +/doc/asio/reference/basic_stream_socket/send/overload3.html +/doc/asio/reference/basic_stream_socket/set_option/ +/doc/asio/reference/basic_stream_socket/set_option.html +/doc/asio/reference/basic_stream_socket/set_option/overload1.html +/doc/asio/reference/basic_stream_socket/set_option/overload2.html +/doc/asio/reference/basic_stream_socket/shutdown/ +/doc/asio/reference/basic_stream_socket/shutdown.html +/doc/asio/reference/basic_stream_socket/shutdown/overload1.html +/doc/asio/reference/basic_stream_socket/shutdown/overload2.html +/doc/asio/reference/basic_stream_socket/shutdown_type.html +/doc/asio/reference/basic_stream_socket/wait/ +/doc/asio/reference/basic_stream_socket/wait.html +/doc/asio/reference/basic_stream_socket/wait/overload1.html +/doc/asio/reference/basic_stream_socket/wait/overload2.html +/doc/asio/reference/basic_stream_socket/wait_type.html +/doc/asio/reference/basic_stream_socket/write_some/ +/doc/asio/reference/basic_stream_socket/write_some.html +/doc/asio/reference/basic_stream_socket/write_some/overload1.html +/doc/asio/reference/basic_stream_socket/write_some/overload2.html +/doc/asio/reference/basic_system_executor/ +/doc/asio/reference/basic_system_executor/basic_system_executor.html +/doc/asio/reference/basic_system_executor/context.html +/doc/asio/reference/basic_system_executor/defer.html +/doc/asio/reference/basic_system_executor/dispatch.html +/doc/asio/reference/basic_system_executor/execute.html +/doc/asio/reference/basic_system_executor.html +/doc/asio/reference/basic_system_executor/on_work_finished.html +/doc/asio/reference/basic_system_executor/on_work_started.html +/doc/asio/reference/basic_system_executor/operator_eq__eq_.html +/doc/asio/reference/basic_system_executor/operator_not__eq_.html +/doc/asio/reference/basic_system_executor/post.html +/doc/asio/reference/basic_system_executor/query/ +/doc/asio/reference/basic_system_executor/query.html +/doc/asio/reference/basic_system_executor/query/overload1.html +/doc/asio/reference/basic_system_executor/query/overload2.html +/doc/asio/reference/basic_system_executor/query/overload3.html +/doc/asio/reference/basic_system_executor/query__static/ +/doc/asio/reference/basic_system_executor/query__static.html +/doc/asio/reference/basic_system_executor/query__static/overload1.html +/doc/asio/reference/basic_system_executor/query__static/overload2.html +/doc/asio/reference/basic_system_executor/query__static/overload3.html +/doc/asio/reference/basic_system_executor/query__static/overload4.html +/doc/asio/reference/basic_system_executor/require/ +/doc/asio/reference/basic_system_executor/require.html +/doc/asio/reference/basic_system_executor/require/overload1.html +/doc/asio/reference/basic_system_executor/require/overload2.html +/doc/asio/reference/basic_system_executor/require/overload3.html +/doc/asio/reference/basic_system_executor/require/overload4.html +/doc/asio/reference/basic_system_executor/require/overload5.html +/doc/asio/reference/basic_system_executor/require/overload6.html +/doc/asio/reference/basic_system_executor/require/overload7.html +/doc/asio/reference/basic_waitable_timer/ +/doc/asio/reference/basic_waitable_timer/async_wait.html +/doc/asio/reference/basic_waitable_timer/basic_waitable_timer/ +/doc/asio/reference/basic_waitable_timer/_basic_waitable_timer.html +/doc/asio/reference/basic_waitable_timer/basic_waitable_timer.html +/doc/asio/reference/basic_waitable_timer/basic_waitable_timer/overload1.html +/doc/asio/reference/basic_waitable_timer/basic_waitable_timer/overload2.html +/doc/asio/reference/basic_waitable_timer/basic_waitable_timer/overload3.html +/doc/asio/reference/basic_waitable_timer/basic_waitable_timer/overload4.html +/doc/asio/reference/basic_waitable_timer/basic_waitable_timer/overload5.html +/doc/asio/reference/basic_waitable_timer/basic_waitable_timer/overload6.html +/doc/asio/reference/basic_waitable_timer/basic_waitable_timer/overload7.html +/doc/asio/reference/basic_waitable_timer/basic_waitable_timer/overload8.html +/doc/asio/reference/basic_waitable_timer/cancel/ +/doc/asio/reference/basic_waitable_timer/cancel.html +/doc/asio/reference/basic_waitable_timer/cancel_one/ +/doc/asio/reference/basic_waitable_timer/cancel_one.html +/doc/asio/reference/basic_waitable_timer/cancel_one/overload1.html +/doc/asio/reference/basic_waitable_timer/cancel_one/overload2.html +/doc/asio/reference/basic_waitable_timer/cancel/overload1.html +/doc/asio/reference/basic_waitable_timer/cancel/overload2.html +/doc/asio/reference/basic_waitable_timer/clock_type.html +/doc/asio/reference/basic_waitable_timer/duration.html +/doc/asio/reference/basic_waitable_timer/executor_type.html +/doc/asio/reference/basic_waitable_timer/expires_after.html +/doc/asio/reference/basic_waitable_timer/expires_at/ +/doc/asio/reference/basic_waitable_timer/expires_at.html +/doc/asio/reference/basic_waitable_timer/expires_at/overload1.html +/doc/asio/reference/basic_waitable_timer/expires_at/overload2.html +/doc/asio/reference/basic_waitable_timer/expires_at/overload3.html +/doc/asio/reference/basic_waitable_timer/expires_from_now/ +/doc/asio/reference/basic_waitable_timer/expires_from_now.html +/doc/asio/reference/basic_waitable_timer/expires_from_now/overload1.html +/doc/asio/reference/basic_waitable_timer/expires_from_now/overload2.html +/doc/asio/reference/basic_waitable_timer/expires_from_now/overload3.html +/doc/asio/reference/basic_waitable_timer/expiry.html +/doc/asio/reference/basic_waitable_timer/get_executor.html +/doc/asio/reference/basic_waitable_timer.html +/doc/asio/reference/basic_waitable_timer/operator_eq_/ +/doc/asio/reference/basic_waitable_timer/operator_eq_.html +/doc/asio/reference/basic_waitable_timer/operator_eq_/overload1.html +/doc/asio/reference/basic_waitable_timer/operator_eq_/overload2.html +/doc/asio/reference/basic_waitable_timer__rebind_executor/ +/doc/asio/reference/basic_waitable_timer__rebind_executor.html +/doc/asio/reference/basic_waitable_timer__rebind_executor/other.html +/doc/asio/reference/basic_waitable_timer/time_point.html +/doc/asio/reference/basic_waitable_timer/traits_type.html +/doc/asio/reference/basic_waitable_timer/wait/ +/doc/asio/reference/basic_waitable_timer/wait.html +/doc/asio/reference/basic_waitable_timer/wait/overload1.html +/doc/asio/reference/basic_waitable_timer/wait/overload2.html +/doc/asio/reference/basic_yield_context/ +/doc/asio/reference/basic_yield_context/basic_yield_context/ +/doc/asio/reference/basic_yield_context/basic_yield_context.html +/doc/asio/reference/basic_yield_context/basic_yield_context/overload1.html +/doc/asio/reference/basic_yield_context/basic_yield_context/overload2.html +/doc/asio/reference/basic_yield_context/callee_type.html +/doc/asio/reference/basic_yield_context/caller_type.html +/doc/asio/reference/basic_yield_context.html +/doc/asio/reference/basic_yield_context/operator_lb__rb_.html +/doc/asio/reference/bind_executor/ +/doc/asio/reference/bind_executor.html +/doc/asio/reference/bind_executor/overload1.html +/doc/asio/reference/bind_executor/overload2.html +/doc/asio/reference/buffer/ +/doc/asio/reference/buffer_cast/ +/doc/asio/reference/buffer_cast.html +/doc/asio/reference/buffer_cast/overload1.html +/doc/asio/reference/buffer_cast/overload2.html +/doc/asio/reference/buffer_copy/ +/doc/asio/reference/buffer_copy.html +/doc/asio/reference/buffer_copy/overload1.html +/doc/asio/reference/buffer_copy/overload2.html +/doc/asio/reference/BufferedHandshakeHandler.html +/doc/asio/reference/buffered_read_stream/ +/doc/asio/reference/buffered_read_stream/async_fill.html +/doc/asio/reference/buffered_read_stream/async_read_some.html +/doc/asio/reference/buffered_read_stream/async_write_some.html +/doc/asio/reference/buffered_read_stream/buffered_read_stream/ +/doc/asio/reference/buffered_read_stream/buffered_read_stream.html +/doc/asio/reference/buffered_read_stream/buffered_read_stream/overload1.html +/doc/asio/reference/buffered_read_stream/buffered_read_stream/overload2.html +/doc/asio/reference/buffered_read_stream/close/ +/doc/asio/reference/buffered_read_stream/close.html +/doc/asio/reference/buffered_read_stream/close/overload1.html +/doc/asio/reference/buffered_read_stream/close/overload2.html +/doc/asio/reference/buffered_read_stream/default_buffer_size.html +/doc/asio/reference/buffered_read_stream/executor_type.html +/doc/asio/reference/buffered_read_stream/fill/ +/doc/asio/reference/buffered_read_stream/fill.html +/doc/asio/reference/buffered_read_stream/fill/overload1.html +/doc/asio/reference/buffered_read_stream/fill/overload2.html +/doc/asio/reference/buffered_read_stream/get_executor.html +/doc/asio/reference/buffered_read_stream.html +/doc/asio/reference/buffered_read_stream/in_avail/ +/doc/asio/reference/buffered_read_stream/in_avail.html +/doc/asio/reference/buffered_read_stream/in_avail/overload1.html +/doc/asio/reference/buffered_read_stream/in_avail/overload2.html +/doc/asio/reference/buffered_read_stream/lowest_layer/ +/doc/asio/reference/buffered_read_stream/lowest_layer.html +/doc/asio/reference/buffered_read_stream/lowest_layer/overload1.html +/doc/asio/reference/buffered_read_stream/lowest_layer/overload2.html +/doc/asio/reference/buffered_read_stream/lowest_layer_type.html +/doc/asio/reference/buffered_read_stream/next_layer.html +/doc/asio/reference/buffered_read_stream/next_layer_type.html +/doc/asio/reference/buffered_read_stream/peek/ +/doc/asio/reference/buffered_read_stream/peek.html +/doc/asio/reference/buffered_read_stream/peek/overload1.html +/doc/asio/reference/buffered_read_stream/peek/overload2.html +/doc/asio/reference/buffered_read_stream/read_some/ +/doc/asio/reference/buffered_read_stream/read_some.html +/doc/asio/reference/buffered_read_stream/read_some/overload1.html +/doc/asio/reference/buffered_read_stream/read_some/overload2.html +/doc/asio/reference/buffered_read_stream/write_some/ +/doc/asio/reference/buffered_read_stream/write_some.html +/doc/asio/reference/buffered_read_stream/write_some/overload1.html +/doc/asio/reference/buffered_read_stream/write_some/overload2.html +/doc/asio/reference/buffered_stream/ +/doc/asio/reference/buffered_stream/async_fill.html +/doc/asio/reference/buffered_stream/async_flush.html +/doc/asio/reference/buffered_stream/async_read_some.html +/doc/asio/reference/buffered_stream/async_write_some.html +/doc/asio/reference/buffered_stream/buffered_stream/ +/doc/asio/reference/buffered_stream/buffered_stream.html +/doc/asio/reference/buffered_stream/buffered_stream/overload1.html +/doc/asio/reference/buffered_stream/buffered_stream/overload2.html +/doc/asio/reference/buffered_stream/close/ +/doc/asio/reference/buffered_stream/close.html +/doc/asio/reference/buffered_stream/close/overload1.html +/doc/asio/reference/buffered_stream/close/overload2.html +/doc/asio/reference/buffered_stream/executor_type.html +/doc/asio/reference/buffered_stream/fill/ +/doc/asio/reference/buffered_stream/fill.html +/doc/asio/reference/buffered_stream/fill/overload1.html +/doc/asio/reference/buffered_stream/fill/overload2.html +/doc/asio/reference/buffered_stream/flush/ +/doc/asio/reference/buffered_stream/flush.html +/doc/asio/reference/buffered_stream/flush/overload1.html +/doc/asio/reference/buffered_stream/flush/overload2.html +/doc/asio/reference/buffered_stream/get_executor.html +/doc/asio/reference/buffered_stream.html +/doc/asio/reference/buffered_stream/in_avail/ +/doc/asio/reference/buffered_stream/in_avail.html +/doc/asio/reference/buffered_stream/in_avail/overload1.html +/doc/asio/reference/buffered_stream/in_avail/overload2.html +/doc/asio/reference/buffered_stream/lowest_layer/ +/doc/asio/reference/buffered_stream/lowest_layer.html +/doc/asio/reference/buffered_stream/lowest_layer/overload1.html +/doc/asio/reference/buffered_stream/lowest_layer/overload2.html +/doc/asio/reference/buffered_stream/lowest_layer_type.html +/doc/asio/reference/buffered_stream/next_layer.html +/doc/asio/reference/buffered_stream/next_layer_type.html +/doc/asio/reference/buffered_stream/peek/ +/doc/asio/reference/buffered_stream/peek.html +/doc/asio/reference/buffered_stream/peek/overload1.html +/doc/asio/reference/buffered_stream/peek/overload2.html +/doc/asio/reference/buffered_stream/read_some/ +/doc/asio/reference/buffered_stream/read_some.html +/doc/asio/reference/buffered_stream/read_some/overload1.html +/doc/asio/reference/buffered_stream/read_some/overload2.html +/doc/asio/reference/buffered_stream/write_some/ +/doc/asio/reference/buffered_stream/write_some.html +/doc/asio/reference/buffered_stream/write_some/overload1.html +/doc/asio/reference/buffered_stream/write_some/overload2.html +/doc/asio/reference/buffered_write_stream/ +/doc/asio/reference/buffered_write_stream/async_flush.html +/doc/asio/reference/buffered_write_stream/async_read_some.html +/doc/asio/reference/buffered_write_stream/async_write_some.html +/doc/asio/reference/buffered_write_stream/buffered_write_stream/ +/doc/asio/reference/buffered_write_stream/buffered_write_stream.html +/doc/asio/reference/buffered_write_stream/buffered_write_stream/overload1.html +/doc/asio/reference/buffered_write_stream/buffered_write_stream/overload2.html +/doc/asio/reference/buffered_write_stream/close/ +/doc/asio/reference/buffered_write_stream/close.html +/doc/asio/reference/buffered_write_stream/close/overload1.html +/doc/asio/reference/buffered_write_stream/close/overload2.html +/doc/asio/reference/buffered_write_stream/default_buffer_size.html +/doc/asio/reference/buffered_write_stream/executor_type.html +/doc/asio/reference/buffered_write_stream/flush/ +/doc/asio/reference/buffered_write_stream/flush.html +/doc/asio/reference/buffered_write_stream/flush/overload1.html +/doc/asio/reference/buffered_write_stream/flush/overload2.html +/doc/asio/reference/buffered_write_stream/get_executor.html +/doc/asio/reference/buffered_write_stream.html +/doc/asio/reference/buffered_write_stream/in_avail/ +/doc/asio/reference/buffered_write_stream/in_avail.html +/doc/asio/reference/buffered_write_stream/in_avail/overload1.html +/doc/asio/reference/buffered_write_stream/in_avail/overload2.html +/doc/asio/reference/buffered_write_stream/lowest_layer/ +/doc/asio/reference/buffered_write_stream/lowest_layer.html +/doc/asio/reference/buffered_write_stream/lowest_layer/overload1.html +/doc/asio/reference/buffered_write_stream/lowest_layer/overload2.html +/doc/asio/reference/buffered_write_stream/lowest_layer_type.html +/doc/asio/reference/buffered_write_stream/next_layer.html +/doc/asio/reference/buffered_write_stream/next_layer_type.html +/doc/asio/reference/buffered_write_stream/peek/ +/doc/asio/reference/buffered_write_stream/peek.html +/doc/asio/reference/buffered_write_stream/peek/overload1.html +/doc/asio/reference/buffered_write_stream/peek/overload2.html +/doc/asio/reference/buffered_write_stream/read_some/ +/doc/asio/reference/buffered_write_stream/read_some.html +/doc/asio/reference/buffered_write_stream/read_some/overload1.html +/doc/asio/reference/buffered_write_stream/read_some/overload2.html +/doc/asio/reference/buffered_write_stream/write_some/ +/doc/asio/reference/buffered_write_stream/write_some.html +/doc/asio/reference/buffered_write_stream/write_some/overload1.html +/doc/asio/reference/buffered_write_stream/write_some/overload2.html +/doc/asio/reference/buffer.html +/doc/asio/reference/buffer/overload10.html +/doc/asio/reference/buffer/overload11.html +/doc/asio/reference/buffer/overload12.html +/doc/asio/reference/buffer/overload13.html +/doc/asio/reference/buffer/overload14.html +/doc/asio/reference/buffer/overload15.html +/doc/asio/reference/buffer/overload16.html +/doc/asio/reference/buffer/overload17.html +/doc/asio/reference/buffer/overload18.html +/doc/asio/reference/buffer/overload19.html +/doc/asio/reference/buffer/overload1.html +/doc/asio/reference/buffer/overload20.html +/doc/asio/reference/buffer/overload21.html +/doc/asio/reference/buffer/overload22.html +/doc/asio/reference/buffer/overload23.html +/doc/asio/reference/buffer/overload24.html +/doc/asio/reference/buffer/overload25.html +/doc/asio/reference/buffer/overload26.html +/doc/asio/reference/buffer/overload27.html +/doc/asio/reference/buffer/overload28.html +/doc/asio/reference/buffer/overload29.html +/doc/asio/reference/buffer/overload2.html +/doc/asio/reference/buffer/overload30.html +/doc/asio/reference/buffer/overload31.html +/doc/asio/reference/buffer/overload32.html +/doc/asio/reference/buffer/overload3.html +/doc/asio/reference/buffer/overload4.html +/doc/asio/reference/buffer/overload5.html +/doc/asio/reference/buffer/overload6.html +/doc/asio/reference/buffer/overload7.html +/doc/asio/reference/buffer/overload8.html +/doc/asio/reference/buffer/overload9.html +/doc/asio/reference/buffers_begin.html +/doc/asio/reference/buffers_end.html +/doc/asio/reference/buffer_sequence_begin/ +/doc/asio/reference/buffer_sequence_begin.html +/doc/asio/reference/buffer_sequence_begin/overload1.html +/doc/asio/reference/buffer_sequence_begin/overload2.html +/doc/asio/reference/buffer_sequence_begin/overload3.html +/doc/asio/reference/buffer_sequence_begin/overload4.html +/doc/asio/reference/buffer_sequence_end/ +/doc/asio/reference/buffer_sequence_end.html +/doc/asio/reference/buffer_sequence_end/overload1.html +/doc/asio/reference/buffer_sequence_end/overload2.html +/doc/asio/reference/buffer_sequence_end/overload3.html +/doc/asio/reference/buffer_sequence_end/overload4.html +/doc/asio/reference/buffers_iterator/ +/doc/asio/reference/buffers_iterator/begin.html +/doc/asio/reference/buffers_iterator/buffers_iterator.html +/doc/asio/reference/buffers_iterator/difference_type.html +/doc/asio/reference/buffers_iterator/end.html +/doc/asio/reference/buffers_iterator.html +/doc/asio/reference/buffers_iterator/iterator_category.html +/doc/asio/reference/buffers_iterator/operator_arrow_.html +/doc/asio/reference/buffers_iterator/operator_eq__eq_.html +/doc/asio/reference/buffers_iterator/operator_gt__eq_.html +/doc/asio/reference/buffers_iterator/operator_gt_.html +/doc/asio/reference/buffers_iterator/operator_lb__rb_.html +/doc/asio/reference/buffers_iterator/operator_lt__eq_.html +/doc/asio/reference/buffers_iterator/operator_lt_.html +/doc/asio/reference/buffers_iterator/operator_minus_/ +/doc/asio/reference/buffers_iterator/operator_minus__eq_.html +/doc/asio/reference/buffers_iterator/operator_minus_.html +/doc/asio/reference/buffers_iterator/operator_minus__minus_/ +/doc/asio/reference/buffers_iterator/operator_minus__minus_.html +/doc/asio/reference/buffers_iterator/operator_minus__minus_/overload1.html +/doc/asio/reference/buffers_iterator/operator_minus__minus_/overload2.html +/doc/asio/reference/buffers_iterator/operator_minus_/overload1.html +/doc/asio/reference/buffers_iterator/operator_minus_/overload2.html +/doc/asio/reference/buffers_iterator/operator_not__eq_.html +/doc/asio/reference/buffers_iterator/operator_plus_/ +/doc/asio/reference/buffers_iterator/operator_plus__eq_.html +/doc/asio/reference/buffers_iterator/operator_plus_.html +/doc/asio/reference/buffers_iterator/operator_plus_/overload1.html +/doc/asio/reference/buffers_iterator/operator_plus_/overload2.html +/doc/asio/reference/buffers_iterator/operator_plus__plus_/ +/doc/asio/reference/buffers_iterator/operator_plus__plus_.html +/doc/asio/reference/buffers_iterator/operator_plus__plus_/overload1.html +/doc/asio/reference/buffers_iterator/operator_plus__plus_/overload2.html +/doc/asio/reference/buffers_iterator/operator__star_.html +/doc/asio/reference/buffers_iterator/pointer.html +/doc/asio/reference/buffers_iterator/reference.html +/doc/asio/reference/buffers_iterator/value_type.html +/doc/asio/reference/buffer_size.html +/doc/asio/reference/can_prefer.html +/doc/asio/reference/can_query.html +/doc/asio/reference/can_require_concept.html +/doc/asio/reference/can_require.html +/doc/asio/reference/CompletionCondition.html +/doc/asio/reference/CompletionHandler.html +/doc/asio/reference/connect/ +/doc/asio/reference/ConnectCondition.html +/doc/asio/reference/ConnectHandler.html +/doc/asio/reference/connect.html +/doc/asio/reference/connect/overload10.html +/doc/asio/reference/connect/overload11.html +/doc/asio/reference/connect/overload12.html +/doc/asio/reference/connect/overload1.html +/doc/asio/reference/connect/overload2.html +/doc/asio/reference/connect/overload3.html +/doc/asio/reference/connect/overload4.html +/doc/asio/reference/connect/overload5.html +/doc/asio/reference/connect/overload6.html +/doc/asio/reference/connect/overload7.html +/doc/asio/reference/connect/overload8.html +/doc/asio/reference/connect/overload9.html +/doc/asio/reference/const_buffer/ +/doc/asio/reference/const_buffer/const_buffer/ +/doc/asio/reference/const_buffer/const_buffer.html +/doc/asio/reference/const_buffer/const_buffer/overload1.html +/doc/asio/reference/const_buffer/const_buffer/overload2.html +/doc/asio/reference/const_buffer/const_buffer/overload3.html +/doc/asio/reference/const_buffer/data.html +/doc/asio/reference/const_buffer.html +/doc/asio/reference/const_buffer/operator_plus_/ +/doc/asio/reference/const_buffer/operator_plus__eq_.html +/doc/asio/reference/const_buffer/operator_plus_.html +/doc/asio/reference/const_buffer/operator_plus_/overload1.html +/doc/asio/reference/const_buffer/operator_plus_/overload2.html +/doc/asio/reference/const_buffers_1/ +/doc/asio/reference/const_buffers_1/begin.html +/doc/asio/reference/const_buffers_1/const_buffers_1/ +/doc/asio/reference/const_buffers_1/const_buffers_1.html +/doc/asio/reference/const_buffers_1/const_buffers_1/overload1.html +/doc/asio/reference/const_buffers_1/const_buffers_1/overload2.html +/doc/asio/reference/const_buffers_1/const_iterator.html +/doc/asio/reference/const_buffers_1/data.html +/doc/asio/reference/const_buffers_1/end.html +/doc/asio/reference/const_buffers_1.html +/doc/asio/reference/const_buffers_1/operator_plus_/ +/doc/asio/reference/const_buffers_1/operator_plus__eq_.html +/doc/asio/reference/const_buffers_1/operator_plus_.html +/doc/asio/reference/const_buffers_1/operator_plus_/overload1.html +/doc/asio/reference/const_buffers_1/operator_plus_/overload2.html +/doc/asio/reference/const_buffers_1/size.html +/doc/asio/reference/const_buffers_1/value_type.html +/doc/asio/reference/ConstBufferSequence.html +/doc/asio/reference/const_buffer/size.html +/doc/asio/reference/coroutine/ +/doc/asio/reference/coroutine/coroutine.html +/doc/asio/reference/coroutine.html +/doc/asio/reference/coroutine/is_child.html +/doc/asio/reference/coroutine/is_complete.html +/doc/asio/reference/coroutine/is_parent.html +/doc/asio/reference/co_spawn/ +/doc/asio/reference/co_spawn.html +/doc/asio/reference/co_spawn/overload1.html +/doc/asio/reference/co_spawn/overload2.html +/doc/asio/reference/co_spawn/overload3.html +/doc/asio/reference/co_spawn/overload4.html +/doc/asio/reference/co_spawn/overload5.html +/doc/asio/reference/co_spawn/overload6.html +/doc/asio/reference/deadline_timer.html +/doc/asio/reference/default_completion_token/ +/doc/asio/reference/default_completion_token.html +/doc/asio/reference/default_completion_token/type.html +/doc/asio/reference/defer/ +/doc/asio/reference/defer.html +/doc/asio/reference/defer/overload1.html +/doc/asio/reference/defer/overload2.html +/doc/asio/reference/defer/overload3.html +/doc/asio/reference/detached.html +/doc/asio/reference/detached_t/ +/doc/asio/reference/detached_t/as_default_on.html +/doc/asio/reference/detached_t/detached_t.html +/doc/asio/reference/detached_t__executor_with_default/ +/doc/asio/reference/detached_t__executor_with_default/default_completion_token_type.html +/doc/asio/reference/detached_t__executor_with_default/executor_with_default/ +/doc/asio/reference/detached_t__executor_with_default/executor_with_default.html +/doc/asio/reference/detached_t__executor_with_default/executor_with_default/overload1.html +/doc/asio/reference/detached_t__executor_with_default/executor_with_default/overload2.html +/doc/asio/reference/detached_t__executor_with_default.html +/doc/asio/reference/detached_t.html +/doc/asio/reference/dispatch/ +/doc/asio/reference/dispatch.html +/doc/asio/reference/dispatch/overload1.html +/doc/asio/reference/dispatch/overload2.html +/doc/asio/reference/dispatch/overload3.html +/doc/asio/reference/dynamic_buffer/ +/doc/asio/reference/DynamicBuffer.html +/doc/asio/reference/dynamic_buffer.html +/doc/asio/reference/dynamic_buffer/overload1.html +/doc/asio/reference/dynamic_buffer/overload2.html +/doc/asio/reference/dynamic_buffer/overload3.html +/doc/asio/reference/dynamic_buffer/overload4.html +/doc/asio/reference/DynamicBuffer_v1.html +/doc/asio/reference/DynamicBuffer_v2.html +/doc/asio/reference/dynamic_string_buffer/ +/doc/asio/reference/dynamic_string_buffer/capacity.html +/doc/asio/reference/dynamic_string_buffer/commit.html +/doc/asio/reference/dynamic_string_buffer/const_buffers_type.html +/doc/asio/reference/dynamic_string_buffer/consume.html +/doc/asio/reference/dynamic_string_buffer/data/ +/doc/asio/reference/dynamic_string_buffer/data.html +/doc/asio/reference/dynamic_string_buffer/data/overload1.html +/doc/asio/reference/dynamic_string_buffer/data/overload2.html +/doc/asio/reference/dynamic_string_buffer/data/overload3.html +/doc/asio/reference/dynamic_string_buffer/dynamic_string_buffer/ +/doc/asio/reference/dynamic_string_buffer/dynamic_string_buffer.html +/doc/asio/reference/dynamic_string_buffer/dynamic_string_buffer/overload1.html +/doc/asio/reference/dynamic_string_buffer/dynamic_string_buffer/overload2.html +/doc/asio/reference/dynamic_string_buffer/dynamic_string_buffer/overload3.html +/doc/asio/reference/dynamic_string_buffer/grow.html +/doc/asio/reference/dynamic_string_buffer.html +/doc/asio/reference/dynamic_string_buffer/max_size.html +/doc/asio/reference/dynamic_string_buffer/mutable_buffers_type.html +/doc/asio/reference/dynamic_string_buffer/prepare.html +/doc/asio/reference/dynamic_string_buffer/shrink.html +/doc/asio/reference/dynamic_string_buffer/size.html +/doc/asio/reference/dynamic_vector_buffer/ +/doc/asio/reference/dynamic_vector_buffer/capacity.html +/doc/asio/reference/dynamic_vector_buffer/commit.html +/doc/asio/reference/dynamic_vector_buffer/const_buffers_type.html +/doc/asio/reference/dynamic_vector_buffer/consume.html +/doc/asio/reference/dynamic_vector_buffer/data/ +/doc/asio/reference/dynamic_vector_buffer/data.html +/doc/asio/reference/dynamic_vector_buffer/data/overload1.html +/doc/asio/reference/dynamic_vector_buffer/data/overload2.html +/doc/asio/reference/dynamic_vector_buffer/data/overload3.html +/doc/asio/reference/dynamic_vector_buffer/dynamic_vector_buffer/ +/doc/asio/reference/dynamic_vector_buffer/dynamic_vector_buffer.html +/doc/asio/reference/dynamic_vector_buffer/dynamic_vector_buffer/overload1.html +/doc/asio/reference/dynamic_vector_buffer/dynamic_vector_buffer/overload2.html +/doc/asio/reference/dynamic_vector_buffer/dynamic_vector_buffer/overload3.html +/doc/asio/reference/dynamic_vector_buffer/grow.html +/doc/asio/reference/dynamic_vector_buffer.html +/doc/asio/reference/dynamic_vector_buffer/max_size.html +/doc/asio/reference/dynamic_vector_buffer/mutable_buffers_type.html +/doc/asio/reference/dynamic_vector_buffer/prepare.html +/doc/asio/reference/dynamic_vector_buffer/shrink.html +/doc/asio/reference/dynamic_vector_buffer/size.html +/doc/asio/reference/Endpoint.html +/doc/asio/reference/EndpointSequence.html +/doc/asio/reference/error__addrinfo_category.html +/doc/asio/reference/error__addrinfo_errors.html +/doc/asio/reference/error__basic_errors.html +/doc/asio/reference/error_category/ +/doc/asio/reference/error_category/_error_category.html +/doc/asio/reference/error_category.html +/doc/asio/reference/error_category/message.html +/doc/asio/reference/error_category/name.html +/doc/asio/reference/error_category/operator_eq__eq_.html +/doc/asio/reference/error_category/operator_not__eq_.html +/doc/asio/reference/error_code/ +/doc/asio/reference/error_code/assign.html +/doc/asio/reference/error_code/category.html +/doc/asio/reference/error_code/clear.html +/doc/asio/reference/error_code/error_code/ +/doc/asio/reference/error_code/error_code.html +/doc/asio/reference/error_code/error_code/overload1.html +/doc/asio/reference/error_code/error_code/overload2.html +/doc/asio/reference/error_code/error_code/overload3.html +/doc/asio/reference/error_code.html +/doc/asio/reference/error_code/message.html +/doc/asio/reference/error_code/operator_eq__eq_.html +/doc/asio/reference/error_code/operator_not__eq_.html +/doc/asio/reference/error_code/operator_not_.html +/doc/asio/reference/error_code/operator_unspecified_bool_type.html +/doc/asio/reference/error_code/unspecified_bool_true.html +/doc/asio/reference/error_code/unspecified_bool_type.html +/doc/asio/reference/error_code__unspecified_bool_type_t.html +/doc/asio/reference/error_code/value.html +/doc/asio/reference/error__get_addrinfo_category.html +/doc/asio/reference/error__get_misc_category.html +/doc/asio/reference/error__get_netdb_category.html +/doc/asio/reference/error__get_ssl_category.html +/doc/asio/reference/error__get_system_category.html +/doc/asio/reference/error__make_error_code/ +/doc/asio/reference/error__make_error_code.html +/doc/asio/reference/error__make_error_code/overload1.html +/doc/asio/reference/error__make_error_code/overload2.html +/doc/asio/reference/error__make_error_code/overload3.html +/doc/asio/reference/error__make_error_code/overload4.html +/doc/asio/reference/error__make_error_code/overload5.html +/doc/asio/reference/error__misc_category.html +/doc/asio/reference/error__misc_errors.html +/doc/asio/reference/error__netdb_category.html +/doc/asio/reference/error__netdb_errors.html +/doc/asio/reference/error__ssl_category.html +/doc/asio/reference/error__ssl_errors.html +/doc/asio/reference/error__system_category.html +/doc/asio/reference/execution__allocator.html +/doc/asio/reference/execution__allocator_t/ +/doc/asio/reference/execution__allocator_t/allocator_t.html +/doc/asio/reference/execution__allocator_t.html +/doc/asio/reference/execution__allocator_t/is_applicable_property_v.html +/doc/asio/reference/execution__allocator_t/is_preferable.html +/doc/asio/reference/execution__allocator_t/is_requirable.html +/doc/asio/reference/execution__allocator_t/value.html +/doc/asio/reference/execution__any_executor/ +/doc/asio/reference/execution__any_executor/any_executor/ +/doc/asio/reference/execution__any_executor/_any_executor.html +/doc/asio/reference/execution__any_executor/any_executor.html +/doc/asio/reference/execution__any_executor/any_executor/overload1.html +/doc/asio/reference/execution__any_executor/any_executor/overload2.html +/doc/asio/reference/execution__any_executor/any_executor/overload3.html +/doc/asio/reference/execution__any_executor/any_executor/overload4.html +/doc/asio/reference/execution__any_executor/any_executor/overload5.html +/doc/asio/reference/execution__any_executor/any_executor/overload6.html +/doc/asio/reference/execution__any_executor/context.html +/doc/asio/reference/execution__any_executor/execute.html +/doc/asio/reference/execution__any_executor.html +/doc/asio/reference/execution__any_executor/operator_bool.html +/doc/asio/reference/execution__any_executor/operator_eq_/ +/doc/asio/reference/execution__any_executor/operator_eq__eq_/ +/doc/asio/reference/execution__any_executor/operator_eq__eq_.html +/doc/asio/reference/execution__any_executor/operator_eq__eq_/overload1.html +/doc/asio/reference/execution__any_executor/operator_eq__eq_/overload2.html +/doc/asio/reference/execution__any_executor/operator_eq__eq_/overload3.html +/doc/asio/reference/execution__any_executor/operator_eq_.html +/doc/asio/reference/execution__any_executor/operator_eq_/overload1.html +/doc/asio/reference/execution__any_executor/operator_eq_/overload2.html +/doc/asio/reference/execution__any_executor/operator_eq_/overload3.html +/doc/asio/reference/execution__any_executor/operator_eq_/overload4.html +/doc/asio/reference/execution__any_executor/operator_not__eq_/ +/doc/asio/reference/execution__any_executor/operator_not__eq_.html +/doc/asio/reference/execution__any_executor/operator_not__eq_/overload1.html +/doc/asio/reference/execution__any_executor/operator_not__eq_/overload2.html +/doc/asio/reference/execution__any_executor/operator_not__eq_/overload3.html +/doc/asio/reference/execution__any_executor/prefer.html +/doc/asio/reference/execution__any_executor/query.html +/doc/asio/reference/execution__any_executor/require.html +/doc/asio/reference/execution__any_executor/swap.html +/doc/asio/reference/execution__any_executor/target/ +/doc/asio/reference/execution__any_executor/target.html +/doc/asio/reference/execution__any_executor/target/overload1.html +/doc/asio/reference/execution__any_executor/target/overload2.html +/doc/asio/reference/execution__any_executor/target_type.html +/doc/asio/reference/execution__bad_executor/ +/doc/asio/reference/execution__bad_executor/bad_executor.html +/doc/asio/reference/execution__bad_executor.html +/doc/asio/reference/execution__bad_executor/what.html +/doc/asio/reference/execution__blocking_adaptation.html +/doc/asio/reference/execution__blocking_adaptation_t/ +/doc/asio/reference/execution__blocking_adaptation_t/allowed.html +/doc/asio/reference/execution__blocking_adaptation_t__allowed_t/ +/doc/asio/reference/execution__blocking_adaptation_t__allowed_t/allowed_t.html +/doc/asio/reference/execution__blocking_adaptation_t__allowed_t.html +/doc/asio/reference/execution__blocking_adaptation_t__allowed_t/is_applicable_property_v.html +/doc/asio/reference/execution__blocking_adaptation_t__allowed_t/is_preferable.html +/doc/asio/reference/execution__blocking_adaptation_t__allowed_t/is_requirable.html +/doc/asio/reference/execution__blocking_adaptation_t__allowed_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__blocking_adaptation_t__allowed_t/value.html +/doc/asio/reference/execution__blocking_adaptation_t/blocking_adaptation_t/ +/doc/asio/reference/execution__blocking_adaptation_t/blocking_adaptation_t.html +/doc/asio/reference/execution__blocking_adaptation_t/blocking_adaptation_t/overload1.html +/doc/asio/reference/execution__blocking_adaptation_t/blocking_adaptation_t/overload2.html +/doc/asio/reference/execution__blocking_adaptation_t/blocking_adaptation_t/overload3.html +/doc/asio/reference/execution__blocking_adaptation_t/disallowed.html +/doc/asio/reference/execution__blocking_adaptation_t__disallowed_t/ +/doc/asio/reference/execution__blocking_adaptation_t__disallowed_t/disallowed_t.html +/doc/asio/reference/execution__blocking_adaptation_t__disallowed_t.html +/doc/asio/reference/execution__blocking_adaptation_t__disallowed_t/is_applicable_property_v.html +/doc/asio/reference/execution__blocking_adaptation_t__disallowed_t/is_preferable.html +/doc/asio/reference/execution__blocking_adaptation_t__disallowed_t/is_requirable.html +/doc/asio/reference/execution__blocking_adaptation_t__disallowed_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__blocking_adaptation_t__disallowed_t/value.html +/doc/asio/reference/execution__blocking_adaptation_t.html +/doc/asio/reference/execution__blocking_adaptation_t/is_applicable_property_v.html +/doc/asio/reference/execution__blocking_adaptation_t/is_preferable.html +/doc/asio/reference/execution__blocking_adaptation_t/is_requirable.html +/doc/asio/reference/execution__blocking_adaptation_t/operator_eq__eq_.html +/doc/asio/reference/execution__blocking_adaptation_t/operator_not__eq_.html +/doc/asio/reference/execution__blocking_adaptation_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__blocking.html +/doc/asio/reference/execution__blocking_t/ +/doc/asio/reference/execution__blocking_t/always.html +/doc/asio/reference/execution__blocking_t__always_t/ +/doc/asio/reference/execution__blocking_t__always_t/always_t.html +/doc/asio/reference/execution__blocking_t__always_t.html +/doc/asio/reference/execution__blocking_t__always_t/is_applicable_property_v.html +/doc/asio/reference/execution__blocking_t__always_t/is_preferable.html +/doc/asio/reference/execution__blocking_t__always_t/is_requirable.html +/doc/asio/reference/execution__blocking_t__always_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__blocking_t__always_t/value.html +/doc/asio/reference/execution__blocking_t/blocking_t/ +/doc/asio/reference/execution__blocking_t/blocking_t.html +/doc/asio/reference/execution__blocking_t/blocking_t/overload1.html +/doc/asio/reference/execution__blocking_t/blocking_t/overload2.html +/doc/asio/reference/execution__blocking_t/blocking_t/overload3.html +/doc/asio/reference/execution__blocking_t/blocking_t/overload4.html +/doc/asio/reference/execution__blocking_t.html +/doc/asio/reference/execution__blocking_t/is_applicable_property_v.html +/doc/asio/reference/execution__blocking_t/is_preferable.html +/doc/asio/reference/execution__blocking_t/is_requirable.html +/doc/asio/reference/execution__blocking_t/never.html +/doc/asio/reference/execution__blocking_t__never_t/ +/doc/asio/reference/execution__blocking_t__never_t.html +/doc/asio/reference/execution__blocking_t__never_t/is_applicable_property_v.html +/doc/asio/reference/execution__blocking_t__never_t/is_preferable.html +/doc/asio/reference/execution__blocking_t__never_t/is_requirable.html +/doc/asio/reference/execution__blocking_t__never_t/never_t.html +/doc/asio/reference/execution__blocking_t__never_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__blocking_t__never_t/value.html +/doc/asio/reference/execution__blocking_t/operator_eq__eq_.html +/doc/asio/reference/execution__blocking_t/operator_not__eq_.html +/doc/asio/reference/execution__blocking_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__blocking_t/possibly.html +/doc/asio/reference/execution__blocking_t__possibly_t/ +/doc/asio/reference/execution__blocking_t__possibly_t.html +/doc/asio/reference/execution__blocking_t__possibly_t/is_applicable_property_v.html +/doc/asio/reference/execution__blocking_t__possibly_t/is_preferable.html +/doc/asio/reference/execution__blocking_t__possibly_t/is_requirable.html +/doc/asio/reference/execution__blocking_t__possibly_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__blocking_t__possibly_t/possibly_t.html +/doc/asio/reference/execution__blocking_t__possibly_t/value.html +/doc/asio/reference/execution__bulk_execute.html +/doc/asio/reference/execution__bulk_guarantee.html +/doc/asio/reference/execution__bulk_guarantee_t/ +/doc/asio/reference/execution__bulk_guarantee_t/bulk_guarantee_t/ +/doc/asio/reference/execution__bulk_guarantee_t/bulk_guarantee_t.html +/doc/asio/reference/execution__bulk_guarantee_t/bulk_guarantee_t/overload1.html +/doc/asio/reference/execution__bulk_guarantee_t/bulk_guarantee_t/overload2.html +/doc/asio/reference/execution__bulk_guarantee_t/bulk_guarantee_t/overload3.html +/doc/asio/reference/execution__bulk_guarantee_t/bulk_guarantee_t/overload4.html +/doc/asio/reference/execution__bulk_guarantee_t.html +/doc/asio/reference/execution__bulk_guarantee_t/is_applicable_property_v.html +/doc/asio/reference/execution__bulk_guarantee_t/is_preferable.html +/doc/asio/reference/execution__bulk_guarantee_t/is_requirable.html +/doc/asio/reference/execution__bulk_guarantee_t/operator_eq__eq_.html +/doc/asio/reference/execution__bulk_guarantee_t/operator_not__eq_.html +/doc/asio/reference/execution__bulk_guarantee_t/parallel.html +/doc/asio/reference/execution__bulk_guarantee_t__parallel_t/ +/doc/asio/reference/execution__bulk_guarantee_t__parallel_t.html +/doc/asio/reference/execution__bulk_guarantee_t__parallel_t/is_applicable_property_v.html +/doc/asio/reference/execution__bulk_guarantee_t__parallel_t/is_preferable.html +/doc/asio/reference/execution__bulk_guarantee_t__parallel_t/is_requirable.html +/doc/asio/reference/execution__bulk_guarantee_t__parallel_t/parallel_t.html +/doc/asio/reference/execution__bulk_guarantee_t__parallel_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__bulk_guarantee_t__parallel_t/value.html +/doc/asio/reference/execution__bulk_guarantee_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__bulk_guarantee_t/sequenced.html +/doc/asio/reference/execution__bulk_guarantee_t__sequenced_t/ +/doc/asio/reference/execution__bulk_guarantee_t__sequenced_t.html +/doc/asio/reference/execution__bulk_guarantee_t__sequenced_t/is_applicable_property_v.html +/doc/asio/reference/execution__bulk_guarantee_t__sequenced_t/is_preferable.html +/doc/asio/reference/execution__bulk_guarantee_t__sequenced_t/is_requirable.html +/doc/asio/reference/execution__bulk_guarantee_t__sequenced_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__bulk_guarantee_t__sequenced_t/sequenced_t.html +/doc/asio/reference/execution__bulk_guarantee_t__sequenced_t/value.html +/doc/asio/reference/execution__bulk_guarantee_t/unsequenced.html +/doc/asio/reference/execution__bulk_guarantee_t__unsequenced_t/ +/doc/asio/reference/execution__bulk_guarantee_t__unsequenced_t.html +/doc/asio/reference/execution__bulk_guarantee_t__unsequenced_t/is_applicable_property_v.html +/doc/asio/reference/execution__bulk_guarantee_t__unsequenced_t/is_preferable.html +/doc/asio/reference/execution__bulk_guarantee_t__unsequenced_t/is_requirable.html +/doc/asio/reference/execution__bulk_guarantee_t__unsequenced_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__bulk_guarantee_t__unsequenced_t/unsequenced_t.html +/doc/asio/reference/execution__bulk_guarantee_t__unsequenced_t/value.html +/doc/asio/reference/execution__can_bulk_execute.html +/doc/asio/reference/execution__can_connect.html +/doc/asio/reference/execution__can_execute.html +/doc/asio/reference/execution__can_schedule.html +/doc/asio/reference/execution__can_set_done.html +/doc/asio/reference/execution__can_set_error.html +/doc/asio/reference/execution__can_set_value.html +/doc/asio/reference/execution__can_start.html +/doc/asio/reference/execution__can_submit.html +/doc/asio/reference/execution__connect.html +/doc/asio/reference/execution__connect_result/ +/doc/asio/reference/execution__connect_result.html +/doc/asio/reference/execution__connect_result/type.html +/doc/asio/reference/execution_context/ +/doc/asio/reference/execution_context/add_service.html +/doc/asio/reference/execution__context_as.html +/doc/asio/reference/execution__context_as_t/ +/doc/asio/reference/execution__context_as_t.html +/doc/asio/reference/execution__context_as_t/is_applicable_property_v.html +/doc/asio/reference/execution__context_as_t/is_preferable.html +/doc/asio/reference/execution__context_as_t/is_requirable.html +/doc/asio/reference/execution__context_as_t/polymorphic_query_result_type.html +/doc/asio/reference/execution_context/destroy.html +/doc/asio/reference/execution_context/_execution_context.html +/doc/asio/reference/execution_context/execution_context.html +/doc/asio/reference/execution_context/fork_event.html +/doc/asio/reference/execution_context/has_service.html +/doc/asio/reference/ExecutionContext.html +/doc/asio/reference/execution__context.html +/doc/asio/reference/execution_context.html +/doc/asio/reference/execution_context__id/ +/doc/asio/reference/execution_context__id.html +/doc/asio/reference/execution_context__id/id.html +/doc/asio/reference/execution_context/make_service.html +/doc/asio/reference/execution_context/notify_fork.html +/doc/asio/reference/execution_context__service/ +/doc/asio/reference/execution_context__service/context.html +/doc/asio/reference/execution_context__service.html +/doc/asio/reference/execution_context__service/notify_fork.html +/doc/asio/reference/execution_context__service/_service.html +/doc/asio/reference/execution_context__service/service.html +/doc/asio/reference/execution_context__service/shutdown.html +/doc/asio/reference/execution_context/shutdown.html +/doc/asio/reference/execution__context_t/ +/doc/asio/reference/execution__context_t.html +/doc/asio/reference/execution__context_t/is_applicable_property_v.html +/doc/asio/reference/execution__context_t/is_preferable.html +/doc/asio/reference/execution__context_t/is_requirable.html +/doc/asio/reference/execution__context_t/polymorphic_query_result_type.html +/doc/asio/reference/execution_context/use_service/ +/doc/asio/reference/execution_context/use_service.html +/doc/asio/reference/execution_context/use_service/overload1.html +/doc/asio/reference/execution_context/use_service/overload2.html +/doc/asio/reference/execution__execute.html +/doc/asio/reference/execution__executor_index/ +/doc/asio/reference/execution__executor_index.html +/doc/asio/reference/execution__executor_index/type.html +/doc/asio/reference/execution__executor_shape/ +/doc/asio/reference/execution__executor_shape.html +/doc/asio/reference/execution__executor_shape/type.html +/doc/asio/reference/execution__invocable_archetype/ +/doc/asio/reference/execution__invocable_archetype.html +/doc/asio/reference/execution__invocable_archetype/operator_lp__rp_.html +/doc/asio/reference/execution__is_executor.html +/doc/asio/reference/execution__is_executor_of.html +/doc/asio/reference/execution__is_nothrow_receiver_of.html +/doc/asio/reference/execution__is_operation_state.html +/doc/asio/reference/execution__is_receiver.html +/doc/asio/reference/execution__is_receiver_of.html +/doc/asio/reference/execution__is_scheduler.html +/doc/asio/reference/execution__is_sender.html +/doc/asio/reference/execution__is_sender_to.html +/doc/asio/reference/execution__is_typed_sender.html +/doc/asio/reference/execution__mapping.html +/doc/asio/reference/execution__mapping_t/ +/doc/asio/reference/execution__mapping_t.html +/doc/asio/reference/execution__mapping_t/is_applicable_property_v.html +/doc/asio/reference/execution__mapping_t/is_preferable.html +/doc/asio/reference/execution__mapping_t/is_requirable.html +/doc/asio/reference/execution__mapping_t/mapping_t/ +/doc/asio/reference/execution__mapping_t/mapping_t.html +/doc/asio/reference/execution__mapping_t/mapping_t/overload1.html +/doc/asio/reference/execution__mapping_t/mapping_t/overload2.html +/doc/asio/reference/execution__mapping_t/mapping_t/overload3.html +/doc/asio/reference/execution__mapping_t/mapping_t/overload4.html +/doc/asio/reference/execution__mapping_t/new_thread.html +/doc/asio/reference/execution__mapping_t__new_thread_t/ +/doc/asio/reference/execution__mapping_t__new_thread_t.html +/doc/asio/reference/execution__mapping_t__new_thread_t/is_applicable_property_v.html +/doc/asio/reference/execution__mapping_t__new_thread_t/is_preferable.html +/doc/asio/reference/execution__mapping_t__new_thread_t/is_requirable.html +/doc/asio/reference/execution__mapping_t__new_thread_t/new_thread_t.html +/doc/asio/reference/execution__mapping_t__new_thread_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__mapping_t__new_thread_t/value.html +/doc/asio/reference/execution__mapping_t/operator_eq__eq_.html +/doc/asio/reference/execution__mapping_t/operator_not__eq_.html +/doc/asio/reference/execution__mapping_t/other.html +/doc/asio/reference/execution__mapping_t__other_t/ +/doc/asio/reference/execution__mapping_t__other_t.html +/doc/asio/reference/execution__mapping_t__other_t/is_applicable_property_v.html +/doc/asio/reference/execution__mapping_t__other_t/is_preferable.html +/doc/asio/reference/execution__mapping_t__other_t/is_requirable.html +/doc/asio/reference/execution__mapping_t__other_t/other_t.html +/doc/asio/reference/execution__mapping_t__other_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__mapping_t__other_t/value.html +/doc/asio/reference/execution__mapping_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__mapping_t/thread.html +/doc/asio/reference/execution__mapping_t__thread_t/ +/doc/asio/reference/execution__mapping_t__thread_t.html +/doc/asio/reference/execution__mapping_t__thread_t/is_applicable_property_v.html +/doc/asio/reference/execution__mapping_t__thread_t/is_preferable.html +/doc/asio/reference/execution__mapping_t__thread_t/is_requirable.html +/doc/asio/reference/execution__mapping_t__thread_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__mapping_t__thread_t/thread_t.html +/doc/asio/reference/execution__mapping_t__thread_t/value.html +/doc/asio/reference/execution__occupancy.html +/doc/asio/reference/execution__occupancy_t/ +/doc/asio/reference/execution__occupancy_t.html +/doc/asio/reference/execution__occupancy_t/is_applicable_property_v.html +/doc/asio/reference/execution__occupancy_t/is_preferable.html +/doc/asio/reference/execution__occupancy_t/is_requirable.html +/doc/asio/reference/execution__occupancy_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__outstanding_work.html +/doc/asio/reference/execution__outstanding_work_t/ +/doc/asio/reference/execution__outstanding_work_t.html +/doc/asio/reference/execution__outstanding_work_t/is_applicable_property_v.html +/doc/asio/reference/execution__outstanding_work_t/is_preferable.html +/doc/asio/reference/execution__outstanding_work_t/is_requirable.html +/doc/asio/reference/execution__outstanding_work_t/operator_eq__eq_.html +/doc/asio/reference/execution__outstanding_work_t/operator_not__eq_.html +/doc/asio/reference/execution__outstanding_work_t/outstanding_work_t/ +/doc/asio/reference/execution__outstanding_work_t/outstanding_work_t.html +/doc/asio/reference/execution__outstanding_work_t/outstanding_work_t/overload1.html +/doc/asio/reference/execution__outstanding_work_t/outstanding_work_t/overload2.html +/doc/asio/reference/execution__outstanding_work_t/outstanding_work_t/overload3.html +/doc/asio/reference/execution__outstanding_work_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__outstanding_work_t/tracked.html +/doc/asio/reference/execution__outstanding_work_t__tracked_t/ +/doc/asio/reference/execution__outstanding_work_t__tracked_t.html +/doc/asio/reference/execution__outstanding_work_t__tracked_t/is_applicable_property_v.html +/doc/asio/reference/execution__outstanding_work_t__tracked_t/is_preferable.html +/doc/asio/reference/execution__outstanding_work_t__tracked_t/is_requirable.html +/doc/asio/reference/execution__outstanding_work_t__tracked_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__outstanding_work_t__tracked_t/tracked_t.html +/doc/asio/reference/execution__outstanding_work_t__tracked_t/value.html +/doc/asio/reference/execution__outstanding_work_t/untracked.html +/doc/asio/reference/execution__outstanding_work_t__untracked_t/ +/doc/asio/reference/execution__outstanding_work_t__untracked_t.html +/doc/asio/reference/execution__outstanding_work_t__untracked_t/is_applicable_property_v.html +/doc/asio/reference/execution__outstanding_work_t__untracked_t/is_preferable.html +/doc/asio/reference/execution__outstanding_work_t__untracked_t/is_requirable.html +/doc/asio/reference/execution__outstanding_work_t__untracked_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__outstanding_work_t__untracked_t/untracked_t.html +/doc/asio/reference/execution__outstanding_work_t__untracked_t/value.html +/doc/asio/reference/execution__prefer_only/ +/doc/asio/reference/execution__prefer_only.html +/doc/asio/reference/execution__prefer_only/is_applicable_property_v.html +/doc/asio/reference/execution__prefer_only/is_preferable.html +/doc/asio/reference/execution__prefer_only/is_requirable.html +/doc/asio/reference/execution__prefer_only/polymorphic_query_result_type.html +/doc/asio/reference/execution__receiver_invocation_error/ +/doc/asio/reference/execution__receiver_invocation_error.html +/doc/asio/reference/execution__receiver_invocation_error/receiver_invocation_error.html +/doc/asio/reference/execution__relationship.html +/doc/asio/reference/execution__relationship_t/ +/doc/asio/reference/execution__relationship_t/continuation.html +/doc/asio/reference/execution__relationship_t__continuation_t/ +/doc/asio/reference/execution__relationship_t__continuation_t/continuation_t.html +/doc/asio/reference/execution__relationship_t__continuation_t.html +/doc/asio/reference/execution__relationship_t__continuation_t/is_applicable_property_v.html +/doc/asio/reference/execution__relationship_t__continuation_t/is_preferable.html +/doc/asio/reference/execution__relationship_t__continuation_t/is_requirable.html +/doc/asio/reference/execution__relationship_t__continuation_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__relationship_t__continuation_t/value.html +/doc/asio/reference/execution__relationship_t/fork.html +/doc/asio/reference/execution__relationship_t__fork_t/ +/doc/asio/reference/execution__relationship_t__fork_t/fork_t.html +/doc/asio/reference/execution__relationship_t__fork_t.html +/doc/asio/reference/execution__relationship_t__fork_t/is_applicable_property_v.html +/doc/asio/reference/execution__relationship_t__fork_t/is_preferable.html +/doc/asio/reference/execution__relationship_t__fork_t/is_requirable.html +/doc/asio/reference/execution__relationship_t__fork_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__relationship_t__fork_t/value.html +/doc/asio/reference/execution__relationship_t.html +/doc/asio/reference/execution__relationship_t/is_applicable_property_v.html +/doc/asio/reference/execution__relationship_t/is_preferable.html +/doc/asio/reference/execution__relationship_t/is_requirable.html +/doc/asio/reference/execution__relationship_t/operator_eq__eq_.html +/doc/asio/reference/execution__relationship_t/operator_not__eq_.html +/doc/asio/reference/execution__relationship_t/polymorphic_query_result_type.html +/doc/asio/reference/execution__relationship_t/relationship_t/ +/doc/asio/reference/execution__relationship_t/relationship_t.html +/doc/asio/reference/execution__relationship_t/relationship_t/overload1.html +/doc/asio/reference/execution__relationship_t/relationship_t/overload2.html +/doc/asio/reference/execution__relationship_t/relationship_t/overload3.html +/doc/asio/reference/execution__schedule.html +/doc/asio/reference/execution__sender_base.html +/doc/asio/reference/execution__sender_traits.html +/doc/asio/reference/execution__set_done.html +/doc/asio/reference/execution__set_error.html +/doc/asio/reference/execution__set_value.html +/doc/asio/reference/execution__start.html +/doc/asio/reference/execution__submit.html +/doc/asio/reference/executor/ +/doc/asio/reference/Executor1.html +/doc/asio/reference/executor_arg.html +/doc/asio/reference/executor_arg_t/ +/doc/asio/reference/executor_arg_t/executor_arg_t.html +/doc/asio/reference/executor_arg_t.html +/doc/asio/reference/executor_binder/ +/doc/asio/reference/executor_binder/argument_type.html +/doc/asio/reference/executor_binder/executor_binder/ +/doc/asio/reference/executor_binder/_executor_binder.html +/doc/asio/reference/executor_binder/executor_binder.html +/doc/asio/reference/executor_binder/executor_binder/overload1.html +/doc/asio/reference/executor_binder/executor_binder/overload2.html +/doc/asio/reference/executor_binder/executor_binder/overload3.html +/doc/asio/reference/executor_binder/executor_binder/overload4.html +/doc/asio/reference/executor_binder/executor_binder/overload5.html +/doc/asio/reference/executor_binder/executor_binder/overload6.html +/doc/asio/reference/executor_binder/executor_binder/overload7.html +/doc/asio/reference/executor_binder/executor_binder/overload8.html +/doc/asio/reference/executor_binder/executor_binder/overload9.html +/doc/asio/reference/executor_binder/executor_type.html +/doc/asio/reference/executor_binder/first_argument_type.html +/doc/asio/reference/executor_binder/get/ +/doc/asio/reference/executor_binder/get_executor.html +/doc/asio/reference/executor_binder/get.html +/doc/asio/reference/executor_binder/get/overload1.html +/doc/asio/reference/executor_binder/get/overload2.html +/doc/asio/reference/executor_binder.html +/doc/asio/reference/executor_binder/operator_lp__rp_/ +/doc/asio/reference/executor_binder/operator_lp__rp_.html +/doc/asio/reference/executor_binder/operator_lp__rp_/overload1.html +/doc/asio/reference/executor_binder/operator_lp__rp_/overload2.html +/doc/asio/reference/executor_binder/result_type.html +/doc/asio/reference/executor_binder/second_argument_type.html +/doc/asio/reference/executor_binder/target_type.html +/doc/asio/reference/executor/context.html +/doc/asio/reference/executor/defer.html +/doc/asio/reference/executor/dispatch.html +/doc/asio/reference/executor/executor/ +/doc/asio/reference/executor/_executor.html +/doc/asio/reference/executor/executor.html +/doc/asio/reference/executor/executor/overload1.html +/doc/asio/reference/executor/executor/overload2.html +/doc/asio/reference/executor/executor/overload3.html +/doc/asio/reference/executor/executor/overload4.html +/doc/asio/reference/executor/executor/overload5.html +/doc/asio/reference/executor/executor/overload6.html +/doc/asio/reference/executor.html +/doc/asio/reference/executor/on_work_finished.html +/doc/asio/reference/executor/on_work_started.html +/doc/asio/reference/executor/operator_eq_/ +/doc/asio/reference/executor/operator_eq__eq_.html +/doc/asio/reference/executor/operator_eq_.html +/doc/asio/reference/executor/operator_eq_/overload1.html +/doc/asio/reference/executor/operator_eq_/overload2.html +/doc/asio/reference/executor/operator_eq_/overload3.html +/doc/asio/reference/executor/operator_eq_/overload4.html +/doc/asio/reference/executor/operator_not__eq_.html +/doc/asio/reference/executor/operator_unspecified_bool_type.html +/doc/asio/reference/executor/post.html +/doc/asio/reference/executor/target/ +/doc/asio/reference/executor/target.html +/doc/asio/reference/executor/target/overload1.html +/doc/asio/reference/executor/target/overload2.html +/doc/asio/reference/executor/target_type.html +/doc/asio/reference/executor/unspecified_bool_true.html +/doc/asio/reference/executor/unspecified_bool_type.html +/doc/asio/reference/executor__unspecified_bool_type_t.html +/doc/asio/reference/executor_work_guard/ +/doc/asio/reference/executor_work_guard/executor_type.html +/doc/asio/reference/executor_work_guard/executor_work_guard/ +/doc/asio/reference/executor_work_guard/_executor_work_guard.html +/doc/asio/reference/executor_work_guard/executor_work_guard.html +/doc/asio/reference/executor_work_guard/executor_work_guard/overload1.html +/doc/asio/reference/executor_work_guard/executor_work_guard/overload2.html +/doc/asio/reference/executor_work_guard/executor_work_guard/overload3.html +/doc/asio/reference/executor_work_guard/get_executor.html +/doc/asio/reference/executor_work_guard.html +/doc/asio/reference/executor_work_guard/owns_work.html +/doc/asio/reference/executor_work_guard/reset.html +/doc/asio/reference/generic__basic_endpoint/ +/doc/asio/reference/generic__basic_endpoint/basic_endpoint/ +/doc/asio/reference/generic__basic_endpoint/basic_endpoint.html +/doc/asio/reference/generic__basic_endpoint/basic_endpoint/overload1.html +/doc/asio/reference/generic__basic_endpoint/basic_endpoint/overload2.html +/doc/asio/reference/generic__basic_endpoint/basic_endpoint/overload3.html +/doc/asio/reference/generic__basic_endpoint/basic_endpoint/overload4.html +/doc/asio/reference/generic__basic_endpoint/capacity.html +/doc/asio/reference/generic__basic_endpoint/data/ +/doc/asio/reference/generic__basic_endpoint/data.html +/doc/asio/reference/generic__basic_endpoint/data/overload1.html +/doc/asio/reference/generic__basic_endpoint/data/overload2.html +/doc/asio/reference/generic__basic_endpoint/data_type.html +/doc/asio/reference/generic__basic_endpoint.html +/doc/asio/reference/generic__basic_endpoint/operator_eq__eq_.html +/doc/asio/reference/generic__basic_endpoint/operator_eq_.html +/doc/asio/reference/generic__basic_endpoint/operator_gt__eq_.html +/doc/asio/reference/generic__basic_endpoint/operator_gt_.html +/doc/asio/reference/generic__basic_endpoint/operator_lt__eq_.html +/doc/asio/reference/generic__basic_endpoint/operator_lt_.html +/doc/asio/reference/generic__basic_endpoint/operator_not__eq_.html +/doc/asio/reference/generic__basic_endpoint/protocol.html +/doc/asio/reference/generic__basic_endpoint/protocol_type.html +/doc/asio/reference/generic__basic_endpoint/resize.html +/doc/asio/reference/generic__basic_endpoint/size.html +/doc/asio/reference/generic__datagram_protocol/ +/doc/asio/reference/generic__datagram_protocol/datagram_protocol/ +/doc/asio/reference/generic__datagram_protocol/datagram_protocol.html +/doc/asio/reference/generic__datagram_protocol/datagram_protocol/overload1.html +/doc/asio/reference/generic__datagram_protocol/datagram_protocol/overload2.html +/doc/asio/reference/generic__datagram_protocol/endpoint.html +/doc/asio/reference/generic__datagram_protocol/family.html +/doc/asio/reference/generic__datagram_protocol.html +/doc/asio/reference/generic__datagram_protocol/operator_eq__eq_.html +/doc/asio/reference/generic__datagram_protocol/operator_not__eq_.html +/doc/asio/reference/generic__datagram_protocol/protocol.html +/doc/asio/reference/generic__datagram_protocol/socket.html +/doc/asio/reference/generic__datagram_protocol/type.html +/doc/asio/reference/generic__raw_protocol/ +/doc/asio/reference/generic__raw_protocol/endpoint.html +/doc/asio/reference/generic__raw_protocol/family.html +/doc/asio/reference/generic__raw_protocol.html +/doc/asio/reference/generic__raw_protocol/operator_eq__eq_.html +/doc/asio/reference/generic__raw_protocol/operator_not__eq_.html +/doc/asio/reference/generic__raw_protocol/protocol.html +/doc/asio/reference/generic__raw_protocol/raw_protocol/ +/doc/asio/reference/generic__raw_protocol/raw_protocol.html +/doc/asio/reference/generic__raw_protocol/raw_protocol/overload1.html +/doc/asio/reference/generic__raw_protocol/raw_protocol/overload2.html +/doc/asio/reference/generic__raw_protocol/socket.html +/doc/asio/reference/generic__raw_protocol/type.html +/doc/asio/reference/generic__seq_packet_protocol/ +/doc/asio/reference/generic__seq_packet_protocol/endpoint.html +/doc/asio/reference/generic__seq_packet_protocol/family.html +/doc/asio/reference/generic__seq_packet_protocol.html +/doc/asio/reference/generic__seq_packet_protocol/operator_eq__eq_.html +/doc/asio/reference/generic__seq_packet_protocol/operator_not__eq_.html +/doc/asio/reference/generic__seq_packet_protocol/protocol.html +/doc/asio/reference/generic__seq_packet_protocol/seq_packet_protocol/ +/doc/asio/reference/generic__seq_packet_protocol/seq_packet_protocol.html +/doc/asio/reference/generic__seq_packet_protocol/seq_packet_protocol/overload1.html +/doc/asio/reference/generic__seq_packet_protocol/seq_packet_protocol/overload2.html +/doc/asio/reference/generic__seq_packet_protocol/socket.html +/doc/asio/reference/generic__seq_packet_protocol/type.html +/doc/asio/reference/generic__stream_protocol/ +/doc/asio/reference/generic__stream_protocol/endpoint.html +/doc/asio/reference/generic__stream_protocol/family.html +/doc/asio/reference/generic__stream_protocol.html +/doc/asio/reference/generic__stream_protocol/iostream.html +/doc/asio/reference/generic__stream_protocol/operator_eq__eq_.html +/doc/asio/reference/generic__stream_protocol/operator_not__eq_.html +/doc/asio/reference/generic__stream_protocol/protocol.html +/doc/asio/reference/generic__stream_protocol/socket.html +/doc/asio/reference/generic__stream_protocol/stream_protocol/ +/doc/asio/reference/generic__stream_protocol/stream_protocol.html +/doc/asio/reference/generic__stream_protocol/stream_protocol/overload1.html +/doc/asio/reference/generic__stream_protocol/stream_protocol/overload2.html +/doc/asio/reference/generic__stream_protocol/type.html +/doc/asio/reference/get_associated_allocator/ +/doc/asio/reference/get_associated_allocator.html +/doc/asio/reference/get_associated_allocator/overload1.html +/doc/asio/reference/get_associated_allocator/overload2.html +/doc/asio/reference/get_associated_executor/ +/doc/asio/reference/get_associated_executor.html +/doc/asio/reference/get_associated_executor/overload1.html +/doc/asio/reference/get_associated_executor/overload2.html +/doc/asio/reference/get_associated_executor/overload3.html +/doc/asio/reference/GettableSerialPortOption.html +/doc/asio/reference/GettableSocketOption.html +/doc/asio/reference/Handler.html +/doc/asio/reference/HandshakeHandler.html +/doc/asio/reference/high_resolution_timer.html +/doc/asio/reference.html +/doc/asio/reference/InternetProtocol.html +/doc/asio/reference/invalid_service_owner/ +/doc/asio/reference/invalid_service_owner.html +/doc/asio/reference/invalid_service_owner/invalid_service_owner.html +/doc/asio/reference/io_context/ +/doc/asio/reference/io_context/add_service.html +/doc/asio/reference/io_context__basic_executor_type/ +/doc/asio/reference/io_context__basic_executor_type/basic_executor_type/ +/doc/asio/reference/io_context__basic_executor_type/_basic_executor_type.html +/doc/asio/reference/io_context__basic_executor_type/basic_executor_type.html +/doc/asio/reference/io_context__basic_executor_type/basic_executor_type/overload1.html +/doc/asio/reference/io_context__basic_executor_type/basic_executor_type/overload2.html +/doc/asio/reference/io_context__basic_executor_type/context.html +/doc/asio/reference/io_context__basic_executor_type/defer.html +/doc/asio/reference/io_context__basic_executor_type/dispatch.html +/doc/asio/reference/io_context__basic_executor_type/execute.html +/doc/asio/reference/io_context__basic_executor_type.html +/doc/asio/reference/io_context__basic_executor_type/on_work_finished.html +/doc/asio/reference/io_context__basic_executor_type/on_work_started.html +/doc/asio/reference/io_context__basic_executor_type/operator_eq_/ +/doc/asio/reference/io_context__basic_executor_type/operator_eq__eq_.html +/doc/asio/reference/io_context__basic_executor_type/operator_eq_.html +/doc/asio/reference/io_context__basic_executor_type/operator_eq_/overload1.html +/doc/asio/reference/io_context__basic_executor_type/operator_eq_/overload2.html +/doc/asio/reference/io_context__basic_executor_type/operator_not__eq_.html +/doc/asio/reference/io_context__basic_executor_type/post.html +/doc/asio/reference/io_context__basic_executor_type/query/ +/doc/asio/reference/io_context__basic_executor_type/query.html +/doc/asio/reference/io_context__basic_executor_type/query/overload1.html +/doc/asio/reference/io_context__basic_executor_type/query/overload2.html +/doc/asio/reference/io_context__basic_executor_type/query/overload3.html +/doc/asio/reference/io_context__basic_executor_type/query/overload4.html +/doc/asio/reference/io_context__basic_executor_type/query/overload5.html +/doc/asio/reference/io_context__basic_executor_type/query__static/ +/doc/asio/reference/io_context__basic_executor_type/query__static.html +/doc/asio/reference/io_context__basic_executor_type/query__static/overload1.html +/doc/asio/reference/io_context__basic_executor_type/query__static/overload2.html +/doc/asio/reference/io_context__basic_executor_type/require/ +/doc/asio/reference/io_context__basic_executor_type/require.html +/doc/asio/reference/io_context__basic_executor_type/require/overload1.html +/doc/asio/reference/io_context__basic_executor_type/require/overload2.html +/doc/asio/reference/io_context__basic_executor_type/require/overload3.html +/doc/asio/reference/io_context__basic_executor_type/require/overload4.html +/doc/asio/reference/io_context__basic_executor_type/require/overload5.html +/doc/asio/reference/io_context__basic_executor_type/require/overload6.html +/doc/asio/reference/io_context__basic_executor_type/require/overload7.html +/doc/asio/reference/io_context__basic_executor_type/require/overload8.html +/doc/asio/reference/io_context__basic_executor_type/running_in_this_thread.html +/doc/asio/reference/io_context/count_type.html +/doc/asio/reference/io_context/destroy.html +/doc/asio/reference/io_context/dispatch.html +/doc/asio/reference/io_context/executor_type.html +/doc/asio/reference/io_context/fork_event.html +/doc/asio/reference/io_context/get_executor.html +/doc/asio/reference/io_context/has_service.html +/doc/asio/reference/io_context.html +/doc/asio/reference/io_context/io_context/ +/doc/asio/reference/io_context/_io_context.html +/doc/asio/reference/io_context/io_context.html +/doc/asio/reference/io_context/io_context/overload1.html +/doc/asio/reference/io_context/io_context/overload2.html +/doc/asio/reference/io_context/make_service.html +/doc/asio/reference/io_context/notify_fork.html +/doc/asio/reference/io_context/poll/ +/doc/asio/reference/io_context/poll.html +/doc/asio/reference/io_context/poll_one/ +/doc/asio/reference/io_context/poll_one.html +/doc/asio/reference/io_context/poll_one/overload1.html +/doc/asio/reference/io_context/poll_one/overload2.html +/doc/asio/reference/io_context/poll/overload1.html +/doc/asio/reference/io_context/poll/overload2.html +/doc/asio/reference/io_context/post.html +/doc/asio/reference/io_context/reset.html +/doc/asio/reference/io_context/restart.html +/doc/asio/reference/io_context/run/ +/doc/asio/reference/io_context/run_for.html +/doc/asio/reference/io_context/run.html +/doc/asio/reference/io_context/run_one/ +/doc/asio/reference/io_context/run_one_for.html +/doc/asio/reference/io_context/run_one.html +/doc/asio/reference/io_context/run_one/overload1.html +/doc/asio/reference/io_context/run_one/overload2.html +/doc/asio/reference/io_context/run_one_until.html +/doc/asio/reference/io_context/run/overload1.html +/doc/asio/reference/io_context/run/overload2.html +/doc/asio/reference/io_context/run_until.html +/doc/asio/reference/io_context__service/ +/doc/asio/reference/io_context__service/get_io_context.html +/doc/asio/reference/io_context__service.html +/doc/asio/reference/io_context__service/_service.html +/doc/asio/reference/io_context__service/service.html +/doc/asio/reference/io_context/shutdown.html +/doc/asio/reference/io_context/stop.html +/doc/asio/reference/io_context/stopped.html +/doc/asio/reference/io_context__strand/ +/doc/asio/reference/io_context__strand/context.html +/doc/asio/reference/io_context__strand/defer.html +/doc/asio/reference/io_context__strand/dispatch/ +/doc/asio/reference/io_context__strand/dispatch.html +/doc/asio/reference/io_context__strand/dispatch/overload1.html +/doc/asio/reference/io_context__strand/dispatch/overload2.html +/doc/asio/reference/io_context__strand.html +/doc/asio/reference/io_context__strand/on_work_finished.html +/doc/asio/reference/io_context__strand/on_work_started.html +/doc/asio/reference/io_context__strand/operator_eq__eq_.html +/doc/asio/reference/io_context__strand/operator_not__eq_.html +/doc/asio/reference/io_context__strand/post/ +/doc/asio/reference/io_context__strand/post.html +/doc/asio/reference/io_context__strand/post/overload1.html +/doc/asio/reference/io_context__strand/post/overload2.html +/doc/asio/reference/io_context__strand/running_in_this_thread.html +/doc/asio/reference/io_context__strand/_strand.html +/doc/asio/reference/io_context__strand/strand.html +/doc/asio/reference/io_context__strand/wrap.html +/doc/asio/reference/io_context/use_service/ +/doc/asio/reference/io_context/use_service.html +/doc/asio/reference/io_context/use_service/overload1.html +/doc/asio/reference/io_context/use_service/overload2.html +/doc/asio/reference/io_context__work/ +/doc/asio/reference/io_context__work/get_io_context.html +/doc/asio/reference/io_context__work.html +/doc/asio/reference/io_context__work/work/ +/doc/asio/reference/io_context__work/_work.html +/doc/asio/reference/io_context__work/work.html +/doc/asio/reference/io_context__work/work/overload1.html +/doc/asio/reference/io_context__work/work/overload2.html +/doc/asio/reference/io_context/wrap.html +/doc/asio/reference/IoControlCommand.html +/doc/asio/reference/IoObjectService.html +/doc/asio/reference/io_service.html +/doc/asio/reference/ip__address/ +/doc/asio/reference/ip__address/address/ +/doc/asio/reference/ip__address/address.html +/doc/asio/reference/ip__address/address/overload1.html +/doc/asio/reference/ip__address/address/overload2.html +/doc/asio/reference/ip__address/address/overload3.html +/doc/asio/reference/ip__address/address/overload4.html +/doc/asio/reference/ip__address/from_string/ +/doc/asio/reference/ip__address/from_string.html +/doc/asio/reference/ip__address/from_string/overload1.html +/doc/asio/reference/ip__address/from_string/overload2.html +/doc/asio/reference/ip__address/from_string/overload3.html +/doc/asio/reference/ip__address/from_string/overload4.html +/doc/asio/reference/ip__address.html +/doc/asio/reference/ip__address/is_loopback.html +/doc/asio/reference/ip__address/is_multicast.html +/doc/asio/reference/ip__address/is_unspecified.html +/doc/asio/reference/ip__address/is_v4.html +/doc/asio/reference/ip__address/is_v6.html +/doc/asio/reference/ip__address/make_address/ +/doc/asio/reference/ip__address/make_address.html +/doc/asio/reference/ip__address/make_address/overload1.html +/doc/asio/reference/ip__address/make_address/overload2.html +/doc/asio/reference/ip__address/make_address/overload3.html +/doc/asio/reference/ip__address/make_address/overload4.html +/doc/asio/reference/ip__address/make_address/overload5.html +/doc/asio/reference/ip__address/make_address/overload6.html +/doc/asio/reference/ip__address/operator_eq_/ +/doc/asio/reference/ip__address/operator_eq__eq_.html +/doc/asio/reference/ip__address/operator_eq_.html +/doc/asio/reference/ip__address/operator_eq_/overload1.html +/doc/asio/reference/ip__address/operator_eq_/overload2.html +/doc/asio/reference/ip__address/operator_eq_/overload3.html +/doc/asio/reference/ip__address/operator_gt__eq_.html +/doc/asio/reference/ip__address/operator_gt_.html +/doc/asio/reference/ip__address/operator_lt__eq_.html +/doc/asio/reference/ip__address/operator_lt_.html +/doc/asio/reference/ip__address/operator_lt__lt_.html +/doc/asio/reference/ip__address/operator_not__eq_.html +/doc/asio/reference/ip__address/to_string/ +/doc/asio/reference/ip__address/to_string.html +/doc/asio/reference/ip__address/to_string/overload1.html +/doc/asio/reference/ip__address/to_string/overload2.html +/doc/asio/reference/ip__address/to_v4.html +/doc/asio/reference/ip__address/to_v6.html +/doc/asio/reference/ip__address_v4/ +/doc/asio/reference/ip__address_v4/address_v4/ +/doc/asio/reference/ip__address_v4/address_v4.html +/doc/asio/reference/ip__address_v4/address_v4/overload1.html +/doc/asio/reference/ip__address_v4/address_v4/overload2.html +/doc/asio/reference/ip__address_v4/address_v4/overload3.html +/doc/asio/reference/ip__address_v4/address_v4/overload4.html +/doc/asio/reference/ip__address_v4/any.html +/doc/asio/reference/ip__address_v4/broadcast/ +/doc/asio/reference/ip__address_v4/broadcast.html +/doc/asio/reference/ip__address_v4/broadcast/overload1.html +/doc/asio/reference/ip__address_v4/broadcast/overload2.html +/doc/asio/reference/ip__address_v4/bytes_type.html +/doc/asio/reference/ip__address_v4/from_string/ +/doc/asio/reference/ip__address_v4/from_string.html +/doc/asio/reference/ip__address_v4/from_string/overload1.html +/doc/asio/reference/ip__address_v4/from_string/overload2.html +/doc/asio/reference/ip__address_v4/from_string/overload3.html +/doc/asio/reference/ip__address_v4/from_string/overload4.html +/doc/asio/reference/ip__address_v4.html +/doc/asio/reference/ip__address_v4/is_class_a.html +/doc/asio/reference/ip__address_v4/is_class_b.html +/doc/asio/reference/ip__address_v4/is_class_c.html +/doc/asio/reference/ip__address_v4/is_loopback.html +/doc/asio/reference/ip__address_v4/is_multicast.html +/doc/asio/reference/ip__address_v4/is_unspecified.html +/doc/asio/reference/ip__address_v4_iterator.html +/doc/asio/reference/ip__address_v4/loopback.html +/doc/asio/reference/ip__address_v4/make_address_v4/ +/doc/asio/reference/ip__address_v4/make_address_v4.html +/doc/asio/reference/ip__address_v4/make_address_v4/overload1.html +/doc/asio/reference/ip__address_v4/make_address_v4/overload2.html +/doc/asio/reference/ip__address_v4/make_address_v4/overload3.html +/doc/asio/reference/ip__address_v4/make_address_v4/overload4.html +/doc/asio/reference/ip__address_v4/make_address_v4/overload5.html +/doc/asio/reference/ip__address_v4/make_address_v4/overload6.html +/doc/asio/reference/ip__address_v4/make_address_v4/overload7.html +/doc/asio/reference/ip__address_v4/make_address_v4/overload8.html +/doc/asio/reference/ip__address_v4/make_address_v4/overload9.html +/doc/asio/reference/ip__address_v4/make_network_v4/ +/doc/asio/reference/ip__address_v4/make_network_v4.html +/doc/asio/reference/ip__address_v4/make_network_v4/overload1.html +/doc/asio/reference/ip__address_v4/make_network_v4/overload2.html +/doc/asio/reference/ip__address_v4/netmask.html +/doc/asio/reference/ip__address_v4/operator_eq__eq_.html +/doc/asio/reference/ip__address_v4/operator_eq_.html +/doc/asio/reference/ip__address_v4/operator_gt__eq_.html +/doc/asio/reference/ip__address_v4/operator_gt_.html +/doc/asio/reference/ip__address_v4/operator_lt__eq_.html +/doc/asio/reference/ip__address_v4/operator_lt_.html +/doc/asio/reference/ip__address_v4/operator_lt__lt_/ +/doc/asio/reference/ip__address_v4/operator_lt__lt_.html +/doc/asio/reference/ip__address_v4/operator_lt__lt_/overload1.html +/doc/asio/reference/ip__address_v4/operator_lt__lt_/overload2.html +/doc/asio/reference/ip__address_v4/operator_not__eq_.html +/doc/asio/reference/ip__address_v4_range.html +/doc/asio/reference/ip__address_v4/to_bytes.html +/doc/asio/reference/ip__address_v4/to_string/ +/doc/asio/reference/ip__address_v4/to_string.html +/doc/asio/reference/ip__address_v4/to_string/overload1.html +/doc/asio/reference/ip__address_v4/to_string/overload2.html +/doc/asio/reference/ip__address_v4/to_uint.html +/doc/asio/reference/ip__address_v4/to_ulong.html +/doc/asio/reference/ip__address_v4/uint_type.html +/doc/asio/reference/ip__address_v6/ +/doc/asio/reference/ip__address_v6/address_v6/ +/doc/asio/reference/ip__address_v6/address_v6.html +/doc/asio/reference/ip__address_v6/address_v6/overload1.html +/doc/asio/reference/ip__address_v6/address_v6/overload2.html +/doc/asio/reference/ip__address_v6/address_v6/overload3.html +/doc/asio/reference/ip__address_v6/any.html +/doc/asio/reference/ip__address_v6/bytes_type.html +/doc/asio/reference/ip__address_v6/from_string/ +/doc/asio/reference/ip__address_v6/from_string.html +/doc/asio/reference/ip__address_v6/from_string/overload1.html +/doc/asio/reference/ip__address_v6/from_string/overload2.html +/doc/asio/reference/ip__address_v6/from_string/overload3.html +/doc/asio/reference/ip__address_v6/from_string/overload4.html +/doc/asio/reference/ip__address_v6.html +/doc/asio/reference/ip__address_v6/is_link_local.html +/doc/asio/reference/ip__address_v6/is_loopback.html +/doc/asio/reference/ip__address_v6/is_multicast_global.html +/doc/asio/reference/ip__address_v6/is_multicast.html +/doc/asio/reference/ip__address_v6/is_multicast_link_local.html +/doc/asio/reference/ip__address_v6/is_multicast_node_local.html +/doc/asio/reference/ip__address_v6/is_multicast_org_local.html +/doc/asio/reference/ip__address_v6/is_multicast_site_local.html +/doc/asio/reference/ip__address_v6/is_site_local.html +/doc/asio/reference/ip__address_v6/is_unspecified.html +/doc/asio/reference/ip__address_v6/is_v4_compatible.html +/doc/asio/reference/ip__address_v6/is_v4_mapped.html +/doc/asio/reference/ip__address_v6_iterator.html +/doc/asio/reference/ip__address_v6/loopback.html +/doc/asio/reference/ip__address_v6/make_address_v6/ +/doc/asio/reference/ip__address_v6/make_address_v6.html +/doc/asio/reference/ip__address_v6/make_address_v6/overload1.html +/doc/asio/reference/ip__address_v6/make_address_v6/overload2.html +/doc/asio/reference/ip__address_v6/make_address_v6/overload3.html +/doc/asio/reference/ip__address_v6/make_address_v6/overload4.html +/doc/asio/reference/ip__address_v6/make_address_v6/overload5.html +/doc/asio/reference/ip__address_v6/make_address_v6/overload6.html +/doc/asio/reference/ip__address_v6/make_address_v6/overload7.html +/doc/asio/reference/ip__address_v6/make_address_v6/overload8.html +/doc/asio/reference/ip__address_v6/make_network_v6.html +/doc/asio/reference/ip__address_v6/operator_eq__eq_.html +/doc/asio/reference/ip__address_v6/operator_eq_.html +/doc/asio/reference/ip__address_v6/operator_gt__eq_.html +/doc/asio/reference/ip__address_v6/operator_gt_.html +/doc/asio/reference/ip__address_v6/operator_lt__eq_.html +/doc/asio/reference/ip__address_v6/operator_lt_.html +/doc/asio/reference/ip__address_v6/operator_lt__lt_/ +/doc/asio/reference/ip__address_v6/operator_lt__lt_.html +/doc/asio/reference/ip__address_v6/operator_lt__lt_/overload1.html +/doc/asio/reference/ip__address_v6/operator_lt__lt_/overload2.html +/doc/asio/reference/ip__address_v6/operator_not__eq_.html +/doc/asio/reference/ip__address_v6_range.html +/doc/asio/reference/ip__address_v6/scope_id/ +/doc/asio/reference/ip__address_v6/scope_id.html +/doc/asio/reference/ip__address_v6/scope_id/overload1.html +/doc/asio/reference/ip__address_v6/scope_id/overload2.html +/doc/asio/reference/ip__address_v6/to_bytes.html +/doc/asio/reference/ip__address_v6/to_string/ +/doc/asio/reference/ip__address_v6/to_string.html +/doc/asio/reference/ip__address_v6/to_string/overload1.html +/doc/asio/reference/ip__address_v6/to_string/overload2.html +/doc/asio/reference/ip__address_v6/to_v4.html +/doc/asio/reference/ip__address_v6/v4_compatible.html +/doc/asio/reference/ip__address_v6/v4_mapped.html +/doc/asio/reference/ip__bad_address_cast/ +/doc/asio/reference/ip__bad_address_cast/_bad_address_cast.html +/doc/asio/reference/ip__bad_address_cast/bad_address_cast.html +/doc/asio/reference/ip__bad_address_cast.html +/doc/asio/reference/ip__bad_address_cast/what.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/ +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/basic_address_iterator/ +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/basic_address_iterator.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/basic_address_iterator/overload1.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/basic_address_iterator/overload2.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/difference_type.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/iterator_category.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_arrow_.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_eq__eq_.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_eq_.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_minus__minus_/ +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_minus__minus_.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_minus__minus_/overload1.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_minus__minus_/overload2.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_not__eq_.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_plus__plus_/ +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_plus__plus_.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_plus__plus_/overload1.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_plus__plus_/overload2.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator__star_.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/pointer.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/reference.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/value_type.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/ +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/basic_address_iterator/ +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/basic_address_iterator.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/basic_address_iterator/overload1.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/basic_address_iterator/overload2.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/difference_type.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/iterator_category.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_arrow_.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_eq__eq_.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_eq_.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_minus__minus_/ +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_minus__minus_.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_minus__minus_/overload1.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_minus__minus_/overload2.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_not__eq_.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_plus__plus_/ +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_plus__plus_.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_plus__plus_/overload1.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_plus__plus_/overload2.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator__star_.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/pointer.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/reference.html +/doc/asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/value_type.html +/doc/asio/reference/ip__basic_address_range_lt__address_v4__gt_/ +/doc/asio/reference/ip__basic_address_range_lt__address_v4__gt_/basic_address_range/ +/doc/asio/reference/ip__basic_address_range_lt__address_v4__gt_/basic_address_range.html +/doc/asio/reference/ip__basic_address_range_lt__address_v4__gt_/basic_address_range/overload1.html +/doc/asio/reference/ip__basic_address_range_lt__address_v4__gt_/basic_address_range/overload2.html +/doc/asio/reference/ip__basic_address_range_lt__address_v4__gt_/basic_address_range/overload3.html +/doc/asio/reference/ip__basic_address_range_lt__address_v4__gt_/begin.html +/doc/asio/reference/ip__basic_address_range_lt__address_v4__gt_/empty.html +/doc/asio/reference/ip__basic_address_range_lt__address_v4__gt_/end.html +/doc/asio/reference/ip__basic_address_range_lt__address_v4__gt_/find.html +/doc/asio/reference/ip__basic_address_range_lt__address_v4__gt_.html +/doc/asio/reference/ip__basic_address_range_lt__address_v4__gt_/iterator.html +/doc/asio/reference/ip__basic_address_range_lt__address_v4__gt_/operator_eq_.html +/doc/asio/reference/ip__basic_address_range_lt__address_v4__gt_/size.html +/doc/asio/reference/ip__basic_address_range_lt__address_v6__gt_/ +/doc/asio/reference/ip__basic_address_range_lt__address_v6__gt_/basic_address_range/ +/doc/asio/reference/ip__basic_address_range_lt__address_v6__gt_/basic_address_range.html +/doc/asio/reference/ip__basic_address_range_lt__address_v6__gt_/basic_address_range/overload1.html +/doc/asio/reference/ip__basic_address_range_lt__address_v6__gt_/basic_address_range/overload2.html +/doc/asio/reference/ip__basic_address_range_lt__address_v6__gt_/basic_address_range/overload3.html +/doc/asio/reference/ip__basic_address_range_lt__address_v6__gt_/begin.html +/doc/asio/reference/ip__basic_address_range_lt__address_v6__gt_/empty.html +/doc/asio/reference/ip__basic_address_range_lt__address_v6__gt_/end.html +/doc/asio/reference/ip__basic_address_range_lt__address_v6__gt_/find.html +/doc/asio/reference/ip__basic_address_range_lt__address_v6__gt_.html +/doc/asio/reference/ip__basic_address_range_lt__address_v6__gt_/iterator.html +/doc/asio/reference/ip__basic_address_range_lt__address_v6__gt_/operator_eq_.html +/doc/asio/reference/ip__basic_endpoint/ +/doc/asio/reference/ip__basic_endpoint/address/ +/doc/asio/reference/ip__basic_endpoint/address.html +/doc/asio/reference/ip__basic_endpoint/address/overload1.html +/doc/asio/reference/ip__basic_endpoint/address/overload2.html +/doc/asio/reference/ip__basic_endpoint/basic_endpoint/ +/doc/asio/reference/ip__basic_endpoint/basic_endpoint.html +/doc/asio/reference/ip__basic_endpoint/basic_endpoint/overload1.html +/doc/asio/reference/ip__basic_endpoint/basic_endpoint/overload2.html +/doc/asio/reference/ip__basic_endpoint/basic_endpoint/overload3.html +/doc/asio/reference/ip__basic_endpoint/basic_endpoint/overload4.html +/doc/asio/reference/ip__basic_endpoint/basic_endpoint/overload5.html +/doc/asio/reference/ip__basic_endpoint/capacity.html +/doc/asio/reference/ip__basic_endpoint/data/ +/doc/asio/reference/ip__basic_endpoint/data.html +/doc/asio/reference/ip__basic_endpoint/data/overload1.html +/doc/asio/reference/ip__basic_endpoint/data/overload2.html +/doc/asio/reference/ip__basic_endpoint/data_type.html +/doc/asio/reference/ip__basic_endpoint.html +/doc/asio/reference/ip__basic_endpoint/operator_eq_/ +/doc/asio/reference/ip__basic_endpoint/operator_eq__eq_.html +/doc/asio/reference/ip__basic_endpoint/operator_eq_.html +/doc/asio/reference/ip__basic_endpoint/operator_eq_/overload1.html +/doc/asio/reference/ip__basic_endpoint/operator_eq_/overload2.html +/doc/asio/reference/ip__basic_endpoint/operator_gt__eq_.html +/doc/asio/reference/ip__basic_endpoint/operator_gt_.html +/doc/asio/reference/ip__basic_endpoint/operator_lt__eq_.html +/doc/asio/reference/ip__basic_endpoint/operator_lt_.html +/doc/asio/reference/ip__basic_endpoint/operator_lt__lt_.html +/doc/asio/reference/ip__basic_endpoint/operator_not__eq_.html +/doc/asio/reference/ip__basic_endpoint/port/ +/doc/asio/reference/ip__basic_endpoint/port.html +/doc/asio/reference/ip__basic_endpoint/port/overload1.html +/doc/asio/reference/ip__basic_endpoint/port/overload2.html +/doc/asio/reference/ip__basic_endpoint/protocol.html +/doc/asio/reference/ip__basic_endpoint/protocol_type.html +/doc/asio/reference/ip__basic_endpoint/resize.html +/doc/asio/reference/ip__basic_endpoint/size.html +/doc/asio/reference/ip__basic_resolver/ +/doc/asio/reference/ip__basic_resolver/address_configured.html +/doc/asio/reference/ip__basic_resolver/all_matching.html +/doc/asio/reference/ip__basic_resolver/async_resolve/ +/doc/asio/reference/ip__basic_resolver/async_resolve.html +/doc/asio/reference/ip__basic_resolver/async_resolve/overload1.html +/doc/asio/reference/ip__basic_resolver/async_resolve/overload2.html +/doc/asio/reference/ip__basic_resolver/async_resolve/overload3.html +/doc/asio/reference/ip__basic_resolver/async_resolve/overload4.html +/doc/asio/reference/ip__basic_resolver/async_resolve/overload5.html +/doc/asio/reference/ip__basic_resolver/async_resolve/overload6.html +/doc/asio/reference/ip__basic_resolver/basic_resolver/ +/doc/asio/reference/ip__basic_resolver/_basic_resolver.html +/doc/asio/reference/ip__basic_resolver/basic_resolver.html +/doc/asio/reference/ip__basic_resolver/basic_resolver/overload1.html +/doc/asio/reference/ip__basic_resolver/basic_resolver/overload2.html +/doc/asio/reference/ip__basic_resolver/basic_resolver/overload3.html +/doc/asio/reference/ip__basic_resolver/cancel.html +/doc/asio/reference/ip__basic_resolver/canonical_name.html +/doc/asio/reference/ip__basic_resolver/endpoint_type.html +/doc/asio/reference/ip__basic_resolver_entry/ +/doc/asio/reference/ip__basic_resolver_entry/basic_resolver_entry/ +/doc/asio/reference/ip__basic_resolver_entry/basic_resolver_entry.html +/doc/asio/reference/ip__basic_resolver_entry/basic_resolver_entry/overload1.html +/doc/asio/reference/ip__basic_resolver_entry/basic_resolver_entry/overload2.html +/doc/asio/reference/ip__basic_resolver_entry/endpoint.html +/doc/asio/reference/ip__basic_resolver_entry/endpoint_type.html +/doc/asio/reference/ip__basic_resolver_entry/host_name/ +/doc/asio/reference/ip__basic_resolver_entry/host_name.html +/doc/asio/reference/ip__basic_resolver_entry/host_name/overload1.html +/doc/asio/reference/ip__basic_resolver_entry/host_name/overload2.html +/doc/asio/reference/ip__basic_resolver_entry.html +/doc/asio/reference/ip__basic_resolver_entry/operator_endpoint_type.html +/doc/asio/reference/ip__basic_resolver_entry/protocol_type.html +/doc/asio/reference/ip__basic_resolver_entry/service_name/ +/doc/asio/reference/ip__basic_resolver_entry/service_name.html +/doc/asio/reference/ip__basic_resolver_entry/service_name/overload1.html +/doc/asio/reference/ip__basic_resolver_entry/service_name/overload2.html +/doc/asio/reference/ip__basic_resolver/executor_type.html +/doc/asio/reference/ip__basic_resolver/flags.html +/doc/asio/reference/ip__basic_resolver/get_executor.html +/doc/asio/reference/ip__basic_resolver.html +/doc/asio/reference/ip__basic_resolver_iterator/ +/doc/asio/reference/ip__basic_resolver_iterator/basic_resolver_iterator/ +/doc/asio/reference/ip__basic_resolver_iterator/basic_resolver_iterator.html +/doc/asio/reference/ip__basic_resolver_iterator/basic_resolver_iterator/overload1.html +/doc/asio/reference/ip__basic_resolver_iterator/basic_resolver_iterator/overload2.html +/doc/asio/reference/ip__basic_resolver_iterator/basic_resolver_iterator/overload3.html +/doc/asio/reference/ip__basic_resolver_iterator/dereference.html +/doc/asio/reference/ip__basic_resolver_iterator/difference_type.html +/doc/asio/reference/ip__basic_resolver_iterator/equal.html +/doc/asio/reference/ip__basic_resolver/iterator.html +/doc/asio/reference/ip__basic_resolver_iterator.html +/doc/asio/reference/ip__basic_resolver_iterator/increment.html +/doc/asio/reference/ip__basic_resolver_iterator/index_.html +/doc/asio/reference/ip__basic_resolver_iterator/iterator_category.html +/doc/asio/reference/ip__basic_resolver_iterator/operator_arrow_.html +/doc/asio/reference/ip__basic_resolver_iterator/operator_eq_/ +/doc/asio/reference/ip__basic_resolver_iterator/operator_eq__eq_.html +/doc/asio/reference/ip__basic_resolver_iterator/operator_eq_.html +/doc/asio/reference/ip__basic_resolver_iterator/operator_eq_/overload1.html +/doc/asio/reference/ip__basic_resolver_iterator/operator_eq_/overload2.html +/doc/asio/reference/ip__basic_resolver_iterator/operator_not__eq_.html +/doc/asio/reference/ip__basic_resolver_iterator/operator_plus__plus_/ +/doc/asio/reference/ip__basic_resolver_iterator/operator_plus__plus_.html +/doc/asio/reference/ip__basic_resolver_iterator/operator_plus__plus_/overload1.html +/doc/asio/reference/ip__basic_resolver_iterator/operator_plus__plus_/overload2.html +/doc/asio/reference/ip__basic_resolver_iterator/operator__star_.html +/doc/asio/reference/ip__basic_resolver_iterator/pointer.html +/doc/asio/reference/ip__basic_resolver_iterator/reference.html +/doc/asio/reference/ip__basic_resolver_iterator/values_.html +/doc/asio/reference/ip__basic_resolver_iterator/value_type.html +/doc/asio/reference/ip__basic_resolver/numeric_host.html +/doc/asio/reference/ip__basic_resolver/numeric_service.html +/doc/asio/reference/ip__basic_resolver/operator_eq_.html +/doc/asio/reference/ip__basic_resolver/passive.html +/doc/asio/reference/ip__basic_resolver/protocol_type.html +/doc/asio/reference/ip__basic_resolver_query/ +/doc/asio/reference/ip__basic_resolver_query/address_configured.html +/doc/asio/reference/ip__basic_resolver_query/all_matching.html +/doc/asio/reference/ip__basic_resolver_query/basic_resolver_query/ +/doc/asio/reference/ip__basic_resolver_query/basic_resolver_query.html +/doc/asio/reference/ip__basic_resolver_query/basic_resolver_query/overload1.html +/doc/asio/reference/ip__basic_resolver_query/basic_resolver_query/overload2.html +/doc/asio/reference/ip__basic_resolver_query/basic_resolver_query/overload3.html +/doc/asio/reference/ip__basic_resolver_query/basic_resolver_query/overload4.html +/doc/asio/reference/ip__basic_resolver_query/canonical_name.html +/doc/asio/reference/ip__basic_resolver_query/flags.html +/doc/asio/reference/ip__basic_resolver_query/hints.html +/doc/asio/reference/ip__basic_resolver_query/host_name.html +/doc/asio/reference/ip__basic_resolver/query.html +/doc/asio/reference/ip__basic_resolver_query.html +/doc/asio/reference/ip__basic_resolver_query/numeric_host.html +/doc/asio/reference/ip__basic_resolver_query/numeric_service.html +/doc/asio/reference/ip__basic_resolver_query/passive.html +/doc/asio/reference/ip__basic_resolver_query/protocol_type.html +/doc/asio/reference/ip__basic_resolver_query/service_name.html +/doc/asio/reference/ip__basic_resolver_query/v4_mapped.html +/doc/asio/reference/ip__basic_resolver__rebind_executor/ +/doc/asio/reference/ip__basic_resolver__rebind_executor.html +/doc/asio/reference/ip__basic_resolver__rebind_executor/other.html +/doc/asio/reference/ip__basic_resolver/resolve/ +/doc/asio/reference/ip__basic_resolver/resolve.html +/doc/asio/reference/ip__basic_resolver/resolve/overload10.html +/doc/asio/reference/ip__basic_resolver/resolve/overload11.html +/doc/asio/reference/ip__basic_resolver/resolve/overload12.html +/doc/asio/reference/ip__basic_resolver/resolve/overload1.html +/doc/asio/reference/ip__basic_resolver/resolve/overload2.html +/doc/asio/reference/ip__basic_resolver/resolve/overload3.html +/doc/asio/reference/ip__basic_resolver/resolve/overload4.html +/doc/asio/reference/ip__basic_resolver/resolve/overload5.html +/doc/asio/reference/ip__basic_resolver/resolve/overload6.html +/doc/asio/reference/ip__basic_resolver/resolve/overload7.html +/doc/asio/reference/ip__basic_resolver/resolve/overload8.html +/doc/asio/reference/ip__basic_resolver/resolve/overload9.html +/doc/asio/reference/ip__basic_resolver_results/ +/doc/asio/reference/ip__basic_resolver_results/basic_resolver_results/ +/doc/asio/reference/ip__basic_resolver_results/basic_resolver_results.html +/doc/asio/reference/ip__basic_resolver_results/basic_resolver_results/overload1.html +/doc/asio/reference/ip__basic_resolver_results/basic_resolver_results/overload2.html +/doc/asio/reference/ip__basic_resolver_results/basic_resolver_results/overload3.html +/doc/asio/reference/ip__basic_resolver_results/begin.html +/doc/asio/reference/ip__basic_resolver_results/cbegin.html +/doc/asio/reference/ip__basic_resolver_results/cend.html +/doc/asio/reference/ip__basic_resolver_results/const_iterator.html +/doc/asio/reference/ip__basic_resolver_results/const_reference.html +/doc/asio/reference/ip__basic_resolver_results/dereference.html +/doc/asio/reference/ip__basic_resolver_results/difference_type.html +/doc/asio/reference/ip__basic_resolver_results/empty.html +/doc/asio/reference/ip__basic_resolver_results/end.html +/doc/asio/reference/ip__basic_resolver_results/endpoint_type.html +/doc/asio/reference/ip__basic_resolver_results/equal.html +/doc/asio/reference/ip__basic_resolver_results.html +/doc/asio/reference/ip__basic_resolver_results/increment.html +/doc/asio/reference/ip__basic_resolver_results/index_.html +/doc/asio/reference/ip__basic_resolver_results/iterator_category.html +/doc/asio/reference/ip__basic_resolver_results/iterator.html +/doc/asio/reference/ip__basic_resolver_results/max_size.html +/doc/asio/reference/ip__basic_resolver_results/operator_arrow_.html +/doc/asio/reference/ip__basic_resolver_results/operator_eq_/ +/doc/asio/reference/ip__basic_resolver_results/operator_eq__eq_/ +/doc/asio/reference/ip__basic_resolver_results/operator_eq__eq_.html +/doc/asio/reference/ip__basic_resolver_results/operator_eq__eq_/overload1.html +/doc/asio/reference/ip__basic_resolver_results/operator_eq__eq_/overload2.html +/doc/asio/reference/ip__basic_resolver_results/operator_eq_.html +/doc/asio/reference/ip__basic_resolver_results/operator_eq_/overload1.html +/doc/asio/reference/ip__basic_resolver_results/operator_eq_/overload2.html +/doc/asio/reference/ip__basic_resolver_results/operator_not__eq_/ +/doc/asio/reference/ip__basic_resolver_results/operator_not__eq_.html +/doc/asio/reference/ip__basic_resolver_results/operator_not__eq_/overload1.html +/doc/asio/reference/ip__basic_resolver_results/operator_not__eq_/overload2.html +/doc/asio/reference/ip__basic_resolver_results/operator_plus__plus_/ +/doc/asio/reference/ip__basic_resolver_results/operator_plus__plus_.html +/doc/asio/reference/ip__basic_resolver_results/operator_plus__plus_/overload1.html +/doc/asio/reference/ip__basic_resolver_results/operator_plus__plus_/overload2.html +/doc/asio/reference/ip__basic_resolver_results/operator__star_.html +/doc/asio/reference/ip__basic_resolver_results/pointer.html +/doc/asio/reference/ip__basic_resolver_results/protocol_type.html +/doc/asio/reference/ip__basic_resolver_results/reference.html +/doc/asio/reference/ip__basic_resolver_results/size.html +/doc/asio/reference/ip__basic_resolver_results/size_type.html +/doc/asio/reference/ip__basic_resolver_results/swap.html +/doc/asio/reference/ip__basic_resolver/results_type.html +/doc/asio/reference/ip__basic_resolver_results/values_.html +/doc/asio/reference/ip__basic_resolver_results/value_type.html +/doc/asio/reference/ip__basic_resolver/v4_mapped.html +/doc/asio/reference/ip__host_name/ +/doc/asio/reference/ip__host_name.html +/doc/asio/reference/ip__host_name/overload1.html +/doc/asio/reference/ip__host_name/overload2.html +/doc/asio/reference/ip__icmp/ +/doc/asio/reference/ip__icmp/endpoint.html +/doc/asio/reference/ip__icmp/family.html +/doc/asio/reference/ip__icmp.html +/doc/asio/reference/ip__icmp/operator_eq__eq_.html +/doc/asio/reference/ip__icmp/operator_not__eq_.html +/doc/asio/reference/ip__icmp/protocol.html +/doc/asio/reference/ip__icmp/resolver.html +/doc/asio/reference/ip__icmp/socket.html +/doc/asio/reference/ip__icmp/type.html +/doc/asio/reference/ip__icmp/v4.html +/doc/asio/reference/ip__icmp/v6.html +/doc/asio/reference/ip__multicast__enable_loopback.html +/doc/asio/reference/ip__multicast__hops.html +/doc/asio/reference/ip__multicast__join_group.html +/doc/asio/reference/ip__multicast__leave_group.html +/doc/asio/reference/ip__multicast__outbound_interface.html +/doc/asio/reference/ip__network_v4/ +/doc/asio/reference/ip__network_v4/address.html +/doc/asio/reference/ip__network_v4/broadcast.html +/doc/asio/reference/ip__network_v4/canonical.html +/doc/asio/reference/ip__network_v4/hosts.html +/doc/asio/reference/ip__network_v4.html +/doc/asio/reference/ip__network_v4/is_host.html +/doc/asio/reference/ip__network_v4/is_subnet_of.html +/doc/asio/reference/ip__network_v4/make_network_v4/ +/doc/asio/reference/ip__network_v4/make_network_v4.html +/doc/asio/reference/ip__network_v4/make_network_v4/overload1.html +/doc/asio/reference/ip__network_v4/make_network_v4/overload2.html +/doc/asio/reference/ip__network_v4/make_network_v4/overload3.html +/doc/asio/reference/ip__network_v4/make_network_v4/overload4.html +/doc/asio/reference/ip__network_v4/make_network_v4/overload5.html +/doc/asio/reference/ip__network_v4/make_network_v4/overload6.html +/doc/asio/reference/ip__network_v4/netmask.html +/doc/asio/reference/ip__network_v4/network.html +/doc/asio/reference/ip__network_v4/network_v4/ +/doc/asio/reference/ip__network_v4/network_v4.html +/doc/asio/reference/ip__network_v4/network_v4/overload1.html +/doc/asio/reference/ip__network_v4/network_v4/overload2.html +/doc/asio/reference/ip__network_v4/network_v4/overload3.html +/doc/asio/reference/ip__network_v4/network_v4/overload4.html +/doc/asio/reference/ip__network_v4/operator_eq__eq_.html +/doc/asio/reference/ip__network_v4/operator_eq_.html +/doc/asio/reference/ip__network_v4/operator_not__eq_.html +/doc/asio/reference/ip__network_v4/prefix_length.html +/doc/asio/reference/ip__network_v4/to_string/ +/doc/asio/reference/ip__network_v4/to_string.html +/doc/asio/reference/ip__network_v4/to_string/overload1.html +/doc/asio/reference/ip__network_v4/to_string/overload2.html +/doc/asio/reference/ip__network_v6/ +/doc/asio/reference/ip__network_v6/address.html +/doc/asio/reference/ip__network_v6/canonical.html +/doc/asio/reference/ip__network_v6/hosts.html +/doc/asio/reference/ip__network_v6.html +/doc/asio/reference/ip__network_v6/is_host.html +/doc/asio/reference/ip__network_v6/is_subnet_of.html +/doc/asio/reference/ip__network_v6/make_network_v6/ +/doc/asio/reference/ip__network_v6/make_network_v6.html +/doc/asio/reference/ip__network_v6/make_network_v6/overload1.html +/doc/asio/reference/ip__network_v6/make_network_v6/overload2.html +/doc/asio/reference/ip__network_v6/make_network_v6/overload3.html +/doc/asio/reference/ip__network_v6/make_network_v6/overload4.html +/doc/asio/reference/ip__network_v6/make_network_v6/overload5.html +/doc/asio/reference/ip__network_v6/make_network_v6/overload6.html +/doc/asio/reference/ip__network_v6/network.html +/doc/asio/reference/ip__network_v6/network_v6/ +/doc/asio/reference/ip__network_v6/network_v6.html +/doc/asio/reference/ip__network_v6/network_v6/overload1.html +/doc/asio/reference/ip__network_v6/network_v6/overload2.html +/doc/asio/reference/ip__network_v6/network_v6/overload3.html +/doc/asio/reference/ip__network_v6/operator_eq__eq_.html +/doc/asio/reference/ip__network_v6/operator_eq_.html +/doc/asio/reference/ip__network_v6/operator_not__eq_.html +/doc/asio/reference/ip__network_v6/prefix_length.html +/doc/asio/reference/ip__network_v6/to_string/ +/doc/asio/reference/ip__network_v6/to_string.html +/doc/asio/reference/ip__network_v6/to_string/overload1.html +/doc/asio/reference/ip__network_v6/to_string/overload2.html +/doc/asio/reference/ip__resolver_base/ +/doc/asio/reference/ip__resolver_base/address_configured.html +/doc/asio/reference/ip__resolver_base/all_matching.html +/doc/asio/reference/ip__resolver_base/canonical_name.html +/doc/asio/reference/ip__resolver_base/flags.html +/doc/asio/reference/ip__resolver_base.html +/doc/asio/reference/ip__resolver_base/numeric_host.html +/doc/asio/reference/ip__resolver_base/numeric_service.html +/doc/asio/reference/ip__resolver_base/passive.html +/doc/asio/reference/ip__resolver_base/_resolver_base.html +/doc/asio/reference/ip__resolver_base/v4_mapped.html +/doc/asio/reference/ip__resolver_query_base/ +/doc/asio/reference/ip__resolver_query_base/address_configured.html +/doc/asio/reference/ip__resolver_query_base/all_matching.html +/doc/asio/reference/ip__resolver_query_base/canonical_name.html +/doc/asio/reference/ip__resolver_query_base/flags.html +/doc/asio/reference/ip__resolver_query_base.html +/doc/asio/reference/ip__resolver_query_base/numeric_host.html +/doc/asio/reference/ip__resolver_query_base/numeric_service.html +/doc/asio/reference/ip__resolver_query_base/passive.html +/doc/asio/reference/ip__resolver_query_base/_resolver_query_base.html +/doc/asio/reference/ip__resolver_query_base/v4_mapped.html +/doc/asio/reference/ip__tcp/ +/doc/asio/reference/ip__tcp/acceptor.html +/doc/asio/reference/ip__tcp/endpoint.html +/doc/asio/reference/ip__tcp/family.html +/doc/asio/reference/ip__tcp.html +/doc/asio/reference/ip__tcp/iostream.html +/doc/asio/reference/ip__tcp/no_delay.html +/doc/asio/reference/ip__tcp/operator_eq__eq_.html +/doc/asio/reference/ip__tcp/operator_not__eq_.html +/doc/asio/reference/ip__tcp/protocol.html +/doc/asio/reference/ip__tcp/resolver.html +/doc/asio/reference/ip__tcp/socket.html +/doc/asio/reference/ip__tcp/type.html +/doc/asio/reference/ip__tcp/v4.html +/doc/asio/reference/ip__tcp/v6.html +/doc/asio/reference/ip__udp/ +/doc/asio/reference/ip__udp/endpoint.html +/doc/asio/reference/ip__udp/family.html +/doc/asio/reference/ip__udp.html +/doc/asio/reference/ip__udp/operator_eq__eq_.html +/doc/asio/reference/ip__udp/operator_not__eq_.html +/doc/asio/reference/ip__udp/protocol.html +/doc/asio/reference/ip__udp/resolver.html +/doc/asio/reference/ip__udp/socket.html +/doc/asio/reference/ip__udp/type.html +/doc/asio/reference/ip__udp/v4.html +/doc/asio/reference/ip__udp/v6.html +/doc/asio/reference/ip__unicast__hops.html +/doc/asio/reference/ip__v4_mapped_t.html +/doc/asio/reference/ip__v6_only.html +/doc/asio/reference/is_applicable_property.html +/doc/asio/reference/is_const_buffer_sequence.html +/doc/asio/reference/is_dynamic_buffer.html +/doc/asio/reference/is_dynamic_buffer_v1.html +/doc/asio/reference/is_dynamic_buffer_v2.html +/doc/asio/reference/is_endpoint_sequence/ +/doc/asio/reference/is_endpoint_sequence.html +/doc/asio/reference/is_endpoint_sequence/value.html +/doc/asio/reference/is_executor.html +/doc/asio/reference/is_match_condition/ +/doc/asio/reference/is_match_condition.html +/doc/asio/reference/is_match_condition/value.html +/doc/asio/reference/is_mutable_buffer_sequence.html +/doc/asio/reference/is_nothrow_prefer.html +/doc/asio/reference/is_nothrow_query.html +/doc/asio/reference/is_nothrow_require_concept.html +/doc/asio/reference/is_nothrow_require.html +/doc/asio/reference/is_read_buffered/ +/doc/asio/reference/is_read_buffered.html +/doc/asio/reference/is_read_buffered/value.html +/doc/asio/reference/is_write_buffered/ +/doc/asio/reference/is_write_buffered.html +/doc/asio/reference/is_write_buffered/value.html +/doc/asio/reference/IteratorConnectHandler.html +/doc/asio/reference/LegacyCompletionHandler.html +/doc/asio/reference/local__basic_endpoint/ +/doc/asio/reference/local__basic_endpoint/basic_endpoint/ +/doc/asio/reference/local__basic_endpoint/basic_endpoint.html +/doc/asio/reference/local__basic_endpoint/basic_endpoint/overload1.html +/doc/asio/reference/local__basic_endpoint/basic_endpoint/overload2.html +/doc/asio/reference/local__basic_endpoint/basic_endpoint/overload3.html +/doc/asio/reference/local__basic_endpoint/basic_endpoint/overload4.html +/doc/asio/reference/local__basic_endpoint/capacity.html +/doc/asio/reference/local__basic_endpoint/data/ +/doc/asio/reference/local__basic_endpoint/data.html +/doc/asio/reference/local__basic_endpoint/data/overload1.html +/doc/asio/reference/local__basic_endpoint/data/overload2.html +/doc/asio/reference/local__basic_endpoint/data_type.html +/doc/asio/reference/local__basic_endpoint.html +/doc/asio/reference/local__basic_endpoint/operator_eq__eq_.html +/doc/asio/reference/local__basic_endpoint/operator_eq_.html +/doc/asio/reference/local__basic_endpoint/operator_gt__eq_.html +/doc/asio/reference/local__basic_endpoint/operator_gt_.html +/doc/asio/reference/local__basic_endpoint/operator_lt__eq_.html +/doc/asio/reference/local__basic_endpoint/operator_lt_.html +/doc/asio/reference/local__basic_endpoint/operator_lt__lt_.html +/doc/asio/reference/local__basic_endpoint/operator_not__eq_.html +/doc/asio/reference/local__basic_endpoint/path/ +/doc/asio/reference/local__basic_endpoint/path.html +/doc/asio/reference/local__basic_endpoint/path/overload1.html +/doc/asio/reference/local__basic_endpoint/path/overload2.html +/doc/asio/reference/local__basic_endpoint/path/overload3.html +/doc/asio/reference/local__basic_endpoint/protocol.html +/doc/asio/reference/local__basic_endpoint/protocol_type.html +/doc/asio/reference/local__basic_endpoint/resize.html +/doc/asio/reference/local__basic_endpoint/size.html +/doc/asio/reference/local__connect_pair/ +/doc/asio/reference/local__connect_pair.html +/doc/asio/reference/local__connect_pair/overload1.html +/doc/asio/reference/local__connect_pair/overload2.html +/doc/asio/reference/local__datagram_protocol/ +/doc/asio/reference/local__datagram_protocol/endpoint.html +/doc/asio/reference/local__datagram_protocol/family.html +/doc/asio/reference/local__datagram_protocol.html +/doc/asio/reference/local__datagram_protocol/protocol.html +/doc/asio/reference/local__datagram_protocol/socket.html +/doc/asio/reference/local__datagram_protocol/type.html +/doc/asio/reference/local__stream_protocol/ +/doc/asio/reference/local__stream_protocol/acceptor.html +/doc/asio/reference/local__stream_protocol/endpoint.html +/doc/asio/reference/local__stream_protocol/family.html +/doc/asio/reference/local__stream_protocol.html +/doc/asio/reference/local__stream_protocol/iostream.html +/doc/asio/reference/local__stream_protocol/protocol.html +/doc/asio/reference/local__stream_protocol/socket.html +/doc/asio/reference/local__stream_protocol/type.html +/doc/asio/reference/make_strand/ +/doc/asio/reference/make_strand.html +/doc/asio/reference/make_strand/overload1.html +/doc/asio/reference/make_strand/overload2.html +/doc/asio/reference/make_work_guard/ +/doc/asio/reference/make_work_guard.html +/doc/asio/reference/make_work_guard/overload1.html +/doc/asio/reference/make_work_guard/overload2.html +/doc/asio/reference/make_work_guard/overload3.html +/doc/asio/reference/make_work_guard/overload4.html +/doc/asio/reference/make_work_guard/overload5.html +/doc/asio/reference/MoveAcceptHandler.html +/doc/asio/reference/multiple_exceptions/ +/doc/asio/reference/multiple_exceptions/first_exception.html +/doc/asio/reference/multiple_exceptions.html +/doc/asio/reference/multiple_exceptions/multiple_exceptions.html +/doc/asio/reference/multiple_exceptions/what.html +/doc/asio/reference/mutable_buffer/ +/doc/asio/reference/mutable_buffer/data.html +/doc/asio/reference/mutable_buffer.html +/doc/asio/reference/mutable_buffer/mutable_buffer/ +/doc/asio/reference/mutable_buffer/mutable_buffer.html +/doc/asio/reference/mutable_buffer/mutable_buffer/overload1.html +/doc/asio/reference/mutable_buffer/mutable_buffer/overload2.html +/doc/asio/reference/mutable_buffer/operator_plus_/ +/doc/asio/reference/mutable_buffer/operator_plus__eq_.html +/doc/asio/reference/mutable_buffer/operator_plus_.html +/doc/asio/reference/mutable_buffer/operator_plus_/overload1.html +/doc/asio/reference/mutable_buffer/operator_plus_/overload2.html +/doc/asio/reference/mutable_buffers_1/ +/doc/asio/reference/mutable_buffers_1/begin.html +/doc/asio/reference/mutable_buffers_1/const_iterator.html +/doc/asio/reference/mutable_buffers_1/data.html +/doc/asio/reference/mutable_buffers_1/end.html +/doc/asio/reference/mutable_buffers_1.html +/doc/asio/reference/mutable_buffers_1/mutable_buffers_1/ +/doc/asio/reference/mutable_buffers_1/mutable_buffers_1.html +/doc/asio/reference/mutable_buffers_1/mutable_buffers_1/overload1.html +/doc/asio/reference/mutable_buffers_1/mutable_buffers_1/overload2.html +/doc/asio/reference/mutable_buffers_1/operator_plus_/ +/doc/asio/reference/mutable_buffers_1/operator_plus__eq_.html +/doc/asio/reference/mutable_buffers_1/operator_plus_.html +/doc/asio/reference/mutable_buffers_1/operator_plus_/overload1.html +/doc/asio/reference/mutable_buffers_1/operator_plus_/overload2.html +/doc/asio/reference/mutable_buffers_1/size.html +/doc/asio/reference/mutable_buffers_1/value_type.html +/doc/asio/reference/MutableBufferSequence.html +/doc/asio/reference/mutable_buffer/size.html +/doc/asio/reference/null_buffers/ +/doc/asio/reference/null_buffers/begin.html +/doc/asio/reference/null_buffers/const_iterator.html +/doc/asio/reference/null_buffers/end.html +/doc/asio/reference/null_buffers.html +/doc/asio/reference/null_buffers/value_type.html +/doc/asio/reference/OperationState.html +/doc/asio/reference/operator_lt__lt_.html +/doc/asio/reference/placeholders__bytes_transferred.html +/doc/asio/reference/placeholders__endpoint.html +/doc/asio/reference/placeholders__error.html +/doc/asio/reference/placeholders__iterator.html +/doc/asio/reference/placeholders__results.html +/doc/asio/reference/placeholders__signal_number.html +/doc/asio/reference/posix__basic_descriptor/ +/doc/asio/reference/posix__basic_descriptor/assign/ +/doc/asio/reference/posix__basic_descriptor/assign.html +/doc/asio/reference/posix__basic_descriptor/assign/overload1.html +/doc/asio/reference/posix__basic_descriptor/assign/overload2.html +/doc/asio/reference/posix__basic_descriptor/async_wait.html +/doc/asio/reference/posix__basic_descriptor/basic_descriptor/ +/doc/asio/reference/posix__basic_descriptor/_basic_descriptor.html +/doc/asio/reference/posix__basic_descriptor/basic_descriptor.html +/doc/asio/reference/posix__basic_descriptor/basic_descriptor/overload1.html +/doc/asio/reference/posix__basic_descriptor/basic_descriptor/overload2.html +/doc/asio/reference/posix__basic_descriptor/basic_descriptor/overload3.html +/doc/asio/reference/posix__basic_descriptor/basic_descriptor/overload4.html +/doc/asio/reference/posix__basic_descriptor/basic_descriptor/overload5.html +/doc/asio/reference/posix__basic_descriptor/bytes_readable.html +/doc/asio/reference/posix__basic_descriptor/cancel/ +/doc/asio/reference/posix__basic_descriptor/cancel.html +/doc/asio/reference/posix__basic_descriptor/cancel/overload1.html +/doc/asio/reference/posix__basic_descriptor/cancel/overload2.html +/doc/asio/reference/posix__basic_descriptor/close/ +/doc/asio/reference/posix__basic_descriptor/close.html +/doc/asio/reference/posix__basic_descriptor/close/overload1.html +/doc/asio/reference/posix__basic_descriptor/close/overload2.html +/doc/asio/reference/posix__basic_descriptor/executor_type.html +/doc/asio/reference/posix__basic_descriptor/get_executor.html +/doc/asio/reference/posix__basic_descriptor.html +/doc/asio/reference/posix__basic_descriptor/impl_.html +/doc/asio/reference/posix__basic_descriptor/io_control/ +/doc/asio/reference/posix__basic_descriptor/io_control.html +/doc/asio/reference/posix__basic_descriptor/io_control/overload1.html +/doc/asio/reference/posix__basic_descriptor/io_control/overload2.html +/doc/asio/reference/posix__basic_descriptor/is_open.html +/doc/asio/reference/posix__basic_descriptor/lowest_layer/ +/doc/asio/reference/posix__basic_descriptor/lowest_layer.html +/doc/asio/reference/posix__basic_descriptor/lowest_layer/overload1.html +/doc/asio/reference/posix__basic_descriptor/lowest_layer/overload2.html +/doc/asio/reference/posix__basic_descriptor/lowest_layer_type.html +/doc/asio/reference/posix__basic_descriptor/native_handle.html +/doc/asio/reference/posix__basic_descriptor/native_handle_type.html +/doc/asio/reference/posix__basic_descriptor/native_non_blocking/ +/doc/asio/reference/posix__basic_descriptor/native_non_blocking.html +/doc/asio/reference/posix__basic_descriptor/native_non_blocking/overload1.html +/doc/asio/reference/posix__basic_descriptor/native_non_blocking/overload2.html +/doc/asio/reference/posix__basic_descriptor/native_non_blocking/overload3.html +/doc/asio/reference/posix__basic_descriptor/non_blocking/ +/doc/asio/reference/posix__basic_descriptor/non_blocking.html +/doc/asio/reference/posix__basic_descriptor/non_blocking/overload1.html +/doc/asio/reference/posix__basic_descriptor/non_blocking/overload2.html +/doc/asio/reference/posix__basic_descriptor/non_blocking/overload3.html +/doc/asio/reference/posix__basic_descriptor/operator_eq_.html +/doc/asio/reference/posix__basic_descriptor__rebind_executor/ +/doc/asio/reference/posix__basic_descriptor__rebind_executor.html +/doc/asio/reference/posix__basic_descriptor__rebind_executor/other.html +/doc/asio/reference/posix__basic_descriptor/release.html +/doc/asio/reference/posix__basic_descriptor/wait/ +/doc/asio/reference/posix__basic_descriptor/wait.html +/doc/asio/reference/posix__basic_descriptor/wait/overload1.html +/doc/asio/reference/posix__basic_descriptor/wait/overload2.html +/doc/asio/reference/posix__basic_descriptor/wait_type.html +/doc/asio/reference/posix__basic_stream_descriptor/ +/doc/asio/reference/posix__basic_stream_descriptor/assign/ +/doc/asio/reference/posix__basic_stream_descriptor/assign.html +/doc/asio/reference/posix__basic_stream_descriptor/assign/overload1.html +/doc/asio/reference/posix__basic_stream_descriptor/assign/overload2.html +/doc/asio/reference/posix__basic_stream_descriptor/async_read_some.html +/doc/asio/reference/posix__basic_stream_descriptor/async_wait.html +/doc/asio/reference/posix__basic_stream_descriptor/async_write_some.html +/doc/asio/reference/posix__basic_stream_descriptor/basic_stream_descriptor/ +/doc/asio/reference/posix__basic_stream_descriptor/basic_stream_descriptor.html +/doc/asio/reference/posix__basic_stream_descriptor/basic_stream_descriptor/overload1.html +/doc/asio/reference/posix__basic_stream_descriptor/basic_stream_descriptor/overload2.html +/doc/asio/reference/posix__basic_stream_descriptor/basic_stream_descriptor/overload3.html +/doc/asio/reference/posix__basic_stream_descriptor/basic_stream_descriptor/overload4.html +/doc/asio/reference/posix__basic_stream_descriptor/basic_stream_descriptor/overload5.html +/doc/asio/reference/posix__basic_stream_descriptor/bytes_readable.html +/doc/asio/reference/posix__basic_stream_descriptor/cancel/ +/doc/asio/reference/posix__basic_stream_descriptor/cancel.html +/doc/asio/reference/posix__basic_stream_descriptor/cancel/overload1.html +/doc/asio/reference/posix__basic_stream_descriptor/cancel/overload2.html +/doc/asio/reference/posix__basic_stream_descriptor/close/ +/doc/asio/reference/posix__basic_stream_descriptor/close.html +/doc/asio/reference/posix__basic_stream_descriptor/close/overload1.html +/doc/asio/reference/posix__basic_stream_descriptor/close/overload2.html +/doc/asio/reference/posix__basic_stream_descriptor/executor_type.html +/doc/asio/reference/posix__basic_stream_descriptor/get_executor.html +/doc/asio/reference/posix__basic_stream_descriptor.html +/doc/asio/reference/posix__basic_stream_descriptor/impl_.html +/doc/asio/reference/posix__basic_stream_descriptor/io_control/ +/doc/asio/reference/posix__basic_stream_descriptor/io_control.html +/doc/asio/reference/posix__basic_stream_descriptor/io_control/overload1.html +/doc/asio/reference/posix__basic_stream_descriptor/io_control/overload2.html +/doc/asio/reference/posix__basic_stream_descriptor/is_open.html +/doc/asio/reference/posix__basic_stream_descriptor/lowest_layer/ +/doc/asio/reference/posix__basic_stream_descriptor/lowest_layer.html +/doc/asio/reference/posix__basic_stream_descriptor/lowest_layer/overload1.html +/doc/asio/reference/posix__basic_stream_descriptor/lowest_layer/overload2.html +/doc/asio/reference/posix__basic_stream_descriptor/lowest_layer_type.html +/doc/asio/reference/posix__basic_stream_descriptor/native_handle.html +/doc/asio/reference/posix__basic_stream_descriptor/native_handle_type.html +/doc/asio/reference/posix__basic_stream_descriptor/native_non_blocking/ +/doc/asio/reference/posix__basic_stream_descriptor/native_non_blocking.html +/doc/asio/reference/posix__basic_stream_descriptor/native_non_blocking/overload1.html +/doc/asio/reference/posix__basic_stream_descriptor/native_non_blocking/overload2.html +/doc/asio/reference/posix__basic_stream_descriptor/native_non_blocking/overload3.html +/doc/asio/reference/posix__basic_stream_descriptor/non_blocking/ +/doc/asio/reference/posix__basic_stream_descriptor/non_blocking.html +/doc/asio/reference/posix__basic_stream_descriptor/non_blocking/overload1.html +/doc/asio/reference/posix__basic_stream_descriptor/non_blocking/overload2.html +/doc/asio/reference/posix__basic_stream_descriptor/non_blocking/overload3.html +/doc/asio/reference/posix__basic_stream_descriptor/operator_eq_.html +/doc/asio/reference/posix__basic_stream_descriptor/read_some/ +/doc/asio/reference/posix__basic_stream_descriptor/read_some.html +/doc/asio/reference/posix__basic_stream_descriptor/read_some/overload1.html +/doc/asio/reference/posix__basic_stream_descriptor/read_some/overload2.html +/doc/asio/reference/posix__basic_stream_descriptor__rebind_executor/ +/doc/asio/reference/posix__basic_stream_descriptor__rebind_executor.html +/doc/asio/reference/posix__basic_stream_descriptor__rebind_executor/other.html +/doc/asio/reference/posix__basic_stream_descriptor/release.html +/doc/asio/reference/posix__basic_stream_descriptor/wait/ +/doc/asio/reference/posix__basic_stream_descriptor/wait.html +/doc/asio/reference/posix__basic_stream_descriptor/wait/overload1.html +/doc/asio/reference/posix__basic_stream_descriptor/wait/overload2.html +/doc/asio/reference/posix__basic_stream_descriptor/wait_type.html +/doc/asio/reference/posix__basic_stream_descriptor/write_some/ +/doc/asio/reference/posix__basic_stream_descriptor/write_some.html +/doc/asio/reference/posix__basic_stream_descriptor/write_some/overload1.html +/doc/asio/reference/posix__basic_stream_descriptor/write_some/overload2.html +/doc/asio/reference/posix__descriptor_base/ +/doc/asio/reference/posix__descriptor_base/bytes_readable.html +/doc/asio/reference/posix__descriptor_base/_descriptor_base.html +/doc/asio/reference/posix__descriptor_base.html +/doc/asio/reference/posix__descriptor_base/wait_type.html +/doc/asio/reference/posix__descriptor.html +/doc/asio/reference/posix__stream_descriptor.html +/doc/asio/reference/post/ +/doc/asio/reference/post.html +/doc/asio/reference/post/overload1.html +/doc/asio/reference/post/overload2.html +/doc/asio/reference/post/overload3.html +/doc/asio/reference/prefer.html +/doc/asio/reference/prefer_result/ +/doc/asio/reference/prefer_result.html +/doc/asio/reference/prefer_result/type.html +/doc/asio/reference/ProtoAllocator.html +/doc/asio/reference/Protocol.html +/doc/asio/reference/query.html +/doc/asio/reference/query_result/ +/doc/asio/reference/query_result.html +/doc/asio/reference/query_result/type.html +/doc/asio/reference/RangeConnectHandler.html +/doc/asio/reference/read/ +/doc/asio/reference/read_at/ +/doc/asio/reference/read_at.html +/doc/asio/reference/read_at/overload1.html +/doc/asio/reference/read_at/overload2.html +/doc/asio/reference/read_at/overload3.html +/doc/asio/reference/read_at/overload4.html +/doc/asio/reference/read_at/overload5.html +/doc/asio/reference/read_at/overload6.html +/doc/asio/reference/read_at/overload7.html +/doc/asio/reference/read_at/overload8.html +/doc/asio/reference/ReadHandler.html +/doc/asio/reference/read.html +/doc/asio/reference/read/overload10.html +/doc/asio/reference/read/overload11.html +/doc/asio/reference/read/overload12.html +/doc/asio/reference/read/overload13.html +/doc/asio/reference/read/overload14.html +/doc/asio/reference/read/overload15.html +/doc/asio/reference/read/overload16.html +/doc/asio/reference/read/overload1.html +/doc/asio/reference/read/overload2.html +/doc/asio/reference/read/overload3.html +/doc/asio/reference/read/overload4.html +/doc/asio/reference/read/overload5.html +/doc/asio/reference/read/overload6.html +/doc/asio/reference/read/overload7.html +/doc/asio/reference/read/overload8.html +/doc/asio/reference/read/overload9.html +/doc/asio/reference/read_until/ +/doc/asio/reference/read_until.html +/doc/asio/reference/read_until/overload10.html +/doc/asio/reference/read_until/overload11.html +/doc/asio/reference/read_until/overload12.html +/doc/asio/reference/read_until/overload13.html +/doc/asio/reference/read_until/overload14.html +/doc/asio/reference/read_until/overload15.html +/doc/asio/reference/read_until/overload16.html +/doc/asio/reference/read_until/overload17.html +/doc/asio/reference/read_until/overload18.html +/doc/asio/reference/read_until/overload19.html +/doc/asio/reference/read_until/overload1.html +/doc/asio/reference/read_until/overload20.html +/doc/asio/reference/read_until/overload21.html +/doc/asio/reference/read_until/overload22.html +/doc/asio/reference/read_until/overload23.html +/doc/asio/reference/read_until/overload24.html +/doc/asio/reference/read_until/overload2.html +/doc/asio/reference/read_until/overload3.html +/doc/asio/reference/read_until/overload4.html +/doc/asio/reference/read_until/overload5.html +/doc/asio/reference/read_until/overload6.html +/doc/asio/reference/read_until/overload7.html +/doc/asio/reference/read_until/overload8.html +/doc/asio/reference/read_until/overload9.html +/doc/asio/reference/read_write_operations.html +/doc/asio/reference/Receiver.html +/doc/asio/reference/redirect_error.html +/doc/asio/reference/redirect_error_t/ +/doc/asio/reference/redirect_error_t/ec_.html +/doc/asio/reference/redirect_error_t.html +/doc/asio/reference/redirect_error_t/redirect_error_t.html +/doc/asio/reference/redirect_error_t/token_.html +/doc/asio/reference/require_concept.html +/doc/asio/reference/require_concept_result/ +/doc/asio/reference/require_concept_result.html +/doc/asio/reference/require_concept_result/type.html +/doc/asio/reference/require.html +/doc/asio/reference/require_result/ +/doc/asio/reference/require_result.html +/doc/asio/reference/require_result/type.html +/doc/asio/reference/ResolveHandler.html +/doc/asio/reference/resolver_errc__try_again.html +/doc/asio/reference/Scheduler.html +/doc/asio/reference/Sender.html +/doc/asio/reference/serial_port_base/ +/doc/asio/reference/serial_port_base__baud_rate/ +/doc/asio/reference/serial_port_base__baud_rate/baud_rate.html +/doc/asio/reference/serial_port_base__baud_rate.html +/doc/asio/reference/serial_port_base__baud_rate/load.html +/doc/asio/reference/serial_port_base__baud_rate/store.html +/doc/asio/reference/serial_port_base__baud_rate/value.html +/doc/asio/reference/serial_port_base__character_size/ +/doc/asio/reference/serial_port_base__character_size/character_size.html +/doc/asio/reference/serial_port_base__character_size.html +/doc/asio/reference/serial_port_base__character_size/load.html +/doc/asio/reference/serial_port_base__character_size/store.html +/doc/asio/reference/serial_port_base__character_size/value.html +/doc/asio/reference/serial_port_base__flow_control/ +/doc/asio/reference/serial_port_base__flow_control/flow_control.html +/doc/asio/reference/serial_port_base__flow_control.html +/doc/asio/reference/serial_port_base__flow_control/load.html +/doc/asio/reference/serial_port_base__flow_control/store.html +/doc/asio/reference/serial_port_base__flow_control/type.html +/doc/asio/reference/serial_port_base__flow_control/value.html +/doc/asio/reference/serial_port_base.html +/doc/asio/reference/serial_port_base__parity/ +/doc/asio/reference/serial_port_base__parity.html +/doc/asio/reference/serial_port_base__parity/load.html +/doc/asio/reference/serial_port_base__parity/parity.html +/doc/asio/reference/serial_port_base__parity/store.html +/doc/asio/reference/serial_port_base__parity/type.html +/doc/asio/reference/serial_port_base__parity/value.html +/doc/asio/reference/serial_port_base/_serial_port_base.html +/doc/asio/reference/serial_port_base__stop_bits/ +/doc/asio/reference/serial_port_base__stop_bits.html +/doc/asio/reference/serial_port_base__stop_bits/load.html +/doc/asio/reference/serial_port_base__stop_bits/stop_bits.html +/doc/asio/reference/serial_port_base__stop_bits/store.html +/doc/asio/reference/serial_port_base__stop_bits/type.html +/doc/asio/reference/serial_port_base__stop_bits/value.html +/doc/asio/reference/serial_port.html +/doc/asio/reference/service_already_exists/ +/doc/asio/reference/service_already_exists.html +/doc/asio/reference/service_already_exists/service_already_exists.html +/doc/asio/reference/Service.html +/doc/asio/reference/SettableSerialPortOption.html +/doc/asio/reference/SettableSocketOption.html +/doc/asio/reference/ShutdownHandler.html +/doc/asio/reference/SignalHandler.html +/doc/asio/reference/signal_set.html +/doc/asio/reference/socket_base/ +/doc/asio/reference/socket_base/broadcast.html +/doc/asio/reference/socket_base/bytes_readable.html +/doc/asio/reference/socket_base/debug.html +/doc/asio/reference/socket_base/do_not_route.html +/doc/asio/reference/socket_base/enable_connection_aborted.html +/doc/asio/reference/socket_base.html +/doc/asio/reference/socket_base/keep_alive.html +/doc/asio/reference/socket_base/linger.html +/doc/asio/reference/socket_base/max_connections.html +/doc/asio/reference/socket_base/max_listen_connections.html +/doc/asio/reference/socket_base/message_do_not_route.html +/doc/asio/reference/socket_base/message_end_of_record.html +/doc/asio/reference/socket_base/message_flags.html +/doc/asio/reference/socket_base/message_out_of_band.html +/doc/asio/reference/socket_base/message_peek.html +/doc/asio/reference/socket_base/out_of_band_inline.html +/doc/asio/reference/socket_base/receive_buffer_size.html +/doc/asio/reference/socket_base/receive_low_watermark.html +/doc/asio/reference/socket_base/reuse_address.html +/doc/asio/reference/socket_base/send_buffer_size.html +/doc/asio/reference/socket_base/send_low_watermark.html +/doc/asio/reference/socket_base/shutdown_type.html +/doc/asio/reference/socket_base/_socket_base.html +/doc/asio/reference/socket_base/wait_type.html +/doc/asio/reference/spawn/ +/doc/asio/reference/spawn.html +/doc/asio/reference/spawn/overload1.html +/doc/asio/reference/spawn/overload2.html +/doc/asio/reference/spawn/overload3.html +/doc/asio/reference/spawn/overload4.html +/doc/asio/reference/spawn/overload5.html +/doc/asio/reference/spawn/overload6.html +/doc/asio/reference/spawn/overload7.html +/doc/asio/reference/ssl__context/ +/doc/asio/reference/ssl__context/add_certificate_authority/ +/doc/asio/reference/ssl__context/add_certificate_authority.html +/doc/asio/reference/ssl__context/add_certificate_authority/overload1.html +/doc/asio/reference/ssl__context/add_certificate_authority/overload2.html +/doc/asio/reference/ssl__context/add_verify_path/ +/doc/asio/reference/ssl__context/add_verify_path.html +/doc/asio/reference/ssl__context/add_verify_path/overload1.html +/doc/asio/reference/ssl__context/add_verify_path/overload2.html +/doc/asio/reference/ssl__context_base/ +/doc/asio/reference/ssl__context_base/_context_base.html +/doc/asio/reference/ssl__context_base/default_workarounds.html +/doc/asio/reference/ssl__context_base/file_format.html +/doc/asio/reference/ssl__context_base.html +/doc/asio/reference/ssl__context_base/method.html +/doc/asio/reference/ssl__context_base/no_compression.html +/doc/asio/reference/ssl__context_base/no_sslv2.html +/doc/asio/reference/ssl__context_base/no_sslv3.html +/doc/asio/reference/ssl__context_base/no_tlsv1_1.html +/doc/asio/reference/ssl__context_base/no_tlsv1_2.html +/doc/asio/reference/ssl__context_base/no_tlsv1_3.html +/doc/asio/reference/ssl__context_base/no_tlsv1.html +/doc/asio/reference/ssl__context_base/options.html +/doc/asio/reference/ssl__context_base/password_purpose.html +/doc/asio/reference/ssl__context_base/single_dh_use.html +/doc/asio/reference/ssl__context/clear_options/ +/doc/asio/reference/ssl__context/clear_options.html +/doc/asio/reference/ssl__context/clear_options/overload1.html +/doc/asio/reference/ssl__context/clear_options/overload2.html +/doc/asio/reference/ssl__context/context/ +/doc/asio/reference/ssl__context/_context.html +/doc/asio/reference/ssl__context/context.html +/doc/asio/reference/ssl__context/context/overload1.html +/doc/asio/reference/ssl__context/context/overload2.html +/doc/asio/reference/ssl__context/context/overload3.html +/doc/asio/reference/ssl__context/default_workarounds.html +/doc/asio/reference/ssl__context/file_format.html +/doc/asio/reference/ssl__context.html +/doc/asio/reference/ssl__context/load_verify_file/ +/doc/asio/reference/ssl__context/load_verify_file.html +/doc/asio/reference/ssl__context/load_verify_file/overload1.html +/doc/asio/reference/ssl__context/load_verify_file/overload2.html +/doc/asio/reference/ssl__context/method.html +/doc/asio/reference/ssl__context/native_handle.html +/doc/asio/reference/ssl__context/native_handle_type.html +/doc/asio/reference/ssl__context/no_compression.html +/doc/asio/reference/ssl__context/no_sslv2.html +/doc/asio/reference/ssl__context/no_sslv3.html +/doc/asio/reference/ssl__context/no_tlsv1_1.html +/doc/asio/reference/ssl__context/no_tlsv1_2.html +/doc/asio/reference/ssl__context/no_tlsv1_3.html +/doc/asio/reference/ssl__context/no_tlsv1.html +/doc/asio/reference/ssl__context/operator_eq_.html +/doc/asio/reference/ssl__context/options.html +/doc/asio/reference/ssl__context/password_purpose.html +/doc/asio/reference/ssl__context/set_default_verify_paths/ +/doc/asio/reference/ssl__context/set_default_verify_paths.html +/doc/asio/reference/ssl__context/set_default_verify_paths/overload1.html +/doc/asio/reference/ssl__context/set_default_verify_paths/overload2.html +/doc/asio/reference/ssl__context/set_options/ +/doc/asio/reference/ssl__context/set_options.html +/doc/asio/reference/ssl__context/set_options/overload1.html +/doc/asio/reference/ssl__context/set_options/overload2.html +/doc/asio/reference/ssl__context/set_password_callback/ +/doc/asio/reference/ssl__context/set_password_callback.html +/doc/asio/reference/ssl__context/set_password_callback/overload1.html +/doc/asio/reference/ssl__context/set_password_callback/overload2.html +/doc/asio/reference/ssl__context/set_verify_callback/ +/doc/asio/reference/ssl__context/set_verify_callback.html +/doc/asio/reference/ssl__context/set_verify_callback/overload1.html +/doc/asio/reference/ssl__context/set_verify_callback/overload2.html +/doc/asio/reference/ssl__context/set_verify_depth/ +/doc/asio/reference/ssl__context/set_verify_depth.html +/doc/asio/reference/ssl__context/set_verify_depth/overload1.html +/doc/asio/reference/ssl__context/set_verify_depth/overload2.html +/doc/asio/reference/ssl__context/set_verify_mode/ +/doc/asio/reference/ssl__context/set_verify_mode.html +/doc/asio/reference/ssl__context/set_verify_mode/overload1.html +/doc/asio/reference/ssl__context/set_verify_mode/overload2.html +/doc/asio/reference/ssl__context/single_dh_use.html +/doc/asio/reference/ssl__context/use_certificate/ +/doc/asio/reference/ssl__context/use_certificate_chain/ +/doc/asio/reference/ssl__context/use_certificate_chain_file/ +/doc/asio/reference/ssl__context/use_certificate_chain_file.html +/doc/asio/reference/ssl__context/use_certificate_chain_file/overload1.html +/doc/asio/reference/ssl__context/use_certificate_chain_file/overload2.html +/doc/asio/reference/ssl__context/use_certificate_chain.html +/doc/asio/reference/ssl__context/use_certificate_chain/overload1.html +/doc/asio/reference/ssl__context/use_certificate_chain/overload2.html +/doc/asio/reference/ssl__context/use_certificate_file/ +/doc/asio/reference/ssl__context/use_certificate_file.html +/doc/asio/reference/ssl__context/use_certificate_file/overload1.html +/doc/asio/reference/ssl__context/use_certificate_file/overload2.html +/doc/asio/reference/ssl__context/use_certificate.html +/doc/asio/reference/ssl__context/use_certificate/overload1.html +/doc/asio/reference/ssl__context/use_certificate/overload2.html +/doc/asio/reference/ssl__context/use_private_key/ +/doc/asio/reference/ssl__context/use_private_key_file/ +/doc/asio/reference/ssl__context/use_private_key_file.html +/doc/asio/reference/ssl__context/use_private_key_file/overload1.html +/doc/asio/reference/ssl__context/use_private_key_file/overload2.html +/doc/asio/reference/ssl__context/use_private_key.html +/doc/asio/reference/ssl__context/use_private_key/overload1.html +/doc/asio/reference/ssl__context/use_private_key/overload2.html +/doc/asio/reference/ssl__context/use_rsa_private_key/ +/doc/asio/reference/ssl__context/use_rsa_private_key_file/ +/doc/asio/reference/ssl__context/use_rsa_private_key_file.html +/doc/asio/reference/ssl__context/use_rsa_private_key_file/overload1.html +/doc/asio/reference/ssl__context/use_rsa_private_key_file/overload2.html +/doc/asio/reference/ssl__context/use_rsa_private_key.html +/doc/asio/reference/ssl__context/use_rsa_private_key/overload1.html +/doc/asio/reference/ssl__context/use_rsa_private_key/overload2.html +/doc/asio/reference/ssl__context/use_tmp_dh/ +/doc/asio/reference/ssl__context/use_tmp_dh_file/ +/doc/asio/reference/ssl__context/use_tmp_dh_file.html +/doc/asio/reference/ssl__context/use_tmp_dh_file/overload1.html +/doc/asio/reference/ssl__context/use_tmp_dh_file/overload2.html +/doc/asio/reference/ssl__context/use_tmp_dh.html +/doc/asio/reference/ssl__context/use_tmp_dh/overload1.html +/doc/asio/reference/ssl__context/use_tmp_dh/overload2.html +/doc/asio/reference/ssl__error__get_stream_category.html +/doc/asio/reference/ssl__error__make_error_code.html +/doc/asio/reference/ssl__error__stream_category.html +/doc/asio/reference/ssl__error__stream_errors.html +/doc/asio/reference/ssl__host_name_verification/ +/doc/asio/reference/ssl__host_name_verification/host_name_verification.html +/doc/asio/reference/ssl__host_name_verification.html +/doc/asio/reference/ssl__host_name_verification/operator_lp__rp_.html +/doc/asio/reference/ssl__host_name_verification/result_type.html +/doc/asio/reference/ssl__rfc2818_verification/ +/doc/asio/reference/ssl__rfc2818_verification.html +/doc/asio/reference/ssl__rfc2818_verification/operator_lp__rp_.html +/doc/asio/reference/ssl__rfc2818_verification/result_type.html +/doc/asio/reference/ssl__rfc2818_verification/rfc2818_verification.html +/doc/asio/reference/ssl__stream/ +/doc/asio/reference/ssl__stream/async_handshake/ +/doc/asio/reference/ssl__stream/async_handshake.html +/doc/asio/reference/ssl__stream/async_handshake/overload1.html +/doc/asio/reference/ssl__stream/async_handshake/overload2.html +/doc/asio/reference/ssl__stream/async_read_some.html +/doc/asio/reference/ssl__stream/async_shutdown.html +/doc/asio/reference/ssl__stream/async_write_some.html +/doc/asio/reference/ssl__stream_base/ +/doc/asio/reference/ssl__stream_base/handshake_type.html +/doc/asio/reference/ssl__stream_base.html +/doc/asio/reference/ssl__stream_base/_stream_base.html +/doc/asio/reference/ssl__stream/executor_type.html +/doc/asio/reference/ssl__stream/get_executor.html +/doc/asio/reference/ssl__stream/handshake/ +/doc/asio/reference/ssl__stream/handshake.html +/doc/asio/reference/ssl__stream/handshake/overload1.html +/doc/asio/reference/ssl__stream/handshake/overload2.html +/doc/asio/reference/ssl__stream/handshake/overload3.html +/doc/asio/reference/ssl__stream/handshake/overload4.html +/doc/asio/reference/ssl__stream/handshake_type.html +/doc/asio/reference/ssl__stream.html +/doc/asio/reference/ssl__stream__impl_struct/ +/doc/asio/reference/ssl__stream__impl_struct.html +/doc/asio/reference/ssl__stream__impl_struct/ssl.html +/doc/asio/reference/ssl__stream/lowest_layer/ +/doc/asio/reference/ssl__stream/lowest_layer.html +/doc/asio/reference/ssl__stream/lowest_layer/overload1.html +/doc/asio/reference/ssl__stream/lowest_layer/overload2.html +/doc/asio/reference/ssl__stream/lowest_layer_type.html +/doc/asio/reference/ssl__stream/native_handle.html +/doc/asio/reference/ssl__stream/native_handle_type.html +/doc/asio/reference/ssl__stream/next_layer/ +/doc/asio/reference/ssl__stream/next_layer.html +/doc/asio/reference/ssl__stream/next_layer/overload1.html +/doc/asio/reference/ssl__stream/next_layer/overload2.html +/doc/asio/reference/ssl__stream/next_layer_type.html +/doc/asio/reference/ssl__stream/read_some/ +/doc/asio/reference/ssl__stream/read_some.html +/doc/asio/reference/ssl__stream/read_some/overload1.html +/doc/asio/reference/ssl__stream/read_some/overload2.html +/doc/asio/reference/ssl__stream/set_verify_callback/ +/doc/asio/reference/ssl__stream/set_verify_callback.html +/doc/asio/reference/ssl__stream/set_verify_callback/overload1.html +/doc/asio/reference/ssl__stream/set_verify_callback/overload2.html +/doc/asio/reference/ssl__stream/set_verify_depth/ +/doc/asio/reference/ssl__stream/set_verify_depth.html +/doc/asio/reference/ssl__stream/set_verify_depth/overload1.html +/doc/asio/reference/ssl__stream/set_verify_depth/overload2.html +/doc/asio/reference/ssl__stream/set_verify_mode/ +/doc/asio/reference/ssl__stream/set_verify_mode.html +/doc/asio/reference/ssl__stream/set_verify_mode/overload1.html +/doc/asio/reference/ssl__stream/set_verify_mode/overload2.html +/doc/asio/reference/ssl__stream/shutdown/ +/doc/asio/reference/ssl__stream/shutdown.html +/doc/asio/reference/ssl__stream/shutdown/overload1.html +/doc/asio/reference/ssl__stream/shutdown/overload2.html +/doc/asio/reference/ssl__stream/stream/ +/doc/asio/reference/ssl__stream/_stream.html +/doc/asio/reference/ssl__stream/stream.html +/doc/asio/reference/ssl__stream/stream/overload1.html +/doc/asio/reference/ssl__stream/stream/overload2.html +/doc/asio/reference/ssl__stream/write_some/ +/doc/asio/reference/ssl__stream/write_some.html +/doc/asio/reference/ssl__stream/write_some/overload1.html +/doc/asio/reference/ssl__stream/write_some/overload2.html +/doc/asio/reference/ssl__verify_client_once.html +/doc/asio/reference/ssl__verify_context/ +/doc/asio/reference/ssl__verify_context.html +/doc/asio/reference/ssl__verify_context/native_handle.html +/doc/asio/reference/ssl__verify_context/native_handle_type.html +/doc/asio/reference/ssl__verify_context/verify_context.html +/doc/asio/reference/ssl__verify_fail_if_no_peer_cert.html +/doc/asio/reference/ssl__verify_mode.html +/doc/asio/reference/ssl__verify_none.html +/doc/asio/reference/ssl__verify_peer.html +/doc/asio/reference/static_thread_pool.html +/doc/asio/reference/steady_timer.html +/doc/asio/reference/strand/ +/doc/asio/reference/strand/defer.html +/doc/asio/reference/strand/dispatch.html +/doc/asio/reference/strand/execute.html +/doc/asio/reference/strand/get_inner_executor.html +/doc/asio/reference/strand.html +/doc/asio/reference/strand/inner_executor_type.html +/doc/asio/reference/strand/operator_eq_/ +/doc/asio/reference/strand/operator_eq__eq_.html +/doc/asio/reference/strand/operator_eq_.html +/doc/asio/reference/strand/operator_eq_/overload1.html +/doc/asio/reference/strand/operator_eq_/overload2.html +/doc/asio/reference/strand/operator_eq_/overload3.html +/doc/asio/reference/strand/operator_eq_/overload4.html +/doc/asio/reference/strand/operator_not__eq_.html +/doc/asio/reference/strand/post.html +/doc/asio/reference/strand/prefer.html +/doc/asio/reference/strand/query.html +/doc/asio/reference/strand/require.html +/doc/asio/reference/strand/running_in_this_thread.html +/doc/asio/reference/strand/strand/ +/doc/asio/reference/strand/_strand.html +/doc/asio/reference/strand/strand.html +/doc/asio/reference/strand/strand/overload1.html +/doc/asio/reference/strand/strand/overload2.html +/doc/asio/reference/strand/strand/overload3.html +/doc/asio/reference/strand/strand/overload4.html +/doc/asio/reference/strand/strand/overload5.html +/doc/asio/reference/strand/strand/overload6.html +/doc/asio/reference/streambuf.html +/doc/asio/reference/synchronous_socket_operations.html +/doc/asio/reference/SyncRandomAccessReadDevice.html +/doc/asio/reference/SyncRandomAccessWriteDevice.html +/doc/asio/reference/SyncReadStream.html +/doc/asio/reference/SyncWriteStream.html +/doc/asio/reference/system_category.html +/doc/asio/reference/system_context/ +/doc/asio/reference/system_context/add_service.html +/doc/asio/reference/system_context/destroy.html +/doc/asio/reference/system_context/executor_type.html +/doc/asio/reference/system_context/fork_event.html +/doc/asio/reference/system_context/get_executor.html +/doc/asio/reference/system_context/has_service.html +/doc/asio/reference/system_context.html +/doc/asio/reference/system_context/join.html +/doc/asio/reference/system_context/make_service.html +/doc/asio/reference/system_context/notify_fork.html +/doc/asio/reference/system_context/shutdown.html +/doc/asio/reference/system_context/stop.html +/doc/asio/reference/system_context/stopped.html +/doc/asio/reference/system_context/_system_context.html +/doc/asio/reference/system_context/use_service/ +/doc/asio/reference/system_context/use_service.html +/doc/asio/reference/system_context/use_service/overload1.html +/doc/asio/reference/system_context/use_service/overload2.html +/doc/asio/reference/system_error/ +/doc/asio/reference/system_error/code.html +/doc/asio/reference/system_error.html +/doc/asio/reference/system_error/operator_eq_.html +/doc/asio/reference/system_error/system_error/ +/doc/asio/reference/system_error/_system_error.html +/doc/asio/reference/system_error/system_error.html +/doc/asio/reference/system_error/system_error/overload1.html +/doc/asio/reference/system_error/system_error/overload2.html +/doc/asio/reference/system_error/system_error/overload3.html +/doc/asio/reference/system_error/what.html +/doc/asio/reference/system_executor.html +/doc/asio/reference/system_timer.html +/doc/asio/reference/this_coro__executor.html +/doc/asio/reference/this_coro__executor_t/ +/doc/asio/reference/this_coro__executor_t/executor_t.html +/doc/asio/reference/this_coro__executor_t.html +/doc/asio/reference/thread/ +/doc/asio/reference/thread.html +/doc/asio/reference/thread/join.html +/doc/asio/reference/thread_pool/ +/doc/asio/reference/thread_pool/add_service.html +/doc/asio/reference/thread_pool/attach.html +/doc/asio/reference/thread_pool__basic_executor_type/ +/doc/asio/reference/thread_pool__basic_executor_type/basic_executor_type/ +/doc/asio/reference/thread_pool__basic_executor_type/_basic_executor_type.html +/doc/asio/reference/thread_pool__basic_executor_type/basic_executor_type.html +/doc/asio/reference/thread_pool__basic_executor_type/basic_executor_type/overload1.html +/doc/asio/reference/thread_pool__basic_executor_type/basic_executor_type/overload2.html +/doc/asio/reference/thread_pool__basic_executor_type/bulk_execute.html +/doc/asio/reference/thread_pool__basic_executor_type/context.html +/doc/asio/reference/thread_pool__basic_executor_type/defer.html +/doc/asio/reference/thread_pool__basic_executor_type/dispatch.html +/doc/asio/reference/thread_pool__basic_executor_type/execute.html +/doc/asio/reference/thread_pool__basic_executor_type.html +/doc/asio/reference/thread_pool__basic_executor_type/on_work_finished.html +/doc/asio/reference/thread_pool__basic_executor_type/on_work_started.html +/doc/asio/reference/thread_pool__basic_executor_type/operator_eq_/ +/doc/asio/reference/thread_pool__basic_executor_type/operator_eq__eq_.html +/doc/asio/reference/thread_pool__basic_executor_type/operator_eq_.html +/doc/asio/reference/thread_pool__basic_executor_type/operator_eq_/overload1.html +/doc/asio/reference/thread_pool__basic_executor_type/operator_eq_/overload2.html +/doc/asio/reference/thread_pool__basic_executor_type/operator_not__eq_.html +/doc/asio/reference/thread_pool__basic_executor_type/post.html +/doc/asio/reference/thread_pool__basic_executor_type/query/ +/doc/asio/reference/thread_pool__basic_executor_type/query.html +/doc/asio/reference/thread_pool__basic_executor_type/query/overload1.html +/doc/asio/reference/thread_pool__basic_executor_type/query/overload2.html +/doc/asio/reference/thread_pool__basic_executor_type/query/overload3.html +/doc/asio/reference/thread_pool__basic_executor_type/query/overload4.html +/doc/asio/reference/thread_pool__basic_executor_type/query/overload5.html +/doc/asio/reference/thread_pool__basic_executor_type/query/overload6.html +/doc/asio/reference/thread_pool__basic_executor_type/query__static/ +/doc/asio/reference/thread_pool__basic_executor_type/query__static.html +/doc/asio/reference/thread_pool__basic_executor_type/query__static/overload1.html +/doc/asio/reference/thread_pool__basic_executor_type/query__static/overload2.html +/doc/asio/reference/thread_pool__basic_executor_type/query__static/overload3.html +/doc/asio/reference/thread_pool__basic_executor_type/require/ +/doc/asio/reference/thread_pool__basic_executor_type/require.html +/doc/asio/reference/thread_pool__basic_executor_type/require/overload1.html +/doc/asio/reference/thread_pool__basic_executor_type/require/overload2.html +/doc/asio/reference/thread_pool__basic_executor_type/require/overload3.html +/doc/asio/reference/thread_pool__basic_executor_type/require/overload4.html +/doc/asio/reference/thread_pool__basic_executor_type/require/overload5.html +/doc/asio/reference/thread_pool__basic_executor_type/require/overload6.html +/doc/asio/reference/thread_pool__basic_executor_type/require/overload7.html +/doc/asio/reference/thread_pool__basic_executor_type/require/overload8.html +/doc/asio/reference/thread_pool__basic_executor_type/require/overload9.html +/doc/asio/reference/thread_pool__basic_executor_type/running_in_this_thread.html +/doc/asio/reference/thread_pool__basic_executor_type/schedule.html +/doc/asio/reference/thread_pool__basic_executor_type/sender_type.html +/doc/asio/reference/thread_pool/destroy.html +/doc/asio/reference/thread_pool/executor.html +/doc/asio/reference/thread_pool/executor_type.html +/doc/asio/reference/thread_pool/fork_event.html +/doc/asio/reference/thread_pool/get_executor.html +/doc/asio/reference/thread_pool/has_service.html +/doc/asio/reference/thread_pool.html +/doc/asio/reference/thread_pool/join.html +/doc/asio/reference/thread_pool/make_service.html +/doc/asio/reference/thread_pool/notify_fork.html +/doc/asio/reference/thread_pool/scheduler.html +/doc/asio/reference/thread_pool/scheduler_type.html +/doc/asio/reference/thread_pool/shutdown.html +/doc/asio/reference/thread_pool/stop.html +/doc/asio/reference/thread_pool/thread_pool/ +/doc/asio/reference/thread_pool/_thread_pool.html +/doc/asio/reference/thread_pool/thread_pool.html +/doc/asio/reference/thread_pool/thread_pool/overload1.html +/doc/asio/reference/thread_pool/thread_pool/overload2.html +/doc/asio/reference/thread_pool/use_service/ +/doc/asio/reference/thread_pool/use_service.html +/doc/asio/reference/thread_pool/use_service/overload1.html +/doc/asio/reference/thread_pool/use_service/overload2.html +/doc/asio/reference/thread_pool/wait.html +/doc/asio/reference/thread/_thread.html +/doc/asio/reference/thread/thread.html +/doc/asio/reference/TimeTraits.html +/doc/asio/reference/time_traits_lt__ptime__gt_/ +/doc/asio/reference/time_traits_lt__ptime__gt_/add.html +/doc/asio/reference/time_traits_lt__ptime__gt_/duration_type.html +/doc/asio/reference/time_traits_lt__ptime__gt_.html +/doc/asio/reference/time_traits_lt__ptime__gt_/less_than.html +/doc/asio/reference/time_traits_lt__ptime__gt_/now.html +/doc/asio/reference/time_traits_lt__ptime__gt_/subtract.html +/doc/asio/reference/time_traits_lt__ptime__gt_/time_type.html +/doc/asio/reference/time_traits_lt__ptime__gt_/to_posix_duration.html +/doc/asio/reference/transfer_all.html +/doc/asio/reference/transfer_at_least.html +/doc/asio/reference/transfer_exactly.html +/doc/asio/reference/use_awaitable.html +/doc/asio/reference/use_awaitable_t/ +/doc/asio/reference/use_awaitable_t/as_default_on.html +/doc/asio/reference/use_awaitable_t__executor_with_default/ +/doc/asio/reference/use_awaitable_t__executor_with_default/default_completion_token_type.html +/doc/asio/reference/use_awaitable_t__executor_with_default/executor_with_default/ +/doc/asio/reference/use_awaitable_t__executor_with_default/executor_with_default.html +/doc/asio/reference/use_awaitable_t__executor_with_default/executor_with_default/overload1.html +/doc/asio/reference/use_awaitable_t__executor_with_default/executor_with_default/overload2.html +/doc/asio/reference/use_awaitable_t__executor_with_default.html +/doc/asio/reference/use_awaitable_t.html +/doc/asio/reference/use_awaitable_t/use_awaitable_t/ +/doc/asio/reference/use_awaitable_t/use_awaitable_t.html +/doc/asio/reference/use_awaitable_t/use_awaitable_t/overload1.html +/doc/asio/reference/use_awaitable_t/use_awaitable_t/overload2.html +/doc/asio/reference/use_future.html +/doc/asio/reference/use_future_t/ +/doc/asio/reference/use_future_t/allocator_type.html +/doc/asio/reference/use_future_t/get_allocator.html +/doc/asio/reference/use_future_t.html +/doc/asio/reference/use_future_t/operator_lb__rb_.html +/doc/asio/reference/use_future_t/operator_lp__rp_.html +/doc/asio/reference/use_future_t/rebind.html +/doc/asio/reference/use_future_t/use_future_t/ +/doc/asio/reference/use_future_t/use_future_t.html +/doc/asio/reference/use_future_t/use_future_t/overload1.html +/doc/asio/reference/use_future_t/use_future_t/overload2.html +/doc/asio/reference/uses_executor.html +/doc/asio/reference/WaitHandler.html +/doc/asio/reference/wait_traits/ +/doc/asio/reference/WaitTraits.html +/doc/asio/reference/wait_traits.html +/doc/asio/reference/wait_traits/to_wait_duration/ +/doc/asio/reference/wait_traits/to_wait_duration.html +/doc/asio/reference/wait_traits/to_wait_duration/overload1.html +/doc/asio/reference/wait_traits/to_wait_duration/overload2.html +/doc/asio/reference/windows__basic_object_handle/ +/doc/asio/reference/windows__basic_object_handle/assign/ +/doc/asio/reference/windows__basic_object_handle/assign.html +/doc/asio/reference/windows__basic_object_handle/assign/overload1.html +/doc/asio/reference/windows__basic_object_handle/assign/overload2.html +/doc/asio/reference/windows__basic_object_handle/async_wait.html +/doc/asio/reference/windows__basic_object_handle/basic_object_handle/ +/doc/asio/reference/windows__basic_object_handle/basic_object_handle.html +/doc/asio/reference/windows__basic_object_handle/basic_object_handle/overload1.html +/doc/asio/reference/windows__basic_object_handle/basic_object_handle/overload2.html +/doc/asio/reference/windows__basic_object_handle/basic_object_handle/overload3.html +/doc/asio/reference/windows__basic_object_handle/basic_object_handle/overload4.html +/doc/asio/reference/windows__basic_object_handle/basic_object_handle/overload5.html +/doc/asio/reference/windows__basic_object_handle/cancel/ +/doc/asio/reference/windows__basic_object_handle/cancel.html +/doc/asio/reference/windows__basic_object_handle/cancel/overload1.html +/doc/asio/reference/windows__basic_object_handle/cancel/overload2.html +/doc/asio/reference/windows__basic_object_handle/close/ +/doc/asio/reference/windows__basic_object_handle/close.html +/doc/asio/reference/windows__basic_object_handle/close/overload1.html +/doc/asio/reference/windows__basic_object_handle/close/overload2.html +/doc/asio/reference/windows__basic_object_handle/executor_type.html +/doc/asio/reference/windows__basic_object_handle/get_executor.html +/doc/asio/reference/windows__basic_object_handle.html +/doc/asio/reference/windows__basic_object_handle/is_open.html +/doc/asio/reference/windows__basic_object_handle/lowest_layer/ +/doc/asio/reference/windows__basic_object_handle/lowest_layer.html +/doc/asio/reference/windows__basic_object_handle/lowest_layer/overload1.html +/doc/asio/reference/windows__basic_object_handle/lowest_layer/overload2.html +/doc/asio/reference/windows__basic_object_handle/lowest_layer_type.html +/doc/asio/reference/windows__basic_object_handle/native_handle.html +/doc/asio/reference/windows__basic_object_handle/native_handle_type.html +/doc/asio/reference/windows__basic_object_handle/operator_eq_.html +/doc/asio/reference/windows__basic_object_handle__rebind_executor/ +/doc/asio/reference/windows__basic_object_handle__rebind_executor.html +/doc/asio/reference/windows__basic_object_handle__rebind_executor/other.html +/doc/asio/reference/windows__basic_object_handle/wait/ +/doc/asio/reference/windows__basic_object_handle/wait.html +/doc/asio/reference/windows__basic_object_handle/wait/overload1.html +/doc/asio/reference/windows__basic_object_handle/wait/overload2.html +/doc/asio/reference/windows__basic_overlapped_handle/ +/doc/asio/reference/windows__basic_overlapped_handle/assign/ +/doc/asio/reference/windows__basic_overlapped_handle/assign.html +/doc/asio/reference/windows__basic_overlapped_handle/assign/overload1.html +/doc/asio/reference/windows__basic_overlapped_handle/assign/overload2.html +/doc/asio/reference/windows__basic_overlapped_handle/basic_overlapped_handle/ +/doc/asio/reference/windows__basic_overlapped_handle/_basic_overlapped_handle.html +/doc/asio/reference/windows__basic_overlapped_handle/basic_overlapped_handle.html +/doc/asio/reference/windows__basic_overlapped_handle/basic_overlapped_handle/overload1.html +/doc/asio/reference/windows__basic_overlapped_handle/basic_overlapped_handle/overload2.html +/doc/asio/reference/windows__basic_overlapped_handle/basic_overlapped_handle/overload3.html +/doc/asio/reference/windows__basic_overlapped_handle/basic_overlapped_handle/overload4.html +/doc/asio/reference/windows__basic_overlapped_handle/basic_overlapped_handle/overload5.html +/doc/asio/reference/windows__basic_overlapped_handle/cancel/ +/doc/asio/reference/windows__basic_overlapped_handle/cancel.html +/doc/asio/reference/windows__basic_overlapped_handle/cancel/overload1.html +/doc/asio/reference/windows__basic_overlapped_handle/cancel/overload2.html +/doc/asio/reference/windows__basic_overlapped_handle/close/ +/doc/asio/reference/windows__basic_overlapped_handle/close.html +/doc/asio/reference/windows__basic_overlapped_handle/close/overload1.html +/doc/asio/reference/windows__basic_overlapped_handle/close/overload2.html +/doc/asio/reference/windows__basic_overlapped_handle/executor_type.html +/doc/asio/reference/windows__basic_overlapped_handle/get_executor.html +/doc/asio/reference/windows__basic_overlapped_handle.html +/doc/asio/reference/windows__basic_overlapped_handle/impl_.html +/doc/asio/reference/windows__basic_overlapped_handle/is_open.html +/doc/asio/reference/windows__basic_overlapped_handle/lowest_layer/ +/doc/asio/reference/windows__basic_overlapped_handle/lowest_layer.html +/doc/asio/reference/windows__basic_overlapped_handle/lowest_layer/overload1.html +/doc/asio/reference/windows__basic_overlapped_handle/lowest_layer/overload2.html +/doc/asio/reference/windows__basic_overlapped_handle/lowest_layer_type.html +/doc/asio/reference/windows__basic_overlapped_handle/native_handle.html +/doc/asio/reference/windows__basic_overlapped_handle/native_handle_type.html +/doc/asio/reference/windows__basic_overlapped_handle/operator_eq_.html +/doc/asio/reference/windows__basic_overlapped_handle__rebind_executor/ +/doc/asio/reference/windows__basic_overlapped_handle__rebind_executor.html +/doc/asio/reference/windows__basic_overlapped_handle__rebind_executor/other.html +/doc/asio/reference/windows__basic_random_access_handle/ +/doc/asio/reference/windows__basic_random_access_handle/assign/ +/doc/asio/reference/windows__basic_random_access_handle/assign.html +/doc/asio/reference/windows__basic_random_access_handle/assign/overload1.html +/doc/asio/reference/windows__basic_random_access_handle/assign/overload2.html +/doc/asio/reference/windows__basic_random_access_handle/async_read_some_at.html +/doc/asio/reference/windows__basic_random_access_handle/async_write_some_at.html +/doc/asio/reference/windows__basic_random_access_handle/basic_random_access_handle/ +/doc/asio/reference/windows__basic_random_access_handle/basic_random_access_handle.html +/doc/asio/reference/windows__basic_random_access_handle/basic_random_access_handle/overload1.html +/doc/asio/reference/windows__basic_random_access_handle/basic_random_access_handle/overload2.html +/doc/asio/reference/windows__basic_random_access_handle/basic_random_access_handle/overload3.html +/doc/asio/reference/windows__basic_random_access_handle/basic_random_access_handle/overload4.html +/doc/asio/reference/windows__basic_random_access_handle/basic_random_access_handle/overload5.html +/doc/asio/reference/windows__basic_random_access_handle/cancel/ +/doc/asio/reference/windows__basic_random_access_handle/cancel.html +/doc/asio/reference/windows__basic_random_access_handle/cancel/overload1.html +/doc/asio/reference/windows__basic_random_access_handle/cancel/overload2.html +/doc/asio/reference/windows__basic_random_access_handle/close/ +/doc/asio/reference/windows__basic_random_access_handle/close.html +/doc/asio/reference/windows__basic_random_access_handle/close/overload1.html +/doc/asio/reference/windows__basic_random_access_handle/close/overload2.html +/doc/asio/reference/windows__basic_random_access_handle/executor_type.html +/doc/asio/reference/windows__basic_random_access_handle/get_executor.html +/doc/asio/reference/windows__basic_random_access_handle.html +/doc/asio/reference/windows__basic_random_access_handle/impl_.html +/doc/asio/reference/windows__basic_random_access_handle/is_open.html +/doc/asio/reference/windows__basic_random_access_handle/lowest_layer/ +/doc/asio/reference/windows__basic_random_access_handle/lowest_layer.html +/doc/asio/reference/windows__basic_random_access_handle/lowest_layer/overload1.html +/doc/asio/reference/windows__basic_random_access_handle/lowest_layer/overload2.html +/doc/asio/reference/windows__basic_random_access_handle/lowest_layer_type.html +/doc/asio/reference/windows__basic_random_access_handle/native_handle.html +/doc/asio/reference/windows__basic_random_access_handle/native_handle_type.html +/doc/asio/reference/windows__basic_random_access_handle/operator_eq_.html +/doc/asio/reference/windows__basic_random_access_handle/read_some_at/ +/doc/asio/reference/windows__basic_random_access_handle/read_some_at.html +/doc/asio/reference/windows__basic_random_access_handle/read_some_at/overload1.html +/doc/asio/reference/windows__basic_random_access_handle/read_some_at/overload2.html +/doc/asio/reference/windows__basic_random_access_handle__rebind_executor/ +/doc/asio/reference/windows__basic_random_access_handle__rebind_executor.html +/doc/asio/reference/windows__basic_random_access_handle__rebind_executor/other.html +/doc/asio/reference/windows__basic_random_access_handle/write_some_at/ +/doc/asio/reference/windows__basic_random_access_handle/write_some_at.html +/doc/asio/reference/windows__basic_random_access_handle/write_some_at/overload1.html +/doc/asio/reference/windows__basic_random_access_handle/write_some_at/overload2.html +/doc/asio/reference/windows__basic_stream_handle/ +/doc/asio/reference/windows__basic_stream_handle/assign/ +/doc/asio/reference/windows__basic_stream_handle/assign.html +/doc/asio/reference/windows__basic_stream_handle/assign/overload1.html +/doc/asio/reference/windows__basic_stream_handle/assign/overload2.html +/doc/asio/reference/windows__basic_stream_handle/async_read_some.html +/doc/asio/reference/windows__basic_stream_handle/async_write_some.html +/doc/asio/reference/windows__basic_stream_handle/basic_stream_handle/ +/doc/asio/reference/windows__basic_stream_handle/basic_stream_handle.html +/doc/asio/reference/windows__basic_stream_handle/basic_stream_handle/overload1.html +/doc/asio/reference/windows__basic_stream_handle/basic_stream_handle/overload2.html +/doc/asio/reference/windows__basic_stream_handle/basic_stream_handle/overload3.html +/doc/asio/reference/windows__basic_stream_handle/basic_stream_handle/overload4.html +/doc/asio/reference/windows__basic_stream_handle/basic_stream_handle/overload5.html +/doc/asio/reference/windows__basic_stream_handle/cancel/ +/doc/asio/reference/windows__basic_stream_handle/cancel.html +/doc/asio/reference/windows__basic_stream_handle/cancel/overload1.html +/doc/asio/reference/windows__basic_stream_handle/cancel/overload2.html +/doc/asio/reference/windows__basic_stream_handle/close/ +/doc/asio/reference/windows__basic_stream_handle/close.html +/doc/asio/reference/windows__basic_stream_handle/close/overload1.html +/doc/asio/reference/windows__basic_stream_handle/close/overload2.html +/doc/asio/reference/windows__basic_stream_handle/executor_type.html +/doc/asio/reference/windows__basic_stream_handle/get_executor.html +/doc/asio/reference/windows__basic_stream_handle.html +/doc/asio/reference/windows__basic_stream_handle/impl_.html +/doc/asio/reference/windows__basic_stream_handle/is_open.html +/doc/asio/reference/windows__basic_stream_handle/lowest_layer/ +/doc/asio/reference/windows__basic_stream_handle/lowest_layer.html +/doc/asio/reference/windows__basic_stream_handle/lowest_layer/overload1.html +/doc/asio/reference/windows__basic_stream_handle/lowest_layer/overload2.html +/doc/asio/reference/windows__basic_stream_handle/lowest_layer_type.html +/doc/asio/reference/windows__basic_stream_handle/native_handle.html +/doc/asio/reference/windows__basic_stream_handle/native_handle_type.html +/doc/asio/reference/windows__basic_stream_handle/operator_eq_.html +/doc/asio/reference/windows__basic_stream_handle/read_some/ +/doc/asio/reference/windows__basic_stream_handle/read_some.html +/doc/asio/reference/windows__basic_stream_handle/read_some/overload1.html +/doc/asio/reference/windows__basic_stream_handle/read_some/overload2.html +/doc/asio/reference/windows__basic_stream_handle__rebind_executor/ +/doc/asio/reference/windows__basic_stream_handle__rebind_executor.html +/doc/asio/reference/windows__basic_stream_handle__rebind_executor/other.html +/doc/asio/reference/windows__basic_stream_handle/write_some/ +/doc/asio/reference/windows__basic_stream_handle/write_some.html +/doc/asio/reference/windows__basic_stream_handle/write_some/overload1.html +/doc/asio/reference/windows__basic_stream_handle/write_some/overload2.html +/doc/asio/reference/windows__object_handle.html +/doc/asio/reference/windows__overlapped_handle.html +/doc/asio/reference/windows__overlapped_ptr/ +/doc/asio/reference/windows__overlapped_ptr/complete.html +/doc/asio/reference/windows__overlapped_ptr/get/ +/doc/asio/reference/windows__overlapped_ptr/get.html +/doc/asio/reference/windows__overlapped_ptr/get/overload1.html +/doc/asio/reference/windows__overlapped_ptr/get/overload2.html +/doc/asio/reference/windows__overlapped_ptr.html +/doc/asio/reference/windows__overlapped_ptr/overlapped_ptr/ +/doc/asio/reference/windows__overlapped_ptr/_overlapped_ptr.html +/doc/asio/reference/windows__overlapped_ptr/overlapped_ptr.html +/doc/asio/reference/windows__overlapped_ptr/overlapped_ptr/overload1.html +/doc/asio/reference/windows__overlapped_ptr/overlapped_ptr/overload2.html +/doc/asio/reference/windows__overlapped_ptr/overlapped_ptr/overload3.html +/doc/asio/reference/windows__overlapped_ptr/release.html +/doc/asio/reference/windows__overlapped_ptr/reset/ +/doc/asio/reference/windows__overlapped_ptr/reset.html +/doc/asio/reference/windows__overlapped_ptr/reset/overload1.html +/doc/asio/reference/windows__overlapped_ptr/reset/overload2.html +/doc/asio/reference/windows__overlapped_ptr/reset/overload3.html +/doc/asio/reference/windows__random_access_handle.html +/doc/asio/reference/windows__stream_handle.html +/doc/asio/reference/write/ +/doc/asio/reference/write_at/ +/doc/asio/reference/write_at.html +/doc/asio/reference/write_at/overload1.html +/doc/asio/reference/write_at/overload2.html +/doc/asio/reference/write_at/overload3.html +/doc/asio/reference/write_at/overload4.html +/doc/asio/reference/write_at/overload5.html +/doc/asio/reference/write_at/overload6.html +/doc/asio/reference/write_at/overload7.html +/doc/asio/reference/write_at/overload8.html +/doc/asio/reference/WriteHandler.html +/doc/asio/reference/write.html +/doc/asio/reference/write/overload10.html +/doc/asio/reference/write/overload11.html +/doc/asio/reference/write/overload12.html +/doc/asio/reference/write/overload13.html +/doc/asio/reference/write/overload14.html +/doc/asio/reference/write/overload15.html +/doc/asio/reference/write/overload16.html +/doc/asio/reference/write/overload1.html +/doc/asio/reference/write/overload2.html +/doc/asio/reference/write/overload3.html +/doc/asio/reference/write/overload4.html +/doc/asio/reference/write/overload5.html +/doc/asio/reference/write/overload6.html +/doc/asio/reference/write/overload7.html +/doc/asio/reference/write/overload8.html +/doc/asio/reference/write/overload9.html +/doc/asio/reference/yield_context.html +/doc/asio/tutorial/ +/doc/asio/tutorial/boost_bind.html +/doc/asio/tutorial.html +/doc/asio/tutorial/tutdaytime1/ +/doc/asio/tutorial/tutdaytime1.html +/doc/asio/tutorial/tutdaytime1/src.html +/doc/asio/tutorial/tutdaytime2/ +/doc/asio/tutorial/tutdaytime2.html +/doc/asio/tutorial/tutdaytime2/src.html +/doc/asio/tutorial/tutdaytime3/ +/doc/asio/tutorial/tutdaytime3.html +/doc/asio/tutorial/tutdaytime3/src.html +/doc/asio/tutorial/tutdaytime4/ +/doc/asio/tutorial/tutdaytime4.html +/doc/asio/tutorial/tutdaytime4/src.html +/doc/asio/tutorial/tutdaytime5/ +/doc/asio/tutorial/tutdaytime5.html +/doc/asio/tutorial/tutdaytime5/src.html +/doc/asio/tutorial/tutdaytime6/ +/doc/asio/tutorial/tutdaytime6.html +/doc/asio/tutorial/tutdaytime6/src.html +/doc/asio/tutorial/tutdaytime7/ +/doc/asio/tutorial/tutdaytime7.html +/doc/asio/tutorial/tutdaytime7/src.html +/doc/asio/tutorial/tuttimer1/ +/doc/asio/tutorial/tuttimer1.html +/doc/asio/tutorial/tuttimer1/src.html +/doc/asio/tutorial/tuttimer2/ +/doc/asio/tutorial/tuttimer2.html +/doc/asio/tutorial/tuttimer2/src.html +/doc/asio/tutorial/tuttimer3/ +/doc/asio/tutorial/tuttimer3.html +/doc/asio/tutorial/tuttimer3/src.html +/doc/asio/tutorial/tuttimer4/ +/doc/asio/tutorial/tuttimer4.html +/doc/asio/tutorial/tuttimer4/src.html +/doc/asio/tutorial/tuttimer5/ +/doc/asio/tutorial/tuttimer5.html +/doc/asio/tutorial/tuttimer5/src.html +/doc/asio/using.html +/doc/async_op1.png +/doc/async_op2.png +/doc/blank.png +/doc/boostbook.css +/doc/caution.png +/doc/draft.png +/doc/examples/ +/doc/examples/diffs/ +/doc/examples/diffs/allocation/ +/doc/examples/diffs/allocation/server.cpp.html +/doc/examples/diffs/buffers/ +/doc/examples/diffs/buffers/reference_counted.cpp.html +/doc/examples/diffs/chat/ +/doc/examples/diffs/chat/chat_client.cpp.html +/doc/examples/diffs/chat/chat_message.hpp.html +/doc/examples/diffs/chat/chat_server.cpp.html +/doc/examples/diffs/echo/ +/doc/examples/diffs/echo/async_tcp_echo_server.cpp.html +/doc/examples/diffs/echo/async_udp_echo_server.cpp.html +/doc/examples/diffs/echo/blocking_tcp_echo_client.cpp.html +/doc/examples/diffs/echo/blocking_tcp_echo_server.cpp.html +/doc/examples/diffs/echo/blocking_udp_echo_client.cpp.html +/doc/examples/diffs/echo/blocking_udp_echo_server.cpp.html +/doc/examples/diffs/executors/ +/doc/examples/diffs/executors/actor.cpp.html +/doc/examples/diffs/executors/bank_account_1.cpp.html +/doc/examples/diffs/executors/bank_account_2.cpp.html +/doc/examples/diffs/executors/fork_join.cpp.html +/doc/examples/diffs/executors/pipeline.cpp.html +/doc/examples/diffs/executors/priority_scheduler.cpp.html +/doc/examples/diffs/fork/ +/doc/examples/diffs/fork/daemon.cpp.html +/doc/examples/diffs/fork/process_per_connection.cpp.html +/doc/examples/diffs/futures/ +/doc/examples/diffs/futures/daytime_client.cpp.html +/doc/examples/diffs/handler_tracking/ +/doc/examples/diffs/handler_tracking/async_tcp_echo_server.cpp.html +/doc/examples/diffs/handler_tracking/custom_tracking.hpp.html +/doc/examples/diffs/http/ +/doc/examples/diffs/http/server/ +/doc/examples/diffs/http/server/connection.cpp.html +/doc/examples/diffs/http/server/connection.hpp.html +/doc/examples/diffs/http/server/connection_manager.cpp.html +/doc/examples/diffs/http/server/connection_manager.hpp.html +/doc/examples/diffs/http/server/header.hpp.html +/doc/examples/diffs/http/server/main.cpp.html +/doc/examples/diffs/http/server/mime_types.cpp.html +/doc/examples/diffs/http/server/mime_types.hpp.html +/doc/examples/diffs/http/server/reply.cpp.html +/doc/examples/diffs/http/server/reply.hpp.html +/doc/examples/diffs/http/server/request_handler.cpp.html +/doc/examples/diffs/http/server/request_handler.hpp.html +/doc/examples/diffs/http/server/request.hpp.html +/doc/examples/diffs/http/server/request_parser.cpp.html +/doc/examples/diffs/http/server/request_parser.hpp.html +/doc/examples/diffs/http/server/server.cpp.html +/doc/examples/diffs/http/server/server.hpp.html +/doc/examples/diffs/invocation/ +/doc/examples/diffs/invocation/prioritised_handlers.cpp.html +/doc/examples/diffs/iostreams/ +/doc/examples/diffs/iostreams/http_client.cpp.html +/doc/examples/diffs/local/ +/doc/examples/diffs/local/connect_pair.cpp.html +/doc/examples/diffs/local/iostream_client.cpp.html +/doc/examples/diffs/local/stream_client.cpp.html +/doc/examples/diffs/local/stream_server.cpp.html +/doc/examples/diffs/multicast/ +/doc/examples/diffs/multicast/receiver.cpp.html +/doc/examples/diffs/multicast/sender.cpp.html +/doc/examples/diffs/nonblocking/ +/doc/examples/diffs/nonblocking/third_party_lib.cpp.html +/doc/examples/diffs/operations/ +/doc/examples/diffs/operations/composed_1.cpp.html +/doc/examples/diffs/operations/composed_2.cpp.html +/doc/examples/diffs/operations/composed_3.cpp.html +/doc/examples/diffs/operations/composed_4.cpp.html +/doc/examples/diffs/operations/composed_5.cpp.html +/doc/examples/diffs/operations/composed_6.cpp.html +/doc/examples/diffs/operations/composed_7.cpp.html +/doc/examples/diffs/operations/composed_8.cpp.html +/doc/examples/diffs/socks4/ +/doc/examples/diffs/socks4/socks4.hpp.html +/doc/examples/diffs/socks4/sync_client.cpp.html +/doc/examples/diffs/spawn/ +/doc/examples/diffs/spawn/echo_server.cpp.html +/doc/examples/diffs/spawn/parallel_grep.cpp.html +/doc/examples/diffs/ssl/ +/doc/examples/diffs/ssl/client.cpp.html +/doc/examples/diffs/ssl/server.cpp.html +/doc/examples/diffs/timeouts/ +/doc/examples/diffs/timeouts/async_tcp_client.cpp.html +/doc/examples/diffs/timeouts/blocking_tcp_client.cpp.html +/doc/examples/diffs/timeouts/blocking_token_tcp_client.cpp.html +/doc/examples/diffs/timeouts/blocking_udp_client.cpp.html +/doc/examples/diffs/timeouts/server.cpp.html +/doc/examples/diffs/timers/ +/doc/examples/diffs/timers/time_t_timer.cpp.html +/doc/home.png +/doc/important.png +/doc/index.html +/doc/next_disabled.png +/doc/next.png +/doc/note.png +/doc/prev_disabled.png +/doc/prev.png +/doc/proactor.png +/doc/standalone_HTML.manifest +/doc/sync_op.png +/doc/tip.png +/doc/up_disabled.png +/doc/up.png +/doc/warning.png +/include/ +/include/asio/ +/include/asio/any_io_executor.hpp +/include/asio/associated_allocator.hpp +/include/asio/associated_executor.hpp +/include/asio/async_result.hpp +/include/asio/awaitable.hpp +/include/asio/basic_datagram_socket.hpp +/include/asio/basic_deadline_timer.hpp +/include/asio/basic_io_object.hpp +/include/asio/basic_raw_socket.hpp +/include/asio/basic_seq_packet_socket.hpp +/include/asio/basic_serial_port.hpp +/include/asio/basic_signal_set.hpp +/include/asio/basic_socket_acceptor.hpp +/include/asio/basic_socket.hpp +/include/asio/basic_socket_iostream.hpp +/include/asio/basic_socket_streambuf.hpp +/include/asio/basic_streambuf_fwd.hpp +/include/asio/basic_streambuf.hpp +/include/asio/basic_stream_socket.hpp +/include/asio/basic_waitable_timer.hpp +/include/asio/bind_executor.hpp +/include/asio/buffered_read_stream_fwd.hpp +/include/asio/buffered_read_stream.hpp +/include/asio/buffered_stream_fwd.hpp +/include/asio/buffered_stream.hpp +/include/asio/buffered_write_stream_fwd.hpp +/include/asio/buffered_write_stream.hpp +/include/asio/buffer.hpp +/include/asio/buffers_iterator.hpp +/include/asio/completion_condition.hpp +/include/asio/compose.hpp +/include/asio/connect.hpp +/include/asio/coroutine.hpp +/include/asio/co_spawn.hpp +/include/asio/deadline_timer.hpp +/include/asio/defer.hpp +/include/asio/detached.hpp +/include/asio/detail/ +/include/asio/detail/array_fwd.hpp +/include/asio/detail/array.hpp +/include/asio/detail/assert.hpp +/include/asio/detail/atomic_count.hpp +/include/asio/detail/base_from_completion_cond.hpp +/include/asio/detail/bind_handler.hpp +/include/asio/detail/blocking_executor_op.hpp +/include/asio/detail/buffered_stream_storage.hpp +/include/asio/detail/buffer_resize_guard.hpp +/include/asio/detail/buffer_sequence_adapter.hpp +/include/asio/detail/bulk_executor_op.hpp +/include/asio/detail/call_stack.hpp +/include/asio/detail/chrono.hpp +/include/asio/detail/chrono_time_traits.hpp +/include/asio/detail/completion_handler.hpp +/include/asio/detail/concurrency_hint.hpp +/include/asio/detail/conditionally_enabled_event.hpp +/include/asio/detail/conditionally_enabled_mutex.hpp +/include/asio/detail/config.hpp +/include/asio/detail/consuming_buffers.hpp +/include/asio/detail/cstddef.hpp +/include/asio/detail/cstdint.hpp +/include/asio/detail/date_time_fwd.hpp +/include/asio/detail/deadline_timer_service.hpp +/include/asio/detail/dependent_type.hpp +/include/asio/detail/descriptor_ops.hpp +/include/asio/detail/descriptor_read_op.hpp +/include/asio/detail/descriptor_write_op.hpp +/include/asio/detail/dev_poll_reactor.hpp +/include/asio/detail/epoll_reactor.hpp +/include/asio/detail/eventfd_select_interrupter.hpp +/include/asio/detail/event.hpp +/include/asio/detail/executor_function.hpp +/include/asio/detail/executor_op.hpp +/include/asio/detail/fd_set_adapter.hpp +/include/asio/detail/fenced_block.hpp +/include/asio/detail/functional.hpp +/include/asio/detail/future.hpp +/include/asio/detail/gcc_arm_fenced_block.hpp +/include/asio/detail/gcc_hppa_fenced_block.hpp +/include/asio/detail/gcc_sync_fenced_block.hpp +/include/asio/detail/gcc_x86_fenced_block.hpp +/include/asio/detail/global.hpp +/include/asio/detail/handler_alloc_helpers.hpp +/include/asio/detail/handler_cont_helpers.hpp +/include/asio/detail/handler_invoke_helpers.hpp +/include/asio/detail/handler_tracking.hpp +/include/asio/detail/handler_type_requirements.hpp +/include/asio/detail/handler_work.hpp +/include/asio/detail/hash_map.hpp +/include/asio/detail/impl/ +/include/asio/detail/impl/buffer_sequence_adapter.ipp +/include/asio/detail/impl/descriptor_ops.ipp +/include/asio/detail/impl/dev_poll_reactor.hpp +/include/asio/detail/impl/dev_poll_reactor.ipp +/include/asio/detail/impl/epoll_reactor.hpp +/include/asio/detail/impl/epoll_reactor.ipp +/include/asio/detail/impl/eventfd_select_interrupter.ipp +/include/asio/detail/impl/handler_tracking.ipp +/include/asio/detail/impl/kqueue_reactor.hpp +/include/asio/detail/impl/kqueue_reactor.ipp +/include/asio/detail/impl/null_event.ipp +/include/asio/detail/impl/pipe_select_interrupter.ipp +/include/asio/detail/impl/posix_event.ipp +/include/asio/detail/impl/posix_mutex.ipp +/include/asio/detail/impl/posix_thread.ipp +/include/asio/detail/impl/posix_tss_ptr.ipp +/include/asio/detail/impl/reactive_descriptor_service.ipp +/include/asio/detail/impl/reactive_serial_port_service.ipp +/include/asio/detail/impl/reactive_socket_service_base.ipp +/include/asio/detail/impl/resolver_service_base.ipp +/include/asio/detail/impl/scheduler.ipp +/include/asio/detail/impl/select_reactor.hpp +/include/asio/detail/impl/select_reactor.ipp +/include/asio/detail/impl/service_registry.hpp +/include/asio/detail/impl/service_registry.ipp +/include/asio/detail/impl/signal_set_service.ipp +/include/asio/detail/impl/socket_ops.ipp +/include/asio/detail/impl/socket_select_interrupter.ipp +/include/asio/detail/impl/strand_executor_service.hpp +/include/asio/detail/impl/strand_executor_service.ipp +/include/asio/detail/impl/strand_service.hpp +/include/asio/detail/impl/strand_service.ipp +/include/asio/detail/impl/throw_error.ipp +/include/asio/detail/impl/timer_queue_ptime.ipp +/include/asio/detail/impl/timer_queue_set.ipp +/include/asio/detail/impl/win_event.ipp +/include/asio/detail/impl/win_iocp_handle_service.ipp +/include/asio/detail/impl/win_iocp_io_context.hpp +/include/asio/detail/impl/win_iocp_io_context.ipp +/include/asio/detail/impl/win_iocp_serial_port_service.ipp +/include/asio/detail/impl/win_iocp_socket_service_base.ipp +/include/asio/detail/impl/win_mutex.ipp +/include/asio/detail/impl/win_object_handle_service.ipp +/include/asio/detail/impl/winrt_ssocket_service_base.ipp +/include/asio/detail/impl/winrt_timer_scheduler.hpp +/include/asio/detail/impl/winrt_timer_scheduler.ipp +/include/asio/detail/impl/winsock_init.ipp +/include/asio/detail/impl/win_static_mutex.ipp +/include/asio/detail/impl/win_thread.ipp +/include/asio/detail/impl/win_tss_ptr.ipp +/include/asio/detail/io_control.hpp +/include/asio/detail/io_object_impl.hpp +/include/asio/detail/is_buffer_sequence.hpp +/include/asio/detail/is_executor.hpp +/include/asio/detail/keyword_tss_ptr.hpp +/include/asio/detail/kqueue_reactor.hpp +/include/asio/detail/limits.hpp +/include/asio/detail/local_free_on_block_exit.hpp +/include/asio/detail/macos_fenced_block.hpp +/include/asio/detail/memory.hpp +/include/asio/detail/mutex.hpp +/include/asio/detail/non_const_lvalue.hpp +/include/asio/detail/noncopyable.hpp +/include/asio/detail/null_event.hpp +/include/asio/detail/null_fenced_block.hpp +/include/asio/detail/null_global.hpp +/include/asio/detail/null_mutex.hpp +/include/asio/detail/null_reactor.hpp +/include/asio/detail/null_signal_blocker.hpp +/include/asio/detail/null_socket_service.hpp +/include/asio/detail/null_static_mutex.hpp +/include/asio/detail/null_thread.hpp +/include/asio/detail/null_tss_ptr.hpp +/include/asio/detail/object_pool.hpp +/include/asio/detail/old_win_sdk_compat.hpp +/include/asio/detail/operation.hpp +/include/asio/detail/op_queue.hpp +/include/asio/detail/pipe_select_interrupter.hpp +/include/asio/detail/pop_options.hpp +/include/asio/detail/posix_event.hpp +/include/asio/detail/posix_fd_set_adapter.hpp +/include/asio/detail/posix_global.hpp +/include/asio/detail/posix_mutex.hpp +/include/asio/detail/posix_signal_blocker.hpp +/include/asio/detail/posix_static_mutex.hpp +/include/asio/detail/posix_thread.hpp +/include/asio/detail/posix_tss_ptr.hpp +/include/asio/detail/push_options.hpp +/include/asio/detail/reactive_descriptor_service.hpp +/include/asio/detail/reactive_null_buffers_op.hpp +/include/asio/detail/reactive_serial_port_service.hpp +/include/asio/detail/reactive_socket_accept_op.hpp +/include/asio/detail/reactive_socket_connect_op.hpp +/include/asio/detail/reactive_socket_recvfrom_op.hpp +/include/asio/detail/reactive_socket_recvmsg_op.hpp +/include/asio/detail/reactive_socket_recv_op.hpp +/include/asio/detail/reactive_socket_send_op.hpp +/include/asio/detail/reactive_socket_sendto_op.hpp +/include/asio/detail/reactive_socket_service_base.hpp +/include/asio/detail/reactive_socket_service.hpp +/include/asio/detail/reactive_wait_op.hpp +/include/asio/detail/reactor_fwd.hpp +/include/asio/detail/reactor.hpp +/include/asio/detail/reactor_op.hpp +/include/asio/detail/reactor_op_queue.hpp +/include/asio/detail/recycling_allocator.hpp +/include/asio/detail/regex_fwd.hpp +/include/asio/detail/resolve_endpoint_op.hpp +/include/asio/detail/resolve_op.hpp +/include/asio/detail/resolve_query_op.hpp +/include/asio/detail/resolver_service_base.hpp +/include/asio/detail/resolver_service.hpp +/include/asio/detail/scheduler.hpp +/include/asio/detail/scheduler_operation.hpp +/include/asio/detail/scheduler_thread_info.hpp +/include/asio/detail/scoped_lock.hpp +/include/asio/detail/scoped_ptr.hpp +/include/asio/detail/select_interrupter.hpp +/include/asio/detail/select_reactor.hpp +/include/asio/detail/service_registry.hpp +/include/asio/detail/signal_blocker.hpp +/include/asio/detail/signal_handler.hpp +/include/asio/detail/signal_init.hpp +/include/asio/detail/signal_op.hpp +/include/asio/detail/signal_set_service.hpp +/include/asio/detail/socket_holder.hpp +/include/asio/detail/socket_ops.hpp +/include/asio/detail/socket_option.hpp +/include/asio/detail/socket_select_interrupter.hpp +/include/asio/detail/socket_types.hpp +/include/asio/detail/solaris_fenced_block.hpp +/include/asio/detail/source_location.hpp +/include/asio/detail/static_mutex.hpp +/include/asio/detail/std_event.hpp +/include/asio/detail/std_fenced_block.hpp +/include/asio/detail/std_global.hpp +/include/asio/detail/std_mutex.hpp +/include/asio/detail/std_static_mutex.hpp +/include/asio/detail/std_thread.hpp +/include/asio/detail/strand_executor_service.hpp +/include/asio/detail/strand_service.hpp +/include/asio/detail/string_view.hpp +/include/asio/detail/thread_context.hpp +/include/asio/detail/thread_group.hpp +/include/asio/detail/thread.hpp +/include/asio/detail/thread_info_base.hpp +/include/asio/detail/throw_error.hpp +/include/asio/detail/throw_exception.hpp +/include/asio/detail/timer_queue_base.hpp +/include/asio/detail/timer_queue.hpp +/include/asio/detail/timer_queue_ptime.hpp +/include/asio/detail/timer_queue_set.hpp +/include/asio/detail/timer_scheduler_fwd.hpp +/include/asio/detail/timer_scheduler.hpp +/include/asio/detail/tss_ptr.hpp +/include/asio/detail/type_traits.hpp +/include/asio/detail/variadic_templates.hpp +/include/asio/detail/wait_handler.hpp +/include/asio/detail/wait_op.hpp +/include/asio/detail/winapp_thread.hpp +/include/asio/detail/wince_thread.hpp +/include/asio/detail/win_event.hpp +/include/asio/detail/win_fd_set_adapter.hpp +/include/asio/detail/win_fenced_block.hpp +/include/asio/detail/win_global.hpp +/include/asio/detail/win_iocp_handle_read_op.hpp +/include/asio/detail/win_iocp_handle_service.hpp +/include/asio/detail/win_iocp_handle_write_op.hpp +/include/asio/detail/win_iocp_io_context.hpp +/include/asio/detail/win_iocp_null_buffers_op.hpp +/include/asio/detail/win_iocp_operation.hpp +/include/asio/detail/win_iocp_overlapped_op.hpp +/include/asio/detail/win_iocp_overlapped_ptr.hpp +/include/asio/detail/win_iocp_serial_port_service.hpp +/include/asio/detail/win_iocp_socket_accept_op.hpp +/include/asio/detail/win_iocp_socket_connect_op.hpp +/include/asio/detail/win_iocp_socket_recvfrom_op.hpp +/include/asio/detail/win_iocp_socket_recvmsg_op.hpp +/include/asio/detail/win_iocp_socket_recv_op.hpp +/include/asio/detail/win_iocp_socket_send_op.hpp +/include/asio/detail/win_iocp_socket_service_base.hpp +/include/asio/detail/win_iocp_socket_service.hpp +/include/asio/detail/win_iocp_thread_info.hpp +/include/asio/detail/win_iocp_wait_op.hpp +/include/asio/detail/win_mutex.hpp +/include/asio/detail/win_object_handle_service.hpp +/include/asio/detail/winrt_async_manager.hpp +/include/asio/detail/winrt_async_op.hpp +/include/asio/detail/winrt_resolve_op.hpp +/include/asio/detail/winrt_resolver_service.hpp +/include/asio/detail/winrt_socket_connect_op.hpp +/include/asio/detail/winrt_socket_recv_op.hpp +/include/asio/detail/winrt_socket_send_op.hpp +/include/asio/detail/winrt_ssocket_service_base.hpp +/include/asio/detail/winrt_ssocket_service.hpp +/include/asio/detail/winrt_timer_scheduler.hpp +/include/asio/detail/winrt_utils.hpp +/include/asio/detail/winsock_init.hpp +/include/asio/detail/win_static_mutex.hpp +/include/asio/detail/win_thread.hpp +/include/asio/detail/win_tss_ptr.hpp +/include/asio/detail/work_dispatcher.hpp +/include/asio/detail/wrapped_handler.hpp +/include/asio/dispatch.hpp +/include/asio/error_code.hpp +/include/asio/error.hpp +/include/asio/execution/ +/include/asio/execution/allocator.hpp +/include/asio/execution/any_executor.hpp +/include/asio/execution/bad_executor.hpp +/include/asio/execution/blocking_adaptation.hpp +/include/asio/execution/blocking.hpp +/include/asio/execution/bulk_execute.hpp +/include/asio/execution/bulk_guarantee.hpp +/include/asio/execution/connect.hpp +/include/asio/execution/context_as.hpp +/include/asio/execution/context.hpp +/include/asio/execution_context.hpp +/include/asio/execution/detail/ +/include/asio/execution/detail/as_invocable.hpp +/include/asio/execution/detail/as_operation.hpp +/include/asio/execution/detail/as_receiver.hpp +/include/asio/execution/detail/bulk_sender.hpp +/include/asio/execution/detail/submit_receiver.hpp +/include/asio/execution/detail/void_receiver.hpp +/include/asio/execution/execute.hpp +/include/asio/execution/executor.hpp +/include/asio/execution.hpp +/include/asio/execution/impl/ +/include/asio/execution/impl/bad_executor.ipp +/include/asio/execution/impl/receiver_invocation_error.ipp +/include/asio/execution/invocable_archetype.hpp +/include/asio/execution/mapping.hpp +/include/asio/execution/occupancy.hpp +/include/asio/execution/operation_state.hpp +/include/asio/execution/outstanding_work.hpp +/include/asio/execution/prefer_only.hpp +/include/asio/execution/receiver.hpp +/include/asio/execution/receiver_invocation_error.hpp +/include/asio/execution/relationship.hpp +/include/asio/execution/schedule.hpp +/include/asio/execution/scheduler.hpp +/include/asio/execution/sender.hpp +/include/asio/execution/set_done.hpp +/include/asio/execution/set_error.hpp +/include/asio/execution/set_value.hpp +/include/asio/execution/start.hpp +/include/asio/execution/submit.hpp +/include/asio/executor.hpp +/include/asio/executor_work_guard.hpp +/include/asio/generic/ +/include/asio/generic/basic_endpoint.hpp +/include/asio/generic/datagram_protocol.hpp +/include/asio/generic/detail/ +/include/asio/generic/detail/endpoint.hpp +/include/asio/generic/detail/impl/ +/include/asio/generic/detail/impl/endpoint.ipp +/include/asio/generic/raw_protocol.hpp +/include/asio/generic/seq_packet_protocol.hpp +/include/asio/generic/stream_protocol.hpp +/include/asio/handler_alloc_hook.hpp +/include/asio/handler_continuation_hook.hpp +/include/asio/handler_invoke_hook.hpp +/include/asio/high_resolution_timer.hpp +/include/asio.hpp +/include/asio/impl/ +/include/asio/impl/awaitable.hpp +/include/asio/impl/buffered_read_stream.hpp +/include/asio/impl/buffered_write_stream.hpp +/include/asio/impl/compose.hpp +/include/asio/impl/connect.hpp +/include/asio/impl/co_spawn.hpp +/include/asio/impl/defer.hpp +/include/asio/impl/detached.hpp +/include/asio/impl/dispatch.hpp +/include/asio/impl/error_code.ipp +/include/asio/impl/error.ipp +/include/asio/impl/execution_context.hpp +/include/asio/impl/execution_context.ipp +/include/asio/impl/executor.hpp +/include/asio/impl/executor.ipp +/include/asio/impl/handler_alloc_hook.ipp +/include/asio/impl/io_context.hpp +/include/asio/impl/io_context.ipp +/include/asio/impl/multiple_exceptions.ipp +/include/asio/impl/post.hpp +/include/asio/impl/read_at.hpp +/include/asio/impl/read.hpp +/include/asio/impl/read_until.hpp +/include/asio/impl/redirect_error.hpp +/include/asio/impl/serial_port_base.hpp +/include/asio/impl/serial_port_base.ipp +/include/asio/impl/spawn.hpp +/include/asio/impl/src.cpp +/include/asio/impl/src.hpp +/include/asio/impl/system_context.hpp +/include/asio/impl/system_context.ipp +/include/asio/impl/system_executor.hpp +/include/asio/impl/thread_pool.hpp +/include/asio/impl/thread_pool.ipp +/include/asio/impl/use_awaitable.hpp +/include/asio/impl/use_future.hpp +/include/asio/impl/write_at.hpp +/include/asio/impl/write.hpp +/include/asio/io_context.hpp +/include/asio/io_context_strand.hpp +/include/asio/io_service.hpp +/include/asio/io_service_strand.hpp +/include/asio/ip/ +/include/asio/ip/address.hpp +/include/asio/ip/address_v4.hpp +/include/asio/ip/address_v4_iterator.hpp +/include/asio/ip/address_v4_range.hpp +/include/asio/ip/address_v6.hpp +/include/asio/ip/address_v6_iterator.hpp +/include/asio/ip/address_v6_range.hpp +/include/asio/ip/bad_address_cast.hpp +/include/asio/ip/basic_endpoint.hpp +/include/asio/ip/basic_resolver_entry.hpp +/include/asio/ip/basic_resolver.hpp +/include/asio/ip/basic_resolver_iterator.hpp +/include/asio/ip/basic_resolver_query.hpp +/include/asio/ip/basic_resolver_results.hpp +/include/asio/ip/detail/ +/include/asio/ip/detail/endpoint.hpp +/include/asio/ip/detail/impl/ +/include/asio/ip/detail/impl/endpoint.ipp +/include/asio/ip/detail/socket_option.hpp +/include/asio/ip/host_name.hpp +/include/asio/ip/icmp.hpp +/include/asio/ip/impl/ +/include/asio/ip/impl/address.hpp +/include/asio/ip/impl/address.ipp +/include/asio/ip/impl/address_v4.hpp +/include/asio/ip/impl/address_v4.ipp +/include/asio/ip/impl/address_v6.hpp +/include/asio/ip/impl/address_v6.ipp +/include/asio/ip/impl/basic_endpoint.hpp +/include/asio/ip/impl/host_name.ipp +/include/asio/ip/impl/network_v4.hpp +/include/asio/ip/impl/network_v4.ipp +/include/asio/ip/impl/network_v6.hpp +/include/asio/ip/impl/network_v6.ipp +/include/asio/ip/multicast.hpp +/include/asio/ip/network_v4.hpp +/include/asio/ip/network_v6.hpp +/include/asio/ip/resolver_base.hpp +/include/asio/ip/resolver_query_base.hpp +/include/asio/ip/tcp.hpp +/include/asio/ip/udp.hpp +/include/asio/ip/unicast.hpp +/include/asio/ip/v6_only.hpp +/include/asio/is_applicable_property.hpp +/include/asio/is_executor.hpp +/include/asio/is_read_buffered.hpp +/include/asio/is_write_buffered.hpp +/include/asio/local/ +/include/asio/local/basic_endpoint.hpp +/include/asio/local/connect_pair.hpp +/include/asio/local/datagram_protocol.hpp +/include/asio/local/detail/ +/include/asio/local/detail/endpoint.hpp +/include/asio/local/detail/impl/ +/include/asio/local/detail/impl/endpoint.ipp +/include/asio/local/stream_protocol.hpp +/include/asio/multiple_exceptions.hpp +/include/asio/packaged_task.hpp +/include/asio/placeholders.hpp +/include/asio/posix/ +/include/asio/posix/basic_descriptor.hpp +/include/asio/posix/basic_stream_descriptor.hpp +/include/asio/posix/descriptor_base.hpp +/include/asio/posix/descriptor.hpp +/include/asio/posix/stream_descriptor.hpp +/include/asio/post.hpp +/include/asio/prefer.hpp +/include/asio/query.hpp +/include/asio/read_at.hpp +/include/asio/read.hpp +/include/asio/read_until.hpp +/include/asio/redirect_error.hpp +/include/asio/require_concept.hpp +/include/asio/require.hpp +/include/asio/serial_port_base.hpp +/include/asio/serial_port.hpp +/include/asio/signal_set.hpp +/include/asio/socket_base.hpp +/include/asio/spawn.hpp +/include/asio/ssl/ +/include/asio/ssl/context_base.hpp +/include/asio/ssl/context.hpp +/include/asio/ssl/detail/ +/include/asio/ssl/detail/buffered_handshake_op.hpp +/include/asio/ssl/detail/engine.hpp +/include/asio/ssl/detail/handshake_op.hpp +/include/asio/ssl/detail/impl/ +/include/asio/ssl/detail/impl/engine.ipp +/include/asio/ssl/detail/impl/openssl_init.ipp +/include/asio/ssl/detail/io.hpp +/include/asio/ssl/detail/openssl_init.hpp +/include/asio/ssl/detail/openssl_types.hpp +/include/asio/ssl/detail/password_callback.hpp +/include/asio/ssl/detail/read_op.hpp +/include/asio/ssl/detail/shutdown_op.hpp +/include/asio/ssl/detail/stream_core.hpp +/include/asio/ssl/detail/verify_callback.hpp +/include/asio/ssl/detail/write_op.hpp +/include/asio/ssl/error.hpp +/include/asio/ssl/host_name_verification.hpp +/include/asio/ssl.hpp +/include/asio/ssl/impl/ +/include/asio/ssl/impl/context.hpp +/include/asio/ssl/impl/context.ipp +/include/asio/ssl/impl/error.ipp +/include/asio/ssl/impl/host_name_verification.ipp +/include/asio/ssl/impl/rfc2818_verification.ipp +/include/asio/ssl/impl/src.hpp +/include/asio/ssl/rfc2818_verification.hpp +/include/asio/ssl/stream_base.hpp +/include/asio/ssl/stream.hpp +/include/asio/ssl/verify_context.hpp +/include/asio/ssl/verify_mode.hpp +/include/asio/static_thread_pool.hpp +/include/asio/steady_timer.hpp +/include/asio/strand.hpp +/include/asio/streambuf.hpp +/include/asio/system_context.hpp +/include/asio/system_error.hpp +/include/asio/system_executor.hpp +/include/asio/system_timer.hpp +/include/asio/this_coro.hpp +/include/asio/thread.hpp +/include/asio/thread_pool.hpp +/include/asio/time_traits.hpp +/include/asio/traits/ +/include/asio/traits/bulk_execute_free.hpp +/include/asio/traits/bulk_execute_member.hpp +/include/asio/traits/connect_free.hpp +/include/asio/traits/connect_member.hpp +/include/asio/traits/equality_comparable.hpp +/include/asio/traits/execute_free.hpp +/include/asio/traits/execute_member.hpp +/include/asio/traits/prefer_free.hpp +/include/asio/traits/prefer_member.hpp +/include/asio/traits/query_free.hpp +/include/asio/traits/query_member.hpp +/include/asio/traits/query_static_constexpr_member.hpp +/include/asio/traits/require_concept_free.hpp +/include/asio/traits/require_concept_member.hpp +/include/asio/traits/require_free.hpp +/include/asio/traits/require_member.hpp +/include/asio/traits/schedule_free.hpp +/include/asio/traits/schedule_member.hpp +/include/asio/traits/set_done_free.hpp +/include/asio/traits/set_done_member.hpp +/include/asio/traits/set_error_free.hpp +/include/asio/traits/set_error_member.hpp +/include/asio/traits/set_value_free.hpp +/include/asio/traits/set_value_member.hpp +/include/asio/traits/start_free.hpp +/include/asio/traits/start_member.hpp +/include/asio/traits/static_query.hpp +/include/asio/traits/static_require_concept.hpp +/include/asio/traits/static_require.hpp +/include/asio/traits/submit_free.hpp +/include/asio/traits/submit_member.hpp +/include/asio/ts/ +/include/asio/ts/buffer.hpp +/include/asio/ts/executor.hpp +/include/asio/ts/internet.hpp +/include/asio/ts/io_context.hpp +/include/asio/ts/netfwd.hpp +/include/asio/ts/net.hpp +/include/asio/ts/socket.hpp +/include/asio/ts/timer.hpp +/include/asio/unyield.hpp +/include/asio/use_awaitable.hpp +/include/asio/use_future.hpp +/include/asio/uses_executor.hpp +/include/asio/version.hpp +/include/asio/wait_traits.hpp +/include/asio/windows/ +/include/asio/windows/basic_object_handle.hpp +/include/asio/windows/basic_overlapped_handle.hpp +/include/asio/windows/basic_random_access_handle.hpp +/include/asio/windows/basic_stream_handle.hpp +/include/asio/windows/object_handle.hpp +/include/asio/windows/overlapped_handle.hpp +/include/asio/windows/overlapped_ptr.hpp +/include/asio/windows/random_access_handle.hpp +/include/asio/windows/stream_handle.hpp +/include/asio/write_at.hpp +/include/asio/write.hpp +/include/asio/yield.hpp +/include/Makefile.am +/include/Makefile.in +/INSTALL +/install-sh +/LICENSE_1_0.txt +/Makefile.am +/Makefile.in +/missing +/README +/src/ +/src/asio.cpp +/src/asio_ssl.cpp +/src/examples/ +/src/examples/cpp03/ +/src/examples/cpp03/allocation/ +/src/examples/cpp03/allocation/server.cpp +/src/examples/cpp03/buffers/ +/src/examples/cpp03/buffers/reference_counted.cpp +/src/examples/cpp03/chat/ +/src/examples/cpp03/chat/chat_client.cpp +/src/examples/cpp03/chat/chat_message.hpp +/src/examples/cpp03/chat/chat_server.cpp +/src/examples/cpp03/chat/posix_chat_client.cpp +/src/examples/cpp03/echo/ +/src/examples/cpp03/echo/async_tcp_echo_server.cpp +/src/examples/cpp03/echo/async_udp_echo_server.cpp +/src/examples/cpp03/echo/blocking_tcp_echo_client.cpp +/src/examples/cpp03/echo/blocking_tcp_echo_server.cpp +/src/examples/cpp03/echo/blocking_udp_echo_client.cpp +/src/examples/cpp03/echo/blocking_udp_echo_server.cpp +/src/examples/cpp03/fork/ +/src/examples/cpp03/fork/daemon.cpp +/src/examples/cpp03/fork/process_per_connection.cpp +/src/examples/cpp03/http/ +/src/examples/cpp03/http/client/ +/src/examples/cpp03/http/client/async_client.cpp +/src/examples/cpp03/http/client/sync_client.cpp +/src/examples/cpp03/http/server/ +/src/examples/cpp03/http/server2/ +/src/examples/cpp03/http/server2/connection.cpp +/src/examples/cpp03/http/server2/connection.hpp +/src/examples/cpp03/http/server2/header.hpp +/src/examples/cpp03/http/server2/io_context_pool.cpp +/src/examples/cpp03/http/server2/io_context_pool.hpp +/src/examples/cpp03/http/server2/main.cpp +/src/examples/cpp03/http/server2/mime_types.cpp +/src/examples/cpp03/http/server2/mime_types.hpp +/src/examples/cpp03/http/server2/reply.cpp +/src/examples/cpp03/http/server2/reply.hpp +/src/examples/cpp03/http/server2/request_handler.cpp +/src/examples/cpp03/http/server2/request_handler.hpp +/src/examples/cpp03/http/server2/request.hpp +/src/examples/cpp03/http/server2/request_parser.cpp +/src/examples/cpp03/http/server2/request_parser.hpp +/src/examples/cpp03/http/server2/server.cpp +/src/examples/cpp03/http/server2/server.hpp +/src/examples/cpp03/http/server3/ +/src/examples/cpp03/http/server3/connection.cpp +/src/examples/cpp03/http/server3/connection.hpp +/src/examples/cpp03/http/server3/header.hpp +/src/examples/cpp03/http/server3/main.cpp +/src/examples/cpp03/http/server3/mime_types.cpp +/src/examples/cpp03/http/server3/mime_types.hpp +/src/examples/cpp03/http/server3/reply.cpp +/src/examples/cpp03/http/server3/reply.hpp +/src/examples/cpp03/http/server3/request_handler.cpp +/src/examples/cpp03/http/server3/request_handler.hpp +/src/examples/cpp03/http/server3/request.hpp +/src/examples/cpp03/http/server3/request_parser.cpp +/src/examples/cpp03/http/server3/request_parser.hpp +/src/examples/cpp03/http/server3/server.cpp +/src/examples/cpp03/http/server3/server.hpp +/src/examples/cpp03/http/server4/ +/src/examples/cpp03/http/server4/file_handler.cpp +/src/examples/cpp03/http/server4/file_handler.hpp +/src/examples/cpp03/http/server4/header.hpp +/src/examples/cpp03/http/server4/main.cpp +/src/examples/cpp03/http/server4/mime_types.cpp +/src/examples/cpp03/http/server4/mime_types.hpp +/src/examples/cpp03/http/server4/reply.cpp +/src/examples/cpp03/http/server4/reply.hpp +/src/examples/cpp03/http/server4/request.hpp +/src/examples/cpp03/http/server4/request_parser.cpp +/src/examples/cpp03/http/server4/request_parser.hpp +/src/examples/cpp03/http/server4/server.cpp +/src/examples/cpp03/http/server4/server.hpp +/src/examples/cpp03/http/server/connection.cpp +/src/examples/cpp03/http/server/connection.hpp +/src/examples/cpp03/http/server/connection_manager.cpp +/src/examples/cpp03/http/server/connection_manager.hpp +/src/examples/cpp03/http/server/header.hpp +/src/examples/cpp03/http/server/main.cpp +/src/examples/cpp03/http/server/mime_types.cpp +/src/examples/cpp03/http/server/mime_types.hpp +/src/examples/cpp03/http/server/reply.cpp +/src/examples/cpp03/http/server/reply.hpp +/src/examples/cpp03/http/server/request_handler.cpp +/src/examples/cpp03/http/server/request_handler.hpp +/src/examples/cpp03/http/server/request.hpp +/src/examples/cpp03/http/server/request_parser.cpp +/src/examples/cpp03/http/server/request_parser.hpp +/src/examples/cpp03/http/server/server.cpp +/src/examples/cpp03/http/server/server.hpp +/src/examples/cpp03/icmp/ +/src/examples/cpp03/icmp/icmp_header.hpp +/src/examples/cpp03/icmp/ipv4_header.hpp +/src/examples/cpp03/icmp/ping.cpp +/src/examples/cpp03/invocation/ +/src/examples/cpp03/invocation/prioritised_handlers.cpp +/src/examples/cpp03/iostreams/ +/src/examples/cpp03/iostreams/daytime_client.cpp +/src/examples/cpp03/iostreams/daytime_server.cpp +/src/examples/cpp03/iostreams/http_client.cpp +/src/examples/cpp03/local/ +/src/examples/cpp03/local/connect_pair.cpp +/src/examples/cpp03/local/iostream_client.cpp +/src/examples/cpp03/local/stream_client.cpp +/src/examples/cpp03/local/stream_server.cpp +/src/examples/cpp03/Makefile.am +/src/examples/cpp03/Makefile.in +/src/examples/cpp03/multicast/ +/src/examples/cpp03/multicast/receiver.cpp +/src/examples/cpp03/multicast/sender.cpp +/src/examples/cpp03/nonblocking/ +/src/examples/cpp03/nonblocking/third_party_lib.cpp +/src/examples/cpp03/porthopper/ +/src/examples/cpp03/porthopper/client.cpp +/src/examples/cpp03/porthopper/protocol.hpp +/src/examples/cpp03/porthopper/server.cpp +/src/examples/cpp03/serialization/ +/src/examples/cpp03/serialization/client.cpp +/src/examples/cpp03/serialization/connection.hpp +/src/examples/cpp03/serialization/server.cpp +/src/examples/cpp03/serialization/stock.hpp +/src/examples/cpp03/services/ +/src/examples/cpp03/services/basic_logger.hpp +/src/examples/cpp03/services/daytime_client.cpp +/src/examples/cpp03/services/logger.hpp +/src/examples/cpp03/services/logger_service.cpp +/src/examples/cpp03/services/logger_service.hpp +/src/examples/cpp03/socks4/ +/src/examples/cpp03/socks4/socks4.hpp +/src/examples/cpp03/socks4/sync_client.cpp +/src/examples/cpp03/spawn/ +/src/examples/cpp03/spawn/echo_server.cpp +/src/examples/cpp03/spawn/parallel_grep.cpp +/src/examples/cpp03/ssl/ +/src/examples/cpp03/ssl/ca.pem +/src/examples/cpp03/ssl/client.cpp +/src/examples/cpp03/ssl/dh2048.pem +/src/examples/cpp03/ssl/README +/src/examples/cpp03/ssl/server.cpp +/src/examples/cpp03/ssl/server.pem +/src/examples/cpp03/timeouts/ +/src/examples/cpp03/timeouts/async_tcp_client.cpp +/src/examples/cpp03/timeouts/blocking_tcp_client.cpp +/src/examples/cpp03/timeouts/blocking_token_tcp_client.cpp +/src/examples/cpp03/timeouts/blocking_udp_client.cpp +/src/examples/cpp03/timeouts/server.cpp +/src/examples/cpp03/timers/ +/src/examples/cpp03/timers/time_t_timer.cpp +/src/examples/cpp03/tutorial/ +/src/examples/cpp03/tutorial/daytime1/ +/src/examples/cpp03/tutorial/daytime1/client.cpp +/src/examples/cpp03/tutorial/daytime2/ +/src/examples/cpp03/tutorial/daytime2/server.cpp +/src/examples/cpp03/tutorial/daytime3/ +/src/examples/cpp03/tutorial/daytime3/server.cpp +/src/examples/cpp03/tutorial/daytime4/ +/src/examples/cpp03/tutorial/daytime4/client.cpp +/src/examples/cpp03/tutorial/daytime5/ +/src/examples/cpp03/tutorial/daytime5/server.cpp +/src/examples/cpp03/tutorial/daytime6/ +/src/examples/cpp03/tutorial/daytime6/server.cpp +/src/examples/cpp03/tutorial/daytime7/ +/src/examples/cpp03/tutorial/daytime7/server.cpp +/src/examples/cpp03/tutorial/timer1/ +/src/examples/cpp03/tutorial/timer1/timer.cpp +/src/examples/cpp03/tutorial/timer2/ +/src/examples/cpp03/tutorial/timer2/timer.cpp +/src/examples/cpp03/tutorial/timer3/ +/src/examples/cpp03/tutorial/timer3/timer.cpp +/src/examples/cpp03/tutorial/timer4/ +/src/examples/cpp03/tutorial/timer4/timer.cpp +/src/examples/cpp03/tutorial/timer5/ +/src/examples/cpp03/tutorial/timer5/timer.cpp +/src/examples/cpp03/windows/ +/src/examples/cpp03/windows/transmit_file.cpp +/src/examples/cpp11/ +/src/examples/cpp11/allocation/ +/src/examples/cpp11/allocation/server.cpp +/src/examples/cpp11/buffers/ +/src/examples/cpp11/buffers/reference_counted.cpp +/src/examples/cpp11/chat/ +/src/examples/cpp11/chat/chat_client.cpp +/src/examples/cpp11/chat/chat_message.hpp +/src/examples/cpp11/chat/chat_server.cpp +/src/examples/cpp11/echo/ +/src/examples/cpp11/echo/async_tcp_echo_server.cpp +/src/examples/cpp11/echo/async_udp_echo_server.cpp +/src/examples/cpp11/echo/blocking_tcp_echo_client.cpp +/src/examples/cpp11/echo/blocking_tcp_echo_server.cpp +/src/examples/cpp11/echo/blocking_udp_echo_client.cpp +/src/examples/cpp11/echo/blocking_udp_echo_server.cpp +/src/examples/cpp11/executors/ +/src/examples/cpp11/executors/actor.cpp +/src/examples/cpp11/executors/bank_account_1.cpp +/src/examples/cpp11/executors/bank_account_2.cpp +/src/examples/cpp11/executors/fork_join.cpp +/src/examples/cpp11/executors/pipeline.cpp +/src/examples/cpp11/executors/priority_scheduler.cpp +/src/examples/cpp11/fork/ +/src/examples/cpp11/fork/daemon.cpp +/src/examples/cpp11/fork/process_per_connection.cpp +/src/examples/cpp11/futures/ +/src/examples/cpp11/futures/daytime_client.cpp +/src/examples/cpp11/handler_tracking/ +/src/examples/cpp11/handler_tracking/async_tcp_echo_server.cpp +/src/examples/cpp11/handler_tracking/custom_tracking.hpp +/src/examples/cpp11/http/ +/src/examples/cpp11/http/server/ +/src/examples/cpp11/http/server/connection.cpp +/src/examples/cpp11/http/server/connection.hpp +/src/examples/cpp11/http/server/connection_manager.cpp +/src/examples/cpp11/http/server/connection_manager.hpp +/src/examples/cpp11/http/server/header.hpp +/src/examples/cpp11/http/server/main.cpp +/src/examples/cpp11/http/server/mime_types.cpp +/src/examples/cpp11/http/server/mime_types.hpp +/src/examples/cpp11/http/server/reply.cpp +/src/examples/cpp11/http/server/reply.hpp +/src/examples/cpp11/http/server/request_handler.cpp +/src/examples/cpp11/http/server/request_handler.hpp +/src/examples/cpp11/http/server/request.hpp +/src/examples/cpp11/http/server/request_parser.cpp +/src/examples/cpp11/http/server/request_parser.hpp +/src/examples/cpp11/http/server/server.cpp +/src/examples/cpp11/http/server/server.hpp +/src/examples/cpp11/invocation/ +/src/examples/cpp11/invocation/prioritised_handlers.cpp +/src/examples/cpp11/iostreams/ +/src/examples/cpp11/iostreams/http_client.cpp +/src/examples/cpp11/local/ +/src/examples/cpp11/local/connect_pair.cpp +/src/examples/cpp11/local/iostream_client.cpp +/src/examples/cpp11/local/stream_client.cpp +/src/examples/cpp11/local/stream_server.cpp +/src/examples/cpp11/Makefile.am +/src/examples/cpp11/Makefile.in +/src/examples/cpp11/multicast/ +/src/examples/cpp11/multicast/receiver.cpp +/src/examples/cpp11/multicast/sender.cpp +/src/examples/cpp11/nonblocking/ +/src/examples/cpp11/nonblocking/third_party_lib.cpp +/src/examples/cpp11/operations/ +/src/examples/cpp11/operations/composed_1.cpp +/src/examples/cpp11/operations/composed_2.cpp +/src/examples/cpp11/operations/composed_3.cpp +/src/examples/cpp11/operations/composed_4.cpp +/src/examples/cpp11/operations/composed_5.cpp +/src/examples/cpp11/operations/composed_6.cpp +/src/examples/cpp11/operations/composed_7.cpp +/src/examples/cpp11/operations/composed_8.cpp +/src/examples/cpp11/socks4/ +/src/examples/cpp11/socks4/socks4.hpp +/src/examples/cpp11/socks4/sync_client.cpp +/src/examples/cpp11/spawn/ +/src/examples/cpp11/spawn/echo_server.cpp +/src/examples/cpp11/spawn/parallel_grep.cpp +/src/examples/cpp11/ssl/ +/src/examples/cpp11/ssl/client.cpp +/src/examples/cpp11/ssl/server.cpp +/src/examples/cpp11/timeouts/ +/src/examples/cpp11/timeouts/async_tcp_client.cpp +/src/examples/cpp11/timeouts/blocking_tcp_client.cpp +/src/examples/cpp11/timeouts/blocking_token_tcp_client.cpp +/src/examples/cpp11/timeouts/blocking_udp_client.cpp +/src/examples/cpp11/timeouts/server.cpp +/src/examples/cpp11/timers/ +/src/examples/cpp11/timers/time_t_timer.cpp +/src/examples/cpp14/ +/src/examples/cpp14/echo/ +/src/examples/cpp14/echo/async_tcp_echo_server.cpp +/src/examples/cpp14/echo/async_udp_echo_server.cpp +/src/examples/cpp14/echo/blocking_tcp_echo_client.cpp +/src/examples/cpp14/echo/blocking_tcp_echo_server.cpp +/src/examples/cpp14/echo/blocking_udp_echo_client.cpp +/src/examples/cpp14/echo/blocking_udp_echo_server.cpp +/src/examples/cpp14/executors/ +/src/examples/cpp14/executors/actor.cpp +/src/examples/cpp14/executors/async_1.cpp +/src/examples/cpp14/executors/async_2.cpp +/src/examples/cpp14/executors/bank_account_1.cpp +/src/examples/cpp14/executors/bank_account_2.cpp +/src/examples/cpp14/executors/fork_join.cpp +/src/examples/cpp14/executors/pipeline.cpp +/src/examples/cpp14/executors/priority_scheduler.cpp +/src/examples/cpp14/iostreams/ +/src/examples/cpp14/iostreams/http_client.cpp +/src/examples/cpp14/Makefile.am +/src/examples/cpp14/Makefile.in +/src/examples/cpp14/operations/ +/src/examples/cpp14/operations/composed_1.cpp +/src/examples/cpp14/operations/composed_2.cpp +/src/examples/cpp14/operations/composed_3.cpp +/src/examples/cpp14/operations/composed_4.cpp +/src/examples/cpp14/operations/composed_5.cpp +/src/examples/cpp14/operations/composed_6.cpp +/src/examples/cpp14/operations/composed_7.cpp +/src/examples/cpp14/operations/composed_8.cpp +/src/examples/cpp17/ +/src/examples/cpp17/coroutines_ts/ +/src/examples/cpp17/coroutines_ts/chat_server.cpp +/src/examples/cpp17/coroutines_ts/echo_server.cpp +/src/examples/cpp17/coroutines_ts/echo_server_with_default.cpp +/src/examples/cpp17/coroutines_ts/range_based_for.cpp +/src/examples/cpp17/coroutines_ts/refactored_echo_server.cpp +/src/examples/cpp17/Makefile.am +/src/examples/cpp17/Makefile.in +/src/Makefile.am +/src/Makefile.in +/src/Makefile.mgw +/src/Makefile.msc +/src/tests/ +/src/tests/latency/ +/src/tests/latency/allocator.hpp +/src/tests/latency/high_res_clock.hpp +/src/tests/latency/tcp_client.cpp +/src/tests/latency/tcp_server.cpp +/src/tests/latency/udp_client.cpp +/src/tests/latency/udp_server.cpp +/src/tests/Makefile.am +/src/tests/Makefile.in +/src/tests/performance/ +/src/tests/performance/client.cpp +/src/tests/performance/handler_allocator.hpp +/src/tests/performance/server.cpp +/src/tests/properties/ +/src/tests/properties/cpp03/ +/src/tests/properties/cpp03/can_prefer_free_prefer.cpp +/src/tests/properties/cpp03/can_prefer_free_require.cpp +/src/tests/properties/cpp03/can_prefer_member_prefer.cpp +/src/tests/properties/cpp03/can_prefer_member_require.cpp +/src/tests/properties/cpp03/can_prefer_not_applicable_free_prefer.cpp +/src/tests/properties/cpp03/can_prefer_not_applicable_free_require.cpp +/src/tests/properties/cpp03/can_prefer_not_applicable_member_prefer.cpp +/src/tests/properties/cpp03/can_prefer_not_applicable_member_require.cpp +/src/tests/properties/cpp03/can_prefer_not_applicable_static.cpp +/src/tests/properties/cpp03/can_prefer_not_applicable_unsupported.cpp +/src/tests/properties/cpp03/can_prefer_not_preferable_free_prefer.cpp +/src/tests/properties/cpp03/can_prefer_not_preferable_free_require.cpp +/src/tests/properties/cpp03/can_prefer_not_preferable_member_prefer.cpp +/src/tests/properties/cpp03/can_prefer_not_preferable_member_require.cpp +/src/tests/properties/cpp03/can_prefer_not_preferable_static.cpp +/src/tests/properties/cpp03/can_prefer_not_preferable_unsupported.cpp +/src/tests/properties/cpp03/can_prefer_static.cpp +/src/tests/properties/cpp03/can_prefer_unsupported.cpp +/src/tests/properties/cpp03/can_query_free.cpp +/src/tests/properties/cpp03/can_query_member.cpp +/src/tests/properties/cpp03/can_query_not_applicable_free.cpp +/src/tests/properties/cpp03/can_query_not_applicable_member.cpp +/src/tests/properties/cpp03/can_query_not_applicable_static.cpp +/src/tests/properties/cpp03/can_query_not_applicable_unsupported.cpp +/src/tests/properties/cpp03/can_query_static.cpp +/src/tests/properties/cpp03/can_query_unsupported.cpp +/src/tests/properties/cpp03/can_require_concept_free.cpp +/src/tests/properties/cpp03/can_require_concept_member.cpp +/src/tests/properties/cpp03/can_require_concept_not_applicable_free.cpp +/src/tests/properties/cpp03/can_require_concept_not_applicable_member.cpp +/src/tests/properties/cpp03/can_require_concept_not_applicable_static.cpp +/src/tests/properties/cpp03/can_require_concept_not_applicable_unsupported.cpp +/src/tests/properties/cpp03/can_require_concept_static.cpp +/src/tests/properties/cpp03/can_require_concept_unsupported.cpp +/src/tests/properties/cpp03/can_require_free.cpp +/src/tests/properties/cpp03/can_require_member.cpp +/src/tests/properties/cpp03/can_require_not_applicable_free.cpp +/src/tests/properties/cpp03/can_require_not_applicable_member.cpp +/src/tests/properties/cpp03/can_require_not_applicable_static.cpp +/src/tests/properties/cpp03/can_require_not_applicable_unsupported.cpp +/src/tests/properties/cpp03/can_require_static.cpp +/src/tests/properties/cpp03/can_require_unsupported.cpp +/src/tests/properties/cpp03/prefer_free_prefer.cpp +/src/tests/properties/cpp03/prefer_free_require.cpp +/src/tests/properties/cpp03/prefer_member_prefer.cpp +/src/tests/properties/cpp03/prefer_member_require.cpp +/src/tests/properties/cpp03/prefer_static.cpp +/src/tests/properties/cpp03/prefer_unsupported.cpp +/src/tests/properties/cpp03/query_free.cpp +/src/tests/properties/cpp03/query_member.cpp +/src/tests/properties/cpp03/query_static.cpp +/src/tests/properties/cpp03/require_concept_free.cpp +/src/tests/properties/cpp03/require_concept_member.cpp +/src/tests/properties/cpp03/require_concept_static.cpp +/src/tests/properties/cpp03/require_free.cpp +/src/tests/properties/cpp03/require_member.cpp +/src/tests/properties/cpp03/require_static.cpp +/src/tests/properties/cpp11/ +/src/tests/properties/cpp11/can_prefer_free_prefer.cpp +/src/tests/properties/cpp11/can_prefer_free_require.cpp +/src/tests/properties/cpp11/can_prefer_member_prefer.cpp +/src/tests/properties/cpp11/can_prefer_member_require.cpp +/src/tests/properties/cpp11/can_prefer_not_applicable_free_prefer.cpp +/src/tests/properties/cpp11/can_prefer_not_applicable_free_require.cpp +/src/tests/properties/cpp11/can_prefer_not_applicable_member_prefer.cpp +/src/tests/properties/cpp11/can_prefer_not_applicable_member_require.cpp +/src/tests/properties/cpp11/can_prefer_not_applicable_static.cpp +/src/tests/properties/cpp11/can_prefer_not_applicable_unsupported.cpp +/src/tests/properties/cpp11/can_prefer_not_preferable_free_prefer.cpp +/src/tests/properties/cpp11/can_prefer_not_preferable_free_require.cpp +/src/tests/properties/cpp11/can_prefer_not_preferable_member_prefer.cpp +/src/tests/properties/cpp11/can_prefer_not_preferable_member_require.cpp +/src/tests/properties/cpp11/can_prefer_not_preferable_static.cpp +/src/tests/properties/cpp11/can_prefer_not_preferable_unsupported.cpp +/src/tests/properties/cpp11/can_prefer_static.cpp +/src/tests/properties/cpp11/can_prefer_unsupported.cpp +/src/tests/properties/cpp11/can_query_free.cpp +/src/tests/properties/cpp11/can_query_member.cpp +/src/tests/properties/cpp11/can_query_not_applicable_free.cpp +/src/tests/properties/cpp11/can_query_not_applicable_member.cpp +/src/tests/properties/cpp11/can_query_not_applicable_static.cpp +/src/tests/properties/cpp11/can_query_not_applicable_unsupported.cpp +/src/tests/properties/cpp11/can_query_static.cpp +/src/tests/properties/cpp11/can_query_unsupported.cpp +/src/tests/properties/cpp11/can_require_concept_free.cpp +/src/tests/properties/cpp11/can_require_concept_member.cpp +/src/tests/properties/cpp11/can_require_concept_not_applicable_free.cpp +/src/tests/properties/cpp11/can_require_concept_not_applicable_member.cpp +/src/tests/properties/cpp11/can_require_concept_not_applicable_static.cpp +/src/tests/properties/cpp11/can_require_concept_not_applicable_unsupported.cpp +/src/tests/properties/cpp11/can_require_concept_static.cpp +/src/tests/properties/cpp11/can_require_concept_unsupported.cpp +/src/tests/properties/cpp11/can_require_free.cpp +/src/tests/properties/cpp11/can_require_member.cpp +/src/tests/properties/cpp11/can_require_not_applicable_free.cpp +/src/tests/properties/cpp11/can_require_not_applicable_member.cpp +/src/tests/properties/cpp11/can_require_not_applicable_static.cpp +/src/tests/properties/cpp11/can_require_not_applicable_unsupported.cpp +/src/tests/properties/cpp11/can_require_static.cpp +/src/tests/properties/cpp11/can_require_unsupported.cpp +/src/tests/properties/cpp11/prefer_free_prefer.cpp +/src/tests/properties/cpp11/prefer_free_require.cpp +/src/tests/properties/cpp11/prefer_member_prefer.cpp +/src/tests/properties/cpp11/prefer_member_require.cpp +/src/tests/properties/cpp11/prefer_static.cpp +/src/tests/properties/cpp11/prefer_unsupported.cpp +/src/tests/properties/cpp11/query_free.cpp +/src/tests/properties/cpp11/query_member.cpp +/src/tests/properties/cpp11/query_static.cpp +/src/tests/properties/cpp11/require_concept_free.cpp +/src/tests/properties/cpp11/require_concept_member.cpp +/src/tests/properties/cpp11/require_concept_static.cpp +/src/tests/properties/cpp11/require_free.cpp +/src/tests/properties/cpp11/require_member.cpp +/src/tests/properties/cpp11/require_static.cpp +/src/tests/properties/cpp14/ +/src/tests/properties/cpp14/can_prefer_free_prefer.cpp +/src/tests/properties/cpp14/can_prefer_free_require.cpp +/src/tests/properties/cpp14/can_prefer_member_prefer.cpp +/src/tests/properties/cpp14/can_prefer_member_require.cpp +/src/tests/properties/cpp14/can_prefer_not_applicable_free_prefer.cpp +/src/tests/properties/cpp14/can_prefer_not_applicable_free_require.cpp +/src/tests/properties/cpp14/can_prefer_not_applicable_member_prefer.cpp +/src/tests/properties/cpp14/can_prefer_not_applicable_member_require.cpp +/src/tests/properties/cpp14/can_prefer_not_applicable_static.cpp +/src/tests/properties/cpp14/can_prefer_not_applicable_unsupported.cpp +/src/tests/properties/cpp14/can_prefer_not_preferable_free_prefer.cpp +/src/tests/properties/cpp14/can_prefer_not_preferable_free_require.cpp +/src/tests/properties/cpp14/can_prefer_not_preferable_member_prefer.cpp +/src/tests/properties/cpp14/can_prefer_not_preferable_member_require.cpp +/src/tests/properties/cpp14/can_prefer_not_preferable_static.cpp +/src/tests/properties/cpp14/can_prefer_not_preferable_unsupported.cpp +/src/tests/properties/cpp14/can_prefer_static.cpp +/src/tests/properties/cpp14/can_prefer_unsupported.cpp +/src/tests/properties/cpp14/can_query_free.cpp +/src/tests/properties/cpp14/can_query_member.cpp +/src/tests/properties/cpp14/can_query_not_applicable_free.cpp +/src/tests/properties/cpp14/can_query_not_applicable_member.cpp +/src/tests/properties/cpp14/can_query_not_applicable_static.cpp +/src/tests/properties/cpp14/can_query_not_applicable_unsupported.cpp +/src/tests/properties/cpp14/can_query_static.cpp +/src/tests/properties/cpp14/can_query_unsupported.cpp +/src/tests/properties/cpp14/can_require_concept_free.cpp +/src/tests/properties/cpp14/can_require_concept_member.cpp +/src/tests/properties/cpp14/can_require_concept_not_applicable_free.cpp +/src/tests/properties/cpp14/can_require_concept_not_applicable_member.cpp +/src/tests/properties/cpp14/can_require_concept_not_applicable_static.cpp +/src/tests/properties/cpp14/can_require_concept_not_applicable_unsupported.cpp +/src/tests/properties/cpp14/can_require_concept_static.cpp +/src/tests/properties/cpp14/can_require_concept_unsupported.cpp +/src/tests/properties/cpp14/can_require_free.cpp +/src/tests/properties/cpp14/can_require_member.cpp +/src/tests/properties/cpp14/can_require_not_applicable_free.cpp +/src/tests/properties/cpp14/can_require_not_applicable_member.cpp +/src/tests/properties/cpp14/can_require_not_applicable_static.cpp +/src/tests/properties/cpp14/can_require_not_applicable_unsupported.cpp +/src/tests/properties/cpp14/can_require_static.cpp +/src/tests/properties/cpp14/can_require_unsupported.cpp +/src/tests/properties/cpp14/prefer_free_prefer.cpp +/src/tests/properties/cpp14/prefer_free_require.cpp +/src/tests/properties/cpp14/prefer_member_prefer.cpp +/src/tests/properties/cpp14/prefer_member_require.cpp +/src/tests/properties/cpp14/prefer_static.cpp +/src/tests/properties/cpp14/prefer_unsupported.cpp +/src/tests/properties/cpp14/query_free.cpp +/src/tests/properties/cpp14/query_member.cpp +/src/tests/properties/cpp14/query_static.cpp +/src/tests/properties/cpp14/require_concept_free.cpp +/src/tests/properties/cpp14/require_concept_member.cpp +/src/tests/properties/cpp14/require_concept_static.cpp +/src/tests/properties/cpp14/require_free.cpp +/src/tests/properties/cpp14/require_member.cpp +/src/tests/properties/cpp14/require_static.cpp +/src/tests/properties/Makefile.am +/src/tests/properties/Makefile.in +/src/tests/unit/ +/src/tests/unit/archetypes/ +/src/tests/unit/archetypes/async_ops.hpp +/src/tests/unit/archetypes/async_result.hpp +/src/tests/unit/archetypes/gettable_socket_option.hpp +/src/tests/unit/archetypes/io_control_command.hpp +/src/tests/unit/archetypes/settable_socket_option.hpp +/src/tests/unit/associated_allocator.cpp +/src/tests/unit/associated_executor.cpp +/src/tests/unit/async_result.cpp +/src/tests/unit/awaitable.cpp +/src/tests/unit/basic_datagram_socket.cpp +/src/tests/unit/basic_deadline_timer.cpp +/src/tests/unit/basic_raw_socket.cpp +/src/tests/unit/basic_seq_packet_socket.cpp +/src/tests/unit/basic_serial_port.cpp +/src/tests/unit/basic_signal_set.cpp +/src/tests/unit/basic_socket_acceptor.cpp +/src/tests/unit/basic_socket.cpp +/src/tests/unit/basic_streambuf.cpp +/src/tests/unit/basic_stream_socket.cpp +/src/tests/unit/basic_waitable_timer.cpp +/src/tests/unit/bind_executor.cpp +/src/tests/unit/buffer.cpp +/src/tests/unit/buffered_read_stream.cpp +/src/tests/unit/buffered_stream.cpp +/src/tests/unit/buffered_write_stream.cpp +/src/tests/unit/buffers_iterator.cpp +/src/tests/unit/completion_condition.cpp +/src/tests/unit/compose.cpp +/src/tests/unit/connect.cpp +/src/tests/unit/coroutine.cpp +/src/tests/unit/co_spawn.cpp +/src/tests/unit/deadline_timer.cpp +/src/tests/unit/defer.cpp +/src/tests/unit/detached.cpp +/src/tests/unit/dispatch.cpp +/src/tests/unit/error.cpp +/src/tests/unit/execution/ +/src/tests/unit/execution/any_executor.cpp +/src/tests/unit/execution/blocking_adaptation.cpp +/src/tests/unit/execution/blocking.cpp +/src/tests/unit/execution/bulk_execute.cpp +/src/tests/unit/execution/bulk_guarantee.cpp +/src/tests/unit/execution/connect.cpp +/src/tests/unit/execution/context_as.cpp +/src/tests/unit/execution_context.cpp +/src/tests/unit/execution/execute.cpp +/src/tests/unit/execution/executor.cpp +/src/tests/unit/execution/invocable_archetype.cpp +/src/tests/unit/execution/mapping.cpp +/src/tests/unit/execution/operation_state.cpp +/src/tests/unit/execution/outstanding_work.cpp +/src/tests/unit/execution/prefer_only.cpp +/src/tests/unit/execution/receiver.cpp +/src/tests/unit/execution/relationship.cpp +/src/tests/unit/execution/schedule.cpp +/src/tests/unit/execution/scheduler.cpp +/src/tests/unit/execution/sender.cpp +/src/tests/unit/execution/set_done.cpp +/src/tests/unit/execution/set_error.cpp +/src/tests/unit/execution/set_value.cpp +/src/tests/unit/execution/start.cpp +/src/tests/unit/execution/submit.cpp +/src/tests/unit/executor.cpp +/src/tests/unit/executor_work_guard.cpp +/src/tests/unit/generic/ +/src/tests/unit/generic/basic_endpoint.cpp +/src/tests/unit/generic/datagram_protocol.cpp +/src/tests/unit/generic/raw_protocol.cpp +/src/tests/unit/generic/seq_packet_protocol.cpp +/src/tests/unit/generic/stream_protocol.cpp +/src/tests/unit/high_resolution_timer.cpp +/src/tests/unit/io_context.cpp +/src/tests/unit/io_context_strand.cpp +/src/tests/unit/ip/ +/src/tests/unit/ip/address.cpp +/src/tests/unit/ip/address_v4.cpp +/src/tests/unit/ip/address_v4_iterator.cpp +/src/tests/unit/ip/address_v4_range.cpp +/src/tests/unit/ip/address_v6.cpp +/src/tests/unit/ip/address_v6_iterator.cpp +/src/tests/unit/ip/address_v6_range.cpp +/src/tests/unit/ip/basic_endpoint.cpp +/src/tests/unit/ip/basic_resolver.cpp +/src/tests/unit/ip/basic_resolver_entry.cpp +/src/tests/unit/ip/basic_resolver_iterator.cpp +/src/tests/unit/ip/basic_resolver_query.cpp +/src/tests/unit/ip/host_name.cpp +/src/tests/unit/ip/icmp.cpp +/src/tests/unit/ip/multicast.cpp +/src/tests/unit/ip/network_v4.cpp +/src/tests/unit/ip/network_v6.cpp +/src/tests/unit/ip/resolver_query_base.cpp +/src/tests/unit/ip/tcp.cpp +/src/tests/unit/ip/udp.cpp +/src/tests/unit/ip/unicast.cpp +/src/tests/unit/ip/v6_only.cpp +/src/tests/unit/is_read_buffered.cpp +/src/tests/unit/is_write_buffered.cpp +/src/tests/unit/local/ +/src/tests/unit/local/basic_endpoint.cpp +/src/tests/unit/local/connect_pair.cpp +/src/tests/unit/local/datagram_protocol.cpp +/src/tests/unit/local/stream_protocol.cpp +/src/tests/unit/packaged_task.cpp +/src/tests/unit/placeholders.cpp +/src/tests/unit/posix/ +/src/tests/unit/posix/basic_descriptor.cpp +/src/tests/unit/posix/basic_stream_descriptor.cpp +/src/tests/unit/posix/descriptor_base.cpp +/src/tests/unit/posix/descriptor.cpp +/src/tests/unit/posix/stream_descriptor.cpp +/src/tests/unit/post.cpp +/src/tests/unit/read_at.cpp +/src/tests/unit/read.cpp +/src/tests/unit/read_until.cpp +/src/tests/unit/redirect_error.cpp +/src/tests/unit/serial_port_base.cpp +/src/tests/unit/serial_port.cpp +/src/tests/unit/signal_set.cpp +/src/tests/unit/socket_base.cpp +/src/tests/unit/ssl/ +/src/tests/unit/ssl/context_base.cpp +/src/tests/unit/ssl/context.cpp +/src/tests/unit/ssl/error.cpp +/src/tests/unit/ssl/host_name_verification.cpp +/src/tests/unit/ssl/rfc2818_verification.cpp +/src/tests/unit/ssl/stream_base.cpp +/src/tests/unit/ssl/stream.cpp +/src/tests/unit/static_thread_pool.cpp +/src/tests/unit/steady_timer.cpp +/src/tests/unit/strand.cpp +/src/tests/unit/streambuf.cpp +/src/tests/unit/system_context.cpp +/src/tests/unit/system_executor.cpp +/src/tests/unit/system_timer.cpp +/src/tests/unit/this_coro.cpp +/src/tests/unit/thread.cpp +/src/tests/unit/thread_pool.cpp +/src/tests/unit/time_traits.cpp +/src/tests/unit/ts/ +/src/tests/unit/ts/buffer.cpp +/src/tests/unit/ts/executor.cpp +/src/tests/unit/ts/internet.cpp +/src/tests/unit/ts/io_context.cpp +/src/tests/unit/ts/net.cpp +/src/tests/unit/ts/netfwd.cpp +/src/tests/unit/ts/socket.cpp +/src/tests/unit/ts/timer.cpp +/src/tests/unit/unit_test.hpp +/src/tests/unit/use_awaitable.cpp +/src/tests/unit/use_future.cpp +/src/tests/unit/uses_executor.cpp +/src/tests/unit/wait_traits.cpp +/src/tests/unit/windows/ +/src/tests/unit/windows/basic_object_handle.cpp +/src/tests/unit/windows/basic_overlapped_handle.cpp +/src/tests/unit/windows/basic_random_access_handle.cpp +/src/tests/unit/windows/basic_stream_handle.cpp +/src/tests/unit/windows/object_handle.cpp +/src/tests/unit/windows/overlapped_handle.cpp +/src/tests/unit/windows/overlapped_ptr.cpp +/src/tests/unit/windows/random_access_handle.cpp +/src/tests/unit/windows/stream_handle.cpp +/src/tests/unit/write_at.cpp +/src/tests/unit/write.cpp +/src/tools/ +/src/tools/handlerlive.pl +/src/tools/handlertree.pl +/src/tools/handlerviz.pl +/test-driver diff --git a/tidal-link/link/modules/asio-standalone/asio/autogen.sh b/tidal-link/link/modules/asio-standalone/asio/autogen.sh new file mode 100644 index 000000000..42075e32b --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/autogen.sh @@ -0,0 +1,55 @@ +#!/bin/sh + +# Helps bootstrapping the application when checked out from CVS. +# Requires GNU autoconf, GNU automake and GNU which. +# +# Copyright (C) 2004, by +# +# Carlo Wood, Run on IRC +# RSA-1024 0x624ACAD5 1997-01-26 Sign & Encrypt +# Fingerprint16 = 32 EC A7 B6 AC DB 65 A6 F6 F6 55 DD 1C DC FF 61 +# + +# Do sanity checks. +# Directory check. +if [ ! -f autogen.sh ]; then + echo "Run ./autogen.sh from the directory it exists in." + exit 1 +fi + +AUTOMAKE=${AUTOMAKE:-automake} +ACLOCAL=${ACLOCAL:-aclocal} +AUTOCONF=${AUTOCONF:-autoconf} + +($AUTOCONF --version) >/dev/null 2>/dev/null || (echo "You need GNU autoconf to install from CVS (ftp://ftp.gnu.org/gnu/autoconf/)"; exit 1) || exit 1 +($AUTOMAKE --version) >/dev/null 2>/dev/null || (echo "You need GNU automake 1.7 or higher to install from CVS (ftp://ftp.gnu.org/gnu/automake/)"; exit 1) || exit 1 + +# Determine the version of automake. +automake_version=`$AUTOMAKE --version | head -n 1 | sed -e 's/[^12]*\([12]\.[0-9][^ ]*\).*/\1/'` +automake_major=`echo $automake_version | cut -f1 -d.` +automake_minor=`echo $automake_version | cut -f2 -d.` +automake_version_number=`expr "$automake_major" \* 1000 \+ "$automake_minor"` + +# Require automake 1.7. +if expr "1007" \> "$automake_version_number" >/dev/null; then + $AUTOMAKE --version | head -n 1 + echo "" + echo "Fatal error: automake 1.7 or higher is required. Please set \$AUTOMAKE" + echo "to point to a newer automake, or upgrade." + echo "" + exit 1 +fi + +run() +{ + echo "Running $1 ..." + $1 +} + +# This is needed when someone just upgraded automake and this cache is still generated by an old version. +rm -rf autom4te.cache config.cache + +run "$ACLOCAL" +run "$AUTOCONF" +run "$AUTOMAKE --add-missing --foreign" + diff --git a/tidal-link/link/modules/asio-standalone/asio/boost_asio.manifest b/tidal-link/link/modules/asio-standalone/asio/boost_asio.manifest new file mode 100644 index 000000000..9c6c6e2bc --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/boost_asio.manifest @@ -0,0 +1,6153 @@ +/ +/boost/ +/boost/asio/ +/boost/asio/any_io_executor.hpp +/boost/asio/associated_allocator.hpp +/boost/asio/associated_executor.hpp +/boost/asio/async_result.hpp +/boost/asio/awaitable.hpp +/boost/asio/basic_datagram_socket.hpp +/boost/asio/basic_deadline_timer.hpp +/boost/asio/basic_io_object.hpp +/boost/asio/basic_raw_socket.hpp +/boost/asio/basic_seq_packet_socket.hpp +/boost/asio/basic_serial_port.hpp +/boost/asio/basic_signal_set.hpp +/boost/asio/basic_socket_acceptor.hpp +/boost/asio/basic_socket.hpp +/boost/asio/basic_socket_iostream.hpp +/boost/asio/basic_socket_streambuf.hpp +/boost/asio/basic_streambuf_fwd.hpp +/boost/asio/basic_streambuf.hpp +/boost/asio/basic_stream_socket.hpp +/boost/asio/basic_waitable_timer.hpp +/boost/asio/bind_executor.hpp +/boost/asio/buffered_read_stream_fwd.hpp +/boost/asio/buffered_read_stream.hpp +/boost/asio/buffered_stream_fwd.hpp +/boost/asio/buffered_stream.hpp +/boost/asio/buffered_write_stream_fwd.hpp +/boost/asio/buffered_write_stream.hpp +/boost/asio/buffer.hpp +/boost/asio/buffers_iterator.hpp +/boost/asio/completion_condition.hpp +/boost/asio/compose.hpp +/boost/asio/connect.hpp +/boost/asio/coroutine.hpp +/boost/asio/co_spawn.hpp +/boost/asio/deadline_timer.hpp +/boost/asio/defer.hpp +/boost/asio/detached.hpp +/boost/asio/detail/ +/boost/asio/detail/array_fwd.hpp +/boost/asio/detail/array.hpp +/boost/asio/detail/assert.hpp +/boost/asio/detail/atomic_count.hpp +/boost/asio/detail/base_from_completion_cond.hpp +/boost/asio/detail/bind_handler.hpp +/boost/asio/detail/blocking_executor_op.hpp +/boost/asio/detail/buffered_stream_storage.hpp +/boost/asio/detail/buffer_resize_guard.hpp +/boost/asio/detail/buffer_sequence_adapter.hpp +/boost/asio/detail/bulk_executor_op.hpp +/boost/asio/detail/call_stack.hpp +/boost/asio/detail/chrono.hpp +/boost/asio/detail/chrono_time_traits.hpp +/boost/asio/detail/completion_handler.hpp +/boost/asio/detail/concurrency_hint.hpp +/boost/asio/detail/conditionally_enabled_event.hpp +/boost/asio/detail/conditionally_enabled_mutex.hpp +/boost/asio/detail/config.hpp +/boost/asio/detail/consuming_buffers.hpp +/boost/asio/detail/cstddef.hpp +/boost/asio/detail/cstdint.hpp +/boost/asio/detail/date_time_fwd.hpp +/boost/asio/detail/deadline_timer_service.hpp +/boost/asio/detail/dependent_type.hpp +/boost/asio/detail/descriptor_ops.hpp +/boost/asio/detail/descriptor_read_op.hpp +/boost/asio/detail/descriptor_write_op.hpp +/boost/asio/detail/dev_poll_reactor.hpp +/boost/asio/detail/epoll_reactor.hpp +/boost/asio/detail/eventfd_select_interrupter.hpp +/boost/asio/detail/event.hpp +/boost/asio/detail/executor_function.hpp +/boost/asio/detail/executor_op.hpp +/boost/asio/detail/fd_set_adapter.hpp +/boost/asio/detail/fenced_block.hpp +/boost/asio/detail/functional.hpp +/boost/asio/detail/future.hpp +/boost/asio/detail/gcc_arm_fenced_block.hpp +/boost/asio/detail/gcc_hppa_fenced_block.hpp +/boost/asio/detail/gcc_sync_fenced_block.hpp +/boost/asio/detail/gcc_x86_fenced_block.hpp +/boost/asio/detail/global.hpp +/boost/asio/detail/handler_alloc_helpers.hpp +/boost/asio/detail/handler_cont_helpers.hpp +/boost/asio/detail/handler_invoke_helpers.hpp +/boost/asio/detail/handler_tracking.hpp +/boost/asio/detail/handler_type_requirements.hpp +/boost/asio/detail/handler_work.hpp +/boost/asio/detail/hash_map.hpp +/boost/asio/detail/impl/ +/boost/asio/detail/impl/buffer_sequence_adapter.ipp +/boost/asio/detail/impl/descriptor_ops.ipp +/boost/asio/detail/impl/dev_poll_reactor.hpp +/boost/asio/detail/impl/dev_poll_reactor.ipp +/boost/asio/detail/impl/epoll_reactor.hpp +/boost/asio/detail/impl/epoll_reactor.ipp +/boost/asio/detail/impl/eventfd_select_interrupter.ipp +/boost/asio/detail/impl/handler_tracking.ipp +/boost/asio/detail/impl/kqueue_reactor.hpp +/boost/asio/detail/impl/kqueue_reactor.ipp +/boost/asio/detail/impl/null_event.ipp +/boost/asio/detail/impl/pipe_select_interrupter.ipp +/boost/asio/detail/impl/posix_event.ipp +/boost/asio/detail/impl/posix_mutex.ipp +/boost/asio/detail/impl/posix_thread.ipp +/boost/asio/detail/impl/posix_tss_ptr.ipp +/boost/asio/detail/impl/reactive_descriptor_service.ipp +/boost/asio/detail/impl/reactive_serial_port_service.ipp +/boost/asio/detail/impl/reactive_socket_service_base.ipp +/boost/asio/detail/impl/resolver_service_base.ipp +/boost/asio/detail/impl/scheduler.ipp +/boost/asio/detail/impl/select_reactor.hpp +/boost/asio/detail/impl/select_reactor.ipp +/boost/asio/detail/impl/service_registry.hpp +/boost/asio/detail/impl/service_registry.ipp +/boost/asio/detail/impl/signal_set_service.ipp +/boost/asio/detail/impl/socket_ops.ipp +/boost/asio/detail/impl/socket_select_interrupter.ipp +/boost/asio/detail/impl/strand_executor_service.hpp +/boost/asio/detail/impl/strand_executor_service.ipp +/boost/asio/detail/impl/strand_service.hpp +/boost/asio/detail/impl/strand_service.ipp +/boost/asio/detail/impl/throw_error.ipp +/boost/asio/detail/impl/timer_queue_ptime.ipp +/boost/asio/detail/impl/timer_queue_set.ipp +/boost/asio/detail/impl/win_event.ipp +/boost/asio/detail/impl/win_iocp_handle_service.ipp +/boost/asio/detail/impl/win_iocp_io_context.hpp +/boost/asio/detail/impl/win_iocp_io_context.ipp +/boost/asio/detail/impl/win_iocp_serial_port_service.ipp +/boost/asio/detail/impl/win_iocp_socket_service_base.ipp +/boost/asio/detail/impl/win_mutex.ipp +/boost/asio/detail/impl/win_object_handle_service.ipp +/boost/asio/detail/impl/winrt_ssocket_service_base.ipp +/boost/asio/detail/impl/winrt_timer_scheduler.hpp +/boost/asio/detail/impl/winrt_timer_scheduler.ipp +/boost/asio/detail/impl/winsock_init.ipp +/boost/asio/detail/impl/win_static_mutex.ipp +/boost/asio/detail/impl/win_thread.ipp +/boost/asio/detail/impl/win_tss_ptr.ipp +/boost/asio/detail/io_control.hpp +/boost/asio/detail/io_object_impl.hpp +/boost/asio/detail/is_buffer_sequence.hpp +/boost/asio/detail/is_executor.hpp +/boost/asio/detail/keyword_tss_ptr.hpp +/boost/asio/detail/kqueue_reactor.hpp +/boost/asio/detail/limits.hpp +/boost/asio/detail/local_free_on_block_exit.hpp +/boost/asio/detail/macos_fenced_block.hpp +/boost/asio/detail/memory.hpp +/boost/asio/detail/mutex.hpp +/boost/asio/detail/non_const_lvalue.hpp +/boost/asio/detail/noncopyable.hpp +/boost/asio/detail/null_event.hpp +/boost/asio/detail/null_fenced_block.hpp +/boost/asio/detail/null_global.hpp +/boost/asio/detail/null_mutex.hpp +/boost/asio/detail/null_reactor.hpp +/boost/asio/detail/null_signal_blocker.hpp +/boost/asio/detail/null_socket_service.hpp +/boost/asio/detail/null_static_mutex.hpp +/boost/asio/detail/null_thread.hpp +/boost/asio/detail/null_tss_ptr.hpp +/boost/asio/detail/object_pool.hpp +/boost/asio/detail/old_win_sdk_compat.hpp +/boost/asio/detail/operation.hpp +/boost/asio/detail/op_queue.hpp +/boost/asio/detail/pipe_select_interrupter.hpp +/boost/asio/detail/pop_options.hpp +/boost/asio/detail/posix_event.hpp +/boost/asio/detail/posix_fd_set_adapter.hpp +/boost/asio/detail/posix_global.hpp +/boost/asio/detail/posix_mutex.hpp +/boost/asio/detail/posix_signal_blocker.hpp +/boost/asio/detail/posix_static_mutex.hpp +/boost/asio/detail/posix_thread.hpp +/boost/asio/detail/posix_tss_ptr.hpp +/boost/asio/detail/push_options.hpp +/boost/asio/detail/reactive_descriptor_service.hpp +/boost/asio/detail/reactive_null_buffers_op.hpp +/boost/asio/detail/reactive_serial_port_service.hpp +/boost/asio/detail/reactive_socket_accept_op.hpp +/boost/asio/detail/reactive_socket_connect_op.hpp +/boost/asio/detail/reactive_socket_recvfrom_op.hpp +/boost/asio/detail/reactive_socket_recvmsg_op.hpp +/boost/asio/detail/reactive_socket_recv_op.hpp +/boost/asio/detail/reactive_socket_send_op.hpp +/boost/asio/detail/reactive_socket_sendto_op.hpp +/boost/asio/detail/reactive_socket_service_base.hpp +/boost/asio/detail/reactive_socket_service.hpp +/boost/asio/detail/reactive_wait_op.hpp +/boost/asio/detail/reactor_fwd.hpp +/boost/asio/detail/reactor.hpp +/boost/asio/detail/reactor_op.hpp +/boost/asio/detail/reactor_op_queue.hpp +/boost/asio/detail/recycling_allocator.hpp +/boost/asio/detail/regex_fwd.hpp +/boost/asio/detail/resolve_endpoint_op.hpp +/boost/asio/detail/resolve_op.hpp +/boost/asio/detail/resolve_query_op.hpp +/boost/asio/detail/resolver_service_base.hpp +/boost/asio/detail/resolver_service.hpp +/boost/asio/detail/scheduler.hpp +/boost/asio/detail/scheduler_operation.hpp +/boost/asio/detail/scheduler_thread_info.hpp +/boost/asio/detail/scoped_lock.hpp +/boost/asio/detail/scoped_ptr.hpp +/boost/asio/detail/select_interrupter.hpp +/boost/asio/detail/select_reactor.hpp +/boost/asio/detail/service_registry.hpp +/boost/asio/detail/signal_blocker.hpp +/boost/asio/detail/signal_handler.hpp +/boost/asio/detail/signal_init.hpp +/boost/asio/detail/signal_op.hpp +/boost/asio/detail/signal_set_service.hpp +/boost/asio/detail/socket_holder.hpp +/boost/asio/detail/socket_ops.hpp +/boost/asio/detail/socket_option.hpp +/boost/asio/detail/socket_select_interrupter.hpp +/boost/asio/detail/socket_types.hpp +/boost/asio/detail/solaris_fenced_block.hpp +/boost/asio/detail/source_location.hpp +/boost/asio/detail/static_mutex.hpp +/boost/asio/detail/std_event.hpp +/boost/asio/detail/std_fenced_block.hpp +/boost/asio/detail/std_global.hpp +/boost/asio/detail/std_mutex.hpp +/boost/asio/detail/std_static_mutex.hpp +/boost/asio/detail/std_thread.hpp +/boost/asio/detail/strand_executor_service.hpp +/boost/asio/detail/strand_service.hpp +/boost/asio/detail/string_view.hpp +/boost/asio/detail/thread_context.hpp +/boost/asio/detail/thread_group.hpp +/boost/asio/detail/thread.hpp +/boost/asio/detail/thread_info_base.hpp +/boost/asio/detail/throw_error.hpp +/boost/asio/detail/throw_exception.hpp +/boost/asio/detail/timer_queue_base.hpp +/boost/asio/detail/timer_queue.hpp +/boost/asio/detail/timer_queue_ptime.hpp +/boost/asio/detail/timer_queue_set.hpp +/boost/asio/detail/timer_scheduler_fwd.hpp +/boost/asio/detail/timer_scheduler.hpp +/boost/asio/detail/tss_ptr.hpp +/boost/asio/detail/type_traits.hpp +/boost/asio/detail/variadic_templates.hpp +/boost/asio/detail/wait_handler.hpp +/boost/asio/detail/wait_op.hpp +/boost/asio/detail/winapp_thread.hpp +/boost/asio/detail/wince_thread.hpp +/boost/asio/detail/win_event.hpp +/boost/asio/detail/win_fd_set_adapter.hpp +/boost/asio/detail/win_fenced_block.hpp +/boost/asio/detail/win_global.hpp +/boost/asio/detail/win_iocp_handle_read_op.hpp +/boost/asio/detail/win_iocp_handle_service.hpp +/boost/asio/detail/win_iocp_handle_write_op.hpp +/boost/asio/detail/win_iocp_io_context.hpp +/boost/asio/detail/win_iocp_null_buffers_op.hpp +/boost/asio/detail/win_iocp_operation.hpp +/boost/asio/detail/win_iocp_overlapped_op.hpp +/boost/asio/detail/win_iocp_overlapped_ptr.hpp +/boost/asio/detail/win_iocp_serial_port_service.hpp +/boost/asio/detail/win_iocp_socket_accept_op.hpp +/boost/asio/detail/win_iocp_socket_connect_op.hpp +/boost/asio/detail/win_iocp_socket_recvfrom_op.hpp +/boost/asio/detail/win_iocp_socket_recvmsg_op.hpp +/boost/asio/detail/win_iocp_socket_recv_op.hpp +/boost/asio/detail/win_iocp_socket_send_op.hpp +/boost/asio/detail/win_iocp_socket_service_base.hpp +/boost/asio/detail/win_iocp_socket_service.hpp +/boost/asio/detail/win_iocp_thread_info.hpp +/boost/asio/detail/win_iocp_wait_op.hpp +/boost/asio/detail/win_mutex.hpp +/boost/asio/detail/win_object_handle_service.hpp +/boost/asio/detail/winrt_async_manager.hpp +/boost/asio/detail/winrt_async_op.hpp +/boost/asio/detail/winrt_resolve_op.hpp +/boost/asio/detail/winrt_resolver_service.hpp +/boost/asio/detail/winrt_socket_connect_op.hpp +/boost/asio/detail/winrt_socket_recv_op.hpp +/boost/asio/detail/winrt_socket_send_op.hpp +/boost/asio/detail/winrt_ssocket_service_base.hpp +/boost/asio/detail/winrt_ssocket_service.hpp +/boost/asio/detail/winrt_timer_scheduler.hpp +/boost/asio/detail/winrt_utils.hpp +/boost/asio/detail/winsock_init.hpp +/boost/asio/detail/win_static_mutex.hpp +/boost/asio/detail/win_thread.hpp +/boost/asio/detail/win_tss_ptr.hpp +/boost/asio/detail/work_dispatcher.hpp +/boost/asio/detail/wrapped_handler.hpp +/boost/asio/dispatch.hpp +/boost/asio/error.hpp +/boost/asio/execution/ +/boost/asio/execution/allocator.hpp +/boost/asio/execution/any_executor.hpp +/boost/asio/execution/bad_executor.hpp +/boost/asio/execution/blocking_adaptation.hpp +/boost/asio/execution/blocking.hpp +/boost/asio/execution/bulk_execute.hpp +/boost/asio/execution/bulk_guarantee.hpp +/boost/asio/execution/connect.hpp +/boost/asio/execution/context_as.hpp +/boost/asio/execution/context.hpp +/boost/asio/execution_context.hpp +/boost/asio/execution/detail/ +/boost/asio/execution/detail/as_invocable.hpp +/boost/asio/execution/detail/as_operation.hpp +/boost/asio/execution/detail/as_receiver.hpp +/boost/asio/execution/detail/bulk_sender.hpp +/boost/asio/execution/detail/submit_receiver.hpp +/boost/asio/execution/detail/void_receiver.hpp +/boost/asio/execution/execute.hpp +/boost/asio/execution/executor.hpp +/boost/asio/execution.hpp +/boost/asio/execution/impl/ +/boost/asio/execution/impl/bad_executor.ipp +/boost/asio/execution/impl/receiver_invocation_error.ipp +/boost/asio/execution/invocable_archetype.hpp +/boost/asio/execution/mapping.hpp +/boost/asio/execution/occupancy.hpp +/boost/asio/execution/operation_state.hpp +/boost/asio/execution/outstanding_work.hpp +/boost/asio/execution/prefer_only.hpp +/boost/asio/execution/receiver.hpp +/boost/asio/execution/receiver_invocation_error.hpp +/boost/asio/execution/relationship.hpp +/boost/asio/execution/schedule.hpp +/boost/asio/execution/scheduler.hpp +/boost/asio/execution/sender.hpp +/boost/asio/execution/set_done.hpp +/boost/asio/execution/set_error.hpp +/boost/asio/execution/set_value.hpp +/boost/asio/execution/start.hpp +/boost/asio/execution/submit.hpp +/boost/asio/executor.hpp +/boost/asio/executor_work_guard.hpp +/boost/asio/generic/ +/boost/asio/generic/basic_endpoint.hpp +/boost/asio/generic/datagram_protocol.hpp +/boost/asio/generic/detail/ +/boost/asio/generic/detail/endpoint.hpp +/boost/asio/generic/detail/impl/ +/boost/asio/generic/detail/impl/endpoint.ipp +/boost/asio/generic/raw_protocol.hpp +/boost/asio/generic/seq_packet_protocol.hpp +/boost/asio/generic/stream_protocol.hpp +/boost/asio/handler_alloc_hook.hpp +/boost/asio/handler_continuation_hook.hpp +/boost/asio/handler_invoke_hook.hpp +/boost/asio/high_resolution_timer.hpp +/boost/asio.hpp +/boost/asio/impl/ +/boost/asio/impl/awaitable.hpp +/boost/asio/impl/buffered_read_stream.hpp +/boost/asio/impl/buffered_write_stream.hpp +/boost/asio/impl/compose.hpp +/boost/asio/impl/connect.hpp +/boost/asio/impl/co_spawn.hpp +/boost/asio/impl/defer.hpp +/boost/asio/impl/detached.hpp +/boost/asio/impl/dispatch.hpp +/boost/asio/impl/error.ipp +/boost/asio/impl/execution_context.hpp +/boost/asio/impl/execution_context.ipp +/boost/asio/impl/executor.hpp +/boost/asio/impl/executor.ipp +/boost/asio/impl/handler_alloc_hook.ipp +/boost/asio/impl/io_context.hpp +/boost/asio/impl/io_context.ipp +/boost/asio/impl/multiple_exceptions.ipp +/boost/asio/impl/post.hpp +/boost/asio/impl/read_at.hpp +/boost/asio/impl/read.hpp +/boost/asio/impl/read_until.hpp +/boost/asio/impl/redirect_error.hpp +/boost/asio/impl/serial_port_base.hpp +/boost/asio/impl/serial_port_base.ipp +/boost/asio/impl/spawn.hpp +/boost/asio/impl/src.cpp +/boost/asio/impl/src.hpp +/boost/asio/impl/system_context.hpp +/boost/asio/impl/system_context.ipp +/boost/asio/impl/system_executor.hpp +/boost/asio/impl/thread_pool.hpp +/boost/asio/impl/thread_pool.ipp +/boost/asio/impl/use_awaitable.hpp +/boost/asio/impl/use_future.hpp +/boost/asio/impl/write_at.hpp +/boost/asio/impl/write.hpp +/boost/asio/io_context.hpp +/boost/asio/io_context_strand.hpp +/boost/asio/io_service.hpp +/boost/asio/io_service_strand.hpp +/boost/asio/ip/ +/boost/asio/ip/address.hpp +/boost/asio/ip/address_v4.hpp +/boost/asio/ip/address_v4_iterator.hpp +/boost/asio/ip/address_v4_range.hpp +/boost/asio/ip/address_v6.hpp +/boost/asio/ip/address_v6_iterator.hpp +/boost/asio/ip/address_v6_range.hpp +/boost/asio/ip/bad_address_cast.hpp +/boost/asio/ip/basic_endpoint.hpp +/boost/asio/ip/basic_resolver_entry.hpp +/boost/asio/ip/basic_resolver.hpp +/boost/asio/ip/basic_resolver_iterator.hpp +/boost/asio/ip/basic_resolver_query.hpp +/boost/asio/ip/basic_resolver_results.hpp +/boost/asio/ip/detail/ +/boost/asio/ip/detail/endpoint.hpp +/boost/asio/ip/detail/impl/ +/boost/asio/ip/detail/impl/endpoint.ipp +/boost/asio/ip/detail/socket_option.hpp +/boost/asio/ip/host_name.hpp +/boost/asio/ip/icmp.hpp +/boost/asio/ip/impl/ +/boost/asio/ip/impl/address.hpp +/boost/asio/ip/impl/address.ipp +/boost/asio/ip/impl/address_v4.hpp +/boost/asio/ip/impl/address_v4.ipp +/boost/asio/ip/impl/address_v6.hpp +/boost/asio/ip/impl/address_v6.ipp +/boost/asio/ip/impl/basic_endpoint.hpp +/boost/asio/ip/impl/host_name.ipp +/boost/asio/ip/impl/network_v4.hpp +/boost/asio/ip/impl/network_v4.ipp +/boost/asio/ip/impl/network_v6.hpp +/boost/asio/ip/impl/network_v6.ipp +/boost/asio/ip/multicast.hpp +/boost/asio/ip/network_v4.hpp +/boost/asio/ip/network_v6.hpp +/boost/asio/ip/resolver_base.hpp +/boost/asio/ip/resolver_query_base.hpp +/boost/asio/ip/tcp.hpp +/boost/asio/ip/udp.hpp +/boost/asio/ip/unicast.hpp +/boost/asio/ip/v6_only.hpp +/boost/asio/is_applicable_property.hpp +/boost/asio/is_executor.hpp +/boost/asio/is_read_buffered.hpp +/boost/asio/is_write_buffered.hpp +/boost/asio/local/ +/boost/asio/local/basic_endpoint.hpp +/boost/asio/local/connect_pair.hpp +/boost/asio/local/datagram_protocol.hpp +/boost/asio/local/detail/ +/boost/asio/local/detail/endpoint.hpp +/boost/asio/local/detail/impl/ +/boost/asio/local/detail/impl/endpoint.ipp +/boost/asio/local/stream_protocol.hpp +/boost/asio/multiple_exceptions.hpp +/boost/asio/packaged_task.hpp +/boost/asio/placeholders.hpp +/boost/asio/posix/ +/boost/asio/posix/basic_descriptor.hpp +/boost/asio/posix/basic_stream_descriptor.hpp +/boost/asio/posix/descriptor_base.hpp +/boost/asio/posix/descriptor.hpp +/boost/asio/posix/stream_descriptor.hpp +/boost/asio/post.hpp +/boost/asio/prefer.hpp +/boost/asio/query.hpp +/boost/asio/read_at.hpp +/boost/asio/read.hpp +/boost/asio/read_until.hpp +/boost/asio/redirect_error.hpp +/boost/asio/require_concept.hpp +/boost/asio/require.hpp +/boost/asio/serial_port_base.hpp +/boost/asio/serial_port.hpp +/boost/asio/signal_set.hpp +/boost/asio/socket_base.hpp +/boost/asio/spawn.hpp +/boost/asio/ssl/ +/boost/asio/ssl/context_base.hpp +/boost/asio/ssl/context.hpp +/boost/asio/ssl/detail/ +/boost/asio/ssl/detail/buffered_handshake_op.hpp +/boost/asio/ssl/detail/engine.hpp +/boost/asio/ssl/detail/handshake_op.hpp +/boost/asio/ssl/detail/impl/ +/boost/asio/ssl/detail/impl/engine.ipp +/boost/asio/ssl/detail/impl/openssl_init.ipp +/boost/asio/ssl/detail/io.hpp +/boost/asio/ssl/detail/openssl_init.hpp +/boost/asio/ssl/detail/openssl_types.hpp +/boost/asio/ssl/detail/password_callback.hpp +/boost/asio/ssl/detail/read_op.hpp +/boost/asio/ssl/detail/shutdown_op.hpp +/boost/asio/ssl/detail/stream_core.hpp +/boost/asio/ssl/detail/verify_callback.hpp +/boost/asio/ssl/detail/write_op.hpp +/boost/asio/ssl/error.hpp +/boost/asio/ssl/host_name_verification.hpp +/boost/asio/ssl.hpp +/boost/asio/ssl/impl/ +/boost/asio/ssl/impl/context.hpp +/boost/asio/ssl/impl/context.ipp +/boost/asio/ssl/impl/error.ipp +/boost/asio/ssl/impl/host_name_verification.ipp +/boost/asio/ssl/impl/rfc2818_verification.ipp +/boost/asio/ssl/impl/src.hpp +/boost/asio/ssl/rfc2818_verification.hpp +/boost/asio/ssl/stream_base.hpp +/boost/asio/ssl/stream.hpp +/boost/asio/ssl/verify_context.hpp +/boost/asio/ssl/verify_mode.hpp +/boost/asio/static_thread_pool.hpp +/boost/asio/steady_timer.hpp +/boost/asio/strand.hpp +/boost/asio/streambuf.hpp +/boost/asio/system_context.hpp +/boost/asio/system_executor.hpp +/boost/asio/system_timer.hpp +/boost/asio/this_coro.hpp +/boost/asio/thread_pool.hpp +/boost/asio/time_traits.hpp +/boost/asio/traits/ +/boost/asio/traits/bulk_execute_free.hpp +/boost/asio/traits/bulk_execute_member.hpp +/boost/asio/traits/connect_free.hpp +/boost/asio/traits/connect_member.hpp +/boost/asio/traits/equality_comparable.hpp +/boost/asio/traits/execute_free.hpp +/boost/asio/traits/execute_member.hpp +/boost/asio/traits/prefer_free.hpp +/boost/asio/traits/prefer_member.hpp +/boost/asio/traits/query_free.hpp +/boost/asio/traits/query_member.hpp +/boost/asio/traits/query_static_constexpr_member.hpp +/boost/asio/traits/require_concept_free.hpp +/boost/asio/traits/require_concept_member.hpp +/boost/asio/traits/require_free.hpp +/boost/asio/traits/require_member.hpp +/boost/asio/traits/schedule_free.hpp +/boost/asio/traits/schedule_member.hpp +/boost/asio/traits/set_done_free.hpp +/boost/asio/traits/set_done_member.hpp +/boost/asio/traits/set_error_free.hpp +/boost/asio/traits/set_error_member.hpp +/boost/asio/traits/set_value_free.hpp +/boost/asio/traits/set_value_member.hpp +/boost/asio/traits/start_free.hpp +/boost/asio/traits/start_member.hpp +/boost/asio/traits/static_query.hpp +/boost/asio/traits/static_require_concept.hpp +/boost/asio/traits/static_require.hpp +/boost/asio/traits/submit_free.hpp +/boost/asio/traits/submit_member.hpp +/boost/asio/ts/ +/boost/asio/ts/buffer.hpp +/boost/asio/ts/executor.hpp +/boost/asio/ts/internet.hpp +/boost/asio/ts/io_context.hpp +/boost/asio/ts/netfwd.hpp +/boost/asio/ts/net.hpp +/boost/asio/ts/socket.hpp +/boost/asio/ts/timer.hpp +/boost/asio/unyield.hpp +/boost/asio/use_awaitable.hpp +/boost/asio/use_future.hpp +/boost/asio/uses_executor.hpp +/boost/asio/version.hpp +/boost/asio/wait_traits.hpp +/boost/asio/windows/ +/boost/asio/windows/basic_object_handle.hpp +/boost/asio/windows/basic_overlapped_handle.hpp +/boost/asio/windows/basic_random_access_handle.hpp +/boost/asio/windows/basic_stream_handle.hpp +/boost/asio/windows/object_handle.hpp +/boost/asio/windows/overlapped_handle.hpp +/boost/asio/windows/overlapped_ptr.hpp +/boost/asio/windows/random_access_handle.hpp +/boost/asio/windows/stream_handle.hpp +/boost/asio/write_at.hpp +/boost/asio/write.hpp +/boost/asio/yield.hpp +/boost/cerrno.hpp +/boost/config/ +/boost/config/warning_disable.hpp +/boost/system/ +/boost/system/api_config.hpp +/boost/system/config.hpp +/boost/system/cygwin_error.hpp +/boost/system/detail/ +/boost/system/detail/config.hpp +/boost/system/detail/generic_category.hpp +/boost/system/detail/std_interoperability.hpp +/boost/system/detail/system_category_posix.hpp +/boost/system/detail/system_category_win32.hpp +/boost/system/error_code.hpp +/boost/system/linux_error.hpp +/boost/system/system_error.hpp +/boost/system/windows_error.hpp +/doc/ +/doc/html/ +/doc/html/boost_asio/ +/doc/html/boost_asio/async_op1.png +/doc/html/boost_asio/async_op2.png +/doc/html/boost_asio/example/ +/doc/html/boost_asio/example/cpp03/ +/doc/html/boost_asio/example/cpp03/allocation/ +/doc/html/boost_asio/example/cpp03/allocation/server.cpp +/doc/html/boost_asio/example/cpp03/buffers/ +/doc/html/boost_asio/example/cpp03/buffers/reference_counted.cpp +/doc/html/boost_asio/example/cpp03/chat/ +/doc/html/boost_asio/example/cpp03/chat/chat_client.cpp +/doc/html/boost_asio/example/cpp03/chat/chat_message.hpp +/doc/html/boost_asio/example/cpp03/chat/chat_server.cpp +/doc/html/boost_asio/example/cpp03/chat/posix_chat_client.cpp +/doc/html/boost_asio/example/cpp03/echo/ +/doc/html/boost_asio/example/cpp03/echo/async_tcp_echo_server.cpp +/doc/html/boost_asio/example/cpp03/echo/async_udp_echo_server.cpp +/doc/html/boost_asio/example/cpp03/echo/blocking_tcp_echo_client.cpp +/doc/html/boost_asio/example/cpp03/echo/blocking_tcp_echo_server.cpp +/doc/html/boost_asio/example/cpp03/echo/blocking_udp_echo_client.cpp +/doc/html/boost_asio/example/cpp03/echo/blocking_udp_echo_server.cpp +/doc/html/boost_asio/example/cpp03/fork/ +/doc/html/boost_asio/example/cpp03/fork/daemon.cpp +/doc/html/boost_asio/example/cpp03/fork/process_per_connection.cpp +/doc/html/boost_asio/example/cpp03/http/ +/doc/html/boost_asio/example/cpp03/http/client/ +/doc/html/boost_asio/example/cpp03/http/client/async_client.cpp +/doc/html/boost_asio/example/cpp03/http/client/sync_client.cpp +/doc/html/boost_asio/example/cpp03/http/server/ +/doc/html/boost_asio/example/cpp03/http/server2/ +/doc/html/boost_asio/example/cpp03/http/server2/connection.cpp +/doc/html/boost_asio/example/cpp03/http/server2/connection.hpp +/doc/html/boost_asio/example/cpp03/http/server2/header.hpp +/doc/html/boost_asio/example/cpp03/http/server2/io_context_pool.cpp +/doc/html/boost_asio/example/cpp03/http/server2/io_context_pool.hpp +/doc/html/boost_asio/example/cpp03/http/server2/main.cpp +/doc/html/boost_asio/example/cpp03/http/server2/mime_types.cpp +/doc/html/boost_asio/example/cpp03/http/server2/mime_types.hpp +/doc/html/boost_asio/example/cpp03/http/server2/reply.cpp +/doc/html/boost_asio/example/cpp03/http/server2/reply.hpp +/doc/html/boost_asio/example/cpp03/http/server2/request_handler.cpp +/doc/html/boost_asio/example/cpp03/http/server2/request_handler.hpp +/doc/html/boost_asio/example/cpp03/http/server2/request.hpp +/doc/html/boost_asio/example/cpp03/http/server2/request_parser.cpp +/doc/html/boost_asio/example/cpp03/http/server2/request_parser.hpp +/doc/html/boost_asio/example/cpp03/http/server2/server.cpp +/doc/html/boost_asio/example/cpp03/http/server2/server.hpp +/doc/html/boost_asio/example/cpp03/http/server3/ +/doc/html/boost_asio/example/cpp03/http/server3/connection.cpp +/doc/html/boost_asio/example/cpp03/http/server3/connection.hpp +/doc/html/boost_asio/example/cpp03/http/server3/header.hpp +/doc/html/boost_asio/example/cpp03/http/server3/main.cpp +/doc/html/boost_asio/example/cpp03/http/server3/mime_types.cpp +/doc/html/boost_asio/example/cpp03/http/server3/mime_types.hpp +/doc/html/boost_asio/example/cpp03/http/server3/reply.cpp +/doc/html/boost_asio/example/cpp03/http/server3/reply.hpp +/doc/html/boost_asio/example/cpp03/http/server3/request_handler.cpp +/doc/html/boost_asio/example/cpp03/http/server3/request_handler.hpp +/doc/html/boost_asio/example/cpp03/http/server3/request.hpp +/doc/html/boost_asio/example/cpp03/http/server3/request_parser.cpp +/doc/html/boost_asio/example/cpp03/http/server3/request_parser.hpp +/doc/html/boost_asio/example/cpp03/http/server3/server.cpp +/doc/html/boost_asio/example/cpp03/http/server3/server.hpp +/doc/html/boost_asio/example/cpp03/http/server4/ +/doc/html/boost_asio/example/cpp03/http/server4/file_handler.cpp +/doc/html/boost_asio/example/cpp03/http/server4/file_handler.hpp +/doc/html/boost_asio/example/cpp03/http/server4/header.hpp +/doc/html/boost_asio/example/cpp03/http/server4/main.cpp +/doc/html/boost_asio/example/cpp03/http/server4/mime_types.cpp +/doc/html/boost_asio/example/cpp03/http/server4/mime_types.hpp +/doc/html/boost_asio/example/cpp03/http/server4/reply.cpp +/doc/html/boost_asio/example/cpp03/http/server4/reply.hpp +/doc/html/boost_asio/example/cpp03/http/server4/request.hpp +/doc/html/boost_asio/example/cpp03/http/server4/request_parser.cpp +/doc/html/boost_asio/example/cpp03/http/server4/request_parser.hpp +/doc/html/boost_asio/example/cpp03/http/server4/server.cpp +/doc/html/boost_asio/example/cpp03/http/server4/server.hpp +/doc/html/boost_asio/example/cpp03/http/server/connection.cpp +/doc/html/boost_asio/example/cpp03/http/server/connection.hpp +/doc/html/boost_asio/example/cpp03/http/server/connection_manager.cpp +/doc/html/boost_asio/example/cpp03/http/server/connection_manager.hpp +/doc/html/boost_asio/example/cpp03/http/server/header.hpp +/doc/html/boost_asio/example/cpp03/http/server/main.cpp +/doc/html/boost_asio/example/cpp03/http/server/mime_types.cpp +/doc/html/boost_asio/example/cpp03/http/server/mime_types.hpp +/doc/html/boost_asio/example/cpp03/http/server/reply.cpp +/doc/html/boost_asio/example/cpp03/http/server/reply.hpp +/doc/html/boost_asio/example/cpp03/http/server/request_handler.cpp +/doc/html/boost_asio/example/cpp03/http/server/request_handler.hpp +/doc/html/boost_asio/example/cpp03/http/server/request.hpp +/doc/html/boost_asio/example/cpp03/http/server/request_parser.cpp +/doc/html/boost_asio/example/cpp03/http/server/request_parser.hpp +/doc/html/boost_asio/example/cpp03/http/server/server.cpp +/doc/html/boost_asio/example/cpp03/http/server/server.hpp +/doc/html/boost_asio/example/cpp03/icmp/ +/doc/html/boost_asio/example/cpp03/icmp/icmp_header.hpp +/doc/html/boost_asio/example/cpp03/icmp/ipv4_header.hpp +/doc/html/boost_asio/example/cpp03/icmp/ping.cpp +/doc/html/boost_asio/example/cpp03/invocation/ +/doc/html/boost_asio/example/cpp03/invocation/prioritised_handlers.cpp +/doc/html/boost_asio/example/cpp03/iostreams/ +/doc/html/boost_asio/example/cpp03/iostreams/daytime_client.cpp +/doc/html/boost_asio/example/cpp03/iostreams/daytime_server.cpp +/doc/html/boost_asio/example/cpp03/iostreams/http_client.cpp +/doc/html/boost_asio/example/cpp03/local/ +/doc/html/boost_asio/example/cpp03/local/connect_pair.cpp +/doc/html/boost_asio/example/cpp03/local/iostream_client.cpp +/doc/html/boost_asio/example/cpp03/local/stream_client.cpp +/doc/html/boost_asio/example/cpp03/local/stream_server.cpp +/doc/html/boost_asio/example/cpp03/multicast/ +/doc/html/boost_asio/example/cpp03/multicast/receiver.cpp +/doc/html/boost_asio/example/cpp03/multicast/sender.cpp +/doc/html/boost_asio/example/cpp03/nonblocking/ +/doc/html/boost_asio/example/cpp03/nonblocking/third_party_lib.cpp +/doc/html/boost_asio/example/cpp03/porthopper/ +/doc/html/boost_asio/example/cpp03/porthopper/client.cpp +/doc/html/boost_asio/example/cpp03/porthopper/protocol.hpp +/doc/html/boost_asio/example/cpp03/porthopper/server.cpp +/doc/html/boost_asio/example/cpp03/serialization/ +/doc/html/boost_asio/example/cpp03/serialization/client.cpp +/doc/html/boost_asio/example/cpp03/serialization/connection.hpp +/doc/html/boost_asio/example/cpp03/serialization/server.cpp +/doc/html/boost_asio/example/cpp03/serialization/stock.hpp +/doc/html/boost_asio/example/cpp03/services/ +/doc/html/boost_asio/example/cpp03/services/basic_logger.hpp +/doc/html/boost_asio/example/cpp03/services/daytime_client.cpp +/doc/html/boost_asio/example/cpp03/services/logger.hpp +/doc/html/boost_asio/example/cpp03/services/logger_service.cpp +/doc/html/boost_asio/example/cpp03/services/logger_service.hpp +/doc/html/boost_asio/example/cpp03/socks4/ +/doc/html/boost_asio/example/cpp03/socks4/socks4.hpp +/doc/html/boost_asio/example/cpp03/socks4/sync_client.cpp +/doc/html/boost_asio/example/cpp03/spawn/ +/doc/html/boost_asio/example/cpp03/spawn/echo_server.cpp +/doc/html/boost_asio/example/cpp03/spawn/parallel_grep.cpp +/doc/html/boost_asio/example/cpp03/ssl/ +/doc/html/boost_asio/example/cpp03/ssl/client.cpp +/doc/html/boost_asio/example/cpp03/ssl/server.cpp +/doc/html/boost_asio/example/cpp03/timeouts/ +/doc/html/boost_asio/example/cpp03/timeouts/async_tcp_client.cpp +/doc/html/boost_asio/example/cpp03/timeouts/blocking_tcp_client.cpp +/doc/html/boost_asio/example/cpp03/timeouts/blocking_token_tcp_client.cpp +/doc/html/boost_asio/example/cpp03/timeouts/blocking_udp_client.cpp +/doc/html/boost_asio/example/cpp03/timeouts/server.cpp +/doc/html/boost_asio/example/cpp03/timers/ +/doc/html/boost_asio/example/cpp03/timers/time_t_timer.cpp +/doc/html/boost_asio/example/cpp03/windows/ +/doc/html/boost_asio/example/cpp03/windows/transmit_file.cpp +/doc/html/boost_asio/example/cpp11/ +/doc/html/boost_asio/example/cpp11/allocation/ +/doc/html/boost_asio/example/cpp11/allocation/server.cpp +/doc/html/boost_asio/example/cpp11/buffers/ +/doc/html/boost_asio/example/cpp11/buffers/reference_counted.cpp +/doc/html/boost_asio/example/cpp11/chat/ +/doc/html/boost_asio/example/cpp11/chat/chat_client.cpp +/doc/html/boost_asio/example/cpp11/chat/chat_message.hpp +/doc/html/boost_asio/example/cpp11/chat/chat_server.cpp +/doc/html/boost_asio/example/cpp11/echo/ +/doc/html/boost_asio/example/cpp11/echo/async_tcp_echo_server.cpp +/doc/html/boost_asio/example/cpp11/echo/async_udp_echo_server.cpp +/doc/html/boost_asio/example/cpp11/echo/blocking_tcp_echo_client.cpp +/doc/html/boost_asio/example/cpp11/echo/blocking_tcp_echo_server.cpp +/doc/html/boost_asio/example/cpp11/echo/blocking_udp_echo_client.cpp +/doc/html/boost_asio/example/cpp11/echo/blocking_udp_echo_server.cpp +/doc/html/boost_asio/example/cpp11/executors/ +/doc/html/boost_asio/example/cpp11/executors/actor.cpp +/doc/html/boost_asio/example/cpp11/executors/bank_account_1.cpp +/doc/html/boost_asio/example/cpp11/executors/bank_account_2.cpp +/doc/html/boost_asio/example/cpp11/executors/fork_join.cpp +/doc/html/boost_asio/example/cpp11/executors/pipeline.cpp +/doc/html/boost_asio/example/cpp11/executors/priority_scheduler.cpp +/doc/html/boost_asio/example/cpp11/fork/ +/doc/html/boost_asio/example/cpp11/fork/daemon.cpp +/doc/html/boost_asio/example/cpp11/fork/process_per_connection.cpp +/doc/html/boost_asio/example/cpp11/futures/ +/doc/html/boost_asio/example/cpp11/futures/daytime_client.cpp +/doc/html/boost_asio/example/cpp11/handler_tracking/ +/doc/html/boost_asio/example/cpp11/handler_tracking/async_tcp_echo_server.cpp +/doc/html/boost_asio/example/cpp11/handler_tracking/custom_tracking.hpp +/doc/html/boost_asio/example/cpp11/http/ +/doc/html/boost_asio/example/cpp11/http/server/ +/doc/html/boost_asio/example/cpp11/http/server/connection.cpp +/doc/html/boost_asio/example/cpp11/http/server/connection.hpp +/doc/html/boost_asio/example/cpp11/http/server/connection_manager.cpp +/doc/html/boost_asio/example/cpp11/http/server/connection_manager.hpp +/doc/html/boost_asio/example/cpp11/http/server/header.hpp +/doc/html/boost_asio/example/cpp11/http/server/main.cpp +/doc/html/boost_asio/example/cpp11/http/server/mime_types.cpp +/doc/html/boost_asio/example/cpp11/http/server/mime_types.hpp +/doc/html/boost_asio/example/cpp11/http/server/reply.cpp +/doc/html/boost_asio/example/cpp11/http/server/reply.hpp +/doc/html/boost_asio/example/cpp11/http/server/request_handler.cpp +/doc/html/boost_asio/example/cpp11/http/server/request_handler.hpp +/doc/html/boost_asio/example/cpp11/http/server/request.hpp +/doc/html/boost_asio/example/cpp11/http/server/request_parser.cpp +/doc/html/boost_asio/example/cpp11/http/server/request_parser.hpp +/doc/html/boost_asio/example/cpp11/http/server/server.cpp +/doc/html/boost_asio/example/cpp11/http/server/server.hpp +/doc/html/boost_asio/example/cpp11/invocation/ +/doc/html/boost_asio/example/cpp11/invocation/prioritised_handlers.cpp +/doc/html/boost_asio/example/cpp11/local/ +/doc/html/boost_asio/example/cpp11/local/connect_pair.cpp +/doc/html/boost_asio/example/cpp11/local/iostream_client.cpp +/doc/html/boost_asio/example/cpp11/local/stream_client.cpp +/doc/html/boost_asio/example/cpp11/local/stream_server.cpp +/doc/html/boost_asio/example/cpp11/multicast/ +/doc/html/boost_asio/example/cpp11/multicast/receiver.cpp +/doc/html/boost_asio/example/cpp11/multicast/sender.cpp +/doc/html/boost_asio/example/cpp11/nonblocking/ +/doc/html/boost_asio/example/cpp11/nonblocking/third_party_lib.cpp +/doc/html/boost_asio/example/cpp11/operations/ +/doc/html/boost_asio/example/cpp11/operations/composed_1.cpp +/doc/html/boost_asio/example/cpp11/operations/composed_2.cpp +/doc/html/boost_asio/example/cpp11/operations/composed_3.cpp +/doc/html/boost_asio/example/cpp11/operations/composed_4.cpp +/doc/html/boost_asio/example/cpp11/operations/composed_5.cpp +/doc/html/boost_asio/example/cpp11/operations/composed_6.cpp +/doc/html/boost_asio/example/cpp11/operations/composed_7.cpp +/doc/html/boost_asio/example/cpp11/operations/composed_8.cpp +/doc/html/boost_asio/example/cpp11/socks4/ +/doc/html/boost_asio/example/cpp11/socks4/socks4.hpp +/doc/html/boost_asio/example/cpp11/socks4/sync_client.cpp +/doc/html/boost_asio/example/cpp11/spawn/ +/doc/html/boost_asio/example/cpp11/spawn/echo_server.cpp +/doc/html/boost_asio/example/cpp11/spawn/parallel_grep.cpp +/doc/html/boost_asio/example/cpp11/ssl/ +/doc/html/boost_asio/example/cpp11/ssl/client.cpp +/doc/html/boost_asio/example/cpp11/ssl/server.cpp +/doc/html/boost_asio/example/cpp11/timeouts/ +/doc/html/boost_asio/example/cpp11/timeouts/async_tcp_client.cpp +/doc/html/boost_asio/example/cpp11/timeouts/blocking_tcp_client.cpp +/doc/html/boost_asio/example/cpp11/timeouts/blocking_token_tcp_client.cpp +/doc/html/boost_asio/example/cpp11/timeouts/blocking_udp_client.cpp +/doc/html/boost_asio/example/cpp11/timeouts/server.cpp +/doc/html/boost_asio/example/cpp11/timers/ +/doc/html/boost_asio/example/cpp11/timers/time_t_timer.cpp +/doc/html/boost_asio/example/cpp14/ +/doc/html/boost_asio/example/cpp14/operations/ +/doc/html/boost_asio/example/cpp14/operations/composed_1.cpp +/doc/html/boost_asio/example/cpp14/operations/composed_2.cpp +/doc/html/boost_asio/example/cpp14/operations/composed_3.cpp +/doc/html/boost_asio/example/cpp14/operations/composed_4.cpp +/doc/html/boost_asio/example/cpp14/operations/composed_5.cpp +/doc/html/boost_asio/example/cpp14/operations/composed_6.cpp +/doc/html/boost_asio/example/cpp14/operations/composed_7.cpp +/doc/html/boost_asio/example/cpp14/operations/composed_8.cpp +/doc/html/boost_asio/example/cpp17/ +/doc/html/boost_asio/example/cpp17/coroutines_ts/ +/doc/html/boost_asio/example/cpp17/coroutines_ts/chat_server.cpp +/doc/html/boost_asio/example/cpp17/coroutines_ts/echo_server.cpp +/doc/html/boost_asio/example/cpp17/coroutines_ts/echo_server_with_default.cpp +/doc/html/boost_asio/example/cpp17/coroutines_ts/range_based_for.cpp +/doc/html/boost_asio/example/cpp17/coroutines_ts/refactored_echo_server.cpp +/doc/html/boost_asio/examples/ +/doc/html/boost_asio/examples/cpp03_examples.html +/doc/html/boost_asio/examples/cpp11_examples.html +/doc/html/boost_asio/examples/cpp14_examples.html +/doc/html/boost_asio/examples/cpp17_examples.html +/doc/html/boost_asio/examples.html +/doc/html/boost_asio/history.html +/doc/html/boost_asio.html +/doc/html/boost_asio/index.html +/doc/html/boost_asio/net_ts.html +/doc/html/boost_asio/overview/ +/doc/html/boost_asio/overview/core/ +/doc/html/boost_asio/overview/core/allocation.html +/doc/html/boost_asio/overview/core/async.html +/doc/html/boost_asio/overview/core/basics.html +/doc/html/boost_asio/overview/core/buffers.html +/doc/html/boost_asio/overview/core/concurrency_hint.html +/doc/html/boost_asio/overview/core/coroutine.html +/doc/html/boost_asio/overview/core/coroutines_ts.html +/doc/html/boost_asio/overview/core/handler_tracking.html +/doc/html/boost_asio/overview/core.html +/doc/html/boost_asio/overview/core/line_based.html +/doc/html/boost_asio/overview/core/reactor.html +/doc/html/boost_asio/overview/core/spawn.html +/doc/html/boost_asio/overview/core/strands.html +/doc/html/boost_asio/overview/core/streams.html +/doc/html/boost_asio/overview/core/threads.html +/doc/html/boost_asio/overview/cpp2011/ +/doc/html/boost_asio/overview/cpp2011/array.html +/doc/html/boost_asio/overview/cpp2011/atomic.html +/doc/html/boost_asio/overview/cpp2011/chrono.html +/doc/html/boost_asio/overview/cpp2011/futures.html +/doc/html/boost_asio/overview/cpp2011.html +/doc/html/boost_asio/overview/cpp2011/move_handlers.html +/doc/html/boost_asio/overview/cpp2011/move_objects.html +/doc/html/boost_asio/overview/cpp2011/shared_ptr.html +/doc/html/boost_asio/overview/cpp2011/variadic.html +/doc/html/boost_asio/overview.html +/doc/html/boost_asio/overview/implementation.html +/doc/html/boost_asio/overview/networking/ +/doc/html/boost_asio/overview/networking/bsd_sockets.html +/doc/html/boost_asio/overview/networking.html +/doc/html/boost_asio/overview/networking/iostreams.html +/doc/html/boost_asio/overview/networking/other_protocols.html +/doc/html/boost_asio/overview/networking/protocols.html +/doc/html/boost_asio/overview/posix/ +/doc/html/boost_asio/overview/posix/fork.html +/doc/html/boost_asio/overview/posix.html +/doc/html/boost_asio/overview/posix/local.html +/doc/html/boost_asio/overview/posix/stream_descriptor.html +/doc/html/boost_asio/overview/rationale.html +/doc/html/boost_asio/overview/serial_ports.html +/doc/html/boost_asio/overview/signals.html +/doc/html/boost_asio/overview/ssl.html +/doc/html/boost_asio/overview/timers.html +/doc/html/boost_asio/overview/windows/ +/doc/html/boost_asio/overview/windows.html +/doc/html/boost_asio/overview/windows/object_handle.html +/doc/html/boost_asio/overview/windows/random_access_handle.html +/doc/html/boost_asio/overview/windows/stream_handle.html +/doc/html/boost_asio/proactor.png +/doc/html/boost_asio/reference/ +/doc/html/boost_asio/reference/AcceptableProtocol.html +/doc/html/boost_asio/reference/AcceptHandler.html +/doc/html/boost_asio/reference/any_io_executor.html +/doc/html/boost_asio/reference/asio_handler_allocate.html +/doc/html/boost_asio/reference/asio_handler_deallocate.html +/doc/html/boost_asio/reference/asio_handler_invoke/ +/doc/html/boost_asio/reference/asio_handler_invoke.html +/doc/html/boost_asio/reference/asio_handler_invoke/overload1.html +/doc/html/boost_asio/reference/asio_handler_invoke/overload2.html +/doc/html/boost_asio/reference/asio_handler_is_continuation.html +/doc/html/boost_asio/reference/associated_allocator/ +/doc/html/boost_asio/reference/associated_allocator/get.html +/doc/html/boost_asio/reference/associated_allocator.html +/doc/html/boost_asio/reference/associated_allocator/type.html +/doc/html/boost_asio/reference/associated_executor/ +/doc/html/boost_asio/reference/associated_executor/get.html +/doc/html/boost_asio/reference/associated_executor.html +/doc/html/boost_asio/reference/associated_executor/type.html +/doc/html/boost_asio/reference/async_completion/ +/doc/html/boost_asio/reference/async_completion/async_completion.html +/doc/html/boost_asio/reference/async_completion/completion_handler.html +/doc/html/boost_asio/reference/async_completion/completion_handler_type.html +/doc/html/boost_asio/reference/async_completion.html +/doc/html/boost_asio/reference/async_completion/result.html +/doc/html/boost_asio/reference/async_compose.html +/doc/html/boost_asio/reference/async_connect/ +/doc/html/boost_asio/reference/async_connect.html +/doc/html/boost_asio/reference/async_connect/overload1.html +/doc/html/boost_asio/reference/async_connect/overload2.html +/doc/html/boost_asio/reference/async_connect/overload3.html +/doc/html/boost_asio/reference/async_connect/overload4.html +/doc/html/boost_asio/reference/async_connect/overload5.html +/doc/html/boost_asio/reference/async_connect/overload6.html +/doc/html/boost_asio/reference/asynchronous_operations.html +/doc/html/boost_asio/reference/asynchronous_socket_operations.html +/doc/html/boost_asio/reference/async_initiate.html +/doc/html/boost_asio/reference/AsyncRandomAccessReadDevice.html +/doc/html/boost_asio/reference/AsyncRandomAccessWriteDevice.html +/doc/html/boost_asio/reference/async_read/ +/doc/html/boost_asio/reference/async_read_at/ +/doc/html/boost_asio/reference/async_read_at.html +/doc/html/boost_asio/reference/async_read_at/overload1.html +/doc/html/boost_asio/reference/async_read_at/overload2.html +/doc/html/boost_asio/reference/async_read_at/overload3.html +/doc/html/boost_asio/reference/async_read_at/overload4.html +/doc/html/boost_asio/reference/async_read.html +/doc/html/boost_asio/reference/async_read/overload1.html +/doc/html/boost_asio/reference/async_read/overload2.html +/doc/html/boost_asio/reference/async_read/overload3.html +/doc/html/boost_asio/reference/async_read/overload4.html +/doc/html/boost_asio/reference/async_read/overload5.html +/doc/html/boost_asio/reference/async_read/overload6.html +/doc/html/boost_asio/reference/async_read/overload7.html +/doc/html/boost_asio/reference/async_read/overload8.html +/doc/html/boost_asio/reference/AsyncReadStream.html +/doc/html/boost_asio/reference/async_read_until/ +/doc/html/boost_asio/reference/async_read_until.html +/doc/html/boost_asio/reference/async_read_until/overload10.html +/doc/html/boost_asio/reference/async_read_until/overload11.html +/doc/html/boost_asio/reference/async_read_until/overload12.html +/doc/html/boost_asio/reference/async_read_until/overload1.html +/doc/html/boost_asio/reference/async_read_until/overload2.html +/doc/html/boost_asio/reference/async_read_until/overload3.html +/doc/html/boost_asio/reference/async_read_until/overload4.html +/doc/html/boost_asio/reference/async_read_until/overload5.html +/doc/html/boost_asio/reference/async_read_until/overload6.html +/doc/html/boost_asio/reference/async_read_until/overload7.html +/doc/html/boost_asio/reference/async_read_until/overload8.html +/doc/html/boost_asio/reference/async_read_until/overload9.html +/doc/html/boost_asio/reference/async_result/ +/doc/html/boost_asio/reference/async_result/async_result.html +/doc/html/boost_asio/reference/async_result/completion_handler_type.html +/doc/html/boost_asio/reference/async_result/get.html +/doc/html/boost_asio/reference/async_result.html +/doc/html/boost_asio/reference/async_result/initiate.html +/doc/html/boost_asio/reference/async_result_lt__std__packaged_task_lt__Result_lp_Args_ellipsis__rp__gt__comma__Signature__gt_/ +/doc/html/boost_asio/reference/async_result_lt__std__packaged_task_lt__Result_lp_Args_ellipsis__rp__gt__comma__Signature__gt_/async_result.html +/doc/html/boost_asio/reference/async_result_lt__std__packaged_task_lt__Result_lp_Args_ellipsis__rp__gt__comma__Signature__gt_/completion_handler_type.html +/doc/html/boost_asio/reference/async_result_lt__std__packaged_task_lt__Result_lp_Args_ellipsis__rp__gt__comma__Signature__gt_/get.html +/doc/html/boost_asio/reference/async_result_lt__std__packaged_task_lt__Result_lp_Args_ellipsis__rp__gt__comma__Signature__gt_.html +/doc/html/boost_asio/reference/async_result_lt__std__packaged_task_lt__Result_lp_Args_ellipsis__rp__gt__comma__Signature__gt_/return_type.html +/doc/html/boost_asio/reference/async_result/return_type.html +/doc/html/boost_asio/reference/async_write/ +/doc/html/boost_asio/reference/async_write_at/ +/doc/html/boost_asio/reference/async_write_at.html +/doc/html/boost_asio/reference/async_write_at/overload1.html +/doc/html/boost_asio/reference/async_write_at/overload2.html +/doc/html/boost_asio/reference/async_write_at/overload3.html +/doc/html/boost_asio/reference/async_write_at/overload4.html +/doc/html/boost_asio/reference/async_write.html +/doc/html/boost_asio/reference/async_write/overload1.html +/doc/html/boost_asio/reference/async_write/overload2.html +/doc/html/boost_asio/reference/async_write/overload3.html +/doc/html/boost_asio/reference/async_write/overload4.html +/doc/html/boost_asio/reference/async_write/overload5.html +/doc/html/boost_asio/reference/async_write/overload6.html +/doc/html/boost_asio/reference/async_write/overload7.html +/doc/html/boost_asio/reference/async_write/overload8.html +/doc/html/boost_asio/reference/AsyncWriteStream.html +/doc/html/boost_asio/reference/awaitable/ +/doc/html/boost_asio/reference/awaitable/awaitable/ +/doc/html/boost_asio/reference/awaitable/_awaitable.html +/doc/html/boost_asio/reference/awaitable/awaitable.html +/doc/html/boost_asio/reference/awaitable/awaitable/overload1.html +/doc/html/boost_asio/reference/awaitable/awaitable/overload2.html +/doc/html/boost_asio/reference/awaitable/executor_type.html +/doc/html/boost_asio/reference/awaitable.html +/doc/html/boost_asio/reference/awaitable/valid.html +/doc/html/boost_asio/reference/awaitable/value_type.html +/doc/html/boost_asio/reference/bad_executor/ +/doc/html/boost_asio/reference/bad_executor/bad_executor.html +/doc/html/boost_asio/reference/bad_executor.html +/doc/html/boost_asio/reference/bad_executor/what.html +/doc/html/boost_asio/reference/basic_datagram_socket/ +/doc/html/boost_asio/reference/basic_datagram_socket/assign/ +/doc/html/boost_asio/reference/basic_datagram_socket/assign.html +/doc/html/boost_asio/reference/basic_datagram_socket/assign/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/assign/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/async_connect.html +/doc/html/boost_asio/reference/basic_datagram_socket/async_receive/ +/doc/html/boost_asio/reference/basic_datagram_socket/async_receive_from/ +/doc/html/boost_asio/reference/basic_datagram_socket/async_receive_from.html +/doc/html/boost_asio/reference/basic_datagram_socket/async_receive_from/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/async_receive_from/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/async_receive.html +/doc/html/boost_asio/reference/basic_datagram_socket/async_receive/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/async_receive/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/async_send/ +/doc/html/boost_asio/reference/basic_datagram_socket/async_send.html +/doc/html/boost_asio/reference/basic_datagram_socket/async_send/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/async_send/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/async_send_to/ +/doc/html/boost_asio/reference/basic_datagram_socket/async_send_to.html +/doc/html/boost_asio/reference/basic_datagram_socket/async_send_to/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/async_send_to/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/async_wait.html +/doc/html/boost_asio/reference/basic_datagram_socket/at_mark/ +/doc/html/boost_asio/reference/basic_datagram_socket/at_mark.html +/doc/html/boost_asio/reference/basic_datagram_socket/at_mark/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/at_mark/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/available/ +/doc/html/boost_asio/reference/basic_datagram_socket/available.html +/doc/html/boost_asio/reference/basic_datagram_socket/available/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/available/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/basic_datagram_socket/ +/doc/html/boost_asio/reference/basic_datagram_socket/_basic_datagram_socket.html +/doc/html/boost_asio/reference/basic_datagram_socket/basic_datagram_socket.html +/doc/html/boost_asio/reference/basic_datagram_socket/basic_datagram_socket/overload10.html +/doc/html/boost_asio/reference/basic_datagram_socket/basic_datagram_socket/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/basic_datagram_socket/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/basic_datagram_socket/overload3.html +/doc/html/boost_asio/reference/basic_datagram_socket/basic_datagram_socket/overload4.html +/doc/html/boost_asio/reference/basic_datagram_socket/basic_datagram_socket/overload5.html +/doc/html/boost_asio/reference/basic_datagram_socket/basic_datagram_socket/overload6.html +/doc/html/boost_asio/reference/basic_datagram_socket/basic_datagram_socket/overload7.html +/doc/html/boost_asio/reference/basic_datagram_socket/basic_datagram_socket/overload8.html +/doc/html/boost_asio/reference/basic_datagram_socket/basic_datagram_socket/overload9.html +/doc/html/boost_asio/reference/basic_datagram_socket/bind/ +/doc/html/boost_asio/reference/basic_datagram_socket/bind.html +/doc/html/boost_asio/reference/basic_datagram_socket/bind/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/bind/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/broadcast.html +/doc/html/boost_asio/reference/basic_datagram_socket/bytes_readable.html +/doc/html/boost_asio/reference/basic_datagram_socket/cancel/ +/doc/html/boost_asio/reference/basic_datagram_socket/cancel.html +/doc/html/boost_asio/reference/basic_datagram_socket/cancel/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/cancel/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/close/ +/doc/html/boost_asio/reference/basic_datagram_socket/close.html +/doc/html/boost_asio/reference/basic_datagram_socket/close/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/close/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/connect/ +/doc/html/boost_asio/reference/basic_datagram_socket/connect.html +/doc/html/boost_asio/reference/basic_datagram_socket/connect/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/connect/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/debug.html +/doc/html/boost_asio/reference/basic_datagram_socket/do_not_route.html +/doc/html/boost_asio/reference/basic_datagram_socket/enable_connection_aborted.html +/doc/html/boost_asio/reference/basic_datagram_socket/endpoint_type.html +/doc/html/boost_asio/reference/basic_datagram_socket/executor_type.html +/doc/html/boost_asio/reference/basic_datagram_socket/get_executor.html +/doc/html/boost_asio/reference/basic_datagram_socket/get_option/ +/doc/html/boost_asio/reference/basic_datagram_socket/get_option.html +/doc/html/boost_asio/reference/basic_datagram_socket/get_option/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/get_option/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket.html +/doc/html/boost_asio/reference/basic_datagram_socket/impl_.html +/doc/html/boost_asio/reference/basic_datagram_socket/io_control/ +/doc/html/boost_asio/reference/basic_datagram_socket/io_control.html +/doc/html/boost_asio/reference/basic_datagram_socket/io_control/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/io_control/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/is_open.html +/doc/html/boost_asio/reference/basic_datagram_socket/keep_alive.html +/doc/html/boost_asio/reference/basic_datagram_socket/linger.html +/doc/html/boost_asio/reference/basic_datagram_socket/local_endpoint/ +/doc/html/boost_asio/reference/basic_datagram_socket/local_endpoint.html +/doc/html/boost_asio/reference/basic_datagram_socket/local_endpoint/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/local_endpoint/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/lowest_layer/ +/doc/html/boost_asio/reference/basic_datagram_socket/lowest_layer.html +/doc/html/boost_asio/reference/basic_datagram_socket/lowest_layer/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/lowest_layer/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/lowest_layer_type.html +/doc/html/boost_asio/reference/basic_datagram_socket/max_connections.html +/doc/html/boost_asio/reference/basic_datagram_socket/max_listen_connections.html +/doc/html/boost_asio/reference/basic_datagram_socket/message_do_not_route.html +/doc/html/boost_asio/reference/basic_datagram_socket/message_end_of_record.html +/doc/html/boost_asio/reference/basic_datagram_socket/message_flags.html +/doc/html/boost_asio/reference/basic_datagram_socket/message_out_of_band.html +/doc/html/boost_asio/reference/basic_datagram_socket/message_peek.html +/doc/html/boost_asio/reference/basic_datagram_socket/native_handle.html +/doc/html/boost_asio/reference/basic_datagram_socket/native_handle_type.html +/doc/html/boost_asio/reference/basic_datagram_socket/native_non_blocking/ +/doc/html/boost_asio/reference/basic_datagram_socket/native_non_blocking.html +/doc/html/boost_asio/reference/basic_datagram_socket/native_non_blocking/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/native_non_blocking/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/native_non_blocking/overload3.html +/doc/html/boost_asio/reference/basic_datagram_socket/non_blocking/ +/doc/html/boost_asio/reference/basic_datagram_socket/non_blocking.html +/doc/html/boost_asio/reference/basic_datagram_socket/non_blocking/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/non_blocking/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/non_blocking/overload3.html +/doc/html/boost_asio/reference/basic_datagram_socket/open/ +/doc/html/boost_asio/reference/basic_datagram_socket/open.html +/doc/html/boost_asio/reference/basic_datagram_socket/open/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/open/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/operator_eq_/ +/doc/html/boost_asio/reference/basic_datagram_socket/operator_eq_.html +/doc/html/boost_asio/reference/basic_datagram_socket/operator_eq_/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/operator_eq_/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/out_of_band_inline.html +/doc/html/boost_asio/reference/basic_datagram_socket/protocol_type.html +/doc/html/boost_asio/reference/basic_datagram_socket__rebind_executor/ +/doc/html/boost_asio/reference/basic_datagram_socket__rebind_executor.html +/doc/html/boost_asio/reference/basic_datagram_socket__rebind_executor/other.html +/doc/html/boost_asio/reference/basic_datagram_socket/receive/ +/doc/html/boost_asio/reference/basic_datagram_socket/receive_buffer_size.html +/doc/html/boost_asio/reference/basic_datagram_socket/receive_from/ +/doc/html/boost_asio/reference/basic_datagram_socket/receive_from.html +/doc/html/boost_asio/reference/basic_datagram_socket/receive_from/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/receive_from/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/receive_from/overload3.html +/doc/html/boost_asio/reference/basic_datagram_socket/receive.html +/doc/html/boost_asio/reference/basic_datagram_socket/receive_low_watermark.html +/doc/html/boost_asio/reference/basic_datagram_socket/receive/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/receive/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/receive/overload3.html +/doc/html/boost_asio/reference/basic_datagram_socket/release/ +/doc/html/boost_asio/reference/basic_datagram_socket/release.html +/doc/html/boost_asio/reference/basic_datagram_socket/release/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/release/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/remote_endpoint/ +/doc/html/boost_asio/reference/basic_datagram_socket/remote_endpoint.html +/doc/html/boost_asio/reference/basic_datagram_socket/remote_endpoint/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/remote_endpoint/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/reuse_address.html +/doc/html/boost_asio/reference/basic_datagram_socket/send/ +/doc/html/boost_asio/reference/basic_datagram_socket/send_buffer_size.html +/doc/html/boost_asio/reference/basic_datagram_socket/send.html +/doc/html/boost_asio/reference/basic_datagram_socket/send_low_watermark.html +/doc/html/boost_asio/reference/basic_datagram_socket/send/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/send/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/send/overload3.html +/doc/html/boost_asio/reference/basic_datagram_socket/send_to/ +/doc/html/boost_asio/reference/basic_datagram_socket/send_to.html +/doc/html/boost_asio/reference/basic_datagram_socket/send_to/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/send_to/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/send_to/overload3.html +/doc/html/boost_asio/reference/basic_datagram_socket/set_option/ +/doc/html/boost_asio/reference/basic_datagram_socket/set_option.html +/doc/html/boost_asio/reference/basic_datagram_socket/set_option/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/set_option/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/shutdown/ +/doc/html/boost_asio/reference/basic_datagram_socket/shutdown.html +/doc/html/boost_asio/reference/basic_datagram_socket/shutdown/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/shutdown/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/shutdown_type.html +/doc/html/boost_asio/reference/basic_datagram_socket/wait/ +/doc/html/boost_asio/reference/basic_datagram_socket/wait.html +/doc/html/boost_asio/reference/basic_datagram_socket/wait/overload1.html +/doc/html/boost_asio/reference/basic_datagram_socket/wait/overload2.html +/doc/html/boost_asio/reference/basic_datagram_socket/wait_type.html +/doc/html/boost_asio/reference/basic_deadline_timer/ +/doc/html/boost_asio/reference/basic_deadline_timer/async_wait.html +/doc/html/boost_asio/reference/basic_deadline_timer/basic_deadline_timer/ +/doc/html/boost_asio/reference/basic_deadline_timer/_basic_deadline_timer.html +/doc/html/boost_asio/reference/basic_deadline_timer/basic_deadline_timer.html +/doc/html/boost_asio/reference/basic_deadline_timer/basic_deadline_timer/overload1.html +/doc/html/boost_asio/reference/basic_deadline_timer/basic_deadline_timer/overload2.html +/doc/html/boost_asio/reference/basic_deadline_timer/basic_deadline_timer/overload3.html +/doc/html/boost_asio/reference/basic_deadline_timer/basic_deadline_timer/overload4.html +/doc/html/boost_asio/reference/basic_deadline_timer/basic_deadline_timer/overload5.html +/doc/html/boost_asio/reference/basic_deadline_timer/basic_deadline_timer/overload6.html +/doc/html/boost_asio/reference/basic_deadline_timer/basic_deadline_timer/overload7.html +/doc/html/boost_asio/reference/basic_deadline_timer/cancel/ +/doc/html/boost_asio/reference/basic_deadline_timer/cancel.html +/doc/html/boost_asio/reference/basic_deadline_timer/cancel_one/ +/doc/html/boost_asio/reference/basic_deadline_timer/cancel_one.html +/doc/html/boost_asio/reference/basic_deadline_timer/cancel_one/overload1.html +/doc/html/boost_asio/reference/basic_deadline_timer/cancel_one/overload2.html +/doc/html/boost_asio/reference/basic_deadline_timer/cancel/overload1.html +/doc/html/boost_asio/reference/basic_deadline_timer/cancel/overload2.html +/doc/html/boost_asio/reference/basic_deadline_timer/duration_type.html +/doc/html/boost_asio/reference/basic_deadline_timer/executor_type.html +/doc/html/boost_asio/reference/basic_deadline_timer/expires_at/ +/doc/html/boost_asio/reference/basic_deadline_timer/expires_at.html +/doc/html/boost_asio/reference/basic_deadline_timer/expires_at/overload1.html +/doc/html/boost_asio/reference/basic_deadline_timer/expires_at/overload2.html +/doc/html/boost_asio/reference/basic_deadline_timer/expires_at/overload3.html +/doc/html/boost_asio/reference/basic_deadline_timer/expires_from_now/ +/doc/html/boost_asio/reference/basic_deadline_timer/expires_from_now.html +/doc/html/boost_asio/reference/basic_deadline_timer/expires_from_now/overload1.html +/doc/html/boost_asio/reference/basic_deadline_timer/expires_from_now/overload2.html +/doc/html/boost_asio/reference/basic_deadline_timer/expires_from_now/overload3.html +/doc/html/boost_asio/reference/basic_deadline_timer/get_executor.html +/doc/html/boost_asio/reference/basic_deadline_timer.html +/doc/html/boost_asio/reference/basic_deadline_timer/operator_eq_.html +/doc/html/boost_asio/reference/basic_deadline_timer__rebind_executor/ +/doc/html/boost_asio/reference/basic_deadline_timer__rebind_executor.html +/doc/html/boost_asio/reference/basic_deadline_timer__rebind_executor/other.html +/doc/html/boost_asio/reference/basic_deadline_timer/time_type.html +/doc/html/boost_asio/reference/basic_deadline_timer/traits_type.html +/doc/html/boost_asio/reference/basic_deadline_timer/wait/ +/doc/html/boost_asio/reference/basic_deadline_timer/wait.html +/doc/html/boost_asio/reference/basic_deadline_timer/wait/overload1.html +/doc/html/boost_asio/reference/basic_deadline_timer/wait/overload2.html +/doc/html/boost_asio/reference/basic_io_object/ +/doc/html/boost_asio/reference/basic_io_object/basic_io_object/ +/doc/html/boost_asio/reference/basic_io_object/_basic_io_object.html +/doc/html/boost_asio/reference/basic_io_object/basic_io_object.html +/doc/html/boost_asio/reference/basic_io_object/basic_io_object/overload1.html +/doc/html/boost_asio/reference/basic_io_object/basic_io_object/overload2.html +/doc/html/boost_asio/reference/basic_io_object/basic_io_object/overload3.html +/doc/html/boost_asio/reference/basic_io_object/executor_type.html +/doc/html/boost_asio/reference/basic_io_object/get_executor.html +/doc/html/boost_asio/reference/basic_io_object/get_implementation/ +/doc/html/boost_asio/reference/basic_io_object/get_implementation.html +/doc/html/boost_asio/reference/basic_io_object/get_implementation/overload1.html +/doc/html/boost_asio/reference/basic_io_object/get_implementation/overload2.html +/doc/html/boost_asio/reference/basic_io_object/get_io_context.html +/doc/html/boost_asio/reference/basic_io_object/get_io_service.html +/doc/html/boost_asio/reference/basic_io_object/get_service/ +/doc/html/boost_asio/reference/basic_io_object/get_service.html +/doc/html/boost_asio/reference/basic_io_object/get_service/overload1.html +/doc/html/boost_asio/reference/basic_io_object/get_service/overload2.html +/doc/html/boost_asio/reference/basic_io_object.html +/doc/html/boost_asio/reference/basic_io_object/implementation_type.html +/doc/html/boost_asio/reference/basic_io_object/operator_eq_.html +/doc/html/boost_asio/reference/basic_io_object/service_type.html +/doc/html/boost_asio/reference/basic_raw_socket/ +/doc/html/boost_asio/reference/basic_raw_socket/assign/ +/doc/html/boost_asio/reference/basic_raw_socket/assign.html +/doc/html/boost_asio/reference/basic_raw_socket/assign/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/assign/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/async_connect.html +/doc/html/boost_asio/reference/basic_raw_socket/async_receive/ +/doc/html/boost_asio/reference/basic_raw_socket/async_receive_from/ +/doc/html/boost_asio/reference/basic_raw_socket/async_receive_from.html +/doc/html/boost_asio/reference/basic_raw_socket/async_receive_from/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/async_receive_from/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/async_receive.html +/doc/html/boost_asio/reference/basic_raw_socket/async_receive/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/async_receive/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/async_send/ +/doc/html/boost_asio/reference/basic_raw_socket/async_send.html +/doc/html/boost_asio/reference/basic_raw_socket/async_send/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/async_send/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/async_send_to/ +/doc/html/boost_asio/reference/basic_raw_socket/async_send_to.html +/doc/html/boost_asio/reference/basic_raw_socket/async_send_to/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/async_send_to/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/async_wait.html +/doc/html/boost_asio/reference/basic_raw_socket/at_mark/ +/doc/html/boost_asio/reference/basic_raw_socket/at_mark.html +/doc/html/boost_asio/reference/basic_raw_socket/at_mark/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/at_mark/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/available/ +/doc/html/boost_asio/reference/basic_raw_socket/available.html +/doc/html/boost_asio/reference/basic_raw_socket/available/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/available/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/basic_raw_socket/ +/doc/html/boost_asio/reference/basic_raw_socket/_basic_raw_socket.html +/doc/html/boost_asio/reference/basic_raw_socket/basic_raw_socket.html +/doc/html/boost_asio/reference/basic_raw_socket/basic_raw_socket/overload10.html +/doc/html/boost_asio/reference/basic_raw_socket/basic_raw_socket/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/basic_raw_socket/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/basic_raw_socket/overload3.html +/doc/html/boost_asio/reference/basic_raw_socket/basic_raw_socket/overload4.html +/doc/html/boost_asio/reference/basic_raw_socket/basic_raw_socket/overload5.html +/doc/html/boost_asio/reference/basic_raw_socket/basic_raw_socket/overload6.html +/doc/html/boost_asio/reference/basic_raw_socket/basic_raw_socket/overload7.html +/doc/html/boost_asio/reference/basic_raw_socket/basic_raw_socket/overload8.html +/doc/html/boost_asio/reference/basic_raw_socket/basic_raw_socket/overload9.html +/doc/html/boost_asio/reference/basic_raw_socket/bind/ +/doc/html/boost_asio/reference/basic_raw_socket/bind.html +/doc/html/boost_asio/reference/basic_raw_socket/bind/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/bind/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/broadcast.html +/doc/html/boost_asio/reference/basic_raw_socket/bytes_readable.html +/doc/html/boost_asio/reference/basic_raw_socket/cancel/ +/doc/html/boost_asio/reference/basic_raw_socket/cancel.html +/doc/html/boost_asio/reference/basic_raw_socket/cancel/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/cancel/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/close/ +/doc/html/boost_asio/reference/basic_raw_socket/close.html +/doc/html/boost_asio/reference/basic_raw_socket/close/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/close/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/connect/ +/doc/html/boost_asio/reference/basic_raw_socket/connect.html +/doc/html/boost_asio/reference/basic_raw_socket/connect/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/connect/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/debug.html +/doc/html/boost_asio/reference/basic_raw_socket/do_not_route.html +/doc/html/boost_asio/reference/basic_raw_socket/enable_connection_aborted.html +/doc/html/boost_asio/reference/basic_raw_socket/endpoint_type.html +/doc/html/boost_asio/reference/basic_raw_socket/executor_type.html +/doc/html/boost_asio/reference/basic_raw_socket/get_executor.html +/doc/html/boost_asio/reference/basic_raw_socket/get_option/ +/doc/html/boost_asio/reference/basic_raw_socket/get_option.html +/doc/html/boost_asio/reference/basic_raw_socket/get_option/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/get_option/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket.html +/doc/html/boost_asio/reference/basic_raw_socket/impl_.html +/doc/html/boost_asio/reference/basic_raw_socket/io_control/ +/doc/html/boost_asio/reference/basic_raw_socket/io_control.html +/doc/html/boost_asio/reference/basic_raw_socket/io_control/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/io_control/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/is_open.html +/doc/html/boost_asio/reference/basic_raw_socket/keep_alive.html +/doc/html/boost_asio/reference/basic_raw_socket/linger.html +/doc/html/boost_asio/reference/basic_raw_socket/local_endpoint/ +/doc/html/boost_asio/reference/basic_raw_socket/local_endpoint.html +/doc/html/boost_asio/reference/basic_raw_socket/local_endpoint/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/local_endpoint/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/lowest_layer/ +/doc/html/boost_asio/reference/basic_raw_socket/lowest_layer.html +/doc/html/boost_asio/reference/basic_raw_socket/lowest_layer/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/lowest_layer/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/lowest_layer_type.html +/doc/html/boost_asio/reference/basic_raw_socket/max_connections.html +/doc/html/boost_asio/reference/basic_raw_socket/max_listen_connections.html +/doc/html/boost_asio/reference/basic_raw_socket/message_do_not_route.html +/doc/html/boost_asio/reference/basic_raw_socket/message_end_of_record.html +/doc/html/boost_asio/reference/basic_raw_socket/message_flags.html +/doc/html/boost_asio/reference/basic_raw_socket/message_out_of_band.html +/doc/html/boost_asio/reference/basic_raw_socket/message_peek.html +/doc/html/boost_asio/reference/basic_raw_socket/native_handle.html +/doc/html/boost_asio/reference/basic_raw_socket/native_handle_type.html +/doc/html/boost_asio/reference/basic_raw_socket/native_non_blocking/ +/doc/html/boost_asio/reference/basic_raw_socket/native_non_blocking.html +/doc/html/boost_asio/reference/basic_raw_socket/native_non_blocking/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/native_non_blocking/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/native_non_blocking/overload3.html +/doc/html/boost_asio/reference/basic_raw_socket/non_blocking/ +/doc/html/boost_asio/reference/basic_raw_socket/non_blocking.html +/doc/html/boost_asio/reference/basic_raw_socket/non_blocking/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/non_blocking/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/non_blocking/overload3.html +/doc/html/boost_asio/reference/basic_raw_socket/open/ +/doc/html/boost_asio/reference/basic_raw_socket/open.html +/doc/html/boost_asio/reference/basic_raw_socket/open/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/open/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/operator_eq_/ +/doc/html/boost_asio/reference/basic_raw_socket/operator_eq_.html +/doc/html/boost_asio/reference/basic_raw_socket/operator_eq_/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/operator_eq_/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/out_of_band_inline.html +/doc/html/boost_asio/reference/basic_raw_socket/protocol_type.html +/doc/html/boost_asio/reference/basic_raw_socket__rebind_executor/ +/doc/html/boost_asio/reference/basic_raw_socket__rebind_executor.html +/doc/html/boost_asio/reference/basic_raw_socket__rebind_executor/other.html +/doc/html/boost_asio/reference/basic_raw_socket/receive/ +/doc/html/boost_asio/reference/basic_raw_socket/receive_buffer_size.html +/doc/html/boost_asio/reference/basic_raw_socket/receive_from/ +/doc/html/boost_asio/reference/basic_raw_socket/receive_from.html +/doc/html/boost_asio/reference/basic_raw_socket/receive_from/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/receive_from/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/receive_from/overload3.html +/doc/html/boost_asio/reference/basic_raw_socket/receive.html +/doc/html/boost_asio/reference/basic_raw_socket/receive_low_watermark.html +/doc/html/boost_asio/reference/basic_raw_socket/receive/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/receive/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/receive/overload3.html +/doc/html/boost_asio/reference/basic_raw_socket/release/ +/doc/html/boost_asio/reference/basic_raw_socket/release.html +/doc/html/boost_asio/reference/basic_raw_socket/release/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/release/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/remote_endpoint/ +/doc/html/boost_asio/reference/basic_raw_socket/remote_endpoint.html +/doc/html/boost_asio/reference/basic_raw_socket/remote_endpoint/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/remote_endpoint/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/reuse_address.html +/doc/html/boost_asio/reference/basic_raw_socket/send/ +/doc/html/boost_asio/reference/basic_raw_socket/send_buffer_size.html +/doc/html/boost_asio/reference/basic_raw_socket/send.html +/doc/html/boost_asio/reference/basic_raw_socket/send_low_watermark.html +/doc/html/boost_asio/reference/basic_raw_socket/send/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/send/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/send/overload3.html +/doc/html/boost_asio/reference/basic_raw_socket/send_to/ +/doc/html/boost_asio/reference/basic_raw_socket/send_to.html +/doc/html/boost_asio/reference/basic_raw_socket/send_to/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/send_to/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/send_to/overload3.html +/doc/html/boost_asio/reference/basic_raw_socket/set_option/ +/doc/html/boost_asio/reference/basic_raw_socket/set_option.html +/doc/html/boost_asio/reference/basic_raw_socket/set_option/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/set_option/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/shutdown/ +/doc/html/boost_asio/reference/basic_raw_socket/shutdown.html +/doc/html/boost_asio/reference/basic_raw_socket/shutdown/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/shutdown/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/shutdown_type.html +/doc/html/boost_asio/reference/basic_raw_socket/wait/ +/doc/html/boost_asio/reference/basic_raw_socket/wait.html +/doc/html/boost_asio/reference/basic_raw_socket/wait/overload1.html +/doc/html/boost_asio/reference/basic_raw_socket/wait/overload2.html +/doc/html/boost_asio/reference/basic_raw_socket/wait_type.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/assign/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/assign.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/assign/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/assign/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/async_connect.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/async_receive/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/async_receive.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/async_receive/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/async_receive/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/async_send.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/async_wait.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/at_mark/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/at_mark.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/at_mark/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/at_mark/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/available/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/available.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/available/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/available/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/_basic_seq_packet_socket.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/basic_seq_packet_socket.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload10.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload3.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload4.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload5.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload6.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload7.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload8.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/basic_seq_packet_socket/overload9.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/bind/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/bind.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/bind/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/bind/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/broadcast.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/bytes_readable.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/cancel/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/cancel.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/cancel/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/cancel/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/close/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/close.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/close/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/close/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/connect/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/connect.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/connect/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/connect/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/debug.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/do_not_route.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/enable_connection_aborted.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/endpoint_type.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/executor_type.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/get_executor.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/get_option/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/get_option.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/get_option/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/get_option/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/impl_.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/io_control/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/io_control.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/io_control/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/io_control/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/is_open.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/keep_alive.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/linger.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/local_endpoint/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/local_endpoint.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/local_endpoint/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/local_endpoint/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/lowest_layer/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/lowest_layer.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/lowest_layer/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/lowest_layer/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/lowest_layer_type.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/max_connections.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/max_listen_connections.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/message_do_not_route.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/message_end_of_record.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/message_flags.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/message_out_of_band.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/message_peek.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/native_handle.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/native_handle_type.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/native_non_blocking/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/native_non_blocking.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/native_non_blocking/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/native_non_blocking/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/native_non_blocking/overload3.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/non_blocking/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/non_blocking.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/non_blocking/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/non_blocking/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/non_blocking/overload3.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/open/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/open.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/open/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/open/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/operator_eq_/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/operator_eq_.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/operator_eq_/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/operator_eq_/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/out_of_band_inline.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/protocol_type.html +/doc/html/boost_asio/reference/basic_seq_packet_socket__rebind_executor/ +/doc/html/boost_asio/reference/basic_seq_packet_socket__rebind_executor.html +/doc/html/boost_asio/reference/basic_seq_packet_socket__rebind_executor/other.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/receive/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/receive_buffer_size.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/receive.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/receive_low_watermark.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/receive/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/receive/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/receive/overload3.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/release/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/release.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/release/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/release/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/remote_endpoint/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/remote_endpoint.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/remote_endpoint/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/remote_endpoint/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/reuse_address.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/send/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/send_buffer_size.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/send.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/send_low_watermark.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/send/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/send/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/set_option/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/set_option.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/set_option/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/set_option/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/shutdown/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/shutdown.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/shutdown/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/shutdown/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/shutdown_type.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/wait/ +/doc/html/boost_asio/reference/basic_seq_packet_socket/wait.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/wait/overload1.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/wait/overload2.html +/doc/html/boost_asio/reference/basic_seq_packet_socket/wait_type.html +/doc/html/boost_asio/reference/basic_serial_port/ +/doc/html/boost_asio/reference/basic_serial_port/assign/ +/doc/html/boost_asio/reference/basic_serial_port/assign.html +/doc/html/boost_asio/reference/basic_serial_port/assign/overload1.html +/doc/html/boost_asio/reference/basic_serial_port/assign/overload2.html +/doc/html/boost_asio/reference/basic_serial_port/async_read_some.html +/doc/html/boost_asio/reference/basic_serial_port/async_write_some.html +/doc/html/boost_asio/reference/basic_serial_port/basic_serial_port/ +/doc/html/boost_asio/reference/basic_serial_port/_basic_serial_port.html +/doc/html/boost_asio/reference/basic_serial_port/basic_serial_port.html +/doc/html/boost_asio/reference/basic_serial_port/basic_serial_port/overload1.html +/doc/html/boost_asio/reference/basic_serial_port/basic_serial_port/overload2.html +/doc/html/boost_asio/reference/basic_serial_port/basic_serial_port/overload3.html +/doc/html/boost_asio/reference/basic_serial_port/basic_serial_port/overload4.html +/doc/html/boost_asio/reference/basic_serial_port/basic_serial_port/overload5.html +/doc/html/boost_asio/reference/basic_serial_port/basic_serial_port/overload6.html +/doc/html/boost_asio/reference/basic_serial_port/basic_serial_port/overload7.html +/doc/html/boost_asio/reference/basic_serial_port/basic_serial_port/overload8.html +/doc/html/boost_asio/reference/basic_serial_port/basic_serial_port/overload9.html +/doc/html/boost_asio/reference/basic_serial_port/cancel/ +/doc/html/boost_asio/reference/basic_serial_port/cancel.html +/doc/html/boost_asio/reference/basic_serial_port/cancel/overload1.html +/doc/html/boost_asio/reference/basic_serial_port/cancel/overload2.html +/doc/html/boost_asio/reference/basic_serial_port/close/ +/doc/html/boost_asio/reference/basic_serial_port/close.html +/doc/html/boost_asio/reference/basic_serial_port/close/overload1.html +/doc/html/boost_asio/reference/basic_serial_port/close/overload2.html +/doc/html/boost_asio/reference/basic_serial_port/executor_type.html +/doc/html/boost_asio/reference/basic_serial_port/get_executor.html +/doc/html/boost_asio/reference/basic_serial_port/get_option/ +/doc/html/boost_asio/reference/basic_serial_port/get_option.html +/doc/html/boost_asio/reference/basic_serial_port/get_option/overload1.html +/doc/html/boost_asio/reference/basic_serial_port/get_option/overload2.html +/doc/html/boost_asio/reference/basic_serial_port.html +/doc/html/boost_asio/reference/basic_serial_port/is_open.html +/doc/html/boost_asio/reference/basic_serial_port/lowest_layer/ +/doc/html/boost_asio/reference/basic_serial_port/lowest_layer.html +/doc/html/boost_asio/reference/basic_serial_port/lowest_layer/overload1.html +/doc/html/boost_asio/reference/basic_serial_port/lowest_layer/overload2.html +/doc/html/boost_asio/reference/basic_serial_port/lowest_layer_type.html +/doc/html/boost_asio/reference/basic_serial_port/native_handle.html +/doc/html/boost_asio/reference/basic_serial_port/native_handle_type.html +/doc/html/boost_asio/reference/basic_serial_port/open/ +/doc/html/boost_asio/reference/basic_serial_port/open.html +/doc/html/boost_asio/reference/basic_serial_port/open/overload1.html +/doc/html/boost_asio/reference/basic_serial_port/open/overload2.html +/doc/html/boost_asio/reference/basic_serial_port/operator_eq_.html +/doc/html/boost_asio/reference/basic_serial_port/read_some/ +/doc/html/boost_asio/reference/basic_serial_port/read_some.html +/doc/html/boost_asio/reference/basic_serial_port/read_some/overload1.html +/doc/html/boost_asio/reference/basic_serial_port/read_some/overload2.html +/doc/html/boost_asio/reference/basic_serial_port__rebind_executor/ +/doc/html/boost_asio/reference/basic_serial_port__rebind_executor.html +/doc/html/boost_asio/reference/basic_serial_port__rebind_executor/other.html +/doc/html/boost_asio/reference/basic_serial_port/send_break/ +/doc/html/boost_asio/reference/basic_serial_port/send_break.html +/doc/html/boost_asio/reference/basic_serial_port/send_break/overload1.html +/doc/html/boost_asio/reference/basic_serial_port/send_break/overload2.html +/doc/html/boost_asio/reference/basic_serial_port/set_option/ +/doc/html/boost_asio/reference/basic_serial_port/set_option.html +/doc/html/boost_asio/reference/basic_serial_port/set_option/overload1.html +/doc/html/boost_asio/reference/basic_serial_port/set_option/overload2.html +/doc/html/boost_asio/reference/basic_serial_port/write_some/ +/doc/html/boost_asio/reference/basic_serial_port/write_some.html +/doc/html/boost_asio/reference/basic_serial_port/write_some/overload1.html +/doc/html/boost_asio/reference/basic_serial_port/write_some/overload2.html +/doc/html/boost_asio/reference/basic_signal_set/ +/doc/html/boost_asio/reference/basic_signal_set/add/ +/doc/html/boost_asio/reference/basic_signal_set/add.html +/doc/html/boost_asio/reference/basic_signal_set/add/overload1.html +/doc/html/boost_asio/reference/basic_signal_set/add/overload2.html +/doc/html/boost_asio/reference/basic_signal_set/async_wait.html +/doc/html/boost_asio/reference/basic_signal_set/basic_signal_set/ +/doc/html/boost_asio/reference/basic_signal_set/_basic_signal_set.html +/doc/html/boost_asio/reference/basic_signal_set/basic_signal_set.html +/doc/html/boost_asio/reference/basic_signal_set/basic_signal_set/overload1.html +/doc/html/boost_asio/reference/basic_signal_set/basic_signal_set/overload2.html +/doc/html/boost_asio/reference/basic_signal_set/basic_signal_set/overload3.html +/doc/html/boost_asio/reference/basic_signal_set/basic_signal_set/overload4.html +/doc/html/boost_asio/reference/basic_signal_set/basic_signal_set/overload5.html +/doc/html/boost_asio/reference/basic_signal_set/basic_signal_set/overload6.html +/doc/html/boost_asio/reference/basic_signal_set/basic_signal_set/overload7.html +/doc/html/boost_asio/reference/basic_signal_set/basic_signal_set/overload8.html +/doc/html/boost_asio/reference/basic_signal_set/cancel/ +/doc/html/boost_asio/reference/basic_signal_set/cancel.html +/doc/html/boost_asio/reference/basic_signal_set/cancel/overload1.html +/doc/html/boost_asio/reference/basic_signal_set/cancel/overload2.html +/doc/html/boost_asio/reference/basic_signal_set/clear/ +/doc/html/boost_asio/reference/basic_signal_set/clear.html +/doc/html/boost_asio/reference/basic_signal_set/clear/overload1.html +/doc/html/boost_asio/reference/basic_signal_set/clear/overload2.html +/doc/html/boost_asio/reference/basic_signal_set/executor_type.html +/doc/html/boost_asio/reference/basic_signal_set/get_executor.html +/doc/html/boost_asio/reference/basic_signal_set.html +/doc/html/boost_asio/reference/basic_signal_set__rebind_executor/ +/doc/html/boost_asio/reference/basic_signal_set__rebind_executor.html +/doc/html/boost_asio/reference/basic_signal_set__rebind_executor/other.html +/doc/html/boost_asio/reference/basic_signal_set/remove/ +/doc/html/boost_asio/reference/basic_signal_set/remove.html +/doc/html/boost_asio/reference/basic_signal_set/remove/overload1.html +/doc/html/boost_asio/reference/basic_signal_set/remove/overload2.html +/doc/html/boost_asio/reference/basic_socket/ +/doc/html/boost_asio/reference/basic_socket_acceptor/ +/doc/html/boost_asio/reference/basic_socket_acceptor/accept/ +/doc/html/boost_asio/reference/basic_socket_acceptor/accept.html +/doc/html/boost_asio/reference/basic_socket_acceptor/accept/overload10.html +/doc/html/boost_asio/reference/basic_socket_acceptor/accept/overload11.html +/doc/html/boost_asio/reference/basic_socket_acceptor/accept/overload12.html +/doc/html/boost_asio/reference/basic_socket_acceptor/accept/overload13.html +/doc/html/boost_asio/reference/basic_socket_acceptor/accept/overload14.html +/doc/html/boost_asio/reference/basic_socket_acceptor/accept/overload15.html +/doc/html/boost_asio/reference/basic_socket_acceptor/accept/overload16.html +/doc/html/boost_asio/reference/basic_socket_acceptor/accept/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/accept/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor/accept/overload3.html +/doc/html/boost_asio/reference/basic_socket_acceptor/accept/overload4.html +/doc/html/boost_asio/reference/basic_socket_acceptor/accept/overload5.html +/doc/html/boost_asio/reference/basic_socket_acceptor/accept/overload6.html +/doc/html/boost_asio/reference/basic_socket_acceptor/accept/overload7.html +/doc/html/boost_asio/reference/basic_socket_acceptor/accept/overload8.html +/doc/html/boost_asio/reference/basic_socket_acceptor/accept/overload9.html +/doc/html/boost_asio/reference/basic_socket_acceptor/assign/ +/doc/html/boost_asio/reference/basic_socket_acceptor/assign.html +/doc/html/boost_asio/reference/basic_socket_acceptor/assign/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/assign/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor/async_accept/ +/doc/html/boost_asio/reference/basic_socket_acceptor/async_accept.html +/doc/html/boost_asio/reference/basic_socket_acceptor/async_accept/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/async_accept/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor/async_accept/overload3.html +/doc/html/boost_asio/reference/basic_socket_acceptor/async_accept/overload4.html +/doc/html/boost_asio/reference/basic_socket_acceptor/async_accept/overload5.html +/doc/html/boost_asio/reference/basic_socket_acceptor/async_accept/overload6.html +/doc/html/boost_asio/reference/basic_socket_acceptor/async_accept/overload7.html +/doc/html/boost_asio/reference/basic_socket_acceptor/async_accept/overload8.html +/doc/html/boost_asio/reference/basic_socket_acceptor/async_wait.html +/doc/html/boost_asio/reference/basic_socket_acceptor/basic_socket_acceptor/ +/doc/html/boost_asio/reference/basic_socket_acceptor/_basic_socket_acceptor.html +/doc/html/boost_asio/reference/basic_socket_acceptor/basic_socket_acceptor.html +/doc/html/boost_asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload10.html +/doc/html/boost_asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload3.html +/doc/html/boost_asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload4.html +/doc/html/boost_asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload5.html +/doc/html/boost_asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload6.html +/doc/html/boost_asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload7.html +/doc/html/boost_asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload8.html +/doc/html/boost_asio/reference/basic_socket_acceptor/basic_socket_acceptor/overload9.html +/doc/html/boost_asio/reference/basic_socket_acceptor/bind/ +/doc/html/boost_asio/reference/basic_socket_acceptor/bind.html +/doc/html/boost_asio/reference/basic_socket_acceptor/bind/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/bind/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor/broadcast.html +/doc/html/boost_asio/reference/basic_socket_acceptor/bytes_readable.html +/doc/html/boost_asio/reference/basic_socket_acceptor/cancel/ +/doc/html/boost_asio/reference/basic_socket_acceptor/cancel.html +/doc/html/boost_asio/reference/basic_socket_acceptor/cancel/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/cancel/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor/close/ +/doc/html/boost_asio/reference/basic_socket_acceptor/close.html +/doc/html/boost_asio/reference/basic_socket_acceptor/close/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/close/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor/debug.html +/doc/html/boost_asio/reference/basic_socket_acceptor/do_not_route.html +/doc/html/boost_asio/reference/basic_socket_acceptor/enable_connection_aborted.html +/doc/html/boost_asio/reference/basic_socket_acceptor/endpoint_type.html +/doc/html/boost_asio/reference/basic_socket_acceptor/executor_type.html +/doc/html/boost_asio/reference/basic_socket_acceptor/get_executor.html +/doc/html/boost_asio/reference/basic_socket_acceptor/get_option/ +/doc/html/boost_asio/reference/basic_socket_acceptor/get_option.html +/doc/html/boost_asio/reference/basic_socket_acceptor/get_option/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/get_option/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor.html +/doc/html/boost_asio/reference/basic_socket_acceptor/io_control/ +/doc/html/boost_asio/reference/basic_socket_acceptor/io_control.html +/doc/html/boost_asio/reference/basic_socket_acceptor/io_control/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/io_control/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor/is_open.html +/doc/html/boost_asio/reference/basic_socket_acceptor/keep_alive.html +/doc/html/boost_asio/reference/basic_socket_acceptor/linger.html +/doc/html/boost_asio/reference/basic_socket_acceptor/listen/ +/doc/html/boost_asio/reference/basic_socket_acceptor/listen.html +/doc/html/boost_asio/reference/basic_socket_acceptor/listen/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/listen/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor/local_endpoint/ +/doc/html/boost_asio/reference/basic_socket_acceptor/local_endpoint.html +/doc/html/boost_asio/reference/basic_socket_acceptor/local_endpoint/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/local_endpoint/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor/max_connections.html +/doc/html/boost_asio/reference/basic_socket_acceptor/max_listen_connections.html +/doc/html/boost_asio/reference/basic_socket_acceptor/message_do_not_route.html +/doc/html/boost_asio/reference/basic_socket_acceptor/message_end_of_record.html +/doc/html/boost_asio/reference/basic_socket_acceptor/message_flags.html +/doc/html/boost_asio/reference/basic_socket_acceptor/message_out_of_band.html +/doc/html/boost_asio/reference/basic_socket_acceptor/message_peek.html +/doc/html/boost_asio/reference/basic_socket_acceptor/native_handle.html +/doc/html/boost_asio/reference/basic_socket_acceptor/native_handle_type.html +/doc/html/boost_asio/reference/basic_socket_acceptor/native_non_blocking/ +/doc/html/boost_asio/reference/basic_socket_acceptor/native_non_blocking.html +/doc/html/boost_asio/reference/basic_socket_acceptor/native_non_blocking/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/native_non_blocking/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor/native_non_blocking/overload3.html +/doc/html/boost_asio/reference/basic_socket_acceptor/non_blocking/ +/doc/html/boost_asio/reference/basic_socket_acceptor/non_blocking.html +/doc/html/boost_asio/reference/basic_socket_acceptor/non_blocking/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/non_blocking/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor/non_blocking/overload3.html +/doc/html/boost_asio/reference/basic_socket_acceptor/open/ +/doc/html/boost_asio/reference/basic_socket_acceptor/open.html +/doc/html/boost_asio/reference/basic_socket_acceptor/open/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/open/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor/operator_eq_/ +/doc/html/boost_asio/reference/basic_socket_acceptor/operator_eq_.html +/doc/html/boost_asio/reference/basic_socket_acceptor/operator_eq_/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/operator_eq_/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor/out_of_band_inline.html +/doc/html/boost_asio/reference/basic_socket_acceptor/protocol_type.html +/doc/html/boost_asio/reference/basic_socket_acceptor__rebind_executor/ +/doc/html/boost_asio/reference/basic_socket_acceptor__rebind_executor.html +/doc/html/boost_asio/reference/basic_socket_acceptor__rebind_executor/other.html +/doc/html/boost_asio/reference/basic_socket_acceptor/receive_buffer_size.html +/doc/html/boost_asio/reference/basic_socket_acceptor/receive_low_watermark.html +/doc/html/boost_asio/reference/basic_socket_acceptor/release/ +/doc/html/boost_asio/reference/basic_socket_acceptor/release.html +/doc/html/boost_asio/reference/basic_socket_acceptor/release/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/release/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor/reuse_address.html +/doc/html/boost_asio/reference/basic_socket_acceptor/send_buffer_size.html +/doc/html/boost_asio/reference/basic_socket_acceptor/send_low_watermark.html +/doc/html/boost_asio/reference/basic_socket_acceptor/set_option/ +/doc/html/boost_asio/reference/basic_socket_acceptor/set_option.html +/doc/html/boost_asio/reference/basic_socket_acceptor/set_option/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/set_option/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor/shutdown_type.html +/doc/html/boost_asio/reference/basic_socket_acceptor/wait/ +/doc/html/boost_asio/reference/basic_socket_acceptor/wait.html +/doc/html/boost_asio/reference/basic_socket_acceptor/wait/overload1.html +/doc/html/boost_asio/reference/basic_socket_acceptor/wait/overload2.html +/doc/html/boost_asio/reference/basic_socket_acceptor/wait_type.html +/doc/html/boost_asio/reference/basic_socket/assign/ +/doc/html/boost_asio/reference/basic_socket/assign.html +/doc/html/boost_asio/reference/basic_socket/assign/overload1.html +/doc/html/boost_asio/reference/basic_socket/assign/overload2.html +/doc/html/boost_asio/reference/basic_socket/async_connect.html +/doc/html/boost_asio/reference/basic_socket/async_wait.html +/doc/html/boost_asio/reference/basic_socket/at_mark/ +/doc/html/boost_asio/reference/basic_socket/at_mark.html +/doc/html/boost_asio/reference/basic_socket/at_mark/overload1.html +/doc/html/boost_asio/reference/basic_socket/at_mark/overload2.html +/doc/html/boost_asio/reference/basic_socket/available/ +/doc/html/boost_asio/reference/basic_socket/available.html +/doc/html/boost_asio/reference/basic_socket/available/overload1.html +/doc/html/boost_asio/reference/basic_socket/available/overload2.html +/doc/html/boost_asio/reference/basic_socket/basic_socket/ +/doc/html/boost_asio/reference/basic_socket/_basic_socket.html +/doc/html/boost_asio/reference/basic_socket/basic_socket.html +/doc/html/boost_asio/reference/basic_socket/basic_socket/overload10.html +/doc/html/boost_asio/reference/basic_socket/basic_socket/overload1.html +/doc/html/boost_asio/reference/basic_socket/basic_socket/overload2.html +/doc/html/boost_asio/reference/basic_socket/basic_socket/overload3.html +/doc/html/boost_asio/reference/basic_socket/basic_socket/overload4.html +/doc/html/boost_asio/reference/basic_socket/basic_socket/overload5.html +/doc/html/boost_asio/reference/basic_socket/basic_socket/overload6.html +/doc/html/boost_asio/reference/basic_socket/basic_socket/overload7.html +/doc/html/boost_asio/reference/basic_socket/basic_socket/overload8.html +/doc/html/boost_asio/reference/basic_socket/basic_socket/overload9.html +/doc/html/boost_asio/reference/basic_socket/bind/ +/doc/html/boost_asio/reference/basic_socket/bind.html +/doc/html/boost_asio/reference/basic_socket/bind/overload1.html +/doc/html/boost_asio/reference/basic_socket/bind/overload2.html +/doc/html/boost_asio/reference/basic_socket/broadcast.html +/doc/html/boost_asio/reference/basic_socket/bytes_readable.html +/doc/html/boost_asio/reference/basic_socket/cancel/ +/doc/html/boost_asio/reference/basic_socket/cancel.html +/doc/html/boost_asio/reference/basic_socket/cancel/overload1.html +/doc/html/boost_asio/reference/basic_socket/cancel/overload2.html +/doc/html/boost_asio/reference/basic_socket/close/ +/doc/html/boost_asio/reference/basic_socket/close.html +/doc/html/boost_asio/reference/basic_socket/close/overload1.html +/doc/html/boost_asio/reference/basic_socket/close/overload2.html +/doc/html/boost_asio/reference/basic_socket/connect/ +/doc/html/boost_asio/reference/basic_socket/connect.html +/doc/html/boost_asio/reference/basic_socket/connect/overload1.html +/doc/html/boost_asio/reference/basic_socket/connect/overload2.html +/doc/html/boost_asio/reference/basic_socket/debug.html +/doc/html/boost_asio/reference/basic_socket/do_not_route.html +/doc/html/boost_asio/reference/basic_socket/enable_connection_aborted.html +/doc/html/boost_asio/reference/basic_socket/endpoint_type.html +/doc/html/boost_asio/reference/basic_socket/executor_type.html +/doc/html/boost_asio/reference/basic_socket/get_executor.html +/doc/html/boost_asio/reference/basic_socket/get_option/ +/doc/html/boost_asio/reference/basic_socket/get_option.html +/doc/html/boost_asio/reference/basic_socket/get_option/overload1.html +/doc/html/boost_asio/reference/basic_socket/get_option/overload2.html +/doc/html/boost_asio/reference/basic_socket.html +/doc/html/boost_asio/reference/basic_socket/impl_.html +/doc/html/boost_asio/reference/basic_socket/io_control/ +/doc/html/boost_asio/reference/basic_socket/io_control.html +/doc/html/boost_asio/reference/basic_socket/io_control/overload1.html +/doc/html/boost_asio/reference/basic_socket/io_control/overload2.html +/doc/html/boost_asio/reference/basic_socket_iostream/ +/doc/html/boost_asio/reference/basic_socket_iostream/basic_socket_iostream/ +/doc/html/boost_asio/reference/basic_socket_iostream/basic_socket_iostream.html +/doc/html/boost_asio/reference/basic_socket_iostream/basic_socket_iostream/overload1.html +/doc/html/boost_asio/reference/basic_socket_iostream/basic_socket_iostream/overload2.html +/doc/html/boost_asio/reference/basic_socket_iostream/basic_socket_iostream/overload3.html +/doc/html/boost_asio/reference/basic_socket_iostream/basic_socket_iostream/overload4.html +/doc/html/boost_asio/reference/basic_socket_iostream/clock_type.html +/doc/html/boost_asio/reference/basic_socket_iostream/close.html +/doc/html/boost_asio/reference/basic_socket_iostream/connect.html +/doc/html/boost_asio/reference/basic_socket_iostream/duration.html +/doc/html/boost_asio/reference/basic_socket_iostream/duration_type.html +/doc/html/boost_asio/reference/basic_socket_iostream/endpoint_type.html +/doc/html/boost_asio/reference/basic_socket_iostream/error.html +/doc/html/boost_asio/reference/basic_socket_iostream/expires_after.html +/doc/html/boost_asio/reference/basic_socket_iostream/expires_at/ +/doc/html/boost_asio/reference/basic_socket_iostream/expires_at.html +/doc/html/boost_asio/reference/basic_socket_iostream/expires_at/overload1.html +/doc/html/boost_asio/reference/basic_socket_iostream/expires_at/overload2.html +/doc/html/boost_asio/reference/basic_socket_iostream/expires_from_now/ +/doc/html/boost_asio/reference/basic_socket_iostream/expires_from_now.html +/doc/html/boost_asio/reference/basic_socket_iostream/expires_from_now/overload1.html +/doc/html/boost_asio/reference/basic_socket_iostream/expires_from_now/overload2.html +/doc/html/boost_asio/reference/basic_socket_iostream/expiry.html +/doc/html/boost_asio/reference/basic_socket_iostream.html +/doc/html/boost_asio/reference/basic_socket_iostream/operator_eq_.html +/doc/html/boost_asio/reference/basic_socket_iostream/protocol_type.html +/doc/html/boost_asio/reference/basic_socket_iostream/rdbuf.html +/doc/html/boost_asio/reference/basic_socket_iostream/socket.html +/doc/html/boost_asio/reference/basic_socket_iostream/time_point.html +/doc/html/boost_asio/reference/basic_socket_iostream/time_type.html +/doc/html/boost_asio/reference/basic_socket/is_open.html +/doc/html/boost_asio/reference/basic_socket/keep_alive.html +/doc/html/boost_asio/reference/basic_socket/linger.html +/doc/html/boost_asio/reference/basic_socket/local_endpoint/ +/doc/html/boost_asio/reference/basic_socket/local_endpoint.html +/doc/html/boost_asio/reference/basic_socket/local_endpoint/overload1.html +/doc/html/boost_asio/reference/basic_socket/local_endpoint/overload2.html +/doc/html/boost_asio/reference/basic_socket/lowest_layer/ +/doc/html/boost_asio/reference/basic_socket/lowest_layer.html +/doc/html/boost_asio/reference/basic_socket/lowest_layer/overload1.html +/doc/html/boost_asio/reference/basic_socket/lowest_layer/overload2.html +/doc/html/boost_asio/reference/basic_socket/lowest_layer_type.html +/doc/html/boost_asio/reference/basic_socket/max_connections.html +/doc/html/boost_asio/reference/basic_socket/max_listen_connections.html +/doc/html/boost_asio/reference/basic_socket/message_do_not_route.html +/doc/html/boost_asio/reference/basic_socket/message_end_of_record.html +/doc/html/boost_asio/reference/basic_socket/message_flags.html +/doc/html/boost_asio/reference/basic_socket/message_out_of_band.html +/doc/html/boost_asio/reference/basic_socket/message_peek.html +/doc/html/boost_asio/reference/basic_socket/native_handle.html +/doc/html/boost_asio/reference/basic_socket/native_handle_type.html +/doc/html/boost_asio/reference/basic_socket/native_non_blocking/ +/doc/html/boost_asio/reference/basic_socket/native_non_blocking.html +/doc/html/boost_asio/reference/basic_socket/native_non_blocking/overload1.html +/doc/html/boost_asio/reference/basic_socket/native_non_blocking/overload2.html +/doc/html/boost_asio/reference/basic_socket/native_non_blocking/overload3.html +/doc/html/boost_asio/reference/basic_socket/non_blocking/ +/doc/html/boost_asio/reference/basic_socket/non_blocking.html +/doc/html/boost_asio/reference/basic_socket/non_blocking/overload1.html +/doc/html/boost_asio/reference/basic_socket/non_blocking/overload2.html +/doc/html/boost_asio/reference/basic_socket/non_blocking/overload3.html +/doc/html/boost_asio/reference/basic_socket/open/ +/doc/html/boost_asio/reference/basic_socket/open.html +/doc/html/boost_asio/reference/basic_socket/open/overload1.html +/doc/html/boost_asio/reference/basic_socket/open/overload2.html +/doc/html/boost_asio/reference/basic_socket/operator_eq_/ +/doc/html/boost_asio/reference/basic_socket/operator_eq_.html +/doc/html/boost_asio/reference/basic_socket/operator_eq_/overload1.html +/doc/html/boost_asio/reference/basic_socket/operator_eq_/overload2.html +/doc/html/boost_asio/reference/basic_socket/out_of_band_inline.html +/doc/html/boost_asio/reference/basic_socket/protocol_type.html +/doc/html/boost_asio/reference/basic_socket__rebind_executor/ +/doc/html/boost_asio/reference/basic_socket__rebind_executor.html +/doc/html/boost_asio/reference/basic_socket__rebind_executor/other.html +/doc/html/boost_asio/reference/basic_socket/receive_buffer_size.html +/doc/html/boost_asio/reference/basic_socket/receive_low_watermark.html +/doc/html/boost_asio/reference/basic_socket/release/ +/doc/html/boost_asio/reference/basic_socket/release.html +/doc/html/boost_asio/reference/basic_socket/release/overload1.html +/doc/html/boost_asio/reference/basic_socket/release/overload2.html +/doc/html/boost_asio/reference/basic_socket/remote_endpoint/ +/doc/html/boost_asio/reference/basic_socket/remote_endpoint.html +/doc/html/boost_asio/reference/basic_socket/remote_endpoint/overload1.html +/doc/html/boost_asio/reference/basic_socket/remote_endpoint/overload2.html +/doc/html/boost_asio/reference/basic_socket/reuse_address.html +/doc/html/boost_asio/reference/basic_socket/send_buffer_size.html +/doc/html/boost_asio/reference/basic_socket/send_low_watermark.html +/doc/html/boost_asio/reference/basic_socket/set_option/ +/doc/html/boost_asio/reference/basic_socket/set_option.html +/doc/html/boost_asio/reference/basic_socket/set_option/overload1.html +/doc/html/boost_asio/reference/basic_socket/set_option/overload2.html +/doc/html/boost_asio/reference/basic_socket/shutdown/ +/doc/html/boost_asio/reference/basic_socket/shutdown.html +/doc/html/boost_asio/reference/basic_socket/shutdown/overload1.html +/doc/html/boost_asio/reference/basic_socket/shutdown/overload2.html +/doc/html/boost_asio/reference/basic_socket/shutdown_type.html +/doc/html/boost_asio/reference/basic_socket_streambuf/ +/doc/html/boost_asio/reference/basic_socket_streambuf/basic_socket_streambuf/ +/doc/html/boost_asio/reference/basic_socket_streambuf/_basic_socket_streambuf.html +/doc/html/boost_asio/reference/basic_socket_streambuf/basic_socket_streambuf.html +/doc/html/boost_asio/reference/basic_socket_streambuf/basic_socket_streambuf/overload1.html +/doc/html/boost_asio/reference/basic_socket_streambuf/basic_socket_streambuf/overload2.html +/doc/html/boost_asio/reference/basic_socket_streambuf/basic_socket_streambuf/overload3.html +/doc/html/boost_asio/reference/basic_socket_streambuf/clock_type.html +/doc/html/boost_asio/reference/basic_socket_streambuf/close.html +/doc/html/boost_asio/reference/basic_socket_streambuf/connect/ +/doc/html/boost_asio/reference/basic_socket_streambuf/connect.html +/doc/html/boost_asio/reference/basic_socket_streambuf/connect/overload1.html +/doc/html/boost_asio/reference/basic_socket_streambuf/connect/overload2.html +/doc/html/boost_asio/reference/basic_socket_streambuf/duration.html +/doc/html/boost_asio/reference/basic_socket_streambuf/duration_type.html +/doc/html/boost_asio/reference/basic_socket_streambuf/endpoint_type.html +/doc/html/boost_asio/reference/basic_socket_streambuf/error.html +/doc/html/boost_asio/reference/basic_socket_streambuf/expires_after.html +/doc/html/boost_asio/reference/basic_socket_streambuf/expires_at/ +/doc/html/boost_asio/reference/basic_socket_streambuf/expires_at.html +/doc/html/boost_asio/reference/basic_socket_streambuf/expires_at/overload1.html +/doc/html/boost_asio/reference/basic_socket_streambuf/expires_at/overload2.html +/doc/html/boost_asio/reference/basic_socket_streambuf/expires_from_now/ +/doc/html/boost_asio/reference/basic_socket_streambuf/expires_from_now.html +/doc/html/boost_asio/reference/basic_socket_streambuf/expires_from_now/overload1.html +/doc/html/boost_asio/reference/basic_socket_streambuf/expires_from_now/overload2.html +/doc/html/boost_asio/reference/basic_socket_streambuf/expiry.html +/doc/html/boost_asio/reference/basic_socket_streambuf.html +/doc/html/boost_asio/reference/basic_socket_streambuf/operator_eq_.html +/doc/html/boost_asio/reference/basic_socket_streambuf/overflow.html +/doc/html/boost_asio/reference/basic_socket_streambuf/protocol_type.html +/doc/html/boost_asio/reference/basic_socket_streambuf/puberror.html +/doc/html/boost_asio/reference/basic_socket_streambuf/setbuf.html +/doc/html/boost_asio/reference/basic_socket_streambuf/socket.html +/doc/html/boost_asio/reference/basic_socket_streambuf/sync.html +/doc/html/boost_asio/reference/basic_socket_streambuf/time_point.html +/doc/html/boost_asio/reference/basic_socket_streambuf/time_type.html +/doc/html/boost_asio/reference/basic_socket_streambuf/underflow.html +/doc/html/boost_asio/reference/basic_socket/wait/ +/doc/html/boost_asio/reference/basic_socket/wait.html +/doc/html/boost_asio/reference/basic_socket/wait/overload1.html +/doc/html/boost_asio/reference/basic_socket/wait/overload2.html +/doc/html/boost_asio/reference/basic_socket/wait_type.html +/doc/html/boost_asio/reference/basic_streambuf/ +/doc/html/boost_asio/reference/basic_streambuf/basic_streambuf.html +/doc/html/boost_asio/reference/basic_streambuf/capacity.html +/doc/html/boost_asio/reference/basic_streambuf/commit.html +/doc/html/boost_asio/reference/basic_streambuf/const_buffers_type.html +/doc/html/boost_asio/reference/basic_streambuf/consume.html +/doc/html/boost_asio/reference/basic_streambuf/data.html +/doc/html/boost_asio/reference/basic_streambuf.html +/doc/html/boost_asio/reference/basic_streambuf/max_size.html +/doc/html/boost_asio/reference/basic_streambuf/mutable_buffers_type.html +/doc/html/boost_asio/reference/basic_streambuf/overflow.html +/doc/html/boost_asio/reference/basic_streambuf/prepare.html +/doc/html/boost_asio/reference/basic_streambuf_ref/ +/doc/html/boost_asio/reference/basic_streambuf_ref/basic_streambuf_ref/ +/doc/html/boost_asio/reference/basic_streambuf_ref/basic_streambuf_ref.html +/doc/html/boost_asio/reference/basic_streambuf_ref/basic_streambuf_ref/overload1.html +/doc/html/boost_asio/reference/basic_streambuf_ref/basic_streambuf_ref/overload2.html +/doc/html/boost_asio/reference/basic_streambuf_ref/basic_streambuf_ref/overload3.html +/doc/html/boost_asio/reference/basic_streambuf_ref/capacity.html +/doc/html/boost_asio/reference/basic_streambuf_ref/commit.html +/doc/html/boost_asio/reference/basic_streambuf_ref/const_buffers_type.html +/doc/html/boost_asio/reference/basic_streambuf_ref/consume.html +/doc/html/boost_asio/reference/basic_streambuf_ref/data.html +/doc/html/boost_asio/reference/basic_streambuf_ref.html +/doc/html/boost_asio/reference/basic_streambuf_ref/max_size.html +/doc/html/boost_asio/reference/basic_streambuf_ref/mutable_buffers_type.html +/doc/html/boost_asio/reference/basic_streambuf_ref/prepare.html +/doc/html/boost_asio/reference/basic_streambuf_ref/size.html +/doc/html/boost_asio/reference/basic_streambuf/reserve.html +/doc/html/boost_asio/reference/basic_streambuf/size.html +/doc/html/boost_asio/reference/basic_streambuf/underflow.html +/doc/html/boost_asio/reference/basic_stream_socket/ +/doc/html/boost_asio/reference/basic_stream_socket/assign/ +/doc/html/boost_asio/reference/basic_stream_socket/assign.html +/doc/html/boost_asio/reference/basic_stream_socket/assign/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/assign/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/async_connect.html +/doc/html/boost_asio/reference/basic_stream_socket/async_read_some.html +/doc/html/boost_asio/reference/basic_stream_socket/async_receive/ +/doc/html/boost_asio/reference/basic_stream_socket/async_receive.html +/doc/html/boost_asio/reference/basic_stream_socket/async_receive/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/async_receive/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/async_send/ +/doc/html/boost_asio/reference/basic_stream_socket/async_send.html +/doc/html/boost_asio/reference/basic_stream_socket/async_send/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/async_send/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/async_wait.html +/doc/html/boost_asio/reference/basic_stream_socket/async_write_some.html +/doc/html/boost_asio/reference/basic_stream_socket/at_mark/ +/doc/html/boost_asio/reference/basic_stream_socket/at_mark.html +/doc/html/boost_asio/reference/basic_stream_socket/at_mark/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/at_mark/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/available/ +/doc/html/boost_asio/reference/basic_stream_socket/available.html +/doc/html/boost_asio/reference/basic_stream_socket/available/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/available/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/basic_stream_socket/ +/doc/html/boost_asio/reference/basic_stream_socket/_basic_stream_socket.html +/doc/html/boost_asio/reference/basic_stream_socket/basic_stream_socket.html +/doc/html/boost_asio/reference/basic_stream_socket/basic_stream_socket/overload10.html +/doc/html/boost_asio/reference/basic_stream_socket/basic_stream_socket/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/basic_stream_socket/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/basic_stream_socket/overload3.html +/doc/html/boost_asio/reference/basic_stream_socket/basic_stream_socket/overload4.html +/doc/html/boost_asio/reference/basic_stream_socket/basic_stream_socket/overload5.html +/doc/html/boost_asio/reference/basic_stream_socket/basic_stream_socket/overload6.html +/doc/html/boost_asio/reference/basic_stream_socket/basic_stream_socket/overload7.html +/doc/html/boost_asio/reference/basic_stream_socket/basic_stream_socket/overload8.html +/doc/html/boost_asio/reference/basic_stream_socket/basic_stream_socket/overload9.html +/doc/html/boost_asio/reference/basic_stream_socket/bind/ +/doc/html/boost_asio/reference/basic_stream_socket/bind.html +/doc/html/boost_asio/reference/basic_stream_socket/bind/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/bind/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/broadcast.html +/doc/html/boost_asio/reference/basic_stream_socket/bytes_readable.html +/doc/html/boost_asio/reference/basic_stream_socket/cancel/ +/doc/html/boost_asio/reference/basic_stream_socket/cancel.html +/doc/html/boost_asio/reference/basic_stream_socket/cancel/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/cancel/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/close/ +/doc/html/boost_asio/reference/basic_stream_socket/close.html +/doc/html/boost_asio/reference/basic_stream_socket/close/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/close/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/connect/ +/doc/html/boost_asio/reference/basic_stream_socket/connect.html +/doc/html/boost_asio/reference/basic_stream_socket/connect/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/connect/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/debug.html +/doc/html/boost_asio/reference/basic_stream_socket/do_not_route.html +/doc/html/boost_asio/reference/basic_stream_socket/enable_connection_aborted.html +/doc/html/boost_asio/reference/basic_stream_socket/endpoint_type.html +/doc/html/boost_asio/reference/basic_stream_socket/executor_type.html +/doc/html/boost_asio/reference/basic_stream_socket/get_executor.html +/doc/html/boost_asio/reference/basic_stream_socket/get_option/ +/doc/html/boost_asio/reference/basic_stream_socket/get_option.html +/doc/html/boost_asio/reference/basic_stream_socket/get_option/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/get_option/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket.html +/doc/html/boost_asio/reference/basic_stream_socket/impl_.html +/doc/html/boost_asio/reference/basic_stream_socket/io_control/ +/doc/html/boost_asio/reference/basic_stream_socket/io_control.html +/doc/html/boost_asio/reference/basic_stream_socket/io_control/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/io_control/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/is_open.html +/doc/html/boost_asio/reference/basic_stream_socket/keep_alive.html +/doc/html/boost_asio/reference/basic_stream_socket/linger.html +/doc/html/boost_asio/reference/basic_stream_socket/local_endpoint/ +/doc/html/boost_asio/reference/basic_stream_socket/local_endpoint.html +/doc/html/boost_asio/reference/basic_stream_socket/local_endpoint/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/local_endpoint/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/lowest_layer/ +/doc/html/boost_asio/reference/basic_stream_socket/lowest_layer.html +/doc/html/boost_asio/reference/basic_stream_socket/lowest_layer/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/lowest_layer/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/lowest_layer_type.html +/doc/html/boost_asio/reference/basic_stream_socket/max_connections.html +/doc/html/boost_asio/reference/basic_stream_socket/max_listen_connections.html +/doc/html/boost_asio/reference/basic_stream_socket/message_do_not_route.html +/doc/html/boost_asio/reference/basic_stream_socket/message_end_of_record.html +/doc/html/boost_asio/reference/basic_stream_socket/message_flags.html +/doc/html/boost_asio/reference/basic_stream_socket/message_out_of_band.html +/doc/html/boost_asio/reference/basic_stream_socket/message_peek.html +/doc/html/boost_asio/reference/basic_stream_socket/native_handle.html +/doc/html/boost_asio/reference/basic_stream_socket/native_handle_type.html +/doc/html/boost_asio/reference/basic_stream_socket/native_non_blocking/ +/doc/html/boost_asio/reference/basic_stream_socket/native_non_blocking.html +/doc/html/boost_asio/reference/basic_stream_socket/native_non_blocking/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/native_non_blocking/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/native_non_blocking/overload3.html +/doc/html/boost_asio/reference/basic_stream_socket/non_blocking/ +/doc/html/boost_asio/reference/basic_stream_socket/non_blocking.html +/doc/html/boost_asio/reference/basic_stream_socket/non_blocking/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/non_blocking/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/non_blocking/overload3.html +/doc/html/boost_asio/reference/basic_stream_socket/open/ +/doc/html/boost_asio/reference/basic_stream_socket/open.html +/doc/html/boost_asio/reference/basic_stream_socket/open/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/open/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/operator_eq_/ +/doc/html/boost_asio/reference/basic_stream_socket/operator_eq_.html +/doc/html/boost_asio/reference/basic_stream_socket/operator_eq_/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/operator_eq_/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/out_of_band_inline.html +/doc/html/boost_asio/reference/basic_stream_socket/protocol_type.html +/doc/html/boost_asio/reference/basic_stream_socket/read_some/ +/doc/html/boost_asio/reference/basic_stream_socket/read_some.html +/doc/html/boost_asio/reference/basic_stream_socket/read_some/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/read_some/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket__rebind_executor/ +/doc/html/boost_asio/reference/basic_stream_socket__rebind_executor.html +/doc/html/boost_asio/reference/basic_stream_socket__rebind_executor/other.html +/doc/html/boost_asio/reference/basic_stream_socket/receive/ +/doc/html/boost_asio/reference/basic_stream_socket/receive_buffer_size.html +/doc/html/boost_asio/reference/basic_stream_socket/receive.html +/doc/html/boost_asio/reference/basic_stream_socket/receive_low_watermark.html +/doc/html/boost_asio/reference/basic_stream_socket/receive/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/receive/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/receive/overload3.html +/doc/html/boost_asio/reference/basic_stream_socket/release/ +/doc/html/boost_asio/reference/basic_stream_socket/release.html +/doc/html/boost_asio/reference/basic_stream_socket/release/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/release/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/remote_endpoint/ +/doc/html/boost_asio/reference/basic_stream_socket/remote_endpoint.html +/doc/html/boost_asio/reference/basic_stream_socket/remote_endpoint/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/remote_endpoint/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/reuse_address.html +/doc/html/boost_asio/reference/basic_stream_socket/send/ +/doc/html/boost_asio/reference/basic_stream_socket/send_buffer_size.html +/doc/html/boost_asio/reference/basic_stream_socket/send.html +/doc/html/boost_asio/reference/basic_stream_socket/send_low_watermark.html +/doc/html/boost_asio/reference/basic_stream_socket/send/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/send/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/send/overload3.html +/doc/html/boost_asio/reference/basic_stream_socket/set_option/ +/doc/html/boost_asio/reference/basic_stream_socket/set_option.html +/doc/html/boost_asio/reference/basic_stream_socket/set_option/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/set_option/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/shutdown/ +/doc/html/boost_asio/reference/basic_stream_socket/shutdown.html +/doc/html/boost_asio/reference/basic_stream_socket/shutdown/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/shutdown/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/shutdown_type.html +/doc/html/boost_asio/reference/basic_stream_socket/wait/ +/doc/html/boost_asio/reference/basic_stream_socket/wait.html +/doc/html/boost_asio/reference/basic_stream_socket/wait/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/wait/overload2.html +/doc/html/boost_asio/reference/basic_stream_socket/wait_type.html +/doc/html/boost_asio/reference/basic_stream_socket/write_some/ +/doc/html/boost_asio/reference/basic_stream_socket/write_some.html +/doc/html/boost_asio/reference/basic_stream_socket/write_some/overload1.html +/doc/html/boost_asio/reference/basic_stream_socket/write_some/overload2.html +/doc/html/boost_asio/reference/basic_system_executor/ +/doc/html/boost_asio/reference/basic_system_executor/basic_system_executor.html +/doc/html/boost_asio/reference/basic_system_executor/context.html +/doc/html/boost_asio/reference/basic_system_executor/defer.html +/doc/html/boost_asio/reference/basic_system_executor/dispatch.html +/doc/html/boost_asio/reference/basic_system_executor/execute.html +/doc/html/boost_asio/reference/basic_system_executor.html +/doc/html/boost_asio/reference/basic_system_executor/on_work_finished.html +/doc/html/boost_asio/reference/basic_system_executor/on_work_started.html +/doc/html/boost_asio/reference/basic_system_executor/operator_eq__eq_.html +/doc/html/boost_asio/reference/basic_system_executor/operator_not__eq_.html +/doc/html/boost_asio/reference/basic_system_executor/post.html +/doc/html/boost_asio/reference/basic_system_executor/query/ +/doc/html/boost_asio/reference/basic_system_executor/query.html +/doc/html/boost_asio/reference/basic_system_executor/query/overload1.html +/doc/html/boost_asio/reference/basic_system_executor/query/overload2.html +/doc/html/boost_asio/reference/basic_system_executor/query/overload3.html +/doc/html/boost_asio/reference/basic_system_executor/query__static/ +/doc/html/boost_asio/reference/basic_system_executor/query__static.html +/doc/html/boost_asio/reference/basic_system_executor/query__static/overload1.html +/doc/html/boost_asio/reference/basic_system_executor/query__static/overload2.html +/doc/html/boost_asio/reference/basic_system_executor/query__static/overload3.html +/doc/html/boost_asio/reference/basic_system_executor/query__static/overload4.html +/doc/html/boost_asio/reference/basic_system_executor/require/ +/doc/html/boost_asio/reference/basic_system_executor/require.html +/doc/html/boost_asio/reference/basic_system_executor/require/overload1.html +/doc/html/boost_asio/reference/basic_system_executor/require/overload2.html +/doc/html/boost_asio/reference/basic_system_executor/require/overload3.html +/doc/html/boost_asio/reference/basic_system_executor/require/overload4.html +/doc/html/boost_asio/reference/basic_system_executor/require/overload5.html +/doc/html/boost_asio/reference/basic_system_executor/require/overload6.html +/doc/html/boost_asio/reference/basic_system_executor/require/overload7.html +/doc/html/boost_asio/reference/basic_waitable_timer/ +/doc/html/boost_asio/reference/basic_waitable_timer/async_wait.html +/doc/html/boost_asio/reference/basic_waitable_timer/basic_waitable_timer/ +/doc/html/boost_asio/reference/basic_waitable_timer/_basic_waitable_timer.html +/doc/html/boost_asio/reference/basic_waitable_timer/basic_waitable_timer.html +/doc/html/boost_asio/reference/basic_waitable_timer/basic_waitable_timer/overload1.html +/doc/html/boost_asio/reference/basic_waitable_timer/basic_waitable_timer/overload2.html +/doc/html/boost_asio/reference/basic_waitable_timer/basic_waitable_timer/overload3.html +/doc/html/boost_asio/reference/basic_waitable_timer/basic_waitable_timer/overload4.html +/doc/html/boost_asio/reference/basic_waitable_timer/basic_waitable_timer/overload5.html +/doc/html/boost_asio/reference/basic_waitable_timer/basic_waitable_timer/overload6.html +/doc/html/boost_asio/reference/basic_waitable_timer/basic_waitable_timer/overload7.html +/doc/html/boost_asio/reference/basic_waitable_timer/basic_waitable_timer/overload8.html +/doc/html/boost_asio/reference/basic_waitable_timer/cancel/ +/doc/html/boost_asio/reference/basic_waitable_timer/cancel.html +/doc/html/boost_asio/reference/basic_waitable_timer/cancel_one/ +/doc/html/boost_asio/reference/basic_waitable_timer/cancel_one.html +/doc/html/boost_asio/reference/basic_waitable_timer/cancel_one/overload1.html +/doc/html/boost_asio/reference/basic_waitable_timer/cancel_one/overload2.html +/doc/html/boost_asio/reference/basic_waitable_timer/cancel/overload1.html +/doc/html/boost_asio/reference/basic_waitable_timer/cancel/overload2.html +/doc/html/boost_asio/reference/basic_waitable_timer/clock_type.html +/doc/html/boost_asio/reference/basic_waitable_timer/duration.html +/doc/html/boost_asio/reference/basic_waitable_timer/executor_type.html +/doc/html/boost_asio/reference/basic_waitable_timer/expires_after.html +/doc/html/boost_asio/reference/basic_waitable_timer/expires_at/ +/doc/html/boost_asio/reference/basic_waitable_timer/expires_at.html +/doc/html/boost_asio/reference/basic_waitable_timer/expires_at/overload1.html +/doc/html/boost_asio/reference/basic_waitable_timer/expires_at/overload2.html +/doc/html/boost_asio/reference/basic_waitable_timer/expires_at/overload3.html +/doc/html/boost_asio/reference/basic_waitable_timer/expires_from_now/ +/doc/html/boost_asio/reference/basic_waitable_timer/expires_from_now.html +/doc/html/boost_asio/reference/basic_waitable_timer/expires_from_now/overload1.html +/doc/html/boost_asio/reference/basic_waitable_timer/expires_from_now/overload2.html +/doc/html/boost_asio/reference/basic_waitable_timer/expires_from_now/overload3.html +/doc/html/boost_asio/reference/basic_waitable_timer/expiry.html +/doc/html/boost_asio/reference/basic_waitable_timer/get_executor.html +/doc/html/boost_asio/reference/basic_waitable_timer.html +/doc/html/boost_asio/reference/basic_waitable_timer/operator_eq_/ +/doc/html/boost_asio/reference/basic_waitable_timer/operator_eq_.html +/doc/html/boost_asio/reference/basic_waitable_timer/operator_eq_/overload1.html +/doc/html/boost_asio/reference/basic_waitable_timer/operator_eq_/overload2.html +/doc/html/boost_asio/reference/basic_waitable_timer__rebind_executor/ +/doc/html/boost_asio/reference/basic_waitable_timer__rebind_executor.html +/doc/html/boost_asio/reference/basic_waitable_timer__rebind_executor/other.html +/doc/html/boost_asio/reference/basic_waitable_timer/time_point.html +/doc/html/boost_asio/reference/basic_waitable_timer/traits_type.html +/doc/html/boost_asio/reference/basic_waitable_timer/wait/ +/doc/html/boost_asio/reference/basic_waitable_timer/wait.html +/doc/html/boost_asio/reference/basic_waitable_timer/wait/overload1.html +/doc/html/boost_asio/reference/basic_waitable_timer/wait/overload2.html +/doc/html/boost_asio/reference/basic_yield_context/ +/doc/html/boost_asio/reference/basic_yield_context/basic_yield_context/ +/doc/html/boost_asio/reference/basic_yield_context/basic_yield_context.html +/doc/html/boost_asio/reference/basic_yield_context/basic_yield_context/overload1.html +/doc/html/boost_asio/reference/basic_yield_context/basic_yield_context/overload2.html +/doc/html/boost_asio/reference/basic_yield_context/callee_type.html +/doc/html/boost_asio/reference/basic_yield_context/caller_type.html +/doc/html/boost_asio/reference/basic_yield_context.html +/doc/html/boost_asio/reference/basic_yield_context/operator_lb__rb_.html +/doc/html/boost_asio/reference/bind_executor/ +/doc/html/boost_asio/reference/bind_executor.html +/doc/html/boost_asio/reference/bind_executor/overload1.html +/doc/html/boost_asio/reference/bind_executor/overload2.html +/doc/html/boost_asio/reference/buffer/ +/doc/html/boost_asio/reference/buffer_cast/ +/doc/html/boost_asio/reference/buffer_cast.html +/doc/html/boost_asio/reference/buffer_cast/overload1.html +/doc/html/boost_asio/reference/buffer_cast/overload2.html +/doc/html/boost_asio/reference/buffer_copy/ +/doc/html/boost_asio/reference/buffer_copy.html +/doc/html/boost_asio/reference/buffer_copy/overload1.html +/doc/html/boost_asio/reference/buffer_copy/overload2.html +/doc/html/boost_asio/reference/BufferedHandshakeHandler.html +/doc/html/boost_asio/reference/buffered_read_stream/ +/doc/html/boost_asio/reference/buffered_read_stream/async_fill.html +/doc/html/boost_asio/reference/buffered_read_stream/async_read_some.html +/doc/html/boost_asio/reference/buffered_read_stream/async_write_some.html +/doc/html/boost_asio/reference/buffered_read_stream/buffered_read_stream/ +/doc/html/boost_asio/reference/buffered_read_stream/buffered_read_stream.html +/doc/html/boost_asio/reference/buffered_read_stream/buffered_read_stream/overload1.html +/doc/html/boost_asio/reference/buffered_read_stream/buffered_read_stream/overload2.html +/doc/html/boost_asio/reference/buffered_read_stream/close/ +/doc/html/boost_asio/reference/buffered_read_stream/close.html +/doc/html/boost_asio/reference/buffered_read_stream/close/overload1.html +/doc/html/boost_asio/reference/buffered_read_stream/close/overload2.html +/doc/html/boost_asio/reference/buffered_read_stream/default_buffer_size.html +/doc/html/boost_asio/reference/buffered_read_stream/executor_type.html +/doc/html/boost_asio/reference/buffered_read_stream/fill/ +/doc/html/boost_asio/reference/buffered_read_stream/fill.html +/doc/html/boost_asio/reference/buffered_read_stream/fill/overload1.html +/doc/html/boost_asio/reference/buffered_read_stream/fill/overload2.html +/doc/html/boost_asio/reference/buffered_read_stream/get_executor.html +/doc/html/boost_asio/reference/buffered_read_stream.html +/doc/html/boost_asio/reference/buffered_read_stream/in_avail/ +/doc/html/boost_asio/reference/buffered_read_stream/in_avail.html +/doc/html/boost_asio/reference/buffered_read_stream/in_avail/overload1.html +/doc/html/boost_asio/reference/buffered_read_stream/in_avail/overload2.html +/doc/html/boost_asio/reference/buffered_read_stream/lowest_layer/ +/doc/html/boost_asio/reference/buffered_read_stream/lowest_layer.html +/doc/html/boost_asio/reference/buffered_read_stream/lowest_layer/overload1.html +/doc/html/boost_asio/reference/buffered_read_stream/lowest_layer/overload2.html +/doc/html/boost_asio/reference/buffered_read_stream/lowest_layer_type.html +/doc/html/boost_asio/reference/buffered_read_stream/next_layer.html +/doc/html/boost_asio/reference/buffered_read_stream/next_layer_type.html +/doc/html/boost_asio/reference/buffered_read_stream/peek/ +/doc/html/boost_asio/reference/buffered_read_stream/peek.html +/doc/html/boost_asio/reference/buffered_read_stream/peek/overload1.html +/doc/html/boost_asio/reference/buffered_read_stream/peek/overload2.html +/doc/html/boost_asio/reference/buffered_read_stream/read_some/ +/doc/html/boost_asio/reference/buffered_read_stream/read_some.html +/doc/html/boost_asio/reference/buffered_read_stream/read_some/overload1.html +/doc/html/boost_asio/reference/buffered_read_stream/read_some/overload2.html +/doc/html/boost_asio/reference/buffered_read_stream/write_some/ +/doc/html/boost_asio/reference/buffered_read_stream/write_some.html +/doc/html/boost_asio/reference/buffered_read_stream/write_some/overload1.html +/doc/html/boost_asio/reference/buffered_read_stream/write_some/overload2.html +/doc/html/boost_asio/reference/buffered_stream/ +/doc/html/boost_asio/reference/buffered_stream/async_fill.html +/doc/html/boost_asio/reference/buffered_stream/async_flush.html +/doc/html/boost_asio/reference/buffered_stream/async_read_some.html +/doc/html/boost_asio/reference/buffered_stream/async_write_some.html +/doc/html/boost_asio/reference/buffered_stream/buffered_stream/ +/doc/html/boost_asio/reference/buffered_stream/buffered_stream.html +/doc/html/boost_asio/reference/buffered_stream/buffered_stream/overload1.html +/doc/html/boost_asio/reference/buffered_stream/buffered_stream/overload2.html +/doc/html/boost_asio/reference/buffered_stream/close/ +/doc/html/boost_asio/reference/buffered_stream/close.html +/doc/html/boost_asio/reference/buffered_stream/close/overload1.html +/doc/html/boost_asio/reference/buffered_stream/close/overload2.html +/doc/html/boost_asio/reference/buffered_stream/executor_type.html +/doc/html/boost_asio/reference/buffered_stream/fill/ +/doc/html/boost_asio/reference/buffered_stream/fill.html +/doc/html/boost_asio/reference/buffered_stream/fill/overload1.html +/doc/html/boost_asio/reference/buffered_stream/fill/overload2.html +/doc/html/boost_asio/reference/buffered_stream/flush/ +/doc/html/boost_asio/reference/buffered_stream/flush.html +/doc/html/boost_asio/reference/buffered_stream/flush/overload1.html +/doc/html/boost_asio/reference/buffered_stream/flush/overload2.html +/doc/html/boost_asio/reference/buffered_stream/get_executor.html +/doc/html/boost_asio/reference/buffered_stream.html +/doc/html/boost_asio/reference/buffered_stream/in_avail/ +/doc/html/boost_asio/reference/buffered_stream/in_avail.html +/doc/html/boost_asio/reference/buffered_stream/in_avail/overload1.html +/doc/html/boost_asio/reference/buffered_stream/in_avail/overload2.html +/doc/html/boost_asio/reference/buffered_stream/lowest_layer/ +/doc/html/boost_asio/reference/buffered_stream/lowest_layer.html +/doc/html/boost_asio/reference/buffered_stream/lowest_layer/overload1.html +/doc/html/boost_asio/reference/buffered_stream/lowest_layer/overload2.html +/doc/html/boost_asio/reference/buffered_stream/lowest_layer_type.html +/doc/html/boost_asio/reference/buffered_stream/next_layer.html +/doc/html/boost_asio/reference/buffered_stream/next_layer_type.html +/doc/html/boost_asio/reference/buffered_stream/peek/ +/doc/html/boost_asio/reference/buffered_stream/peek.html +/doc/html/boost_asio/reference/buffered_stream/peek/overload1.html +/doc/html/boost_asio/reference/buffered_stream/peek/overload2.html +/doc/html/boost_asio/reference/buffered_stream/read_some/ +/doc/html/boost_asio/reference/buffered_stream/read_some.html +/doc/html/boost_asio/reference/buffered_stream/read_some/overload1.html +/doc/html/boost_asio/reference/buffered_stream/read_some/overload2.html +/doc/html/boost_asio/reference/buffered_stream/write_some/ +/doc/html/boost_asio/reference/buffered_stream/write_some.html +/doc/html/boost_asio/reference/buffered_stream/write_some/overload1.html +/doc/html/boost_asio/reference/buffered_stream/write_some/overload2.html +/doc/html/boost_asio/reference/buffered_write_stream/ +/doc/html/boost_asio/reference/buffered_write_stream/async_flush.html +/doc/html/boost_asio/reference/buffered_write_stream/async_read_some.html +/doc/html/boost_asio/reference/buffered_write_stream/async_write_some.html +/doc/html/boost_asio/reference/buffered_write_stream/buffered_write_stream/ +/doc/html/boost_asio/reference/buffered_write_stream/buffered_write_stream.html +/doc/html/boost_asio/reference/buffered_write_stream/buffered_write_stream/overload1.html +/doc/html/boost_asio/reference/buffered_write_stream/buffered_write_stream/overload2.html +/doc/html/boost_asio/reference/buffered_write_stream/close/ +/doc/html/boost_asio/reference/buffered_write_stream/close.html +/doc/html/boost_asio/reference/buffered_write_stream/close/overload1.html +/doc/html/boost_asio/reference/buffered_write_stream/close/overload2.html +/doc/html/boost_asio/reference/buffered_write_stream/default_buffer_size.html +/doc/html/boost_asio/reference/buffered_write_stream/executor_type.html +/doc/html/boost_asio/reference/buffered_write_stream/flush/ +/doc/html/boost_asio/reference/buffered_write_stream/flush.html +/doc/html/boost_asio/reference/buffered_write_stream/flush/overload1.html +/doc/html/boost_asio/reference/buffered_write_stream/flush/overload2.html +/doc/html/boost_asio/reference/buffered_write_stream/get_executor.html +/doc/html/boost_asio/reference/buffered_write_stream.html +/doc/html/boost_asio/reference/buffered_write_stream/in_avail/ +/doc/html/boost_asio/reference/buffered_write_stream/in_avail.html +/doc/html/boost_asio/reference/buffered_write_stream/in_avail/overload1.html +/doc/html/boost_asio/reference/buffered_write_stream/in_avail/overload2.html +/doc/html/boost_asio/reference/buffered_write_stream/lowest_layer/ +/doc/html/boost_asio/reference/buffered_write_stream/lowest_layer.html +/doc/html/boost_asio/reference/buffered_write_stream/lowest_layer/overload1.html +/doc/html/boost_asio/reference/buffered_write_stream/lowest_layer/overload2.html +/doc/html/boost_asio/reference/buffered_write_stream/lowest_layer_type.html +/doc/html/boost_asio/reference/buffered_write_stream/next_layer.html +/doc/html/boost_asio/reference/buffered_write_stream/next_layer_type.html +/doc/html/boost_asio/reference/buffered_write_stream/peek/ +/doc/html/boost_asio/reference/buffered_write_stream/peek.html +/doc/html/boost_asio/reference/buffered_write_stream/peek/overload1.html +/doc/html/boost_asio/reference/buffered_write_stream/peek/overload2.html +/doc/html/boost_asio/reference/buffered_write_stream/read_some/ +/doc/html/boost_asio/reference/buffered_write_stream/read_some.html +/doc/html/boost_asio/reference/buffered_write_stream/read_some/overload1.html +/doc/html/boost_asio/reference/buffered_write_stream/read_some/overload2.html +/doc/html/boost_asio/reference/buffered_write_stream/write_some/ +/doc/html/boost_asio/reference/buffered_write_stream/write_some.html +/doc/html/boost_asio/reference/buffered_write_stream/write_some/overload1.html +/doc/html/boost_asio/reference/buffered_write_stream/write_some/overload2.html +/doc/html/boost_asio/reference/buffer.html +/doc/html/boost_asio/reference/buffer/overload10.html +/doc/html/boost_asio/reference/buffer/overload11.html +/doc/html/boost_asio/reference/buffer/overload12.html +/doc/html/boost_asio/reference/buffer/overload13.html +/doc/html/boost_asio/reference/buffer/overload14.html +/doc/html/boost_asio/reference/buffer/overload15.html +/doc/html/boost_asio/reference/buffer/overload16.html +/doc/html/boost_asio/reference/buffer/overload17.html +/doc/html/boost_asio/reference/buffer/overload18.html +/doc/html/boost_asio/reference/buffer/overload19.html +/doc/html/boost_asio/reference/buffer/overload1.html +/doc/html/boost_asio/reference/buffer/overload20.html +/doc/html/boost_asio/reference/buffer/overload21.html +/doc/html/boost_asio/reference/buffer/overload22.html +/doc/html/boost_asio/reference/buffer/overload23.html +/doc/html/boost_asio/reference/buffer/overload24.html +/doc/html/boost_asio/reference/buffer/overload25.html +/doc/html/boost_asio/reference/buffer/overload26.html +/doc/html/boost_asio/reference/buffer/overload27.html +/doc/html/boost_asio/reference/buffer/overload28.html +/doc/html/boost_asio/reference/buffer/overload29.html +/doc/html/boost_asio/reference/buffer/overload2.html +/doc/html/boost_asio/reference/buffer/overload30.html +/doc/html/boost_asio/reference/buffer/overload31.html +/doc/html/boost_asio/reference/buffer/overload32.html +/doc/html/boost_asio/reference/buffer/overload3.html +/doc/html/boost_asio/reference/buffer/overload4.html +/doc/html/boost_asio/reference/buffer/overload5.html +/doc/html/boost_asio/reference/buffer/overload6.html +/doc/html/boost_asio/reference/buffer/overload7.html +/doc/html/boost_asio/reference/buffer/overload8.html +/doc/html/boost_asio/reference/buffer/overload9.html +/doc/html/boost_asio/reference/buffers_begin.html +/doc/html/boost_asio/reference/buffers_end.html +/doc/html/boost_asio/reference/buffer_sequence_begin/ +/doc/html/boost_asio/reference/buffer_sequence_begin.html +/doc/html/boost_asio/reference/buffer_sequence_begin/overload1.html +/doc/html/boost_asio/reference/buffer_sequence_begin/overload2.html +/doc/html/boost_asio/reference/buffer_sequence_begin/overload3.html +/doc/html/boost_asio/reference/buffer_sequence_begin/overload4.html +/doc/html/boost_asio/reference/buffer_sequence_end/ +/doc/html/boost_asio/reference/buffer_sequence_end.html +/doc/html/boost_asio/reference/buffer_sequence_end/overload1.html +/doc/html/boost_asio/reference/buffer_sequence_end/overload2.html +/doc/html/boost_asio/reference/buffer_sequence_end/overload3.html +/doc/html/boost_asio/reference/buffer_sequence_end/overload4.html +/doc/html/boost_asio/reference/buffers_iterator/ +/doc/html/boost_asio/reference/buffers_iterator/begin.html +/doc/html/boost_asio/reference/buffers_iterator/buffers_iterator.html +/doc/html/boost_asio/reference/buffers_iterator/difference_type.html +/doc/html/boost_asio/reference/buffers_iterator/end.html +/doc/html/boost_asio/reference/buffers_iterator.html +/doc/html/boost_asio/reference/buffers_iterator/iterator_category.html +/doc/html/boost_asio/reference/buffers_iterator/operator_arrow_.html +/doc/html/boost_asio/reference/buffers_iterator/operator_eq__eq_.html +/doc/html/boost_asio/reference/buffers_iterator/operator_gt__eq_.html +/doc/html/boost_asio/reference/buffers_iterator/operator_gt_.html +/doc/html/boost_asio/reference/buffers_iterator/operator_lb__rb_.html +/doc/html/boost_asio/reference/buffers_iterator/operator_lt__eq_.html +/doc/html/boost_asio/reference/buffers_iterator/operator_lt_.html +/doc/html/boost_asio/reference/buffers_iterator/operator_minus_/ +/doc/html/boost_asio/reference/buffers_iterator/operator_minus__eq_.html +/doc/html/boost_asio/reference/buffers_iterator/operator_minus_.html +/doc/html/boost_asio/reference/buffers_iterator/operator_minus__minus_/ +/doc/html/boost_asio/reference/buffers_iterator/operator_minus__minus_.html +/doc/html/boost_asio/reference/buffers_iterator/operator_minus__minus_/overload1.html +/doc/html/boost_asio/reference/buffers_iterator/operator_minus__minus_/overload2.html +/doc/html/boost_asio/reference/buffers_iterator/operator_minus_/overload1.html +/doc/html/boost_asio/reference/buffers_iterator/operator_minus_/overload2.html +/doc/html/boost_asio/reference/buffers_iterator/operator_not__eq_.html +/doc/html/boost_asio/reference/buffers_iterator/operator_plus_/ +/doc/html/boost_asio/reference/buffers_iterator/operator_plus__eq_.html +/doc/html/boost_asio/reference/buffers_iterator/operator_plus_.html +/doc/html/boost_asio/reference/buffers_iterator/operator_plus_/overload1.html +/doc/html/boost_asio/reference/buffers_iterator/operator_plus_/overload2.html +/doc/html/boost_asio/reference/buffers_iterator/operator_plus__plus_/ +/doc/html/boost_asio/reference/buffers_iterator/operator_plus__plus_.html +/doc/html/boost_asio/reference/buffers_iterator/operator_plus__plus_/overload1.html +/doc/html/boost_asio/reference/buffers_iterator/operator_plus__plus_/overload2.html +/doc/html/boost_asio/reference/buffers_iterator/operator__star_.html +/doc/html/boost_asio/reference/buffers_iterator/pointer.html +/doc/html/boost_asio/reference/buffers_iterator/reference.html +/doc/html/boost_asio/reference/buffers_iterator/value_type.html +/doc/html/boost_asio/reference/buffer_size.html +/doc/html/boost_asio/reference/can_prefer.html +/doc/html/boost_asio/reference/can_query.html +/doc/html/boost_asio/reference/can_require_concept.html +/doc/html/boost_asio/reference/can_require.html +/doc/html/boost_asio/reference/CompletionCondition.html +/doc/html/boost_asio/reference/CompletionHandler.html +/doc/html/boost_asio/reference/connect/ +/doc/html/boost_asio/reference/ConnectCondition.html +/doc/html/boost_asio/reference/ConnectHandler.html +/doc/html/boost_asio/reference/connect.html +/doc/html/boost_asio/reference/connect/overload10.html +/doc/html/boost_asio/reference/connect/overload11.html +/doc/html/boost_asio/reference/connect/overload12.html +/doc/html/boost_asio/reference/connect/overload1.html +/doc/html/boost_asio/reference/connect/overload2.html +/doc/html/boost_asio/reference/connect/overload3.html +/doc/html/boost_asio/reference/connect/overload4.html +/doc/html/boost_asio/reference/connect/overload5.html +/doc/html/boost_asio/reference/connect/overload6.html +/doc/html/boost_asio/reference/connect/overload7.html +/doc/html/boost_asio/reference/connect/overload8.html +/doc/html/boost_asio/reference/connect/overload9.html +/doc/html/boost_asio/reference/const_buffer/ +/doc/html/boost_asio/reference/const_buffer/const_buffer/ +/doc/html/boost_asio/reference/const_buffer/const_buffer.html +/doc/html/boost_asio/reference/const_buffer/const_buffer/overload1.html +/doc/html/boost_asio/reference/const_buffer/const_buffer/overload2.html +/doc/html/boost_asio/reference/const_buffer/const_buffer/overload3.html +/doc/html/boost_asio/reference/const_buffer/data.html +/doc/html/boost_asio/reference/const_buffer.html +/doc/html/boost_asio/reference/const_buffer/operator_plus_/ +/doc/html/boost_asio/reference/const_buffer/operator_plus__eq_.html +/doc/html/boost_asio/reference/const_buffer/operator_plus_.html +/doc/html/boost_asio/reference/const_buffer/operator_plus_/overload1.html +/doc/html/boost_asio/reference/const_buffer/operator_plus_/overload2.html +/doc/html/boost_asio/reference/const_buffers_1/ +/doc/html/boost_asio/reference/const_buffers_1/begin.html +/doc/html/boost_asio/reference/const_buffers_1/const_buffers_1/ +/doc/html/boost_asio/reference/const_buffers_1/const_buffers_1.html +/doc/html/boost_asio/reference/const_buffers_1/const_buffers_1/overload1.html +/doc/html/boost_asio/reference/const_buffers_1/const_buffers_1/overload2.html +/doc/html/boost_asio/reference/const_buffers_1/const_iterator.html +/doc/html/boost_asio/reference/const_buffers_1/data.html +/doc/html/boost_asio/reference/const_buffers_1/end.html +/doc/html/boost_asio/reference/const_buffers_1.html +/doc/html/boost_asio/reference/const_buffers_1/operator_plus_/ +/doc/html/boost_asio/reference/const_buffers_1/operator_plus__eq_.html +/doc/html/boost_asio/reference/const_buffers_1/operator_plus_.html +/doc/html/boost_asio/reference/const_buffers_1/operator_plus_/overload1.html +/doc/html/boost_asio/reference/const_buffers_1/operator_plus_/overload2.html +/doc/html/boost_asio/reference/const_buffers_1/size.html +/doc/html/boost_asio/reference/const_buffers_1/value_type.html +/doc/html/boost_asio/reference/ConstBufferSequence.html +/doc/html/boost_asio/reference/const_buffer/size.html +/doc/html/boost_asio/reference/coroutine/ +/doc/html/boost_asio/reference/coroutine/coroutine.html +/doc/html/boost_asio/reference/coroutine.html +/doc/html/boost_asio/reference/coroutine/is_child.html +/doc/html/boost_asio/reference/coroutine/is_complete.html +/doc/html/boost_asio/reference/coroutine/is_parent.html +/doc/html/boost_asio/reference/co_spawn/ +/doc/html/boost_asio/reference/co_spawn.html +/doc/html/boost_asio/reference/co_spawn/overload1.html +/doc/html/boost_asio/reference/co_spawn/overload2.html +/doc/html/boost_asio/reference/co_spawn/overload3.html +/doc/html/boost_asio/reference/co_spawn/overload4.html +/doc/html/boost_asio/reference/co_spawn/overload5.html +/doc/html/boost_asio/reference/co_spawn/overload6.html +/doc/html/boost_asio/reference/deadline_timer.html +/doc/html/boost_asio/reference/default_completion_token/ +/doc/html/boost_asio/reference/default_completion_token.html +/doc/html/boost_asio/reference/default_completion_token/type.html +/doc/html/boost_asio/reference/defer/ +/doc/html/boost_asio/reference/defer.html +/doc/html/boost_asio/reference/defer/overload1.html +/doc/html/boost_asio/reference/defer/overload2.html +/doc/html/boost_asio/reference/defer/overload3.html +/doc/html/boost_asio/reference/detached.html +/doc/html/boost_asio/reference/detached_t/ +/doc/html/boost_asio/reference/detached_t/as_default_on.html +/doc/html/boost_asio/reference/detached_t/detached_t.html +/doc/html/boost_asio/reference/detached_t__executor_with_default/ +/doc/html/boost_asio/reference/detached_t__executor_with_default/default_completion_token_type.html +/doc/html/boost_asio/reference/detached_t__executor_with_default/executor_with_default/ +/doc/html/boost_asio/reference/detached_t__executor_with_default/executor_with_default.html +/doc/html/boost_asio/reference/detached_t__executor_with_default/executor_with_default/overload1.html +/doc/html/boost_asio/reference/detached_t__executor_with_default/executor_with_default/overload2.html +/doc/html/boost_asio/reference/detached_t__executor_with_default.html +/doc/html/boost_asio/reference/detached_t.html +/doc/html/boost_asio/reference/dispatch/ +/doc/html/boost_asio/reference/dispatch.html +/doc/html/boost_asio/reference/dispatch/overload1.html +/doc/html/boost_asio/reference/dispatch/overload2.html +/doc/html/boost_asio/reference/dispatch/overload3.html +/doc/html/boost_asio/reference/dynamic_buffer/ +/doc/html/boost_asio/reference/DynamicBuffer.html +/doc/html/boost_asio/reference/dynamic_buffer.html +/doc/html/boost_asio/reference/dynamic_buffer/overload1.html +/doc/html/boost_asio/reference/dynamic_buffer/overload2.html +/doc/html/boost_asio/reference/dynamic_buffer/overload3.html +/doc/html/boost_asio/reference/dynamic_buffer/overload4.html +/doc/html/boost_asio/reference/DynamicBuffer_v1.html +/doc/html/boost_asio/reference/DynamicBuffer_v2.html +/doc/html/boost_asio/reference/dynamic_string_buffer/ +/doc/html/boost_asio/reference/dynamic_string_buffer/capacity.html +/doc/html/boost_asio/reference/dynamic_string_buffer/commit.html +/doc/html/boost_asio/reference/dynamic_string_buffer/const_buffers_type.html +/doc/html/boost_asio/reference/dynamic_string_buffer/consume.html +/doc/html/boost_asio/reference/dynamic_string_buffer/data/ +/doc/html/boost_asio/reference/dynamic_string_buffer/data.html +/doc/html/boost_asio/reference/dynamic_string_buffer/data/overload1.html +/doc/html/boost_asio/reference/dynamic_string_buffer/data/overload2.html +/doc/html/boost_asio/reference/dynamic_string_buffer/data/overload3.html +/doc/html/boost_asio/reference/dynamic_string_buffer/dynamic_string_buffer/ +/doc/html/boost_asio/reference/dynamic_string_buffer/dynamic_string_buffer.html +/doc/html/boost_asio/reference/dynamic_string_buffer/dynamic_string_buffer/overload1.html +/doc/html/boost_asio/reference/dynamic_string_buffer/dynamic_string_buffer/overload2.html +/doc/html/boost_asio/reference/dynamic_string_buffer/dynamic_string_buffer/overload3.html +/doc/html/boost_asio/reference/dynamic_string_buffer/grow.html +/doc/html/boost_asio/reference/dynamic_string_buffer.html +/doc/html/boost_asio/reference/dynamic_string_buffer/max_size.html +/doc/html/boost_asio/reference/dynamic_string_buffer/mutable_buffers_type.html +/doc/html/boost_asio/reference/dynamic_string_buffer/prepare.html +/doc/html/boost_asio/reference/dynamic_string_buffer/shrink.html +/doc/html/boost_asio/reference/dynamic_string_buffer/size.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/ +/doc/html/boost_asio/reference/dynamic_vector_buffer/capacity.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/commit.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/const_buffers_type.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/consume.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/data/ +/doc/html/boost_asio/reference/dynamic_vector_buffer/data.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/data/overload1.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/data/overload2.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/data/overload3.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/dynamic_vector_buffer/ +/doc/html/boost_asio/reference/dynamic_vector_buffer/dynamic_vector_buffer.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/dynamic_vector_buffer/overload1.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/dynamic_vector_buffer/overload2.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/dynamic_vector_buffer/overload3.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/grow.html +/doc/html/boost_asio/reference/dynamic_vector_buffer.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/max_size.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/mutable_buffers_type.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/prepare.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/shrink.html +/doc/html/boost_asio/reference/dynamic_vector_buffer/size.html +/doc/html/boost_asio/reference/Endpoint.html +/doc/html/boost_asio/reference/EndpointSequence.html +/doc/html/boost_asio/reference/error__addrinfo_category.html +/doc/html/boost_asio/reference/error__addrinfo_errors.html +/doc/html/boost_asio/reference/error__basic_errors.html +/doc/html/boost_asio/reference/error__get_addrinfo_category.html +/doc/html/boost_asio/reference/error__get_misc_category.html +/doc/html/boost_asio/reference/error__get_netdb_category.html +/doc/html/boost_asio/reference/error__get_ssl_category.html +/doc/html/boost_asio/reference/error__get_system_category.html +/doc/html/boost_asio/reference/error__make_error_code/ +/doc/html/boost_asio/reference/error__make_error_code.html +/doc/html/boost_asio/reference/error__make_error_code/overload1.html +/doc/html/boost_asio/reference/error__make_error_code/overload2.html +/doc/html/boost_asio/reference/error__make_error_code/overload3.html +/doc/html/boost_asio/reference/error__make_error_code/overload4.html +/doc/html/boost_asio/reference/error__make_error_code/overload5.html +/doc/html/boost_asio/reference/error__misc_category.html +/doc/html/boost_asio/reference/error__misc_errors.html +/doc/html/boost_asio/reference/error__netdb_category.html +/doc/html/boost_asio/reference/error__netdb_errors.html +/doc/html/boost_asio/reference/error__ssl_category.html +/doc/html/boost_asio/reference/error__ssl_errors.html +/doc/html/boost_asio/reference/error__system_category.html +/doc/html/boost_asio/reference/execution__allocator.html +/doc/html/boost_asio/reference/execution__allocator_t/ +/doc/html/boost_asio/reference/execution__allocator_t/allocator_t.html +/doc/html/boost_asio/reference/execution__allocator_t.html +/doc/html/boost_asio/reference/execution__allocator_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__allocator_t/is_preferable.html +/doc/html/boost_asio/reference/execution__allocator_t/is_requirable.html +/doc/html/boost_asio/reference/execution__allocator_t/value.html +/doc/html/boost_asio/reference/execution__any_executor/ +/doc/html/boost_asio/reference/execution__any_executor/any_executor/ +/doc/html/boost_asio/reference/execution__any_executor/_any_executor.html +/doc/html/boost_asio/reference/execution__any_executor/any_executor.html +/doc/html/boost_asio/reference/execution__any_executor/any_executor/overload1.html +/doc/html/boost_asio/reference/execution__any_executor/any_executor/overload2.html +/doc/html/boost_asio/reference/execution__any_executor/any_executor/overload3.html +/doc/html/boost_asio/reference/execution__any_executor/any_executor/overload4.html +/doc/html/boost_asio/reference/execution__any_executor/any_executor/overload5.html +/doc/html/boost_asio/reference/execution__any_executor/any_executor/overload6.html +/doc/html/boost_asio/reference/execution__any_executor/context.html +/doc/html/boost_asio/reference/execution__any_executor/execute.html +/doc/html/boost_asio/reference/execution__any_executor.html +/doc/html/boost_asio/reference/execution__any_executor/operator_bool.html +/doc/html/boost_asio/reference/execution__any_executor/operator_eq_/ +/doc/html/boost_asio/reference/execution__any_executor/operator_eq__eq_/ +/doc/html/boost_asio/reference/execution__any_executor/operator_eq__eq_.html +/doc/html/boost_asio/reference/execution__any_executor/operator_eq__eq_/overload1.html +/doc/html/boost_asio/reference/execution__any_executor/operator_eq__eq_/overload2.html +/doc/html/boost_asio/reference/execution__any_executor/operator_eq__eq_/overload3.html +/doc/html/boost_asio/reference/execution__any_executor/operator_eq_.html +/doc/html/boost_asio/reference/execution__any_executor/operator_eq_/overload1.html +/doc/html/boost_asio/reference/execution__any_executor/operator_eq_/overload2.html +/doc/html/boost_asio/reference/execution__any_executor/operator_eq_/overload3.html +/doc/html/boost_asio/reference/execution__any_executor/operator_eq_/overload4.html +/doc/html/boost_asio/reference/execution__any_executor/operator_not__eq_/ +/doc/html/boost_asio/reference/execution__any_executor/operator_not__eq_.html +/doc/html/boost_asio/reference/execution__any_executor/operator_not__eq_/overload1.html +/doc/html/boost_asio/reference/execution__any_executor/operator_not__eq_/overload2.html +/doc/html/boost_asio/reference/execution__any_executor/operator_not__eq_/overload3.html +/doc/html/boost_asio/reference/execution__any_executor/prefer.html +/doc/html/boost_asio/reference/execution__any_executor/query.html +/doc/html/boost_asio/reference/execution__any_executor/require.html +/doc/html/boost_asio/reference/execution__any_executor/swap.html +/doc/html/boost_asio/reference/execution__any_executor/target/ +/doc/html/boost_asio/reference/execution__any_executor/target.html +/doc/html/boost_asio/reference/execution__any_executor/target/overload1.html +/doc/html/boost_asio/reference/execution__any_executor/target/overload2.html +/doc/html/boost_asio/reference/execution__any_executor/target_type.html +/doc/html/boost_asio/reference/execution__bad_executor/ +/doc/html/boost_asio/reference/execution__bad_executor/bad_executor.html +/doc/html/boost_asio/reference/execution__bad_executor.html +/doc/html/boost_asio/reference/execution__bad_executor/what.html +/doc/html/boost_asio/reference/execution__blocking_adaptation.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t/ +/doc/html/boost_asio/reference/execution__blocking_adaptation_t/allowed.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t__allowed_t/ +/doc/html/boost_asio/reference/execution__blocking_adaptation_t__allowed_t/allowed_t.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t__allowed_t.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t__allowed_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t__allowed_t/is_preferable.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t__allowed_t/is_requirable.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t__allowed_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t__allowed_t/value.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t/blocking_adaptation_t/ +/doc/html/boost_asio/reference/execution__blocking_adaptation_t/blocking_adaptation_t.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t/blocking_adaptation_t/overload1.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t/blocking_adaptation_t/overload2.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t/blocking_adaptation_t/overload3.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t/disallowed.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t__disallowed_t/ +/doc/html/boost_asio/reference/execution__blocking_adaptation_t__disallowed_t/disallowed_t.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t__disallowed_t.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t__disallowed_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t__disallowed_t/is_preferable.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t__disallowed_t/is_requirable.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t__disallowed_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t__disallowed_t/value.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t/is_preferable.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t/is_requirable.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t/operator_eq__eq_.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t/operator_not__eq_.html +/doc/html/boost_asio/reference/execution__blocking_adaptation_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__blocking.html +/doc/html/boost_asio/reference/execution__blocking_t/ +/doc/html/boost_asio/reference/execution__blocking_t/always.html +/doc/html/boost_asio/reference/execution__blocking_t__always_t/ +/doc/html/boost_asio/reference/execution__blocking_t__always_t/always_t.html +/doc/html/boost_asio/reference/execution__blocking_t__always_t.html +/doc/html/boost_asio/reference/execution__blocking_t__always_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__blocking_t__always_t/is_preferable.html +/doc/html/boost_asio/reference/execution__blocking_t__always_t/is_requirable.html +/doc/html/boost_asio/reference/execution__blocking_t__always_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__blocking_t__always_t/value.html +/doc/html/boost_asio/reference/execution__blocking_t/blocking_t/ +/doc/html/boost_asio/reference/execution__blocking_t/blocking_t.html +/doc/html/boost_asio/reference/execution__blocking_t/blocking_t/overload1.html +/doc/html/boost_asio/reference/execution__blocking_t/blocking_t/overload2.html +/doc/html/boost_asio/reference/execution__blocking_t/blocking_t/overload3.html +/doc/html/boost_asio/reference/execution__blocking_t/blocking_t/overload4.html +/doc/html/boost_asio/reference/execution__blocking_t.html +/doc/html/boost_asio/reference/execution__blocking_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__blocking_t/is_preferable.html +/doc/html/boost_asio/reference/execution__blocking_t/is_requirable.html +/doc/html/boost_asio/reference/execution__blocking_t/never.html +/doc/html/boost_asio/reference/execution__blocking_t__never_t/ +/doc/html/boost_asio/reference/execution__blocking_t__never_t.html +/doc/html/boost_asio/reference/execution__blocking_t__never_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__blocking_t__never_t/is_preferable.html +/doc/html/boost_asio/reference/execution__blocking_t__never_t/is_requirable.html +/doc/html/boost_asio/reference/execution__blocking_t__never_t/never_t.html +/doc/html/boost_asio/reference/execution__blocking_t__never_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__blocking_t__never_t/value.html +/doc/html/boost_asio/reference/execution__blocking_t/operator_eq__eq_.html +/doc/html/boost_asio/reference/execution__blocking_t/operator_not__eq_.html +/doc/html/boost_asio/reference/execution__blocking_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__blocking_t/possibly.html +/doc/html/boost_asio/reference/execution__blocking_t__possibly_t/ +/doc/html/boost_asio/reference/execution__blocking_t__possibly_t.html +/doc/html/boost_asio/reference/execution__blocking_t__possibly_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__blocking_t__possibly_t/is_preferable.html +/doc/html/boost_asio/reference/execution__blocking_t__possibly_t/is_requirable.html +/doc/html/boost_asio/reference/execution__blocking_t__possibly_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__blocking_t__possibly_t/possibly_t.html +/doc/html/boost_asio/reference/execution__blocking_t__possibly_t/value.html +/doc/html/boost_asio/reference/execution__bulk_execute.html +/doc/html/boost_asio/reference/execution__bulk_guarantee.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t/ +/doc/html/boost_asio/reference/execution__bulk_guarantee_t/bulk_guarantee_t/ +/doc/html/boost_asio/reference/execution__bulk_guarantee_t/bulk_guarantee_t.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t/bulk_guarantee_t/overload1.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t/bulk_guarantee_t/overload2.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t/bulk_guarantee_t/overload3.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t/bulk_guarantee_t/overload4.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t/is_preferable.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t/is_requirable.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t/operator_eq__eq_.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t/operator_not__eq_.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t/parallel.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__parallel_t/ +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__parallel_t.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__parallel_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__parallel_t/is_preferable.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__parallel_t/is_requirable.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__parallel_t/parallel_t.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__parallel_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__parallel_t/value.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t/sequenced.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__sequenced_t/ +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__sequenced_t.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__sequenced_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__sequenced_t/is_preferable.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__sequenced_t/is_requirable.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__sequenced_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__sequenced_t/sequenced_t.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__sequenced_t/value.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t/unsequenced.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__unsequenced_t/ +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__unsequenced_t.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__unsequenced_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__unsequenced_t/is_preferable.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__unsequenced_t/is_requirable.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__unsequenced_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__unsequenced_t/unsequenced_t.html +/doc/html/boost_asio/reference/execution__bulk_guarantee_t__unsequenced_t/value.html +/doc/html/boost_asio/reference/execution__can_bulk_execute.html +/doc/html/boost_asio/reference/execution__can_connect.html +/doc/html/boost_asio/reference/execution__can_execute.html +/doc/html/boost_asio/reference/execution__can_schedule.html +/doc/html/boost_asio/reference/execution__can_set_done.html +/doc/html/boost_asio/reference/execution__can_set_error.html +/doc/html/boost_asio/reference/execution__can_set_value.html +/doc/html/boost_asio/reference/execution__can_start.html +/doc/html/boost_asio/reference/execution__can_submit.html +/doc/html/boost_asio/reference/execution__connect.html +/doc/html/boost_asio/reference/execution__connect_result/ +/doc/html/boost_asio/reference/execution__connect_result.html +/doc/html/boost_asio/reference/execution__connect_result/type.html +/doc/html/boost_asio/reference/execution_context/ +/doc/html/boost_asio/reference/execution_context/add_service.html +/doc/html/boost_asio/reference/execution__context_as.html +/doc/html/boost_asio/reference/execution__context_as_t/ +/doc/html/boost_asio/reference/execution__context_as_t.html +/doc/html/boost_asio/reference/execution__context_as_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__context_as_t/is_preferable.html +/doc/html/boost_asio/reference/execution__context_as_t/is_requirable.html +/doc/html/boost_asio/reference/execution__context_as_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution_context/destroy.html +/doc/html/boost_asio/reference/execution_context/_execution_context.html +/doc/html/boost_asio/reference/execution_context/execution_context.html +/doc/html/boost_asio/reference/execution_context/fork_event.html +/doc/html/boost_asio/reference/execution_context/has_service.html +/doc/html/boost_asio/reference/ExecutionContext.html +/doc/html/boost_asio/reference/execution__context.html +/doc/html/boost_asio/reference/execution_context.html +/doc/html/boost_asio/reference/execution_context__id/ +/doc/html/boost_asio/reference/execution_context__id.html +/doc/html/boost_asio/reference/execution_context__id/id.html +/doc/html/boost_asio/reference/execution_context/make_service.html +/doc/html/boost_asio/reference/execution_context/notify_fork.html +/doc/html/boost_asio/reference/execution_context__service/ +/doc/html/boost_asio/reference/execution_context__service/context.html +/doc/html/boost_asio/reference/execution_context__service.html +/doc/html/boost_asio/reference/execution_context__service/notify_fork.html +/doc/html/boost_asio/reference/execution_context__service/_service.html +/doc/html/boost_asio/reference/execution_context__service/service.html +/doc/html/boost_asio/reference/execution_context__service/shutdown.html +/doc/html/boost_asio/reference/execution_context/shutdown.html +/doc/html/boost_asio/reference/execution__context_t/ +/doc/html/boost_asio/reference/execution__context_t.html +/doc/html/boost_asio/reference/execution__context_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__context_t/is_preferable.html +/doc/html/boost_asio/reference/execution__context_t/is_requirable.html +/doc/html/boost_asio/reference/execution__context_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution_context/use_service/ +/doc/html/boost_asio/reference/execution_context/use_service.html +/doc/html/boost_asio/reference/execution_context/use_service/overload1.html +/doc/html/boost_asio/reference/execution_context/use_service/overload2.html +/doc/html/boost_asio/reference/execution__execute.html +/doc/html/boost_asio/reference/execution__executor_index/ +/doc/html/boost_asio/reference/execution__executor_index.html +/doc/html/boost_asio/reference/execution__executor_index/type.html +/doc/html/boost_asio/reference/execution__executor_shape/ +/doc/html/boost_asio/reference/execution__executor_shape.html +/doc/html/boost_asio/reference/execution__executor_shape/type.html +/doc/html/boost_asio/reference/execution__invocable_archetype/ +/doc/html/boost_asio/reference/execution__invocable_archetype.html +/doc/html/boost_asio/reference/execution__invocable_archetype/operator_lp__rp_.html +/doc/html/boost_asio/reference/execution__is_executor.html +/doc/html/boost_asio/reference/execution__is_executor_of.html +/doc/html/boost_asio/reference/execution__is_nothrow_receiver_of.html +/doc/html/boost_asio/reference/execution__is_operation_state.html +/doc/html/boost_asio/reference/execution__is_receiver.html +/doc/html/boost_asio/reference/execution__is_receiver_of.html +/doc/html/boost_asio/reference/execution__is_scheduler.html +/doc/html/boost_asio/reference/execution__is_sender.html +/doc/html/boost_asio/reference/execution__is_sender_to.html +/doc/html/boost_asio/reference/execution__is_typed_sender.html +/doc/html/boost_asio/reference/execution__mapping.html +/doc/html/boost_asio/reference/execution__mapping_t/ +/doc/html/boost_asio/reference/execution__mapping_t.html +/doc/html/boost_asio/reference/execution__mapping_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__mapping_t/is_preferable.html +/doc/html/boost_asio/reference/execution__mapping_t/is_requirable.html +/doc/html/boost_asio/reference/execution__mapping_t/mapping_t/ +/doc/html/boost_asio/reference/execution__mapping_t/mapping_t.html +/doc/html/boost_asio/reference/execution__mapping_t/mapping_t/overload1.html +/doc/html/boost_asio/reference/execution__mapping_t/mapping_t/overload2.html +/doc/html/boost_asio/reference/execution__mapping_t/mapping_t/overload3.html +/doc/html/boost_asio/reference/execution__mapping_t/mapping_t/overload4.html +/doc/html/boost_asio/reference/execution__mapping_t/new_thread.html +/doc/html/boost_asio/reference/execution__mapping_t__new_thread_t/ +/doc/html/boost_asio/reference/execution__mapping_t__new_thread_t.html +/doc/html/boost_asio/reference/execution__mapping_t__new_thread_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__mapping_t__new_thread_t/is_preferable.html +/doc/html/boost_asio/reference/execution__mapping_t__new_thread_t/is_requirable.html +/doc/html/boost_asio/reference/execution__mapping_t__new_thread_t/new_thread_t.html +/doc/html/boost_asio/reference/execution__mapping_t__new_thread_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__mapping_t__new_thread_t/value.html +/doc/html/boost_asio/reference/execution__mapping_t/operator_eq__eq_.html +/doc/html/boost_asio/reference/execution__mapping_t/operator_not__eq_.html +/doc/html/boost_asio/reference/execution__mapping_t/other.html +/doc/html/boost_asio/reference/execution__mapping_t__other_t/ +/doc/html/boost_asio/reference/execution__mapping_t__other_t.html +/doc/html/boost_asio/reference/execution__mapping_t__other_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__mapping_t__other_t/is_preferable.html +/doc/html/boost_asio/reference/execution__mapping_t__other_t/is_requirable.html +/doc/html/boost_asio/reference/execution__mapping_t__other_t/other_t.html +/doc/html/boost_asio/reference/execution__mapping_t__other_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__mapping_t__other_t/value.html +/doc/html/boost_asio/reference/execution__mapping_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__mapping_t/thread.html +/doc/html/boost_asio/reference/execution__mapping_t__thread_t/ +/doc/html/boost_asio/reference/execution__mapping_t__thread_t.html +/doc/html/boost_asio/reference/execution__mapping_t__thread_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__mapping_t__thread_t/is_preferable.html +/doc/html/boost_asio/reference/execution__mapping_t__thread_t/is_requirable.html +/doc/html/boost_asio/reference/execution__mapping_t__thread_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__mapping_t__thread_t/thread_t.html +/doc/html/boost_asio/reference/execution__mapping_t__thread_t/value.html +/doc/html/boost_asio/reference/execution__occupancy.html +/doc/html/boost_asio/reference/execution__occupancy_t/ +/doc/html/boost_asio/reference/execution__occupancy_t.html +/doc/html/boost_asio/reference/execution__occupancy_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__occupancy_t/is_preferable.html +/doc/html/boost_asio/reference/execution__occupancy_t/is_requirable.html +/doc/html/boost_asio/reference/execution__occupancy_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__outstanding_work.html +/doc/html/boost_asio/reference/execution__outstanding_work_t/ +/doc/html/boost_asio/reference/execution__outstanding_work_t.html +/doc/html/boost_asio/reference/execution__outstanding_work_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__outstanding_work_t/is_preferable.html +/doc/html/boost_asio/reference/execution__outstanding_work_t/is_requirable.html +/doc/html/boost_asio/reference/execution__outstanding_work_t/operator_eq__eq_.html +/doc/html/boost_asio/reference/execution__outstanding_work_t/operator_not__eq_.html +/doc/html/boost_asio/reference/execution__outstanding_work_t/outstanding_work_t/ +/doc/html/boost_asio/reference/execution__outstanding_work_t/outstanding_work_t.html +/doc/html/boost_asio/reference/execution__outstanding_work_t/outstanding_work_t/overload1.html +/doc/html/boost_asio/reference/execution__outstanding_work_t/outstanding_work_t/overload2.html +/doc/html/boost_asio/reference/execution__outstanding_work_t/outstanding_work_t/overload3.html +/doc/html/boost_asio/reference/execution__outstanding_work_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__outstanding_work_t/tracked.html +/doc/html/boost_asio/reference/execution__outstanding_work_t__tracked_t/ +/doc/html/boost_asio/reference/execution__outstanding_work_t__tracked_t.html +/doc/html/boost_asio/reference/execution__outstanding_work_t__tracked_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__outstanding_work_t__tracked_t/is_preferable.html +/doc/html/boost_asio/reference/execution__outstanding_work_t__tracked_t/is_requirable.html +/doc/html/boost_asio/reference/execution__outstanding_work_t__tracked_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__outstanding_work_t__tracked_t/tracked_t.html +/doc/html/boost_asio/reference/execution__outstanding_work_t__tracked_t/value.html +/doc/html/boost_asio/reference/execution__outstanding_work_t/untracked.html +/doc/html/boost_asio/reference/execution__outstanding_work_t__untracked_t/ +/doc/html/boost_asio/reference/execution__outstanding_work_t__untracked_t.html +/doc/html/boost_asio/reference/execution__outstanding_work_t__untracked_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__outstanding_work_t__untracked_t/is_preferable.html +/doc/html/boost_asio/reference/execution__outstanding_work_t__untracked_t/is_requirable.html +/doc/html/boost_asio/reference/execution__outstanding_work_t__untracked_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__outstanding_work_t__untracked_t/untracked_t.html +/doc/html/boost_asio/reference/execution__outstanding_work_t__untracked_t/value.html +/doc/html/boost_asio/reference/execution__prefer_only/ +/doc/html/boost_asio/reference/execution__prefer_only.html +/doc/html/boost_asio/reference/execution__prefer_only/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__prefer_only/is_preferable.html +/doc/html/boost_asio/reference/execution__prefer_only/is_requirable.html +/doc/html/boost_asio/reference/execution__prefer_only/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__receiver_invocation_error/ +/doc/html/boost_asio/reference/execution__receiver_invocation_error.html +/doc/html/boost_asio/reference/execution__receiver_invocation_error/receiver_invocation_error.html +/doc/html/boost_asio/reference/execution__relationship.html +/doc/html/boost_asio/reference/execution__relationship_t/ +/doc/html/boost_asio/reference/execution__relationship_t/continuation.html +/doc/html/boost_asio/reference/execution__relationship_t__continuation_t/ +/doc/html/boost_asio/reference/execution__relationship_t__continuation_t/continuation_t.html +/doc/html/boost_asio/reference/execution__relationship_t__continuation_t.html +/doc/html/boost_asio/reference/execution__relationship_t__continuation_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__relationship_t__continuation_t/is_preferable.html +/doc/html/boost_asio/reference/execution__relationship_t__continuation_t/is_requirable.html +/doc/html/boost_asio/reference/execution__relationship_t__continuation_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__relationship_t__continuation_t/value.html +/doc/html/boost_asio/reference/execution__relationship_t/fork.html +/doc/html/boost_asio/reference/execution__relationship_t__fork_t/ +/doc/html/boost_asio/reference/execution__relationship_t__fork_t/fork_t.html +/doc/html/boost_asio/reference/execution__relationship_t__fork_t.html +/doc/html/boost_asio/reference/execution__relationship_t__fork_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__relationship_t__fork_t/is_preferable.html +/doc/html/boost_asio/reference/execution__relationship_t__fork_t/is_requirable.html +/doc/html/boost_asio/reference/execution__relationship_t__fork_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__relationship_t__fork_t/value.html +/doc/html/boost_asio/reference/execution__relationship_t.html +/doc/html/boost_asio/reference/execution__relationship_t/is_applicable_property_v.html +/doc/html/boost_asio/reference/execution__relationship_t/is_preferable.html +/doc/html/boost_asio/reference/execution__relationship_t/is_requirable.html +/doc/html/boost_asio/reference/execution__relationship_t/operator_eq__eq_.html +/doc/html/boost_asio/reference/execution__relationship_t/operator_not__eq_.html +/doc/html/boost_asio/reference/execution__relationship_t/polymorphic_query_result_type.html +/doc/html/boost_asio/reference/execution__relationship_t/relationship_t/ +/doc/html/boost_asio/reference/execution__relationship_t/relationship_t.html +/doc/html/boost_asio/reference/execution__relationship_t/relationship_t/overload1.html +/doc/html/boost_asio/reference/execution__relationship_t/relationship_t/overload2.html +/doc/html/boost_asio/reference/execution__relationship_t/relationship_t/overload3.html +/doc/html/boost_asio/reference/execution__schedule.html +/doc/html/boost_asio/reference/execution__sender_base.html +/doc/html/boost_asio/reference/execution__sender_traits.html +/doc/html/boost_asio/reference/execution__set_done.html +/doc/html/boost_asio/reference/execution__set_error.html +/doc/html/boost_asio/reference/execution__set_value.html +/doc/html/boost_asio/reference/execution__start.html +/doc/html/boost_asio/reference/execution__submit.html +/doc/html/boost_asio/reference/executor/ +/doc/html/boost_asio/reference/Executor1.html +/doc/html/boost_asio/reference/executor_arg.html +/doc/html/boost_asio/reference/executor_arg_t/ +/doc/html/boost_asio/reference/executor_arg_t/executor_arg_t.html +/doc/html/boost_asio/reference/executor_arg_t.html +/doc/html/boost_asio/reference/executor_binder/ +/doc/html/boost_asio/reference/executor_binder/argument_type.html +/doc/html/boost_asio/reference/executor_binder/executor_binder/ +/doc/html/boost_asio/reference/executor_binder/_executor_binder.html +/doc/html/boost_asio/reference/executor_binder/executor_binder.html +/doc/html/boost_asio/reference/executor_binder/executor_binder/overload1.html +/doc/html/boost_asio/reference/executor_binder/executor_binder/overload2.html +/doc/html/boost_asio/reference/executor_binder/executor_binder/overload3.html +/doc/html/boost_asio/reference/executor_binder/executor_binder/overload4.html +/doc/html/boost_asio/reference/executor_binder/executor_binder/overload5.html +/doc/html/boost_asio/reference/executor_binder/executor_binder/overload6.html +/doc/html/boost_asio/reference/executor_binder/executor_binder/overload7.html +/doc/html/boost_asio/reference/executor_binder/executor_binder/overload8.html +/doc/html/boost_asio/reference/executor_binder/executor_binder/overload9.html +/doc/html/boost_asio/reference/executor_binder/executor_type.html +/doc/html/boost_asio/reference/executor_binder/first_argument_type.html +/doc/html/boost_asio/reference/executor_binder/get/ +/doc/html/boost_asio/reference/executor_binder/get_executor.html +/doc/html/boost_asio/reference/executor_binder/get.html +/doc/html/boost_asio/reference/executor_binder/get/overload1.html +/doc/html/boost_asio/reference/executor_binder/get/overload2.html +/doc/html/boost_asio/reference/executor_binder.html +/doc/html/boost_asio/reference/executor_binder/operator_lp__rp_/ +/doc/html/boost_asio/reference/executor_binder/operator_lp__rp_.html +/doc/html/boost_asio/reference/executor_binder/operator_lp__rp_/overload1.html +/doc/html/boost_asio/reference/executor_binder/operator_lp__rp_/overload2.html +/doc/html/boost_asio/reference/executor_binder/result_type.html +/doc/html/boost_asio/reference/executor_binder/second_argument_type.html +/doc/html/boost_asio/reference/executor_binder/target_type.html +/doc/html/boost_asio/reference/executor/context.html +/doc/html/boost_asio/reference/executor/defer.html +/doc/html/boost_asio/reference/executor/dispatch.html +/doc/html/boost_asio/reference/executor/executor/ +/doc/html/boost_asio/reference/executor/_executor.html +/doc/html/boost_asio/reference/executor/executor.html +/doc/html/boost_asio/reference/executor/executor/overload1.html +/doc/html/boost_asio/reference/executor/executor/overload2.html +/doc/html/boost_asio/reference/executor/executor/overload3.html +/doc/html/boost_asio/reference/executor/executor/overload4.html +/doc/html/boost_asio/reference/executor/executor/overload5.html +/doc/html/boost_asio/reference/executor/executor/overload6.html +/doc/html/boost_asio/reference/executor.html +/doc/html/boost_asio/reference/executor/on_work_finished.html +/doc/html/boost_asio/reference/executor/on_work_started.html +/doc/html/boost_asio/reference/executor/operator_eq_/ +/doc/html/boost_asio/reference/executor/operator_eq__eq_.html +/doc/html/boost_asio/reference/executor/operator_eq_.html +/doc/html/boost_asio/reference/executor/operator_eq_/overload1.html +/doc/html/boost_asio/reference/executor/operator_eq_/overload2.html +/doc/html/boost_asio/reference/executor/operator_eq_/overload3.html +/doc/html/boost_asio/reference/executor/operator_eq_/overload4.html +/doc/html/boost_asio/reference/executor/operator_not__eq_.html +/doc/html/boost_asio/reference/executor/operator_unspecified_bool_type.html +/doc/html/boost_asio/reference/executor/post.html +/doc/html/boost_asio/reference/executor/target/ +/doc/html/boost_asio/reference/executor/target.html +/doc/html/boost_asio/reference/executor/target/overload1.html +/doc/html/boost_asio/reference/executor/target/overload2.html +/doc/html/boost_asio/reference/executor/target_type.html +/doc/html/boost_asio/reference/executor/unspecified_bool_true.html +/doc/html/boost_asio/reference/executor/unspecified_bool_type.html +/doc/html/boost_asio/reference/executor__unspecified_bool_type_t.html +/doc/html/boost_asio/reference/executor_work_guard/ +/doc/html/boost_asio/reference/executor_work_guard/executor_type.html +/doc/html/boost_asio/reference/executor_work_guard/executor_work_guard/ +/doc/html/boost_asio/reference/executor_work_guard/_executor_work_guard.html +/doc/html/boost_asio/reference/executor_work_guard/executor_work_guard.html +/doc/html/boost_asio/reference/executor_work_guard/executor_work_guard/overload1.html +/doc/html/boost_asio/reference/executor_work_guard/executor_work_guard/overload2.html +/doc/html/boost_asio/reference/executor_work_guard/executor_work_guard/overload3.html +/doc/html/boost_asio/reference/executor_work_guard/get_executor.html +/doc/html/boost_asio/reference/executor_work_guard.html +/doc/html/boost_asio/reference/executor_work_guard/owns_work.html +/doc/html/boost_asio/reference/executor_work_guard/reset.html +/doc/html/boost_asio/reference/generic__basic_endpoint/ +/doc/html/boost_asio/reference/generic__basic_endpoint/basic_endpoint/ +/doc/html/boost_asio/reference/generic__basic_endpoint/basic_endpoint.html +/doc/html/boost_asio/reference/generic__basic_endpoint/basic_endpoint/overload1.html +/doc/html/boost_asio/reference/generic__basic_endpoint/basic_endpoint/overload2.html +/doc/html/boost_asio/reference/generic__basic_endpoint/basic_endpoint/overload3.html +/doc/html/boost_asio/reference/generic__basic_endpoint/basic_endpoint/overload4.html +/doc/html/boost_asio/reference/generic__basic_endpoint/capacity.html +/doc/html/boost_asio/reference/generic__basic_endpoint/data/ +/doc/html/boost_asio/reference/generic__basic_endpoint/data.html +/doc/html/boost_asio/reference/generic__basic_endpoint/data/overload1.html +/doc/html/boost_asio/reference/generic__basic_endpoint/data/overload2.html +/doc/html/boost_asio/reference/generic__basic_endpoint/data_type.html +/doc/html/boost_asio/reference/generic__basic_endpoint.html +/doc/html/boost_asio/reference/generic__basic_endpoint/operator_eq__eq_.html +/doc/html/boost_asio/reference/generic__basic_endpoint/operator_eq_.html +/doc/html/boost_asio/reference/generic__basic_endpoint/operator_gt__eq_.html +/doc/html/boost_asio/reference/generic__basic_endpoint/operator_gt_.html +/doc/html/boost_asio/reference/generic__basic_endpoint/operator_lt__eq_.html +/doc/html/boost_asio/reference/generic__basic_endpoint/operator_lt_.html +/doc/html/boost_asio/reference/generic__basic_endpoint/operator_not__eq_.html +/doc/html/boost_asio/reference/generic__basic_endpoint/protocol.html +/doc/html/boost_asio/reference/generic__basic_endpoint/protocol_type.html +/doc/html/boost_asio/reference/generic__basic_endpoint/resize.html +/doc/html/boost_asio/reference/generic__basic_endpoint/size.html +/doc/html/boost_asio/reference/generic__datagram_protocol/ +/doc/html/boost_asio/reference/generic__datagram_protocol/datagram_protocol/ +/doc/html/boost_asio/reference/generic__datagram_protocol/datagram_protocol.html +/doc/html/boost_asio/reference/generic__datagram_protocol/datagram_protocol/overload1.html +/doc/html/boost_asio/reference/generic__datagram_protocol/datagram_protocol/overload2.html +/doc/html/boost_asio/reference/generic__datagram_protocol/endpoint.html +/doc/html/boost_asio/reference/generic__datagram_protocol/family.html +/doc/html/boost_asio/reference/generic__datagram_protocol.html +/doc/html/boost_asio/reference/generic__datagram_protocol/operator_eq__eq_.html +/doc/html/boost_asio/reference/generic__datagram_protocol/operator_not__eq_.html +/doc/html/boost_asio/reference/generic__datagram_protocol/protocol.html +/doc/html/boost_asio/reference/generic__datagram_protocol/socket.html +/doc/html/boost_asio/reference/generic__datagram_protocol/type.html +/doc/html/boost_asio/reference/generic__raw_protocol/ +/doc/html/boost_asio/reference/generic__raw_protocol/endpoint.html +/doc/html/boost_asio/reference/generic__raw_protocol/family.html +/doc/html/boost_asio/reference/generic__raw_protocol.html +/doc/html/boost_asio/reference/generic__raw_protocol/operator_eq__eq_.html +/doc/html/boost_asio/reference/generic__raw_protocol/operator_not__eq_.html +/doc/html/boost_asio/reference/generic__raw_protocol/protocol.html +/doc/html/boost_asio/reference/generic__raw_protocol/raw_protocol/ +/doc/html/boost_asio/reference/generic__raw_protocol/raw_protocol.html +/doc/html/boost_asio/reference/generic__raw_protocol/raw_protocol/overload1.html +/doc/html/boost_asio/reference/generic__raw_protocol/raw_protocol/overload2.html +/doc/html/boost_asio/reference/generic__raw_protocol/socket.html +/doc/html/boost_asio/reference/generic__raw_protocol/type.html +/doc/html/boost_asio/reference/generic__seq_packet_protocol/ +/doc/html/boost_asio/reference/generic__seq_packet_protocol/endpoint.html +/doc/html/boost_asio/reference/generic__seq_packet_protocol/family.html +/doc/html/boost_asio/reference/generic__seq_packet_protocol.html +/doc/html/boost_asio/reference/generic__seq_packet_protocol/operator_eq__eq_.html +/doc/html/boost_asio/reference/generic__seq_packet_protocol/operator_not__eq_.html +/doc/html/boost_asio/reference/generic__seq_packet_protocol/protocol.html +/doc/html/boost_asio/reference/generic__seq_packet_protocol/seq_packet_protocol/ +/doc/html/boost_asio/reference/generic__seq_packet_protocol/seq_packet_protocol.html +/doc/html/boost_asio/reference/generic__seq_packet_protocol/seq_packet_protocol/overload1.html +/doc/html/boost_asio/reference/generic__seq_packet_protocol/seq_packet_protocol/overload2.html +/doc/html/boost_asio/reference/generic__seq_packet_protocol/socket.html +/doc/html/boost_asio/reference/generic__seq_packet_protocol/type.html +/doc/html/boost_asio/reference/generic__stream_protocol/ +/doc/html/boost_asio/reference/generic__stream_protocol/endpoint.html +/doc/html/boost_asio/reference/generic__stream_protocol/family.html +/doc/html/boost_asio/reference/generic__stream_protocol.html +/doc/html/boost_asio/reference/generic__stream_protocol/iostream.html +/doc/html/boost_asio/reference/generic__stream_protocol/operator_eq__eq_.html +/doc/html/boost_asio/reference/generic__stream_protocol/operator_not__eq_.html +/doc/html/boost_asio/reference/generic__stream_protocol/protocol.html +/doc/html/boost_asio/reference/generic__stream_protocol/socket.html +/doc/html/boost_asio/reference/generic__stream_protocol/stream_protocol/ +/doc/html/boost_asio/reference/generic__stream_protocol/stream_protocol.html +/doc/html/boost_asio/reference/generic__stream_protocol/stream_protocol/overload1.html +/doc/html/boost_asio/reference/generic__stream_protocol/stream_protocol/overload2.html +/doc/html/boost_asio/reference/generic__stream_protocol/type.html +/doc/html/boost_asio/reference/get_associated_allocator/ +/doc/html/boost_asio/reference/get_associated_allocator.html +/doc/html/boost_asio/reference/get_associated_allocator/overload1.html +/doc/html/boost_asio/reference/get_associated_allocator/overload2.html +/doc/html/boost_asio/reference/get_associated_executor/ +/doc/html/boost_asio/reference/get_associated_executor.html +/doc/html/boost_asio/reference/get_associated_executor/overload1.html +/doc/html/boost_asio/reference/get_associated_executor/overload2.html +/doc/html/boost_asio/reference/get_associated_executor/overload3.html +/doc/html/boost_asio/reference/GettableSerialPortOption.html +/doc/html/boost_asio/reference/GettableSocketOption.html +/doc/html/boost_asio/reference/Handler.html +/doc/html/boost_asio/reference/HandshakeHandler.html +/doc/html/boost_asio/reference/high_resolution_timer.html +/doc/html/boost_asio/reference.html +/doc/html/boost_asio/reference/InternetProtocol.html +/doc/html/boost_asio/reference/invalid_service_owner/ +/doc/html/boost_asio/reference/invalid_service_owner.html +/doc/html/boost_asio/reference/invalid_service_owner/invalid_service_owner.html +/doc/html/boost_asio/reference/io_context/ +/doc/html/boost_asio/reference/io_context/add_service.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/ +/doc/html/boost_asio/reference/io_context__basic_executor_type/basic_executor_type/ +/doc/html/boost_asio/reference/io_context__basic_executor_type/_basic_executor_type.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/basic_executor_type.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/basic_executor_type/overload1.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/basic_executor_type/overload2.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/context.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/defer.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/dispatch.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/execute.html +/doc/html/boost_asio/reference/io_context__basic_executor_type.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/on_work_finished.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/on_work_started.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/operator_eq_/ +/doc/html/boost_asio/reference/io_context__basic_executor_type/operator_eq__eq_.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/operator_eq_.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/operator_eq_/overload1.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/operator_eq_/overload2.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/operator_not__eq_.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/post.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/query/ +/doc/html/boost_asio/reference/io_context__basic_executor_type/query.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/query/overload1.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/query/overload2.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/query/overload3.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/query/overload4.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/query/overload5.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/query__static/ +/doc/html/boost_asio/reference/io_context__basic_executor_type/query__static.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/query__static/overload1.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/query__static/overload2.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/require/ +/doc/html/boost_asio/reference/io_context__basic_executor_type/require.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/require/overload1.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/require/overload2.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/require/overload3.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/require/overload4.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/require/overload5.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/require/overload6.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/require/overload7.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/require/overload8.html +/doc/html/boost_asio/reference/io_context__basic_executor_type/running_in_this_thread.html +/doc/html/boost_asio/reference/io_context/count_type.html +/doc/html/boost_asio/reference/io_context/destroy.html +/doc/html/boost_asio/reference/io_context/dispatch.html +/doc/html/boost_asio/reference/io_context/executor_type.html +/doc/html/boost_asio/reference/io_context/fork_event.html +/doc/html/boost_asio/reference/io_context/get_executor.html +/doc/html/boost_asio/reference/io_context/has_service.html +/doc/html/boost_asio/reference/io_context.html +/doc/html/boost_asio/reference/io_context/io_context/ +/doc/html/boost_asio/reference/io_context/_io_context.html +/doc/html/boost_asio/reference/io_context/io_context.html +/doc/html/boost_asio/reference/io_context/io_context/overload1.html +/doc/html/boost_asio/reference/io_context/io_context/overload2.html +/doc/html/boost_asio/reference/io_context/make_service.html +/doc/html/boost_asio/reference/io_context/notify_fork.html +/doc/html/boost_asio/reference/io_context/poll/ +/doc/html/boost_asio/reference/io_context/poll.html +/doc/html/boost_asio/reference/io_context/poll_one/ +/doc/html/boost_asio/reference/io_context/poll_one.html +/doc/html/boost_asio/reference/io_context/poll_one/overload1.html +/doc/html/boost_asio/reference/io_context/poll_one/overload2.html +/doc/html/boost_asio/reference/io_context/poll/overload1.html +/doc/html/boost_asio/reference/io_context/poll/overload2.html +/doc/html/boost_asio/reference/io_context/post.html +/doc/html/boost_asio/reference/io_context/reset.html +/doc/html/boost_asio/reference/io_context/restart.html +/doc/html/boost_asio/reference/io_context/run/ +/doc/html/boost_asio/reference/io_context/run_for.html +/doc/html/boost_asio/reference/io_context/run.html +/doc/html/boost_asio/reference/io_context/run_one/ +/doc/html/boost_asio/reference/io_context/run_one_for.html +/doc/html/boost_asio/reference/io_context/run_one.html +/doc/html/boost_asio/reference/io_context/run_one/overload1.html +/doc/html/boost_asio/reference/io_context/run_one/overload2.html +/doc/html/boost_asio/reference/io_context/run_one_until.html +/doc/html/boost_asio/reference/io_context/run/overload1.html +/doc/html/boost_asio/reference/io_context/run/overload2.html +/doc/html/boost_asio/reference/io_context/run_until.html +/doc/html/boost_asio/reference/io_context__service/ +/doc/html/boost_asio/reference/io_context__service/get_io_context.html +/doc/html/boost_asio/reference/io_context__service.html +/doc/html/boost_asio/reference/io_context__service/_service.html +/doc/html/boost_asio/reference/io_context__service/service.html +/doc/html/boost_asio/reference/io_context/shutdown.html +/doc/html/boost_asio/reference/io_context/stop.html +/doc/html/boost_asio/reference/io_context/stopped.html +/doc/html/boost_asio/reference/io_context__strand/ +/doc/html/boost_asio/reference/io_context__strand/context.html +/doc/html/boost_asio/reference/io_context__strand/defer.html +/doc/html/boost_asio/reference/io_context__strand/dispatch/ +/doc/html/boost_asio/reference/io_context__strand/dispatch.html +/doc/html/boost_asio/reference/io_context__strand/dispatch/overload1.html +/doc/html/boost_asio/reference/io_context__strand/dispatch/overload2.html +/doc/html/boost_asio/reference/io_context__strand.html +/doc/html/boost_asio/reference/io_context__strand/on_work_finished.html +/doc/html/boost_asio/reference/io_context__strand/on_work_started.html +/doc/html/boost_asio/reference/io_context__strand/operator_eq__eq_.html +/doc/html/boost_asio/reference/io_context__strand/operator_not__eq_.html +/doc/html/boost_asio/reference/io_context__strand/post/ +/doc/html/boost_asio/reference/io_context__strand/post.html +/doc/html/boost_asio/reference/io_context__strand/post/overload1.html +/doc/html/boost_asio/reference/io_context__strand/post/overload2.html +/doc/html/boost_asio/reference/io_context__strand/running_in_this_thread.html +/doc/html/boost_asio/reference/io_context__strand/_strand.html +/doc/html/boost_asio/reference/io_context__strand/strand.html +/doc/html/boost_asio/reference/io_context__strand/wrap.html +/doc/html/boost_asio/reference/io_context/use_service/ +/doc/html/boost_asio/reference/io_context/use_service.html +/doc/html/boost_asio/reference/io_context/use_service/overload1.html +/doc/html/boost_asio/reference/io_context/use_service/overload2.html +/doc/html/boost_asio/reference/io_context__work/ +/doc/html/boost_asio/reference/io_context__work/get_io_context.html +/doc/html/boost_asio/reference/io_context__work.html +/doc/html/boost_asio/reference/io_context__work/work/ +/doc/html/boost_asio/reference/io_context__work/_work.html +/doc/html/boost_asio/reference/io_context__work/work.html +/doc/html/boost_asio/reference/io_context__work/work/overload1.html +/doc/html/boost_asio/reference/io_context__work/work/overload2.html +/doc/html/boost_asio/reference/io_context/wrap.html +/doc/html/boost_asio/reference/IoControlCommand.html +/doc/html/boost_asio/reference/IoObjectService.html +/doc/html/boost_asio/reference/io_service.html +/doc/html/boost_asio/reference/ip__address/ +/doc/html/boost_asio/reference/ip__address/address/ +/doc/html/boost_asio/reference/ip__address/address.html +/doc/html/boost_asio/reference/ip__address/address/overload1.html +/doc/html/boost_asio/reference/ip__address/address/overload2.html +/doc/html/boost_asio/reference/ip__address/address/overload3.html +/doc/html/boost_asio/reference/ip__address/address/overload4.html +/doc/html/boost_asio/reference/ip__address/from_string/ +/doc/html/boost_asio/reference/ip__address/from_string.html +/doc/html/boost_asio/reference/ip__address/from_string/overload1.html +/doc/html/boost_asio/reference/ip__address/from_string/overload2.html +/doc/html/boost_asio/reference/ip__address/from_string/overload3.html +/doc/html/boost_asio/reference/ip__address/from_string/overload4.html +/doc/html/boost_asio/reference/ip__address.html +/doc/html/boost_asio/reference/ip__address/is_loopback.html +/doc/html/boost_asio/reference/ip__address/is_multicast.html +/doc/html/boost_asio/reference/ip__address/is_unspecified.html +/doc/html/boost_asio/reference/ip__address/is_v4.html +/doc/html/boost_asio/reference/ip__address/is_v6.html +/doc/html/boost_asio/reference/ip__address/make_address/ +/doc/html/boost_asio/reference/ip__address/make_address.html +/doc/html/boost_asio/reference/ip__address/make_address/overload1.html +/doc/html/boost_asio/reference/ip__address/make_address/overload2.html +/doc/html/boost_asio/reference/ip__address/make_address/overload3.html +/doc/html/boost_asio/reference/ip__address/make_address/overload4.html +/doc/html/boost_asio/reference/ip__address/make_address/overload5.html +/doc/html/boost_asio/reference/ip__address/make_address/overload6.html +/doc/html/boost_asio/reference/ip__address/operator_eq_/ +/doc/html/boost_asio/reference/ip__address/operator_eq__eq_.html +/doc/html/boost_asio/reference/ip__address/operator_eq_.html +/doc/html/boost_asio/reference/ip__address/operator_eq_/overload1.html +/doc/html/boost_asio/reference/ip__address/operator_eq_/overload2.html +/doc/html/boost_asio/reference/ip__address/operator_eq_/overload3.html +/doc/html/boost_asio/reference/ip__address/operator_gt__eq_.html +/doc/html/boost_asio/reference/ip__address/operator_gt_.html +/doc/html/boost_asio/reference/ip__address/operator_lt__eq_.html +/doc/html/boost_asio/reference/ip__address/operator_lt_.html +/doc/html/boost_asio/reference/ip__address/operator_lt__lt_.html +/doc/html/boost_asio/reference/ip__address/operator_not__eq_.html +/doc/html/boost_asio/reference/ip__address/to_string/ +/doc/html/boost_asio/reference/ip__address/to_string.html +/doc/html/boost_asio/reference/ip__address/to_string/overload1.html +/doc/html/boost_asio/reference/ip__address/to_string/overload2.html +/doc/html/boost_asio/reference/ip__address/to_v4.html +/doc/html/boost_asio/reference/ip__address/to_v6.html +/doc/html/boost_asio/reference/ip__address_v4/ +/doc/html/boost_asio/reference/ip__address_v4/address_v4/ +/doc/html/boost_asio/reference/ip__address_v4/address_v4.html +/doc/html/boost_asio/reference/ip__address_v4/address_v4/overload1.html +/doc/html/boost_asio/reference/ip__address_v4/address_v4/overload2.html +/doc/html/boost_asio/reference/ip__address_v4/address_v4/overload3.html +/doc/html/boost_asio/reference/ip__address_v4/address_v4/overload4.html +/doc/html/boost_asio/reference/ip__address_v4/any.html +/doc/html/boost_asio/reference/ip__address_v4/broadcast/ +/doc/html/boost_asio/reference/ip__address_v4/broadcast.html +/doc/html/boost_asio/reference/ip__address_v4/broadcast/overload1.html +/doc/html/boost_asio/reference/ip__address_v4/broadcast/overload2.html +/doc/html/boost_asio/reference/ip__address_v4/bytes_type.html +/doc/html/boost_asio/reference/ip__address_v4/from_string/ +/doc/html/boost_asio/reference/ip__address_v4/from_string.html +/doc/html/boost_asio/reference/ip__address_v4/from_string/overload1.html +/doc/html/boost_asio/reference/ip__address_v4/from_string/overload2.html +/doc/html/boost_asio/reference/ip__address_v4/from_string/overload3.html +/doc/html/boost_asio/reference/ip__address_v4/from_string/overload4.html +/doc/html/boost_asio/reference/ip__address_v4.html +/doc/html/boost_asio/reference/ip__address_v4/is_class_a.html +/doc/html/boost_asio/reference/ip__address_v4/is_class_b.html +/doc/html/boost_asio/reference/ip__address_v4/is_class_c.html +/doc/html/boost_asio/reference/ip__address_v4/is_loopback.html +/doc/html/boost_asio/reference/ip__address_v4/is_multicast.html +/doc/html/boost_asio/reference/ip__address_v4/is_unspecified.html +/doc/html/boost_asio/reference/ip__address_v4_iterator.html +/doc/html/boost_asio/reference/ip__address_v4/loopback.html +/doc/html/boost_asio/reference/ip__address_v4/make_address_v4/ +/doc/html/boost_asio/reference/ip__address_v4/make_address_v4.html +/doc/html/boost_asio/reference/ip__address_v4/make_address_v4/overload1.html +/doc/html/boost_asio/reference/ip__address_v4/make_address_v4/overload2.html +/doc/html/boost_asio/reference/ip__address_v4/make_address_v4/overload3.html +/doc/html/boost_asio/reference/ip__address_v4/make_address_v4/overload4.html +/doc/html/boost_asio/reference/ip__address_v4/make_address_v4/overload5.html +/doc/html/boost_asio/reference/ip__address_v4/make_address_v4/overload6.html +/doc/html/boost_asio/reference/ip__address_v4/make_address_v4/overload7.html +/doc/html/boost_asio/reference/ip__address_v4/make_address_v4/overload8.html +/doc/html/boost_asio/reference/ip__address_v4/make_address_v4/overload9.html +/doc/html/boost_asio/reference/ip__address_v4/make_network_v4/ +/doc/html/boost_asio/reference/ip__address_v4/make_network_v4.html +/doc/html/boost_asio/reference/ip__address_v4/make_network_v4/overload1.html +/doc/html/boost_asio/reference/ip__address_v4/make_network_v4/overload2.html +/doc/html/boost_asio/reference/ip__address_v4/netmask.html +/doc/html/boost_asio/reference/ip__address_v4/operator_eq__eq_.html +/doc/html/boost_asio/reference/ip__address_v4/operator_eq_.html +/doc/html/boost_asio/reference/ip__address_v4/operator_gt__eq_.html +/doc/html/boost_asio/reference/ip__address_v4/operator_gt_.html +/doc/html/boost_asio/reference/ip__address_v4/operator_lt__eq_.html +/doc/html/boost_asio/reference/ip__address_v4/operator_lt_.html +/doc/html/boost_asio/reference/ip__address_v4/operator_lt__lt_/ +/doc/html/boost_asio/reference/ip__address_v4/operator_lt__lt_.html +/doc/html/boost_asio/reference/ip__address_v4/operator_lt__lt_/overload1.html +/doc/html/boost_asio/reference/ip__address_v4/operator_lt__lt_/overload2.html +/doc/html/boost_asio/reference/ip__address_v4/operator_not__eq_.html +/doc/html/boost_asio/reference/ip__address_v4_range.html +/doc/html/boost_asio/reference/ip__address_v4/to_bytes.html +/doc/html/boost_asio/reference/ip__address_v4/to_string/ +/doc/html/boost_asio/reference/ip__address_v4/to_string.html +/doc/html/boost_asio/reference/ip__address_v4/to_string/overload1.html +/doc/html/boost_asio/reference/ip__address_v4/to_string/overload2.html +/doc/html/boost_asio/reference/ip__address_v4/to_uint.html +/doc/html/boost_asio/reference/ip__address_v4/to_ulong.html +/doc/html/boost_asio/reference/ip__address_v4/uint_type.html +/doc/html/boost_asio/reference/ip__address_v6/ +/doc/html/boost_asio/reference/ip__address_v6/address_v6/ +/doc/html/boost_asio/reference/ip__address_v6/address_v6.html +/doc/html/boost_asio/reference/ip__address_v6/address_v6/overload1.html +/doc/html/boost_asio/reference/ip__address_v6/address_v6/overload2.html +/doc/html/boost_asio/reference/ip__address_v6/address_v6/overload3.html +/doc/html/boost_asio/reference/ip__address_v6/any.html +/doc/html/boost_asio/reference/ip__address_v6/bytes_type.html +/doc/html/boost_asio/reference/ip__address_v6/from_string/ +/doc/html/boost_asio/reference/ip__address_v6/from_string.html +/doc/html/boost_asio/reference/ip__address_v6/from_string/overload1.html +/doc/html/boost_asio/reference/ip__address_v6/from_string/overload2.html +/doc/html/boost_asio/reference/ip__address_v6/from_string/overload3.html +/doc/html/boost_asio/reference/ip__address_v6/from_string/overload4.html +/doc/html/boost_asio/reference/ip__address_v6.html +/doc/html/boost_asio/reference/ip__address_v6/is_link_local.html +/doc/html/boost_asio/reference/ip__address_v6/is_loopback.html +/doc/html/boost_asio/reference/ip__address_v6/is_multicast_global.html +/doc/html/boost_asio/reference/ip__address_v6/is_multicast.html +/doc/html/boost_asio/reference/ip__address_v6/is_multicast_link_local.html +/doc/html/boost_asio/reference/ip__address_v6/is_multicast_node_local.html +/doc/html/boost_asio/reference/ip__address_v6/is_multicast_org_local.html +/doc/html/boost_asio/reference/ip__address_v6/is_multicast_site_local.html +/doc/html/boost_asio/reference/ip__address_v6/is_site_local.html +/doc/html/boost_asio/reference/ip__address_v6/is_unspecified.html +/doc/html/boost_asio/reference/ip__address_v6/is_v4_compatible.html +/doc/html/boost_asio/reference/ip__address_v6/is_v4_mapped.html +/doc/html/boost_asio/reference/ip__address_v6_iterator.html +/doc/html/boost_asio/reference/ip__address_v6/loopback.html +/doc/html/boost_asio/reference/ip__address_v6/make_address_v6/ +/doc/html/boost_asio/reference/ip__address_v6/make_address_v6.html +/doc/html/boost_asio/reference/ip__address_v6/make_address_v6/overload1.html +/doc/html/boost_asio/reference/ip__address_v6/make_address_v6/overload2.html +/doc/html/boost_asio/reference/ip__address_v6/make_address_v6/overload3.html +/doc/html/boost_asio/reference/ip__address_v6/make_address_v6/overload4.html +/doc/html/boost_asio/reference/ip__address_v6/make_address_v6/overload5.html +/doc/html/boost_asio/reference/ip__address_v6/make_address_v6/overload6.html +/doc/html/boost_asio/reference/ip__address_v6/make_address_v6/overload7.html +/doc/html/boost_asio/reference/ip__address_v6/make_address_v6/overload8.html +/doc/html/boost_asio/reference/ip__address_v6/make_network_v6.html +/doc/html/boost_asio/reference/ip__address_v6/operator_eq__eq_.html +/doc/html/boost_asio/reference/ip__address_v6/operator_eq_.html +/doc/html/boost_asio/reference/ip__address_v6/operator_gt__eq_.html +/doc/html/boost_asio/reference/ip__address_v6/operator_gt_.html +/doc/html/boost_asio/reference/ip__address_v6/operator_lt__eq_.html +/doc/html/boost_asio/reference/ip__address_v6/operator_lt_.html +/doc/html/boost_asio/reference/ip__address_v6/operator_lt__lt_/ +/doc/html/boost_asio/reference/ip__address_v6/operator_lt__lt_.html +/doc/html/boost_asio/reference/ip__address_v6/operator_lt__lt_/overload1.html +/doc/html/boost_asio/reference/ip__address_v6/operator_lt__lt_/overload2.html +/doc/html/boost_asio/reference/ip__address_v6/operator_not__eq_.html +/doc/html/boost_asio/reference/ip__address_v6_range.html +/doc/html/boost_asio/reference/ip__address_v6/scope_id/ +/doc/html/boost_asio/reference/ip__address_v6/scope_id.html +/doc/html/boost_asio/reference/ip__address_v6/scope_id/overload1.html +/doc/html/boost_asio/reference/ip__address_v6/scope_id/overload2.html +/doc/html/boost_asio/reference/ip__address_v6/to_bytes.html +/doc/html/boost_asio/reference/ip__address_v6/to_string/ +/doc/html/boost_asio/reference/ip__address_v6/to_string.html +/doc/html/boost_asio/reference/ip__address_v6/to_string/overload1.html +/doc/html/boost_asio/reference/ip__address_v6/to_string/overload2.html +/doc/html/boost_asio/reference/ip__address_v6/to_v4.html +/doc/html/boost_asio/reference/ip__address_v6/v4_compatible.html +/doc/html/boost_asio/reference/ip__address_v6/v4_mapped.html +/doc/html/boost_asio/reference/ip__bad_address_cast/ +/doc/html/boost_asio/reference/ip__bad_address_cast/_bad_address_cast.html +/doc/html/boost_asio/reference/ip__bad_address_cast/bad_address_cast.html +/doc/html/boost_asio/reference/ip__bad_address_cast.html +/doc/html/boost_asio/reference/ip__bad_address_cast/what.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/ +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/basic_address_iterator/ +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/basic_address_iterator.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/basic_address_iterator/overload1.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/basic_address_iterator/overload2.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/difference_type.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/iterator_category.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_arrow_.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_eq__eq_.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_eq_.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_minus__minus_/ +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_minus__minus_.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_minus__minus_/overload1.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_minus__minus_/overload2.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_not__eq_.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_plus__plus_/ +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_plus__plus_.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_plus__plus_/overload1.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator_plus__plus_/overload2.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/operator__star_.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/pointer.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/reference.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v4__gt_/value_type.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/ +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/basic_address_iterator/ +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/basic_address_iterator.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/basic_address_iterator/overload1.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/basic_address_iterator/overload2.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/difference_type.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/iterator_category.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_arrow_.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_eq__eq_.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_eq_.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_minus__minus_/ +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_minus__minus_.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_minus__minus_/overload1.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_minus__minus_/overload2.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_not__eq_.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_plus__plus_/ +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_plus__plus_.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_plus__plus_/overload1.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator_plus__plus_/overload2.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/operator__star_.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/pointer.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/reference.html +/doc/html/boost_asio/reference/ip__basic_address_iterator_lt__address_v6__gt_/value_type.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v4__gt_/ +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v4__gt_/basic_address_range/ +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v4__gt_/basic_address_range.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v4__gt_/basic_address_range/overload1.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v4__gt_/basic_address_range/overload2.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v4__gt_/basic_address_range/overload3.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v4__gt_/begin.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v4__gt_/empty.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v4__gt_/end.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v4__gt_/find.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v4__gt_.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v4__gt_/iterator.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v4__gt_/operator_eq_.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v4__gt_/size.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v6__gt_/ +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v6__gt_/basic_address_range/ +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v6__gt_/basic_address_range.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v6__gt_/basic_address_range/overload1.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v6__gt_/basic_address_range/overload2.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v6__gt_/basic_address_range/overload3.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v6__gt_/begin.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v6__gt_/empty.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v6__gt_/end.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v6__gt_/find.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v6__gt_.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v6__gt_/iterator.html +/doc/html/boost_asio/reference/ip__basic_address_range_lt__address_v6__gt_/operator_eq_.html +/doc/html/boost_asio/reference/ip__basic_endpoint/ +/doc/html/boost_asio/reference/ip__basic_endpoint/address/ +/doc/html/boost_asio/reference/ip__basic_endpoint/address.html +/doc/html/boost_asio/reference/ip__basic_endpoint/address/overload1.html +/doc/html/boost_asio/reference/ip__basic_endpoint/address/overload2.html +/doc/html/boost_asio/reference/ip__basic_endpoint/basic_endpoint/ +/doc/html/boost_asio/reference/ip__basic_endpoint/basic_endpoint.html +/doc/html/boost_asio/reference/ip__basic_endpoint/basic_endpoint/overload1.html +/doc/html/boost_asio/reference/ip__basic_endpoint/basic_endpoint/overload2.html +/doc/html/boost_asio/reference/ip__basic_endpoint/basic_endpoint/overload3.html +/doc/html/boost_asio/reference/ip__basic_endpoint/basic_endpoint/overload4.html +/doc/html/boost_asio/reference/ip__basic_endpoint/basic_endpoint/overload5.html +/doc/html/boost_asio/reference/ip__basic_endpoint/capacity.html +/doc/html/boost_asio/reference/ip__basic_endpoint/data/ +/doc/html/boost_asio/reference/ip__basic_endpoint/data.html +/doc/html/boost_asio/reference/ip__basic_endpoint/data/overload1.html +/doc/html/boost_asio/reference/ip__basic_endpoint/data/overload2.html +/doc/html/boost_asio/reference/ip__basic_endpoint/data_type.html +/doc/html/boost_asio/reference/ip__basic_endpoint.html +/doc/html/boost_asio/reference/ip__basic_endpoint/operator_eq_/ +/doc/html/boost_asio/reference/ip__basic_endpoint/operator_eq__eq_.html +/doc/html/boost_asio/reference/ip__basic_endpoint/operator_eq_.html +/doc/html/boost_asio/reference/ip__basic_endpoint/operator_eq_/overload1.html +/doc/html/boost_asio/reference/ip__basic_endpoint/operator_eq_/overload2.html +/doc/html/boost_asio/reference/ip__basic_endpoint/operator_gt__eq_.html +/doc/html/boost_asio/reference/ip__basic_endpoint/operator_gt_.html +/doc/html/boost_asio/reference/ip__basic_endpoint/operator_lt__eq_.html +/doc/html/boost_asio/reference/ip__basic_endpoint/operator_lt_.html +/doc/html/boost_asio/reference/ip__basic_endpoint/operator_lt__lt_.html +/doc/html/boost_asio/reference/ip__basic_endpoint/operator_not__eq_.html +/doc/html/boost_asio/reference/ip__basic_endpoint/port/ +/doc/html/boost_asio/reference/ip__basic_endpoint/port.html +/doc/html/boost_asio/reference/ip__basic_endpoint/port/overload1.html +/doc/html/boost_asio/reference/ip__basic_endpoint/port/overload2.html +/doc/html/boost_asio/reference/ip__basic_endpoint/protocol.html +/doc/html/boost_asio/reference/ip__basic_endpoint/protocol_type.html +/doc/html/boost_asio/reference/ip__basic_endpoint/resize.html +/doc/html/boost_asio/reference/ip__basic_endpoint/size.html +/doc/html/boost_asio/reference/ip__basic_resolver/ +/doc/html/boost_asio/reference/ip__basic_resolver/address_configured.html +/doc/html/boost_asio/reference/ip__basic_resolver/all_matching.html +/doc/html/boost_asio/reference/ip__basic_resolver/async_resolve/ +/doc/html/boost_asio/reference/ip__basic_resolver/async_resolve.html +/doc/html/boost_asio/reference/ip__basic_resolver/async_resolve/overload1.html +/doc/html/boost_asio/reference/ip__basic_resolver/async_resolve/overload2.html +/doc/html/boost_asio/reference/ip__basic_resolver/async_resolve/overload3.html +/doc/html/boost_asio/reference/ip__basic_resolver/async_resolve/overload4.html +/doc/html/boost_asio/reference/ip__basic_resolver/async_resolve/overload5.html +/doc/html/boost_asio/reference/ip__basic_resolver/async_resolve/overload6.html +/doc/html/boost_asio/reference/ip__basic_resolver/basic_resolver/ +/doc/html/boost_asio/reference/ip__basic_resolver/_basic_resolver.html +/doc/html/boost_asio/reference/ip__basic_resolver/basic_resolver.html +/doc/html/boost_asio/reference/ip__basic_resolver/basic_resolver/overload1.html +/doc/html/boost_asio/reference/ip__basic_resolver/basic_resolver/overload2.html +/doc/html/boost_asio/reference/ip__basic_resolver/basic_resolver/overload3.html +/doc/html/boost_asio/reference/ip__basic_resolver/cancel.html +/doc/html/boost_asio/reference/ip__basic_resolver/canonical_name.html +/doc/html/boost_asio/reference/ip__basic_resolver/endpoint_type.html +/doc/html/boost_asio/reference/ip__basic_resolver_entry/ +/doc/html/boost_asio/reference/ip__basic_resolver_entry/basic_resolver_entry/ +/doc/html/boost_asio/reference/ip__basic_resolver_entry/basic_resolver_entry.html +/doc/html/boost_asio/reference/ip__basic_resolver_entry/basic_resolver_entry/overload1.html +/doc/html/boost_asio/reference/ip__basic_resolver_entry/basic_resolver_entry/overload2.html +/doc/html/boost_asio/reference/ip__basic_resolver_entry/endpoint.html +/doc/html/boost_asio/reference/ip__basic_resolver_entry/endpoint_type.html +/doc/html/boost_asio/reference/ip__basic_resolver_entry/host_name/ +/doc/html/boost_asio/reference/ip__basic_resolver_entry/host_name.html +/doc/html/boost_asio/reference/ip__basic_resolver_entry/host_name/overload1.html +/doc/html/boost_asio/reference/ip__basic_resolver_entry/host_name/overload2.html +/doc/html/boost_asio/reference/ip__basic_resolver_entry.html +/doc/html/boost_asio/reference/ip__basic_resolver_entry/operator_endpoint_type.html +/doc/html/boost_asio/reference/ip__basic_resolver_entry/protocol_type.html +/doc/html/boost_asio/reference/ip__basic_resolver_entry/service_name/ +/doc/html/boost_asio/reference/ip__basic_resolver_entry/service_name.html +/doc/html/boost_asio/reference/ip__basic_resolver_entry/service_name/overload1.html +/doc/html/boost_asio/reference/ip__basic_resolver_entry/service_name/overload2.html +/doc/html/boost_asio/reference/ip__basic_resolver/executor_type.html +/doc/html/boost_asio/reference/ip__basic_resolver/flags.html +/doc/html/boost_asio/reference/ip__basic_resolver/get_executor.html +/doc/html/boost_asio/reference/ip__basic_resolver.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/ +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/basic_resolver_iterator/ +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/basic_resolver_iterator.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/basic_resolver_iterator/overload1.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/basic_resolver_iterator/overload2.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/basic_resolver_iterator/overload3.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/dereference.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/difference_type.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/equal.html +/doc/html/boost_asio/reference/ip__basic_resolver/iterator.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/increment.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/index_.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/iterator_category.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/operator_arrow_.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/operator_eq_/ +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/operator_eq__eq_.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/operator_eq_.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/operator_eq_/overload1.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/operator_eq_/overload2.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/operator_not__eq_.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/operator_plus__plus_/ +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/operator_plus__plus_.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/operator_plus__plus_/overload1.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/operator_plus__plus_/overload2.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/operator__star_.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/pointer.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/reference.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/values_.html +/doc/html/boost_asio/reference/ip__basic_resolver_iterator/value_type.html +/doc/html/boost_asio/reference/ip__basic_resolver/numeric_host.html +/doc/html/boost_asio/reference/ip__basic_resolver/numeric_service.html +/doc/html/boost_asio/reference/ip__basic_resolver/operator_eq_.html +/doc/html/boost_asio/reference/ip__basic_resolver/passive.html +/doc/html/boost_asio/reference/ip__basic_resolver/protocol_type.html +/doc/html/boost_asio/reference/ip__basic_resolver_query/ +/doc/html/boost_asio/reference/ip__basic_resolver_query/address_configured.html +/doc/html/boost_asio/reference/ip__basic_resolver_query/all_matching.html +/doc/html/boost_asio/reference/ip__basic_resolver_query/basic_resolver_query/ +/doc/html/boost_asio/reference/ip__basic_resolver_query/basic_resolver_query.html +/doc/html/boost_asio/reference/ip__basic_resolver_query/basic_resolver_query/overload1.html +/doc/html/boost_asio/reference/ip__basic_resolver_query/basic_resolver_query/overload2.html +/doc/html/boost_asio/reference/ip__basic_resolver_query/basic_resolver_query/overload3.html +/doc/html/boost_asio/reference/ip__basic_resolver_query/basic_resolver_query/overload4.html +/doc/html/boost_asio/reference/ip__basic_resolver_query/canonical_name.html +/doc/html/boost_asio/reference/ip__basic_resolver_query/flags.html +/doc/html/boost_asio/reference/ip__basic_resolver_query/hints.html +/doc/html/boost_asio/reference/ip__basic_resolver_query/host_name.html +/doc/html/boost_asio/reference/ip__basic_resolver/query.html +/doc/html/boost_asio/reference/ip__basic_resolver_query.html +/doc/html/boost_asio/reference/ip__basic_resolver_query/numeric_host.html +/doc/html/boost_asio/reference/ip__basic_resolver_query/numeric_service.html +/doc/html/boost_asio/reference/ip__basic_resolver_query/passive.html +/doc/html/boost_asio/reference/ip__basic_resolver_query/protocol_type.html +/doc/html/boost_asio/reference/ip__basic_resolver_query/service_name.html +/doc/html/boost_asio/reference/ip__basic_resolver_query/v4_mapped.html +/doc/html/boost_asio/reference/ip__basic_resolver__rebind_executor/ +/doc/html/boost_asio/reference/ip__basic_resolver__rebind_executor.html +/doc/html/boost_asio/reference/ip__basic_resolver__rebind_executor/other.html +/doc/html/boost_asio/reference/ip__basic_resolver/resolve/ +/doc/html/boost_asio/reference/ip__basic_resolver/resolve.html +/doc/html/boost_asio/reference/ip__basic_resolver/resolve/overload10.html +/doc/html/boost_asio/reference/ip__basic_resolver/resolve/overload11.html +/doc/html/boost_asio/reference/ip__basic_resolver/resolve/overload12.html +/doc/html/boost_asio/reference/ip__basic_resolver/resolve/overload1.html +/doc/html/boost_asio/reference/ip__basic_resolver/resolve/overload2.html +/doc/html/boost_asio/reference/ip__basic_resolver/resolve/overload3.html +/doc/html/boost_asio/reference/ip__basic_resolver/resolve/overload4.html +/doc/html/boost_asio/reference/ip__basic_resolver/resolve/overload5.html +/doc/html/boost_asio/reference/ip__basic_resolver/resolve/overload6.html +/doc/html/boost_asio/reference/ip__basic_resolver/resolve/overload7.html +/doc/html/boost_asio/reference/ip__basic_resolver/resolve/overload8.html +/doc/html/boost_asio/reference/ip__basic_resolver/resolve/overload9.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/ +/doc/html/boost_asio/reference/ip__basic_resolver_results/basic_resolver_results/ +/doc/html/boost_asio/reference/ip__basic_resolver_results/basic_resolver_results.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/basic_resolver_results/overload1.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/basic_resolver_results/overload2.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/basic_resolver_results/overload3.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/begin.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/cbegin.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/cend.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/const_iterator.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/const_reference.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/dereference.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/difference_type.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/empty.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/end.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/endpoint_type.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/equal.html +/doc/html/boost_asio/reference/ip__basic_resolver_results.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/increment.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/index_.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/iterator_category.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/iterator.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/max_size.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator_arrow_.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator_eq_/ +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator_eq__eq_/ +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator_eq__eq_.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator_eq__eq_/overload1.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator_eq__eq_/overload2.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator_eq_.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator_eq_/overload1.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator_eq_/overload2.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator_not__eq_/ +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator_not__eq_.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator_not__eq_/overload1.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator_not__eq_/overload2.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator_plus__plus_/ +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator_plus__plus_.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator_plus__plus_/overload1.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator_plus__plus_/overload2.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/operator__star_.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/pointer.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/protocol_type.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/reference.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/size.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/size_type.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/swap.html +/doc/html/boost_asio/reference/ip__basic_resolver/results_type.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/values_.html +/doc/html/boost_asio/reference/ip__basic_resolver_results/value_type.html +/doc/html/boost_asio/reference/ip__basic_resolver/v4_mapped.html +/doc/html/boost_asio/reference/ip__host_name/ +/doc/html/boost_asio/reference/ip__host_name.html +/doc/html/boost_asio/reference/ip__host_name/overload1.html +/doc/html/boost_asio/reference/ip__host_name/overload2.html +/doc/html/boost_asio/reference/ip__icmp/ +/doc/html/boost_asio/reference/ip__icmp/endpoint.html +/doc/html/boost_asio/reference/ip__icmp/family.html +/doc/html/boost_asio/reference/ip__icmp.html +/doc/html/boost_asio/reference/ip__icmp/operator_eq__eq_.html +/doc/html/boost_asio/reference/ip__icmp/operator_not__eq_.html +/doc/html/boost_asio/reference/ip__icmp/protocol.html +/doc/html/boost_asio/reference/ip__icmp/resolver.html +/doc/html/boost_asio/reference/ip__icmp/socket.html +/doc/html/boost_asio/reference/ip__icmp/type.html +/doc/html/boost_asio/reference/ip__icmp/v4.html +/doc/html/boost_asio/reference/ip__icmp/v6.html +/doc/html/boost_asio/reference/ip__multicast__enable_loopback.html +/doc/html/boost_asio/reference/ip__multicast__hops.html +/doc/html/boost_asio/reference/ip__multicast__join_group.html +/doc/html/boost_asio/reference/ip__multicast__leave_group.html +/doc/html/boost_asio/reference/ip__multicast__outbound_interface.html +/doc/html/boost_asio/reference/ip__network_v4/ +/doc/html/boost_asio/reference/ip__network_v4/address.html +/doc/html/boost_asio/reference/ip__network_v4/broadcast.html +/doc/html/boost_asio/reference/ip__network_v4/canonical.html +/doc/html/boost_asio/reference/ip__network_v4/hosts.html +/doc/html/boost_asio/reference/ip__network_v4.html +/doc/html/boost_asio/reference/ip__network_v4/is_host.html +/doc/html/boost_asio/reference/ip__network_v4/is_subnet_of.html +/doc/html/boost_asio/reference/ip__network_v4/make_network_v4/ +/doc/html/boost_asio/reference/ip__network_v4/make_network_v4.html +/doc/html/boost_asio/reference/ip__network_v4/make_network_v4/overload1.html +/doc/html/boost_asio/reference/ip__network_v4/make_network_v4/overload2.html +/doc/html/boost_asio/reference/ip__network_v4/make_network_v4/overload3.html +/doc/html/boost_asio/reference/ip__network_v4/make_network_v4/overload4.html +/doc/html/boost_asio/reference/ip__network_v4/make_network_v4/overload5.html +/doc/html/boost_asio/reference/ip__network_v4/make_network_v4/overload6.html +/doc/html/boost_asio/reference/ip__network_v4/netmask.html +/doc/html/boost_asio/reference/ip__network_v4/network.html +/doc/html/boost_asio/reference/ip__network_v4/network_v4/ +/doc/html/boost_asio/reference/ip__network_v4/network_v4.html +/doc/html/boost_asio/reference/ip__network_v4/network_v4/overload1.html +/doc/html/boost_asio/reference/ip__network_v4/network_v4/overload2.html +/doc/html/boost_asio/reference/ip__network_v4/network_v4/overload3.html +/doc/html/boost_asio/reference/ip__network_v4/network_v4/overload4.html +/doc/html/boost_asio/reference/ip__network_v4/operator_eq__eq_.html +/doc/html/boost_asio/reference/ip__network_v4/operator_eq_.html +/doc/html/boost_asio/reference/ip__network_v4/operator_not__eq_.html +/doc/html/boost_asio/reference/ip__network_v4/prefix_length.html +/doc/html/boost_asio/reference/ip__network_v4/to_string/ +/doc/html/boost_asio/reference/ip__network_v4/to_string.html +/doc/html/boost_asio/reference/ip__network_v4/to_string/overload1.html +/doc/html/boost_asio/reference/ip__network_v4/to_string/overload2.html +/doc/html/boost_asio/reference/ip__network_v6/ +/doc/html/boost_asio/reference/ip__network_v6/address.html +/doc/html/boost_asio/reference/ip__network_v6/canonical.html +/doc/html/boost_asio/reference/ip__network_v6/hosts.html +/doc/html/boost_asio/reference/ip__network_v6.html +/doc/html/boost_asio/reference/ip__network_v6/is_host.html +/doc/html/boost_asio/reference/ip__network_v6/is_subnet_of.html +/doc/html/boost_asio/reference/ip__network_v6/make_network_v6/ +/doc/html/boost_asio/reference/ip__network_v6/make_network_v6.html +/doc/html/boost_asio/reference/ip__network_v6/make_network_v6/overload1.html +/doc/html/boost_asio/reference/ip__network_v6/make_network_v6/overload2.html +/doc/html/boost_asio/reference/ip__network_v6/make_network_v6/overload3.html +/doc/html/boost_asio/reference/ip__network_v6/make_network_v6/overload4.html +/doc/html/boost_asio/reference/ip__network_v6/make_network_v6/overload5.html +/doc/html/boost_asio/reference/ip__network_v6/make_network_v6/overload6.html +/doc/html/boost_asio/reference/ip__network_v6/network.html +/doc/html/boost_asio/reference/ip__network_v6/network_v6/ +/doc/html/boost_asio/reference/ip__network_v6/network_v6.html +/doc/html/boost_asio/reference/ip__network_v6/network_v6/overload1.html +/doc/html/boost_asio/reference/ip__network_v6/network_v6/overload2.html +/doc/html/boost_asio/reference/ip__network_v6/network_v6/overload3.html +/doc/html/boost_asio/reference/ip__network_v6/operator_eq__eq_.html +/doc/html/boost_asio/reference/ip__network_v6/operator_eq_.html +/doc/html/boost_asio/reference/ip__network_v6/operator_not__eq_.html +/doc/html/boost_asio/reference/ip__network_v6/prefix_length.html +/doc/html/boost_asio/reference/ip__network_v6/to_string/ +/doc/html/boost_asio/reference/ip__network_v6/to_string.html +/doc/html/boost_asio/reference/ip__network_v6/to_string/overload1.html +/doc/html/boost_asio/reference/ip__network_v6/to_string/overload2.html +/doc/html/boost_asio/reference/ip__resolver_base/ +/doc/html/boost_asio/reference/ip__resolver_base/address_configured.html +/doc/html/boost_asio/reference/ip__resolver_base/all_matching.html +/doc/html/boost_asio/reference/ip__resolver_base/canonical_name.html +/doc/html/boost_asio/reference/ip__resolver_base/flags.html +/doc/html/boost_asio/reference/ip__resolver_base.html +/doc/html/boost_asio/reference/ip__resolver_base/numeric_host.html +/doc/html/boost_asio/reference/ip__resolver_base/numeric_service.html +/doc/html/boost_asio/reference/ip__resolver_base/passive.html +/doc/html/boost_asio/reference/ip__resolver_base/_resolver_base.html +/doc/html/boost_asio/reference/ip__resolver_base/v4_mapped.html +/doc/html/boost_asio/reference/ip__resolver_query_base/ +/doc/html/boost_asio/reference/ip__resolver_query_base/address_configured.html +/doc/html/boost_asio/reference/ip__resolver_query_base/all_matching.html +/doc/html/boost_asio/reference/ip__resolver_query_base/canonical_name.html +/doc/html/boost_asio/reference/ip__resolver_query_base/flags.html +/doc/html/boost_asio/reference/ip__resolver_query_base.html +/doc/html/boost_asio/reference/ip__resolver_query_base/numeric_host.html +/doc/html/boost_asio/reference/ip__resolver_query_base/numeric_service.html +/doc/html/boost_asio/reference/ip__resolver_query_base/passive.html +/doc/html/boost_asio/reference/ip__resolver_query_base/_resolver_query_base.html +/doc/html/boost_asio/reference/ip__resolver_query_base/v4_mapped.html +/doc/html/boost_asio/reference/ip__tcp/ +/doc/html/boost_asio/reference/ip__tcp/acceptor.html +/doc/html/boost_asio/reference/ip__tcp/endpoint.html +/doc/html/boost_asio/reference/ip__tcp/family.html +/doc/html/boost_asio/reference/ip__tcp.html +/doc/html/boost_asio/reference/ip__tcp/iostream.html +/doc/html/boost_asio/reference/ip__tcp/no_delay.html +/doc/html/boost_asio/reference/ip__tcp/operator_eq__eq_.html +/doc/html/boost_asio/reference/ip__tcp/operator_not__eq_.html +/doc/html/boost_asio/reference/ip__tcp/protocol.html +/doc/html/boost_asio/reference/ip__tcp/resolver.html +/doc/html/boost_asio/reference/ip__tcp/socket.html +/doc/html/boost_asio/reference/ip__tcp/type.html +/doc/html/boost_asio/reference/ip__tcp/v4.html +/doc/html/boost_asio/reference/ip__tcp/v6.html +/doc/html/boost_asio/reference/ip__udp/ +/doc/html/boost_asio/reference/ip__udp/endpoint.html +/doc/html/boost_asio/reference/ip__udp/family.html +/doc/html/boost_asio/reference/ip__udp.html +/doc/html/boost_asio/reference/ip__udp/operator_eq__eq_.html +/doc/html/boost_asio/reference/ip__udp/operator_not__eq_.html +/doc/html/boost_asio/reference/ip__udp/protocol.html +/doc/html/boost_asio/reference/ip__udp/resolver.html +/doc/html/boost_asio/reference/ip__udp/socket.html +/doc/html/boost_asio/reference/ip__udp/type.html +/doc/html/boost_asio/reference/ip__udp/v4.html +/doc/html/boost_asio/reference/ip__udp/v6.html +/doc/html/boost_asio/reference/ip__unicast__hops.html +/doc/html/boost_asio/reference/ip__v4_mapped_t.html +/doc/html/boost_asio/reference/ip__v6_only.html +/doc/html/boost_asio/reference/is_applicable_property.html +/doc/html/boost_asio/reference/is_const_buffer_sequence.html +/doc/html/boost_asio/reference/is_dynamic_buffer.html +/doc/html/boost_asio/reference/is_dynamic_buffer_v1.html +/doc/html/boost_asio/reference/is_dynamic_buffer_v2.html +/doc/html/boost_asio/reference/is_endpoint_sequence/ +/doc/html/boost_asio/reference/is_endpoint_sequence.html +/doc/html/boost_asio/reference/is_endpoint_sequence/value.html +/doc/html/boost_asio/reference/is_error_code_enum_lt__addrinfo_errors__gt_/ +/doc/html/boost_asio/reference/is_error_code_enum_lt__addrinfo_errors__gt_.html +/doc/html/boost_asio/reference/is_error_code_enum_lt__addrinfo_errors__gt_/value.html +/doc/html/boost_asio/reference/is_error_code_enum_lt__basic_errors__gt_/ +/doc/html/boost_asio/reference/is_error_code_enum_lt__basic_errors__gt_.html +/doc/html/boost_asio/reference/is_error_code_enum_lt__basic_errors__gt_/value.html +/doc/html/boost_asio/reference/is_error_code_enum_lt__boost__asio__ssl__error__stream_errors__gt_/ +/doc/html/boost_asio/reference/is_error_code_enum_lt__boost__asio__ssl__error__stream_errors__gt_.html +/doc/html/boost_asio/reference/is_error_code_enum_lt__boost__asio__ssl__error__stream_errors__gt_/value.html +/doc/html/boost_asio/reference/is_error_code_enum_lt__misc_errors__gt_/ +/doc/html/boost_asio/reference/is_error_code_enum_lt__misc_errors__gt_.html +/doc/html/boost_asio/reference/is_error_code_enum_lt__misc_errors__gt_/value.html +/doc/html/boost_asio/reference/is_error_code_enum_lt__netdb_errors__gt_/ +/doc/html/boost_asio/reference/is_error_code_enum_lt__netdb_errors__gt_.html +/doc/html/boost_asio/reference/is_error_code_enum_lt__netdb_errors__gt_/value.html +/doc/html/boost_asio/reference/is_error_code_enum_lt__ssl_errors__gt_/ +/doc/html/boost_asio/reference/is_error_code_enum_lt__ssl_errors__gt_.html +/doc/html/boost_asio/reference/is_error_code_enum_lt__ssl_errors__gt_/value.html +/doc/html/boost_asio/reference/is_executor.html +/doc/html/boost_asio/reference/is_match_condition/ +/doc/html/boost_asio/reference/is_match_condition.html +/doc/html/boost_asio/reference/is_match_condition/value.html +/doc/html/boost_asio/reference/is_mutable_buffer_sequence.html +/doc/html/boost_asio/reference/is_nothrow_prefer.html +/doc/html/boost_asio/reference/is_nothrow_query.html +/doc/html/boost_asio/reference/is_nothrow_require_concept.html +/doc/html/boost_asio/reference/is_nothrow_require.html +/doc/html/boost_asio/reference/is_read_buffered/ +/doc/html/boost_asio/reference/is_read_buffered.html +/doc/html/boost_asio/reference/is_read_buffered/value.html +/doc/html/boost_asio/reference/is_write_buffered/ +/doc/html/boost_asio/reference/is_write_buffered.html +/doc/html/boost_asio/reference/is_write_buffered/value.html +/doc/html/boost_asio/reference/IteratorConnectHandler.html +/doc/html/boost_asio/reference/LegacyCompletionHandler.html +/doc/html/boost_asio/reference/local__basic_endpoint/ +/doc/html/boost_asio/reference/local__basic_endpoint/basic_endpoint/ +/doc/html/boost_asio/reference/local__basic_endpoint/basic_endpoint.html +/doc/html/boost_asio/reference/local__basic_endpoint/basic_endpoint/overload1.html +/doc/html/boost_asio/reference/local__basic_endpoint/basic_endpoint/overload2.html +/doc/html/boost_asio/reference/local__basic_endpoint/basic_endpoint/overload3.html +/doc/html/boost_asio/reference/local__basic_endpoint/basic_endpoint/overload4.html +/doc/html/boost_asio/reference/local__basic_endpoint/capacity.html +/doc/html/boost_asio/reference/local__basic_endpoint/data/ +/doc/html/boost_asio/reference/local__basic_endpoint/data.html +/doc/html/boost_asio/reference/local__basic_endpoint/data/overload1.html +/doc/html/boost_asio/reference/local__basic_endpoint/data/overload2.html +/doc/html/boost_asio/reference/local__basic_endpoint/data_type.html +/doc/html/boost_asio/reference/local__basic_endpoint.html +/doc/html/boost_asio/reference/local__basic_endpoint/operator_eq__eq_.html +/doc/html/boost_asio/reference/local__basic_endpoint/operator_eq_.html +/doc/html/boost_asio/reference/local__basic_endpoint/operator_gt__eq_.html +/doc/html/boost_asio/reference/local__basic_endpoint/operator_gt_.html +/doc/html/boost_asio/reference/local__basic_endpoint/operator_lt__eq_.html +/doc/html/boost_asio/reference/local__basic_endpoint/operator_lt_.html +/doc/html/boost_asio/reference/local__basic_endpoint/operator_lt__lt_.html +/doc/html/boost_asio/reference/local__basic_endpoint/operator_not__eq_.html +/doc/html/boost_asio/reference/local__basic_endpoint/path/ +/doc/html/boost_asio/reference/local__basic_endpoint/path.html +/doc/html/boost_asio/reference/local__basic_endpoint/path/overload1.html +/doc/html/boost_asio/reference/local__basic_endpoint/path/overload2.html +/doc/html/boost_asio/reference/local__basic_endpoint/path/overload3.html +/doc/html/boost_asio/reference/local__basic_endpoint/protocol.html +/doc/html/boost_asio/reference/local__basic_endpoint/protocol_type.html +/doc/html/boost_asio/reference/local__basic_endpoint/resize.html +/doc/html/boost_asio/reference/local__basic_endpoint/size.html +/doc/html/boost_asio/reference/local__connect_pair/ +/doc/html/boost_asio/reference/local__connect_pair.html +/doc/html/boost_asio/reference/local__connect_pair/overload1.html +/doc/html/boost_asio/reference/local__connect_pair/overload2.html +/doc/html/boost_asio/reference/local__datagram_protocol/ +/doc/html/boost_asio/reference/local__datagram_protocol/endpoint.html +/doc/html/boost_asio/reference/local__datagram_protocol/family.html +/doc/html/boost_asio/reference/local__datagram_protocol.html +/doc/html/boost_asio/reference/local__datagram_protocol/protocol.html +/doc/html/boost_asio/reference/local__datagram_protocol/socket.html +/doc/html/boost_asio/reference/local__datagram_protocol/type.html +/doc/html/boost_asio/reference/local__stream_protocol/ +/doc/html/boost_asio/reference/local__stream_protocol/acceptor.html +/doc/html/boost_asio/reference/local__stream_protocol/endpoint.html +/doc/html/boost_asio/reference/local__stream_protocol/family.html +/doc/html/boost_asio/reference/local__stream_protocol.html +/doc/html/boost_asio/reference/local__stream_protocol/iostream.html +/doc/html/boost_asio/reference/local__stream_protocol/protocol.html +/doc/html/boost_asio/reference/local__stream_protocol/socket.html +/doc/html/boost_asio/reference/local__stream_protocol/type.html +/doc/html/boost_asio/reference/make_strand/ +/doc/html/boost_asio/reference/make_strand.html +/doc/html/boost_asio/reference/make_strand/overload1.html +/doc/html/boost_asio/reference/make_strand/overload2.html +/doc/html/boost_asio/reference/make_work_guard/ +/doc/html/boost_asio/reference/make_work_guard.html +/doc/html/boost_asio/reference/make_work_guard/overload1.html +/doc/html/boost_asio/reference/make_work_guard/overload2.html +/doc/html/boost_asio/reference/make_work_guard/overload3.html +/doc/html/boost_asio/reference/make_work_guard/overload4.html +/doc/html/boost_asio/reference/make_work_guard/overload5.html +/doc/html/boost_asio/reference/MoveAcceptHandler.html +/doc/html/boost_asio/reference/multiple_exceptions/ +/doc/html/boost_asio/reference/multiple_exceptions/first_exception.html +/doc/html/boost_asio/reference/multiple_exceptions.html +/doc/html/boost_asio/reference/multiple_exceptions/multiple_exceptions.html +/doc/html/boost_asio/reference/multiple_exceptions/what.html +/doc/html/boost_asio/reference/mutable_buffer/ +/doc/html/boost_asio/reference/mutable_buffer/data.html +/doc/html/boost_asio/reference/mutable_buffer.html +/doc/html/boost_asio/reference/mutable_buffer/mutable_buffer/ +/doc/html/boost_asio/reference/mutable_buffer/mutable_buffer.html +/doc/html/boost_asio/reference/mutable_buffer/mutable_buffer/overload1.html +/doc/html/boost_asio/reference/mutable_buffer/mutable_buffer/overload2.html +/doc/html/boost_asio/reference/mutable_buffer/operator_plus_/ +/doc/html/boost_asio/reference/mutable_buffer/operator_plus__eq_.html +/doc/html/boost_asio/reference/mutable_buffer/operator_plus_.html +/doc/html/boost_asio/reference/mutable_buffer/operator_plus_/overload1.html +/doc/html/boost_asio/reference/mutable_buffer/operator_plus_/overload2.html +/doc/html/boost_asio/reference/mutable_buffers_1/ +/doc/html/boost_asio/reference/mutable_buffers_1/begin.html +/doc/html/boost_asio/reference/mutable_buffers_1/const_iterator.html +/doc/html/boost_asio/reference/mutable_buffers_1/data.html +/doc/html/boost_asio/reference/mutable_buffers_1/end.html +/doc/html/boost_asio/reference/mutable_buffers_1.html +/doc/html/boost_asio/reference/mutable_buffers_1/mutable_buffers_1/ +/doc/html/boost_asio/reference/mutable_buffers_1/mutable_buffers_1.html +/doc/html/boost_asio/reference/mutable_buffers_1/mutable_buffers_1/overload1.html +/doc/html/boost_asio/reference/mutable_buffers_1/mutable_buffers_1/overload2.html +/doc/html/boost_asio/reference/mutable_buffers_1/operator_plus_/ +/doc/html/boost_asio/reference/mutable_buffers_1/operator_plus__eq_.html +/doc/html/boost_asio/reference/mutable_buffers_1/operator_plus_.html +/doc/html/boost_asio/reference/mutable_buffers_1/operator_plus_/overload1.html +/doc/html/boost_asio/reference/mutable_buffers_1/operator_plus_/overload2.html +/doc/html/boost_asio/reference/mutable_buffers_1/size.html +/doc/html/boost_asio/reference/mutable_buffers_1/value_type.html +/doc/html/boost_asio/reference/MutableBufferSequence.html +/doc/html/boost_asio/reference/mutable_buffer/size.html +/doc/html/boost_asio/reference/null_buffers/ +/doc/html/boost_asio/reference/null_buffers/begin.html +/doc/html/boost_asio/reference/null_buffers/const_iterator.html +/doc/html/boost_asio/reference/null_buffers/end.html +/doc/html/boost_asio/reference/null_buffers.html +/doc/html/boost_asio/reference/null_buffers/value_type.html +/doc/html/boost_asio/reference/OperationState.html +/doc/html/boost_asio/reference/placeholders__bytes_transferred.html +/doc/html/boost_asio/reference/placeholders__endpoint.html +/doc/html/boost_asio/reference/placeholders__error.html +/doc/html/boost_asio/reference/placeholders__iterator.html +/doc/html/boost_asio/reference/placeholders__results.html +/doc/html/boost_asio/reference/placeholders__signal_number.html +/doc/html/boost_asio/reference/posix__basic_descriptor/ +/doc/html/boost_asio/reference/posix__basic_descriptor/assign/ +/doc/html/boost_asio/reference/posix__basic_descriptor/assign.html +/doc/html/boost_asio/reference/posix__basic_descriptor/assign/overload1.html +/doc/html/boost_asio/reference/posix__basic_descriptor/assign/overload2.html +/doc/html/boost_asio/reference/posix__basic_descriptor/async_wait.html +/doc/html/boost_asio/reference/posix__basic_descriptor/basic_descriptor/ +/doc/html/boost_asio/reference/posix__basic_descriptor/_basic_descriptor.html +/doc/html/boost_asio/reference/posix__basic_descriptor/basic_descriptor.html +/doc/html/boost_asio/reference/posix__basic_descriptor/basic_descriptor/overload1.html +/doc/html/boost_asio/reference/posix__basic_descriptor/basic_descriptor/overload2.html +/doc/html/boost_asio/reference/posix__basic_descriptor/basic_descriptor/overload3.html +/doc/html/boost_asio/reference/posix__basic_descriptor/basic_descriptor/overload4.html +/doc/html/boost_asio/reference/posix__basic_descriptor/basic_descriptor/overload5.html +/doc/html/boost_asio/reference/posix__basic_descriptor/bytes_readable.html +/doc/html/boost_asio/reference/posix__basic_descriptor/cancel/ +/doc/html/boost_asio/reference/posix__basic_descriptor/cancel.html +/doc/html/boost_asio/reference/posix__basic_descriptor/cancel/overload1.html +/doc/html/boost_asio/reference/posix__basic_descriptor/cancel/overload2.html +/doc/html/boost_asio/reference/posix__basic_descriptor/close/ +/doc/html/boost_asio/reference/posix__basic_descriptor/close.html +/doc/html/boost_asio/reference/posix__basic_descriptor/close/overload1.html +/doc/html/boost_asio/reference/posix__basic_descriptor/close/overload2.html +/doc/html/boost_asio/reference/posix__basic_descriptor/executor_type.html +/doc/html/boost_asio/reference/posix__basic_descriptor/get_executor.html +/doc/html/boost_asio/reference/posix__basic_descriptor.html +/doc/html/boost_asio/reference/posix__basic_descriptor/impl_.html +/doc/html/boost_asio/reference/posix__basic_descriptor/io_control/ +/doc/html/boost_asio/reference/posix__basic_descriptor/io_control.html +/doc/html/boost_asio/reference/posix__basic_descriptor/io_control/overload1.html +/doc/html/boost_asio/reference/posix__basic_descriptor/io_control/overload2.html +/doc/html/boost_asio/reference/posix__basic_descriptor/is_open.html +/doc/html/boost_asio/reference/posix__basic_descriptor/lowest_layer/ +/doc/html/boost_asio/reference/posix__basic_descriptor/lowest_layer.html +/doc/html/boost_asio/reference/posix__basic_descriptor/lowest_layer/overload1.html +/doc/html/boost_asio/reference/posix__basic_descriptor/lowest_layer/overload2.html +/doc/html/boost_asio/reference/posix__basic_descriptor/lowest_layer_type.html +/doc/html/boost_asio/reference/posix__basic_descriptor/native_handle.html +/doc/html/boost_asio/reference/posix__basic_descriptor/native_handle_type.html +/doc/html/boost_asio/reference/posix__basic_descriptor/native_non_blocking/ +/doc/html/boost_asio/reference/posix__basic_descriptor/native_non_blocking.html +/doc/html/boost_asio/reference/posix__basic_descriptor/native_non_blocking/overload1.html +/doc/html/boost_asio/reference/posix__basic_descriptor/native_non_blocking/overload2.html +/doc/html/boost_asio/reference/posix__basic_descriptor/native_non_blocking/overload3.html +/doc/html/boost_asio/reference/posix__basic_descriptor/non_blocking/ +/doc/html/boost_asio/reference/posix__basic_descriptor/non_blocking.html +/doc/html/boost_asio/reference/posix__basic_descriptor/non_blocking/overload1.html +/doc/html/boost_asio/reference/posix__basic_descriptor/non_blocking/overload2.html +/doc/html/boost_asio/reference/posix__basic_descriptor/non_blocking/overload3.html +/doc/html/boost_asio/reference/posix__basic_descriptor/operator_eq_.html +/doc/html/boost_asio/reference/posix__basic_descriptor__rebind_executor/ +/doc/html/boost_asio/reference/posix__basic_descriptor__rebind_executor.html +/doc/html/boost_asio/reference/posix__basic_descriptor__rebind_executor/other.html +/doc/html/boost_asio/reference/posix__basic_descriptor/release.html +/doc/html/boost_asio/reference/posix__basic_descriptor/wait/ +/doc/html/boost_asio/reference/posix__basic_descriptor/wait.html +/doc/html/boost_asio/reference/posix__basic_descriptor/wait/overload1.html +/doc/html/boost_asio/reference/posix__basic_descriptor/wait/overload2.html +/doc/html/boost_asio/reference/posix__basic_descriptor/wait_type.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/ +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/assign/ +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/assign.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/assign/overload1.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/assign/overload2.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/async_read_some.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/async_wait.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/async_write_some.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/basic_stream_descriptor/ +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/basic_stream_descriptor.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/basic_stream_descriptor/overload1.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/basic_stream_descriptor/overload2.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/basic_stream_descriptor/overload3.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/basic_stream_descriptor/overload4.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/basic_stream_descriptor/overload5.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/bytes_readable.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/cancel/ +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/cancel.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/cancel/overload1.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/cancel/overload2.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/close/ +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/close.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/close/overload1.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/close/overload2.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/executor_type.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/get_executor.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/impl_.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/io_control/ +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/io_control.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/io_control/overload1.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/io_control/overload2.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/is_open.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/lowest_layer/ +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/lowest_layer.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/lowest_layer/overload1.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/lowest_layer/overload2.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/lowest_layer_type.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/native_handle.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/native_handle_type.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/native_non_blocking/ +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/native_non_blocking.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/native_non_blocking/overload1.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/native_non_blocking/overload2.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/native_non_blocking/overload3.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/non_blocking/ +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/non_blocking.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/non_blocking/overload1.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/non_blocking/overload2.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/non_blocking/overload3.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/operator_eq_.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/read_some/ +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/read_some.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/read_some/overload1.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/read_some/overload2.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor__rebind_executor/ +/doc/html/boost_asio/reference/posix__basic_stream_descriptor__rebind_executor.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor__rebind_executor/other.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/release.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/wait/ +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/wait.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/wait/overload1.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/wait/overload2.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/wait_type.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/write_some/ +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/write_some.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/write_some/overload1.html +/doc/html/boost_asio/reference/posix__basic_stream_descriptor/write_some/overload2.html +/doc/html/boost_asio/reference/posix__descriptor_base/ +/doc/html/boost_asio/reference/posix__descriptor_base/bytes_readable.html +/doc/html/boost_asio/reference/posix__descriptor_base/_descriptor_base.html +/doc/html/boost_asio/reference/posix__descriptor_base.html +/doc/html/boost_asio/reference/posix__descriptor_base/wait_type.html +/doc/html/boost_asio/reference/posix__descriptor.html +/doc/html/boost_asio/reference/posix__stream_descriptor.html +/doc/html/boost_asio/reference/post/ +/doc/html/boost_asio/reference/post.html +/doc/html/boost_asio/reference/post/overload1.html +/doc/html/boost_asio/reference/post/overload2.html +/doc/html/boost_asio/reference/post/overload3.html +/doc/html/boost_asio/reference/prefer.html +/doc/html/boost_asio/reference/prefer_result/ +/doc/html/boost_asio/reference/prefer_result.html +/doc/html/boost_asio/reference/prefer_result/type.html +/doc/html/boost_asio/reference/ProtoAllocator.html +/doc/html/boost_asio/reference/Protocol.html +/doc/html/boost_asio/reference/query.html +/doc/html/boost_asio/reference/query_result/ +/doc/html/boost_asio/reference/query_result.html +/doc/html/boost_asio/reference/query_result/type.html +/doc/html/boost_asio/reference/RangeConnectHandler.html +/doc/html/boost_asio/reference/read/ +/doc/html/boost_asio/reference/read_at/ +/doc/html/boost_asio/reference/read_at.html +/doc/html/boost_asio/reference/read_at/overload1.html +/doc/html/boost_asio/reference/read_at/overload2.html +/doc/html/boost_asio/reference/read_at/overload3.html +/doc/html/boost_asio/reference/read_at/overload4.html +/doc/html/boost_asio/reference/read_at/overload5.html +/doc/html/boost_asio/reference/read_at/overload6.html +/doc/html/boost_asio/reference/read_at/overload7.html +/doc/html/boost_asio/reference/read_at/overload8.html +/doc/html/boost_asio/reference/ReadHandler.html +/doc/html/boost_asio/reference/read.html +/doc/html/boost_asio/reference/read/overload10.html +/doc/html/boost_asio/reference/read/overload11.html +/doc/html/boost_asio/reference/read/overload12.html +/doc/html/boost_asio/reference/read/overload13.html +/doc/html/boost_asio/reference/read/overload14.html +/doc/html/boost_asio/reference/read/overload15.html +/doc/html/boost_asio/reference/read/overload16.html +/doc/html/boost_asio/reference/read/overload1.html +/doc/html/boost_asio/reference/read/overload2.html +/doc/html/boost_asio/reference/read/overload3.html +/doc/html/boost_asio/reference/read/overload4.html +/doc/html/boost_asio/reference/read/overload5.html +/doc/html/boost_asio/reference/read/overload6.html +/doc/html/boost_asio/reference/read/overload7.html +/doc/html/boost_asio/reference/read/overload8.html +/doc/html/boost_asio/reference/read/overload9.html +/doc/html/boost_asio/reference/read_until/ +/doc/html/boost_asio/reference/read_until.html +/doc/html/boost_asio/reference/read_until/overload10.html +/doc/html/boost_asio/reference/read_until/overload11.html +/doc/html/boost_asio/reference/read_until/overload12.html +/doc/html/boost_asio/reference/read_until/overload13.html +/doc/html/boost_asio/reference/read_until/overload14.html +/doc/html/boost_asio/reference/read_until/overload15.html +/doc/html/boost_asio/reference/read_until/overload16.html +/doc/html/boost_asio/reference/read_until/overload17.html +/doc/html/boost_asio/reference/read_until/overload18.html +/doc/html/boost_asio/reference/read_until/overload19.html +/doc/html/boost_asio/reference/read_until/overload1.html +/doc/html/boost_asio/reference/read_until/overload20.html +/doc/html/boost_asio/reference/read_until/overload21.html +/doc/html/boost_asio/reference/read_until/overload22.html +/doc/html/boost_asio/reference/read_until/overload23.html +/doc/html/boost_asio/reference/read_until/overload24.html +/doc/html/boost_asio/reference/read_until/overload2.html +/doc/html/boost_asio/reference/read_until/overload3.html +/doc/html/boost_asio/reference/read_until/overload4.html +/doc/html/boost_asio/reference/read_until/overload5.html +/doc/html/boost_asio/reference/read_until/overload6.html +/doc/html/boost_asio/reference/read_until/overload7.html +/doc/html/boost_asio/reference/read_until/overload8.html +/doc/html/boost_asio/reference/read_until/overload9.html +/doc/html/boost_asio/reference/read_write_operations.html +/doc/html/boost_asio/reference/Receiver.html +/doc/html/boost_asio/reference/redirect_error.html +/doc/html/boost_asio/reference/redirect_error_t/ +/doc/html/boost_asio/reference/redirect_error_t/ec_.html +/doc/html/boost_asio/reference/redirect_error_t.html +/doc/html/boost_asio/reference/redirect_error_t/redirect_error_t.html +/doc/html/boost_asio/reference/redirect_error_t/token_.html +/doc/html/boost_asio/reference/require_concept.html +/doc/html/boost_asio/reference/require_concept_result/ +/doc/html/boost_asio/reference/require_concept_result.html +/doc/html/boost_asio/reference/require_concept_result/type.html +/doc/html/boost_asio/reference/require.html +/doc/html/boost_asio/reference/require_result/ +/doc/html/boost_asio/reference/require_result.html +/doc/html/boost_asio/reference/require_result/type.html +/doc/html/boost_asio/reference/ResolveHandler.html +/doc/html/boost_asio/reference/resolver_errc__try_again.html +/doc/html/boost_asio/reference/Scheduler.html +/doc/html/boost_asio/reference/Sender.html +/doc/html/boost_asio/reference/serial_port_base/ +/doc/html/boost_asio/reference/serial_port_base__baud_rate/ +/doc/html/boost_asio/reference/serial_port_base__baud_rate/baud_rate.html +/doc/html/boost_asio/reference/serial_port_base__baud_rate.html +/doc/html/boost_asio/reference/serial_port_base__baud_rate/load.html +/doc/html/boost_asio/reference/serial_port_base__baud_rate/store.html +/doc/html/boost_asio/reference/serial_port_base__baud_rate/value.html +/doc/html/boost_asio/reference/serial_port_base__character_size/ +/doc/html/boost_asio/reference/serial_port_base__character_size/character_size.html +/doc/html/boost_asio/reference/serial_port_base__character_size.html +/doc/html/boost_asio/reference/serial_port_base__character_size/load.html +/doc/html/boost_asio/reference/serial_port_base__character_size/store.html +/doc/html/boost_asio/reference/serial_port_base__character_size/value.html +/doc/html/boost_asio/reference/serial_port_base__flow_control/ +/doc/html/boost_asio/reference/serial_port_base__flow_control/flow_control.html +/doc/html/boost_asio/reference/serial_port_base__flow_control.html +/doc/html/boost_asio/reference/serial_port_base__flow_control/load.html +/doc/html/boost_asio/reference/serial_port_base__flow_control/store.html +/doc/html/boost_asio/reference/serial_port_base__flow_control/type.html +/doc/html/boost_asio/reference/serial_port_base__flow_control/value.html +/doc/html/boost_asio/reference/serial_port_base.html +/doc/html/boost_asio/reference/serial_port_base__parity/ +/doc/html/boost_asio/reference/serial_port_base__parity.html +/doc/html/boost_asio/reference/serial_port_base__parity/load.html +/doc/html/boost_asio/reference/serial_port_base__parity/parity.html +/doc/html/boost_asio/reference/serial_port_base__parity/store.html +/doc/html/boost_asio/reference/serial_port_base__parity/type.html +/doc/html/boost_asio/reference/serial_port_base__parity/value.html +/doc/html/boost_asio/reference/serial_port_base/_serial_port_base.html +/doc/html/boost_asio/reference/serial_port_base__stop_bits/ +/doc/html/boost_asio/reference/serial_port_base__stop_bits.html +/doc/html/boost_asio/reference/serial_port_base__stop_bits/load.html +/doc/html/boost_asio/reference/serial_port_base__stop_bits/stop_bits.html +/doc/html/boost_asio/reference/serial_port_base__stop_bits/store.html +/doc/html/boost_asio/reference/serial_port_base__stop_bits/type.html +/doc/html/boost_asio/reference/serial_port_base__stop_bits/value.html +/doc/html/boost_asio/reference/serial_port.html +/doc/html/boost_asio/reference/service_already_exists/ +/doc/html/boost_asio/reference/service_already_exists.html +/doc/html/boost_asio/reference/service_already_exists/service_already_exists.html +/doc/html/boost_asio/reference/Service.html +/doc/html/boost_asio/reference/SettableSerialPortOption.html +/doc/html/boost_asio/reference/SettableSocketOption.html +/doc/html/boost_asio/reference/ShutdownHandler.html +/doc/html/boost_asio/reference/SignalHandler.html +/doc/html/boost_asio/reference/signal_set.html +/doc/html/boost_asio/reference/socket_base/ +/doc/html/boost_asio/reference/socket_base/broadcast.html +/doc/html/boost_asio/reference/socket_base/bytes_readable.html +/doc/html/boost_asio/reference/socket_base/debug.html +/doc/html/boost_asio/reference/socket_base/do_not_route.html +/doc/html/boost_asio/reference/socket_base/enable_connection_aborted.html +/doc/html/boost_asio/reference/socket_base.html +/doc/html/boost_asio/reference/socket_base/keep_alive.html +/doc/html/boost_asio/reference/socket_base/linger.html +/doc/html/boost_asio/reference/socket_base/max_connections.html +/doc/html/boost_asio/reference/socket_base/max_listen_connections.html +/doc/html/boost_asio/reference/socket_base/message_do_not_route.html +/doc/html/boost_asio/reference/socket_base/message_end_of_record.html +/doc/html/boost_asio/reference/socket_base/message_flags.html +/doc/html/boost_asio/reference/socket_base/message_out_of_band.html +/doc/html/boost_asio/reference/socket_base/message_peek.html +/doc/html/boost_asio/reference/socket_base/out_of_band_inline.html +/doc/html/boost_asio/reference/socket_base/receive_buffer_size.html +/doc/html/boost_asio/reference/socket_base/receive_low_watermark.html +/doc/html/boost_asio/reference/socket_base/reuse_address.html +/doc/html/boost_asio/reference/socket_base/send_buffer_size.html +/doc/html/boost_asio/reference/socket_base/send_low_watermark.html +/doc/html/boost_asio/reference/socket_base/shutdown_type.html +/doc/html/boost_asio/reference/socket_base/_socket_base.html +/doc/html/boost_asio/reference/socket_base/wait_type.html +/doc/html/boost_asio/reference/spawn/ +/doc/html/boost_asio/reference/spawn.html +/doc/html/boost_asio/reference/spawn/overload1.html +/doc/html/boost_asio/reference/spawn/overload2.html +/doc/html/boost_asio/reference/spawn/overload3.html +/doc/html/boost_asio/reference/spawn/overload4.html +/doc/html/boost_asio/reference/spawn/overload5.html +/doc/html/boost_asio/reference/spawn/overload6.html +/doc/html/boost_asio/reference/spawn/overload7.html +/doc/html/boost_asio/reference/ssl__context/ +/doc/html/boost_asio/reference/ssl__context/add_certificate_authority/ +/doc/html/boost_asio/reference/ssl__context/add_certificate_authority.html +/doc/html/boost_asio/reference/ssl__context/add_certificate_authority/overload1.html +/doc/html/boost_asio/reference/ssl__context/add_certificate_authority/overload2.html +/doc/html/boost_asio/reference/ssl__context/add_verify_path/ +/doc/html/boost_asio/reference/ssl__context/add_verify_path.html +/doc/html/boost_asio/reference/ssl__context/add_verify_path/overload1.html +/doc/html/boost_asio/reference/ssl__context/add_verify_path/overload2.html +/doc/html/boost_asio/reference/ssl__context_base/ +/doc/html/boost_asio/reference/ssl__context_base/_context_base.html +/doc/html/boost_asio/reference/ssl__context_base/default_workarounds.html +/doc/html/boost_asio/reference/ssl__context_base/file_format.html +/doc/html/boost_asio/reference/ssl__context_base.html +/doc/html/boost_asio/reference/ssl__context_base/method.html +/doc/html/boost_asio/reference/ssl__context_base/no_compression.html +/doc/html/boost_asio/reference/ssl__context_base/no_sslv2.html +/doc/html/boost_asio/reference/ssl__context_base/no_sslv3.html +/doc/html/boost_asio/reference/ssl__context_base/no_tlsv1_1.html +/doc/html/boost_asio/reference/ssl__context_base/no_tlsv1_2.html +/doc/html/boost_asio/reference/ssl__context_base/no_tlsv1_3.html +/doc/html/boost_asio/reference/ssl__context_base/no_tlsv1.html +/doc/html/boost_asio/reference/ssl__context_base/options.html +/doc/html/boost_asio/reference/ssl__context_base/password_purpose.html +/doc/html/boost_asio/reference/ssl__context_base/single_dh_use.html +/doc/html/boost_asio/reference/ssl__context/clear_options/ +/doc/html/boost_asio/reference/ssl__context/clear_options.html +/doc/html/boost_asio/reference/ssl__context/clear_options/overload1.html +/doc/html/boost_asio/reference/ssl__context/clear_options/overload2.html +/doc/html/boost_asio/reference/ssl__context/context/ +/doc/html/boost_asio/reference/ssl__context/_context.html +/doc/html/boost_asio/reference/ssl__context/context.html +/doc/html/boost_asio/reference/ssl__context/context/overload1.html +/doc/html/boost_asio/reference/ssl__context/context/overload2.html +/doc/html/boost_asio/reference/ssl__context/context/overload3.html +/doc/html/boost_asio/reference/ssl__context/default_workarounds.html +/doc/html/boost_asio/reference/ssl__context/file_format.html +/doc/html/boost_asio/reference/ssl__context.html +/doc/html/boost_asio/reference/ssl__context/load_verify_file/ +/doc/html/boost_asio/reference/ssl__context/load_verify_file.html +/doc/html/boost_asio/reference/ssl__context/load_verify_file/overload1.html +/doc/html/boost_asio/reference/ssl__context/load_verify_file/overload2.html +/doc/html/boost_asio/reference/ssl__context/method.html +/doc/html/boost_asio/reference/ssl__context/native_handle.html +/doc/html/boost_asio/reference/ssl__context/native_handle_type.html +/doc/html/boost_asio/reference/ssl__context/no_compression.html +/doc/html/boost_asio/reference/ssl__context/no_sslv2.html +/doc/html/boost_asio/reference/ssl__context/no_sslv3.html +/doc/html/boost_asio/reference/ssl__context/no_tlsv1_1.html +/doc/html/boost_asio/reference/ssl__context/no_tlsv1_2.html +/doc/html/boost_asio/reference/ssl__context/no_tlsv1_3.html +/doc/html/boost_asio/reference/ssl__context/no_tlsv1.html +/doc/html/boost_asio/reference/ssl__context/operator_eq_.html +/doc/html/boost_asio/reference/ssl__context/options.html +/doc/html/boost_asio/reference/ssl__context/password_purpose.html +/doc/html/boost_asio/reference/ssl__context/set_default_verify_paths/ +/doc/html/boost_asio/reference/ssl__context/set_default_verify_paths.html +/doc/html/boost_asio/reference/ssl__context/set_default_verify_paths/overload1.html +/doc/html/boost_asio/reference/ssl__context/set_default_verify_paths/overload2.html +/doc/html/boost_asio/reference/ssl__context/set_options/ +/doc/html/boost_asio/reference/ssl__context/set_options.html +/doc/html/boost_asio/reference/ssl__context/set_options/overload1.html +/doc/html/boost_asio/reference/ssl__context/set_options/overload2.html +/doc/html/boost_asio/reference/ssl__context/set_password_callback/ +/doc/html/boost_asio/reference/ssl__context/set_password_callback.html +/doc/html/boost_asio/reference/ssl__context/set_password_callback/overload1.html +/doc/html/boost_asio/reference/ssl__context/set_password_callback/overload2.html +/doc/html/boost_asio/reference/ssl__context/set_verify_callback/ +/doc/html/boost_asio/reference/ssl__context/set_verify_callback.html +/doc/html/boost_asio/reference/ssl__context/set_verify_callback/overload1.html +/doc/html/boost_asio/reference/ssl__context/set_verify_callback/overload2.html +/doc/html/boost_asio/reference/ssl__context/set_verify_depth/ +/doc/html/boost_asio/reference/ssl__context/set_verify_depth.html +/doc/html/boost_asio/reference/ssl__context/set_verify_depth/overload1.html +/doc/html/boost_asio/reference/ssl__context/set_verify_depth/overload2.html +/doc/html/boost_asio/reference/ssl__context/set_verify_mode/ +/doc/html/boost_asio/reference/ssl__context/set_verify_mode.html +/doc/html/boost_asio/reference/ssl__context/set_verify_mode/overload1.html +/doc/html/boost_asio/reference/ssl__context/set_verify_mode/overload2.html +/doc/html/boost_asio/reference/ssl__context/single_dh_use.html +/doc/html/boost_asio/reference/ssl__context/use_certificate/ +/doc/html/boost_asio/reference/ssl__context/use_certificate_chain/ +/doc/html/boost_asio/reference/ssl__context/use_certificate_chain_file/ +/doc/html/boost_asio/reference/ssl__context/use_certificate_chain_file.html +/doc/html/boost_asio/reference/ssl__context/use_certificate_chain_file/overload1.html +/doc/html/boost_asio/reference/ssl__context/use_certificate_chain_file/overload2.html +/doc/html/boost_asio/reference/ssl__context/use_certificate_chain.html +/doc/html/boost_asio/reference/ssl__context/use_certificate_chain/overload1.html +/doc/html/boost_asio/reference/ssl__context/use_certificate_chain/overload2.html +/doc/html/boost_asio/reference/ssl__context/use_certificate_file/ +/doc/html/boost_asio/reference/ssl__context/use_certificate_file.html +/doc/html/boost_asio/reference/ssl__context/use_certificate_file/overload1.html +/doc/html/boost_asio/reference/ssl__context/use_certificate_file/overload2.html +/doc/html/boost_asio/reference/ssl__context/use_certificate.html +/doc/html/boost_asio/reference/ssl__context/use_certificate/overload1.html +/doc/html/boost_asio/reference/ssl__context/use_certificate/overload2.html +/doc/html/boost_asio/reference/ssl__context/use_private_key/ +/doc/html/boost_asio/reference/ssl__context/use_private_key_file/ +/doc/html/boost_asio/reference/ssl__context/use_private_key_file.html +/doc/html/boost_asio/reference/ssl__context/use_private_key_file/overload1.html +/doc/html/boost_asio/reference/ssl__context/use_private_key_file/overload2.html +/doc/html/boost_asio/reference/ssl__context/use_private_key.html +/doc/html/boost_asio/reference/ssl__context/use_private_key/overload1.html +/doc/html/boost_asio/reference/ssl__context/use_private_key/overload2.html +/doc/html/boost_asio/reference/ssl__context/use_rsa_private_key/ +/doc/html/boost_asio/reference/ssl__context/use_rsa_private_key_file/ +/doc/html/boost_asio/reference/ssl__context/use_rsa_private_key_file.html +/doc/html/boost_asio/reference/ssl__context/use_rsa_private_key_file/overload1.html +/doc/html/boost_asio/reference/ssl__context/use_rsa_private_key_file/overload2.html +/doc/html/boost_asio/reference/ssl__context/use_rsa_private_key.html +/doc/html/boost_asio/reference/ssl__context/use_rsa_private_key/overload1.html +/doc/html/boost_asio/reference/ssl__context/use_rsa_private_key/overload2.html +/doc/html/boost_asio/reference/ssl__context/use_tmp_dh/ +/doc/html/boost_asio/reference/ssl__context/use_tmp_dh_file/ +/doc/html/boost_asio/reference/ssl__context/use_tmp_dh_file.html +/doc/html/boost_asio/reference/ssl__context/use_tmp_dh_file/overload1.html +/doc/html/boost_asio/reference/ssl__context/use_tmp_dh_file/overload2.html +/doc/html/boost_asio/reference/ssl__context/use_tmp_dh.html +/doc/html/boost_asio/reference/ssl__context/use_tmp_dh/overload1.html +/doc/html/boost_asio/reference/ssl__context/use_tmp_dh/overload2.html +/doc/html/boost_asio/reference/ssl__error__get_stream_category.html +/doc/html/boost_asio/reference/ssl__error__make_error_code.html +/doc/html/boost_asio/reference/ssl__error__stream_category.html +/doc/html/boost_asio/reference/ssl__error__stream_errors.html +/doc/html/boost_asio/reference/ssl__host_name_verification/ +/doc/html/boost_asio/reference/ssl__host_name_verification/host_name_verification.html +/doc/html/boost_asio/reference/ssl__host_name_verification.html +/doc/html/boost_asio/reference/ssl__host_name_verification/operator_lp__rp_.html +/doc/html/boost_asio/reference/ssl__host_name_verification/result_type.html +/doc/html/boost_asio/reference/ssl__rfc2818_verification/ +/doc/html/boost_asio/reference/ssl__rfc2818_verification.html +/doc/html/boost_asio/reference/ssl__rfc2818_verification/operator_lp__rp_.html +/doc/html/boost_asio/reference/ssl__rfc2818_verification/result_type.html +/doc/html/boost_asio/reference/ssl__rfc2818_verification/rfc2818_verification.html +/doc/html/boost_asio/reference/ssl__stream/ +/doc/html/boost_asio/reference/ssl__stream/async_handshake/ +/doc/html/boost_asio/reference/ssl__stream/async_handshake.html +/doc/html/boost_asio/reference/ssl__stream/async_handshake/overload1.html +/doc/html/boost_asio/reference/ssl__stream/async_handshake/overload2.html +/doc/html/boost_asio/reference/ssl__stream/async_read_some.html +/doc/html/boost_asio/reference/ssl__stream/async_shutdown.html +/doc/html/boost_asio/reference/ssl__stream/async_write_some.html +/doc/html/boost_asio/reference/ssl__stream_base/ +/doc/html/boost_asio/reference/ssl__stream_base/handshake_type.html +/doc/html/boost_asio/reference/ssl__stream_base.html +/doc/html/boost_asio/reference/ssl__stream_base/_stream_base.html +/doc/html/boost_asio/reference/ssl__stream/executor_type.html +/doc/html/boost_asio/reference/ssl__stream/get_executor.html +/doc/html/boost_asio/reference/ssl__stream/handshake/ +/doc/html/boost_asio/reference/ssl__stream/handshake.html +/doc/html/boost_asio/reference/ssl__stream/handshake/overload1.html +/doc/html/boost_asio/reference/ssl__stream/handshake/overload2.html +/doc/html/boost_asio/reference/ssl__stream/handshake/overload3.html +/doc/html/boost_asio/reference/ssl__stream/handshake/overload4.html +/doc/html/boost_asio/reference/ssl__stream/handshake_type.html +/doc/html/boost_asio/reference/ssl__stream.html +/doc/html/boost_asio/reference/ssl__stream__impl_struct/ +/doc/html/boost_asio/reference/ssl__stream__impl_struct.html +/doc/html/boost_asio/reference/ssl__stream__impl_struct/ssl.html +/doc/html/boost_asio/reference/ssl__stream/lowest_layer/ +/doc/html/boost_asio/reference/ssl__stream/lowest_layer.html +/doc/html/boost_asio/reference/ssl__stream/lowest_layer/overload1.html +/doc/html/boost_asio/reference/ssl__stream/lowest_layer/overload2.html +/doc/html/boost_asio/reference/ssl__stream/lowest_layer_type.html +/doc/html/boost_asio/reference/ssl__stream/native_handle.html +/doc/html/boost_asio/reference/ssl__stream/native_handle_type.html +/doc/html/boost_asio/reference/ssl__stream/next_layer/ +/doc/html/boost_asio/reference/ssl__stream/next_layer.html +/doc/html/boost_asio/reference/ssl__stream/next_layer/overload1.html +/doc/html/boost_asio/reference/ssl__stream/next_layer/overload2.html +/doc/html/boost_asio/reference/ssl__stream/next_layer_type.html +/doc/html/boost_asio/reference/ssl__stream/read_some/ +/doc/html/boost_asio/reference/ssl__stream/read_some.html +/doc/html/boost_asio/reference/ssl__stream/read_some/overload1.html +/doc/html/boost_asio/reference/ssl__stream/read_some/overload2.html +/doc/html/boost_asio/reference/ssl__stream/set_verify_callback/ +/doc/html/boost_asio/reference/ssl__stream/set_verify_callback.html +/doc/html/boost_asio/reference/ssl__stream/set_verify_callback/overload1.html +/doc/html/boost_asio/reference/ssl__stream/set_verify_callback/overload2.html +/doc/html/boost_asio/reference/ssl__stream/set_verify_depth/ +/doc/html/boost_asio/reference/ssl__stream/set_verify_depth.html +/doc/html/boost_asio/reference/ssl__stream/set_verify_depth/overload1.html +/doc/html/boost_asio/reference/ssl__stream/set_verify_depth/overload2.html +/doc/html/boost_asio/reference/ssl__stream/set_verify_mode/ +/doc/html/boost_asio/reference/ssl__stream/set_verify_mode.html +/doc/html/boost_asio/reference/ssl__stream/set_verify_mode/overload1.html +/doc/html/boost_asio/reference/ssl__stream/set_verify_mode/overload2.html +/doc/html/boost_asio/reference/ssl__stream/shutdown/ +/doc/html/boost_asio/reference/ssl__stream/shutdown.html +/doc/html/boost_asio/reference/ssl__stream/shutdown/overload1.html +/doc/html/boost_asio/reference/ssl__stream/shutdown/overload2.html +/doc/html/boost_asio/reference/ssl__stream/stream/ +/doc/html/boost_asio/reference/ssl__stream/_stream.html +/doc/html/boost_asio/reference/ssl__stream/stream.html +/doc/html/boost_asio/reference/ssl__stream/stream/overload1.html +/doc/html/boost_asio/reference/ssl__stream/stream/overload2.html +/doc/html/boost_asio/reference/ssl__stream/write_some/ +/doc/html/boost_asio/reference/ssl__stream/write_some.html +/doc/html/boost_asio/reference/ssl__stream/write_some/overload1.html +/doc/html/boost_asio/reference/ssl__stream/write_some/overload2.html +/doc/html/boost_asio/reference/ssl__verify_client_once.html +/doc/html/boost_asio/reference/ssl__verify_context/ +/doc/html/boost_asio/reference/ssl__verify_context.html +/doc/html/boost_asio/reference/ssl__verify_context/native_handle.html +/doc/html/boost_asio/reference/ssl__verify_context/native_handle_type.html +/doc/html/boost_asio/reference/ssl__verify_context/verify_context.html +/doc/html/boost_asio/reference/ssl__verify_fail_if_no_peer_cert.html +/doc/html/boost_asio/reference/ssl__verify_mode.html +/doc/html/boost_asio/reference/ssl__verify_none.html +/doc/html/boost_asio/reference/ssl__verify_peer.html +/doc/html/boost_asio/reference/static_thread_pool.html +/doc/html/boost_asio/reference/steady_timer.html +/doc/html/boost_asio/reference/strand/ +/doc/html/boost_asio/reference/strand/defer.html +/doc/html/boost_asio/reference/strand/dispatch.html +/doc/html/boost_asio/reference/strand/execute.html +/doc/html/boost_asio/reference/strand/get_inner_executor.html +/doc/html/boost_asio/reference/strand.html +/doc/html/boost_asio/reference/strand/inner_executor_type.html +/doc/html/boost_asio/reference/strand/operator_eq_/ +/doc/html/boost_asio/reference/strand/operator_eq__eq_.html +/doc/html/boost_asio/reference/strand/operator_eq_.html +/doc/html/boost_asio/reference/strand/operator_eq_/overload1.html +/doc/html/boost_asio/reference/strand/operator_eq_/overload2.html +/doc/html/boost_asio/reference/strand/operator_eq_/overload3.html +/doc/html/boost_asio/reference/strand/operator_eq_/overload4.html +/doc/html/boost_asio/reference/strand/operator_not__eq_.html +/doc/html/boost_asio/reference/strand/post.html +/doc/html/boost_asio/reference/strand/prefer.html +/doc/html/boost_asio/reference/strand/query.html +/doc/html/boost_asio/reference/strand/require.html +/doc/html/boost_asio/reference/strand/running_in_this_thread.html +/doc/html/boost_asio/reference/strand/strand/ +/doc/html/boost_asio/reference/strand/_strand.html +/doc/html/boost_asio/reference/strand/strand.html +/doc/html/boost_asio/reference/strand/strand/overload1.html +/doc/html/boost_asio/reference/strand/strand/overload2.html +/doc/html/boost_asio/reference/strand/strand/overload3.html +/doc/html/boost_asio/reference/strand/strand/overload4.html +/doc/html/boost_asio/reference/strand/strand/overload5.html +/doc/html/boost_asio/reference/strand/strand/overload6.html +/doc/html/boost_asio/reference/streambuf.html +/doc/html/boost_asio/reference/synchronous_socket_operations.html +/doc/html/boost_asio/reference/SyncRandomAccessReadDevice.html +/doc/html/boost_asio/reference/SyncRandomAccessWriteDevice.html +/doc/html/boost_asio/reference/SyncReadStream.html +/doc/html/boost_asio/reference/SyncWriteStream.html +/doc/html/boost_asio/reference/system_context/ +/doc/html/boost_asio/reference/system_context/add_service.html +/doc/html/boost_asio/reference/system_context/destroy.html +/doc/html/boost_asio/reference/system_context/executor_type.html +/doc/html/boost_asio/reference/system_context/fork_event.html +/doc/html/boost_asio/reference/system_context/get_executor.html +/doc/html/boost_asio/reference/system_context/has_service.html +/doc/html/boost_asio/reference/system_context.html +/doc/html/boost_asio/reference/system_context/join.html +/doc/html/boost_asio/reference/system_context/make_service.html +/doc/html/boost_asio/reference/system_context/notify_fork.html +/doc/html/boost_asio/reference/system_context/shutdown.html +/doc/html/boost_asio/reference/system_context/stop.html +/doc/html/boost_asio/reference/system_context/stopped.html +/doc/html/boost_asio/reference/system_context/_system_context.html +/doc/html/boost_asio/reference/system_context/use_service/ +/doc/html/boost_asio/reference/system_context/use_service.html +/doc/html/boost_asio/reference/system_context/use_service/overload1.html +/doc/html/boost_asio/reference/system_context/use_service/overload2.html +/doc/html/boost_asio/reference/system_executor.html +/doc/html/boost_asio/reference/system_timer.html +/doc/html/boost_asio/reference/this_coro__executor.html +/doc/html/boost_asio/reference/this_coro__executor_t/ +/doc/html/boost_asio/reference/this_coro__executor_t/executor_t.html +/doc/html/boost_asio/reference/this_coro__executor_t.html +/doc/html/boost_asio/reference/thread_pool/ +/doc/html/boost_asio/reference/thread_pool/add_service.html +/doc/html/boost_asio/reference/thread_pool/attach.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/ +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/basic_executor_type/ +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/_basic_executor_type.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/basic_executor_type.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/basic_executor_type/overload1.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/basic_executor_type/overload2.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/bulk_execute.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/context.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/defer.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/dispatch.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/execute.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/on_work_finished.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/on_work_started.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/operator_eq_/ +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/operator_eq__eq_.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/operator_eq_.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/operator_eq_/overload1.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/operator_eq_/overload2.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/operator_not__eq_.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/post.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/query/ +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/query.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/query/overload1.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/query/overload2.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/query/overload3.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/query/overload4.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/query/overload5.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/query/overload6.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/query__static/ +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/query__static.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/query__static/overload1.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/query__static/overload2.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/query__static/overload3.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/require/ +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/require.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/require/overload1.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/require/overload2.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/require/overload3.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/require/overload4.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/require/overload5.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/require/overload6.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/require/overload7.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/require/overload8.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/require/overload9.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/running_in_this_thread.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/schedule.html +/doc/html/boost_asio/reference/thread_pool__basic_executor_type/sender_type.html +/doc/html/boost_asio/reference/thread_pool/destroy.html +/doc/html/boost_asio/reference/thread_pool/executor.html +/doc/html/boost_asio/reference/thread_pool/executor_type.html +/doc/html/boost_asio/reference/thread_pool/fork_event.html +/doc/html/boost_asio/reference/thread_pool/get_executor.html +/doc/html/boost_asio/reference/thread_pool/has_service.html +/doc/html/boost_asio/reference/thread_pool.html +/doc/html/boost_asio/reference/thread_pool/join.html +/doc/html/boost_asio/reference/thread_pool/make_service.html +/doc/html/boost_asio/reference/thread_pool/notify_fork.html +/doc/html/boost_asio/reference/thread_pool/scheduler.html +/doc/html/boost_asio/reference/thread_pool/scheduler_type.html +/doc/html/boost_asio/reference/thread_pool/shutdown.html +/doc/html/boost_asio/reference/thread_pool/stop.html +/doc/html/boost_asio/reference/thread_pool/thread_pool/ +/doc/html/boost_asio/reference/thread_pool/_thread_pool.html +/doc/html/boost_asio/reference/thread_pool/thread_pool.html +/doc/html/boost_asio/reference/thread_pool/thread_pool/overload1.html +/doc/html/boost_asio/reference/thread_pool/thread_pool/overload2.html +/doc/html/boost_asio/reference/thread_pool/use_service/ +/doc/html/boost_asio/reference/thread_pool/use_service.html +/doc/html/boost_asio/reference/thread_pool/use_service/overload1.html +/doc/html/boost_asio/reference/thread_pool/use_service/overload2.html +/doc/html/boost_asio/reference/thread_pool/wait.html +/doc/html/boost_asio/reference/TimeTraits.html +/doc/html/boost_asio/reference/time_traits_lt__ptime__gt_/ +/doc/html/boost_asio/reference/time_traits_lt__ptime__gt_/add.html +/doc/html/boost_asio/reference/time_traits_lt__ptime__gt_/duration_type.html +/doc/html/boost_asio/reference/time_traits_lt__ptime__gt_.html +/doc/html/boost_asio/reference/time_traits_lt__ptime__gt_/less_than.html +/doc/html/boost_asio/reference/time_traits_lt__ptime__gt_/now.html +/doc/html/boost_asio/reference/time_traits_lt__ptime__gt_/subtract.html +/doc/html/boost_asio/reference/time_traits_lt__ptime__gt_/time_type.html +/doc/html/boost_asio/reference/time_traits_lt__ptime__gt_/to_posix_duration.html +/doc/html/boost_asio/reference/transfer_all.html +/doc/html/boost_asio/reference/transfer_at_least.html +/doc/html/boost_asio/reference/transfer_exactly.html +/doc/html/boost_asio/reference/use_awaitable.html +/doc/html/boost_asio/reference/use_awaitable_t/ +/doc/html/boost_asio/reference/use_awaitable_t/as_default_on.html +/doc/html/boost_asio/reference/use_awaitable_t__executor_with_default/ +/doc/html/boost_asio/reference/use_awaitable_t__executor_with_default/default_completion_token_type.html +/doc/html/boost_asio/reference/use_awaitable_t__executor_with_default/executor_with_default/ +/doc/html/boost_asio/reference/use_awaitable_t__executor_with_default/executor_with_default.html +/doc/html/boost_asio/reference/use_awaitable_t__executor_with_default/executor_with_default/overload1.html +/doc/html/boost_asio/reference/use_awaitable_t__executor_with_default/executor_with_default/overload2.html +/doc/html/boost_asio/reference/use_awaitable_t__executor_with_default.html +/doc/html/boost_asio/reference/use_awaitable_t.html +/doc/html/boost_asio/reference/use_awaitable_t/use_awaitable_t/ +/doc/html/boost_asio/reference/use_awaitable_t/use_awaitable_t.html +/doc/html/boost_asio/reference/use_awaitable_t/use_awaitable_t/overload1.html +/doc/html/boost_asio/reference/use_awaitable_t/use_awaitable_t/overload2.html +/doc/html/boost_asio/reference/use_future.html +/doc/html/boost_asio/reference/use_future_t/ +/doc/html/boost_asio/reference/use_future_t/allocator_type.html +/doc/html/boost_asio/reference/use_future_t/get_allocator.html +/doc/html/boost_asio/reference/use_future_t.html +/doc/html/boost_asio/reference/use_future_t/operator_lb__rb_.html +/doc/html/boost_asio/reference/use_future_t/operator_lp__rp_.html +/doc/html/boost_asio/reference/use_future_t/rebind.html +/doc/html/boost_asio/reference/use_future_t/use_future_t/ +/doc/html/boost_asio/reference/use_future_t/use_future_t.html +/doc/html/boost_asio/reference/use_future_t/use_future_t/overload1.html +/doc/html/boost_asio/reference/use_future_t/use_future_t/overload2.html +/doc/html/boost_asio/reference/uses_executor.html +/doc/html/boost_asio/reference/WaitHandler.html +/doc/html/boost_asio/reference/wait_traits/ +/doc/html/boost_asio/reference/WaitTraits.html +/doc/html/boost_asio/reference/wait_traits.html +/doc/html/boost_asio/reference/wait_traits/to_wait_duration/ +/doc/html/boost_asio/reference/wait_traits/to_wait_duration.html +/doc/html/boost_asio/reference/wait_traits/to_wait_duration/overload1.html +/doc/html/boost_asio/reference/wait_traits/to_wait_duration/overload2.html +/doc/html/boost_asio/reference/windows__basic_object_handle/ +/doc/html/boost_asio/reference/windows__basic_object_handle/assign/ +/doc/html/boost_asio/reference/windows__basic_object_handle/assign.html +/doc/html/boost_asio/reference/windows__basic_object_handle/assign/overload1.html +/doc/html/boost_asio/reference/windows__basic_object_handle/assign/overload2.html +/doc/html/boost_asio/reference/windows__basic_object_handle/async_wait.html +/doc/html/boost_asio/reference/windows__basic_object_handle/basic_object_handle/ +/doc/html/boost_asio/reference/windows__basic_object_handle/basic_object_handle.html +/doc/html/boost_asio/reference/windows__basic_object_handle/basic_object_handle/overload1.html +/doc/html/boost_asio/reference/windows__basic_object_handle/basic_object_handle/overload2.html +/doc/html/boost_asio/reference/windows__basic_object_handle/basic_object_handle/overload3.html +/doc/html/boost_asio/reference/windows__basic_object_handle/basic_object_handle/overload4.html +/doc/html/boost_asio/reference/windows__basic_object_handle/basic_object_handle/overload5.html +/doc/html/boost_asio/reference/windows__basic_object_handle/cancel/ +/doc/html/boost_asio/reference/windows__basic_object_handle/cancel.html +/doc/html/boost_asio/reference/windows__basic_object_handle/cancel/overload1.html +/doc/html/boost_asio/reference/windows__basic_object_handle/cancel/overload2.html +/doc/html/boost_asio/reference/windows__basic_object_handle/close/ +/doc/html/boost_asio/reference/windows__basic_object_handle/close.html +/doc/html/boost_asio/reference/windows__basic_object_handle/close/overload1.html +/doc/html/boost_asio/reference/windows__basic_object_handle/close/overload2.html +/doc/html/boost_asio/reference/windows__basic_object_handle/executor_type.html +/doc/html/boost_asio/reference/windows__basic_object_handle/get_executor.html +/doc/html/boost_asio/reference/windows__basic_object_handle.html +/doc/html/boost_asio/reference/windows__basic_object_handle/is_open.html +/doc/html/boost_asio/reference/windows__basic_object_handle/lowest_layer/ +/doc/html/boost_asio/reference/windows__basic_object_handle/lowest_layer.html +/doc/html/boost_asio/reference/windows__basic_object_handle/lowest_layer/overload1.html +/doc/html/boost_asio/reference/windows__basic_object_handle/lowest_layer/overload2.html +/doc/html/boost_asio/reference/windows__basic_object_handle/lowest_layer_type.html +/doc/html/boost_asio/reference/windows__basic_object_handle/native_handle.html +/doc/html/boost_asio/reference/windows__basic_object_handle/native_handle_type.html +/doc/html/boost_asio/reference/windows__basic_object_handle/operator_eq_.html +/doc/html/boost_asio/reference/windows__basic_object_handle__rebind_executor/ +/doc/html/boost_asio/reference/windows__basic_object_handle__rebind_executor.html +/doc/html/boost_asio/reference/windows__basic_object_handle__rebind_executor/other.html +/doc/html/boost_asio/reference/windows__basic_object_handle/wait/ +/doc/html/boost_asio/reference/windows__basic_object_handle/wait.html +/doc/html/boost_asio/reference/windows__basic_object_handle/wait/overload1.html +/doc/html/boost_asio/reference/windows__basic_object_handle/wait/overload2.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/ +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/assign/ +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/assign.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/assign/overload1.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/assign/overload2.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/basic_overlapped_handle/ +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/_basic_overlapped_handle.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/basic_overlapped_handle.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/basic_overlapped_handle/overload1.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/basic_overlapped_handle/overload2.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/basic_overlapped_handle/overload3.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/basic_overlapped_handle/overload4.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/basic_overlapped_handle/overload5.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/cancel/ +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/cancel.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/cancel/overload1.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/cancel/overload2.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/close/ +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/close.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/close/overload1.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/close/overload2.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/executor_type.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/get_executor.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/impl_.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/is_open.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/lowest_layer/ +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/lowest_layer.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/lowest_layer/overload1.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/lowest_layer/overload2.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/lowest_layer_type.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/native_handle.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/native_handle_type.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle/operator_eq_.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle__rebind_executor/ +/doc/html/boost_asio/reference/windows__basic_overlapped_handle__rebind_executor.html +/doc/html/boost_asio/reference/windows__basic_overlapped_handle__rebind_executor/other.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/ +/doc/html/boost_asio/reference/windows__basic_random_access_handle/assign/ +/doc/html/boost_asio/reference/windows__basic_random_access_handle/assign.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/assign/overload1.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/assign/overload2.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/async_read_some_at.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/async_write_some_at.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/basic_random_access_handle/ +/doc/html/boost_asio/reference/windows__basic_random_access_handle/basic_random_access_handle.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/basic_random_access_handle/overload1.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/basic_random_access_handle/overload2.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/basic_random_access_handle/overload3.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/basic_random_access_handle/overload4.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/basic_random_access_handle/overload5.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/cancel/ +/doc/html/boost_asio/reference/windows__basic_random_access_handle/cancel.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/cancel/overload1.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/cancel/overload2.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/close/ +/doc/html/boost_asio/reference/windows__basic_random_access_handle/close.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/close/overload1.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/close/overload2.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/executor_type.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/get_executor.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/impl_.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/is_open.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/lowest_layer/ +/doc/html/boost_asio/reference/windows__basic_random_access_handle/lowest_layer.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/lowest_layer/overload1.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/lowest_layer/overload2.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/lowest_layer_type.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/native_handle.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/native_handle_type.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/operator_eq_.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/read_some_at/ +/doc/html/boost_asio/reference/windows__basic_random_access_handle/read_some_at.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/read_some_at/overload1.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/read_some_at/overload2.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle__rebind_executor/ +/doc/html/boost_asio/reference/windows__basic_random_access_handle__rebind_executor.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle__rebind_executor/other.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/write_some_at/ +/doc/html/boost_asio/reference/windows__basic_random_access_handle/write_some_at.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/write_some_at/overload1.html +/doc/html/boost_asio/reference/windows__basic_random_access_handle/write_some_at/overload2.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/ +/doc/html/boost_asio/reference/windows__basic_stream_handle/assign/ +/doc/html/boost_asio/reference/windows__basic_stream_handle/assign.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/assign/overload1.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/assign/overload2.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/async_read_some.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/async_write_some.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/basic_stream_handle/ +/doc/html/boost_asio/reference/windows__basic_stream_handle/basic_stream_handle.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/basic_stream_handle/overload1.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/basic_stream_handle/overload2.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/basic_stream_handle/overload3.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/basic_stream_handle/overload4.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/basic_stream_handle/overload5.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/cancel/ +/doc/html/boost_asio/reference/windows__basic_stream_handle/cancel.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/cancel/overload1.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/cancel/overload2.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/close/ +/doc/html/boost_asio/reference/windows__basic_stream_handle/close.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/close/overload1.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/close/overload2.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/executor_type.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/get_executor.html +/doc/html/boost_asio/reference/windows__basic_stream_handle.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/impl_.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/is_open.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/lowest_layer/ +/doc/html/boost_asio/reference/windows__basic_stream_handle/lowest_layer.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/lowest_layer/overload1.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/lowest_layer/overload2.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/lowest_layer_type.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/native_handle.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/native_handle_type.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/operator_eq_.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/read_some/ +/doc/html/boost_asio/reference/windows__basic_stream_handle/read_some.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/read_some/overload1.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/read_some/overload2.html +/doc/html/boost_asio/reference/windows__basic_stream_handle__rebind_executor/ +/doc/html/boost_asio/reference/windows__basic_stream_handle__rebind_executor.html +/doc/html/boost_asio/reference/windows__basic_stream_handle__rebind_executor/other.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/write_some/ +/doc/html/boost_asio/reference/windows__basic_stream_handle/write_some.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/write_some/overload1.html +/doc/html/boost_asio/reference/windows__basic_stream_handle/write_some/overload2.html +/doc/html/boost_asio/reference/windows__object_handle.html +/doc/html/boost_asio/reference/windows__overlapped_handle.html +/doc/html/boost_asio/reference/windows__overlapped_ptr/ +/doc/html/boost_asio/reference/windows__overlapped_ptr/complete.html +/doc/html/boost_asio/reference/windows__overlapped_ptr/get/ +/doc/html/boost_asio/reference/windows__overlapped_ptr/get.html +/doc/html/boost_asio/reference/windows__overlapped_ptr/get/overload1.html +/doc/html/boost_asio/reference/windows__overlapped_ptr/get/overload2.html +/doc/html/boost_asio/reference/windows__overlapped_ptr.html +/doc/html/boost_asio/reference/windows__overlapped_ptr/overlapped_ptr/ +/doc/html/boost_asio/reference/windows__overlapped_ptr/_overlapped_ptr.html +/doc/html/boost_asio/reference/windows__overlapped_ptr/overlapped_ptr.html +/doc/html/boost_asio/reference/windows__overlapped_ptr/overlapped_ptr/overload1.html +/doc/html/boost_asio/reference/windows__overlapped_ptr/overlapped_ptr/overload2.html +/doc/html/boost_asio/reference/windows__overlapped_ptr/overlapped_ptr/overload3.html +/doc/html/boost_asio/reference/windows__overlapped_ptr/release.html +/doc/html/boost_asio/reference/windows__overlapped_ptr/reset/ +/doc/html/boost_asio/reference/windows__overlapped_ptr/reset.html +/doc/html/boost_asio/reference/windows__overlapped_ptr/reset/overload1.html +/doc/html/boost_asio/reference/windows__overlapped_ptr/reset/overload2.html +/doc/html/boost_asio/reference/windows__overlapped_ptr/reset/overload3.html +/doc/html/boost_asio/reference/windows__random_access_handle.html +/doc/html/boost_asio/reference/windows__stream_handle.html +/doc/html/boost_asio/reference/write/ +/doc/html/boost_asio/reference/write_at/ +/doc/html/boost_asio/reference/write_at.html +/doc/html/boost_asio/reference/write_at/overload1.html +/doc/html/boost_asio/reference/write_at/overload2.html +/doc/html/boost_asio/reference/write_at/overload3.html +/doc/html/boost_asio/reference/write_at/overload4.html +/doc/html/boost_asio/reference/write_at/overload5.html +/doc/html/boost_asio/reference/write_at/overload6.html +/doc/html/boost_asio/reference/write_at/overload7.html +/doc/html/boost_asio/reference/write_at/overload8.html +/doc/html/boost_asio/reference/WriteHandler.html +/doc/html/boost_asio/reference/write.html +/doc/html/boost_asio/reference/write/overload10.html +/doc/html/boost_asio/reference/write/overload11.html +/doc/html/boost_asio/reference/write/overload12.html +/doc/html/boost_asio/reference/write/overload13.html +/doc/html/boost_asio/reference/write/overload14.html +/doc/html/boost_asio/reference/write/overload15.html +/doc/html/boost_asio/reference/write/overload16.html +/doc/html/boost_asio/reference/write/overload1.html +/doc/html/boost_asio/reference/write/overload2.html +/doc/html/boost_asio/reference/write/overload3.html +/doc/html/boost_asio/reference/write/overload4.html +/doc/html/boost_asio/reference/write/overload5.html +/doc/html/boost_asio/reference/write/overload6.html +/doc/html/boost_asio/reference/write/overload7.html +/doc/html/boost_asio/reference/write/overload8.html +/doc/html/boost_asio/reference/write/overload9.html +/doc/html/boost_asio/reference/yield_context.html +/doc/html/boost_asio/sync_op.png +/doc/html/boost_asio/tutorial/ +/doc/html/boost_asio/tutorial.html +/doc/html/boost_asio/tutorial/tutdaytime1/ +/doc/html/boost_asio/tutorial/tutdaytime1.html +/doc/html/boost_asio/tutorial/tutdaytime1/src.html +/doc/html/boost_asio/tutorial/tutdaytime2/ +/doc/html/boost_asio/tutorial/tutdaytime2.html +/doc/html/boost_asio/tutorial/tutdaytime2/src.html +/doc/html/boost_asio/tutorial/tutdaytime3/ +/doc/html/boost_asio/tutorial/tutdaytime3.html +/doc/html/boost_asio/tutorial/tutdaytime3/src.html +/doc/html/boost_asio/tutorial/tutdaytime4/ +/doc/html/boost_asio/tutorial/tutdaytime4.html +/doc/html/boost_asio/tutorial/tutdaytime4/src.html +/doc/html/boost_asio/tutorial/tutdaytime5/ +/doc/html/boost_asio/tutorial/tutdaytime5.html +/doc/html/boost_asio/tutorial/tutdaytime5/src.html +/doc/html/boost_asio/tutorial/tutdaytime6/ +/doc/html/boost_asio/tutorial/tutdaytime6.html +/doc/html/boost_asio/tutorial/tutdaytime6/src.html +/doc/html/boost_asio/tutorial/tutdaytime7/ +/doc/html/boost_asio/tutorial/tutdaytime7.html +/doc/html/boost_asio/tutorial/tutdaytime7/src.html +/doc/html/boost_asio/tutorial/tuttimer1/ +/doc/html/boost_asio/tutorial/tuttimer1.html +/doc/html/boost_asio/tutorial/tuttimer1/src.html +/doc/html/boost_asio/tutorial/tuttimer2/ +/doc/html/boost_asio/tutorial/tuttimer2.html +/doc/html/boost_asio/tutorial/tuttimer2/src.html +/doc/html/boost_asio/tutorial/tuttimer3/ +/doc/html/boost_asio/tutorial/tuttimer3.html +/doc/html/boost_asio/tutorial/tuttimer3/src.html +/doc/html/boost_asio/tutorial/tuttimer4/ +/doc/html/boost_asio/tutorial/tuttimer4.html +/doc/html/boost_asio/tutorial/tuttimer4/src.html +/doc/html/boost_asio/tutorial/tuttimer5/ +/doc/html/boost_asio/tutorial/tuttimer5.html +/doc/html/boost_asio/tutorial/tuttimer5/src.html +/doc/html/boost_asio/using.html +/libs/ +/libs/asio/ +/libs/asio/doc/ +/libs/asio/doc/asio.qbk +/libs/asio/doc/doxy2qbk.pl +/libs/asio/doc/examples.qbk +/libs/asio/doc/history.qbk +/libs/asio/doc/html/ +/libs/asio/doc/html/boost_asio/ +/libs/asio/doc/html/boost_asio/example/ +/libs/asio/doc/html/boost_asio/example/cpp03/ +/libs/asio/doc/html/boost_asio/example/cpp03/allocation/ +/libs/asio/doc/html/boost_asio/example/cpp03/buffers/ +/libs/asio/doc/html/boost_asio/example/cpp03/chat/ +/libs/asio/doc/html/boost_asio/example/cpp03/echo/ +/libs/asio/doc/html/boost_asio/example/cpp03/fork/ +/libs/asio/doc/html/boost_asio/example/cpp03/http/ +/libs/asio/doc/html/boost_asio/example/cpp03/http/client/ +/libs/asio/doc/html/boost_asio/example/cpp03/http/server/ +/libs/asio/doc/html/boost_asio/example/cpp03/http/server2/ +/libs/asio/doc/html/boost_asio/example/cpp03/http/server3/ +/libs/asio/doc/html/boost_asio/example/cpp03/http/server4/ +/libs/asio/doc/html/boost_asio/example/cpp03/icmp/ +/libs/asio/doc/html/boost_asio/example/cpp03/invocation/ +/libs/asio/doc/html/boost_asio/example/cpp03/iostreams/ +/libs/asio/doc/html/boost_asio/example/cpp03/local/ +/libs/asio/doc/html/boost_asio/example/cpp03/multicast/ +/libs/asio/doc/html/boost_asio/example/cpp03/nonblocking/ +/libs/asio/doc/html/boost_asio/example/cpp03/porthopper/ +/libs/asio/doc/html/boost_asio/example/cpp03/serialization/ +/libs/asio/doc/html/boost_asio/example/cpp03/services/ +/libs/asio/doc/html/boost_asio/example/cpp03/socks4/ +/libs/asio/doc/html/boost_asio/example/cpp03/spawn/ +/libs/asio/doc/html/boost_asio/example/cpp03/ssl/ +/libs/asio/doc/html/boost_asio/example/cpp03/timeouts/ +/libs/asio/doc/html/boost_asio/example/cpp03/timers/ +/libs/asio/doc/html/boost_asio/example/cpp03/windows/ +/libs/asio/doc/html/boost_asio/example/cpp11/ +/libs/asio/doc/html/boost_asio/example/cpp11/allocation/ +/libs/asio/doc/html/boost_asio/example/cpp11/buffers/ +/libs/asio/doc/html/boost_asio/example/cpp11/chat/ +/libs/asio/doc/html/boost_asio/example/cpp11/echo/ +/libs/asio/doc/html/boost_asio/example/cpp11/executors/ +/libs/asio/doc/html/boost_asio/example/cpp11/fork/ +/libs/asio/doc/html/boost_asio/example/cpp11/futures/ +/libs/asio/doc/html/boost_asio/example/cpp11/handler_tracking/ +/libs/asio/doc/html/boost_asio/example/cpp11/http/ +/libs/asio/doc/html/boost_asio/example/cpp11/http/server/ +/libs/asio/doc/html/boost_asio/example/cpp11/invocation/ +/libs/asio/doc/html/boost_asio/example/cpp11/local/ +/libs/asio/doc/html/boost_asio/example/cpp11/multicast/ +/libs/asio/doc/html/boost_asio/example/cpp11/nonblocking/ +/libs/asio/doc/html/boost_asio/example/cpp11/operations/ +/libs/asio/doc/html/boost_asio/example/cpp11/socks4/ +/libs/asio/doc/html/boost_asio/example/cpp11/spawn/ +/libs/asio/doc/html/boost_asio/example/cpp11/ssl/ +/libs/asio/doc/html/boost_asio/example/cpp11/timeouts/ +/libs/asio/doc/html/boost_asio/example/cpp11/timers/ +/libs/asio/doc/html/boost_asio/example/cpp14/ +/libs/asio/doc/html/boost_asio/example/cpp14/operations/ +/libs/asio/doc/html/boost_asio/example/cpp17/ +/libs/asio/doc/html/boost_asio/example/cpp17/coroutines_ts/ +/libs/asio/doc/html/boost_asio/examples/ +/libs/asio/doc/html/boost_asio/examples/cpp03_examples.html +/libs/asio/doc/html/boost_asio/examples/cpp11_examples.html +/libs/asio/doc/html/boost_asio/examples/cpp14_examples.html +/libs/asio/doc/html/boost_asio/examples/cpp17_examples.html +/libs/asio/doc/html/boost_asio/examples.html +/libs/asio/doc/html/boost_asio/history.html +/libs/asio/doc/html/boost_asio/index.html +/libs/asio/doc/html/boost_asio/net_ts.html +/libs/asio/doc/html/boost_asio/overview/ +/libs/asio/doc/html/boost_asio/overview/core/ +/libs/asio/doc/html/boost_asio/overview/core/allocation.html +/libs/asio/doc/html/boost_asio/overview/core/async.html +/libs/asio/doc/html/boost_asio/overview/core/basics.html +/libs/asio/doc/html/boost_asio/overview/core/buffers.html +/libs/asio/doc/html/boost_asio/overview/core/concurrency_hint.html +/libs/asio/doc/html/boost_asio/overview/core/coroutine.html +/libs/asio/doc/html/boost_asio/overview/core/coroutines_ts.html +/libs/asio/doc/html/boost_asio/overview/core/handler_tracking.html +/libs/asio/doc/html/boost_asio/overview/core.html +/libs/asio/doc/html/boost_asio/overview/core/line_based.html +/libs/asio/doc/html/boost_asio/overview/core/reactor.html +/libs/asio/doc/html/boost_asio/overview/core/spawn.html +/libs/asio/doc/html/boost_asio/overview/core/strands.html +/libs/asio/doc/html/boost_asio/overview/core/streams.html +/libs/asio/doc/html/boost_asio/overview/core/threads.html +/libs/asio/doc/html/boost_asio/overview/cpp2011/ +/libs/asio/doc/html/boost_asio/overview/cpp2011/array.html +/libs/asio/doc/html/boost_asio/overview/cpp2011/atomic.html +/libs/asio/doc/html/boost_asio/overview/cpp2011/chrono.html +/libs/asio/doc/html/boost_asio/overview/cpp2011/futures.html +/libs/asio/doc/html/boost_asio/overview/cpp2011.html +/libs/asio/doc/html/boost_asio/overview/cpp2011/move_handlers.html +/libs/asio/doc/html/boost_asio/overview/cpp2011/move_objects.html +/libs/asio/doc/html/boost_asio/overview/cpp2011/shared_ptr.html +/libs/asio/doc/html/boost_asio/overview/cpp2011/variadic.html +/libs/asio/doc/html/boost_asio/overview.html +/libs/asio/doc/html/boost_asio/overview/implementation.html +/libs/asio/doc/html/boost_asio/overview/networking/ +/libs/asio/doc/html/boost_asio/overview/networking/bsd_sockets.html +/libs/asio/doc/html/boost_asio/overview/networking.html +/libs/asio/doc/html/boost_asio/overview/networking/iostreams.html +/libs/asio/doc/html/boost_asio/overview/networking/other_protocols.html +/libs/asio/doc/html/boost_asio/overview/networking/protocols.html +/libs/asio/doc/html/boost_asio/overview/posix/ +/libs/asio/doc/html/boost_asio/overview/posix/fork.html +/libs/asio/doc/html/boost_asio/overview/posix.html +/libs/asio/doc/html/boost_asio/overview/posix/local.html +/libs/asio/doc/html/boost_asio/overview/posix/stream_descriptor.html +/libs/asio/doc/html/boost_asio/overview/rationale.html +/libs/asio/doc/html/boost_asio/overview/serial_ports.html +/libs/asio/doc/html/boost_asio/overview/signals.html +/libs/asio/doc/html/boost_asio/overview/ssl.html +/libs/asio/doc/html/boost_asio/overview/timers.html +/libs/asio/doc/html/boost_asio/overview/windows/ +/libs/asio/doc/html/boost_asio/overview/windows.html +/libs/asio/doc/html/boost_asio/overview/windows/object_handle.html +/libs/asio/doc/html/boost_asio/overview/windows/random_access_handle.html +/libs/asio/doc/html/boost_asio/overview/windows/stream_handle.html +/libs/asio/doc/html/boost_asio/tutorial/ +/libs/asio/doc/html/boost_asio/tutorial.html +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime1/ +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime1.html +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime1/src.html +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime2/ +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime2.html +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime2/src.html +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime3/ +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime3.html +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime3/src.html +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime4/ +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime4.html +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime4/src.html +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime5/ +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime5.html +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime5/src.html +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime6/ +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime6.html +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime6/src.html +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime7/ +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime7.html +/libs/asio/doc/html/boost_asio/tutorial/tutdaytime7/src.html +/libs/asio/doc/html/boost_asio/tutorial/tuttimer1/ +/libs/asio/doc/html/boost_asio/tutorial/tuttimer1.html +/libs/asio/doc/html/boost_asio/tutorial/tuttimer1/src.html +/libs/asio/doc/html/boost_asio/tutorial/tuttimer2/ +/libs/asio/doc/html/boost_asio/tutorial/tuttimer2.html +/libs/asio/doc/html/boost_asio/tutorial/tuttimer2/src.html +/libs/asio/doc/html/boost_asio/tutorial/tuttimer3/ +/libs/asio/doc/html/boost_asio/tutorial/tuttimer3.html +/libs/asio/doc/html/boost_asio/tutorial/tuttimer3/src.html +/libs/asio/doc/html/boost_asio/tutorial/tuttimer4/ +/libs/asio/doc/html/boost_asio/tutorial/tuttimer4.html +/libs/asio/doc/html/boost_asio/tutorial/tuttimer4/src.html +/libs/asio/doc/html/boost_asio/tutorial/tuttimer5/ +/libs/asio/doc/html/boost_asio/tutorial/tuttimer5.html +/libs/asio/doc/html/boost_asio/tutorial/tuttimer5/src.html +/libs/asio/doc/html/boost_asio/using.html +/libs/asio/doc/html/index.html +/libs/asio/doc/index.xml +/libs/asio/doc/Jamfile.v2 +/libs/asio/doc/net_ts.qbk +/libs/asio/doc/noncopyable_dox.txt +/libs/asio/doc/overview/ +/libs/asio/doc/overview/allocation.qbk +/libs/asio/doc/overview/async_op1.dot +/libs/asio/doc/overview/async_op1.png +/libs/asio/doc/overview/async_op2.dot +/libs/asio/doc/overview/async_op2.png +/libs/asio/doc/overview/async.qbk +/libs/asio/doc/overview/basics.qbk +/libs/asio/doc/overview/bsd_sockets.qbk +/libs/asio/doc/overview/buffers.qbk +/libs/asio/doc/overview/concurrency_hint.qbk +/libs/asio/doc/overview/coroutine.qbk +/libs/asio/doc/overview/coroutines_ts.qbk +/libs/asio/doc/overview/cpp2011.qbk +/libs/asio/doc/overview/handler_tracking.qbk +/libs/asio/doc/overview/implementation.qbk +/libs/asio/doc/overview/iostreams.qbk +/libs/asio/doc/overview/line_based.qbk +/libs/asio/doc/overview/other_protocols.qbk +/libs/asio/doc/overview/posix.qbk +/libs/asio/doc/overview/proactor.dot +/libs/asio/doc/overview/proactor.png +/libs/asio/doc/overview/protocols.qbk +/libs/asio/doc/overview.qbk +/libs/asio/doc/overview/rationale.qbk +/libs/asio/doc/overview/reactor.qbk +/libs/asio/doc/overview/serial_ports.qbk +/libs/asio/doc/overview/signals.qbk +/libs/asio/doc/overview/spawn.qbk +/libs/asio/doc/overview/ssl.qbk +/libs/asio/doc/overview/strands.qbk +/libs/asio/doc/overview/streams.qbk +/libs/asio/doc/overview/sync_op.dot +/libs/asio/doc/overview/sync_op.png +/libs/asio/doc/overview/threads.qbk +/libs/asio/doc/overview/timers.qbk +/libs/asio/doc/overview/windows.qbk +/libs/asio/doc/quickref.xml +/libs/asio/doc/reference.dox +/libs/asio/doc/reference.qbk +/libs/asio/doc/reference.xsl +/libs/asio/doc/requirements/ +/libs/asio/doc/requirements/AcceptableProtocol.qbk +/libs/asio/doc/requirements/AcceptHandler.qbk +/libs/asio/doc/requirements/asynchronous_operations.qbk +/libs/asio/doc/requirements/asynchronous_socket_operations.qbk +/libs/asio/doc/requirements/AsyncRandomAccessReadDevice.qbk +/libs/asio/doc/requirements/AsyncRandomAccessWriteDevice.qbk +/libs/asio/doc/requirements/AsyncReadStream.qbk +/libs/asio/doc/requirements/AsyncWriteStream.qbk +/libs/asio/doc/requirements/BufferedHandshakeHandler.qbk +/libs/asio/doc/requirements/CompletionCondition.qbk +/libs/asio/doc/requirements/CompletionHandler.qbk +/libs/asio/doc/requirements/ConnectCondition.qbk +/libs/asio/doc/requirements/ConnectHandler.qbk +/libs/asio/doc/requirements/ConstBufferSequence.qbk +/libs/asio/doc/requirements/DynamicBuffer.qbk +/libs/asio/doc/requirements/DynamicBuffer_v1.qbk +/libs/asio/doc/requirements/DynamicBuffer_v2.qbk +/libs/asio/doc/requirements/Endpoint.qbk +/libs/asio/doc/requirements/EndpointSequence.qbk +/libs/asio/doc/requirements/ExecutionContext.qbk +/libs/asio/doc/requirements/Executor.qbk +/libs/asio/doc/requirements/GettableSerialPortOption.qbk +/libs/asio/doc/requirements/GettableSocketOption.qbk +/libs/asio/doc/requirements/Handler.qbk +/libs/asio/doc/requirements/HandshakeHandler.qbk +/libs/asio/doc/requirements/InternetProtocol.qbk +/libs/asio/doc/requirements/IoControlCommand.qbk +/libs/asio/doc/requirements/IoObjectService.qbk +/libs/asio/doc/requirements/IteratorConnectHandler.qbk +/libs/asio/doc/requirements/LegacyCompletionHandler.qbk +/libs/asio/doc/requirements/MoveAcceptHandler.qbk +/libs/asio/doc/requirements/MutableBufferSequence.qbk +/libs/asio/doc/requirements/OperationState.qbk +/libs/asio/doc/requirements/ProtoAllocator.qbk +/libs/asio/doc/requirements/Protocol.qbk +/libs/asio/doc/requirements.qbk +/libs/asio/doc/requirements/RangeConnectHandler.qbk +/libs/asio/doc/requirements/ReadHandler.qbk +/libs/asio/doc/requirements/read_write_operations.qbk +/libs/asio/doc/requirements/Receiver.qbk +/libs/asio/doc/requirements/ResolveHandler.qbk +/libs/asio/doc/requirements/Scheduler.qbk +/libs/asio/doc/requirements/Sender.qbk +/libs/asio/doc/requirements/Service.qbk +/libs/asio/doc/requirements/SettableSerialPortOption.qbk +/libs/asio/doc/requirements/SettableSocketOption.qbk +/libs/asio/doc/requirements/ShutdownHandler.qbk +/libs/asio/doc/requirements/SignalHandler.qbk +/libs/asio/doc/requirements/synchronous_socket_operations.qbk +/libs/asio/doc/requirements/SyncRandomAccessReadDevice.qbk +/libs/asio/doc/requirements/SyncRandomAccessWriteDevice.qbk +/libs/asio/doc/requirements/SyncReadStream.qbk +/libs/asio/doc/requirements/SyncWriteStream.qbk +/libs/asio/doc/requirements/TimeTraits.qbk +/libs/asio/doc/requirements/WaitHandler.qbk +/libs/asio/doc/requirements/WaitTraits.qbk +/libs/asio/doc/requirements/WriteHandler.qbk +/libs/asio/doc/std_exception_dox.txt +/libs/asio/doc/tutorial.dox +/libs/asio/doc/tutorial.qbk +/libs/asio/doc/tutorial.xsl +/libs/asio/doc/using.qbk +/libs/asio/example/ +/libs/asio/example/cpp03/ +/libs/asio/example/cpp03/allocation/ +/libs/asio/example/cpp03/allocation/Jamfile.v2 +/libs/asio/example/cpp03/allocation/server.cpp +/libs/asio/example/cpp03/buffers/ +/libs/asio/example/cpp03/buffers/Jamfile.v2 +/libs/asio/example/cpp03/buffers/reference_counted.cpp +/libs/asio/example/cpp03/chat/ +/libs/asio/example/cpp03/chat/chat_client.cpp +/libs/asio/example/cpp03/chat/chat_message.hpp +/libs/asio/example/cpp03/chat/chat_server.cpp +/libs/asio/example/cpp03/chat/Jamfile.v2 +/libs/asio/example/cpp03/chat/posix_chat_client.cpp +/libs/asio/example/cpp03/echo/ +/libs/asio/example/cpp03/echo/async_tcp_echo_server.cpp +/libs/asio/example/cpp03/echo/async_udp_echo_server.cpp +/libs/asio/example/cpp03/echo/blocking_tcp_echo_client.cpp +/libs/asio/example/cpp03/echo/blocking_tcp_echo_server.cpp +/libs/asio/example/cpp03/echo/blocking_udp_echo_client.cpp +/libs/asio/example/cpp03/echo/blocking_udp_echo_server.cpp +/libs/asio/example/cpp03/echo/Jamfile.v2 +/libs/asio/example/cpp03/fork/ +/libs/asio/example/cpp03/fork/daemon.cpp +/libs/asio/example/cpp03/fork/Jamfile.v2 +/libs/asio/example/cpp03/fork/process_per_connection.cpp +/libs/asio/example/cpp03/http/ +/libs/asio/example/cpp03/http/client/ +/libs/asio/example/cpp03/http/client/async_client.cpp +/libs/asio/example/cpp03/http/client/Jamfile.v2 +/libs/asio/example/cpp03/http/client/sync_client.cpp +/libs/asio/example/cpp03/http/doc_root/ +/libs/asio/example/cpp03/http/doc_root/data_1K.html +/libs/asio/example/cpp03/http/doc_root/data_2K.html +/libs/asio/example/cpp03/http/doc_root/data_4K.html +/libs/asio/example/cpp03/http/doc_root/data_8K.html +/libs/asio/example/cpp03/http/server/ +/libs/asio/example/cpp03/http/server2/ +/libs/asio/example/cpp03/http/server2/connection.cpp +/libs/asio/example/cpp03/http/server2/connection.hpp +/libs/asio/example/cpp03/http/server2/header.hpp +/libs/asio/example/cpp03/http/server2/io_context_pool.cpp +/libs/asio/example/cpp03/http/server2/io_context_pool.hpp +/libs/asio/example/cpp03/http/server2/Jamfile.v2 +/libs/asio/example/cpp03/http/server2/main.cpp +/libs/asio/example/cpp03/http/server2/mime_types.cpp +/libs/asio/example/cpp03/http/server2/mime_types.hpp +/libs/asio/example/cpp03/http/server2/reply.cpp +/libs/asio/example/cpp03/http/server2/reply.hpp +/libs/asio/example/cpp03/http/server2/request_handler.cpp +/libs/asio/example/cpp03/http/server2/request_handler.hpp +/libs/asio/example/cpp03/http/server2/request.hpp +/libs/asio/example/cpp03/http/server2/request_parser.cpp +/libs/asio/example/cpp03/http/server2/request_parser.hpp +/libs/asio/example/cpp03/http/server2/server.cpp +/libs/asio/example/cpp03/http/server2/server.hpp +/libs/asio/example/cpp03/http/server3/ +/libs/asio/example/cpp03/http/server3/connection.cpp +/libs/asio/example/cpp03/http/server3/connection.hpp +/libs/asio/example/cpp03/http/server3/header.hpp +/libs/asio/example/cpp03/http/server3/Jamfile.v2 +/libs/asio/example/cpp03/http/server3/main.cpp +/libs/asio/example/cpp03/http/server3/mime_types.cpp +/libs/asio/example/cpp03/http/server3/mime_types.hpp +/libs/asio/example/cpp03/http/server3/reply.cpp +/libs/asio/example/cpp03/http/server3/reply.hpp +/libs/asio/example/cpp03/http/server3/request_handler.cpp +/libs/asio/example/cpp03/http/server3/request_handler.hpp +/libs/asio/example/cpp03/http/server3/request.hpp +/libs/asio/example/cpp03/http/server3/request_parser.cpp +/libs/asio/example/cpp03/http/server3/request_parser.hpp +/libs/asio/example/cpp03/http/server3/server.cpp +/libs/asio/example/cpp03/http/server3/server.hpp +/libs/asio/example/cpp03/http/server4/ +/libs/asio/example/cpp03/http/server4/file_handler.cpp +/libs/asio/example/cpp03/http/server4/file_handler.hpp +/libs/asio/example/cpp03/http/server4/header.hpp +/libs/asio/example/cpp03/http/server4/Jamfile.v2 +/libs/asio/example/cpp03/http/server4/main.cpp +/libs/asio/example/cpp03/http/server4/mime_types.cpp +/libs/asio/example/cpp03/http/server4/mime_types.hpp +/libs/asio/example/cpp03/http/server4/reply.cpp +/libs/asio/example/cpp03/http/server4/reply.hpp +/libs/asio/example/cpp03/http/server4/request.hpp +/libs/asio/example/cpp03/http/server4/request_parser.cpp +/libs/asio/example/cpp03/http/server4/request_parser.hpp +/libs/asio/example/cpp03/http/server4/server.cpp +/libs/asio/example/cpp03/http/server4/server.hpp +/libs/asio/example/cpp03/http/server/connection.cpp +/libs/asio/example/cpp03/http/server/connection.hpp +/libs/asio/example/cpp03/http/server/connection_manager.cpp +/libs/asio/example/cpp03/http/server/connection_manager.hpp +/libs/asio/example/cpp03/http/server/header.hpp +/libs/asio/example/cpp03/http/server/Jamfile.v2 +/libs/asio/example/cpp03/http/server/main.cpp +/libs/asio/example/cpp03/http/server/mime_types.cpp +/libs/asio/example/cpp03/http/server/mime_types.hpp +/libs/asio/example/cpp03/http/server/reply.cpp +/libs/asio/example/cpp03/http/server/reply.hpp +/libs/asio/example/cpp03/http/server/request_handler.cpp +/libs/asio/example/cpp03/http/server/request_handler.hpp +/libs/asio/example/cpp03/http/server/request.hpp +/libs/asio/example/cpp03/http/server/request_parser.cpp +/libs/asio/example/cpp03/http/server/request_parser.hpp +/libs/asio/example/cpp03/http/server/server.cpp +/libs/asio/example/cpp03/http/server/server.hpp +/libs/asio/example/cpp03/icmp/ +/libs/asio/example/cpp03/icmp/icmp_header.hpp +/libs/asio/example/cpp03/icmp/ipv4_header.hpp +/libs/asio/example/cpp03/icmp/Jamfile.v2 +/libs/asio/example/cpp03/icmp/ping.cpp +/libs/asio/example/cpp03/invocation/ +/libs/asio/example/cpp03/invocation/Jamfile.v2 +/libs/asio/example/cpp03/invocation/prioritised_handlers.cpp +/libs/asio/example/cpp03/iostreams/ +/libs/asio/example/cpp03/iostreams/daytime_client.cpp +/libs/asio/example/cpp03/iostreams/daytime_server.cpp +/libs/asio/example/cpp03/iostreams/http_client.cpp +/libs/asio/example/cpp03/iostreams/Jamfile.v2 +/libs/asio/example/cpp03/local/ +/libs/asio/example/cpp03/local/connect_pair.cpp +/libs/asio/example/cpp03/local/iostream_client.cpp +/libs/asio/example/cpp03/local/Jamfile.v2 +/libs/asio/example/cpp03/local/stream_client.cpp +/libs/asio/example/cpp03/local/stream_server.cpp +/libs/asio/example/cpp03/multicast/ +/libs/asio/example/cpp03/multicast/Jamfile.v2 +/libs/asio/example/cpp03/multicast/receiver.cpp +/libs/asio/example/cpp03/multicast/sender.cpp +/libs/asio/example/cpp03/nonblocking/ +/libs/asio/example/cpp03/nonblocking/Jamfile.v2 +/libs/asio/example/cpp03/nonblocking/third_party_lib.cpp +/libs/asio/example/cpp03/porthopper/ +/libs/asio/example/cpp03/porthopper/client.cpp +/libs/asio/example/cpp03/porthopper/Jamfile.v2 +/libs/asio/example/cpp03/porthopper/protocol.hpp +/libs/asio/example/cpp03/porthopper/server.cpp +/libs/asio/example/cpp03/serialization/ +/libs/asio/example/cpp03/serialization/client.cpp +/libs/asio/example/cpp03/serialization/connection.hpp +/libs/asio/example/cpp03/serialization/Jamfile.v2 +/libs/asio/example/cpp03/serialization/server.cpp +/libs/asio/example/cpp03/serialization/stock.hpp +/libs/asio/example/cpp03/services/ +/libs/asio/example/cpp03/services/basic_logger.hpp +/libs/asio/example/cpp03/services/daytime_client.cpp +/libs/asio/example/cpp03/services/Jamfile.v2 +/libs/asio/example/cpp03/services/logger.hpp +/libs/asio/example/cpp03/services/logger_service.cpp +/libs/asio/example/cpp03/services/logger_service.hpp +/libs/asio/example/cpp03/socks4/ +/libs/asio/example/cpp03/socks4/Jamfile.v2 +/libs/asio/example/cpp03/socks4/socks4.hpp +/libs/asio/example/cpp03/socks4/sync_client.cpp +/libs/asio/example/cpp03/spawn/ +/libs/asio/example/cpp03/spawn/echo_server.cpp +/libs/asio/example/cpp03/spawn/Jamfile.v2 +/libs/asio/example/cpp03/spawn/parallel_grep.cpp +/libs/asio/example/cpp03/ssl/ +/libs/asio/example/cpp03/ssl/ca.pem +/libs/asio/example/cpp03/ssl/client.cpp +/libs/asio/example/cpp03/ssl/dh2048.pem +/libs/asio/example/cpp03/ssl/Jamfile.v2 +/libs/asio/example/cpp03/ssl/README +/libs/asio/example/cpp03/ssl/server.cpp +/libs/asio/example/cpp03/ssl/server.pem +/libs/asio/example/cpp03/timeouts/ +/libs/asio/example/cpp03/timeouts/async_tcp_client.cpp +/libs/asio/example/cpp03/timeouts/blocking_tcp_client.cpp +/libs/asio/example/cpp03/timeouts/blocking_token_tcp_client.cpp +/libs/asio/example/cpp03/timeouts/blocking_udp_client.cpp +/libs/asio/example/cpp03/timeouts/Jamfile.v2 +/libs/asio/example/cpp03/timeouts/server.cpp +/libs/asio/example/cpp03/timers/ +/libs/asio/example/cpp03/timers/Jamfile.v2 +/libs/asio/example/cpp03/timers/time_t_timer.cpp +/libs/asio/example/cpp03/tutorial/ +/libs/asio/example/cpp03/tutorial/daytime1/ +/libs/asio/example/cpp03/tutorial/daytime1/client.cpp +/libs/asio/example/cpp03/tutorial/daytime2/ +/libs/asio/example/cpp03/tutorial/daytime2/server.cpp +/libs/asio/example/cpp03/tutorial/daytime3/ +/libs/asio/example/cpp03/tutorial/daytime3/server.cpp +/libs/asio/example/cpp03/tutorial/daytime4/ +/libs/asio/example/cpp03/tutorial/daytime4/client.cpp +/libs/asio/example/cpp03/tutorial/daytime5/ +/libs/asio/example/cpp03/tutorial/daytime5/server.cpp +/libs/asio/example/cpp03/tutorial/daytime6/ +/libs/asio/example/cpp03/tutorial/daytime6/server.cpp +/libs/asio/example/cpp03/tutorial/daytime7/ +/libs/asio/example/cpp03/tutorial/daytime7/server.cpp +/libs/asio/example/cpp03/tutorial/daytime_dox.txt +/libs/asio/example/cpp03/tutorial/index_dox.txt +/libs/asio/example/cpp03/tutorial/Jamfile.v2 +/libs/asio/example/cpp03/tutorial/timer1/ +/libs/asio/example/cpp03/tutorial/timer1/timer.cpp +/libs/asio/example/cpp03/tutorial/timer2/ +/libs/asio/example/cpp03/tutorial/timer2/timer.cpp +/libs/asio/example/cpp03/tutorial/timer3/ +/libs/asio/example/cpp03/tutorial/timer3/timer.cpp +/libs/asio/example/cpp03/tutorial/timer4/ +/libs/asio/example/cpp03/tutorial/timer4/timer.cpp +/libs/asio/example/cpp03/tutorial/timer5/ +/libs/asio/example/cpp03/tutorial/timer5/timer.cpp +/libs/asio/example/cpp03/tutorial/timer_dox.txt +/libs/asio/example/cpp03/windows/ +/libs/asio/example/cpp03/windows/Jamfile.v2 +/libs/asio/example/cpp03/windows/transmit_file.cpp +/libs/asio/example/cpp11/ +/libs/asio/example/cpp11/allocation/ +/libs/asio/example/cpp11/allocation/Jamfile.v2 +/libs/asio/example/cpp11/allocation/server.cpp +/libs/asio/example/cpp11/buffers/ +/libs/asio/example/cpp11/buffers/Jamfile.v2 +/libs/asio/example/cpp11/buffers/reference_counted.cpp +/libs/asio/example/cpp11/chat/ +/libs/asio/example/cpp11/chat/chat_client.cpp +/libs/asio/example/cpp11/chat/chat_message.hpp +/libs/asio/example/cpp11/chat/chat_server.cpp +/libs/asio/example/cpp11/chat/Jamfile.v2 +/libs/asio/example/cpp11/echo/ +/libs/asio/example/cpp11/echo/async_tcp_echo_server.cpp +/libs/asio/example/cpp11/echo/async_udp_echo_server.cpp +/libs/asio/example/cpp11/echo/blocking_tcp_echo_client.cpp +/libs/asio/example/cpp11/echo/blocking_tcp_echo_server.cpp +/libs/asio/example/cpp11/echo/blocking_udp_echo_client.cpp +/libs/asio/example/cpp11/echo/blocking_udp_echo_server.cpp +/libs/asio/example/cpp11/echo/Jamfile.v2 +/libs/asio/example/cpp11/executors/ +/libs/asio/example/cpp11/executors/actor.cpp +/libs/asio/example/cpp11/executors/bank_account_1.cpp +/libs/asio/example/cpp11/executors/bank_account_2.cpp +/libs/asio/example/cpp11/executors/fork_join.cpp +/libs/asio/example/cpp11/executors/Jamfile.v2 +/libs/asio/example/cpp11/executors/pipeline.cpp +/libs/asio/example/cpp11/executors/priority_scheduler.cpp +/libs/asio/example/cpp11/fork/ +/libs/asio/example/cpp11/fork/daemon.cpp +/libs/asio/example/cpp11/fork/Jamfile.v2 +/libs/asio/example/cpp11/fork/process_per_connection.cpp +/libs/asio/example/cpp11/futures/ +/libs/asio/example/cpp11/futures/daytime_client.cpp +/libs/asio/example/cpp11/futures/Jamfile.v2 +/libs/asio/example/cpp11/handler_tracking/ +/libs/asio/example/cpp11/handler_tracking/async_tcp_echo_server.cpp +/libs/asio/example/cpp11/handler_tracking/custom_tracking.hpp +/libs/asio/example/cpp11/handler_tracking/Jamfile.v2 +/libs/asio/example/cpp11/http/ +/libs/asio/example/cpp11/http/server/ +/libs/asio/example/cpp11/http/server/connection.cpp +/libs/asio/example/cpp11/http/server/connection.hpp +/libs/asio/example/cpp11/http/server/connection_manager.cpp +/libs/asio/example/cpp11/http/server/connection_manager.hpp +/libs/asio/example/cpp11/http/server/header.hpp +/libs/asio/example/cpp11/http/server/Jamfile.v2 +/libs/asio/example/cpp11/http/server/main.cpp +/libs/asio/example/cpp11/http/server/mime_types.cpp +/libs/asio/example/cpp11/http/server/mime_types.hpp +/libs/asio/example/cpp11/http/server/reply.cpp +/libs/asio/example/cpp11/http/server/reply.hpp +/libs/asio/example/cpp11/http/server/request_handler.cpp +/libs/asio/example/cpp11/http/server/request_handler.hpp +/libs/asio/example/cpp11/http/server/request.hpp +/libs/asio/example/cpp11/http/server/request_parser.cpp +/libs/asio/example/cpp11/http/server/request_parser.hpp +/libs/asio/example/cpp11/http/server/server.cpp +/libs/asio/example/cpp11/http/server/server.hpp +/libs/asio/example/cpp11/invocation/ +/libs/asio/example/cpp11/invocation/Jamfile.v2 +/libs/asio/example/cpp11/invocation/prioritised_handlers.cpp +/libs/asio/example/cpp11/iostreams/ +/libs/asio/example/cpp11/iostreams/http_client.cpp +/libs/asio/example/cpp11/iostreams/Jamfile.v2 +/libs/asio/example/cpp11/local/ +/libs/asio/example/cpp11/local/connect_pair.cpp +/libs/asio/example/cpp11/local/iostream_client.cpp +/libs/asio/example/cpp11/local/Jamfile.v2 +/libs/asio/example/cpp11/local/stream_client.cpp +/libs/asio/example/cpp11/local/stream_server.cpp +/libs/asio/example/cpp11/multicast/ +/libs/asio/example/cpp11/multicast/Jamfile.v2 +/libs/asio/example/cpp11/multicast/receiver.cpp +/libs/asio/example/cpp11/multicast/sender.cpp +/libs/asio/example/cpp11/nonblocking/ +/libs/asio/example/cpp11/nonblocking/Jamfile.v2 +/libs/asio/example/cpp11/nonblocking/third_party_lib.cpp +/libs/asio/example/cpp11/operations/ +/libs/asio/example/cpp11/operations/composed_1.cpp +/libs/asio/example/cpp11/operations/composed_2.cpp +/libs/asio/example/cpp11/operations/composed_3.cpp +/libs/asio/example/cpp11/operations/composed_4.cpp +/libs/asio/example/cpp11/operations/composed_5.cpp +/libs/asio/example/cpp11/operations/composed_6.cpp +/libs/asio/example/cpp11/operations/composed_7.cpp +/libs/asio/example/cpp11/operations/composed_8.cpp +/libs/asio/example/cpp11/operations/Jamfile.v2 +/libs/asio/example/cpp11/socks4/ +/libs/asio/example/cpp11/socks4/Jamfile.v2 +/libs/asio/example/cpp11/socks4/socks4.hpp +/libs/asio/example/cpp11/socks4/sync_client.cpp +/libs/asio/example/cpp11/spawn/ +/libs/asio/example/cpp11/spawn/echo_server.cpp +/libs/asio/example/cpp11/spawn/Jamfile.v2 +/libs/asio/example/cpp11/spawn/parallel_grep.cpp +/libs/asio/example/cpp11/ssl/ +/libs/asio/example/cpp11/ssl/ca.pem +/libs/asio/example/cpp11/ssl/client.cpp +/libs/asio/example/cpp11/ssl/dh2048.pem +/libs/asio/example/cpp11/ssl/Jamfile.v2 +/libs/asio/example/cpp11/ssl/README +/libs/asio/example/cpp11/ssl/server.cpp +/libs/asio/example/cpp11/ssl/server.pem +/libs/asio/example/cpp11/timeouts/ +/libs/asio/example/cpp11/timeouts/async_tcp_client.cpp +/libs/asio/example/cpp11/timeouts/blocking_tcp_client.cpp +/libs/asio/example/cpp11/timeouts/blocking_token_tcp_client.cpp +/libs/asio/example/cpp11/timeouts/blocking_udp_client.cpp +/libs/asio/example/cpp11/timeouts/Jamfile.v2 +/libs/asio/example/cpp11/timeouts/server.cpp +/libs/asio/example/cpp11/timers/ +/libs/asio/example/cpp11/timers/Jamfile.v2 +/libs/asio/example/cpp11/timers/time_t_timer.cpp +/libs/asio/example/cpp14/ +/libs/asio/example/cpp14/executors/ +/libs/asio/example/cpp14/executors/actor.cpp +/libs/asio/example/cpp14/executors/async_1.cpp +/libs/asio/example/cpp14/executors/async_2.cpp +/libs/asio/example/cpp14/executors/bank_account_1.cpp +/libs/asio/example/cpp14/executors/bank_account_2.cpp +/libs/asio/example/cpp14/executors/fork_join.cpp +/libs/asio/example/cpp14/executors/Jamfile.v2 +/libs/asio/example/cpp14/executors/pipeline.cpp +/libs/asio/example/cpp14/executors/priority_scheduler.cpp +/libs/asio/example/cpp14/operations/ +/libs/asio/example/cpp14/operations/composed_1.cpp +/libs/asio/example/cpp14/operations/composed_2.cpp +/libs/asio/example/cpp14/operations/composed_3.cpp +/libs/asio/example/cpp14/operations/composed_4.cpp +/libs/asio/example/cpp14/operations/composed_5.cpp +/libs/asio/example/cpp14/operations/composed_6.cpp +/libs/asio/example/cpp14/operations/composed_7.cpp +/libs/asio/example/cpp14/operations/composed_8.cpp +/libs/asio/example/cpp14/operations/Jamfile.v2 +/libs/asio/example/cpp17/ +/libs/asio/example/cpp17/coroutines_ts/ +/libs/asio/example/cpp17/coroutines_ts/chat_server.cpp +/libs/asio/example/cpp17/coroutines_ts/echo_server.cpp +/libs/asio/example/cpp17/coroutines_ts/echo_server_with_default.cpp +/libs/asio/example/cpp17/coroutines_ts/range_based_for.cpp +/libs/asio/example/cpp17/coroutines_ts/refactored_echo_server.cpp +/libs/asio/.github/ +/libs/asio/.github/ISSUE_TEMPLATE/ +/libs/asio/.github/ISSUE_TEMPLATE/config.yml +/libs/asio/.github/move.yml +/libs/asio/.github/PULL_REQUEST_TEMPLATE.md +/libs/asio/index.html +/libs/asio/meta/ +/libs/asio/meta/libraries.json +/libs/asio/test/ +/libs/asio/test/archetypes/ +/libs/asio/test/archetypes/async_ops.hpp +/libs/asio/test/archetypes/async_result.hpp +/libs/asio/test/archetypes/gettable_socket_option.hpp +/libs/asio/test/archetypes/io_control_command.hpp +/libs/asio/test/archetypes/settable_socket_option.hpp +/libs/asio/test/associated_allocator.cpp +/libs/asio/test/associated_executor.cpp +/libs/asio/test/async_result.cpp +/libs/asio/test/awaitable.cpp +/libs/asio/test/basic_datagram_socket.cpp +/libs/asio/test/basic_deadline_timer.cpp +/libs/asio/test/basic_raw_socket.cpp +/libs/asio/test/basic_seq_packet_socket.cpp +/libs/asio/test/basic_serial_port.cpp +/libs/asio/test/basic_signal_set.cpp +/libs/asio/test/basic_socket_acceptor.cpp +/libs/asio/test/basic_socket.cpp +/libs/asio/test/basic_streambuf.cpp +/libs/asio/test/basic_stream_socket.cpp +/libs/asio/test/basic_waitable_timer.cpp +/libs/asio/test/bind_executor.cpp +/libs/asio/test/buffer.cpp +/libs/asio/test/buffered_read_stream.cpp +/libs/asio/test/buffered_stream.cpp +/libs/asio/test/buffered_write_stream.cpp +/libs/asio/test/buffers_iterator.cpp +/libs/asio/test/completion_condition.cpp +/libs/asio/test/compose.cpp +/libs/asio/test/connect.cpp +/libs/asio/test/coroutine.cpp +/libs/asio/test/co_spawn.cpp +/libs/asio/test/deadline_timer.cpp +/libs/asio/test/defer.cpp +/libs/asio/test/detached.cpp +/libs/asio/test/dispatch.cpp +/libs/asio/test/error.cpp +/libs/asio/test/execution/ +/libs/asio/test/execution/any_executor.cpp +/libs/asio/test/execution/blocking_adaptation.cpp +/libs/asio/test/execution/blocking.cpp +/libs/asio/test/execution/bulk_execute.cpp +/libs/asio/test/execution/bulk_guarantee.cpp +/libs/asio/test/execution/connect.cpp +/libs/asio/test/execution/context_as.cpp +/libs/asio/test/execution_context.cpp +/libs/asio/test/execution/execute.cpp +/libs/asio/test/execution/executor.cpp +/libs/asio/test/execution/invocable_archetype.cpp +/libs/asio/test/execution/Jamfile.v2 +/libs/asio/test/execution/mapping.cpp +/libs/asio/test/execution/operation_state.cpp +/libs/asio/test/execution/outstanding_work.cpp +/libs/asio/test/execution/prefer_only.cpp +/libs/asio/test/execution/receiver.cpp +/libs/asio/test/execution/relationship.cpp +/libs/asio/test/execution/schedule.cpp +/libs/asio/test/execution/scheduler.cpp +/libs/asio/test/execution/sender.cpp +/libs/asio/test/execution/set_done.cpp +/libs/asio/test/execution/set_error.cpp +/libs/asio/test/execution/set_value.cpp +/libs/asio/test/execution/start.cpp +/libs/asio/test/execution/submit.cpp +/libs/asio/test/executor.cpp +/libs/asio/test/executor_work_guard.cpp +/libs/asio/test/generic/ +/libs/asio/test/generic/basic_endpoint.cpp +/libs/asio/test/generic/datagram_protocol.cpp +/libs/asio/test/generic/raw_protocol.cpp +/libs/asio/test/generic/seq_packet_protocol.cpp +/libs/asio/test/generic/stream_protocol.cpp +/libs/asio/test/high_resolution_timer.cpp +/libs/asio/test/io_context.cpp +/libs/asio/test/io_context_strand.cpp +/libs/asio/test/ip/ +/libs/asio/test/ip/address.cpp +/libs/asio/test/ip/address_v4.cpp +/libs/asio/test/ip/address_v4_iterator.cpp +/libs/asio/test/ip/address_v4_range.cpp +/libs/asio/test/ip/address_v6.cpp +/libs/asio/test/ip/address_v6_iterator.cpp +/libs/asio/test/ip/address_v6_range.cpp +/libs/asio/test/ip/basic_endpoint.cpp +/libs/asio/test/ip/basic_resolver.cpp +/libs/asio/test/ip/basic_resolver_entry.cpp +/libs/asio/test/ip/basic_resolver_iterator.cpp +/libs/asio/test/ip/basic_resolver_query.cpp +/libs/asio/test/ip/host_name.cpp +/libs/asio/test/ip/icmp.cpp +/libs/asio/test/ip/multicast.cpp +/libs/asio/test/ip/network_v4.cpp +/libs/asio/test/ip/network_v6.cpp +/libs/asio/test/ip/resolver_query_base.cpp +/libs/asio/test/ip/tcp.cpp +/libs/asio/test/ip/udp.cpp +/libs/asio/test/ip/unicast.cpp +/libs/asio/test/ip/v6_only.cpp +/libs/asio/test/is_read_buffered.cpp +/libs/asio/test/is_write_buffered.cpp +/libs/asio/test/Jamfile.v2 +/libs/asio/test/latency/ +/libs/asio/test/latency/allocator.hpp +/libs/asio/test/latency/high_res_clock.hpp +/libs/asio/test/latency/Jamfile.v2 +/libs/asio/test/latency/tcp_client.cpp +/libs/asio/test/latency/tcp_server.cpp +/libs/asio/test/latency/udp_client.cpp +/libs/asio/test/latency/udp_server.cpp +/libs/asio/test/local/ +/libs/asio/test/local/basic_endpoint.cpp +/libs/asio/test/local/connect_pair.cpp +/libs/asio/test/local/datagram_protocol.cpp +/libs/asio/test/local/stream_protocol.cpp +/libs/asio/test/packaged_task.cpp +/libs/asio/test/placeholders.cpp +/libs/asio/test/posix/ +/libs/asio/test/posix/basic_descriptor.cpp +/libs/asio/test/posix/basic_stream_descriptor.cpp +/libs/asio/test/posix/descriptor_base.cpp +/libs/asio/test/posix/descriptor.cpp +/libs/asio/test/posix/stream_descriptor.cpp +/libs/asio/test/post.cpp +/libs/asio/test/properties/ +/libs/asio/test/properties/cpp03/ +/libs/asio/test/properties/cpp03/can_prefer_free_prefer.cpp +/libs/asio/test/properties/cpp03/can_prefer_free_require.cpp +/libs/asio/test/properties/cpp03/can_prefer_member_prefer.cpp +/libs/asio/test/properties/cpp03/can_prefer_member_require.cpp +/libs/asio/test/properties/cpp03/can_prefer_not_applicable_free_prefer.cpp +/libs/asio/test/properties/cpp03/can_prefer_not_applicable_free_require.cpp +/libs/asio/test/properties/cpp03/can_prefer_not_applicable_member_prefer.cpp +/libs/asio/test/properties/cpp03/can_prefer_not_applicable_member_require.cpp +/libs/asio/test/properties/cpp03/can_prefer_not_applicable_static.cpp +/libs/asio/test/properties/cpp03/can_prefer_not_applicable_unsupported.cpp +/libs/asio/test/properties/cpp03/can_prefer_not_preferable_free_prefer.cpp +/libs/asio/test/properties/cpp03/can_prefer_not_preferable_free_require.cpp +/libs/asio/test/properties/cpp03/can_prefer_not_preferable_member_prefer.cpp +/libs/asio/test/properties/cpp03/can_prefer_not_preferable_member_require.cpp +/libs/asio/test/properties/cpp03/can_prefer_not_preferable_static.cpp +/libs/asio/test/properties/cpp03/can_prefer_not_preferable_unsupported.cpp +/libs/asio/test/properties/cpp03/can_prefer_static.cpp +/libs/asio/test/properties/cpp03/can_prefer_unsupported.cpp +/libs/asio/test/properties/cpp03/can_query_free.cpp +/libs/asio/test/properties/cpp03/can_query_member.cpp +/libs/asio/test/properties/cpp03/can_query_not_applicable_free.cpp +/libs/asio/test/properties/cpp03/can_query_not_applicable_member.cpp +/libs/asio/test/properties/cpp03/can_query_not_applicable_static.cpp +/libs/asio/test/properties/cpp03/can_query_not_applicable_unsupported.cpp +/libs/asio/test/properties/cpp03/can_query_static.cpp +/libs/asio/test/properties/cpp03/can_query_unsupported.cpp +/libs/asio/test/properties/cpp03/can_require_concept_free.cpp +/libs/asio/test/properties/cpp03/can_require_concept_member.cpp +/libs/asio/test/properties/cpp03/can_require_concept_not_applicable_free.cpp +/libs/asio/test/properties/cpp03/can_require_concept_not_applicable_member.cpp +/libs/asio/test/properties/cpp03/can_require_concept_not_applicable_static.cpp +/libs/asio/test/properties/cpp03/can_require_concept_not_applicable_unsupported.cpp +/libs/asio/test/properties/cpp03/can_require_concept_static.cpp +/libs/asio/test/properties/cpp03/can_require_concept_unsupported.cpp +/libs/asio/test/properties/cpp03/can_require_free.cpp +/libs/asio/test/properties/cpp03/can_require_member.cpp +/libs/asio/test/properties/cpp03/can_require_not_applicable_free.cpp +/libs/asio/test/properties/cpp03/can_require_not_applicable_member.cpp +/libs/asio/test/properties/cpp03/can_require_not_applicable_static.cpp +/libs/asio/test/properties/cpp03/can_require_not_applicable_unsupported.cpp +/libs/asio/test/properties/cpp03/can_require_static.cpp +/libs/asio/test/properties/cpp03/can_require_unsupported.cpp +/libs/asio/test/properties/cpp03/Jamfile.v2 +/libs/asio/test/properties/cpp03/prefer_free_prefer.cpp +/libs/asio/test/properties/cpp03/prefer_free_require.cpp +/libs/asio/test/properties/cpp03/prefer_member_prefer.cpp +/libs/asio/test/properties/cpp03/prefer_member_require.cpp +/libs/asio/test/properties/cpp03/prefer_static.cpp +/libs/asio/test/properties/cpp03/prefer_unsupported.cpp +/libs/asio/test/properties/cpp03/query_free.cpp +/libs/asio/test/properties/cpp03/query_member.cpp +/libs/asio/test/properties/cpp03/query_static.cpp +/libs/asio/test/properties/cpp03/require_concept_free.cpp +/libs/asio/test/properties/cpp03/require_concept_member.cpp +/libs/asio/test/properties/cpp03/require_concept_static.cpp +/libs/asio/test/properties/cpp03/require_free.cpp +/libs/asio/test/properties/cpp03/require_member.cpp +/libs/asio/test/properties/cpp03/require_static.cpp +/libs/asio/test/properties/cpp11/ +/libs/asio/test/properties/cpp11/can_prefer_free_prefer.cpp +/libs/asio/test/properties/cpp11/can_prefer_free_require.cpp +/libs/asio/test/properties/cpp11/can_prefer_member_prefer.cpp +/libs/asio/test/properties/cpp11/can_prefer_member_require.cpp +/libs/asio/test/properties/cpp11/can_prefer_not_applicable_free_prefer.cpp +/libs/asio/test/properties/cpp11/can_prefer_not_applicable_free_require.cpp +/libs/asio/test/properties/cpp11/can_prefer_not_applicable_member_prefer.cpp +/libs/asio/test/properties/cpp11/can_prefer_not_applicable_member_require.cpp +/libs/asio/test/properties/cpp11/can_prefer_not_applicable_static.cpp +/libs/asio/test/properties/cpp11/can_prefer_not_applicable_unsupported.cpp +/libs/asio/test/properties/cpp11/can_prefer_not_preferable_free_prefer.cpp +/libs/asio/test/properties/cpp11/can_prefer_not_preferable_free_require.cpp +/libs/asio/test/properties/cpp11/can_prefer_not_preferable_member_prefer.cpp +/libs/asio/test/properties/cpp11/can_prefer_not_preferable_member_require.cpp +/libs/asio/test/properties/cpp11/can_prefer_not_preferable_static.cpp +/libs/asio/test/properties/cpp11/can_prefer_not_preferable_unsupported.cpp +/libs/asio/test/properties/cpp11/can_prefer_static.cpp +/libs/asio/test/properties/cpp11/can_prefer_unsupported.cpp +/libs/asio/test/properties/cpp11/can_query_free.cpp +/libs/asio/test/properties/cpp11/can_query_member.cpp +/libs/asio/test/properties/cpp11/can_query_not_applicable_free.cpp +/libs/asio/test/properties/cpp11/can_query_not_applicable_member.cpp +/libs/asio/test/properties/cpp11/can_query_not_applicable_static.cpp +/libs/asio/test/properties/cpp11/can_query_not_applicable_unsupported.cpp +/libs/asio/test/properties/cpp11/can_query_static.cpp +/libs/asio/test/properties/cpp11/can_query_unsupported.cpp +/libs/asio/test/properties/cpp11/can_require_concept_free.cpp +/libs/asio/test/properties/cpp11/can_require_concept_member.cpp +/libs/asio/test/properties/cpp11/can_require_concept_not_applicable_free.cpp +/libs/asio/test/properties/cpp11/can_require_concept_not_applicable_member.cpp +/libs/asio/test/properties/cpp11/can_require_concept_not_applicable_static.cpp +/libs/asio/test/properties/cpp11/can_require_concept_not_applicable_unsupported.cpp +/libs/asio/test/properties/cpp11/can_require_concept_static.cpp +/libs/asio/test/properties/cpp11/can_require_concept_unsupported.cpp +/libs/asio/test/properties/cpp11/can_require_free.cpp +/libs/asio/test/properties/cpp11/can_require_member.cpp +/libs/asio/test/properties/cpp11/can_require_not_applicable_free.cpp +/libs/asio/test/properties/cpp11/can_require_not_applicable_member.cpp +/libs/asio/test/properties/cpp11/can_require_not_applicable_static.cpp +/libs/asio/test/properties/cpp11/can_require_not_applicable_unsupported.cpp +/libs/asio/test/properties/cpp11/can_require_static.cpp +/libs/asio/test/properties/cpp11/can_require_unsupported.cpp +/libs/asio/test/properties/cpp11/Jamfile.v2 +/libs/asio/test/properties/cpp11/prefer_free_prefer.cpp +/libs/asio/test/properties/cpp11/prefer_free_require.cpp +/libs/asio/test/properties/cpp11/prefer_member_prefer.cpp +/libs/asio/test/properties/cpp11/prefer_member_require.cpp +/libs/asio/test/properties/cpp11/prefer_static.cpp +/libs/asio/test/properties/cpp11/prefer_unsupported.cpp +/libs/asio/test/properties/cpp11/query_free.cpp +/libs/asio/test/properties/cpp11/query_member.cpp +/libs/asio/test/properties/cpp11/query_static.cpp +/libs/asio/test/properties/cpp11/require_concept_free.cpp +/libs/asio/test/properties/cpp11/require_concept_member.cpp +/libs/asio/test/properties/cpp11/require_concept_static.cpp +/libs/asio/test/properties/cpp11/require_free.cpp +/libs/asio/test/properties/cpp11/require_member.cpp +/libs/asio/test/properties/cpp11/require_static.cpp +/libs/asio/test/properties/cpp14/ +/libs/asio/test/properties/cpp14/can_prefer_free_prefer.cpp +/libs/asio/test/properties/cpp14/can_prefer_free_require.cpp +/libs/asio/test/properties/cpp14/can_prefer_member_prefer.cpp +/libs/asio/test/properties/cpp14/can_prefer_member_require.cpp +/libs/asio/test/properties/cpp14/can_prefer_not_applicable_free_prefer.cpp +/libs/asio/test/properties/cpp14/can_prefer_not_applicable_free_require.cpp +/libs/asio/test/properties/cpp14/can_prefer_not_applicable_member_prefer.cpp +/libs/asio/test/properties/cpp14/can_prefer_not_applicable_member_require.cpp +/libs/asio/test/properties/cpp14/can_prefer_not_applicable_static.cpp +/libs/asio/test/properties/cpp14/can_prefer_not_applicable_unsupported.cpp +/libs/asio/test/properties/cpp14/can_prefer_not_preferable_free_prefer.cpp +/libs/asio/test/properties/cpp14/can_prefer_not_preferable_free_require.cpp +/libs/asio/test/properties/cpp14/can_prefer_not_preferable_member_prefer.cpp +/libs/asio/test/properties/cpp14/can_prefer_not_preferable_member_require.cpp +/libs/asio/test/properties/cpp14/can_prefer_not_preferable_static.cpp +/libs/asio/test/properties/cpp14/can_prefer_not_preferable_unsupported.cpp +/libs/asio/test/properties/cpp14/can_prefer_static.cpp +/libs/asio/test/properties/cpp14/can_prefer_unsupported.cpp +/libs/asio/test/properties/cpp14/can_query_free.cpp +/libs/asio/test/properties/cpp14/can_query_member.cpp +/libs/asio/test/properties/cpp14/can_query_not_applicable_free.cpp +/libs/asio/test/properties/cpp14/can_query_not_applicable_member.cpp +/libs/asio/test/properties/cpp14/can_query_not_applicable_static.cpp +/libs/asio/test/properties/cpp14/can_query_not_applicable_unsupported.cpp +/libs/asio/test/properties/cpp14/can_query_static.cpp +/libs/asio/test/properties/cpp14/can_query_unsupported.cpp +/libs/asio/test/properties/cpp14/can_require_concept_free.cpp +/libs/asio/test/properties/cpp14/can_require_concept_member.cpp +/libs/asio/test/properties/cpp14/can_require_concept_not_applicable_free.cpp +/libs/asio/test/properties/cpp14/can_require_concept_not_applicable_member.cpp +/libs/asio/test/properties/cpp14/can_require_concept_not_applicable_static.cpp +/libs/asio/test/properties/cpp14/can_require_concept_not_applicable_unsupported.cpp +/libs/asio/test/properties/cpp14/can_require_concept_static.cpp +/libs/asio/test/properties/cpp14/can_require_concept_unsupported.cpp +/libs/asio/test/properties/cpp14/can_require_free.cpp +/libs/asio/test/properties/cpp14/can_require_member.cpp +/libs/asio/test/properties/cpp14/can_require_not_applicable_free.cpp +/libs/asio/test/properties/cpp14/can_require_not_applicable_member.cpp +/libs/asio/test/properties/cpp14/can_require_not_applicable_static.cpp +/libs/asio/test/properties/cpp14/can_require_not_applicable_unsupported.cpp +/libs/asio/test/properties/cpp14/can_require_static.cpp +/libs/asio/test/properties/cpp14/can_require_unsupported.cpp +/libs/asio/test/properties/cpp14/Jamfile.v2 +/libs/asio/test/properties/cpp14/prefer_free_prefer.cpp +/libs/asio/test/properties/cpp14/prefer_free_require.cpp +/libs/asio/test/properties/cpp14/prefer_member_prefer.cpp +/libs/asio/test/properties/cpp14/prefer_member_require.cpp +/libs/asio/test/properties/cpp14/prefer_static.cpp +/libs/asio/test/properties/cpp14/prefer_unsupported.cpp +/libs/asio/test/properties/cpp14/query_free.cpp +/libs/asio/test/properties/cpp14/query_member.cpp +/libs/asio/test/properties/cpp14/query_static.cpp +/libs/asio/test/properties/cpp14/require_concept_free.cpp +/libs/asio/test/properties/cpp14/require_concept_member.cpp +/libs/asio/test/properties/cpp14/require_concept_static.cpp +/libs/asio/test/properties/cpp14/require_free.cpp +/libs/asio/test/properties/cpp14/require_member.cpp +/libs/asio/test/properties/cpp14/require_static.cpp +/libs/asio/test/read_at.cpp +/libs/asio/test/read.cpp +/libs/asio/test/read_until.cpp +/libs/asio/test/redirect_error.cpp +/libs/asio/test/serial_port_base.cpp +/libs/asio/test/serial_port.cpp +/libs/asio/test/signal_set.cpp +/libs/asio/test/socket_base.cpp +/libs/asio/test/ssl/ +/libs/asio/test/ssl/context_base.cpp +/libs/asio/test/ssl/context.cpp +/libs/asio/test/ssl/error.cpp +/libs/asio/test/ssl/host_name_verification.cpp +/libs/asio/test/ssl/Jamfile.v2 +/libs/asio/test/ssl/rfc2818_verification.cpp +/libs/asio/test/ssl/stream_base.cpp +/libs/asio/test/ssl/stream.cpp +/libs/asio/test/static_thread_pool.cpp +/libs/asio/test/steady_timer.cpp +/libs/asio/test/strand.cpp +/libs/asio/test/streambuf.cpp +/libs/asio/test/system_context.cpp +/libs/asio/test/system_executor.cpp +/libs/asio/test/system_timer.cpp +/libs/asio/test/this_coro.cpp +/libs/asio/test/thread_pool.cpp +/libs/asio/test/time_traits.cpp +/libs/asio/test/ts/ +/libs/asio/test/ts/buffer.cpp +/libs/asio/test/ts/executor.cpp +/libs/asio/test/ts/internet.cpp +/libs/asio/test/ts/io_context.cpp +/libs/asio/test/ts/net.cpp +/libs/asio/test/ts/netfwd.cpp +/libs/asio/test/ts/socket.cpp +/libs/asio/test/ts/timer.cpp +/libs/asio/test/unit_test.hpp +/libs/asio/test/use_awaitable.cpp +/libs/asio/test/use_future.cpp +/libs/asio/test/uses_executor.cpp +/libs/asio/test/wait_traits.cpp +/libs/asio/test/windows/ +/libs/asio/test/windows/basic_object_handle.cpp +/libs/asio/test/windows/basic_overlapped_handle.cpp +/libs/asio/test/windows/basic_random_access_handle.cpp +/libs/asio/test/windows/basic_stream_handle.cpp +/libs/asio/test/windows/object_handle.cpp +/libs/asio/test/windows/overlapped_handle.cpp +/libs/asio/test/windows/overlapped_ptr.cpp +/libs/asio/test/windows/random_access_handle.cpp +/libs/asio/test/windows/stream_handle.cpp +/libs/asio/test/write_at.cpp +/libs/asio/test/write.cpp +/libs/asio/tools/ +/libs/asio/tools/handlerlive.pl +/libs/asio/tools/handlertree.pl +/libs/asio/tools/handlerviz.pl +/libs/system/ +/libs/system/appveyor.yml +/libs/system/build/ +/libs/system/build/Jamfile +/libs/system/build/Jamfile.v2 +/libs/system/CMakeLists.txt +/libs/system/doc/ +/libs/system/doc/Jamfile +/libs/system/doc/system/ +/libs/system/doc/system/acknowledgements.adoc +/libs/system/doc/system.adoc +/libs/system/doc/system/changes.adoc +/libs/system/doc/system/copyright.adoc +/libs/system/doc/system-docinfo-footer.html +/libs/system/doc/system/history.adoc +/libs/system/doc/system/introduction.adoc +/libs/system/doc/system/rationale.adoc +/libs/system/doc/system/reference.adoc +/libs/system/index.html +/libs/system/meta/ +/libs/system/meta/libraries.json +/libs/system/src/ +/libs/system/src/error_code.cpp +/libs/system/test/ +/libs/system/test/after_main_test.cpp +/libs/system/test/before_main_test.cpp +/libs/system/test/cmake_install_test/ +/libs/system/test/cmake_install_test/CMakeLists.txt +/libs/system/test/CMakeLists.txt +/libs/system/test/cmake_subdir_test/ +/libs/system/test/cmake_subdir_test/CMakeLists.txt +/libs/system/test/config_test.cpp +/libs/system/test/constexpr_test.cpp +/libs/system/test/dynamic_link_test.cpp +/libs/system/test/error_category_test.cpp +/libs/system/test/error_code_test.cpp +/libs/system/test/error_code_user_test.cpp +/libs/system/test/failed_constexpr_test.cpp +/libs/system/test/failed_test.cpp +/libs/system/test/generic_category_test.cpp +/libs/system/test/header_only_test.cpp +/libs/system/test/initialization_test.cpp +/libs/system/test/Jamfile.v2 +/libs/system/test/msvc/ +/libs/system/test/msvc/common.props +/libs/system/test/msvc/config_test/ +/libs/system/test/msvc/config_test/config_test.vcxproj +/libs/system/test/msvc/error_code_test/ +/libs/system/test/msvc/error_code_test/error_code_test.vcxproj +/libs/system/test/msvc/header_only_error_code_test/ +/libs/system/test/msvc/header_only_error_code_test/header_only_error_code_test.vcxproj +/libs/system/test/msvc/header_only_test/ +/libs/system/test/msvc/header_only_test/header_only_test.vcxproj +/libs/system/test/msvc/std_interop_test/ +/libs/system/test/msvc/std_interop_test/std_interop_test.vcxproj +/libs/system/test/msvc/system-dll/ +/libs/system/test/msvc/system-dll/system-dll.vcxproj +/libs/system/test/msvc/system.sln +/libs/system/test/quick.cpp +/libs/system/test/single_instance_1.cpp +/libs/system/test/single_instance_2.cpp +/libs/system/test/single_instance_test.cpp +/libs/system/test/std_interop_test.cpp +/libs/system/test/std_mismatch_test.cpp +/libs/system/test/std_single_instance_1.cpp +/libs/system/test/std_single_instance_2.cpp +/libs/system/test/std_single_instance_test.cpp +/libs/system/test/system_category_test.cpp +/libs/system/test/system_error_test.cpp +/libs/system/test/throws_assign_fail.cpp +/libs/system/test/throw_test.cpp +/libs/system/test/warnings_test.cpp +/libs/system/test/win32_hresult_test.cpp +/libs/system/.travis.yml +/README.txt diff --git a/tidal-link/link/modules/asio-standalone/asio/boostify.pl b/tidal-link/link/modules/asio-standalone/asio/boostify.pl new file mode 100644 index 000000000..460aab952 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/boostify.pl @@ -0,0 +1,635 @@ +#!/usr/bin/perl -w + +use strict; +use File::Path; + +our $boost_dir = "boostified"; + +sub print_line +{ + my ($output, $line, $from, $lineno) = @_; + + # Warn if the resulting line is >80 characters wide. + if (length($line) > 80) + { + if ($from =~ /\.[chi]pp$/) + { + print("Warning: $from:$lineno: output >80 characters wide.\n"); + } + } + + # Write the output. + print($output $line . "\n"); +} + +sub source_contains_asio_thread_usage +{ + my ($from) = @_; + + # Open the input file. + open(my $input, "<$from") or die("Can't open $from for reading"); + + # Check file for use of asio::thread. + while (my $line = <$input>) + { + chomp($line); + if ($line =~ /asio::thread/) + { + close($input); + return 1; + } + elsif ($line =~ /^ *thread /) + { + close($input); + return 1; + } + } + + close($input); + return 0; +} + +sub source_contains_asio_include +{ + my ($from) = @_; + + # Open the input file. + open(my $input, "<$from") or die("Can't open $from for reading"); + + # Check file for inclusion of asio.hpp. + while (my $line = <$input>) + { + chomp($line); + if ($line =~ /# *include [<"]asio\.hpp[>"]/) + { + close($input); + return 1; + } + } + + close($input); + return 0; +} + +sub copy_source_file +{ + my ($from, $to) = @_; + + # Ensure the output directory exists. + my $dir = $to; + $dir =~ s/[^\/]*$//; + mkpath($dir); + + # First determine whether the file makes any use of asio::thread. + my $uses_asio_thread = source_contains_asio_thread_usage($from); + + my $includes_asio = source_contains_asio_include($from); + + my $is_asio_hpp = 0; + $is_asio_hpp = 1 if ($from =~ /asio\.hpp/); + + my $needs_doc_link = 0; + $needs_doc_link = 1 if ($is_asio_hpp); + + my $is_error_hpp = 0; + $is_error_hpp = 1 if ($from =~ /asio\/error\.hpp/); + + my $is_qbk = 0; + $is_qbk = 1 if ($from =~ /.qbk$/); + + my $is_xsl = 0; + $is_xsl = 1 if ($from =~ /.xsl$/); + + my $is_test = 0; + $is_test = 1 if ($from =~ /tests\/unit/); + + my $is_coroutine_related = 0; + $is_coroutine_related = 1 if ($from =~ /await/); + + # Open the files. + open(my $input, "<$from") or die("Can't open $from for reading"); + open(my $output, ">$to") or die("Can't open $to for writing"); + + # Copy the content. + my $lineno = 1; + while (my $line = <$input>) + { + chomp($line); + + # Unconditional replacements. + $line =~ s/[\\@]ref boost_bind/boost::bind()/g; + if ($from =~ /.*\.txt$/) + { + $line =~ s/[\\@]ref async_read/boost::asio::async_read()/g; + $line =~ s/[\\@]ref async_write/boost::asio::async_write()/g; + } + if ($line =~ /asio_detail_posix_thread_function/) + { + $line =~ s/asio_detail_posix_thread_function/boost_asio_detail_posix_thread_function/g; + } + if ($line =~ /asio_signal_handler/) + { + $line =~ s/asio_signal_handler/boost_asio_signal_handler/g; + } + if ($line =~ /ASIO_/ && !($line =~ /BOOST_ASIO_/)) + { + $line =~ s/ASIO_/BOOST_ASIO_/g; + } + + # Extra replacements for quickbook and XSL source only. + if ($is_qbk || $is_xsl) + { + $line =~ s/asio\.examples/boost_asio.examples/g; + $line =~ s/asio\.history/boost_asio.history/g; + $line =~ s/asio\.index/boost_asio.index/g; + $line =~ s/asio\.net_ts/boost_asio.net_ts/g; + $line =~ s/asio\.std_executors/boost_asio.std_executors/g; + $line =~ s/asio\.overview/boost_asio.overview/g; + $line =~ s/asio\.reference/boost_asio.reference/g; + $line =~ s/asio\.tutorial/boost_asio.tutorial/g; + $line =~ s/asio\.using/boost_asio.using/g; + $line =~ s/Asio/Boost.Asio/g; + $line =~ s/changes made in each release/changes made in each Boost release/g; + $line =~ s/\[\$/[\$boost_asio\//g; + $line =~ s/\[@\.\.\/src\/examples/[\@boost_asio\/example/g; + $line =~ s/include\/asio/boost\/asio/g; + $line =~ s/\^asio/^boost\/asio/g; + $line =~ s/namespaceasio/namespaceboost_1_1asio/g; + $line =~ s/ \(\[\@examples\/diffs.*$//; + } + + # Conditional replacements. + if ($line =~ /^( *)namespace asio \{/) + { + if ($is_qbk) + { + print_line($output, $1 . "namespace boost { namespace asio {", $from, $lineno); + } + else + { + print_line($output, $1 . "namespace boost {", $from, $lineno); + print_line($output, $line, $from, $lineno); + } + } + elsif ($line =~ /^( *)} \/\/ namespace asio$/) + { + if ($is_qbk) + { + print_line($output, $1 . "} } // namespace boost::asio", $from, $lineno); + } + else + { + print_line($output, $line, $from, $lineno); + print_line($output, $1 . "} // namespace boost", $from, $lineno); + } + } + elsif ($line =~ /^(# *include )[<"](asio\.hpp)[>"]$/) + { + print_line($output, $1 . "", $from, $lineno); + if ($uses_asio_thread) + { + print_line($output, $1 . "", $from, $lineno) if (!$is_test); + $uses_asio_thread = 0; + } + } + elsif ($line =~ /^(# *include )[<"]boost\/.*[>"].*$/) + { + if (!$includes_asio && $uses_asio_thread) + { + print_line($output, $1 . "", $from, $lineno) if (!$is_test); + $uses_asio_thread = 0; + } + print_line($output, $line, $from, $lineno); + } + elsif ($line =~ /^(# *include )[<"]asio\/thread\.hpp[>"]/) + { + if ($is_test) + { + print_line($output, $1 . "", $from, $lineno); + } + else + { + # Line is removed. + } + } + elsif ($line =~ /(# *include )[<"]asio\/error_code\.hpp[>"]/) + { + if ($is_asio_hpp) + { + # Line is removed. + } + else + { + print_line($output, $1 . "", $from, $lineno) if ($is_error_hpp); + print_line($output, $1 . "", $from, $lineno); + } + } + elsif ($line =~ /# *include [<"]asio\/impl\/error_code\.[hi]pp[>"]/) + { + # Line is removed. + } + elsif ($line =~ /(# *include )[<"]asio\/system_error\.hpp[>"]/) + { + if ($is_asio_hpp) + { + # Line is removed. + } + else + { + print_line($output, $1 . "", $from, $lineno); + } + } + elsif ($line =~ /(^.*# *include )[<"](asio\/[^>"]*)[>"](.*)$/) + { + print_line($output, $1 . "" . $3, $from, $lineno); + } + elsif ($line =~ /#.*defined\(.*ASIO_HAS_STD_SYSTEM_ERROR\)$/) + { + # Line is removed. + } + elsif ($line =~ /asio::thread\b/) + { + if ($is_test) + { + $line =~ s/asio::thread/asio::detail::thread/g; + } + else + { + $line =~ s/asio::thread/boost::thread/g; + } + if (!($line =~ /boost::asio::/)) + { + $line =~ s/asio::/boost::asio::/g; + } + print_line($output, $line, $from, $lineno); + } + elsif ($line =~ /^( *)thread( .*)$/ && !$is_qbk) + { + if ($is_test) + { + print_line($output, $1 . "boost::asio::detail::thread" . $2, $from, $lineno); + } + else + { + print_line($output, $1 . "boost::thread" . $2, $from, $lineno); + } + } + elsif ($line =~ /namespace std \{ *$/ && !$is_coroutine_related) + { + print_line($output, "namespace boost {", $from, $lineno); + print_line($output, "namespace system {", $from, $lineno); + } + elsif ($line =~ /std::error_code/) + { + $line =~ s/std::error_code/boost::system::error_code/g; + $line =~ s/asio::/boost::asio::/g if !$is_xsl; + print_line($output, $line, $from, $lineno); + } + elsif ($line =~ /^} \/\/ namespace std/ && !$is_coroutine_related) + { + print_line($output, "} // namespace system", $from, $lineno); + print_line($output, "} // namespace boost", $from, $lineno); + } + elsif ($line =~ /asio::/ && !($line =~ /boost::asio::/)) + { + $line =~ s/asio::error_code/boost::system::error_code/g; + $line =~ s/asio::error_category/boost::system::error_category/g; + $line =~ s/asio::system_category/boost::system::system_category/g; + $line =~ s/asio::system_error/boost::system::system_error/g; + $line =~ s/asio::/boost::asio::/g if !$is_xsl; + print_line($output, $line, $from, $lineno); + } + elsif ($line =~ /using namespace asio/) + { + $line =~ s/using namespace asio/using namespace boost::asio/g; + print_line($output, $line, $from, $lineno); + } + elsif ($line =~ /asio_handler_alloc_helpers/) + { + $line =~ s/asio_handler_alloc_helpers/boost_asio_handler_alloc_helpers/g; + print_line($output, $line, $from, $lineno); + } + elsif ($line =~ /asio_handler_cont_helpers/) + { + $line =~ s/asio_handler_cont_helpers/boost_asio_handler_cont_helpers/g; + print_line($output, $line, $from, $lineno); + } + elsif ($line =~ /asio_handler_invoke_helpers/) + { + $line =~ s/asio_handler_invoke_helpers/boost_asio_handler_invoke_helpers/g; + print_line($output, $line, $from, $lineno); + } + elsif ($line =~ /[\\@]ref boost_bind/) + { + $line =~ s/[\\@]ref boost_bind/boost::bind()/g; + print_line($output, $line, $from, $lineno); + } + elsif ($line =~ /( *)\[category template\]/) + { + print_line($output, $1 . "[authors [Kohlhoff, Christopher]]", $from, $lineno); + print_line($output, $line, $from, $lineno); + } + elsif ($line =~ /boostify: non-boost docs start here/) + { + while ($line = <$input>) + { + last if $line =~ /boostify: non-boost docs end here/; + } + } + elsif ($line =~ /boostify: non-boost code starts here/) + { + while ($line = <$input>) + { + last if $line =~ /boostify: non-boost code ends here/; + } + } + elsif ($line =~ /^$/ && $needs_doc_link) + { + $needs_doc_link = 0; + print_line($output, "// See www.boost.org/libs/asio for documentation.", $from, $lineno); + print_line($output, "//", $from, $lineno); + print_line($output, $line, $from, $lineno); + } + else + { + print_line($output, $line, $from, $lineno); + } + ++$lineno; + } + + # Ok, we're done. + close($input); + close($output); +} + +sub copy_include_files +{ + my @dirs = ( + "include", + "include/asio", + "include/asio/detail", + "include/asio/detail/impl", + "include/asio/execution", + "include/asio/execution/detail", + "include/asio/execution/impl", + "include/asio/experimental", + "include/asio/experimental/impl", + "include/asio/generic", + "include/asio/generic/detail", + "include/asio/generic/detail/impl", + "include/asio/impl", + "include/asio/ip", + "include/asio/ip/impl", + "include/asio/ip/detail", + "include/asio/ip/detail/impl", + "include/asio/local", + "include/asio/local/detail", + "include/asio/local/detail/impl", + "include/asio/posix", + "include/asio/ssl", + "include/asio/ssl/detail", + "include/asio/ssl/detail/impl", + "include/asio/ssl/impl", + "include/asio/ssl/old", + "include/asio/ssl/old/detail", + "include/asio/traits", + "include/asio/ts", + "include/asio/windows"); + + foreach my $dir (@dirs) + { + our $boost_dir; + my @files = ( glob("$dir/*.hpp"), glob("$dir/*.ipp"), glob("$dir/*cpp") ); + foreach my $file (@files) + { + if ($file ne "include/asio/thread.hpp" + and $file ne "include/asio/error_code.hpp" + and $file ne "include/asio/system_error.hpp" + and $file ne "include/asio/impl/error_code.hpp" + and $file ne "include/asio/impl/error_code.ipp") + { + my $from = $file; + my $to = $file; + $to =~ s/^include\//$boost_dir\/libs\/asio\/include\/boost\//; + copy_source_file($from, $to); + } + } + } +} + +sub create_lib_directory +{ + my @dirs = ( + "doc", + "example", + "test"); + + our $boost_dir; + foreach my $dir (@dirs) + { + mkpath("$boost_dir/libs/asio/$dir"); + } +} + +sub copy_unit_tests +{ + my @dirs = ( + "src/tests/unit", + "src/tests/unit/archetypes", + "src/tests/unit/execution", + "src/tests/unit/generic", + "src/tests/unit/ip", + "src/tests/unit/local", + "src/tests/unit/posix", + "src/tests/unit/ssl", + "src/tests/unit/ts", + "src/tests/unit/windows"); + + our $boost_dir; + foreach my $dir (@dirs) + { + my @files = ( glob("$dir/*.*pp"), glob("$dir/Jamfile*") ); + foreach my $file (@files) + { + if ($file ne "src/tests/unit/thread.cpp" + and $file ne "src/tests/unit/error_handler.cpp" + and $file ne "src/tests/unit/unit_test.cpp") + { + my $from = $file; + my $to = $file; + $to =~ s/^src\/tests\/unit\//$boost_dir\/libs\/asio\/test\//; + copy_source_file($from, $to); + } + } + } +} + +sub copy_latency_tests +{ + my @dirs = ( + "src/tests/latency"); + + our $boost_dir; + foreach my $dir (@dirs) + { + my @files = ( glob("$dir/*.*pp"), glob("$dir/Jamfile*") ); + foreach my $file (@files) + { + my $from = $file; + my $to = $file; + $to =~ s/^src\/tests\/latency\//$boost_dir\/libs\/asio\/test\/latency\//; + copy_source_file($from, $to); + } + } +} + +sub copy_properties_tests +{ + my @dirs = ( + "src/tests/properties/cpp03", + "src/tests/properties/cpp11", + "src/tests/properties/cpp14"); + + our $boost_dir; + foreach my $dir (@dirs) + { + my @files = ( glob("$dir/*.*pp"), glob("$dir/Jamfile*") ); + foreach my $file (@files) + { + my $from = $file; + my $to = $file; + $to =~ s/^src\/tests\/properties\//$boost_dir\/libs\/asio\/test\/properties\//; + copy_source_file($from, $to); + } + } +} + +sub copy_examples +{ + my @dirs = ( + "src/examples/cpp03/allocation", + "src/examples/cpp03/buffers", + "src/examples/cpp03/chat", + "src/examples/cpp03/echo", + "src/examples/cpp03/fork", + "src/examples/cpp03/http/client", + "src/examples/cpp03/http/doc_root", + "src/examples/cpp03/http/server", + "src/examples/cpp03/http/server2", + "src/examples/cpp03/http/server3", + "src/examples/cpp03/http/server4", + "src/examples/cpp03/icmp", + "src/examples/cpp03/invocation", + "src/examples/cpp03/iostreams", + "src/examples/cpp03/local", + "src/examples/cpp03/multicast", + "src/examples/cpp03/nonblocking", + "src/examples/cpp03/porthopper", + "src/examples/cpp03/serialization", + "src/examples/cpp03/services", + "src/examples/cpp03/socks4", + "src/examples/cpp03/spawn", + "src/examples/cpp03/ssl", + "src/examples/cpp03/timeouts", + "src/examples/cpp03/timers", + "src/examples/cpp03/tutorial", + "src/examples/cpp03/tutorial/daytime1", + "src/examples/cpp03/tutorial/daytime2", + "src/examples/cpp03/tutorial/daytime3", + "src/examples/cpp03/tutorial/daytime4", + "src/examples/cpp03/tutorial/daytime5", + "src/examples/cpp03/tutorial/daytime6", + "src/examples/cpp03/tutorial/daytime7", + "src/examples/cpp03/tutorial/timer1", + "src/examples/cpp03/tutorial/timer2", + "src/examples/cpp03/tutorial/timer3", + "src/examples/cpp03/tutorial/timer4", + "src/examples/cpp03/tutorial/timer5", + "src/examples/cpp03/windows", + "src/examples/cpp11/allocation", + "src/examples/cpp11/buffers", + "src/examples/cpp11/chat", + "src/examples/cpp11/echo", + "src/examples/cpp11/executors", + "src/examples/cpp11/fork", + "src/examples/cpp11/futures", + "src/examples/cpp11/handler_tracking", + "src/examples/cpp11/http/server", + "src/examples/cpp11/invocation", + "src/examples/cpp11/iostreams", + "src/examples/cpp11/local", + "src/examples/cpp11/multicast", + "src/examples/cpp11/nonblocking", + "src/examples/cpp11/operations", + "src/examples/cpp11/socks4", + "src/examples/cpp11/spawn", + "src/examples/cpp11/ssl", + "src/examples/cpp11/timeouts", + "src/examples/cpp11/timers", + "src/examples/cpp14/executors", + "src/examples/cpp14/operations", + "src/examples/cpp17/coroutines_ts"); + + our $boost_dir; + foreach my $dir (@dirs) + { + my @files = ( + glob("$dir/*.*pp"), + glob("$dir/*.html"), + glob("$dir/Jamfile*"), + glob("$dir/*.pem"), + glob("$dir/README*"), + glob("$dir/*.txt")); + foreach my $file (@files) + { + my $from = $file; + my $to = $file; + $to =~ s/^src\/examples\//$boost_dir\/libs\/asio\/example\//; + copy_source_file($from, $to); + } + } +} + +sub copy_doc +{ + our $boost_dir; + my @files = ( + "src/doc/asio.qbk", + "src/doc/examples.qbk", + "src/doc/net_ts.qbk", + "src/doc/reference.xsl", + "src/doc/std_executors.qbk", + "src/doc/tutorial.xsl", + glob("src/doc/overview/*.qbk"), + glob("src/doc/requirements/*.qbk")); + foreach my $file (@files) + { + my $from = $file; + my $to = $file; + $to =~ s/^src\/doc\//$boost_dir\/libs\/asio\/doc\//; + copy_source_file($from, $to); + } +} + +sub copy_tools +{ + our $boost_dir; + my @files = ( + glob("src/tools/*.pl")); + foreach my $file (@files) + { + my $from = $file; + my $to = $file; + $to =~ s/^src\/tools\//$boost_dir\/libs\/asio\/tools\//; + copy_source_file($from, $to); + } +} + +copy_include_files(); +create_lib_directory(); +copy_unit_tests(); +copy_latency_tests(); +copy_properties_tests(); +copy_examples(); +copy_doc(); +copy_tools(); diff --git a/tidal-link/link/modules/asio-standalone/asio/configure.ac b/tidal-link/link/modules/asio-standalone/asio/configure.ac new file mode 100644 index 000000000..fd1954cbc --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/configure.ac @@ -0,0 +1,230 @@ +AC_INIT(asio, [1.17.0]) +AC_CONFIG_SRCDIR(include/asio.hpp) +AM_MAINTAINER_MODE +AM_INIT_AUTOMAKE([tar-ustar]) + +AC_CANONICAL_HOST +AM_PROG_CC_C_O +AC_PROG_CXX +AC_LANG(C++) +AC_PROG_RANLIB + +AC_DEFINE(_REENTRANT, [1], [Define this]) + +AC_ARG_WITH(boost, + AC_HELP_STRING([--with-boost=DIR],[location of boost distribution]), +[ + if test "${withval}" = no; then + STANDALONE="yes" + else + if test "${withval}" != system; then + CPPFLAGS="$CPPFLAGS -I${withval}" + LIBS="$LIBS -L${withval}/stage/lib" + fi + CPPFLAGS="$CPPFLAGS -DASIO_ENABLE_BOOST -DBOOST_CHRONO_HEADER_ONLY -DBOOST_CHRONO_DONT_PROVIDE_HYBRID_ERROR_HANDLING" + fi +], +[ + STANDALONE="yes" +]) + +AC_ARG_ENABLE(separate-compilation, +[ --enable-separate-compilation separate compilation of asio source], +[ + SEPARATE_COMPILATION=yes +]) + +AC_ARG_ENABLE(boost-coroutine, +[ --enable-boost-coroutine use Boost.Coroutine to implement stackful coroutines], +[ + HAVE_BOOST_COROUTINE=yes +]) + +if test "$STANDALONE" != yes; then + AC_CHECK_HEADER([boost/noncopyable.hpp],, + [ + echo "Can't find boost headers. Please check the location of the boost" + echo "distribution and rerun configure using the --with-boost=DIR option." + echo "Alternatively, run with --without-boost to enable standalone build." + exit 1 + ],[]) +fi + +AC_ARG_WITH(openssl, + AC_HELP_STRING([--with-openssl=DIR],[location of openssl]), +[ + CPPFLAGS="$CPPFLAGS -I${withval}/include" + LIBS="$LIBS -L${withval}/lib" +],[]) + +AC_CHECK_HEADER([openssl/ssl.h],, +[ + OPENSSL_FOUND=no +],[]) + +if test x$OPENSSL_FOUND != xno; then + LIBS="$LIBS -lssl -lcrypto" +fi + +AM_CONDITIONAL(HAVE_OPENSSL,test x$OPENSSL_FOUND != xno) + +WINDOWS=no +case $host in + *-*-linux*) + CXXFLAGS="$CXXFLAGS -pthread" + LDFLAGS="$LDFLAGS -pthread" + LIBS="$LIBS -lrt" + ;; + *-*-solaris*) + if test "$GXX" = yes; then + CXXFLAGS="$CXXFLAGS -D_PTHREADS" + else + # We'll assume Sun's CC. + CXXFLAGS="$CXXFLAGS -mt" + fi + LIBS="$LIBS -lsocket -lnsl -lpthread" + ;; + *-*-mingw32*) + CXXFLAGS="$CXXFLAGS -mthreads" + LDFLAGS="$LDFLAGS -mthreads" + LIBS="$LIBS -lws2_32 -lmswsock" + WINDOWS=yes + ;; + *-*-mingw64*) + CXXFLAGS="$CXXFLAGS -mthreads" + LDFLAGS="$LDFLAGS -mthreads" + LIBS="$LIBS -lws2_32 -lmswsock" + WINDOWS=yes + ;; + *-pc-cygwin*) + CXXFLAGS="$CXXFLAGS -D__USE_W32_SOCKETS -D_WIN32_WINNT=0x0601" + LIBS="$LIBS -lws2_32 -lmswsock" + WINDOWS=yes + ;; + *-apple-darwin*) + CXXFLAGS="$CXXFLAGS" + LDFLAGS="$LDFLAGS" + ;; + *-*-freebsd*) + CXXFLAGS="$CXXFLAGS -pthread" + LDFLAGS="$LDFLAGS -pthread" + ;; + *-*-netbsd*) + CXXFLAGS="$CXXFLAGS -pthread" + LDFLAGS="$LDFLAGS -pthread" + ;; + *-*-haiku*) + CXXFLAGS="$CXXFLAGS -lnetwork" + LDFLAGS="$LDFLAGS -lnetwork" + +esac + +if test "$GXX" = yes; then + CXXFLAGS="$CXXFLAGS -ftemplate-depth-256" +fi + +if test "$STANDALONE" = yes; then + CPPFLAGS="$CPPFLAGS -DASIO_STANDALONE" +fi + +if test "$SEPARATE_COMPILATION" = yes; then + CPPFLAGS="$CPPFLAGS -DASIO_SEPARATE_COMPILATION" +fi + +AC_MSG_CHECKING([whether C++11 is enabled]) +AC_COMPILE_IFELSE( + [AC_LANG_PROGRAM( + [[#if __cplusplus < 201103L]] + [[#error C++11 not available]] + [[#endif]])], + [AC_MSG_RESULT([yes]) + HAVE_CXX11=yes;], + [AC_MSG_RESULT([no]) + HAVE_CXX11=no;]) + +AC_MSG_CHECKING([whether C++14 is enabled]) +AC_COMPILE_IFELSE( + [AC_LANG_PROGRAM( + [[#if defined(__GNUC__) && !defined(__clang__)]] + [[# if (__GNUC__ <= 6)]] + [[# error C++14 support on this compiler not sufficiently compliant]] + [[# endif]] + [[#endif]] + [[#if __cplusplus < 201402L]] + [[#error C++14 not available]] + [[#endif]])], + [AC_MSG_RESULT([yes]) + HAVE_CXX14=yes;], + [AC_MSG_RESULT([no]) + HAVE_CXX14=no;]) + +AC_MSG_CHECKING([whether C++17 is enabled]) +AC_COMPILE_IFELSE( + [AC_LANG_PROGRAM( + [[#if __cplusplus < 201703L]] + [[#error C++17 not available]] + [[#endif]])], + [AC_MSG_RESULT([yes]) + HAVE_CXX17=yes;], + [AC_MSG_RESULT([no]) + HAVE_CXX17=no;]) + +AC_MSG_CHECKING([whether coroutines are enabled]) +AC_COMPILE_IFELSE( + [AC_LANG_PROGRAM( + [[#if defined(__clang__)]] + [[# if (__cplusplus >= 201703) && (__cpp_coroutines >= 201703)]] + [[# if __has_include()]] + [[# define ASIO_HAS_CO_AWAIT 1]] + [[# endif]] + [[# endif]] + [[#elif defined(__GNUC__)]] + [[# if (__cplusplus >= 201709) && (__cpp_impl_coroutine >= 201902)]] + [[# if __has_include()]] + [[# define ASIO_HAS_CO_AWAIT 1]] + [[# endif]] + [[# endif]] + [[#endif]] + [[#ifndef ASIO_HAS_CO_AWAIT]] + [[# error coroutines not available]] + [[#endif]])], + [AC_MSG_RESULT([yes]) + HAVE_COROUTINES=yes;], + [AC_MSG_RESULT([no]) + HAVE_COROUTINES=no;]) + +if test "$GXX" = yes; then + if test "$STANDALONE" = yes; then + if test "$HAVE_CXX11" = no; then + HAVE_CXX11=yes + CPPFLAGS="-std=c++0x $CPPFLAGS" + fi + fi +fi + +AM_CONDITIONAL(STANDALONE,test x$STANDALONE = xyes) + +AM_CONDITIONAL(SEPARATE_COMPILATION,test x$SEPARATE_COMPILATION = xyes) + +AM_CONDITIONAL(HAVE_BOOST_COROUTINE,test x$HAVE_BOOST_COROUTINE = xyes) + +AM_CONDITIONAL(WINDOWS_TARGET,test x$WINDOWS != xno) + +AM_CONDITIONAL(HAVE_CXX11,test x$HAVE_CXX11 = xyes) + +AM_CONDITIONAL(HAVE_CXX14,test x$HAVE_CXX14 = xyes) + +AM_CONDITIONAL(HAVE_CXX17,test x$HAVE_CXX17 = xyes) + +AM_CONDITIONAL(HAVE_COROUTINES,test x$HAVE_COROUTINES = xyes) + +AC_OUTPUT([ + Makefile + include/Makefile + src/Makefile + src/tests/Makefile + src/tests/properties/Makefile + src/examples/cpp03/Makefile + src/examples/cpp11/Makefile + src/examples/cpp14/Makefile + src/examples/cpp17/Makefile]) diff --git a/tidal-link/link/modules/asio-standalone/asio/include/.gitignore b/tidal-link/link/modules/asio-standalone/asio/include/.gitignore new file mode 100644 index 000000000..282522db0 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/.gitignore @@ -0,0 +1,2 @@ +Makefile +Makefile.in diff --git a/tidal-link/link/modules/asio-standalone/asio/include/Makefile.am b/tidal-link/link/modules/asio-standalone/asio/include/Makefile.am new file mode 100644 index 000000000..265e37ed5 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/Makefile.am @@ -0,0 +1,564 @@ +# find . -name "*.*pp" | sed -e 's/^\.\///' | sed -e 's/^.*$/ & \\/' | sort +nobase_include_HEADERS = \ + asio/any_io_executor.hpp \ + asio/associated_allocator.hpp \ + asio/associated_executor.hpp \ + asio/async_result.hpp \ + asio/awaitable.hpp \ + asio/basic_datagram_socket.hpp \ + asio/basic_deadline_timer.hpp \ + asio/basic_io_object.hpp \ + asio/basic_raw_socket.hpp \ + asio/basic_seq_packet_socket.hpp \ + asio/basic_serial_port.hpp \ + asio/basic_signal_set.hpp \ + asio/basic_socket_acceptor.hpp \ + asio/basic_socket.hpp \ + asio/basic_socket_iostream.hpp \ + asio/basic_socket_streambuf.hpp \ + asio/basic_streambuf_fwd.hpp \ + asio/basic_streambuf.hpp \ + asio/basic_stream_socket.hpp \ + asio/basic_waitable_timer.hpp \ + asio/bind_executor.hpp \ + asio/buffered_read_stream_fwd.hpp \ + asio/buffered_read_stream.hpp \ + asio/buffered_stream_fwd.hpp \ + asio/buffered_stream.hpp \ + asio/buffered_write_stream_fwd.hpp \ + asio/buffered_write_stream.hpp \ + asio/buffer.hpp \ + asio/buffers_iterator.hpp \ + asio/co_spawn.hpp \ + asio/completion_condition.hpp \ + asio/compose.hpp \ + asio/connect.hpp \ + asio/coroutine.hpp \ + asio/deadline_timer.hpp \ + asio/defer.hpp \ + asio/detached.hpp \ + asio/detail/array_fwd.hpp \ + asio/detail/array.hpp \ + asio/detail/assert.hpp \ + asio/detail/atomic_count.hpp \ + asio/detail/base_from_completion_cond.hpp \ + asio/detail/bind_handler.hpp \ + asio/detail/blocking_executor_op.hpp \ + asio/detail/buffered_stream_storage.hpp \ + asio/detail/buffer_resize_guard.hpp \ + asio/detail/buffer_sequence_adapter.hpp \ + asio/detail/bulk_executor_op.hpp \ + asio/detail/call_stack.hpp \ + asio/detail/chrono.hpp \ + asio/detail/chrono_time_traits.hpp \ + asio/detail/completion_handler.hpp \ + asio/detail/concurrency_hint.hpp \ + asio/detail/conditionally_enabled_event.hpp \ + asio/detail/conditionally_enabled_mutex.hpp \ + asio/detail/config.hpp \ + asio/detail/consuming_buffers.hpp \ + asio/detail/cstddef.hpp \ + asio/detail/cstdint.hpp \ + asio/detail/date_time_fwd.hpp \ + asio/detail/deadline_timer_service.hpp \ + asio/detail/dependent_type.hpp \ + asio/detail/descriptor_ops.hpp \ + asio/detail/descriptor_read_op.hpp \ + asio/detail/descriptor_write_op.hpp \ + asio/detail/dev_poll_reactor.hpp \ + asio/detail/epoll_reactor.hpp \ + asio/detail/eventfd_select_interrupter.hpp \ + asio/detail/event.hpp \ + asio/detail/executor_function.hpp \ + asio/detail/executor_op.hpp \ + asio/detail/fd_set_adapter.hpp \ + asio/detail/fenced_block.hpp \ + asio/detail/functional.hpp \ + asio/detail/future.hpp \ + asio/detail/gcc_arm_fenced_block.hpp \ + asio/detail/gcc_hppa_fenced_block.hpp \ + asio/detail/gcc_sync_fenced_block.hpp \ + asio/detail/gcc_x86_fenced_block.hpp \ + asio/detail/global.hpp \ + asio/detail/handler_alloc_helpers.hpp \ + asio/detail/handler_cont_helpers.hpp \ + asio/detail/handler_invoke_helpers.hpp \ + asio/detail/handler_tracking.hpp \ + asio/detail/handler_type_requirements.hpp \ + asio/detail/handler_work.hpp \ + asio/detail/hash_map.hpp \ + asio/detail/impl/buffer_sequence_adapter.ipp \ + asio/detail/impl/descriptor_ops.ipp \ + asio/detail/impl/dev_poll_reactor.hpp \ + asio/detail/impl/dev_poll_reactor.ipp \ + asio/detail/impl/epoll_reactor.hpp \ + asio/detail/impl/epoll_reactor.ipp \ + asio/detail/impl/eventfd_select_interrupter.ipp \ + asio/detail/impl/handler_tracking.ipp \ + asio/detail/impl/kqueue_reactor.hpp \ + asio/detail/impl/kqueue_reactor.ipp \ + asio/detail/impl/null_event.ipp \ + asio/detail/impl/pipe_select_interrupter.ipp \ + asio/detail/impl/posix_event.ipp \ + asio/detail/impl/posix_mutex.ipp \ + asio/detail/impl/posix_thread.ipp \ + asio/detail/impl/posix_tss_ptr.ipp \ + asio/detail/impl/reactive_descriptor_service.ipp \ + asio/detail/impl/reactive_serial_port_service.ipp \ + asio/detail/impl/reactive_socket_service_base.ipp \ + asio/detail/impl/resolver_service_base.ipp \ + asio/detail/impl/scheduler.ipp \ + asio/detail/impl/select_reactor.hpp \ + asio/detail/impl/select_reactor.ipp \ + asio/detail/impl/service_registry.hpp \ + asio/detail/impl/service_registry.ipp \ + asio/detail/impl/signal_set_service.ipp \ + asio/detail/impl/socket_ops.ipp \ + asio/detail/impl/socket_select_interrupter.ipp \ + asio/detail/impl/strand_executor_service.hpp \ + asio/detail/impl/strand_executor_service.ipp \ + asio/detail/impl/strand_service.hpp \ + asio/detail/impl/strand_service.ipp \ + asio/detail/impl/throw_error.ipp \ + asio/detail/impl/timer_queue_ptime.ipp \ + asio/detail/impl/timer_queue_set.ipp \ + asio/detail/impl/win_event.ipp \ + asio/detail/impl/win_iocp_handle_service.ipp \ + asio/detail/impl/win_iocp_io_context.hpp \ + asio/detail/impl/win_iocp_io_context.ipp \ + asio/detail/impl/win_iocp_serial_port_service.ipp \ + asio/detail/impl/win_iocp_socket_service_base.ipp \ + asio/detail/impl/win_mutex.ipp \ + asio/detail/impl/win_object_handle_service.ipp \ + asio/detail/impl/winrt_ssocket_service_base.ipp \ + asio/detail/impl/winrt_timer_scheduler.hpp \ + asio/detail/impl/winrt_timer_scheduler.ipp \ + asio/detail/impl/winsock_init.ipp \ + asio/detail/impl/win_static_mutex.ipp \ + asio/detail/impl/win_thread.ipp \ + asio/detail/impl/win_tss_ptr.ipp \ + asio/detail/io_control.hpp \ + asio/detail/io_object_impl.hpp \ + asio/detail/is_buffer_sequence.hpp \ + asio/detail/is_executor.hpp \ + asio/detail/keyword_tss_ptr.hpp \ + asio/detail/kqueue_reactor.hpp \ + asio/detail/limits.hpp \ + asio/detail/local_free_on_block_exit.hpp \ + asio/detail/macos_fenced_block.hpp \ + asio/detail/memory.hpp \ + asio/detail/mutex.hpp \ + asio/detail/non_const_lvalue.hpp \ + asio/detail/noncopyable.hpp \ + asio/detail/null_event.hpp \ + asio/detail/null_fenced_block.hpp \ + asio/detail/null_global.hpp \ + asio/detail/null_mutex.hpp \ + asio/detail/null_reactor.hpp \ + asio/detail/null_signal_blocker.hpp \ + asio/detail/null_socket_service.hpp \ + asio/detail/null_static_mutex.hpp \ + asio/detail/null_thread.hpp \ + asio/detail/null_tss_ptr.hpp \ + asio/detail/object_pool.hpp \ + asio/detail/old_win_sdk_compat.hpp \ + asio/detail/operation.hpp \ + asio/detail/op_queue.hpp \ + asio/detail/pipe_select_interrupter.hpp \ + asio/detail/pop_options.hpp \ + asio/detail/posix_event.hpp \ + asio/detail/posix_fd_set_adapter.hpp \ + asio/detail/posix_global.hpp \ + asio/detail/posix_mutex.hpp \ + asio/detail/posix_signal_blocker.hpp \ + asio/detail/posix_static_mutex.hpp \ + asio/detail/posix_thread.hpp \ + asio/detail/posix_tss_ptr.hpp \ + asio/detail/push_options.hpp \ + asio/detail/reactive_descriptor_service.hpp \ + asio/detail/reactive_null_buffers_op.hpp \ + asio/detail/reactive_serial_port_service.hpp \ + asio/detail/reactive_socket_accept_op.hpp \ + asio/detail/reactive_socket_connect_op.hpp \ + asio/detail/reactive_socket_recvfrom_op.hpp \ + asio/detail/reactive_socket_recvmsg_op.hpp \ + asio/detail/reactive_socket_recv_op.hpp \ + asio/detail/reactive_socket_send_op.hpp \ + asio/detail/reactive_socket_sendto_op.hpp \ + asio/detail/reactive_socket_service_base.hpp \ + asio/detail/reactive_socket_service.hpp \ + asio/detail/reactive_wait_op.hpp \ + asio/detail/reactor_fwd.hpp \ + asio/detail/reactor.hpp \ + asio/detail/reactor_op.hpp \ + asio/detail/reactor_op_queue.hpp \ + asio/detail/recycling_allocator.hpp \ + asio/detail/regex_fwd.hpp \ + asio/detail/resolve_endpoint_op.hpp \ + asio/detail/resolve_op.hpp \ + asio/detail/resolve_query_op.hpp \ + asio/detail/resolver_service_base.hpp \ + asio/detail/resolver_service.hpp \ + asio/detail/scheduler.hpp \ + asio/detail/scheduler_operation.hpp \ + asio/detail/scheduler_thread_info.hpp \ + asio/detail/scoped_lock.hpp \ + asio/detail/scoped_ptr.hpp \ + asio/detail/select_interrupter.hpp \ + asio/detail/select_reactor.hpp \ + asio/detail/service_registry.hpp \ + asio/detail/signal_blocker.hpp \ + asio/detail/signal_handler.hpp \ + asio/detail/signal_init.hpp \ + asio/detail/signal_op.hpp \ + asio/detail/signal_set_service.hpp \ + asio/detail/socket_holder.hpp \ + asio/detail/socket_ops.hpp \ + asio/detail/socket_option.hpp \ + asio/detail/socket_select_interrupter.hpp \ + asio/detail/socket_types.hpp \ + asio/detail/solaris_fenced_block.hpp \ + asio/detail/source_location.hpp \ + asio/detail/static_mutex.hpp \ + asio/detail/std_event.hpp \ + asio/detail/std_fenced_block.hpp \ + asio/detail/std_global.hpp \ + asio/detail/std_mutex.hpp \ + asio/detail/std_static_mutex.hpp \ + asio/detail/std_thread.hpp \ + asio/detail/strand_executor_service.hpp \ + asio/detail/strand_service.hpp \ + asio/detail/string_view.hpp \ + asio/detail/thread_context.hpp \ + asio/detail/thread_group.hpp \ + asio/detail/thread.hpp \ + asio/detail/thread_info_base.hpp \ + asio/detail/throw_error.hpp \ + asio/detail/throw_exception.hpp \ + asio/detail/timer_queue_base.hpp \ + asio/detail/timer_queue.hpp \ + asio/detail/timer_queue_ptime.hpp \ + asio/detail/timer_queue_set.hpp \ + asio/detail/timer_scheduler_fwd.hpp \ + asio/detail/timer_scheduler.hpp \ + asio/detail/tss_ptr.hpp \ + asio/detail/type_traits.hpp \ + asio/detail/variadic_templates.hpp \ + asio/detail/wait_handler.hpp \ + asio/detail/wait_op.hpp \ + asio/detail/winapp_thread.hpp \ + asio/detail/wince_thread.hpp \ + asio/detail/win_event.hpp \ + asio/detail/win_fd_set_adapter.hpp \ + asio/detail/win_fenced_block.hpp \ + asio/detail/win_global.hpp \ + asio/detail/win_iocp_handle_read_op.hpp \ + asio/detail/win_iocp_handle_service.hpp \ + asio/detail/win_iocp_handle_write_op.hpp \ + asio/detail/win_iocp_io_context.hpp \ + asio/detail/win_iocp_null_buffers_op.hpp \ + asio/detail/win_iocp_operation.hpp \ + asio/detail/win_iocp_overlapped_op.hpp \ + asio/detail/win_iocp_overlapped_ptr.hpp \ + asio/detail/win_iocp_serial_port_service.hpp \ + asio/detail/win_iocp_socket_accept_op.hpp \ + asio/detail/win_iocp_socket_connect_op.hpp \ + asio/detail/win_iocp_socket_recvfrom_op.hpp \ + asio/detail/win_iocp_socket_recvmsg_op.hpp \ + asio/detail/win_iocp_socket_recv_op.hpp \ + asio/detail/win_iocp_socket_send_op.hpp \ + asio/detail/win_iocp_socket_service_base.hpp \ + asio/detail/win_iocp_socket_service.hpp \ + asio/detail/win_iocp_thread_info.hpp \ + asio/detail/win_iocp_wait_op.hpp \ + asio/detail/win_mutex.hpp \ + asio/detail/win_object_handle_service.hpp \ + asio/detail/winrt_async_manager.hpp \ + asio/detail/winrt_async_op.hpp \ + asio/detail/winrt_resolve_op.hpp \ + asio/detail/winrt_resolver_service.hpp \ + asio/detail/winrt_socket_connect_op.hpp \ + asio/detail/winrt_socket_recv_op.hpp \ + asio/detail/winrt_socket_send_op.hpp \ + asio/detail/winrt_ssocket_service_base.hpp \ + asio/detail/winrt_ssocket_service.hpp \ + asio/detail/winrt_timer_scheduler.hpp \ + asio/detail/winrt_utils.hpp \ + asio/detail/winsock_init.hpp \ + asio/detail/win_static_mutex.hpp \ + asio/detail/win_thread.hpp \ + asio/detail/win_tss_ptr.hpp \ + asio/detail/work_dispatcher.hpp \ + asio/detail/wrapped_handler.hpp \ + asio/dispatch.hpp \ + asio/error_code.hpp \ + asio/error.hpp \ + asio/execution.hpp \ + asio/execution_context.hpp \ + asio/execution/allocator.hpp \ + asio/execution/any_executor.hpp \ + asio/execution/bad_executor.hpp \ + asio/execution/blocking.hpp \ + asio/execution/blocking_adaptation.hpp \ + asio/execution/bulk_execute.hpp \ + asio/execution/bulk_guarantee.hpp \ + asio/execution/connect.hpp \ + asio/execution/context.hpp \ + asio/execution/context_as.hpp \ + asio/execution/detail/as_invocable.hpp \ + asio/execution/detail/as_operation.hpp \ + asio/execution/detail/as_receiver.hpp \ + asio/execution/detail/bulk_sender.hpp \ + asio/execution/detail/void_receiver.hpp \ + asio/execution/detail/submit_receiver.hpp \ + asio/execution/execute.hpp \ + asio/execution/executor.hpp \ + asio/execution/impl/bad_executor.ipp \ + asio/execution/impl/receiver_invocation_error.ipp \ + asio/execution/invocable_archetype.hpp \ + asio/execution/mapping.hpp \ + asio/execution/occupancy.hpp \ + asio/execution/operation_state.hpp \ + asio/execution/outstanding_work.hpp \ + asio/execution/prefer_only.hpp \ + asio/execution/receiver.hpp \ + asio/execution/receiver_invocation_error.hpp \ + asio/execution/relationship.hpp \ + asio/execution/schedule.hpp \ + asio/execution/scheduler.hpp \ + asio/execution/sender.hpp \ + asio/execution/set_done.hpp \ + asio/execution/set_error.hpp \ + asio/execution/set_value.hpp \ + asio/execution/start.hpp \ + asio/execution/submit.hpp \ + asio/executor.hpp \ + asio/executor_work_guard.hpp \ + asio/generic/basic_endpoint.hpp \ + asio/generic/datagram_protocol.hpp \ + asio/generic/detail/endpoint.hpp \ + asio/generic/detail/impl/endpoint.ipp \ + asio/generic/raw_protocol.hpp \ + asio/generic/seq_packet_protocol.hpp \ + asio/generic/stream_protocol.hpp \ + asio/handler_alloc_hook.hpp \ + asio/handler_continuation_hook.hpp \ + asio/handler_invoke_hook.hpp \ + asio/high_resolution_timer.hpp \ + asio.hpp \ + asio/impl/awaitable.hpp \ + asio/impl/buffered_read_stream.hpp \ + asio/impl/buffered_write_stream.hpp \ + asio/impl/co_spawn.hpp \ + asio/impl/compose.hpp \ + asio/impl/connect.hpp \ + asio/impl/defer.hpp \ + asio/impl/detached.hpp \ + asio/impl/dispatch.hpp \ + asio/impl/error_code.ipp \ + asio/impl/error.ipp \ + asio/impl/execution_context.hpp \ + asio/impl/execution_context.ipp \ + asio/impl/executor.hpp \ + asio/impl/executor.ipp \ + asio/impl/handler_alloc_hook.ipp \ + asio/impl/io_context.hpp \ + asio/impl/io_context.ipp \ + asio/impl/multiple_exceptions.ipp \ + asio/impl/post.hpp \ + asio/impl/read_at.hpp \ + asio/impl/read.hpp \ + asio/impl/read_until.hpp \ + asio/impl/redirect_error.hpp \ + asio/impl/serial_port_base.hpp \ + asio/impl/serial_port_base.ipp \ + asio/impl/spawn.hpp \ + asio/impl/src.cpp \ + asio/impl/src.hpp \ + asio/impl/system_context.hpp \ + asio/impl/system_context.ipp \ + asio/impl/system_executor.hpp \ + asio/impl/thread_pool.hpp \ + asio/impl/thread_pool.ipp \ + asio/impl/use_awaitable.hpp \ + asio/impl/use_future.hpp \ + asio/impl/write_at.hpp \ + asio/impl/write.hpp \ + asio/io_context.hpp \ + asio/io_context_strand.hpp \ + asio/io_service.hpp \ + asio/io_service_strand.hpp \ + asio/ip/address.hpp \ + asio/ip/address_v4.hpp \ + asio/ip/address_v4_iterator.hpp \ + asio/ip/address_v4_range.hpp \ + asio/ip/address_v6.hpp \ + asio/ip/address_v6_iterator.hpp \ + asio/ip/address_v6_range.hpp \ + asio/ip/bad_address_cast.hpp \ + asio/ip/basic_endpoint.hpp \ + asio/ip/basic_resolver_entry.hpp \ + asio/ip/basic_resolver.hpp \ + asio/ip/basic_resolver_iterator.hpp \ + asio/ip/basic_resolver_query.hpp \ + asio/ip/basic_resolver_results.hpp \ + asio/ip/detail/endpoint.hpp \ + asio/ip/detail/impl/endpoint.ipp \ + asio/ip/detail/socket_option.hpp \ + asio/ip/host_name.hpp \ + asio/ip/icmp.hpp \ + asio/ip/impl/address.hpp \ + asio/ip/impl/address.ipp \ + asio/ip/impl/address_v4.hpp \ + asio/ip/impl/address_v4.ipp \ + asio/ip/impl/address_v6.hpp \ + asio/ip/impl/address_v6.ipp \ + asio/ip/impl/basic_endpoint.hpp \ + asio/ip/impl/host_name.ipp \ + asio/ip/impl/network_v4.hpp \ + asio/ip/impl/network_v4.ipp \ + asio/ip/impl/network_v6.hpp \ + asio/ip/impl/network_v6.ipp \ + asio/ip/multicast.hpp \ + asio/ip/network_v4.hpp \ + asio/ip/network_v6.hpp \ + asio/ip/resolver_base.hpp \ + asio/ip/resolver_query_base.hpp \ + asio/ip/tcp.hpp \ + asio/ip/udp.hpp \ + asio/ip/unicast.hpp \ + asio/ip/v6_only.hpp \ + asio/is_applicable_property.hpp \ + asio/is_executor.hpp \ + asio/is_read_buffered.hpp \ + asio/is_write_buffered.hpp \ + asio/local/basic_endpoint.hpp \ + asio/local/connect_pair.hpp \ + asio/local/datagram_protocol.hpp \ + asio/local/detail/endpoint.hpp \ + asio/local/detail/impl/endpoint.ipp \ + asio/local/stream_protocol.hpp \ + asio/multiple_exceptions.hpp \ + asio/packaged_task.hpp \ + asio/placeholders.hpp \ + asio/posix/basic_descriptor.hpp \ + asio/posix/basic_stream_descriptor.hpp \ + asio/posix/descriptor_base.hpp \ + asio/posix/descriptor.hpp \ + asio/posix/stream_descriptor.hpp \ + asio/post.hpp \ + asio/prefer.hpp \ + asio/query.hpp \ + asio/read_at.hpp \ + asio/read.hpp \ + asio/read_until.hpp \ + asio/redirect_error.hpp \ + asio/require.hpp \ + asio/require_concept.hpp \ + asio/serial_port_base.hpp \ + asio/serial_port.hpp \ + asio/signal_set.hpp \ + asio/socket_base.hpp \ + asio/spawn.hpp \ + asio/ssl/context_base.hpp \ + asio/ssl/context.hpp \ + asio/ssl/detail/buffered_handshake_op.hpp \ + asio/ssl/detail/engine.hpp \ + asio/ssl/detail/handshake_op.hpp \ + asio/ssl/detail/impl/engine.ipp \ + asio/ssl/detail/impl/openssl_init.ipp \ + asio/ssl/detail/io.hpp \ + asio/ssl/detail/openssl_init.hpp \ + asio/ssl/detail/openssl_types.hpp \ + asio/ssl/detail/password_callback.hpp \ + asio/ssl/detail/read_op.hpp \ + asio/ssl/detail/shutdown_op.hpp \ + asio/ssl/detail/stream_core.hpp \ + asio/ssl/detail/verify_callback.hpp \ + asio/ssl/detail/write_op.hpp \ + asio/ssl/error.hpp \ + asio/ssl.hpp \ + asio/ssl/host_name_verification.hpp \ + asio/ssl/impl/context.hpp \ + asio/ssl/impl/context.ipp \ + asio/ssl/impl/error.ipp \ + asio/ssl/impl/host_name_verification.ipp \ + asio/ssl/impl/rfc2818_verification.ipp \ + asio/ssl/impl/src.hpp \ + asio/ssl/rfc2818_verification.hpp \ + asio/ssl/stream_base.hpp \ + asio/ssl/stream.hpp \ + asio/ssl/verify_context.hpp \ + asio/ssl/verify_mode.hpp \ + asio/static_thread_pool.hpp \ + asio/steady_timer.hpp \ + asio/strand.hpp \ + asio/streambuf.hpp \ + asio/system_context.hpp \ + asio/system_error.hpp \ + asio/system_executor.hpp \ + asio/system_timer.hpp \ + asio/this_coro.hpp \ + asio/thread.hpp \ + asio/thread_pool.hpp \ + asio/time_traits.hpp \ + asio/traits/bulk_execute_free.hpp \ + asio/traits/bulk_execute_member.hpp \ + asio/traits/connect_free.hpp \ + asio/traits/connect_member.hpp \ + asio/traits/equality_comparable.hpp \ + asio/traits/execute_free.hpp \ + asio/traits/execute_member.hpp \ + asio/traits/prefer_free.hpp \ + asio/traits/prefer_member.hpp \ + asio/traits/query_free.hpp \ + asio/traits/query_member.hpp \ + asio/traits/query_static_constexpr_member.hpp \ + asio/traits/require_concept_free.hpp \ + asio/traits/require_concept_member.hpp \ + asio/traits/require_free.hpp \ + asio/traits/require_member.hpp \ + asio/traits/schedule_free.hpp \ + asio/traits/schedule_member.hpp \ + asio/traits/set_done_free.hpp \ + asio/traits/set_done_member.hpp \ + asio/traits/set_error_free.hpp \ + asio/traits/set_error_member.hpp \ + asio/traits/set_value_free.hpp \ + asio/traits/set_value_member.hpp \ + asio/traits/start_free.hpp \ + asio/traits/start_member.hpp \ + asio/traits/static_query.hpp \ + asio/traits/static_require.hpp \ + asio/traits/static_require_concept.hpp \ + asio/traits/submit_free.hpp \ + asio/traits/submit_member.hpp \ + asio/ts/buffer.hpp \ + asio/ts/executor.hpp \ + asio/ts/internet.hpp \ + asio/ts/io_context.hpp \ + asio/ts/netfwd.hpp \ + asio/ts/net.hpp \ + asio/ts/socket.hpp \ + asio/ts/timer.hpp \ + asio/unyield.hpp \ + asio/use_awaitable.hpp \ + asio/use_future.hpp \ + asio/uses_executor.hpp \ + asio/version.hpp \ + asio/wait_traits.hpp \ + asio/windows/basic_object_handle.hpp \ + asio/windows/basic_overlapped_handle.hpp \ + asio/windows/basic_random_access_handle.hpp \ + asio/windows/basic_stream_handle.hpp \ + asio/windows/object_handle.hpp \ + asio/windows/overlapped_handle.hpp \ + asio/windows/overlapped_ptr.hpp \ + asio/windows/random_access_handle.hpp \ + asio/windows/stream_handle.hpp \ + asio/write_at.hpp \ + asio/write.hpp \ + asio/yield.hpp + +MAINTAINERCLEANFILES = \ + $(srcdir)/Makefile.in diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio.hpp new file mode 100644 index 000000000..345aec71e --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio.hpp @@ -0,0 +1,182 @@ +// +// asio.hpp +// ~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_HPP +#define ASIO_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/associated_allocator.hpp" +#include "asio/associated_executor.hpp" +#include "asio/async_result.hpp" +#include "asio/awaitable.hpp" +#include "asio/basic_datagram_socket.hpp" +#include "asio/basic_deadline_timer.hpp" +#include "asio/basic_io_object.hpp" +#include "asio/basic_raw_socket.hpp" +#include "asio/basic_seq_packet_socket.hpp" +#include "asio/basic_serial_port.hpp" +#include "asio/basic_signal_set.hpp" +#include "asio/basic_socket.hpp" +#include "asio/basic_socket_acceptor.hpp" +#include "asio/basic_socket_iostream.hpp" +#include "asio/basic_socket_streambuf.hpp" +#include "asio/basic_stream_socket.hpp" +#include "asio/basic_streambuf.hpp" +#include "asio/basic_waitable_timer.hpp" +#include "asio/bind_executor.hpp" +#include "asio/buffer.hpp" +#include "asio/buffered_read_stream_fwd.hpp" +#include "asio/buffered_read_stream.hpp" +#include "asio/buffered_stream_fwd.hpp" +#include "asio/buffered_stream.hpp" +#include "asio/buffered_write_stream_fwd.hpp" +#include "asio/buffered_write_stream.hpp" +#include "asio/buffers_iterator.hpp" +#include "asio/co_spawn.hpp" +#include "asio/completion_condition.hpp" +#include "asio/compose.hpp" +#include "asio/connect.hpp" +#include "asio/coroutine.hpp" +#include "asio/deadline_timer.hpp" +#include "asio/defer.hpp" +#include "asio/detached.hpp" +#include "asio/dispatch.hpp" +#include "asio/error.hpp" +#include "asio/error_code.hpp" +#include "asio/execution.hpp" +#include "asio/execution/allocator.hpp" +#include "asio/execution/any_executor.hpp" +#include "asio/execution/blocking.hpp" +#include "asio/execution/blocking_adaptation.hpp" +#include "asio/execution/bulk_execute.hpp" +#include "asio/execution/bulk_guarantee.hpp" +#include "asio/execution/connect.hpp" +#include "asio/execution/context.hpp" +#include "asio/execution/context_as.hpp" +#include "asio/execution/execute.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/invocable_archetype.hpp" +#include "asio/execution/mapping.hpp" +#include "asio/execution/occupancy.hpp" +#include "asio/execution/operation_state.hpp" +#include "asio/execution/outstanding_work.hpp" +#include "asio/execution/prefer_only.hpp" +#include "asio/execution/receiver.hpp" +#include "asio/execution/receiver_invocation_error.hpp" +#include "asio/execution/relationship.hpp" +#include "asio/execution/schedule.hpp" +#include "asio/execution/scheduler.hpp" +#include "asio/execution/sender.hpp" +#include "asio/execution/set_done.hpp" +#include "asio/execution/set_error.hpp" +#include "asio/execution/set_value.hpp" +#include "asio/execution/start.hpp" +#include "asio/execution_context.hpp" +#include "asio/executor.hpp" +#include "asio/executor_work_guard.hpp" +#include "asio/generic/basic_endpoint.hpp" +#include "asio/generic/datagram_protocol.hpp" +#include "asio/generic/raw_protocol.hpp" +#include "asio/generic/seq_packet_protocol.hpp" +#include "asio/generic/stream_protocol.hpp" +#include "asio/handler_alloc_hook.hpp" +#include "asio/handler_continuation_hook.hpp" +#include "asio/handler_invoke_hook.hpp" +#include "asio/high_resolution_timer.hpp" +#include "asio/io_context.hpp" +#include "asio/io_context_strand.hpp" +#include "asio/io_service.hpp" +#include "asio/io_service_strand.hpp" +#include "asio/ip/address.hpp" +#include "asio/ip/address_v4.hpp" +#include "asio/ip/address_v4_iterator.hpp" +#include "asio/ip/address_v4_range.hpp" +#include "asio/ip/address_v6.hpp" +#include "asio/ip/address_v6_iterator.hpp" +#include "asio/ip/address_v6_range.hpp" +#include "asio/ip/network_v4.hpp" +#include "asio/ip/network_v6.hpp" +#include "asio/ip/bad_address_cast.hpp" +#include "asio/ip/basic_endpoint.hpp" +#include "asio/ip/basic_resolver.hpp" +#include "asio/ip/basic_resolver_entry.hpp" +#include "asio/ip/basic_resolver_iterator.hpp" +#include "asio/ip/basic_resolver_query.hpp" +#include "asio/ip/host_name.hpp" +#include "asio/ip/icmp.hpp" +#include "asio/ip/multicast.hpp" +#include "asio/ip/resolver_base.hpp" +#include "asio/ip/resolver_query_base.hpp" +#include "asio/ip/tcp.hpp" +#include "asio/ip/udp.hpp" +#include "asio/ip/unicast.hpp" +#include "asio/ip/v6_only.hpp" +#include "asio/is_applicable_property.hpp" +#include "asio/is_executor.hpp" +#include "asio/is_read_buffered.hpp" +#include "asio/is_write_buffered.hpp" +#include "asio/local/basic_endpoint.hpp" +#include "asio/local/connect_pair.hpp" +#include "asio/local/datagram_protocol.hpp" +#include "asio/local/stream_protocol.hpp" +#include "asio/multiple_exceptions.hpp" +#include "asio/packaged_task.hpp" +#include "asio/placeholders.hpp" +#include "asio/posix/basic_descriptor.hpp" +#include "asio/posix/basic_stream_descriptor.hpp" +#include "asio/posix/descriptor.hpp" +#include "asio/posix/descriptor_base.hpp" +#include "asio/posix/stream_descriptor.hpp" +#include "asio/post.hpp" +#include "asio/prefer.hpp" +#include "asio/query.hpp" +#include "asio/read.hpp" +#include "asio/read_at.hpp" +#include "asio/read_until.hpp" +#include "asio/redirect_error.hpp" +#include "asio/require.hpp" +#include "asio/require_concept.hpp" +#include "asio/serial_port.hpp" +#include "asio/serial_port_base.hpp" +#include "asio/signal_set.hpp" +#include "asio/socket_base.hpp" +#include "asio/static_thread_pool.hpp" +#include "asio/steady_timer.hpp" +#include "asio/strand.hpp" +#include "asio/streambuf.hpp" +#include "asio/system_context.hpp" +#include "asio/system_error.hpp" +#include "asio/system_executor.hpp" +#include "asio/system_timer.hpp" +#include "asio/this_coro.hpp" +#include "asio/thread.hpp" +#include "asio/thread_pool.hpp" +#include "asio/time_traits.hpp" +#include "asio/use_awaitable.hpp" +#include "asio/use_future.hpp" +#include "asio/uses_executor.hpp" +#include "asio/version.hpp" +#include "asio/wait_traits.hpp" +#include "asio/windows/basic_object_handle.hpp" +#include "asio/windows/basic_overlapped_handle.hpp" +#include "asio/windows/basic_random_access_handle.hpp" +#include "asio/windows/basic_stream_handle.hpp" +#include "asio/windows/object_handle.hpp" +#include "asio/windows/overlapped_handle.hpp" +#include "asio/windows/overlapped_ptr.hpp" +#include "asio/windows/random_access_handle.hpp" +#include "asio/windows/stream_handle.hpp" +#include "asio/write.hpp" +#include "asio/write_at.hpp" + +#endif // ASIO_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/any_io_executor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/any_io_executor.hpp new file mode 100644 index 000000000..3a4d13b6c --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/any_io_executor.hpp @@ -0,0 +1,71 @@ +// +// any_io_executor.hpp +// ~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_ANY_IO_EXECUTOR_HPP +#define ASIO_ANY_IO_EXECUTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#if defined(ASIO_USE_TS_EXECUTOR_AS_DEFAULT) +# include "asio/executor.hpp" +#else // defined(ASIO_USE_TS_EXECUTOR_AS_DEFAULT) +# include "asio/execution.hpp" +# include "asio/execution_context.hpp" +#endif // defined(ASIO_USE_TS_EXECUTOR_AS_DEFAULT) + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if defined(ASIO_USE_TS_EXECUTOR_AS_DEFAULT) + +typedef executor any_io_executor; + +#else // defined(ASIO_USE_TS_EXECUTOR_AS_DEFAULT) + +/// Polymorphic executor type for use with I/O objects. +/** + * The @c any_io_executor type is a polymorphic executor that supports the set + * of properties required by I/O objects. It is defined as the + * execution::any_executor class template parameterised as follows: + * @code execution::any_executor< + * execution::context_as_t, + * execution::blocking_t::never_t, + * execution::prefer_only, + * execution::prefer_only, + * execution::prefer_only, + * execution::prefer_only, + * execution::prefer_only + * > @endcode + */ +#if defined(GENERATING_DOCUMENTATION) +typedef execution::any_executor<...> any_io_executor; +#else // defined(GENERATING_DOCUMENTATION) +typedef execution::any_executor< + execution::context_as_t, + execution::blocking_t::never_t, + execution::prefer_only, + execution::prefer_only, + execution::prefer_only, + execution::prefer_only, + execution::prefer_only + > any_io_executor; +#endif // defined(GENERATING_DOCUMENTATION) + +#endif // defined(ASIO_USE_TS_EXECUTOR_AS_DEFAULT) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_ANY_IO_EXECUTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/associated_allocator.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/associated_allocator.hpp new file mode 100644 index 000000000..14d76b623 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/associated_allocator.hpp @@ -0,0 +1,125 @@ +// +// associated_allocator.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_ASSOCIATED_ALLOCATOR_HPP +#define ASIO_ASSOCIATED_ALLOCATOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include "asio/detail/type_traits.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +struct associated_allocator_impl +{ + typedef E type; + + static type get(const T&, const E& e) ASIO_NOEXCEPT + { + return e; + } +}; + +template +struct associated_allocator_impl::type> +{ + typedef typename T::allocator_type type; + + static type get(const T& t, const E&) ASIO_NOEXCEPT + { + return t.get_allocator(); + } +}; + +} // namespace detail + +/// Traits type used to obtain the allocator associated with an object. +/** + * A program may specialise this traits type if the @c T template parameter in + * the specialisation is a user-defined type. The template parameter @c + * Allocator shall be a type meeting the Allocator requirements. + * + * Specialisations shall meet the following requirements, where @c t is a const + * reference to an object of type @c T, and @c a is an object of type @c + * Allocator. + * + * @li Provide a nested typedef @c type that identifies a type meeting the + * Allocator requirements. + * + * @li Provide a noexcept static member function named @c get, callable as @c + * get(t) and with return type @c type. + * + * @li Provide a noexcept static member function named @c get, callable as @c + * get(t,a) and with return type @c type. + */ +template > +struct associated_allocator +{ + /// If @c T has a nested type @c allocator_type, T::allocator_type. + /// Otherwise @c Allocator. +#if defined(GENERATING_DOCUMENTATION) + typedef see_below type; +#else // defined(GENERATING_DOCUMENTATION) + typedef typename detail::associated_allocator_impl::type type; +#endif // defined(GENERATING_DOCUMENTATION) + + /// If @c T has a nested type @c allocator_type, returns + /// t.get_allocator(). Otherwise returns @c a. + static type get(const T& t, + const Allocator& a = Allocator()) ASIO_NOEXCEPT + { + return detail::associated_allocator_impl::get(t, a); + } +}; + +/// Helper function to obtain an object's associated allocator. +/** + * @returns associated_allocator::get(t) + */ +template +inline typename associated_allocator::type +get_associated_allocator(const T& t) ASIO_NOEXCEPT +{ + return associated_allocator::get(t); +} + +/// Helper function to obtain an object's associated allocator. +/** + * @returns associated_allocator::get(t, a) + */ +template +inline typename associated_allocator::type +get_associated_allocator(const T& t, const Allocator& a) ASIO_NOEXCEPT +{ + return associated_allocator::get(t, a); +} + +#if defined(ASIO_HAS_ALIAS_TEMPLATES) + +template > +using associated_allocator_t + = typename associated_allocator::type; + +#endif // defined(ASIO_HAS_ALIAS_TEMPLATES) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_ASSOCIATED_ALLOCATOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/associated_executor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/associated_executor.hpp new file mode 100644 index 000000000..e1792466f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/associated_executor.hpp @@ -0,0 +1,166 @@ +// +// associated_executor.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_ASSOCIATED_EXECUTOR_HPP +#define ASIO_ASSOCIATED_EXECUTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/executor.hpp" +#include "asio/is_executor.hpp" +#include "asio/system_executor.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +struct associated_executor_impl +{ + typedef void asio_associated_executor_is_unspecialised; + + typedef E type; + + static type get(const T&, const E& e = E()) ASIO_NOEXCEPT + { + return e; + } +}; + +template +struct associated_executor_impl::type> +{ + typedef typename T::executor_type type; + + static type get(const T& t, const E& = E()) ASIO_NOEXCEPT + { + return t.get_executor(); + } +}; + +} // namespace detail + +/// Traits type used to obtain the executor associated with an object. +/** + * A program may specialise this traits type if the @c T template parameter in + * the specialisation is a user-defined type. The template parameter @c + * Executor shall be a type meeting the Executor requirements. + * + * Specialisations shall meet the following requirements, where @c t is a const + * reference to an object of type @c T, and @c e is an object of type @c + * Executor. + * + * @li Provide a nested typedef @c type that identifies a type meeting the + * Executor requirements. + * + * @li Provide a noexcept static member function named @c get, callable as @c + * get(t) and with return type @c type. + * + * @li Provide a noexcept static member function named @c get, callable as @c + * get(t,e) and with return type @c type. + */ +template +struct associated_executor +#if !defined(GENERATING_DOCUMENTATION) + : detail::associated_executor_impl +#endif // !defined(GENERATING_DOCUMENTATION) +{ +#if defined(GENERATING_DOCUMENTATION) + /// If @c T has a nested type @c executor_type, T::executor_type. + /// Otherwise @c Executor. + typedef see_below type; + + /// If @c T has a nested type @c executor_type, returns + /// t.get_executor(). Otherwise returns @c ex. + static type get(const T& t, + const Executor& ex = Executor()) ASIO_NOEXCEPT; +#endif // defined(GENERATING_DOCUMENTATION) +}; + +/// Helper function to obtain an object's associated executor. +/** + * @returns associated_executor::get(t) + */ +template +inline typename associated_executor::type +get_associated_executor(const T& t) ASIO_NOEXCEPT +{ + return associated_executor::get(t); +} + +/// Helper function to obtain an object's associated executor. +/** + * @returns associated_executor::get(t, ex) + */ +template +inline typename associated_executor::type +get_associated_executor(const T& t, const Executor& ex, + typename enable_if< + is_executor::value || execution::is_executor::value + >::type* = 0) ASIO_NOEXCEPT +{ + return associated_executor::get(t, ex); +} + +/// Helper function to obtain an object's associated executor. +/** + * @returns associated_executor::get(t, ctx.get_executor()) + */ +template +inline typename associated_executor::type +get_associated_executor(const T& t, ExecutionContext& ctx, + typename enable_if::value>::type* = 0) ASIO_NOEXCEPT +{ + return associated_executor::get(t, ctx.get_executor()); +} + +#if defined(ASIO_HAS_ALIAS_TEMPLATES) + +template +using associated_executor_t = typename associated_executor::type; + +#endif // defined(ASIO_HAS_ALIAS_TEMPLATES) + +namespace detail { + +template +struct associated_executor_forwarding_base +{ +}; + +template +struct associated_executor_forwarding_base::asio_associated_executor_is_unspecialised, + void + >::value + >::type> +{ + typedef void asio_associated_executor_is_unspecialised; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_ASSOCIATED_EXECUTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/async_result.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/async_result.hpp new file mode 100644 index 000000000..9ccda6cbd --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/async_result.hpp @@ -0,0 +1,582 @@ +// +// async_result.hpp +// ~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_ASYNC_RESULT_HPP +#define ASIO_ASYNC_RESULT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/detail/variadic_templates.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if defined(ASIO_HAS_CONCEPTS) \ + && defined(ASIO_HAS_VARIADIC_TEMPLATES) \ + && defined(ASIO_HAS_DECLTYPE) + +namespace detail { + +template +struct is_completion_signature : false_type +{ +}; + +template +struct is_completion_signature : true_type +{ +}; + +template +ASIO_CONCEPT callable_with = requires(T t, Args&&... args) +{ + t(static_cast(args)...); +}; + +template +struct is_completion_handler_for : false_type +{ +}; + +template +struct is_completion_handler_for + : integral_constant)> +{ +}; + +} // namespace detail + +template +ASIO_CONCEPT completion_signature = + detail::is_completion_signature::value; + +#define ASIO_COMPLETION_SIGNATURE \ + ::asio::completion_signature + +template +ASIO_CONCEPT completion_handler_for = + detail::is_completion_signature::value + && detail::is_completion_handler_for::value; + +#define ASIO_COMPLETION_HANDLER_FOR(s) \ + ::asio::completion_handler_for + +#else // defined(ASIO_HAS_CONCEPTS) + // && defined(ASIO_HAS_VARIADIC_TEMPLATES) + // && defined(ASIO_HAS_DECLTYPE) + +#define ASIO_COMPLETION_SIGNATURE typename +#define ASIO_COMPLETION_HANDLER_FOR(s) typename + +#endif // defined(ASIO_HAS_CONCEPTS) + // && defined(ASIO_HAS_VARIADIC_TEMPLATES) + // && defined(ASIO_HAS_DECLTYPE) + +/// An interface for customising the behaviour of an initiating function. +/** + * The async_result traits class is used for determining: + * + * @li the concrete completion handler type to be called at the end of the + * asynchronous operation; + * + * @li the initiating function return type; and + * + * @li how the return value of the initiating function is obtained. + * + * The trait allows the handler and return types to be determined at the point + * where the specific completion handler signature is known. + * + * This template may be specialised for user-defined completion token types. + * The primary template assumes that the CompletionToken is the completion + * handler. + */ +template +class async_result +{ +public: + /// The concrete completion handler type for the specific signature. + typedef CompletionToken completion_handler_type; + + /// The return type of the initiating function. + typedef void return_type; + + /// Construct an async result from a given handler. + /** + * When using a specalised async_result, the constructor has an opportunity + * to initialise some state associated with the completion handler, which is + * then returned from the initiating function. + */ + explicit async_result(completion_handler_type& h) + { + (void)h; + } + + /// Obtain the value to be returned from the initiating function. + return_type get() + { + } + +#if defined(GENERATING_DOCUMENTATION) + + /// Initiate the asynchronous operation that will produce the result, and + /// obtain the value to be returned from the initiating function. + template + static return_type initiate( + ASIO_MOVE_ARG(Initiation) initiation, + ASIO_MOVE_ARG(RawCompletionToken) token, + ASIO_MOVE_ARG(Args)... args); + +#elif defined(ASIO_HAS_VARIADIC_TEMPLATES) + + template + static return_type initiate( + ASIO_MOVE_ARG(Initiation) initiation, + ASIO_MOVE_ARG(RawCompletionToken) token, + ASIO_MOVE_ARG(Args)... args) + { + ASIO_MOVE_CAST(Initiation)(initiation)( + ASIO_MOVE_CAST(RawCompletionToken)(token), + ASIO_MOVE_CAST(Args)(args)...); + } + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + + template + static return_type initiate( + ASIO_MOVE_ARG(Initiation) initiation, + ASIO_MOVE_ARG(RawCompletionToken) token) + { + ASIO_MOVE_CAST(Initiation)(initiation)( + ASIO_MOVE_CAST(RawCompletionToken)(token)); + } + +#define ASIO_PRIVATE_INITIATE_DEF(n) \ + template \ + static return_type initiate( \ + ASIO_MOVE_ARG(Initiation) initiation, \ + ASIO_MOVE_ARG(RawCompletionToken) token, \ + ASIO_VARIADIC_MOVE_PARAMS(n)) \ + { \ + ASIO_MOVE_CAST(Initiation)(initiation)( \ + ASIO_MOVE_CAST(RawCompletionToken)(token), \ + ASIO_VARIADIC_MOVE_ARGS(n)); \ + } \ + /**/ + ASIO_VARIADIC_GENERATE(ASIO_PRIVATE_INITIATE_DEF) +#undef ASIO_PRIVATE_INITIATE_DEF + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +private: + async_result(const async_result&) ASIO_DELETED; + async_result& operator=(const async_result&) ASIO_DELETED; +}; + +#if !defined(GENERATING_DOCUMENTATION) + +template +class async_result +{ + // Empty. +}; + +#endif // !defined(GENERATING_DOCUMENTATION) + +/// Helper template to deduce the handler type from a CompletionToken, capture +/// a local copy of the handler, and then create an async_result for the +/// handler. +template +struct async_completion +{ + /// The real handler type to be used for the asynchronous operation. + typedef typename asio::async_result< + typename decay::type, + Signature>::completion_handler_type completion_handler_type; + +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + /// Constructor. + /** + * The constructor creates the concrete completion handler and makes the link + * between the handler and the asynchronous result. + */ + explicit async_completion(CompletionToken& token) + : completion_handler(static_cast::value, + completion_handler_type&, CompletionToken&&>::type>(token)), + result(completion_handler) + { + } +#else // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + explicit async_completion(typename decay::type& token) + : completion_handler(token), + result(completion_handler) + { + } + + explicit async_completion(const typename decay::type& token) + : completion_handler(token), + result(completion_handler) + { + } +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + /// A copy of, or reference to, a real handler object. +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + typename conditional< + is_same::value, + completion_handler_type&, completion_handler_type>::type completion_handler; +#else // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + completion_handler_type completion_handler; +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + /// The result of the asynchronous operation's initiating function. + async_result::type, Signature> result; +}; + +namespace detail { + +template +struct async_result_helper + : async_result::type, Signature> +{ +}; + +struct async_result_memfns_base +{ + void initiate(); +}; + +template +struct async_result_memfns_derived + : T, async_result_memfns_base +{ +}; + +template +struct async_result_memfns_check +{ +}; + +template +char (&async_result_initiate_memfn_helper(...))[2]; + +template +char async_result_initiate_memfn_helper( + async_result_memfns_check< + void (async_result_memfns_base::*)(), + &async_result_memfns_derived::initiate>*); + +template +struct async_result_has_initiate_memfn + : integral_constant::type, Signature> + >(0)) != 1> +{ +}; + +} // namespace detail + +#if defined(GENERATING_DOCUMENTATION) +# define ASIO_INITFN_RESULT_TYPE(ct, sig) \ + void_or_deduced +#elif defined(_MSC_VER) && (_MSC_VER < 1500) +# define ASIO_INITFN_RESULT_TYPE(ct, sig) \ + typename ::asio::detail::async_result_helper< \ + ct, sig>::return_type +#define ASIO_HANDLER_TYPE(ct, sig) \ + typename ::asio::detail::async_result_helper< \ + ct, sig>::completion_handler_type +#else +# define ASIO_INITFN_RESULT_TYPE(ct, sig) \ + typename ::asio::async_result< \ + typename ::asio::decay::type, sig>::return_type +#define ASIO_HANDLER_TYPE(ct, sig) \ + typename ::asio::async_result< \ + typename ::asio::decay::type, sig>::completion_handler_type +#endif + +#if defined(GENERATION_DOCUMENTATION) +# define ASIO_INITFN_AUTO_RESULT_TYPE(ct, sig) \ + auto +#elif defined(ASIO_HAS_RETURN_TYPE_DEDUCTION) +# define ASIO_INITFN_AUTO_RESULT_TYPE(ct, sig) \ + auto +#else +# define ASIO_INITFN_AUTO_RESULT_TYPE(ct, sig) \ + ASIO_INITFN_RESULT_TYPE(ct, sig) +#endif + +#if defined(GENERATION_DOCUMENTATION) +# define ASIO_INITFN_DEDUCED_RESULT_TYPE(ct, sig, expr) \ + void_or_deduced +#elif defined(ASIO_HAS_DECLTYPE) +# define ASIO_INITFN_DEDUCED_RESULT_TYPE(ct, sig, expr) \ + decltype expr +#else +# define ASIO_INITFN_DEDUCED_RESULT_TYPE(ct, sig, expr) \ + ASIO_INITFN_RESULT_TYPE(ct, sig) +#endif + +#if defined(GENERATING_DOCUMENTATION) + +template +void_or_deduced async_initiate( + ASIO_MOVE_ARG(Initiation) initiation, + ASIO_NONDEDUCED_MOVE_ARG(CompletionToken), + ASIO_MOVE_ARG(Args)... args); + +#elif defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template +inline typename enable_if< + detail::async_result_has_initiate_memfn::value, + ASIO_INITFN_DEDUCED_RESULT_TYPE(CompletionToken, Signature, + (async_result::type, + Signature>::initiate(declval(), + declval(), + declval()...)))>::type +async_initiate(ASIO_MOVE_ARG(Initiation) initiation, + ASIO_NONDEDUCED_MOVE_ARG(CompletionToken) token, + ASIO_MOVE_ARG(Args)... args) +{ + return async_result::type, + Signature>::initiate(ASIO_MOVE_CAST(Initiation)(initiation), + ASIO_MOVE_CAST(CompletionToken)(token), + ASIO_MOVE_CAST(Args)(args)...); +} + +template +inline typename enable_if< + !detail::async_result_has_initiate_memfn::value, + ASIO_INITFN_RESULT_TYPE(CompletionToken, Signature)>::type +async_initiate(ASIO_MOVE_ARG(Initiation) initiation, + ASIO_NONDEDUCED_MOVE_ARG(CompletionToken) token, + ASIO_MOVE_ARG(Args)... args) +{ + async_completion completion(token); + + ASIO_MOVE_CAST(Initiation)(initiation)( + ASIO_MOVE_CAST(ASIO_HANDLER_TYPE(CompletionToken, + Signature))(completion.completion_handler), + ASIO_MOVE_CAST(Args)(args)...); + + return completion.result.get(); +} + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template +inline typename enable_if< + detail::async_result_has_initiate_memfn::value, + ASIO_INITFN_DEDUCED_RESULT_TYPE(CompletionToken, Signature, + (async_result::type, + Signature>::initiate(declval(), + declval())))>::type +async_initiate(ASIO_MOVE_ARG(Initiation) initiation, + ASIO_NONDEDUCED_MOVE_ARG(CompletionToken) token) +{ + return async_result::type, + Signature>::initiate(ASIO_MOVE_CAST(Initiation)(initiation), + ASIO_MOVE_CAST(CompletionToken)(token)); +} + +template +inline typename enable_if< + !detail::async_result_has_initiate_memfn::value, + ASIO_INITFN_RESULT_TYPE(CompletionToken, Signature)>::type +async_initiate(ASIO_MOVE_ARG(Initiation) initiation, + ASIO_NONDEDUCED_MOVE_ARG(CompletionToken) token) +{ + async_completion completion(token); + + ASIO_MOVE_CAST(Initiation)(initiation)( + ASIO_MOVE_CAST(ASIO_HANDLER_TYPE(CompletionToken, + Signature))(completion.completion_handler)); + + return completion.result.get(); +} + +#define ASIO_PRIVATE_INITIATE_DEF(n) \ + template \ + inline typename enable_if< \ + detail::async_result_has_initiate_memfn< \ + CompletionToken, Signature>::value, \ + ASIO_INITFN_DEDUCED_RESULT_TYPE(CompletionToken, Signature, \ + (async_result::type, \ + Signature>::initiate(declval(), \ + declval(), \ + ASIO_VARIADIC_MOVE_DECLVAL(n))))>::type \ + async_initiate(ASIO_MOVE_ARG(Initiation) initiation, \ + ASIO_NONDEDUCED_MOVE_ARG(CompletionToken) token, \ + ASIO_VARIADIC_MOVE_PARAMS(n)) \ + { \ + return async_result::type, \ + Signature>::initiate(ASIO_MOVE_CAST(Initiation)(initiation), \ + ASIO_MOVE_CAST(CompletionToken)(token), \ + ASIO_VARIADIC_MOVE_ARGS(n)); \ + } \ + \ + template \ + inline typename enable_if< \ + !detail::async_result_has_initiate_memfn< \ + CompletionToken, Signature>::value, \ + ASIO_INITFN_RESULT_TYPE(CompletionToken, Signature)>::type \ + async_initiate(ASIO_MOVE_ARG(Initiation) initiation, \ + ASIO_NONDEDUCED_MOVE_ARG(CompletionToken) token, \ + ASIO_VARIADIC_MOVE_PARAMS(n)) \ + { \ + async_completion completion(token); \ + \ + ASIO_MOVE_CAST(Initiation)(initiation)( \ + ASIO_MOVE_CAST(ASIO_HANDLER_TYPE(CompletionToken, \ + Signature))(completion.completion_handler), \ + ASIO_VARIADIC_MOVE_ARGS(n)); \ + \ + return completion.result.get(); \ + } \ + /**/ + ASIO_VARIADIC_GENERATE(ASIO_PRIVATE_INITIATE_DEF) +#undef ASIO_PRIVATE_INITIATE_DEF + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +#if defined(ASIO_HAS_CONCEPTS) \ + && defined(ASIO_HAS_VARIADIC_TEMPLATES) \ + && defined(ASIO_HAS_DECLTYPE) + +namespace detail { + +template +struct initiation_archetype +{ + template CompletionHandler> + void operator()(CompletionHandler&&) const + { + } +}; + +} // namespace detail + +template +ASIO_CONCEPT completion_token_for = + detail::is_completion_signature::value + && + requires(T&& t) + { + async_initiate(detail::initiation_archetype{}, t); + }; + +#define ASIO_COMPLETION_TOKEN_FOR(s) \ + ::asio::completion_token_for + +#else // defined(ASIO_HAS_CONCEPTS) + // && defined(ASIO_HAS_VARIADIC_TEMPLATES) + // && defined(ASIO_HAS_DECLTYPE) + +#define ASIO_COMPLETION_TOKEN_FOR(s) typename + +#endif // defined(ASIO_HAS_CONCEPTS) + // && defined(ASIO_HAS_VARIADIC_TEMPLATES) + // && defined(ASIO_HAS_DECLTYPE) + +namespace detail { + +template +struct default_completion_token_impl +{ + typedef void type; +}; + +template +struct default_completion_token_impl::type> +{ + typedef typename T::default_completion_token_type type; +}; + +} // namespace detail + +#if defined(GENERATING_DOCUMENTATION) + +/// Traits type used to determine the default completion token type associated +/// with a type (such as an executor). +/** + * A program may specialise this traits type if the @c T template parameter in + * the specialisation is a user-defined type. + * + * Specialisations of this trait may provide a nested typedef @c type, which is + * a default-constructible completion token type. + */ +template +struct default_completion_token +{ + /// If @c T has a nested type @c default_completion_token_type, + /// T::default_completion_token_type. Otherwise the typedef @c type + /// is not defined. + typedef see_below type; +}; +#else +template +struct default_completion_token + : detail::default_completion_token_impl +{ +}; +#endif + +#if defined(ASIO_HAS_ALIAS_TEMPLATES) + +template +using default_completion_token_t = typename default_completion_token::type; + +#endif // defined(ASIO_HAS_ALIAS_TEMPLATES) + +#if defined(ASIO_HAS_DEFAULT_FUNCTION_TEMPLATE_ARGUMENTS) + +#define ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(e) \ + = typename ::asio::default_completion_token::type +#define ASIO_DEFAULT_COMPLETION_TOKEN(e) \ + = typename ::asio::default_completion_token::type() + +#else // defined(ASIO_HAS_DEFAULT_FUNCTION_TEMPLATE_ARGUMENTS) + +#define ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(e) +#define ASIO_DEFAULT_COMPLETION_TOKEN(e) + +#endif // defined(ASIO_HAS_DEFAULT_FUNCTION_TEMPLATE_ARGUMENTS) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_ASYNC_RESULT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/awaitable.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/awaitable.hpp new file mode 100644 index 000000000..e9c74c843 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/awaitable.hpp @@ -0,0 +1,133 @@ +// +// awaitable.hpp +// ~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_AWAITABLE_HPP +#define ASIO_AWAITABLE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_CO_AWAIT) || defined(GENERATING_DOCUMENTATION) + +#if defined(ASIO_HAS_STD_COROUTINE) +# include +#else // defined(ASIO_HAS_STD_COROUTINE) +# include +#endif // defined(ASIO_HAS_STD_COROUTINE) + +#include "asio/any_io_executor.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +#if defined(ASIO_HAS_STD_COROUTINE) +using std::coroutine_handle; +using std::suspend_always; +#else // defined(ASIO_HAS_STD_COROUTINE) +using std::experimental::coroutine_handle; +using std::experimental::suspend_always; +#endif // defined(ASIO_HAS_STD_COROUTINE) + +template class awaitable_thread; +template class awaitable_frame; + +} // namespace detail + +/// The return type of a coroutine or asynchronous operation. +template +class awaitable +{ +public: + /// The type of the awaited value. + typedef T value_type; + + /// The executor type that will be used for the coroutine. + typedef Executor executor_type; + + /// Default constructor. + constexpr awaitable() noexcept + : frame_(nullptr) + { + } + + /// Move constructor. + awaitable(awaitable&& other) noexcept + : frame_(std::exchange(other.frame_, nullptr)) + { + } + + /// Destructor + ~awaitable() + { + if (frame_) + frame_->destroy(); + } + + /// Checks if the awaitable refers to a future result. + bool valid() const noexcept + { + return !!frame_; + } + +#if !defined(GENERATING_DOCUMENTATION) + + // Support for co_await keyword. + bool await_ready() const noexcept + { + return false; + } + + // Support for co_await keyword. + template + void await_suspend( + detail::coroutine_handle> h) + { + frame_->push_frame(&h.promise()); + } + + // Support for co_await keyword. + T await_resume() + { + return awaitable(static_cast(*this)).frame_->get(); + } + +#endif // !defined(GENERATING_DOCUMENTATION) + +private: + template friend class detail::awaitable_thread; + template friend class detail::awaitable_frame; + + // Not copy constructible or copy assignable. + awaitable(const awaitable&) = delete; + awaitable& operator=(const awaitable&) = delete; + + // Construct the awaitable from a coroutine's frame object. + explicit awaitable(detail::awaitable_frame* a) + : frame_(a) + { + } + + detail::awaitable_frame* frame_; +}; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/impl/awaitable.hpp" + +#endif // defined(ASIO_HAS_CO_AWAIT) || defined(GENERATING_DOCUMENTATION) + +#endif // ASIO_AWAITABLE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_datagram_socket.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_datagram_socket.hpp new file mode 100644 index 000000000..ce767ae86 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_datagram_socket.hpp @@ -0,0 +1,1215 @@ +// +// basic_datagram_socket.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BASIC_DATAGRAM_SOCKET_HPP +#define ASIO_BASIC_DATAGRAM_SOCKET_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include "asio/basic_socket.hpp" +#include "asio/detail/handler_type_requirements.hpp" +#include "asio/detail/non_const_lvalue.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if !defined(ASIO_BASIC_DATAGRAM_SOCKET_FWD_DECL) +#define ASIO_BASIC_DATAGRAM_SOCKET_FWD_DECL + +// Forward declaration with defaulted arguments. +template +class basic_datagram_socket; + +#endif // !defined(ASIO_BASIC_DATAGRAM_SOCKET_FWD_DECL) + +/// Provides datagram-oriented socket functionality. +/** + * The basic_datagram_socket class template provides asynchronous and blocking + * datagram-oriented socket functionality. + * + * @par Thread Safety + * @e Distinct @e objects: Safe.@n + * @e Shared @e objects: Unsafe. + */ +template +class basic_datagram_socket + : public basic_socket +{ +public: + /// The type of the executor associated with the object. + typedef Executor executor_type; + + /// Rebinds the socket type to another executor. + template + struct rebind_executor + { + /// The socket type when rebound to the specified executor. + typedef basic_datagram_socket other; + }; + + /// The native representation of a socket. +#if defined(GENERATING_DOCUMENTATION) + typedef implementation_defined native_handle_type; +#else + typedef typename basic_socket::native_handle_type native_handle_type; +#endif + + /// The protocol type. + typedef Protocol protocol_type; + + /// The endpoint type. + typedef typename Protocol::endpoint endpoint_type; + + /// Construct a basic_datagram_socket without opening it. + /** + * This constructor creates a datagram socket without opening it. The open() + * function must be called before data can be sent or received on the socket. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + */ + explicit basic_datagram_socket(const executor_type& ex) + : basic_socket(ex) + { + } + + /// Construct a basic_datagram_socket without opening it. + /** + * This constructor creates a datagram socket without opening it. The open() + * function must be called before data can be sent or received on the socket. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + */ + template + explicit basic_datagram_socket(ExecutionContext& context, + typename enable_if< + is_convertible::value + >::type* = 0) + : basic_socket(context) + { + } + + /// Construct and open a basic_datagram_socket. + /** + * This constructor creates and opens a datagram socket. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @throws asio::system_error Thrown on failure. + */ + basic_datagram_socket(const executor_type& ex, const protocol_type& protocol) + : basic_socket(ex, protocol) + { + } + + /// Construct and open a basic_datagram_socket. + /** + * This constructor creates and opens a datagram socket. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_datagram_socket(ExecutionContext& context, + const protocol_type& protocol, + typename enable_if< + is_convertible::value + >::type* = 0) + : basic_socket(context, protocol) + { + } + + /// Construct a basic_datagram_socket, opening it and binding it to the given + /// local endpoint. + /** + * This constructor creates a datagram socket and automatically opens it bound + * to the specified endpoint on the local machine. The protocol used is the + * protocol associated with the given endpoint. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + * + * @param endpoint An endpoint on the local machine to which the datagram + * socket will be bound. + * + * @throws asio::system_error Thrown on failure. + */ + basic_datagram_socket(const executor_type& ex, const endpoint_type& endpoint) + : basic_socket(ex, endpoint) + { + } + + /// Construct a basic_datagram_socket, opening it and binding it to the given + /// local endpoint. + /** + * This constructor creates a datagram socket and automatically opens it bound + * to the specified endpoint on the local machine. The protocol used is the + * protocol associated with the given endpoint. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + * + * @param endpoint An endpoint on the local machine to which the datagram + * socket will be bound. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_datagram_socket(ExecutionContext& context, + const endpoint_type& endpoint, + typename enable_if< + is_convertible::value + >::type* = 0) + : basic_socket(context, endpoint) + { + } + + /// Construct a basic_datagram_socket on an existing native socket. + /** + * This constructor creates a datagram socket object to hold an existing + * native socket. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @param native_socket The new underlying socket implementation. + * + * @throws asio::system_error Thrown on failure. + */ + basic_datagram_socket(const executor_type& ex, + const protocol_type& protocol, const native_handle_type& native_socket) + : basic_socket(ex, protocol, native_socket) + { + } + + /// Construct a basic_datagram_socket on an existing native socket. + /** + * This constructor creates a datagram socket object to hold an existing + * native socket. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @param native_socket The new underlying socket implementation. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_datagram_socket(ExecutionContext& context, + const protocol_type& protocol, const native_handle_type& native_socket, + typename enable_if< + is_convertible::value + >::type* = 0) + : basic_socket(context, protocol, native_socket) + { + } + +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + /// Move-construct a basic_datagram_socket from another. + /** + * This constructor moves a datagram socket from one object to another. + * + * @param other The other basic_datagram_socket object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_datagram_socket(const executor_type&) + * constructor. + */ + basic_datagram_socket(basic_datagram_socket&& other) ASIO_NOEXCEPT + : basic_socket(std::move(other)) + { + } + + /// Move-assign a basic_datagram_socket from another. + /** + * This assignment operator moves a datagram socket from one object to + * another. + * + * @param other The other basic_datagram_socket object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_datagram_socket(const executor_type&) + * constructor. + */ + basic_datagram_socket& operator=(basic_datagram_socket&& other) + { + basic_socket::operator=(std::move(other)); + return *this; + } + + /// Move-construct a basic_datagram_socket from a socket of another protocol + /// type. + /** + * This constructor moves a datagram socket from one object to another. + * + * @param other The other basic_datagram_socket object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_datagram_socket(const executor_type&) + * constructor. + */ + template + basic_datagram_socket(basic_datagram_socket&& other, + typename enable_if< + is_convertible::value + && is_convertible::value + >::type* = 0) + : basic_socket(std::move(other)) + { + } + + /// Move-assign a basic_datagram_socket from a socket of another protocol + /// type. + /** + * This assignment operator moves a datagram socket from one object to + * another. + * + * @param other The other basic_datagram_socket object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_datagram_socket(const executor_type&) + * constructor. + */ + template + typename enable_if< + is_convertible::value + && is_convertible::value, + basic_datagram_socket& + >::type operator=(basic_datagram_socket&& other) + { + basic_socket::operator=(std::move(other)); + return *this; + } +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + /// Destroys the socket. + /** + * This function destroys the socket, cancelling any outstanding asynchronous + * operations associated with the socket as if by calling @c cancel. + */ + ~basic_datagram_socket() + { + } + + /// Send some data on a connected socket. + /** + * This function is used to send data on the datagram socket. The function + * call will block until the data has been sent successfully or an error + * occurs. + * + * @param buffers One ore more data buffers to be sent on the socket. + * + * @returns The number of bytes sent. + * + * @throws asio::system_error Thrown on failure. + * + * @note The send operation can only be used with a connected socket. Use + * the send_to function to send data on an unconnected datagram socket. + * + * @par Example + * To send a single data buffer use the @ref buffer function as follows: + * @code socket.send(asio::buffer(data, size)); @endcode + * See the @ref buffer documentation for information on sending multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t send(const ConstBufferSequence& buffers) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().send( + this->impl_.get_implementation(), buffers, 0, ec); + asio::detail::throw_error(ec, "send"); + return s; + } + + /// Send some data on a connected socket. + /** + * This function is used to send data on the datagram socket. The function + * call will block until the data has been sent successfully or an error + * occurs. + * + * @param buffers One ore more data buffers to be sent on the socket. + * + * @param flags Flags specifying how the send call is to be made. + * + * @returns The number of bytes sent. + * + * @throws asio::system_error Thrown on failure. + * + * @note The send operation can only be used with a connected socket. Use + * the send_to function to send data on an unconnected datagram socket. + */ + template + std::size_t send(const ConstBufferSequence& buffers, + socket_base::message_flags flags) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().send( + this->impl_.get_implementation(), buffers, flags, ec); + asio::detail::throw_error(ec, "send"); + return s; + } + + /// Send some data on a connected socket. + /** + * This function is used to send data on the datagram socket. The function + * call will block until the data has been sent successfully or an error + * occurs. + * + * @param buffers One or more data buffers to be sent on the socket. + * + * @param flags Flags specifying how the send call is to be made. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns The number of bytes sent. + * + * @note The send operation can only be used with a connected socket. Use + * the send_to function to send data on an unconnected datagram socket. + */ + template + std::size_t send(const ConstBufferSequence& buffers, + socket_base::message_flags flags, asio::error_code& ec) + { + return this->impl_.get_service().send( + this->impl_.get_implementation(), buffers, flags, ec); + } + + /// Start an asynchronous send on a connected socket. + /** + * This function is used to asynchronously send data on the datagram socket. + * The function call always returns immediately. + * + * @param buffers One or more data buffers to be sent on the socket. Although + * the buffers object may be copied as necessary, ownership of the underlying + * memory blocks is retained by the caller, which must guarantee that they + * remain valid until the handler is called. + * + * @param handler The handler to be called when the send operation completes. + * Copies will be made of the handler as required. The function signature of + * the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes sent. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note The async_send operation can only be used with a connected socket. + * Use the async_send_to function to send data on an unconnected datagram + * socket. + * + * @par Example + * To send a single data buffer use the @ref buffer function as follows: + * @code + * socket.async_send(asio::buffer(data, size), handler); + * @endcode + * See the @ref buffer documentation for information on sending multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_send(const ConstBufferSequence& buffers, + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_send(this), handler, + buffers, socket_base::message_flags(0)); + } + + /// Start an asynchronous send on a connected socket. + /** + * This function is used to asynchronously send data on the datagram socket. + * The function call always returns immediately. + * + * @param buffers One or more data buffers to be sent on the socket. Although + * the buffers object may be copied as necessary, ownership of the underlying + * memory blocks is retained by the caller, which must guarantee that they + * remain valid until the handler is called. + * + * @param flags Flags specifying how the send call is to be made. + * + * @param handler The handler to be called when the send operation completes. + * Copies will be made of the handler as required. The function signature of + * the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes sent. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note The async_send operation can only be used with a connected socket. + * Use the async_send_to function to send data on an unconnected datagram + * socket. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_send(const ConstBufferSequence& buffers, + socket_base::message_flags flags, + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_send(this), handler, buffers, flags); + } + + /// Send a datagram to the specified endpoint. + /** + * This function is used to send a datagram to the specified remote endpoint. + * The function call will block until the data has been sent successfully or + * an error occurs. + * + * @param buffers One or more data buffers to be sent to the remote endpoint. + * + * @param destination The remote endpoint to which the data will be sent. + * + * @returns The number of bytes sent. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * To send a single data buffer use the @ref buffer function as follows: + * @code + * asio::ip::udp::endpoint destination( + * asio::ip::address::from_string("1.2.3.4"), 12345); + * socket.send_to(asio::buffer(data, size), destination); + * @endcode + * See the @ref buffer documentation for information on sending multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t send_to(const ConstBufferSequence& buffers, + const endpoint_type& destination) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().send_to( + this->impl_.get_implementation(), buffers, destination, 0, ec); + asio::detail::throw_error(ec, "send_to"); + return s; + } + + /// Send a datagram to the specified endpoint. + /** + * This function is used to send a datagram to the specified remote endpoint. + * The function call will block until the data has been sent successfully or + * an error occurs. + * + * @param buffers One or more data buffers to be sent to the remote endpoint. + * + * @param destination The remote endpoint to which the data will be sent. + * + * @param flags Flags specifying how the send call is to be made. + * + * @returns The number of bytes sent. + * + * @throws asio::system_error Thrown on failure. + */ + template + std::size_t send_to(const ConstBufferSequence& buffers, + const endpoint_type& destination, socket_base::message_flags flags) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().send_to( + this->impl_.get_implementation(), buffers, destination, flags, ec); + asio::detail::throw_error(ec, "send_to"); + return s; + } + + /// Send a datagram to the specified endpoint. + /** + * This function is used to send a datagram to the specified remote endpoint. + * The function call will block until the data has been sent successfully or + * an error occurs. + * + * @param buffers One or more data buffers to be sent to the remote endpoint. + * + * @param destination The remote endpoint to which the data will be sent. + * + * @param flags Flags specifying how the send call is to be made. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns The number of bytes sent. + */ + template + std::size_t send_to(const ConstBufferSequence& buffers, + const endpoint_type& destination, socket_base::message_flags flags, + asio::error_code& ec) + { + return this->impl_.get_service().send_to(this->impl_.get_implementation(), + buffers, destination, flags, ec); + } + + /// Start an asynchronous send. + /** + * This function is used to asynchronously send a datagram to the specified + * remote endpoint. The function call always returns immediately. + * + * @param buffers One or more data buffers to be sent to the remote endpoint. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param destination The remote endpoint to which the data will be sent. + * Copies will be made of the endpoint as required. + * + * @param handler The handler to be called when the send operation completes. + * Copies will be made of the handler as required. The function signature of + * the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes sent. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * To send a single data buffer use the @ref buffer function as follows: + * @code + * asio::ip::udp::endpoint destination( + * asio::ip::address::from_string("1.2.3.4"), 12345); + * socket.async_send_to( + * asio::buffer(data, size), destination, handler); + * @endcode + * See the @ref buffer documentation for information on sending multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_send_to(const ConstBufferSequence& buffers, + const endpoint_type& destination, + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_send_to(this), handler, buffers, + destination, socket_base::message_flags(0)); + } + + /// Start an asynchronous send. + /** + * This function is used to asynchronously send a datagram to the specified + * remote endpoint. The function call always returns immediately. + * + * @param buffers One or more data buffers to be sent to the remote endpoint. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param flags Flags specifying how the send call is to be made. + * + * @param destination The remote endpoint to which the data will be sent. + * Copies will be made of the endpoint as required. + * + * @param handler The handler to be called when the send operation completes. + * Copies will be made of the handler as required. The function signature of + * the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes sent. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_send_to(const ConstBufferSequence& buffers, + const endpoint_type& destination, socket_base::message_flags flags, + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_send_to(this), handler, buffers, destination, flags); + } + + /// Receive some data on a connected socket. + /** + * This function is used to receive data on the datagram socket. The function + * call will block until data has been received successfully or an error + * occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @returns The number of bytes received. + * + * @throws asio::system_error Thrown on failure. + * + * @note The receive operation can only be used with a connected socket. Use + * the receive_from function to receive data on an unconnected datagram + * socket. + * + * @par Example + * To receive into a single data buffer use the @ref buffer function as + * follows: + * @code socket.receive(asio::buffer(data, size)); @endcode + * See the @ref buffer documentation for information on receiving into + * multiple buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t receive(const MutableBufferSequence& buffers) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().receive( + this->impl_.get_implementation(), buffers, 0, ec); + asio::detail::throw_error(ec, "receive"); + return s; + } + + /// Receive some data on a connected socket. + /** + * This function is used to receive data on the datagram socket. The function + * call will block until data has been received successfully or an error + * occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @param flags Flags specifying how the receive call is to be made. + * + * @returns The number of bytes received. + * + * @throws asio::system_error Thrown on failure. + * + * @note The receive operation can only be used with a connected socket. Use + * the receive_from function to receive data on an unconnected datagram + * socket. + */ + template + std::size_t receive(const MutableBufferSequence& buffers, + socket_base::message_flags flags) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().receive( + this->impl_.get_implementation(), buffers, flags, ec); + asio::detail::throw_error(ec, "receive"); + return s; + } + + /// Receive some data on a connected socket. + /** + * This function is used to receive data on the datagram socket. The function + * call will block until data has been received successfully or an error + * occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @param flags Flags specifying how the receive call is to be made. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns The number of bytes received. + * + * @note The receive operation can only be used with a connected socket. Use + * the receive_from function to receive data on an unconnected datagram + * socket. + */ + template + std::size_t receive(const MutableBufferSequence& buffers, + socket_base::message_flags flags, asio::error_code& ec) + { + return this->impl_.get_service().receive( + this->impl_.get_implementation(), buffers, flags, ec); + } + + /// Start an asynchronous receive on a connected socket. + /** + * This function is used to asynchronously receive data from the datagram + * socket. The function call always returns immediately. + * + * @param buffers One or more buffers into which the data will be received. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param handler The handler to be called when the receive operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes received. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note The async_receive operation can only be used with a connected socket. + * Use the async_receive_from function to receive data on an unconnected + * datagram socket. + * + * @par Example + * To receive into a single data buffer use the @ref buffer function as + * follows: + * @code + * socket.async_receive(asio::buffer(data, size), handler); + * @endcode + * See the @ref buffer documentation for information on receiving into + * multiple buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_receive(const MutableBufferSequence& buffers, + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_receive(this), handler, + buffers, socket_base::message_flags(0)); + } + + /// Start an asynchronous receive on a connected socket. + /** + * This function is used to asynchronously receive data from the datagram + * socket. The function call always returns immediately. + * + * @param buffers One or more buffers into which the data will be received. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param flags Flags specifying how the receive call is to be made. + * + * @param handler The handler to be called when the receive operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes received. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note The async_receive operation can only be used with a connected socket. + * Use the async_receive_from function to receive data on an unconnected + * datagram socket. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_receive(const MutableBufferSequence& buffers, + socket_base::message_flags flags, + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_receive(this), handler, buffers, flags); + } + + /// Receive a datagram with the endpoint of the sender. + /** + * This function is used to receive a datagram. The function call will block + * until data has been received successfully or an error occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @param sender_endpoint An endpoint object that receives the endpoint of + * the remote sender of the datagram. + * + * @returns The number of bytes received. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * To receive into a single data buffer use the @ref buffer function as + * follows: + * @code + * asio::ip::udp::endpoint sender_endpoint; + * socket.receive_from( + * asio::buffer(data, size), sender_endpoint); + * @endcode + * See the @ref buffer documentation for information on receiving into + * multiple buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t receive_from(const MutableBufferSequence& buffers, + endpoint_type& sender_endpoint) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().receive_from( + this->impl_.get_implementation(), buffers, sender_endpoint, 0, ec); + asio::detail::throw_error(ec, "receive_from"); + return s; + } + + /// Receive a datagram with the endpoint of the sender. + /** + * This function is used to receive a datagram. The function call will block + * until data has been received successfully or an error occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @param sender_endpoint An endpoint object that receives the endpoint of + * the remote sender of the datagram. + * + * @param flags Flags specifying how the receive call is to be made. + * + * @returns The number of bytes received. + * + * @throws asio::system_error Thrown on failure. + */ + template + std::size_t receive_from(const MutableBufferSequence& buffers, + endpoint_type& sender_endpoint, socket_base::message_flags flags) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().receive_from( + this->impl_.get_implementation(), buffers, sender_endpoint, flags, ec); + asio::detail::throw_error(ec, "receive_from"); + return s; + } + + /// Receive a datagram with the endpoint of the sender. + /** + * This function is used to receive a datagram. The function call will block + * until data has been received successfully or an error occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @param sender_endpoint An endpoint object that receives the endpoint of + * the remote sender of the datagram. + * + * @param flags Flags specifying how the receive call is to be made. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns The number of bytes received. + */ + template + std::size_t receive_from(const MutableBufferSequence& buffers, + endpoint_type& sender_endpoint, socket_base::message_flags flags, + asio::error_code& ec) + { + return this->impl_.get_service().receive_from( + this->impl_.get_implementation(), buffers, sender_endpoint, flags, ec); + } + + /// Start an asynchronous receive. + /** + * This function is used to asynchronously receive a datagram. The function + * call always returns immediately. + * + * @param buffers One or more buffers into which the data will be received. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param sender_endpoint An endpoint object that receives the endpoint of + * the remote sender of the datagram. Ownership of the sender_endpoint object + * is retained by the caller, which must guarantee that it is valid until the + * handler is called. + * + * @param handler The handler to be called when the receive operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes received. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * To receive into a single data buffer use the @ref buffer function as + * follows: + * @code socket.async_receive_from( + * asio::buffer(data, size), sender_endpoint, handler); @endcode + * See the @ref buffer documentation for information on receiving into + * multiple buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_receive_from(const MutableBufferSequence& buffers, + endpoint_type& sender_endpoint, + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_receive_from(this), handler, buffers, + &sender_endpoint, socket_base::message_flags(0)); + } + + /// Start an asynchronous receive. + /** + * This function is used to asynchronously receive a datagram. The function + * call always returns immediately. + * + * @param buffers One or more buffers into which the data will be received. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param sender_endpoint An endpoint object that receives the endpoint of + * the remote sender of the datagram. Ownership of the sender_endpoint object + * is retained by the caller, which must guarantee that it is valid until the + * handler is called. + * + * @param flags Flags specifying how the receive call is to be made. + * + * @param handler The handler to be called when the receive operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes received. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_receive_from(const MutableBufferSequence& buffers, + endpoint_type& sender_endpoint, socket_base::message_flags flags, + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_receive_from(this), handler, + buffers, &sender_endpoint, flags); + } + +private: + // Disallow copying and assignment. + basic_datagram_socket(const basic_datagram_socket&) ASIO_DELETED; + basic_datagram_socket& operator=( + const basic_datagram_socket&) ASIO_DELETED; + + class initiate_async_send + { + public: + typedef Executor executor_type; + + explicit initiate_async_send(basic_datagram_socket* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(WriteHandler) handler, + const ConstBufferSequence& buffers, + socket_base::message_flags flags) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a WriteHandler. + ASIO_WRITE_HANDLER_CHECK(WriteHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_send( + self_->impl_.get_implementation(), buffers, flags, + handler2.value, self_->impl_.get_executor()); + } + + private: + basic_datagram_socket* self_; + }; + + class initiate_async_send_to + { + public: + typedef Executor executor_type; + + explicit initiate_async_send_to(basic_datagram_socket* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(WriteHandler) handler, + const ConstBufferSequence& buffers, const endpoint_type& destination, + socket_base::message_flags flags) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a WriteHandler. + ASIO_WRITE_HANDLER_CHECK(WriteHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_send_to( + self_->impl_.get_implementation(), buffers, destination, + flags, handler2.value, self_->impl_.get_executor()); + } + + private: + basic_datagram_socket* self_; + }; + + class initiate_async_receive + { + public: + typedef Executor executor_type; + + explicit initiate_async_receive(basic_datagram_socket* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(ReadHandler) handler, + const MutableBufferSequence& buffers, + socket_base::message_flags flags) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a ReadHandler. + ASIO_READ_HANDLER_CHECK(ReadHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_receive( + self_->impl_.get_implementation(), buffers, flags, + handler2.value, self_->impl_.get_executor()); + } + + private: + basic_datagram_socket* self_; + }; + + class initiate_async_receive_from + { + public: + typedef Executor executor_type; + + explicit initiate_async_receive_from(basic_datagram_socket* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(ReadHandler) handler, + const MutableBufferSequence& buffers, endpoint_type* sender_endpoint, + socket_base::message_flags flags) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a ReadHandler. + ASIO_READ_HANDLER_CHECK(ReadHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_receive_from( + self_->impl_.get_implementation(), buffers, *sender_endpoint, + flags, handler2.value, self_->impl_.get_executor()); + } + + private: + basic_datagram_socket* self_; + }; +}; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_BASIC_DATAGRAM_SOCKET_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_deadline_timer.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_deadline_timer.hpp new file mode 100644 index 000000000..7e95f2b53 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_deadline_timer.hpp @@ -0,0 +1,693 @@ +// +// basic_deadline_timer.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BASIC_DEADLINE_TIMER_HPP +#define ASIO_BASIC_DEADLINE_TIMER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_BOOST_DATE_TIME) \ + || defined(GENERATING_DOCUMENTATION) + +#include +#include "asio/any_io_executor.hpp" +#include "asio/detail/deadline_timer_service.hpp" +#include "asio/detail/handler_type_requirements.hpp" +#include "asio/detail/io_object_impl.hpp" +#include "asio/detail/non_const_lvalue.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" +#include "asio/execution_context.hpp" +#include "asio/time_traits.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +/// Provides waitable timer functionality. +/** + * The basic_deadline_timer class template provides the ability to perform a + * blocking or asynchronous wait for a timer to expire. + * + * A deadline timer is always in one of two states: "expired" or "not expired". + * If the wait() or async_wait() function is called on an expired timer, the + * wait operation will complete immediately. + * + * Most applications will use the asio::deadline_timer typedef. + * + * @par Thread Safety + * @e Distinct @e objects: Safe.@n + * @e Shared @e objects: Unsafe. + * + * @par Examples + * Performing a blocking wait: + * @code + * // Construct a timer without setting an expiry time. + * asio::deadline_timer timer(my_context); + * + * // Set an expiry time relative to now. + * timer.expires_from_now(boost::posix_time::seconds(5)); + * + * // Wait for the timer to expire. + * timer.wait(); + * @endcode + * + * @par + * Performing an asynchronous wait: + * @code + * void handler(const asio::error_code& error) + * { + * if (!error) + * { + * // Timer expired. + * } + * } + * + * ... + * + * // Construct a timer with an absolute expiry time. + * asio::deadline_timer timer(my_context, + * boost::posix_time::time_from_string("2005-12-07 23:59:59.000")); + * + * // Start an asynchronous wait. + * timer.async_wait(handler); + * @endcode + * + * @par Changing an active deadline_timer's expiry time + * + * Changing the expiry time of a timer while there are pending asynchronous + * waits causes those wait operations to be cancelled. To ensure that the action + * associated with the timer is performed only once, use something like this: + * used: + * + * @code + * void on_some_event() + * { + * if (my_timer.expires_from_now(seconds(5)) > 0) + * { + * // We managed to cancel the timer. Start new asynchronous wait. + * my_timer.async_wait(on_timeout); + * } + * else + * { + * // Too late, timer has already expired! + * } + * } + * + * void on_timeout(const asio::error_code& e) + * { + * if (e != asio::error::operation_aborted) + * { + * // Timer was not cancelled, take necessary action. + * } + * } + * @endcode + * + * @li The asio::basic_deadline_timer::expires_from_now() function + * cancels any pending asynchronous waits, and returns the number of + * asynchronous waits that were cancelled. If it returns 0 then you were too + * late and the wait handler has already been executed, or will soon be + * executed. If it returns 1 then the wait handler was successfully cancelled. + * + * @li If a wait handler is cancelled, the asio::error_code passed to + * it contains the value asio::error::operation_aborted. + */ +template , + typename Executor = any_io_executor> +class basic_deadline_timer +{ +public: + /// The type of the executor associated with the object. + typedef Executor executor_type; + + /// Rebinds the timer type to another executor. + template + struct rebind_executor + { + /// The timer type when rebound to the specified executor. + typedef basic_deadline_timer other; + }; + + /// The time traits type. + typedef TimeTraits traits_type; + + /// The time type. + typedef typename traits_type::time_type time_type; + + /// The duration type. + typedef typename traits_type::duration_type duration_type; + + /// Constructor. + /** + * This constructor creates a timer without setting an expiry time. The + * expires_at() or expires_from_now() functions must be called to set an + * expiry time before the timer can be waited on. + * + * @param ex The I/O executor that the timer will use, by default, to + * dispatch handlers for any asynchronous operations performed on the timer. + */ + explicit basic_deadline_timer(const executor_type& ex) + : impl_(ex) + { + } + + /// Constructor. + /** + * This constructor creates a timer without setting an expiry time. The + * expires_at() or expires_from_now() functions must be called to set an + * expiry time before the timer can be waited on. + * + * @param context An execution context which provides the I/O executor that + * the timer will use, by default, to dispatch handlers for any asynchronous + * operations performed on the timer. + */ + template + explicit basic_deadline_timer(ExecutionContext& context, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + } + + /// Constructor to set a particular expiry time as an absolute time. + /** + * This constructor creates a timer and sets the expiry time. + * + * @param ex The I/O executor that the timer will use, by default, to + * dispatch handlers for any asynchronous operations performed on the timer. + * + * @param expiry_time The expiry time to be used for the timer, expressed + * as an absolute time. + */ + basic_deadline_timer(const executor_type& ex, const time_type& expiry_time) + : impl_(ex) + { + asio::error_code ec; + impl_.get_service().expires_at(impl_.get_implementation(), expiry_time, ec); + asio::detail::throw_error(ec, "expires_at"); + } + + /// Constructor to set a particular expiry time as an absolute time. + /** + * This constructor creates a timer and sets the expiry time. + * + * @param context An execution context which provides the I/O executor that + * the timer will use, by default, to dispatch handlers for any asynchronous + * operations performed on the timer. + * + * @param expiry_time The expiry time to be used for the timer, expressed + * as an absolute time. + */ + template + basic_deadline_timer(ExecutionContext& context, const time_type& expiry_time, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + asio::error_code ec; + impl_.get_service().expires_at(impl_.get_implementation(), expiry_time, ec); + asio::detail::throw_error(ec, "expires_at"); + } + + /// Constructor to set a particular expiry time relative to now. + /** + * This constructor creates a timer and sets the expiry time. + * + * @param ex The I/O executor that the timer will use, by default, to + * dispatch handlers for any asynchronous operations performed on the timer. + * + * @param expiry_time The expiry time to be used for the timer, relative to + * now. + */ + basic_deadline_timer(const executor_type& ex, + const duration_type& expiry_time) + : impl_(ex) + { + asio::error_code ec; + impl_.get_service().expires_from_now( + impl_.get_implementation(), expiry_time, ec); + asio::detail::throw_error(ec, "expires_from_now"); + } + + /// Constructor to set a particular expiry time relative to now. + /** + * This constructor creates a timer and sets the expiry time. + * + * @param context An execution context which provides the I/O executor that + * the timer will use, by default, to dispatch handlers for any asynchronous + * operations performed on the timer. + * + * @param expiry_time The expiry time to be used for the timer, relative to + * now. + */ + template + basic_deadline_timer(ExecutionContext& context, + const duration_type& expiry_time, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + asio::error_code ec; + impl_.get_service().expires_from_now( + impl_.get_implementation(), expiry_time, ec); + asio::detail::throw_error(ec, "expires_from_now"); + } + +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + /// Move-construct a basic_deadline_timer from another. + /** + * This constructor moves a timer from one object to another. + * + * @param other The other basic_deadline_timer object from which the move will + * occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_deadline_timer(const executor_type&) + * constructor. + */ + basic_deadline_timer(basic_deadline_timer&& other) + : impl_(std::move(other.impl_)) + { + } + + /// Move-assign a basic_deadline_timer from another. + /** + * This assignment operator moves a timer from one object to another. Cancels + * any outstanding asynchronous operations associated with the target object. + * + * @param other The other basic_deadline_timer object from which the move will + * occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_deadline_timer(const executor_type&) + * constructor. + */ + basic_deadline_timer& operator=(basic_deadline_timer&& other) + { + impl_ = std::move(other.impl_); + return *this; + } +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + /// Destroys the timer. + /** + * This function destroys the timer, cancelling any outstanding asynchronous + * wait operations associated with the timer as if by calling @c cancel. + */ + ~basic_deadline_timer() + { + } + + /// Get the executor associated with the object. + executor_type get_executor() ASIO_NOEXCEPT + { + return impl_.get_executor(); + } + + /// Cancel any asynchronous operations that are waiting on the timer. + /** + * This function forces the completion of any pending asynchronous wait + * operations against the timer. The handler for each cancelled operation will + * be invoked with the asio::error::operation_aborted error code. + * + * Cancelling the timer does not change the expiry time. + * + * @return The number of asynchronous operations that were cancelled. + * + * @throws asio::system_error Thrown on failure. + * + * @note If the timer has already expired when cancel() is called, then the + * handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + std::size_t cancel() + { + asio::error_code ec; + std::size_t s = impl_.get_service().cancel(impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "cancel"); + return s; + } + + /// Cancel any asynchronous operations that are waiting on the timer. + /** + * This function forces the completion of any pending asynchronous wait + * operations against the timer. The handler for each cancelled operation will + * be invoked with the asio::error::operation_aborted error code. + * + * Cancelling the timer does not change the expiry time. + * + * @param ec Set to indicate what error occurred, if any. + * + * @return The number of asynchronous operations that were cancelled. + * + * @note If the timer has already expired when cancel() is called, then the + * handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + std::size_t cancel(asio::error_code& ec) + { + return impl_.get_service().cancel(impl_.get_implementation(), ec); + } + + /// Cancels one asynchronous operation that is waiting on the timer. + /** + * This function forces the completion of one pending asynchronous wait + * operation against the timer. Handlers are cancelled in FIFO order. The + * handler for the cancelled operation will be invoked with the + * asio::error::operation_aborted error code. + * + * Cancelling the timer does not change the expiry time. + * + * @return The number of asynchronous operations that were cancelled. That is, + * either 0 or 1. + * + * @throws asio::system_error Thrown on failure. + * + * @note If the timer has already expired when cancel_one() is called, then + * the handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + std::size_t cancel_one() + { + asio::error_code ec; + std::size_t s = impl_.get_service().cancel_one( + impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "cancel_one"); + return s; + } + + /// Cancels one asynchronous operation that is waiting on the timer. + /** + * This function forces the completion of one pending asynchronous wait + * operation against the timer. Handlers are cancelled in FIFO order. The + * handler for the cancelled operation will be invoked with the + * asio::error::operation_aborted error code. + * + * Cancelling the timer does not change the expiry time. + * + * @param ec Set to indicate what error occurred, if any. + * + * @return The number of asynchronous operations that were cancelled. That is, + * either 0 or 1. + * + * @note If the timer has already expired when cancel_one() is called, then + * the handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + std::size_t cancel_one(asio::error_code& ec) + { + return impl_.get_service().cancel_one(impl_.get_implementation(), ec); + } + + /// Get the timer's expiry time as an absolute time. + /** + * This function may be used to obtain the timer's current expiry time. + * Whether the timer has expired or not does not affect this value. + */ + time_type expires_at() const + { + return impl_.get_service().expires_at(impl_.get_implementation()); + } + + /// Set the timer's expiry time as an absolute time. + /** + * This function sets the expiry time. Any pending asynchronous wait + * operations will be cancelled. The handler for each cancelled operation will + * be invoked with the asio::error::operation_aborted error code. + * + * @param expiry_time The expiry time to be used for the timer. + * + * @return The number of asynchronous operations that were cancelled. + * + * @throws asio::system_error Thrown on failure. + * + * @note If the timer has already expired when expires_at() is called, then + * the handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + std::size_t expires_at(const time_type& expiry_time) + { + asio::error_code ec; + std::size_t s = impl_.get_service().expires_at( + impl_.get_implementation(), expiry_time, ec); + asio::detail::throw_error(ec, "expires_at"); + return s; + } + + /// Set the timer's expiry time as an absolute time. + /** + * This function sets the expiry time. Any pending asynchronous wait + * operations will be cancelled. The handler for each cancelled operation will + * be invoked with the asio::error::operation_aborted error code. + * + * @param expiry_time The expiry time to be used for the timer. + * + * @param ec Set to indicate what error occurred, if any. + * + * @return The number of asynchronous operations that were cancelled. + * + * @note If the timer has already expired when expires_at() is called, then + * the handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + std::size_t expires_at(const time_type& expiry_time, + asio::error_code& ec) + { + return impl_.get_service().expires_at( + impl_.get_implementation(), expiry_time, ec); + } + + /// Get the timer's expiry time relative to now. + /** + * This function may be used to obtain the timer's current expiry time. + * Whether the timer has expired or not does not affect this value. + */ + duration_type expires_from_now() const + { + return impl_.get_service().expires_from_now(impl_.get_implementation()); + } + + /// Set the timer's expiry time relative to now. + /** + * This function sets the expiry time. Any pending asynchronous wait + * operations will be cancelled. The handler for each cancelled operation will + * be invoked with the asio::error::operation_aborted error code. + * + * @param expiry_time The expiry time to be used for the timer. + * + * @return The number of asynchronous operations that were cancelled. + * + * @throws asio::system_error Thrown on failure. + * + * @note If the timer has already expired when expires_from_now() is called, + * then the handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + std::size_t expires_from_now(const duration_type& expiry_time) + { + asio::error_code ec; + std::size_t s = impl_.get_service().expires_from_now( + impl_.get_implementation(), expiry_time, ec); + asio::detail::throw_error(ec, "expires_from_now"); + return s; + } + + /// Set the timer's expiry time relative to now. + /** + * This function sets the expiry time. Any pending asynchronous wait + * operations will be cancelled. The handler for each cancelled operation will + * be invoked with the asio::error::operation_aborted error code. + * + * @param expiry_time The expiry time to be used for the timer. + * + * @param ec Set to indicate what error occurred, if any. + * + * @return The number of asynchronous operations that were cancelled. + * + * @note If the timer has already expired when expires_from_now() is called, + * then the handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + std::size_t expires_from_now(const duration_type& expiry_time, + asio::error_code& ec) + { + return impl_.get_service().expires_from_now( + impl_.get_implementation(), expiry_time, ec); + } + + /// Perform a blocking wait on the timer. + /** + * This function is used to wait for the timer to expire. This function + * blocks and does not return until the timer has expired. + * + * @throws asio::system_error Thrown on failure. + */ + void wait() + { + asio::error_code ec; + impl_.get_service().wait(impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "wait"); + } + + /// Perform a blocking wait on the timer. + /** + * This function is used to wait for the timer to expire. This function + * blocks and does not return until the timer has expired. + * + * @param ec Set to indicate what error occurred, if any. + */ + void wait(asio::error_code& ec) + { + impl_.get_service().wait(impl_.get_implementation(), ec); + } + + /// Start an asynchronous wait on the timer. + /** + * This function may be used to initiate an asynchronous wait against the + * timer. It always returns immediately. + * + * For each call to async_wait(), the supplied handler will be called exactly + * once. The handler will be called when: + * + * @li The timer has expired. + * + * @li The timer was cancelled, in which case the handler is passed the error + * code asio::error::operation_aborted. + * + * @param handler The handler to be called when the timer expires. Copies + * will be made of the handler as required. The function signature of the + * handler must be: + * @code void handler( + * const asio::error_code& error // Result of operation. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + */ + template < + ASIO_COMPLETION_TOKEN_FOR(void (asio::error_code)) + WaitHandler ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(executor_type)> + ASIO_INITFN_AUTO_RESULT_TYPE(WaitHandler, + void (asio::error_code)) + async_wait( + ASIO_MOVE_ARG(WaitHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_wait(this), handler); + } + +private: + // Disallow copying and assignment. + basic_deadline_timer(const basic_deadline_timer&) ASIO_DELETED; + basic_deadline_timer& operator=( + const basic_deadline_timer&) ASIO_DELETED; + + class initiate_async_wait + { + public: + typedef Executor executor_type; + + explicit initiate_async_wait(basic_deadline_timer* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(WaitHandler) handler) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a WaitHandler. + ASIO_WAIT_HANDLER_CHECK(WaitHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_wait( + self_->impl_.get_implementation(), + handler2.value, self_->impl_.get_executor()); + } + + private: + basic_deadline_timer* self_; + }; + + detail::io_object_impl< + detail::deadline_timer_service, Executor> impl_; +}; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_BOOST_DATE_TIME) + // || defined(GENERATING_DOCUMENTATION) + +#endif // ASIO_BASIC_DEADLINE_TIMER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_io_object.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_io_object.hpp new file mode 100644 index 000000000..b6d5f46fe --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_io_object.hpp @@ -0,0 +1,290 @@ +// +// basic_io_object.hpp +// ~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BASIC_IO_OBJECT_HPP +#define ASIO_BASIC_IO_OBJECT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/io_context.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if defined(ASIO_HAS_MOVE) +namespace detail +{ + // Type trait used to determine whether a service supports move. + template + class service_has_move + { + private: + typedef IoObjectService service_type; + typedef typename service_type::implementation_type implementation_type; + + template + static auto asio_service_has_move_eval(T* t, U* u) + -> decltype(t->move_construct(*u, *u), char()); + static char (&asio_service_has_move_eval(...))[2]; + + public: + static const bool value = + sizeof(asio_service_has_move_eval( + static_cast(0), + static_cast(0))) == 1; + }; +} +#endif // defined(ASIO_HAS_MOVE) + +/// Base class for all I/O objects. +/** + * @note All I/O objects are non-copyable. However, when using C++0x, certain + * I/O objects do support move construction and move assignment. + */ +#if !defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) +template +#else +template ::value> +#endif +class basic_io_object +{ +public: + /// The type of the service that will be used to provide I/O operations. + typedef IoObjectService service_type; + + /// The underlying implementation type of I/O object. + typedef typename service_type::implementation_type implementation_type; + +#if !defined(ASIO_NO_DEPRECATED) + /// (Deprecated: Use get_executor().) Get the io_context associated with the + /// object. + /** + * This function may be used to obtain the io_context object that the I/O + * object uses to dispatch handlers for asynchronous operations. + * + * @return A reference to the io_context object that the I/O object will use + * to dispatch handlers. Ownership is not transferred to the caller. + */ + asio::io_context& get_io_context() + { + return service_.get_io_context(); + } + + /// (Deprecated: Use get_executor().) Get the io_context associated with the + /// object. + /** + * This function may be used to obtain the io_context object that the I/O + * object uses to dispatch handlers for asynchronous operations. + * + * @return A reference to the io_context object that the I/O object will use + * to dispatch handlers. Ownership is not transferred to the caller. + */ + asio::io_context& get_io_service() + { + return service_.get_io_context(); + } +#endif // !defined(ASIO_NO_DEPRECATED) + + /// The type of the executor associated with the object. + typedef asio::io_context::executor_type executor_type; + + /// Get the executor associated with the object. + executor_type get_executor() ASIO_NOEXCEPT + { + return service_.get_io_context().get_executor(); + } + +protected: + /// Construct a basic_io_object. + /** + * Performs: + * @code get_service().construct(get_implementation()); @endcode + */ + explicit basic_io_object(asio::io_context& io_context) + : service_(asio::use_service(io_context)) + { + service_.construct(implementation_); + } + +#if defined(GENERATING_DOCUMENTATION) + /// Move-construct a basic_io_object. + /** + * Performs: + * @code get_service().move_construct( + * get_implementation(), other.get_implementation()); @endcode + * + * @note Available only for services that support movability, + */ + basic_io_object(basic_io_object&& other); + + /// Move-assign a basic_io_object. + /** + * Performs: + * @code get_service().move_assign(get_implementation(), + * other.get_service(), other.get_implementation()); @endcode + * + * @note Available only for services that support movability, + */ + basic_io_object& operator=(basic_io_object&& other); + + /// Perform a converting move-construction of a basic_io_object. + template + basic_io_object(IoObjectService1& other_service, + typename IoObjectService1::implementation_type& other_implementation); +#endif // defined(GENERATING_DOCUMENTATION) + + /// Protected destructor to prevent deletion through this type. + /** + * Performs: + * @code get_service().destroy(get_implementation()); @endcode + */ + ~basic_io_object() + { + service_.destroy(implementation_); + } + + /// Get the service associated with the I/O object. + service_type& get_service() + { + return service_; + } + + /// Get the service associated with the I/O object. + const service_type& get_service() const + { + return service_; + } + + /// Get the underlying implementation of the I/O object. + implementation_type& get_implementation() + { + return implementation_; + } + + /// Get the underlying implementation of the I/O object. + const implementation_type& get_implementation() const + { + return implementation_; + } + +private: + basic_io_object(const basic_io_object&); + basic_io_object& operator=(const basic_io_object&); + + // The service associated with the I/O object. + service_type& service_; + + /// The underlying implementation of the I/O object. + implementation_type implementation_; +}; + +#if defined(ASIO_HAS_MOVE) +// Specialisation for movable objects. +template +class basic_io_object +{ +public: + typedef IoObjectService service_type; + typedef typename service_type::implementation_type implementation_type; + +#if !defined(ASIO_NO_DEPRECATED) + asio::io_context& get_io_context() + { + return service_->get_io_context(); + } + + asio::io_context& get_io_service() + { + return service_->get_io_context(); + } +#endif // !defined(ASIO_NO_DEPRECATED) + + typedef asio::io_context::executor_type executor_type; + + executor_type get_executor() ASIO_NOEXCEPT + { + return service_->get_io_context().get_executor(); + } + +protected: + explicit basic_io_object(asio::io_context& io_context) + : service_(&asio::use_service(io_context)) + { + service_->construct(implementation_); + } + + basic_io_object(basic_io_object&& other) + : service_(&other.get_service()) + { + service_->move_construct(implementation_, other.implementation_); + } + + template + basic_io_object(IoObjectService1& other_service, + typename IoObjectService1::implementation_type& other_implementation) + : service_(&asio::use_service( + other_service.get_io_context())) + { + service_->converting_move_construct(implementation_, + other_service, other_implementation); + } + + ~basic_io_object() + { + service_->destroy(implementation_); + } + + basic_io_object& operator=(basic_io_object&& other) + { + service_->move_assign(implementation_, + *other.service_, other.implementation_); + service_ = other.service_; + return *this; + } + + service_type& get_service() + { + return *service_; + } + + const service_type& get_service() const + { + return *service_; + } + + implementation_type& get_implementation() + { + return implementation_; + } + + const implementation_type& get_implementation() const + { + return implementation_; + } + +private: + basic_io_object(const basic_io_object&); + void operator=(const basic_io_object&); + + IoObjectService* service_; + implementation_type implementation_; +}; +#endif // defined(ASIO_HAS_MOVE) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_BASIC_IO_OBJECT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_raw_socket.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_raw_socket.hpp new file mode 100644 index 000000000..523687058 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_raw_socket.hpp @@ -0,0 +1,1206 @@ +// +// basic_raw_socket.hpp +// ~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BASIC_RAW_SOCKET_HPP +#define ASIO_BASIC_RAW_SOCKET_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include "asio/basic_socket.hpp" +#include "asio/detail/handler_type_requirements.hpp" +#include "asio/detail/non_const_lvalue.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if !defined(ASIO_BASIC_RAW_SOCKET_FWD_DECL) +#define ASIO_BASIC_RAW_SOCKET_FWD_DECL + +// Forward declaration with defaulted arguments. +template +class basic_raw_socket; + +#endif // !defined(ASIO_BASIC_RAW_SOCKET_FWD_DECL) + +/// Provides raw-oriented socket functionality. +/** + * The basic_raw_socket class template provides asynchronous and blocking + * raw-oriented socket functionality. + * + * @par Thread Safety + * @e Distinct @e objects: Safe.@n + * @e Shared @e objects: Unsafe. + */ +template +class basic_raw_socket + : public basic_socket +{ +public: + /// The type of the executor associated with the object. + typedef Executor executor_type; + + /// Rebinds the socket type to another executor. + template + struct rebind_executor + { + /// The socket type when rebound to the specified executor. + typedef basic_raw_socket other; + }; + + /// The native representation of a socket. +#if defined(GENERATING_DOCUMENTATION) + typedef implementation_defined native_handle_type; +#else + typedef typename basic_socket::native_handle_type native_handle_type; +#endif + + /// The protocol type. + typedef Protocol protocol_type; + + /// The endpoint type. + typedef typename Protocol::endpoint endpoint_type; + + /// Construct a basic_raw_socket without opening it. + /** + * This constructor creates a raw socket without opening it. The open() + * function must be called before data can be sent or received on the socket. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + */ + explicit basic_raw_socket(const executor_type& ex) + : basic_socket(ex) + { + } + + /// Construct a basic_raw_socket without opening it. + /** + * This constructor creates a raw socket without opening it. The open() + * function must be called before data can be sent or received on the socket. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + */ + template + explicit basic_raw_socket(ExecutionContext& context, + typename enable_if< + is_convertible::value + >::type* = 0) + : basic_socket(context) + { + } + + /// Construct and open a basic_raw_socket. + /** + * This constructor creates and opens a raw socket. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @throws asio::system_error Thrown on failure. + */ + basic_raw_socket(const executor_type& ex, const protocol_type& protocol) + : basic_socket(ex, protocol) + { + } + + /// Construct and open a basic_raw_socket. + /** + * This constructor creates and opens a raw socket. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_raw_socket(ExecutionContext& context, const protocol_type& protocol, + typename enable_if< + is_convertible::value + >::type* = 0) + : basic_socket(context, protocol) + { + } + + /// Construct a basic_raw_socket, opening it and binding it to the given + /// local endpoint. + /** + * This constructor creates a raw socket and automatically opens it bound + * to the specified endpoint on the local machine. The protocol used is the + * protocol associated with the given endpoint. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + * + * @param endpoint An endpoint on the local machine to which the raw + * socket will be bound. + * + * @throws asio::system_error Thrown on failure. + */ + basic_raw_socket(const executor_type& ex, const endpoint_type& endpoint) + : basic_socket(ex, endpoint) + { + } + + /// Construct a basic_raw_socket, opening it and binding it to the given + /// local endpoint. + /** + * This constructor creates a raw socket and automatically opens it bound + * to the specified endpoint on the local machine. The protocol used is the + * protocol associated with the given endpoint. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + * + * @param endpoint An endpoint on the local machine to which the raw + * socket will be bound. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_raw_socket(ExecutionContext& context, const endpoint_type& endpoint, + typename enable_if< + is_convertible::value + >::type* = 0) + : basic_socket(context, endpoint) + { + } + + /// Construct a basic_raw_socket on an existing native socket. + /** + * This constructor creates a raw socket object to hold an existing + * native socket. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @param native_socket The new underlying socket implementation. + * + * @throws asio::system_error Thrown on failure. + */ + basic_raw_socket(const executor_type& ex, + const protocol_type& protocol, const native_handle_type& native_socket) + : basic_socket(ex, protocol, native_socket) + { + } + + /// Construct a basic_raw_socket on an existing native socket. + /** + * This constructor creates a raw socket object to hold an existing + * native socket. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @param native_socket The new underlying socket implementation. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_raw_socket(ExecutionContext& context, + const protocol_type& protocol, const native_handle_type& native_socket, + typename enable_if< + is_convertible::value + >::type* = 0) + : basic_socket(context, protocol, native_socket) + { + } + +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + /// Move-construct a basic_raw_socket from another. + /** + * This constructor moves a raw socket from one object to another. + * + * @param other The other basic_raw_socket object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_raw_socket(const executor_type&) + * constructor. + */ + basic_raw_socket(basic_raw_socket&& other) ASIO_NOEXCEPT + : basic_socket(std::move(other)) + { + } + + /// Move-assign a basic_raw_socket from another. + /** + * This assignment operator moves a raw socket from one object to another. + * + * @param other The other basic_raw_socket object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_raw_socket(const executor_type&) + * constructor. + */ + basic_raw_socket& operator=(basic_raw_socket&& other) + { + basic_socket::operator=(std::move(other)); + return *this; + } + + /// Move-construct a basic_raw_socket from a socket of another protocol + /// type. + /** + * This constructor moves a raw socket from one object to another. + * + * @param other The other basic_raw_socket object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_raw_socket(const executor_type&) + * constructor. + */ + template + basic_raw_socket(basic_raw_socket&& other, + typename enable_if< + is_convertible::value + && is_convertible::value + >::type* = 0) + : basic_socket(std::move(other)) + { + } + + /// Move-assign a basic_raw_socket from a socket of another protocol type. + /** + * This assignment operator moves a raw socket from one object to another. + * + * @param other The other basic_raw_socket object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_raw_socket(const executor_type&) + * constructor. + */ + template + typename enable_if< + is_convertible::value + && is_convertible::value, + basic_raw_socket& + >::type operator=(basic_raw_socket&& other) + { + basic_socket::operator=(std::move(other)); + return *this; + } +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + /// Destroys the socket. + /** + * This function destroys the socket, cancelling any outstanding asynchronous + * operations associated with the socket as if by calling @c cancel. + */ + ~basic_raw_socket() + { + } + + /// Send some data on a connected socket. + /** + * This function is used to send data on the raw socket. The function call + * will block until the data has been sent successfully or an error occurs. + * + * @param buffers One ore more data buffers to be sent on the socket. + * + * @returns The number of bytes sent. + * + * @throws asio::system_error Thrown on failure. + * + * @note The send operation can only be used with a connected socket. Use + * the send_to function to send data on an unconnected raw socket. + * + * @par Example + * To send a single data buffer use the @ref buffer function as follows: + * @code socket.send(asio::buffer(data, size)); @endcode + * See the @ref buffer documentation for information on sending multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t send(const ConstBufferSequence& buffers) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().send( + this->impl_.get_implementation(), buffers, 0, ec); + asio::detail::throw_error(ec, "send"); + return s; + } + + /// Send some data on a connected socket. + /** + * This function is used to send data on the raw socket. The function call + * will block until the data has been sent successfully or an error occurs. + * + * @param buffers One ore more data buffers to be sent on the socket. + * + * @param flags Flags specifying how the send call is to be made. + * + * @returns The number of bytes sent. + * + * @throws asio::system_error Thrown on failure. + * + * @note The send operation can only be used with a connected socket. Use + * the send_to function to send data on an unconnected raw socket. + */ + template + std::size_t send(const ConstBufferSequence& buffers, + socket_base::message_flags flags) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().send( + this->impl_.get_implementation(), buffers, flags, ec); + asio::detail::throw_error(ec, "send"); + return s; + } + + /// Send some data on a connected socket. + /** + * This function is used to send data on the raw socket. The function call + * will block until the data has been sent successfully or an error occurs. + * + * @param buffers One or more data buffers to be sent on the socket. + * + * @param flags Flags specifying how the send call is to be made. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns The number of bytes sent. + * + * @note The send operation can only be used with a connected socket. Use + * the send_to function to send data on an unconnected raw socket. + */ + template + std::size_t send(const ConstBufferSequence& buffers, + socket_base::message_flags flags, asio::error_code& ec) + { + return this->impl_.get_service().send( + this->impl_.get_implementation(), buffers, flags, ec); + } + + /// Start an asynchronous send on a connected socket. + /** + * This function is used to send data on the raw socket. The function call + * will block until the data has been sent successfully or an error occurs. + * + * @param buffers One or more data buffers to be sent on the socket. Although + * the buffers object may be copied as necessary, ownership of the underlying + * memory blocks is retained by the caller, which must guarantee that they + * remain valid until the handler is called. + * + * @param handler The handler to be called when the send operation completes. + * Copies will be made of the handler as required. The function signature of + * the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes sent. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note The async_send operation can only be used with a connected socket. + * Use the async_send_to function to send data on an unconnected raw + * socket. + * + * @par Example + * To send a single data buffer use the @ref buffer function as follows: + * @code + * socket.async_send(asio::buffer(data, size), handler); + * @endcode + * See the @ref buffer documentation for information on sending multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_send(const ConstBufferSequence& buffers, + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_send(this), handler, + buffers, socket_base::message_flags(0)); + } + + /// Start an asynchronous send on a connected socket. + /** + * This function is used to send data on the raw socket. The function call + * will block until the data has been sent successfully or an error occurs. + * + * @param buffers One or more data buffers to be sent on the socket. Although + * the buffers object may be copied as necessary, ownership of the underlying + * memory blocks is retained by the caller, which must guarantee that they + * remain valid until the handler is called. + * + * @param flags Flags specifying how the send call is to be made. + * + * @param handler The handler to be called when the send operation completes. + * Copies will be made of the handler as required. The function signature of + * the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes sent. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note The async_send operation can only be used with a connected socket. + * Use the async_send_to function to send data on an unconnected raw + * socket. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_send(const ConstBufferSequence& buffers, + socket_base::message_flags flags, + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_send(this), handler, buffers, flags); + } + + /// Send raw data to the specified endpoint. + /** + * This function is used to send raw data to the specified remote endpoint. + * The function call will block until the data has been sent successfully or + * an error occurs. + * + * @param buffers One or more data buffers to be sent to the remote endpoint. + * + * @param destination The remote endpoint to which the data will be sent. + * + * @returns The number of bytes sent. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * To send a single data buffer use the @ref buffer function as follows: + * @code + * asio::ip::udp::endpoint destination( + * asio::ip::address::from_string("1.2.3.4"), 12345); + * socket.send_to(asio::buffer(data, size), destination); + * @endcode + * See the @ref buffer documentation for information on sending multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t send_to(const ConstBufferSequence& buffers, + const endpoint_type& destination) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().send_to( + this->impl_.get_implementation(), buffers, destination, 0, ec); + asio::detail::throw_error(ec, "send_to"); + return s; + } + + /// Send raw data to the specified endpoint. + /** + * This function is used to send raw data to the specified remote endpoint. + * The function call will block until the data has been sent successfully or + * an error occurs. + * + * @param buffers One or more data buffers to be sent to the remote endpoint. + * + * @param destination The remote endpoint to which the data will be sent. + * + * @param flags Flags specifying how the send call is to be made. + * + * @returns The number of bytes sent. + * + * @throws asio::system_error Thrown on failure. + */ + template + std::size_t send_to(const ConstBufferSequence& buffers, + const endpoint_type& destination, socket_base::message_flags flags) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().send_to( + this->impl_.get_implementation(), buffers, destination, flags, ec); + asio::detail::throw_error(ec, "send_to"); + return s; + } + + /// Send raw data to the specified endpoint. + /** + * This function is used to send raw data to the specified remote endpoint. + * The function call will block until the data has been sent successfully or + * an error occurs. + * + * @param buffers One or more data buffers to be sent to the remote endpoint. + * + * @param destination The remote endpoint to which the data will be sent. + * + * @param flags Flags specifying how the send call is to be made. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns The number of bytes sent. + */ + template + std::size_t send_to(const ConstBufferSequence& buffers, + const endpoint_type& destination, socket_base::message_flags flags, + asio::error_code& ec) + { + return this->impl_.get_service().send_to(this->impl_.get_implementation(), + buffers, destination, flags, ec); + } + + /// Start an asynchronous send. + /** + * This function is used to asynchronously send raw data to the specified + * remote endpoint. The function call always returns immediately. + * + * @param buffers One or more data buffers to be sent to the remote endpoint. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param destination The remote endpoint to which the data will be sent. + * Copies will be made of the endpoint as required. + * + * @param handler The handler to be called when the send operation completes. + * Copies will be made of the handler as required. The function signature of + * the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes sent. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * To send a single data buffer use the @ref buffer function as follows: + * @code + * asio::ip::udp::endpoint destination( + * asio::ip::address::from_string("1.2.3.4"), 12345); + * socket.async_send_to( + * asio::buffer(data, size), destination, handler); + * @endcode + * See the @ref buffer documentation for information on sending multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_send_to(const ConstBufferSequence& buffers, + const endpoint_type& destination, + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_send_to(this), handler, buffers, + destination, socket_base::message_flags(0)); + } + + /// Start an asynchronous send. + /** + * This function is used to asynchronously send raw data to the specified + * remote endpoint. The function call always returns immediately. + * + * @param buffers One or more data buffers to be sent to the remote endpoint. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param flags Flags specifying how the send call is to be made. + * + * @param destination The remote endpoint to which the data will be sent. + * Copies will be made of the endpoint as required. + * + * @param handler The handler to be called when the send operation completes. + * Copies will be made of the handler as required. The function signature of + * the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes sent. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_send_to(const ConstBufferSequence& buffers, + const endpoint_type& destination, socket_base::message_flags flags, + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_send_to(this), handler, buffers, destination, flags); + } + + /// Receive some data on a connected socket. + /** + * This function is used to receive data on the raw socket. The function + * call will block until data has been received successfully or an error + * occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @returns The number of bytes received. + * + * @throws asio::system_error Thrown on failure. + * + * @note The receive operation can only be used with a connected socket. Use + * the receive_from function to receive data on an unconnected raw + * socket. + * + * @par Example + * To receive into a single data buffer use the @ref buffer function as + * follows: + * @code socket.receive(asio::buffer(data, size)); @endcode + * See the @ref buffer documentation for information on receiving into + * multiple buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t receive(const MutableBufferSequence& buffers) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().receive( + this->impl_.get_implementation(), buffers, 0, ec); + asio::detail::throw_error(ec, "receive"); + return s; + } + + /// Receive some data on a connected socket. + /** + * This function is used to receive data on the raw socket. The function + * call will block until data has been received successfully or an error + * occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @param flags Flags specifying how the receive call is to be made. + * + * @returns The number of bytes received. + * + * @throws asio::system_error Thrown on failure. + * + * @note The receive operation can only be used with a connected socket. Use + * the receive_from function to receive data on an unconnected raw + * socket. + */ + template + std::size_t receive(const MutableBufferSequence& buffers, + socket_base::message_flags flags) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().receive( + this->impl_.get_implementation(), buffers, flags, ec); + asio::detail::throw_error(ec, "receive"); + return s; + } + + /// Receive some data on a connected socket. + /** + * This function is used to receive data on the raw socket. The function + * call will block until data has been received successfully or an error + * occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @param flags Flags specifying how the receive call is to be made. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns The number of bytes received. + * + * @note The receive operation can only be used with a connected socket. Use + * the receive_from function to receive data on an unconnected raw + * socket. + */ + template + std::size_t receive(const MutableBufferSequence& buffers, + socket_base::message_flags flags, asio::error_code& ec) + { + return this->impl_.get_service().receive( + this->impl_.get_implementation(), buffers, flags, ec); + } + + /// Start an asynchronous receive on a connected socket. + /** + * This function is used to asynchronously receive data from the raw + * socket. The function call always returns immediately. + * + * @param buffers One or more buffers into which the data will be received. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param handler The handler to be called when the receive operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes received. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note The async_receive operation can only be used with a connected socket. + * Use the async_receive_from function to receive data on an unconnected + * raw socket. + * + * @par Example + * To receive into a single data buffer use the @ref buffer function as + * follows: + * @code + * socket.async_receive(asio::buffer(data, size), handler); + * @endcode + * See the @ref buffer documentation for information on receiving into + * multiple buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_receive(const MutableBufferSequence& buffers, + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_receive(this), handler, + buffers, socket_base::message_flags(0)); + } + + /// Start an asynchronous receive on a connected socket. + /** + * This function is used to asynchronously receive data from the raw + * socket. The function call always returns immediately. + * + * @param buffers One or more buffers into which the data will be received. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param flags Flags specifying how the receive call is to be made. + * + * @param handler The handler to be called when the receive operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes received. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note The async_receive operation can only be used with a connected socket. + * Use the async_receive_from function to receive data on an unconnected + * raw socket. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_receive(const MutableBufferSequence& buffers, + socket_base::message_flags flags, + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_receive(this), handler, buffers, flags); + } + + /// Receive raw data with the endpoint of the sender. + /** + * This function is used to receive raw data. The function call will block + * until data has been received successfully or an error occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @param sender_endpoint An endpoint object that receives the endpoint of + * the remote sender of the data. + * + * @returns The number of bytes received. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * To receive into a single data buffer use the @ref buffer function as + * follows: + * @code + * asio::ip::udp::endpoint sender_endpoint; + * socket.receive_from( + * asio::buffer(data, size), sender_endpoint); + * @endcode + * See the @ref buffer documentation for information on receiving into + * multiple buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t receive_from(const MutableBufferSequence& buffers, + endpoint_type& sender_endpoint) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().receive_from( + this->impl_.get_implementation(), buffers, sender_endpoint, 0, ec); + asio::detail::throw_error(ec, "receive_from"); + return s; + } + + /// Receive raw data with the endpoint of the sender. + /** + * This function is used to receive raw data. The function call will block + * until data has been received successfully or an error occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @param sender_endpoint An endpoint object that receives the endpoint of + * the remote sender of the data. + * + * @param flags Flags specifying how the receive call is to be made. + * + * @returns The number of bytes received. + * + * @throws asio::system_error Thrown on failure. + */ + template + std::size_t receive_from(const MutableBufferSequence& buffers, + endpoint_type& sender_endpoint, socket_base::message_flags flags) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().receive_from( + this->impl_.get_implementation(), buffers, sender_endpoint, flags, ec); + asio::detail::throw_error(ec, "receive_from"); + return s; + } + + /// Receive raw data with the endpoint of the sender. + /** + * This function is used to receive raw data. The function call will block + * until data has been received successfully or an error occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @param sender_endpoint An endpoint object that receives the endpoint of + * the remote sender of the data. + * + * @param flags Flags specifying how the receive call is to be made. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns The number of bytes received. + */ + template + std::size_t receive_from(const MutableBufferSequence& buffers, + endpoint_type& sender_endpoint, socket_base::message_flags flags, + asio::error_code& ec) + { + return this->impl_.get_service().receive_from( + this->impl_.get_implementation(), buffers, sender_endpoint, flags, ec); + } + + /// Start an asynchronous receive. + /** + * This function is used to asynchronously receive raw data. The function + * call always returns immediately. + * + * @param buffers One or more buffers into which the data will be received. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param sender_endpoint An endpoint object that receives the endpoint of + * the remote sender of the data. Ownership of the sender_endpoint object + * is retained by the caller, which must guarantee that it is valid until the + * handler is called. + * + * @param handler The handler to be called when the receive operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes received. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * To receive into a single data buffer use the @ref buffer function as + * follows: + * @code socket.async_receive_from( + * asio::buffer(data, size), 0, sender_endpoint, handler); @endcode + * See the @ref buffer documentation for information on receiving into + * multiple buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_receive_from(const MutableBufferSequence& buffers, + endpoint_type& sender_endpoint, + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_receive_from(this), handler, buffers, + &sender_endpoint, socket_base::message_flags(0)); + } + + /// Start an asynchronous receive. + /** + * This function is used to asynchronously receive raw data. The function + * call always returns immediately. + * + * @param buffers One or more buffers into which the data will be received. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param sender_endpoint An endpoint object that receives the endpoint of + * the remote sender of the data. Ownership of the sender_endpoint object + * is retained by the caller, which must guarantee that it is valid until the + * handler is called. + * + * @param flags Flags specifying how the receive call is to be made. + * + * @param handler The handler to be called when the receive operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes received. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_receive_from(const MutableBufferSequence& buffers, + endpoint_type& sender_endpoint, socket_base::message_flags flags, + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_receive_from(this), handler, + buffers, &sender_endpoint, flags); + } + +private: + // Disallow copying and assignment. + basic_raw_socket(const basic_raw_socket&) ASIO_DELETED; + basic_raw_socket& operator=(const basic_raw_socket&) ASIO_DELETED; + + class initiate_async_send + { + public: + typedef Executor executor_type; + + explicit initiate_async_send(basic_raw_socket* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(WriteHandler) handler, + const ConstBufferSequence& buffers, + socket_base::message_flags flags) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a WriteHandler. + ASIO_WRITE_HANDLER_CHECK(WriteHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_send( + self_->impl_.get_implementation(), buffers, flags, + handler2.value, self_->impl_.get_executor()); + } + + private: + basic_raw_socket* self_; + }; + + class initiate_async_send_to + { + public: + typedef Executor executor_type; + + explicit initiate_async_send_to(basic_raw_socket* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(WriteHandler) handler, + const ConstBufferSequence& buffers, const endpoint_type& destination, + socket_base::message_flags flags) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a WriteHandler. + ASIO_WRITE_HANDLER_CHECK(WriteHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_send_to( + self_->impl_.get_implementation(), buffers, destination, + flags, handler2.value, self_->impl_.get_executor()); + } + + private: + basic_raw_socket* self_; + }; + + class initiate_async_receive + { + public: + typedef Executor executor_type; + + explicit initiate_async_receive(basic_raw_socket* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(ReadHandler) handler, + const MutableBufferSequence& buffers, + socket_base::message_flags flags) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a ReadHandler. + ASIO_READ_HANDLER_CHECK(ReadHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_receive( + self_->impl_.get_implementation(), buffers, flags, + handler2.value, self_->impl_.get_executor()); + } + + private: + basic_raw_socket* self_; + }; + + class initiate_async_receive_from + { + public: + typedef Executor executor_type; + + explicit initiate_async_receive_from(basic_raw_socket* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(ReadHandler) handler, + const MutableBufferSequence& buffers, endpoint_type* sender_endpoint, + socket_base::message_flags flags) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a ReadHandler. + ASIO_READ_HANDLER_CHECK(ReadHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_receive_from( + self_->impl_.get_implementation(), buffers, *sender_endpoint, + flags, handler2.value, self_->impl_.get_executor()); + } + + private: + basic_raw_socket* self_; + }; +}; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_BASIC_RAW_SOCKET_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_seq_packet_socket.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_seq_packet_socket.hpp new file mode 100644 index 000000000..810694988 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_seq_packet_socket.hpp @@ -0,0 +1,761 @@ +// +// basic_seq_packet_socket.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BASIC_SEQ_PACKET_SOCKET_HPP +#define ASIO_BASIC_SEQ_PACKET_SOCKET_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include "asio/basic_socket.hpp" +#include "asio/detail/handler_type_requirements.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if !defined(ASIO_BASIC_SEQ_PACKET_SOCKET_FWD_DECL) +#define ASIO_BASIC_SEQ_PACKET_SOCKET_FWD_DECL + +// Forward declaration with defaulted arguments. +template +class basic_seq_packet_socket; + +#endif // !defined(ASIO_BASIC_SEQ_PACKET_SOCKET_FWD_DECL) + +/// Provides sequenced packet socket functionality. +/** + * The basic_seq_packet_socket class template provides asynchronous and blocking + * sequenced packet socket functionality. + * + * @par Thread Safety + * @e Distinct @e objects: Safe.@n + * @e Shared @e objects: Unsafe. + */ +template +class basic_seq_packet_socket + : public basic_socket +{ +public: + /// The type of the executor associated with the object. + typedef Executor executor_type; + + /// Rebinds the socket type to another executor. + template + struct rebind_executor + { + /// The socket type when rebound to the specified executor. + typedef basic_seq_packet_socket other; + }; + + /// The native representation of a socket. +#if defined(GENERATING_DOCUMENTATION) + typedef implementation_defined native_handle_type; +#else + typedef typename basic_socket::native_handle_type native_handle_type; +#endif + + /// The protocol type. + typedef Protocol protocol_type; + + /// The endpoint type. + typedef typename Protocol::endpoint endpoint_type; + + /// Construct a basic_seq_packet_socket without opening it. + /** + * This constructor creates a sequenced packet socket without opening it. The + * socket needs to be opened and then connected or accepted before data can + * be sent or received on it. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + */ + explicit basic_seq_packet_socket(const executor_type& ex) + : basic_socket(ex) + { + } + + /// Construct a basic_seq_packet_socket without opening it. + /** + * This constructor creates a sequenced packet socket without opening it. The + * socket needs to be opened and then connected or accepted before data can + * be sent or received on it. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + */ + template + explicit basic_seq_packet_socket(ExecutionContext& context, + typename enable_if< + is_convertible::value + >::type* = 0) + : basic_socket(context) + { + } + + /// Construct and open a basic_seq_packet_socket. + /** + * This constructor creates and opens a sequenced_packet socket. The socket + * needs to be connected or accepted before data can be sent or received on + * it. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @throws asio::system_error Thrown on failure. + */ + basic_seq_packet_socket(const executor_type& ex, + const protocol_type& protocol) + : basic_socket(ex, protocol) + { + } + + /// Construct and open a basic_seq_packet_socket. + /** + * This constructor creates and opens a sequenced_packet socket. The socket + * needs to be connected or accepted before data can be sent or received on + * it. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_seq_packet_socket(ExecutionContext& context, + const protocol_type& protocol, + typename enable_if< + is_convertible::value + >::type* = 0) + : basic_socket(context, protocol) + { + } + + /// Construct a basic_seq_packet_socket, opening it and binding it to the + /// given local endpoint. + /** + * This constructor creates a sequenced packet socket and automatically opens + * it bound to the specified endpoint on the local machine. The protocol used + * is the protocol associated with the given endpoint. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + * + * @param endpoint An endpoint on the local machine to which the sequenced + * packet socket will be bound. + * + * @throws asio::system_error Thrown on failure. + */ + basic_seq_packet_socket(const executor_type& ex, + const endpoint_type& endpoint) + : basic_socket(ex, endpoint) + { + } + + /// Construct a basic_seq_packet_socket, opening it and binding it to the + /// given local endpoint. + /** + * This constructor creates a sequenced packet socket and automatically opens + * it bound to the specified endpoint on the local machine. The protocol used + * is the protocol associated with the given endpoint. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + * + * @param endpoint An endpoint on the local machine to which the sequenced + * packet socket will be bound. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_seq_packet_socket(ExecutionContext& context, + const endpoint_type& endpoint, + typename enable_if< + is_convertible::value + >::type* = 0) + : basic_socket(context, endpoint) + { + } + + /// Construct a basic_seq_packet_socket on an existing native socket. + /** + * This constructor creates a sequenced packet socket object to hold an + * existing native socket. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @param native_socket The new underlying socket implementation. + * + * @throws asio::system_error Thrown on failure. + */ + basic_seq_packet_socket(const executor_type& ex, + const protocol_type& protocol, const native_handle_type& native_socket) + : basic_socket(ex, protocol, native_socket) + { + } + + /// Construct a basic_seq_packet_socket on an existing native socket. + /** + * This constructor creates a sequenced packet socket object to hold an + * existing native socket. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @param native_socket The new underlying socket implementation. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_seq_packet_socket(ExecutionContext& context, + const protocol_type& protocol, const native_handle_type& native_socket, + typename enable_if< + is_convertible::value + >::type* = 0) + : basic_socket(context, protocol, native_socket) + { + } + +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + /// Move-construct a basic_seq_packet_socket from another. + /** + * This constructor moves a sequenced packet socket from one object to + * another. + * + * @param other The other basic_seq_packet_socket object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_seq_packet_socket(const executor_type&) + * constructor. + */ + basic_seq_packet_socket(basic_seq_packet_socket&& other) ASIO_NOEXCEPT + : basic_socket(std::move(other)) + { + } + + /// Move-assign a basic_seq_packet_socket from another. + /** + * This assignment operator moves a sequenced packet socket from one object to + * another. + * + * @param other The other basic_seq_packet_socket object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_seq_packet_socket(const executor_type&) + * constructor. + */ + basic_seq_packet_socket& operator=(basic_seq_packet_socket&& other) + { + basic_socket::operator=(std::move(other)); + return *this; + } + + /// Move-construct a basic_seq_packet_socket from a socket of another protocol + /// type. + /** + * This constructor moves a sequenced packet socket from one object to + * another. + * + * @param other The other basic_seq_packet_socket object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_seq_packet_socket(const executor_type&) + * constructor. + */ + template + basic_seq_packet_socket(basic_seq_packet_socket&& other, + typename enable_if< + is_convertible::value + && is_convertible::value + >::type* = 0) + : basic_socket(std::move(other)) + { + } + + /// Move-assign a basic_seq_packet_socket from a socket of another protocol + /// type. + /** + * This assignment operator moves a sequenced packet socket from one object to + * another. + * + * @param other The other basic_seq_packet_socket object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_seq_packet_socket(const executor_type&) + * constructor. + */ + template + typename enable_if< + is_convertible::value + && is_convertible::value, + basic_seq_packet_socket& + >::type operator=(basic_seq_packet_socket&& other) + { + basic_socket::operator=(std::move(other)); + return *this; + } +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + /// Destroys the socket. + /** + * This function destroys the socket, cancelling any outstanding asynchronous + * operations associated with the socket as if by calling @c cancel. + */ + ~basic_seq_packet_socket() + { + } + + /// Send some data on the socket. + /** + * This function is used to send data on the sequenced packet socket. The + * function call will block until the data has been sent successfully, or an + * until error occurs. + * + * @param buffers One or more data buffers to be sent on the socket. + * + * @param flags Flags specifying how the send call is to be made. + * + * @returns The number of bytes sent. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * To send a single data buffer use the @ref buffer function as follows: + * @code + * socket.send(asio::buffer(data, size), 0); + * @endcode + * See the @ref buffer documentation for information on sending multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t send(const ConstBufferSequence& buffers, + socket_base::message_flags flags) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().send( + this->impl_.get_implementation(), buffers, flags, ec); + asio::detail::throw_error(ec, "send"); + return s; + } + + /// Send some data on the socket. + /** + * This function is used to send data on the sequenced packet socket. The + * function call will block the data has been sent successfully, or an until + * error occurs. + * + * @param buffers One or more data buffers to be sent on the socket. + * + * @param flags Flags specifying how the send call is to be made. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns The number of bytes sent. Returns 0 if an error occurred. + * + * @note The send operation may not transmit all of the data to the peer. + * Consider using the @ref write function if you need to ensure that all data + * is written before the blocking operation completes. + */ + template + std::size_t send(const ConstBufferSequence& buffers, + socket_base::message_flags flags, asio::error_code& ec) + { + return this->impl_.get_service().send( + this->impl_.get_implementation(), buffers, flags, ec); + } + + /// Start an asynchronous send. + /** + * This function is used to asynchronously send data on the sequenced packet + * socket. The function call always returns immediately. + * + * @param buffers One or more data buffers to be sent on the socket. Although + * the buffers object may be copied as necessary, ownership of the underlying + * memory blocks is retained by the caller, which must guarantee that they + * remain valid until the handler is called. + * + * @param flags Flags specifying how the send call is to be made. + * + * @param handler The handler to be called when the send operation completes. + * Copies will be made of the handler as required. The function signature of + * the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes sent. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * To send a single data buffer use the @ref buffer function as follows: + * @code + * socket.async_send(asio::buffer(data, size), 0, handler); + * @endcode + * See the @ref buffer documentation for information on sending multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_send(const ConstBufferSequence& buffers, + socket_base::message_flags flags, + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_send(this), handler, buffers, flags); + } + + /// Receive some data on the socket. + /** + * This function is used to receive data on the sequenced packet socket. The + * function call will block until data has been received successfully, or + * until an error occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @param out_flags After the receive call completes, contains flags + * associated with the received data. For example, if the + * socket_base::message_end_of_record bit is set then the received data marks + * the end of a record. + * + * @returns The number of bytes received. + * + * @throws asio::system_error Thrown on failure. An error code of + * asio::error::eof indicates that the connection was closed by the + * peer. + * + * @par Example + * To receive into a single data buffer use the @ref buffer function as + * follows: + * @code + * socket.receive(asio::buffer(data, size), out_flags); + * @endcode + * See the @ref buffer documentation for information on receiving into + * multiple buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t receive(const MutableBufferSequence& buffers, + socket_base::message_flags& out_flags) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().receive_with_flags( + this->impl_.get_implementation(), buffers, 0, out_flags, ec); + asio::detail::throw_error(ec, "receive"); + return s; + } + + /// Receive some data on the socket. + /** + * This function is used to receive data on the sequenced packet socket. The + * function call will block until data has been received successfully, or + * until an error occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @param in_flags Flags specifying how the receive call is to be made. + * + * @param out_flags After the receive call completes, contains flags + * associated with the received data. For example, if the + * socket_base::message_end_of_record bit is set then the received data marks + * the end of a record. + * + * @returns The number of bytes received. + * + * @throws asio::system_error Thrown on failure. An error code of + * asio::error::eof indicates that the connection was closed by the + * peer. + * + * @note The receive operation may not receive all of the requested number of + * bytes. Consider using the @ref read function if you need to ensure that the + * requested amount of data is read before the blocking operation completes. + * + * @par Example + * To receive into a single data buffer use the @ref buffer function as + * follows: + * @code + * socket.receive(asio::buffer(data, size), 0, out_flags); + * @endcode + * See the @ref buffer documentation for information on receiving into + * multiple buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t receive(const MutableBufferSequence& buffers, + socket_base::message_flags in_flags, + socket_base::message_flags& out_flags) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().receive_with_flags( + this->impl_.get_implementation(), buffers, in_flags, out_flags, ec); + asio::detail::throw_error(ec, "receive"); + return s; + } + + /// Receive some data on a connected socket. + /** + * This function is used to receive data on the sequenced packet socket. The + * function call will block until data has been received successfully, or + * until an error occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @param in_flags Flags specifying how the receive call is to be made. + * + * @param out_flags After the receive call completes, contains flags + * associated with the received data. For example, if the + * socket_base::message_end_of_record bit is set then the received data marks + * the end of a record. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns The number of bytes received. Returns 0 if an error occurred. + * + * @note The receive operation may not receive all of the requested number of + * bytes. Consider using the @ref read function if you need to ensure that the + * requested amount of data is read before the blocking operation completes. + */ + template + std::size_t receive(const MutableBufferSequence& buffers, + socket_base::message_flags in_flags, + socket_base::message_flags& out_flags, asio::error_code& ec) + { + return this->impl_.get_service().receive_with_flags( + this->impl_.get_implementation(), buffers, in_flags, out_flags, ec); + } + + /// Start an asynchronous receive. + /** + * This function is used to asynchronously receive data from the sequenced + * packet socket. The function call always returns immediately. + * + * @param buffers One or more buffers into which the data will be received. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param out_flags Once the asynchronous operation completes, contains flags + * associated with the received data. For example, if the + * socket_base::message_end_of_record bit is set then the received data marks + * the end of a record. The caller must guarantee that the referenced + * variable remains valid until the handler is called. + * + * @param handler The handler to be called when the receive operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes received. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * To receive into a single data buffer use the @ref buffer function as + * follows: + * @code + * socket.async_receive(asio::buffer(data, size), out_flags, handler); + * @endcode + * See the @ref buffer documentation for information on receiving into + * multiple buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_receive(const MutableBufferSequence& buffers, + socket_base::message_flags& out_flags, + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_receive_with_flags(this), handler, + buffers, socket_base::message_flags(0), &out_flags); + } + + /// Start an asynchronous receive. + /** + * This function is used to asynchronously receive data from the sequenced + * data socket. The function call always returns immediately. + * + * @param buffers One or more buffers into which the data will be received. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param in_flags Flags specifying how the receive call is to be made. + * + * @param out_flags Once the asynchronous operation completes, contains flags + * associated with the received data. For example, if the + * socket_base::message_end_of_record bit is set then the received data marks + * the end of a record. The caller must guarantee that the referenced + * variable remains valid until the handler is called. + * + * @param handler The handler to be called when the receive operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes received. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * To receive into a single data buffer use the @ref buffer function as + * follows: + * @code + * socket.async_receive( + * asio::buffer(data, size), + * 0, out_flags, handler); + * @endcode + * See the @ref buffer documentation for information on receiving into + * multiple buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_receive(const MutableBufferSequence& buffers, + socket_base::message_flags in_flags, + socket_base::message_flags& out_flags, + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_receive_with_flags(this), + handler, buffers, in_flags, &out_flags); + } + +private: + // Disallow copying and assignment. + basic_seq_packet_socket(const basic_seq_packet_socket&) ASIO_DELETED; + basic_seq_packet_socket& operator=( + const basic_seq_packet_socket&) ASIO_DELETED; + + class initiate_async_send + { + public: + typedef Executor executor_type; + + explicit initiate_async_send(basic_seq_packet_socket* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(WriteHandler) handler, + const ConstBufferSequence& buffers, + socket_base::message_flags flags) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a WriteHandler. + ASIO_WRITE_HANDLER_CHECK(WriteHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_send( + self_->impl_.get_implementation(), buffers, flags, + handler2.value, self_->impl_.get_executor()); + } + + private: + basic_seq_packet_socket* self_; + }; + + class initiate_async_receive_with_flags + { + public: + typedef Executor executor_type; + + explicit initiate_async_receive_with_flags(basic_seq_packet_socket* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(ReadHandler) handler, + const MutableBufferSequence& buffers, + socket_base::message_flags in_flags, + socket_base::message_flags* out_flags) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a ReadHandler. + ASIO_READ_HANDLER_CHECK(ReadHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_receive_with_flags( + self_->impl_.get_implementation(), buffers, in_flags, + *out_flags, handler2.value, self_->impl_.get_executor()); + } + + private: + basic_seq_packet_socket* self_; + }; +}; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_BASIC_SEQ_PACKET_SOCKET_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_serial_port.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_serial_port.hpp new file mode 100644 index 000000000..1d09c72f0 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_serial_port.hpp @@ -0,0 +1,907 @@ +// +// basic_serial_port.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// Copyright (c) 2008 Rep Invariant Systems, Inc. (info@repinvariant.com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BASIC_SERIAL_PORT_HPP +#define ASIO_BASIC_SERIAL_PORT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_SERIAL_PORT) \ + || defined(GENERATING_DOCUMENTATION) + +#include +#include "asio/any_io_executor.hpp" +#include "asio/async_result.hpp" +#include "asio/detail/handler_type_requirements.hpp" +#include "asio/detail/io_object_impl.hpp" +#include "asio/detail/non_const_lvalue.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/error.hpp" +#include "asio/execution_context.hpp" +#include "asio/serial_port_base.hpp" +#if defined(ASIO_HAS_IOCP) +# include "asio/detail/win_iocp_serial_port_service.hpp" +#else +# include "asio/detail/reactive_serial_port_service.hpp" +#endif + +#if defined(ASIO_HAS_MOVE) +# include +#endif // defined(ASIO_HAS_MOVE) + +#include "asio/detail/push_options.hpp" + +namespace asio { + +/// Provides serial port functionality. +/** + * The basic_serial_port class provides a wrapper over serial port + * functionality. + * + * @par Thread Safety + * @e Distinct @e objects: Safe.@n + * @e Shared @e objects: Unsafe. + */ +template +class basic_serial_port + : public serial_port_base +{ +public: + /// The type of the executor associated with the object. + typedef Executor executor_type; + + /// Rebinds the serial port type to another executor. + template + struct rebind_executor + { + /// The serial port type when rebound to the specified executor. + typedef basic_serial_port other; + }; + + /// The native representation of a serial port. +#if defined(GENERATING_DOCUMENTATION) + typedef implementation_defined native_handle_type; +#elif defined(ASIO_HAS_IOCP) + typedef detail::win_iocp_serial_port_service::native_handle_type + native_handle_type; +#else + typedef detail::reactive_serial_port_service::native_handle_type + native_handle_type; +#endif + + /// A basic_basic_serial_port is always the lowest layer. + typedef basic_serial_port lowest_layer_type; + + /// Construct a basic_serial_port without opening it. + /** + * This constructor creates a serial port without opening it. + * + * @param ex The I/O executor that the serial port will use, by default, to + * dispatch handlers for any asynchronous operations performed on the + * serial port. + */ + explicit basic_serial_port(const executor_type& ex) + : impl_(ex) + { + } + + /// Construct a basic_serial_port without opening it. + /** + * This constructor creates a serial port without opening it. + * + * @param context An execution context which provides the I/O executor that + * the serial port will use, by default, to dispatch handlers for any + * asynchronous operations performed on the serial port. + */ + template + explicit basic_serial_port(ExecutionContext& context, + typename enable_if< + is_convertible::value, + basic_serial_port + >::type* = 0) + : impl_(context) + { + } + + /// Construct and open a basic_serial_port. + /** + * This constructor creates and opens a serial port for the specified device + * name. + * + * @param ex The I/O executor that the serial port will use, by default, to + * dispatch handlers for any asynchronous operations performed on the + * serial port. + * + * @param device The platform-specific device name for this serial + * port. + */ + basic_serial_port(const executor_type& ex, const char* device) + : impl_(ex) + { + asio::error_code ec; + impl_.get_service().open(impl_.get_implementation(), device, ec); + asio::detail::throw_error(ec, "open"); + } + + /// Construct and open a basic_serial_port. + /** + * This constructor creates and opens a serial port for the specified device + * name. + * + * @param context An execution context which provides the I/O executor that + * the serial port will use, by default, to dispatch handlers for any + * asynchronous operations performed on the serial port. + * + * @param device The platform-specific device name for this serial + * port. + */ + template + basic_serial_port(ExecutionContext& context, const char* device, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + asio::error_code ec; + impl_.get_service().open(impl_.get_implementation(), device, ec); + asio::detail::throw_error(ec, "open"); + } + + /// Construct and open a basic_serial_port. + /** + * This constructor creates and opens a serial port for the specified device + * name. + * + * @param ex The I/O executor that the serial port will use, by default, to + * dispatch handlers for any asynchronous operations performed on the + * serial port. + * + * @param device The platform-specific device name for this serial + * port. + */ + basic_serial_port(const executor_type& ex, const std::string& device) + : impl_(ex) + { + asio::error_code ec; + impl_.get_service().open(impl_.get_implementation(), device, ec); + asio::detail::throw_error(ec, "open"); + } + + /// Construct and open a basic_serial_port. + /** + * This constructor creates and opens a serial port for the specified device + * name. + * + * @param context An execution context which provides the I/O executor that + * the serial port will use, by default, to dispatch handlers for any + * asynchronous operations performed on the serial port. + * + * @param device The platform-specific device name for this serial + * port. + */ + template + basic_serial_port(ExecutionContext& context, const std::string& device, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + asio::error_code ec; + impl_.get_service().open(impl_.get_implementation(), device, ec); + asio::detail::throw_error(ec, "open"); + } + + /// Construct a basic_serial_port on an existing native serial port. + /** + * This constructor creates a serial port object to hold an existing native + * serial port. + * + * @param ex The I/O executor that the serial port will use, by default, to + * dispatch handlers for any asynchronous operations performed on the + * serial port. + * + * @param native_serial_port A native serial port. + * + * @throws asio::system_error Thrown on failure. + */ + basic_serial_port(const executor_type& ex, + const native_handle_type& native_serial_port) + : impl_(ex) + { + asio::error_code ec; + impl_.get_service().assign(impl_.get_implementation(), + native_serial_port, ec); + asio::detail::throw_error(ec, "assign"); + } + + /// Construct a basic_serial_port on an existing native serial port. + /** + * This constructor creates a serial port object to hold an existing native + * serial port. + * + * @param context An execution context which provides the I/O executor that + * the serial port will use, by default, to dispatch handlers for any + * asynchronous operations performed on the serial port. + * + * @param native_serial_port A native serial port. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_serial_port(ExecutionContext& context, + const native_handle_type& native_serial_port, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + asio::error_code ec; + impl_.get_service().assign(impl_.get_implementation(), + native_serial_port, ec); + asio::detail::throw_error(ec, "assign"); + } + +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + /// Move-construct a basic_serial_port from another. + /** + * This constructor moves a serial port from one object to another. + * + * @param other The other basic_serial_port object from which the move will + * occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_serial_port(const executor_type&) + * constructor. + */ + basic_serial_port(basic_serial_port&& other) + : impl_(std::move(other.impl_)) + { + } + + /// Move-assign a basic_serial_port from another. + /** + * This assignment operator moves a serial port from one object to another. + * + * @param other The other basic_serial_port object from which the move will + * occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_serial_port(const executor_type&) + * constructor. + */ + basic_serial_port& operator=(basic_serial_port&& other) + { + impl_ = std::move(other.impl_); + return *this; + } +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + /// Destroys the serial port. + /** + * This function destroys the serial port, cancelling any outstanding + * asynchronous wait operations associated with the serial port as if by + * calling @c cancel. + */ + ~basic_serial_port() + { + } + + /// Get the executor associated with the object. + executor_type get_executor() ASIO_NOEXCEPT + { + return impl_.get_executor(); + } + + /// Get a reference to the lowest layer. + /** + * This function returns a reference to the lowest layer in a stack of + * layers. Since a basic_serial_port cannot contain any further layers, it + * simply returns a reference to itself. + * + * @return A reference to the lowest layer in the stack of layers. Ownership + * is not transferred to the caller. + */ + lowest_layer_type& lowest_layer() + { + return *this; + } + + /// Get a const reference to the lowest layer. + /** + * This function returns a const reference to the lowest layer in a stack of + * layers. Since a basic_serial_port cannot contain any further layers, it + * simply returns a reference to itself. + * + * @return A const reference to the lowest layer in the stack of layers. + * Ownership is not transferred to the caller. + */ + const lowest_layer_type& lowest_layer() const + { + return *this; + } + + /// Open the serial port using the specified device name. + /** + * This function opens the serial port for the specified device name. + * + * @param device The platform-specific device name. + * + * @throws asio::system_error Thrown on failure. + */ + void open(const std::string& device) + { + asio::error_code ec; + impl_.get_service().open(impl_.get_implementation(), device, ec); + asio::detail::throw_error(ec, "open"); + } + + /// Open the serial port using the specified device name. + /** + * This function opens the serial port using the given platform-specific + * device name. + * + * @param device The platform-specific device name. + * + * @param ec Set the indicate what error occurred, if any. + */ + ASIO_SYNC_OP_VOID open(const std::string& device, + asio::error_code& ec) + { + impl_.get_service().open(impl_.get_implementation(), device, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Assign an existing native serial port to the serial port. + /* + * This function opens the serial port to hold an existing native serial port. + * + * @param native_serial_port A native serial port. + * + * @throws asio::system_error Thrown on failure. + */ + void assign(const native_handle_type& native_serial_port) + { + asio::error_code ec; + impl_.get_service().assign(impl_.get_implementation(), + native_serial_port, ec); + asio::detail::throw_error(ec, "assign"); + } + + /// Assign an existing native serial port to the serial port. + /* + * This function opens the serial port to hold an existing native serial port. + * + * @param native_serial_port A native serial port. + * + * @param ec Set to indicate what error occurred, if any. + */ + ASIO_SYNC_OP_VOID assign(const native_handle_type& native_serial_port, + asio::error_code& ec) + { + impl_.get_service().assign(impl_.get_implementation(), + native_serial_port, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Determine whether the serial port is open. + bool is_open() const + { + return impl_.get_service().is_open(impl_.get_implementation()); + } + + /// Close the serial port. + /** + * This function is used to close the serial port. Any asynchronous read or + * write operations will be cancelled immediately, and will complete with the + * asio::error::operation_aborted error. + * + * @throws asio::system_error Thrown on failure. + */ + void close() + { + asio::error_code ec; + impl_.get_service().close(impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "close"); + } + + /// Close the serial port. + /** + * This function is used to close the serial port. Any asynchronous read or + * write operations will be cancelled immediately, and will complete with the + * asio::error::operation_aborted error. + * + * @param ec Set to indicate what error occurred, if any. + */ + ASIO_SYNC_OP_VOID close(asio::error_code& ec) + { + impl_.get_service().close(impl_.get_implementation(), ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Get the native serial port representation. + /** + * This function may be used to obtain the underlying representation of the + * serial port. This is intended to allow access to native serial port + * functionality that is not otherwise provided. + */ + native_handle_type native_handle() + { + return impl_.get_service().native_handle(impl_.get_implementation()); + } + + /// Cancel all asynchronous operations associated with the serial port. + /** + * This function causes all outstanding asynchronous read or write operations + * to finish immediately, and the handlers for cancelled operations will be + * passed the asio::error::operation_aborted error. + * + * @throws asio::system_error Thrown on failure. + */ + void cancel() + { + asio::error_code ec; + impl_.get_service().cancel(impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "cancel"); + } + + /// Cancel all asynchronous operations associated with the serial port. + /** + * This function causes all outstanding asynchronous read or write operations + * to finish immediately, and the handlers for cancelled operations will be + * passed the asio::error::operation_aborted error. + * + * @param ec Set to indicate what error occurred, if any. + */ + ASIO_SYNC_OP_VOID cancel(asio::error_code& ec) + { + impl_.get_service().cancel(impl_.get_implementation(), ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Send a break sequence to the serial port. + /** + * This function causes a break sequence of platform-specific duration to be + * sent out the serial port. + * + * @throws asio::system_error Thrown on failure. + */ + void send_break() + { + asio::error_code ec; + impl_.get_service().send_break(impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "send_break"); + } + + /// Send a break sequence to the serial port. + /** + * This function causes a break sequence of platform-specific duration to be + * sent out the serial port. + * + * @param ec Set to indicate what error occurred, if any. + */ + ASIO_SYNC_OP_VOID send_break(asio::error_code& ec) + { + impl_.get_service().send_break(impl_.get_implementation(), ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Set an option on the serial port. + /** + * This function is used to set an option on the serial port. + * + * @param option The option value to be set on the serial port. + * + * @throws asio::system_error Thrown on failure. + * + * @sa SettableSerialPortOption @n + * asio::serial_port_base::baud_rate @n + * asio::serial_port_base::flow_control @n + * asio::serial_port_base::parity @n + * asio::serial_port_base::stop_bits @n + * asio::serial_port_base::character_size + */ + template + void set_option(const SettableSerialPortOption& option) + { + asio::error_code ec; + impl_.get_service().set_option(impl_.get_implementation(), option, ec); + asio::detail::throw_error(ec, "set_option"); + } + + /// Set an option on the serial port. + /** + * This function is used to set an option on the serial port. + * + * @param option The option value to be set on the serial port. + * + * @param ec Set to indicate what error occurred, if any. + * + * @sa SettableSerialPortOption @n + * asio::serial_port_base::baud_rate @n + * asio::serial_port_base::flow_control @n + * asio::serial_port_base::parity @n + * asio::serial_port_base::stop_bits @n + * asio::serial_port_base::character_size + */ + template + ASIO_SYNC_OP_VOID set_option(const SettableSerialPortOption& option, + asio::error_code& ec) + { + impl_.get_service().set_option(impl_.get_implementation(), option, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Get an option from the serial port. + /** + * This function is used to get the current value of an option on the serial + * port. + * + * @param option The option value to be obtained from the serial port. + * + * @throws asio::system_error Thrown on failure. + * + * @sa GettableSerialPortOption @n + * asio::serial_port_base::baud_rate @n + * asio::serial_port_base::flow_control @n + * asio::serial_port_base::parity @n + * asio::serial_port_base::stop_bits @n + * asio::serial_port_base::character_size + */ + template + void get_option(GettableSerialPortOption& option) const + { + asio::error_code ec; + impl_.get_service().get_option(impl_.get_implementation(), option, ec); + asio::detail::throw_error(ec, "get_option"); + } + + /// Get an option from the serial port. + /** + * This function is used to get the current value of an option on the serial + * port. + * + * @param option The option value to be obtained from the serial port. + * + * @param ec Set to indicate what error occurred, if any. + * + * @sa GettableSerialPortOption @n + * asio::serial_port_base::baud_rate @n + * asio::serial_port_base::flow_control @n + * asio::serial_port_base::parity @n + * asio::serial_port_base::stop_bits @n + * asio::serial_port_base::character_size + */ + template + ASIO_SYNC_OP_VOID get_option(GettableSerialPortOption& option, + asio::error_code& ec) const + { + impl_.get_service().get_option(impl_.get_implementation(), option, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Write some data to the serial port. + /** + * This function is used to write data to the serial port. The function call + * will block until one or more bytes of the data has been written + * successfully, or until an error occurs. + * + * @param buffers One or more data buffers to be written to the serial port. + * + * @returns The number of bytes written. + * + * @throws asio::system_error Thrown on failure. An error code of + * asio::error::eof indicates that the connection was closed by the + * peer. + * + * @note The write_some operation may not transmit all of the data to the + * peer. Consider using the @ref write function if you need to ensure that + * all data is written before the blocking operation completes. + * + * @par Example + * To write a single data buffer use the @ref buffer function as follows: + * @code + * basic_serial_port.write_some(asio::buffer(data, size)); + * @endcode + * See the @ref buffer documentation for information on writing multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t write_some(const ConstBufferSequence& buffers) + { + asio::error_code ec; + std::size_t s = impl_.get_service().write_some( + impl_.get_implementation(), buffers, ec); + asio::detail::throw_error(ec, "write_some"); + return s; + } + + /// Write some data to the serial port. + /** + * This function is used to write data to the serial port. The function call + * will block until one or more bytes of the data has been written + * successfully, or until an error occurs. + * + * @param buffers One or more data buffers to be written to the serial port. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns The number of bytes written. Returns 0 if an error occurred. + * + * @note The write_some operation may not transmit all of the data to the + * peer. Consider using the @ref write function if you need to ensure that + * all data is written before the blocking operation completes. + */ + template + std::size_t write_some(const ConstBufferSequence& buffers, + asio::error_code& ec) + { + return impl_.get_service().write_some( + impl_.get_implementation(), buffers, ec); + } + + /// Start an asynchronous write. + /** + * This function is used to asynchronously write data to the serial port. + * The function call always returns immediately. + * + * @param buffers One or more data buffers to be written to the serial port. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param handler The handler to be called when the write operation completes. + * Copies will be made of the handler as required. The function signature of + * the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes written. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note The write operation may not transmit all of the data to the peer. + * Consider using the @ref async_write function if you need to ensure that all + * data is written before the asynchronous operation completes. + * + * @par Example + * To write a single data buffer use the @ref buffer function as follows: + * @code + * basic_serial_port.async_write_some( + * asio::buffer(data, size), handler); + * @endcode + * See the @ref buffer documentation for information on writing multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_write_some(const ConstBufferSequence& buffers, + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_write_some(this), handler, buffers); + } + + /// Read some data from the serial port. + /** + * This function is used to read data from the serial port. The function + * call will block until one or more bytes of data has been read successfully, + * or until an error occurs. + * + * @param buffers One or more buffers into which the data will be read. + * + * @returns The number of bytes read. + * + * @throws asio::system_error Thrown on failure. An error code of + * asio::error::eof indicates that the connection was closed by the + * peer. + * + * @note The read_some operation may not read all of the requested number of + * bytes. Consider using the @ref read function if you need to ensure that + * the requested amount of data is read before the blocking operation + * completes. + * + * @par Example + * To read into a single data buffer use the @ref buffer function as follows: + * @code + * basic_serial_port.read_some(asio::buffer(data, size)); + * @endcode + * See the @ref buffer documentation for information on reading into multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t read_some(const MutableBufferSequence& buffers) + { + asio::error_code ec; + std::size_t s = impl_.get_service().read_some( + impl_.get_implementation(), buffers, ec); + asio::detail::throw_error(ec, "read_some"); + return s; + } + + /// Read some data from the serial port. + /** + * This function is used to read data from the serial port. The function + * call will block until one or more bytes of data has been read successfully, + * or until an error occurs. + * + * @param buffers One or more buffers into which the data will be read. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns The number of bytes read. Returns 0 if an error occurred. + * + * @note The read_some operation may not read all of the requested number of + * bytes. Consider using the @ref read function if you need to ensure that + * the requested amount of data is read before the blocking operation + * completes. + */ + template + std::size_t read_some(const MutableBufferSequence& buffers, + asio::error_code& ec) + { + return impl_.get_service().read_some( + impl_.get_implementation(), buffers, ec); + } + + /// Start an asynchronous read. + /** + * This function is used to asynchronously read data from the serial port. + * The function call always returns immediately. + * + * @param buffers One or more buffers into which the data will be read. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param handler The handler to be called when the read operation completes. + * Copies will be made of the handler as required. The function signature of + * the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes read. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note The read operation may not read all of the requested number of bytes. + * Consider using the @ref async_read function if you need to ensure that the + * requested amount of data is read before the asynchronous operation + * completes. + * + * @par Example + * To read into a single data buffer use the @ref buffer function as follows: + * @code + * basic_serial_port.async_read_some( + * asio::buffer(data, size), handler); + * @endcode + * See the @ref buffer documentation for information on reading into multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_read_some(const MutableBufferSequence& buffers, + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_read_some(this), handler, buffers); + } + +private: + // Disallow copying and assignment. + basic_serial_port(const basic_serial_port&) ASIO_DELETED; + basic_serial_port& operator=(const basic_serial_port&) ASIO_DELETED; + + class initiate_async_write_some + { + public: + typedef Executor executor_type; + + explicit initiate_async_write_some(basic_serial_port* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(WriteHandler) handler, + const ConstBufferSequence& buffers) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a WriteHandler. + ASIO_WRITE_HANDLER_CHECK(WriteHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_write_some( + self_->impl_.get_implementation(), buffers, + handler2.value, self_->impl_.get_executor()); + } + + private: + basic_serial_port* self_; + }; + + class initiate_async_read_some + { + public: + typedef Executor executor_type; + + explicit initiate_async_read_some(basic_serial_port* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(ReadHandler) handler, + const MutableBufferSequence& buffers) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a ReadHandler. + ASIO_READ_HANDLER_CHECK(ReadHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_read_some( + self_->impl_.get_implementation(), buffers, + handler2.value, self_->impl_.get_executor()); + } + + private: + basic_serial_port* self_; + }; + +#if defined(ASIO_HAS_IOCP) + detail::io_object_impl impl_; +#else + detail::io_object_impl impl_; +#endif +}; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_SERIAL_PORT) + // || defined(GENERATING_DOCUMENTATION) + +#endif // ASIO_BASIC_SERIAL_PORT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_signal_set.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_signal_set.hpp new file mode 100644 index 000000000..b72dcf299 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_signal_set.hpp @@ -0,0 +1,568 @@ +// +// basic_signal_set.hpp +// ~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BASIC_SIGNAL_SET_HPP +#define ASIO_BASIC_SIGNAL_SET_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#include "asio/any_io_executor.hpp" +#include "asio/async_result.hpp" +#include "asio/detail/handler_type_requirements.hpp" +#include "asio/detail/io_object_impl.hpp" +#include "asio/detail/non_const_lvalue.hpp" +#include "asio/detail/signal_set_service.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/error.hpp" +#include "asio/execution_context.hpp" + +namespace asio { + +/// Provides signal functionality. +/** + * The basic_signal_set class provides the ability to perform an asynchronous + * wait for one or more signals to occur. + * + * @par Thread Safety + * @e Distinct @e objects: Safe.@n + * @e Shared @e objects: Unsafe. + * + * @par Example + * Performing an asynchronous wait: + * @code + * void handler( + * const asio::error_code& error, + * int signal_number) + * { + * if (!error) + * { + * // A signal occurred. + * } + * } + * + * ... + * + * // Construct a signal set registered for process termination. + * asio::signal_set signals(my_context, SIGINT, SIGTERM); + * + * // Start an asynchronous wait for one of the signals to occur. + * signals.async_wait(handler); + * @endcode + * + * @par Queueing of signal notifications + * + * If a signal is registered with a signal_set, and the signal occurs when + * there are no waiting handlers, then the signal notification is queued. The + * next async_wait operation on that signal_set will dequeue the notification. + * If multiple notifications are queued, subsequent async_wait operations + * dequeue them one at a time. Signal notifications are dequeued in order of + * ascending signal number. + * + * If a signal number is removed from a signal_set (using the @c remove or @c + * erase member functions) then any queued notifications for that signal are + * discarded. + * + * @par Multiple registration of signals + * + * The same signal number may be registered with different signal_set objects. + * When the signal occurs, one handler is called for each signal_set object. + * + * Note that multiple registration only works for signals that are registered + * using Asio. The application must not also register a signal handler using + * functions such as @c signal() or @c sigaction(). + * + * @par Signal masking on POSIX platforms + * + * POSIX allows signals to be blocked using functions such as @c sigprocmask() + * and @c pthread_sigmask(). For signals to be delivered, programs must ensure + * that any signals registered using signal_set objects are unblocked in at + * least one thread. + */ +template +class basic_signal_set +{ +public: + /// The type of the executor associated with the object. + typedef Executor executor_type; + + /// Rebinds the signal set type to another executor. + template + struct rebind_executor + { + /// The signal set type when rebound to the specified executor. + typedef basic_signal_set other; + }; + + /// Construct a signal set without adding any signals. + /** + * This constructor creates a signal set without registering for any signals. + * + * @param ex The I/O executor that the signal set will use, by default, to + * dispatch handlers for any asynchronous operations performed on the + * signal set. + */ + explicit basic_signal_set(const executor_type& ex) + : impl_(ex) + { + } + + /// Construct a signal set without adding any signals. + /** + * This constructor creates a signal set without registering for any signals. + * + * @param context An execution context which provides the I/O executor that + * the signal set will use, by default, to dispatch handlers for any + * asynchronous operations performed on the signal set. + */ + template + explicit basic_signal_set(ExecutionContext& context, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + } + + /// Construct a signal set and add one signal. + /** + * This constructor creates a signal set and registers for one signal. + * + * @param ex The I/O executor that the signal set will use, by default, to + * dispatch handlers for any asynchronous operations performed on the + * signal set. + * + * @param signal_number_1 The signal number to be added. + * + * @note This constructor is equivalent to performing: + * @code asio::signal_set signals(ex); + * signals.add(signal_number_1); @endcode + */ + basic_signal_set(const executor_type& ex, int signal_number_1) + : impl_(ex) + { + asio::error_code ec; + impl_.get_service().add(impl_.get_implementation(), signal_number_1, ec); + asio::detail::throw_error(ec, "add"); + } + + /// Construct a signal set and add one signal. + /** + * This constructor creates a signal set and registers for one signal. + * + * @param context An execution context which provides the I/O executor that + * the signal set will use, by default, to dispatch handlers for any + * asynchronous operations performed on the signal set. + * + * @param signal_number_1 The signal number to be added. + * + * @note This constructor is equivalent to performing: + * @code asio::signal_set signals(context); + * signals.add(signal_number_1); @endcode + */ + template + basic_signal_set(ExecutionContext& context, int signal_number_1, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + asio::error_code ec; + impl_.get_service().add(impl_.get_implementation(), signal_number_1, ec); + asio::detail::throw_error(ec, "add"); + } + + /// Construct a signal set and add two signals. + /** + * This constructor creates a signal set and registers for two signals. + * + * @param ex The I/O executor that the signal set will use, by default, to + * dispatch handlers for any asynchronous operations performed on the + * signal set. + * + * @param signal_number_1 The first signal number to be added. + * + * @param signal_number_2 The second signal number to be added. + * + * @note This constructor is equivalent to performing: + * @code asio::signal_set signals(ex); + * signals.add(signal_number_1); + * signals.add(signal_number_2); @endcode + */ + basic_signal_set(const executor_type& ex, int signal_number_1, + int signal_number_2) + : impl_(ex) + { + asio::error_code ec; + impl_.get_service().add(impl_.get_implementation(), signal_number_1, ec); + asio::detail::throw_error(ec, "add"); + impl_.get_service().add(impl_.get_implementation(), signal_number_2, ec); + asio::detail::throw_error(ec, "add"); + } + + /// Construct a signal set and add two signals. + /** + * This constructor creates a signal set and registers for two signals. + * + * @param context An execution context which provides the I/O executor that + * the signal set will use, by default, to dispatch handlers for any + * asynchronous operations performed on the signal set. + * + * @param signal_number_1 The first signal number to be added. + * + * @param signal_number_2 The second signal number to be added. + * + * @note This constructor is equivalent to performing: + * @code asio::signal_set signals(context); + * signals.add(signal_number_1); + * signals.add(signal_number_2); @endcode + */ + template + basic_signal_set(ExecutionContext& context, int signal_number_1, + int signal_number_2, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + asio::error_code ec; + impl_.get_service().add(impl_.get_implementation(), signal_number_1, ec); + asio::detail::throw_error(ec, "add"); + impl_.get_service().add(impl_.get_implementation(), signal_number_2, ec); + asio::detail::throw_error(ec, "add"); + } + + /// Construct a signal set and add three signals. + /** + * This constructor creates a signal set and registers for three signals. + * + * @param ex The I/O executor that the signal set will use, by default, to + * dispatch handlers for any asynchronous operations performed on the + * signal set. + * + * @param signal_number_1 The first signal number to be added. + * + * @param signal_number_2 The second signal number to be added. + * + * @param signal_number_3 The third signal number to be added. + * + * @note This constructor is equivalent to performing: + * @code asio::signal_set signals(ex); + * signals.add(signal_number_1); + * signals.add(signal_number_2); + * signals.add(signal_number_3); @endcode + */ + basic_signal_set(const executor_type& ex, int signal_number_1, + int signal_number_2, int signal_number_3) + : impl_(ex) + { + asio::error_code ec; + impl_.get_service().add(impl_.get_implementation(), signal_number_1, ec); + asio::detail::throw_error(ec, "add"); + impl_.get_service().add(impl_.get_implementation(), signal_number_2, ec); + asio::detail::throw_error(ec, "add"); + impl_.get_service().add(impl_.get_implementation(), signal_number_3, ec); + asio::detail::throw_error(ec, "add"); + } + + /// Construct a signal set and add three signals. + /** + * This constructor creates a signal set and registers for three signals. + * + * @param context An execution context which provides the I/O executor that + * the signal set will use, by default, to dispatch handlers for any + * asynchronous operations performed on the signal set. + * + * @param signal_number_1 The first signal number to be added. + * + * @param signal_number_2 The second signal number to be added. + * + * @param signal_number_3 The third signal number to be added. + * + * @note This constructor is equivalent to performing: + * @code asio::signal_set signals(context); + * signals.add(signal_number_1); + * signals.add(signal_number_2); + * signals.add(signal_number_3); @endcode + */ + template + basic_signal_set(ExecutionContext& context, int signal_number_1, + int signal_number_2, int signal_number_3, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + asio::error_code ec; + impl_.get_service().add(impl_.get_implementation(), signal_number_1, ec); + asio::detail::throw_error(ec, "add"); + impl_.get_service().add(impl_.get_implementation(), signal_number_2, ec); + asio::detail::throw_error(ec, "add"); + impl_.get_service().add(impl_.get_implementation(), signal_number_3, ec); + asio::detail::throw_error(ec, "add"); + } + + /// Destroys the signal set. + /** + * This function destroys the signal set, cancelling any outstanding + * asynchronous wait operations associated with the signal set as if by + * calling @c cancel. + */ + ~basic_signal_set() + { + } + + /// Get the executor associated with the object. + executor_type get_executor() ASIO_NOEXCEPT + { + return impl_.get_executor(); + } + + /// Add a signal to a signal_set. + /** + * This function adds the specified signal to the set. It has no effect if the + * signal is already in the set. + * + * @param signal_number The signal to be added to the set. + * + * @throws asio::system_error Thrown on failure. + */ + void add(int signal_number) + { + asio::error_code ec; + impl_.get_service().add(impl_.get_implementation(), signal_number, ec); + asio::detail::throw_error(ec, "add"); + } + + /// Add a signal to a signal_set. + /** + * This function adds the specified signal to the set. It has no effect if the + * signal is already in the set. + * + * @param signal_number The signal to be added to the set. + * + * @param ec Set to indicate what error occurred, if any. + */ + ASIO_SYNC_OP_VOID add(int signal_number, + asio::error_code& ec) + { + impl_.get_service().add(impl_.get_implementation(), signal_number, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Remove a signal from a signal_set. + /** + * This function removes the specified signal from the set. It has no effect + * if the signal is not in the set. + * + * @param signal_number The signal to be removed from the set. + * + * @throws asio::system_error Thrown on failure. + * + * @note Removes any notifications that have been queued for the specified + * signal number. + */ + void remove(int signal_number) + { + asio::error_code ec; + impl_.get_service().remove(impl_.get_implementation(), signal_number, ec); + asio::detail::throw_error(ec, "remove"); + } + + /// Remove a signal from a signal_set. + /** + * This function removes the specified signal from the set. It has no effect + * if the signal is not in the set. + * + * @param signal_number The signal to be removed from the set. + * + * @param ec Set to indicate what error occurred, if any. + * + * @note Removes any notifications that have been queued for the specified + * signal number. + */ + ASIO_SYNC_OP_VOID remove(int signal_number, + asio::error_code& ec) + { + impl_.get_service().remove(impl_.get_implementation(), signal_number, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Remove all signals from a signal_set. + /** + * This function removes all signals from the set. It has no effect if the set + * is already empty. + * + * @throws asio::system_error Thrown on failure. + * + * @note Removes all queued notifications. + */ + void clear() + { + asio::error_code ec; + impl_.get_service().clear(impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "clear"); + } + + /// Remove all signals from a signal_set. + /** + * This function removes all signals from the set. It has no effect if the set + * is already empty. + * + * @param ec Set to indicate what error occurred, if any. + * + * @note Removes all queued notifications. + */ + ASIO_SYNC_OP_VOID clear(asio::error_code& ec) + { + impl_.get_service().clear(impl_.get_implementation(), ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Cancel all operations associated with the signal set. + /** + * This function forces the completion of any pending asynchronous wait + * operations against the signal set. The handler for each cancelled + * operation will be invoked with the asio::error::operation_aborted + * error code. + * + * Cancellation does not alter the set of registered signals. + * + * @throws asio::system_error Thrown on failure. + * + * @note If a registered signal occurred before cancel() is called, then the + * handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + void cancel() + { + asio::error_code ec; + impl_.get_service().cancel(impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "cancel"); + } + + /// Cancel all operations associated with the signal set. + /** + * This function forces the completion of any pending asynchronous wait + * operations against the signal set. The handler for each cancelled + * operation will be invoked with the asio::error::operation_aborted + * error code. + * + * Cancellation does not alter the set of registered signals. + * + * @param ec Set to indicate what error occurred, if any. + * + * @note If a registered signal occurred before cancel() is called, then the + * handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + ASIO_SYNC_OP_VOID cancel(asio::error_code& ec) + { + impl_.get_service().cancel(impl_.get_implementation(), ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Start an asynchronous operation to wait for a signal to be delivered. + /** + * This function may be used to initiate an asynchronous wait against the + * signal set. It always returns immediately. + * + * For each call to async_wait(), the supplied handler will be called exactly + * once. The handler will be called when: + * + * @li One of the registered signals in the signal set occurs; or + * + * @li The signal set was cancelled, in which case the handler is passed the + * error code asio::error::operation_aborted. + * + * @param handler The handler to be called when the signal occurs. Copies + * will be made of the handler as required. The function signature of the + * handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * int signal_number // Indicates which signal occurred. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + */ + template < + ASIO_COMPLETION_TOKEN_FOR(void (asio::error_code, int)) + SignalHandler ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(executor_type)> + ASIO_INITFN_AUTO_RESULT_TYPE(SignalHandler, + void (asio::error_code, int)) + async_wait( + ASIO_MOVE_ARG(SignalHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_wait(this), handler); + } + +private: + // Disallow copying and assignment. + basic_signal_set(const basic_signal_set&) ASIO_DELETED; + basic_signal_set& operator=(const basic_signal_set&) ASIO_DELETED; + + class initiate_async_wait + { + public: + typedef Executor executor_type; + + explicit initiate_async_wait(basic_signal_set* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(SignalHandler) handler) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a SignalHandler. + ASIO_SIGNAL_HANDLER_CHECK(SignalHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_wait( + self_->impl_.get_implementation(), + handler2.value, self_->impl_.get_executor()); + } + + private: + basic_signal_set* self_; + }; + + detail::io_object_impl impl_; +}; + +} // namespace asio + +#endif // ASIO_BASIC_SIGNAL_SET_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_socket.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_socket.hpp new file mode 100644 index 000000000..2504cec0c --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_socket.hpp @@ -0,0 +1,1894 @@ +// +// basic_socket.hpp +// ~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BASIC_SOCKET_HPP +#define ASIO_BASIC_SOCKET_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/any_io_executor.hpp" +#include "asio/detail/config.hpp" +#include "asio/async_result.hpp" +#include "asio/detail/handler_type_requirements.hpp" +#include "asio/detail/io_object_impl.hpp" +#include "asio/detail/non_const_lvalue.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/error.hpp" +#include "asio/execution_context.hpp" +#include "asio/post.hpp" +#include "asio/socket_base.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) +# include "asio/detail/null_socket_service.hpp" +#elif defined(ASIO_HAS_IOCP) +# include "asio/detail/win_iocp_socket_service.hpp" +#else +# include "asio/detail/reactive_socket_service.hpp" +#endif + +#if defined(ASIO_HAS_MOVE) +# include +#endif // defined(ASIO_HAS_MOVE) + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if !defined(ASIO_BASIC_SOCKET_FWD_DECL) +#define ASIO_BASIC_SOCKET_FWD_DECL + +// Forward declaration with defaulted arguments. +template +class basic_socket; + +#endif // !defined(ASIO_BASIC_SOCKET_FWD_DECL) + +/// Provides socket functionality. +/** + * The basic_socket class template provides functionality that is common to both + * stream-oriented and datagram-oriented sockets. + * + * @par Thread Safety + * @e Distinct @e objects: Safe.@n + * @e Shared @e objects: Unsafe. + */ +template +class basic_socket + : public socket_base +{ +public: + /// The type of the executor associated with the object. + typedef Executor executor_type; + + /// Rebinds the socket type to another executor. + template + struct rebind_executor + { + /// The socket type when rebound to the specified executor. + typedef basic_socket other; + }; + + /// The native representation of a socket. +#if defined(GENERATING_DOCUMENTATION) + typedef implementation_defined native_handle_type; +#elif defined(ASIO_WINDOWS_RUNTIME) + typedef typename detail::null_socket_service< + Protocol>::native_handle_type native_handle_type; +#elif defined(ASIO_HAS_IOCP) + typedef typename detail::win_iocp_socket_service< + Protocol>::native_handle_type native_handle_type; +#else + typedef typename detail::reactive_socket_service< + Protocol>::native_handle_type native_handle_type; +#endif + + /// The protocol type. + typedef Protocol protocol_type; + + /// The endpoint type. + typedef typename Protocol::endpoint endpoint_type; + +#if !defined(ASIO_NO_EXTENSIONS) + /// A basic_socket is always the lowest layer. + typedef basic_socket lowest_layer_type; +#endif // !defined(ASIO_NO_EXTENSIONS) + + /// Construct a basic_socket without opening it. + /** + * This constructor creates a socket without opening it. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + */ + explicit basic_socket(const executor_type& ex) + : impl_(ex) + { + } + + /// Construct a basic_socket without opening it. + /** + * This constructor creates a socket without opening it. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + */ + template + explicit basic_socket(ExecutionContext& context, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + } + + /// Construct and open a basic_socket. + /** + * This constructor creates and opens a socket. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @throws asio::system_error Thrown on failure. + */ + basic_socket(const executor_type& ex, const protocol_type& protocol) + : impl_(ex) + { + asio::error_code ec; + impl_.get_service().open(impl_.get_implementation(), protocol, ec); + asio::detail::throw_error(ec, "open"); + } + + /// Construct and open a basic_socket. + /** + * This constructor creates and opens a socket. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_socket(ExecutionContext& context, const protocol_type& protocol, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + asio::error_code ec; + impl_.get_service().open(impl_.get_implementation(), protocol, ec); + asio::detail::throw_error(ec, "open"); + } + + /// Construct a basic_socket, opening it and binding it to the given local + /// endpoint. + /** + * This constructor creates a socket and automatically opens it bound to the + * specified endpoint on the local machine. The protocol used is the protocol + * associated with the given endpoint. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + * + * @param endpoint An endpoint on the local machine to which the socket will + * be bound. + * + * @throws asio::system_error Thrown on failure. + */ + basic_socket(const executor_type& ex, const endpoint_type& endpoint) + : impl_(ex) + { + asio::error_code ec; + const protocol_type protocol = endpoint.protocol(); + impl_.get_service().open(impl_.get_implementation(), protocol, ec); + asio::detail::throw_error(ec, "open"); + impl_.get_service().bind(impl_.get_implementation(), endpoint, ec); + asio::detail::throw_error(ec, "bind"); + } + + /// Construct a basic_socket, opening it and binding it to the given local + /// endpoint. + /** + * This constructor creates a socket and automatically opens it bound to the + * specified endpoint on the local machine. The protocol used is the protocol + * associated with the given endpoint. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + * + * @param endpoint An endpoint on the local machine to which the socket will + * be bound. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_socket(ExecutionContext& context, const endpoint_type& endpoint, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + asio::error_code ec; + const protocol_type protocol = endpoint.protocol(); + impl_.get_service().open(impl_.get_implementation(), protocol, ec); + asio::detail::throw_error(ec, "open"); + impl_.get_service().bind(impl_.get_implementation(), endpoint, ec); + asio::detail::throw_error(ec, "bind"); + } + + /// Construct a basic_socket on an existing native socket. + /** + * This constructor creates a socket object to hold an existing native socket. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @param native_socket A native socket. + * + * @throws asio::system_error Thrown on failure. + */ + basic_socket(const executor_type& ex, const protocol_type& protocol, + const native_handle_type& native_socket) + : impl_(ex) + { + asio::error_code ec; + impl_.get_service().assign(impl_.get_implementation(), + protocol, native_socket, ec); + asio::detail::throw_error(ec, "assign"); + } + + /// Construct a basic_socket on an existing native socket. + /** + * This constructor creates a socket object to hold an existing native socket. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @param native_socket A native socket. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_socket(ExecutionContext& context, const protocol_type& protocol, + const native_handle_type& native_socket, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + asio::error_code ec; + impl_.get_service().assign(impl_.get_implementation(), + protocol, native_socket, ec); + asio::detail::throw_error(ec, "assign"); + } + +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + /// Move-construct a basic_socket from another. + /** + * This constructor moves a socket from one object to another. + * + * @param other The other basic_socket object from which the move will + * occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_socket(const executor_type&) constructor. + */ + basic_socket(basic_socket&& other) ASIO_NOEXCEPT + : impl_(std::move(other.impl_)) + { + } + + /// Move-assign a basic_socket from another. + /** + * This assignment operator moves a socket from one object to another. + * + * @param other The other basic_socket object from which the move will + * occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_socket(const executor_type&) constructor. + */ + basic_socket& operator=(basic_socket&& other) + { + impl_ = std::move(other.impl_); + return *this; + } + + // All sockets have access to each other's implementations. + template + friend class basic_socket; + + /// Move-construct a basic_socket from a socket of another protocol type. + /** + * This constructor moves a socket from one object to another. + * + * @param other The other basic_socket object from which the move will + * occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_socket(const executor_type&) constructor. + */ + template + basic_socket(basic_socket&& other, + typename enable_if< + is_convertible::value + && is_convertible::value + >::type* = 0) + : impl_(std::move(other.impl_)) + { + } + + /// Move-assign a basic_socket from a socket of another protocol type. + /** + * This assignment operator moves a socket from one object to another. + * + * @param other The other basic_socket object from which the move will + * occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_socket(const executor_type&) constructor. + */ + template + typename enable_if< + is_convertible::value + && is_convertible::value, + basic_socket& + >::type operator=(basic_socket && other) + { + basic_socket tmp(std::move(other)); + impl_ = std::move(tmp.impl_); + return *this; + } +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + /// Get the executor associated with the object. + executor_type get_executor() ASIO_NOEXCEPT + { + return impl_.get_executor(); + } + +#if !defined(ASIO_NO_EXTENSIONS) + /// Get a reference to the lowest layer. + /** + * This function returns a reference to the lowest layer in a stack of + * layers. Since a basic_socket cannot contain any further layers, it simply + * returns a reference to itself. + * + * @return A reference to the lowest layer in the stack of layers. Ownership + * is not transferred to the caller. + */ + lowest_layer_type& lowest_layer() + { + return *this; + } + + /// Get a const reference to the lowest layer. + /** + * This function returns a const reference to the lowest layer in a stack of + * layers. Since a basic_socket cannot contain any further layers, it simply + * returns a reference to itself. + * + * @return A const reference to the lowest layer in the stack of layers. + * Ownership is not transferred to the caller. + */ + const lowest_layer_type& lowest_layer() const + { + return *this; + } +#endif // !defined(ASIO_NO_EXTENSIONS) + + /// Open the socket using the specified protocol. + /** + * This function opens the socket so that it will use the specified protocol. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * @code + * asio::ip::tcp::socket socket(my_context); + * socket.open(asio::ip::tcp::v4()); + * @endcode + */ + void open(const protocol_type& protocol = protocol_type()) + { + asio::error_code ec; + impl_.get_service().open(impl_.get_implementation(), protocol, ec); + asio::detail::throw_error(ec, "open"); + } + + /// Open the socket using the specified protocol. + /** + * This function opens the socket so that it will use the specified protocol. + * + * @param protocol An object specifying which protocol is to be used. + * + * @param ec Set to indicate what error occurred, if any. + * + * @par Example + * @code + * asio::ip::tcp::socket socket(my_context); + * asio::error_code ec; + * socket.open(asio::ip::tcp::v4(), ec); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + ASIO_SYNC_OP_VOID open(const protocol_type& protocol, + asio::error_code& ec) + { + impl_.get_service().open(impl_.get_implementation(), protocol, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Assign an existing native socket to the socket. + /* + * This function opens the socket to hold an existing native socket. + * + * @param protocol An object specifying which protocol is to be used. + * + * @param native_socket A native socket. + * + * @throws asio::system_error Thrown on failure. + */ + void assign(const protocol_type& protocol, + const native_handle_type& native_socket) + { + asio::error_code ec; + impl_.get_service().assign(impl_.get_implementation(), + protocol, native_socket, ec); + asio::detail::throw_error(ec, "assign"); + } + + /// Assign an existing native socket to the socket. + /* + * This function opens the socket to hold an existing native socket. + * + * @param protocol An object specifying which protocol is to be used. + * + * @param native_socket A native socket. + * + * @param ec Set to indicate what error occurred, if any. + */ + ASIO_SYNC_OP_VOID assign(const protocol_type& protocol, + const native_handle_type& native_socket, asio::error_code& ec) + { + impl_.get_service().assign(impl_.get_implementation(), + protocol, native_socket, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Determine whether the socket is open. + bool is_open() const + { + return impl_.get_service().is_open(impl_.get_implementation()); + } + + /// Close the socket. + /** + * This function is used to close the socket. Any asynchronous send, receive + * or connect operations will be cancelled immediately, and will complete + * with the asio::error::operation_aborted error. + * + * @throws asio::system_error Thrown on failure. Note that, even if + * the function indicates an error, the underlying descriptor is closed. + * + * @note For portable behaviour with respect to graceful closure of a + * connected socket, call shutdown() before closing the socket. + */ + void close() + { + asio::error_code ec; + impl_.get_service().close(impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "close"); + } + + /// Close the socket. + /** + * This function is used to close the socket. Any asynchronous send, receive + * or connect operations will be cancelled immediately, and will complete + * with the asio::error::operation_aborted error. + * + * @param ec Set to indicate what error occurred, if any. Note that, even if + * the function indicates an error, the underlying descriptor is closed. + * + * @par Example + * @code + * asio::ip::tcp::socket socket(my_context); + * ... + * asio::error_code ec; + * socket.close(ec); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + * + * @note For portable behaviour with respect to graceful closure of a + * connected socket, call shutdown() before closing the socket. + */ + ASIO_SYNC_OP_VOID close(asio::error_code& ec) + { + impl_.get_service().close(impl_.get_implementation(), ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Release ownership of the underlying native socket. + /** + * This function causes all outstanding asynchronous connect, send and receive + * operations to finish immediately, and the handlers for cancelled operations + * will be passed the asio::error::operation_aborted error. Ownership + * of the native socket is then transferred to the caller. + * + * @throws asio::system_error Thrown on failure. + * + * @note This function is unsupported on Windows versions prior to Windows + * 8.1, and will fail with asio::error::operation_not_supported on + * these platforms. + */ +#if defined(ASIO_MSVC) && (ASIO_MSVC >= 1400) \ + && (!defined(_WIN32_WINNT) || _WIN32_WINNT < 0x0603) + __declspec(deprecated("This function always fails with " + "operation_not_supported when used on Windows versions " + "prior to Windows 8.1.")) +#endif + native_handle_type release() + { + asio::error_code ec; + native_handle_type s = impl_.get_service().release( + impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "release"); + return s; + } + + /// Release ownership of the underlying native socket. + /** + * This function causes all outstanding asynchronous connect, send and receive + * operations to finish immediately, and the handlers for cancelled operations + * will be passed the asio::error::operation_aborted error. Ownership + * of the native socket is then transferred to the caller. + * + * @param ec Set to indicate what error occurred, if any. + * + * @note This function is unsupported on Windows versions prior to Windows + * 8.1, and will fail with asio::error::operation_not_supported on + * these platforms. + */ +#if defined(ASIO_MSVC) && (ASIO_MSVC >= 1400) \ + && (!defined(_WIN32_WINNT) || _WIN32_WINNT < 0x0603) + __declspec(deprecated("This function always fails with " + "operation_not_supported when used on Windows versions " + "prior to Windows 8.1.")) +#endif + native_handle_type release(asio::error_code& ec) + { + return impl_.get_service().release(impl_.get_implementation(), ec); + } + + /// Get the native socket representation. + /** + * This function may be used to obtain the underlying representation of the + * socket. This is intended to allow access to native socket functionality + * that is not otherwise provided. + */ + native_handle_type native_handle() + { + return impl_.get_service().native_handle(impl_.get_implementation()); + } + + /// Cancel all asynchronous operations associated with the socket. + /** + * This function causes all outstanding asynchronous connect, send and receive + * operations to finish immediately, and the handlers for cancelled operations + * will be passed the asio::error::operation_aborted error. + * + * @throws asio::system_error Thrown on failure. + * + * @note Calls to cancel() will always fail with + * asio::error::operation_not_supported when run on Windows XP, Windows + * Server 2003, and earlier versions of Windows, unless + * ASIO_ENABLE_CANCELIO is defined. However, the CancelIo function has + * two issues that should be considered before enabling its use: + * + * @li It will only cancel asynchronous operations that were initiated in the + * current thread. + * + * @li It can appear to complete without error, but the request to cancel the + * unfinished operations may be silently ignored by the operating system. + * Whether it works or not seems to depend on the drivers that are installed. + * + * For portable cancellation, consider using one of the following + * alternatives: + * + * @li Disable asio's I/O completion port backend by defining + * ASIO_DISABLE_IOCP. + * + * @li Use the close() function to simultaneously cancel the outstanding + * operations and close the socket. + * + * When running on Windows Vista, Windows Server 2008, and later, the + * CancelIoEx function is always used. This function does not have the + * problems described above. + */ +#if defined(ASIO_MSVC) && (ASIO_MSVC >= 1400) \ + && (!defined(_WIN32_WINNT) || _WIN32_WINNT < 0x0600) \ + && !defined(ASIO_ENABLE_CANCELIO) + __declspec(deprecated("By default, this function always fails with " + "operation_not_supported when used on Windows XP, Windows Server 2003, " + "or earlier. Consult documentation for details.")) +#endif + void cancel() + { + asio::error_code ec; + impl_.get_service().cancel(impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "cancel"); + } + + /// Cancel all asynchronous operations associated with the socket. + /** + * This function causes all outstanding asynchronous connect, send and receive + * operations to finish immediately, and the handlers for cancelled operations + * will be passed the asio::error::operation_aborted error. + * + * @param ec Set to indicate what error occurred, if any. + * + * @note Calls to cancel() will always fail with + * asio::error::operation_not_supported when run on Windows XP, Windows + * Server 2003, and earlier versions of Windows, unless + * ASIO_ENABLE_CANCELIO is defined. However, the CancelIo function has + * two issues that should be considered before enabling its use: + * + * @li It will only cancel asynchronous operations that were initiated in the + * current thread. + * + * @li It can appear to complete without error, but the request to cancel the + * unfinished operations may be silently ignored by the operating system. + * Whether it works or not seems to depend on the drivers that are installed. + * + * For portable cancellation, consider using one of the following + * alternatives: + * + * @li Disable asio's I/O completion port backend by defining + * ASIO_DISABLE_IOCP. + * + * @li Use the close() function to simultaneously cancel the outstanding + * operations and close the socket. + * + * When running on Windows Vista, Windows Server 2008, and later, the + * CancelIoEx function is always used. This function does not have the + * problems described above. + */ +#if defined(ASIO_MSVC) && (ASIO_MSVC >= 1400) \ + && (!defined(_WIN32_WINNT) || _WIN32_WINNT < 0x0600) \ + && !defined(ASIO_ENABLE_CANCELIO) + __declspec(deprecated("By default, this function always fails with " + "operation_not_supported when used on Windows XP, Windows Server 2003, " + "or earlier. Consult documentation for details.")) +#endif + ASIO_SYNC_OP_VOID cancel(asio::error_code& ec) + { + impl_.get_service().cancel(impl_.get_implementation(), ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Determine whether the socket is at the out-of-band data mark. + /** + * This function is used to check whether the socket input is currently + * positioned at the out-of-band data mark. + * + * @return A bool indicating whether the socket is at the out-of-band data + * mark. + * + * @throws asio::system_error Thrown on failure. + */ + bool at_mark() const + { + asio::error_code ec; + bool b = impl_.get_service().at_mark(impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "at_mark"); + return b; + } + + /// Determine whether the socket is at the out-of-band data mark. + /** + * This function is used to check whether the socket input is currently + * positioned at the out-of-band data mark. + * + * @param ec Set to indicate what error occurred, if any. + * + * @return A bool indicating whether the socket is at the out-of-band data + * mark. + */ + bool at_mark(asio::error_code& ec) const + { + return impl_.get_service().at_mark(impl_.get_implementation(), ec); + } + + /// Determine the number of bytes available for reading. + /** + * This function is used to determine the number of bytes that may be read + * without blocking. + * + * @return The number of bytes that may be read without blocking, or 0 if an + * error occurs. + * + * @throws asio::system_error Thrown on failure. + */ + std::size_t available() const + { + asio::error_code ec; + std::size_t s = impl_.get_service().available( + impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "available"); + return s; + } + + /// Determine the number of bytes available for reading. + /** + * This function is used to determine the number of bytes that may be read + * without blocking. + * + * @param ec Set to indicate what error occurred, if any. + * + * @return The number of bytes that may be read without blocking, or 0 if an + * error occurs. + */ + std::size_t available(asio::error_code& ec) const + { + return impl_.get_service().available(impl_.get_implementation(), ec); + } + + /// Bind the socket to the given local endpoint. + /** + * This function binds the socket to the specified endpoint on the local + * machine. + * + * @param endpoint An endpoint on the local machine to which the socket will + * be bound. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * @code + * asio::ip::tcp::socket socket(my_context); + * socket.open(asio::ip::tcp::v4()); + * socket.bind(asio::ip::tcp::endpoint( + * asio::ip::tcp::v4(), 12345)); + * @endcode + */ + void bind(const endpoint_type& endpoint) + { + asio::error_code ec; + impl_.get_service().bind(impl_.get_implementation(), endpoint, ec); + asio::detail::throw_error(ec, "bind"); + } + + /// Bind the socket to the given local endpoint. + /** + * This function binds the socket to the specified endpoint on the local + * machine. + * + * @param endpoint An endpoint on the local machine to which the socket will + * be bound. + * + * @param ec Set to indicate what error occurred, if any. + * + * @par Example + * @code + * asio::ip::tcp::socket socket(my_context); + * socket.open(asio::ip::tcp::v4()); + * asio::error_code ec; + * socket.bind(asio::ip::tcp::endpoint( + * asio::ip::tcp::v4(), 12345), ec); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + ASIO_SYNC_OP_VOID bind(const endpoint_type& endpoint, + asio::error_code& ec) + { + impl_.get_service().bind(impl_.get_implementation(), endpoint, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Connect the socket to the specified endpoint. + /** + * This function is used to connect a socket to the specified remote endpoint. + * The function call will block until the connection is successfully made or + * an error occurs. + * + * The socket is automatically opened if it is not already open. If the + * connect fails, and the socket was automatically opened, the socket is + * not returned to the closed state. + * + * @param peer_endpoint The remote endpoint to which the socket will be + * connected. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * @code + * asio::ip::tcp::socket socket(my_context); + * asio::ip::tcp::endpoint endpoint( + * asio::ip::address::from_string("1.2.3.4"), 12345); + * socket.connect(endpoint); + * @endcode + */ + void connect(const endpoint_type& peer_endpoint) + { + asio::error_code ec; + if (!is_open()) + { + impl_.get_service().open(impl_.get_implementation(), + peer_endpoint.protocol(), ec); + asio::detail::throw_error(ec, "connect"); + } + impl_.get_service().connect(impl_.get_implementation(), peer_endpoint, ec); + asio::detail::throw_error(ec, "connect"); + } + + /// Connect the socket to the specified endpoint. + /** + * This function is used to connect a socket to the specified remote endpoint. + * The function call will block until the connection is successfully made or + * an error occurs. + * + * The socket is automatically opened if it is not already open. If the + * connect fails, and the socket was automatically opened, the socket is + * not returned to the closed state. + * + * @param peer_endpoint The remote endpoint to which the socket will be + * connected. + * + * @param ec Set to indicate what error occurred, if any. + * + * @par Example + * @code + * asio::ip::tcp::socket socket(my_context); + * asio::ip::tcp::endpoint endpoint( + * asio::ip::address::from_string("1.2.3.4"), 12345); + * asio::error_code ec; + * socket.connect(endpoint, ec); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + ASIO_SYNC_OP_VOID connect(const endpoint_type& peer_endpoint, + asio::error_code& ec) + { + if (!is_open()) + { + impl_.get_service().open(impl_.get_implementation(), + peer_endpoint.protocol(), ec); + if (ec) + { + ASIO_SYNC_OP_VOID_RETURN(ec); + } + } + + impl_.get_service().connect(impl_.get_implementation(), peer_endpoint, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Start an asynchronous connect. + /** + * This function is used to asynchronously connect a socket to the specified + * remote endpoint. The function call always returns immediately. + * + * The socket is automatically opened if it is not already open. If the + * connect fails, and the socket was automatically opened, the socket is + * not returned to the closed state. + * + * @param peer_endpoint The remote endpoint to which the socket will be + * connected. Copies will be made of the endpoint object as required. + * + * @param handler The handler to be called when the connection operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error // Result of operation + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * @code + * void connect_handler(const asio::error_code& error) + * { + * if (!error) + * { + * // Connect succeeded. + * } + * } + * + * ... + * + * asio::ip::tcp::socket socket(my_context); + * asio::ip::tcp::endpoint endpoint( + * asio::ip::address::from_string("1.2.3.4"), 12345); + * socket.async_connect(endpoint, connect_handler); + * @endcode + */ + template < + ASIO_COMPLETION_TOKEN_FOR(void (asio::error_code)) + ConnectHandler ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(executor_type)> + ASIO_INITFN_AUTO_RESULT_TYPE(ConnectHandler, + void (asio::error_code)) + async_connect(const endpoint_type& peer_endpoint, + ASIO_MOVE_ARG(ConnectHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + asio::error_code open_ec; + if (!is_open()) + { + const protocol_type protocol = peer_endpoint.protocol(); + impl_.get_service().open(impl_.get_implementation(), protocol, open_ec); + } + + return async_initiate( + initiate_async_connect(this), handler, peer_endpoint, open_ec); + } + + /// Set an option on the socket. + /** + * This function is used to set an option on the socket. + * + * @param option The new option value to be set on the socket. + * + * @throws asio::system_error Thrown on failure. + * + * @sa SettableSocketOption @n + * asio::socket_base::broadcast @n + * asio::socket_base::do_not_route @n + * asio::socket_base::keep_alive @n + * asio::socket_base::linger @n + * asio::socket_base::receive_buffer_size @n + * asio::socket_base::receive_low_watermark @n + * asio::socket_base::reuse_address @n + * asio::socket_base::send_buffer_size @n + * asio::socket_base::send_low_watermark @n + * asio::ip::multicast::join_group @n + * asio::ip::multicast::leave_group @n + * asio::ip::multicast::enable_loopback @n + * asio::ip::multicast::outbound_interface @n + * asio::ip::multicast::hops @n + * asio::ip::tcp::no_delay + * + * @par Example + * Setting the IPPROTO_TCP/TCP_NODELAY option: + * @code + * asio::ip::tcp::socket socket(my_context); + * ... + * asio::ip::tcp::no_delay option(true); + * socket.set_option(option); + * @endcode + */ + template + void set_option(const SettableSocketOption& option) + { + asio::error_code ec; + impl_.get_service().set_option(impl_.get_implementation(), option, ec); + asio::detail::throw_error(ec, "set_option"); + } + + /// Set an option on the socket. + /** + * This function is used to set an option on the socket. + * + * @param option The new option value to be set on the socket. + * + * @param ec Set to indicate what error occurred, if any. + * + * @sa SettableSocketOption @n + * asio::socket_base::broadcast @n + * asio::socket_base::do_not_route @n + * asio::socket_base::keep_alive @n + * asio::socket_base::linger @n + * asio::socket_base::receive_buffer_size @n + * asio::socket_base::receive_low_watermark @n + * asio::socket_base::reuse_address @n + * asio::socket_base::send_buffer_size @n + * asio::socket_base::send_low_watermark @n + * asio::ip::multicast::join_group @n + * asio::ip::multicast::leave_group @n + * asio::ip::multicast::enable_loopback @n + * asio::ip::multicast::outbound_interface @n + * asio::ip::multicast::hops @n + * asio::ip::tcp::no_delay + * + * @par Example + * Setting the IPPROTO_TCP/TCP_NODELAY option: + * @code + * asio::ip::tcp::socket socket(my_context); + * ... + * asio::ip::tcp::no_delay option(true); + * asio::error_code ec; + * socket.set_option(option, ec); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + template + ASIO_SYNC_OP_VOID set_option(const SettableSocketOption& option, + asio::error_code& ec) + { + impl_.get_service().set_option(impl_.get_implementation(), option, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Get an option from the socket. + /** + * This function is used to get the current value of an option on the socket. + * + * @param option The option value to be obtained from the socket. + * + * @throws asio::system_error Thrown on failure. + * + * @sa GettableSocketOption @n + * asio::socket_base::broadcast @n + * asio::socket_base::do_not_route @n + * asio::socket_base::keep_alive @n + * asio::socket_base::linger @n + * asio::socket_base::receive_buffer_size @n + * asio::socket_base::receive_low_watermark @n + * asio::socket_base::reuse_address @n + * asio::socket_base::send_buffer_size @n + * asio::socket_base::send_low_watermark @n + * asio::ip::multicast::join_group @n + * asio::ip::multicast::leave_group @n + * asio::ip::multicast::enable_loopback @n + * asio::ip::multicast::outbound_interface @n + * asio::ip::multicast::hops @n + * asio::ip::tcp::no_delay + * + * @par Example + * Getting the value of the SOL_SOCKET/SO_KEEPALIVE option: + * @code + * asio::ip::tcp::socket socket(my_context); + * ... + * asio::ip::tcp::socket::keep_alive option; + * socket.get_option(option); + * bool is_set = option.value(); + * @endcode + */ + template + void get_option(GettableSocketOption& option) const + { + asio::error_code ec; + impl_.get_service().get_option(impl_.get_implementation(), option, ec); + asio::detail::throw_error(ec, "get_option"); + } + + /// Get an option from the socket. + /** + * This function is used to get the current value of an option on the socket. + * + * @param option The option value to be obtained from the socket. + * + * @param ec Set to indicate what error occurred, if any. + * + * @sa GettableSocketOption @n + * asio::socket_base::broadcast @n + * asio::socket_base::do_not_route @n + * asio::socket_base::keep_alive @n + * asio::socket_base::linger @n + * asio::socket_base::receive_buffer_size @n + * asio::socket_base::receive_low_watermark @n + * asio::socket_base::reuse_address @n + * asio::socket_base::send_buffer_size @n + * asio::socket_base::send_low_watermark @n + * asio::ip::multicast::join_group @n + * asio::ip::multicast::leave_group @n + * asio::ip::multicast::enable_loopback @n + * asio::ip::multicast::outbound_interface @n + * asio::ip::multicast::hops @n + * asio::ip::tcp::no_delay + * + * @par Example + * Getting the value of the SOL_SOCKET/SO_KEEPALIVE option: + * @code + * asio::ip::tcp::socket socket(my_context); + * ... + * asio::ip::tcp::socket::keep_alive option; + * asio::error_code ec; + * socket.get_option(option, ec); + * if (ec) + * { + * // An error occurred. + * } + * bool is_set = option.value(); + * @endcode + */ + template + ASIO_SYNC_OP_VOID get_option(GettableSocketOption& option, + asio::error_code& ec) const + { + impl_.get_service().get_option(impl_.get_implementation(), option, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Perform an IO control command on the socket. + /** + * This function is used to execute an IO control command on the socket. + * + * @param command The IO control command to be performed on the socket. + * + * @throws asio::system_error Thrown on failure. + * + * @sa IoControlCommand @n + * asio::socket_base::bytes_readable @n + * asio::socket_base::non_blocking_io + * + * @par Example + * Getting the number of bytes ready to read: + * @code + * asio::ip::tcp::socket socket(my_context); + * ... + * asio::ip::tcp::socket::bytes_readable command; + * socket.io_control(command); + * std::size_t bytes_readable = command.get(); + * @endcode + */ + template + void io_control(IoControlCommand& command) + { + asio::error_code ec; + impl_.get_service().io_control(impl_.get_implementation(), command, ec); + asio::detail::throw_error(ec, "io_control"); + } + + /// Perform an IO control command on the socket. + /** + * This function is used to execute an IO control command on the socket. + * + * @param command The IO control command to be performed on the socket. + * + * @param ec Set to indicate what error occurred, if any. + * + * @sa IoControlCommand @n + * asio::socket_base::bytes_readable @n + * asio::socket_base::non_blocking_io + * + * @par Example + * Getting the number of bytes ready to read: + * @code + * asio::ip::tcp::socket socket(my_context); + * ... + * asio::ip::tcp::socket::bytes_readable command; + * asio::error_code ec; + * socket.io_control(command, ec); + * if (ec) + * { + * // An error occurred. + * } + * std::size_t bytes_readable = command.get(); + * @endcode + */ + template + ASIO_SYNC_OP_VOID io_control(IoControlCommand& command, + asio::error_code& ec) + { + impl_.get_service().io_control(impl_.get_implementation(), command, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Gets the non-blocking mode of the socket. + /** + * @returns @c true if the socket's synchronous operations will fail with + * asio::error::would_block if they are unable to perform the requested + * operation immediately. If @c false, synchronous operations will block + * until complete. + * + * @note The non-blocking mode has no effect on the behaviour of asynchronous + * operations. Asynchronous operations will never fail with the error + * asio::error::would_block. + */ + bool non_blocking() const + { + return impl_.get_service().non_blocking(impl_.get_implementation()); + } + + /// Sets the non-blocking mode of the socket. + /** + * @param mode If @c true, the socket's synchronous operations will fail with + * asio::error::would_block if they are unable to perform the requested + * operation immediately. If @c false, synchronous operations will block + * until complete. + * + * @throws asio::system_error Thrown on failure. + * + * @note The non-blocking mode has no effect on the behaviour of asynchronous + * operations. Asynchronous operations will never fail with the error + * asio::error::would_block. + */ + void non_blocking(bool mode) + { + asio::error_code ec; + impl_.get_service().non_blocking(impl_.get_implementation(), mode, ec); + asio::detail::throw_error(ec, "non_blocking"); + } + + /// Sets the non-blocking mode of the socket. + /** + * @param mode If @c true, the socket's synchronous operations will fail with + * asio::error::would_block if they are unable to perform the requested + * operation immediately. If @c false, synchronous operations will block + * until complete. + * + * @param ec Set to indicate what error occurred, if any. + * + * @note The non-blocking mode has no effect on the behaviour of asynchronous + * operations. Asynchronous operations will never fail with the error + * asio::error::would_block. + */ + ASIO_SYNC_OP_VOID non_blocking( + bool mode, asio::error_code& ec) + { + impl_.get_service().non_blocking(impl_.get_implementation(), mode, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Gets the non-blocking mode of the native socket implementation. + /** + * This function is used to retrieve the non-blocking mode of the underlying + * native socket. This mode has no effect on the behaviour of the socket + * object's synchronous operations. + * + * @returns @c true if the underlying socket is in non-blocking mode and + * direct system calls may fail with asio::error::would_block (or the + * equivalent system error). + * + * @note The current non-blocking mode is cached by the socket object. + * Consequently, the return value may be incorrect if the non-blocking mode + * was set directly on the native socket. + * + * @par Example + * This function is intended to allow the encapsulation of arbitrary + * non-blocking system calls as asynchronous operations, in a way that is + * transparent to the user of the socket object. The following example + * illustrates how Linux's @c sendfile system call might be encapsulated: + * @code template + * struct sendfile_op + * { + * tcp::socket& sock_; + * int fd_; + * Handler handler_; + * off_t offset_; + * std::size_t total_bytes_transferred_; + * + * // Function call operator meeting WriteHandler requirements. + * // Used as the handler for the async_write_some operation. + * void operator()(asio::error_code ec, std::size_t) + * { + * // Put the underlying socket into non-blocking mode. + * if (!ec) + * if (!sock_.native_non_blocking()) + * sock_.native_non_blocking(true, ec); + * + * if (!ec) + * { + * for (;;) + * { + * // Try the system call. + * errno = 0; + * int n = ::sendfile(sock_.native_handle(), fd_, &offset_, 65536); + * ec = asio::error_code(n < 0 ? errno : 0, + * asio::error::get_system_category()); + * total_bytes_transferred_ += ec ? 0 : n; + * + * // Retry operation immediately if interrupted by signal. + * if (ec == asio::error::interrupted) + * continue; + * + * // Check if we need to run the operation again. + * if (ec == asio::error::would_block + * || ec == asio::error::try_again) + * { + * // We have to wait for the socket to become ready again. + * sock_.async_wait(tcp::socket::wait_write, *this); + * return; + * } + * + * if (ec || n == 0) + * { + * // An error occurred, or we have reached the end of the file. + * // Either way we must exit the loop so we can call the handler. + * break; + * } + * + * // Loop around to try calling sendfile again. + * } + * } + * + * // Pass result back to user's handler. + * handler_(ec, total_bytes_transferred_); + * } + * }; + * + * template + * void async_sendfile(tcp::socket& sock, int fd, Handler h) + * { + * sendfile_op op = { sock, fd, h, 0, 0 }; + * sock.async_wait(tcp::socket::wait_write, op); + * } @endcode + */ + bool native_non_blocking() const + { + return impl_.get_service().native_non_blocking(impl_.get_implementation()); + } + + /// Sets the non-blocking mode of the native socket implementation. + /** + * This function is used to modify the non-blocking mode of the underlying + * native socket. It has no effect on the behaviour of the socket object's + * synchronous operations. + * + * @param mode If @c true, the underlying socket is put into non-blocking + * mode and direct system calls may fail with asio::error::would_block + * (or the equivalent system error). + * + * @throws asio::system_error Thrown on failure. If the @c mode is + * @c false, but the current value of @c non_blocking() is @c true, this + * function fails with asio::error::invalid_argument, as the + * combination does not make sense. + * + * @par Example + * This function is intended to allow the encapsulation of arbitrary + * non-blocking system calls as asynchronous operations, in a way that is + * transparent to the user of the socket object. The following example + * illustrates how Linux's @c sendfile system call might be encapsulated: + * @code template + * struct sendfile_op + * { + * tcp::socket& sock_; + * int fd_; + * Handler handler_; + * off_t offset_; + * std::size_t total_bytes_transferred_; + * + * // Function call operator meeting WriteHandler requirements. + * // Used as the handler for the async_write_some operation. + * void operator()(asio::error_code ec, std::size_t) + * { + * // Put the underlying socket into non-blocking mode. + * if (!ec) + * if (!sock_.native_non_blocking()) + * sock_.native_non_blocking(true, ec); + * + * if (!ec) + * { + * for (;;) + * { + * // Try the system call. + * errno = 0; + * int n = ::sendfile(sock_.native_handle(), fd_, &offset_, 65536); + * ec = asio::error_code(n < 0 ? errno : 0, + * asio::error::get_system_category()); + * total_bytes_transferred_ += ec ? 0 : n; + * + * // Retry operation immediately if interrupted by signal. + * if (ec == asio::error::interrupted) + * continue; + * + * // Check if we need to run the operation again. + * if (ec == asio::error::would_block + * || ec == asio::error::try_again) + * { + * // We have to wait for the socket to become ready again. + * sock_.async_wait(tcp::socket::wait_write, *this); + * return; + * } + * + * if (ec || n == 0) + * { + * // An error occurred, or we have reached the end of the file. + * // Either way we must exit the loop so we can call the handler. + * break; + * } + * + * // Loop around to try calling sendfile again. + * } + * } + * + * // Pass result back to user's handler. + * handler_(ec, total_bytes_transferred_); + * } + * }; + * + * template + * void async_sendfile(tcp::socket& sock, int fd, Handler h) + * { + * sendfile_op op = { sock, fd, h, 0, 0 }; + * sock.async_wait(tcp::socket::wait_write, op); + * } @endcode + */ + void native_non_blocking(bool mode) + { + asio::error_code ec; + impl_.get_service().native_non_blocking( + impl_.get_implementation(), mode, ec); + asio::detail::throw_error(ec, "native_non_blocking"); + } + + /// Sets the non-blocking mode of the native socket implementation. + /** + * This function is used to modify the non-blocking mode of the underlying + * native socket. It has no effect on the behaviour of the socket object's + * synchronous operations. + * + * @param mode If @c true, the underlying socket is put into non-blocking + * mode and direct system calls may fail with asio::error::would_block + * (or the equivalent system error). + * + * @param ec Set to indicate what error occurred, if any. If the @c mode is + * @c false, but the current value of @c non_blocking() is @c true, this + * function fails with asio::error::invalid_argument, as the + * combination does not make sense. + * + * @par Example + * This function is intended to allow the encapsulation of arbitrary + * non-blocking system calls as asynchronous operations, in a way that is + * transparent to the user of the socket object. The following example + * illustrates how Linux's @c sendfile system call might be encapsulated: + * @code template + * struct sendfile_op + * { + * tcp::socket& sock_; + * int fd_; + * Handler handler_; + * off_t offset_; + * std::size_t total_bytes_transferred_; + * + * // Function call operator meeting WriteHandler requirements. + * // Used as the handler for the async_write_some operation. + * void operator()(asio::error_code ec, std::size_t) + * { + * // Put the underlying socket into non-blocking mode. + * if (!ec) + * if (!sock_.native_non_blocking()) + * sock_.native_non_blocking(true, ec); + * + * if (!ec) + * { + * for (;;) + * { + * // Try the system call. + * errno = 0; + * int n = ::sendfile(sock_.native_handle(), fd_, &offset_, 65536); + * ec = asio::error_code(n < 0 ? errno : 0, + * asio::error::get_system_category()); + * total_bytes_transferred_ += ec ? 0 : n; + * + * // Retry operation immediately if interrupted by signal. + * if (ec == asio::error::interrupted) + * continue; + * + * // Check if we need to run the operation again. + * if (ec == asio::error::would_block + * || ec == asio::error::try_again) + * { + * // We have to wait for the socket to become ready again. + * sock_.async_wait(tcp::socket::wait_write, *this); + * return; + * } + * + * if (ec || n == 0) + * { + * // An error occurred, or we have reached the end of the file. + * // Either way we must exit the loop so we can call the handler. + * break; + * } + * + * // Loop around to try calling sendfile again. + * } + * } + * + * // Pass result back to user's handler. + * handler_(ec, total_bytes_transferred_); + * } + * }; + * + * template + * void async_sendfile(tcp::socket& sock, int fd, Handler h) + * { + * sendfile_op op = { sock, fd, h, 0, 0 }; + * sock.async_wait(tcp::socket::wait_write, op); + * } @endcode + */ + ASIO_SYNC_OP_VOID native_non_blocking( + bool mode, asio::error_code& ec) + { + impl_.get_service().native_non_blocking( + impl_.get_implementation(), mode, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Get the local endpoint of the socket. + /** + * This function is used to obtain the locally bound endpoint of the socket. + * + * @returns An object that represents the local endpoint of the socket. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * @code + * asio::ip::tcp::socket socket(my_context); + * ... + * asio::ip::tcp::endpoint endpoint = socket.local_endpoint(); + * @endcode + */ + endpoint_type local_endpoint() const + { + asio::error_code ec; + endpoint_type ep = impl_.get_service().local_endpoint( + impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "local_endpoint"); + return ep; + } + + /// Get the local endpoint of the socket. + /** + * This function is used to obtain the locally bound endpoint of the socket. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns An object that represents the local endpoint of the socket. + * Returns a default-constructed endpoint object if an error occurred. + * + * @par Example + * @code + * asio::ip::tcp::socket socket(my_context); + * ... + * asio::error_code ec; + * asio::ip::tcp::endpoint endpoint = socket.local_endpoint(ec); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + endpoint_type local_endpoint(asio::error_code& ec) const + { + return impl_.get_service().local_endpoint(impl_.get_implementation(), ec); + } + + /// Get the remote endpoint of the socket. + /** + * This function is used to obtain the remote endpoint of the socket. + * + * @returns An object that represents the remote endpoint of the socket. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * @code + * asio::ip::tcp::socket socket(my_context); + * ... + * asio::ip::tcp::endpoint endpoint = socket.remote_endpoint(); + * @endcode + */ + endpoint_type remote_endpoint() const + { + asio::error_code ec; + endpoint_type ep = impl_.get_service().remote_endpoint( + impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "remote_endpoint"); + return ep; + } + + /// Get the remote endpoint of the socket. + /** + * This function is used to obtain the remote endpoint of the socket. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns An object that represents the remote endpoint of the socket. + * Returns a default-constructed endpoint object if an error occurred. + * + * @par Example + * @code + * asio::ip::tcp::socket socket(my_context); + * ... + * asio::error_code ec; + * asio::ip::tcp::endpoint endpoint = socket.remote_endpoint(ec); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + endpoint_type remote_endpoint(asio::error_code& ec) const + { + return impl_.get_service().remote_endpoint(impl_.get_implementation(), ec); + } + + /// Disable sends or receives on the socket. + /** + * This function is used to disable send operations, receive operations, or + * both. + * + * @param what Determines what types of operation will no longer be allowed. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * Shutting down the send side of the socket: + * @code + * asio::ip::tcp::socket socket(my_context); + * ... + * socket.shutdown(asio::ip::tcp::socket::shutdown_send); + * @endcode + */ + void shutdown(shutdown_type what) + { + asio::error_code ec; + impl_.get_service().shutdown(impl_.get_implementation(), what, ec); + asio::detail::throw_error(ec, "shutdown"); + } + + /// Disable sends or receives on the socket. + /** + * This function is used to disable send operations, receive operations, or + * both. + * + * @param what Determines what types of operation will no longer be allowed. + * + * @param ec Set to indicate what error occurred, if any. + * + * @par Example + * Shutting down the send side of the socket: + * @code + * asio::ip::tcp::socket socket(my_context); + * ... + * asio::error_code ec; + * socket.shutdown(asio::ip::tcp::socket::shutdown_send, ec); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + ASIO_SYNC_OP_VOID shutdown(shutdown_type what, + asio::error_code& ec) + { + impl_.get_service().shutdown(impl_.get_implementation(), what, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Wait for the socket to become ready to read, ready to write, or to have + /// pending error conditions. + /** + * This function is used to perform a blocking wait for a socket to enter + * a ready to read, write or error condition state. + * + * @param w Specifies the desired socket state. + * + * @par Example + * Waiting for a socket to become readable. + * @code + * asio::ip::tcp::socket socket(my_context); + * ... + * socket.wait(asio::ip::tcp::socket::wait_read); + * @endcode + */ + void wait(wait_type w) + { + asio::error_code ec; + impl_.get_service().wait(impl_.get_implementation(), w, ec); + asio::detail::throw_error(ec, "wait"); + } + + /// Wait for the socket to become ready to read, ready to write, or to have + /// pending error conditions. + /** + * This function is used to perform a blocking wait for a socket to enter + * a ready to read, write or error condition state. + * + * @param w Specifies the desired socket state. + * + * @param ec Set to indicate what error occurred, if any. + * + * @par Example + * Waiting for a socket to become readable. + * @code + * asio::ip::tcp::socket socket(my_context); + * ... + * asio::error_code ec; + * socket.wait(asio::ip::tcp::socket::wait_read, ec); + * @endcode + */ + ASIO_SYNC_OP_VOID wait(wait_type w, asio::error_code& ec) + { + impl_.get_service().wait(impl_.get_implementation(), w, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Asynchronously wait for the socket to become ready to read, ready to + /// write, or to have pending error conditions. + /** + * This function is used to perform an asynchronous wait for a socket to enter + * a ready to read, write or error condition state. + * + * @param w Specifies the desired socket state. + * + * @param handler The handler to be called when the wait operation completes. + * Copies will be made of the handler as required. The function signature of + * the handler must be: + * @code void handler( + * const asio::error_code& error // Result of operation + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * @code + * void wait_handler(const asio::error_code& error) + * { + * if (!error) + * { + * // Wait succeeded. + * } + * } + * + * ... + * + * asio::ip::tcp::socket socket(my_context); + * ... + * socket.async_wait(asio::ip::tcp::socket::wait_read, wait_handler); + * @endcode + */ + template < + ASIO_COMPLETION_TOKEN_FOR(void (asio::error_code)) + WaitHandler ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(executor_type)> + ASIO_INITFN_AUTO_RESULT_TYPE(WaitHandler, + void (asio::error_code)) + async_wait(wait_type w, + ASIO_MOVE_ARG(WaitHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_wait(this), handler, w); + } + +protected: + /// Protected destructor to prevent deletion through this type. + /** + * This function destroys the socket, cancelling any outstanding asynchronous + * operations associated with the socket as if by calling @c cancel. + */ + ~basic_socket() + { + } + +#if defined(ASIO_WINDOWS_RUNTIME) + detail::io_object_impl< + detail::null_socket_service, Executor> impl_; +#elif defined(ASIO_HAS_IOCP) + detail::io_object_impl< + detail::win_iocp_socket_service, Executor> impl_; +#else + detail::io_object_impl< + detail::reactive_socket_service, Executor> impl_; +#endif + +private: + // Disallow copying and assignment. + basic_socket(const basic_socket&) ASIO_DELETED; + basic_socket& operator=(const basic_socket&) ASIO_DELETED; + + class initiate_async_connect + { + public: + typedef Executor executor_type; + + explicit initiate_async_connect(basic_socket* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(ConnectHandler) handler, + const endpoint_type& peer_endpoint, + const asio::error_code& open_ec) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a ConnectHandler. + ASIO_CONNECT_HANDLER_CHECK(ConnectHandler, handler) type_check; + + if (open_ec) + { + asio::post(self_->impl_.get_executor(), + asio::detail::bind_handler( + ASIO_MOVE_CAST(ConnectHandler)(handler), open_ec)); + } + else + { + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_connect( + self_->impl_.get_implementation(), peer_endpoint, + handler2.value, self_->impl_.get_executor()); + } + } + + private: + basic_socket* self_; + }; + + class initiate_async_wait + { + public: + typedef Executor executor_type; + + explicit initiate_async_wait(basic_socket* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(WaitHandler) handler, wait_type w) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a WaitHandler. + ASIO_WAIT_HANDLER_CHECK(WaitHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_wait( + self_->impl_.get_implementation(), w, + handler2.value, self_->impl_.get_executor()); + } + + private: + basic_socket* self_; + }; +}; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_BASIC_SOCKET_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_socket_acceptor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_socket_acceptor.hpp new file mode 100644 index 000000000..89a83f30b --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_socket_acceptor.hpp @@ -0,0 +1,2501 @@ +// +// basic_socket_acceptor.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BASIC_SOCKET_ACCEPTOR_HPP +#define ASIO_BASIC_SOCKET_ACCEPTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/any_io_executor.hpp" +#include "asio/basic_socket.hpp" +#include "asio/detail/handler_type_requirements.hpp" +#include "asio/detail/io_object_impl.hpp" +#include "asio/detail/non_const_lvalue.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/error.hpp" +#include "asio/execution_context.hpp" +#include "asio/socket_base.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) +# include "asio/detail/null_socket_service.hpp" +#elif defined(ASIO_HAS_IOCP) +# include "asio/detail/win_iocp_socket_service.hpp" +#else +# include "asio/detail/reactive_socket_service.hpp" +#endif + +#if defined(ASIO_HAS_MOVE) +# include +#endif // defined(ASIO_HAS_MOVE) + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if !defined(ASIO_BASIC_SOCKET_ACCEPTOR_FWD_DECL) +#define ASIO_BASIC_SOCKET_ACCEPTOR_FWD_DECL + +// Forward declaration with defaulted arguments. +template +class basic_socket_acceptor; + +#endif // !defined(ASIO_BASIC_SOCKET_ACCEPTOR_FWD_DECL) + +/// Provides the ability to accept new connections. +/** + * The basic_socket_acceptor class template is used for accepting new socket + * connections. + * + * @par Thread Safety + * @e Distinct @e objects: Safe.@n + * @e Shared @e objects: Unsafe. + * + * @par Example + * Opening a socket acceptor with the SO_REUSEADDR option enabled: + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * asio::ip::tcp::endpoint endpoint(asio::ip::tcp::v4(), port); + * acceptor.open(endpoint.protocol()); + * acceptor.set_option(asio::ip::tcp::acceptor::reuse_address(true)); + * acceptor.bind(endpoint); + * acceptor.listen(); + * @endcode + */ +template +class basic_socket_acceptor + : public socket_base +{ +public: + /// The type of the executor associated with the object. + typedef Executor executor_type; + + /// Rebinds the acceptor type to another executor. + template + struct rebind_executor + { + /// The socket type when rebound to the specified executor. + typedef basic_socket_acceptor other; + }; + + /// The native representation of an acceptor. +#if defined(GENERATING_DOCUMENTATION) + typedef implementation_defined native_handle_type; +#elif defined(ASIO_WINDOWS_RUNTIME) + typedef typename detail::null_socket_service< + Protocol>::native_handle_type native_handle_type; +#elif defined(ASIO_HAS_IOCP) + typedef typename detail::win_iocp_socket_service< + Protocol>::native_handle_type native_handle_type; +#else + typedef typename detail::reactive_socket_service< + Protocol>::native_handle_type native_handle_type; +#endif + + /// The protocol type. + typedef Protocol protocol_type; + + /// The endpoint type. + typedef typename Protocol::endpoint endpoint_type; + + /// Construct an acceptor without opening it. + /** + * This constructor creates an acceptor without opening it to listen for new + * connections. The open() function must be called before the acceptor can + * accept new socket connections. + * + * @param ex The I/O executor that the acceptor will use, by default, to + * dispatch handlers for any asynchronous operations performed on the + * acceptor. + */ + explicit basic_socket_acceptor(const executor_type& ex) + : impl_(ex) + { + } + + /// Construct an acceptor without opening it. + /** + * This constructor creates an acceptor without opening it to listen for new + * connections. The open() function must be called before the acceptor can + * accept new socket connections. + * + * @param context An execution context which provides the I/O executor that + * the acceptor will use, by default, to dispatch handlers for any + * asynchronous operations performed on the acceptor. + */ + template + explicit basic_socket_acceptor(ExecutionContext& context, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + } + + /// Construct an open acceptor. + /** + * This constructor creates an acceptor and automatically opens it. + * + * @param ex The I/O executor that the acceptor will use, by default, to + * dispatch handlers for any asynchronous operations performed on the + * acceptor. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @throws asio::system_error Thrown on failure. + */ + basic_socket_acceptor(const executor_type& ex, const protocol_type& protocol) + : impl_(ex) + { + asio::error_code ec; + impl_.get_service().open(impl_.get_implementation(), protocol, ec); + asio::detail::throw_error(ec, "open"); + } + + /// Construct an open acceptor. + /** + * This constructor creates an acceptor and automatically opens it. + * + * @param context An execution context which provides the I/O executor that + * the acceptor will use, by default, to dispatch handlers for any + * asynchronous operations performed on the acceptor. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_socket_acceptor(ExecutionContext& context, + const protocol_type& protocol, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + asio::error_code ec; + impl_.get_service().open(impl_.get_implementation(), protocol, ec); + asio::detail::throw_error(ec, "open"); + } + + /// Construct an acceptor opened on the given endpoint. + /** + * This constructor creates an acceptor and automatically opens it to listen + * for new connections on the specified endpoint. + * + * @param ex The I/O executor that the acceptor will use, by default, to + * dispatch handlers for any asynchronous operations performed on the + * acceptor. + * + * @param endpoint An endpoint on the local machine on which the acceptor + * will listen for new connections. + * + * @param reuse_addr Whether the constructor should set the socket option + * socket_base::reuse_address. + * + * @throws asio::system_error Thrown on failure. + * + * @note This constructor is equivalent to the following code: + * @code + * basic_socket_acceptor acceptor(my_context); + * acceptor.open(endpoint.protocol()); + * if (reuse_addr) + * acceptor.set_option(socket_base::reuse_address(true)); + * acceptor.bind(endpoint); + * acceptor.listen(); + * @endcode + */ + basic_socket_acceptor(const executor_type& ex, + const endpoint_type& endpoint, bool reuse_addr = true) + : impl_(ex) + { + asio::error_code ec; + const protocol_type protocol = endpoint.protocol(); + impl_.get_service().open(impl_.get_implementation(), protocol, ec); + asio::detail::throw_error(ec, "open"); + if (reuse_addr) + { + impl_.get_service().set_option(impl_.get_implementation(), + socket_base::reuse_address(true), ec); + asio::detail::throw_error(ec, "set_option"); + } + impl_.get_service().bind(impl_.get_implementation(), endpoint, ec); + asio::detail::throw_error(ec, "bind"); + impl_.get_service().listen(impl_.get_implementation(), + socket_base::max_listen_connections, ec); + asio::detail::throw_error(ec, "listen"); + } + + /// Construct an acceptor opened on the given endpoint. + /** + * This constructor creates an acceptor and automatically opens it to listen + * for new connections on the specified endpoint. + * + * @param context An execution context which provides the I/O executor that + * the acceptor will use, by default, to dispatch handlers for any + * asynchronous operations performed on the acceptor. + * + * @param endpoint An endpoint on the local machine on which the acceptor + * will listen for new connections. + * + * @param reuse_addr Whether the constructor should set the socket option + * socket_base::reuse_address. + * + * @throws asio::system_error Thrown on failure. + * + * @note This constructor is equivalent to the following code: + * @code + * basic_socket_acceptor acceptor(my_context); + * acceptor.open(endpoint.protocol()); + * if (reuse_addr) + * acceptor.set_option(socket_base::reuse_address(true)); + * acceptor.bind(endpoint); + * acceptor.listen(); + * @endcode + */ + template + basic_socket_acceptor(ExecutionContext& context, + const endpoint_type& endpoint, bool reuse_addr = true, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + asio::error_code ec; + const protocol_type protocol = endpoint.protocol(); + impl_.get_service().open(impl_.get_implementation(), protocol, ec); + asio::detail::throw_error(ec, "open"); + if (reuse_addr) + { + impl_.get_service().set_option(impl_.get_implementation(), + socket_base::reuse_address(true), ec); + asio::detail::throw_error(ec, "set_option"); + } + impl_.get_service().bind(impl_.get_implementation(), endpoint, ec); + asio::detail::throw_error(ec, "bind"); + impl_.get_service().listen(impl_.get_implementation(), + socket_base::max_listen_connections, ec); + asio::detail::throw_error(ec, "listen"); + } + + /// Construct a basic_socket_acceptor on an existing native acceptor. + /** + * This constructor creates an acceptor object to hold an existing native + * acceptor. + * + * @param ex The I/O executor that the acceptor will use, by default, to + * dispatch handlers for any asynchronous operations performed on the + * acceptor. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @param native_acceptor A native acceptor. + * + * @throws asio::system_error Thrown on failure. + */ + basic_socket_acceptor(const executor_type& ex, + const protocol_type& protocol, const native_handle_type& native_acceptor) + : impl_(ex) + { + asio::error_code ec; + impl_.get_service().assign(impl_.get_implementation(), + protocol, native_acceptor, ec); + asio::detail::throw_error(ec, "assign"); + } + + /// Construct a basic_socket_acceptor on an existing native acceptor. + /** + * This constructor creates an acceptor object to hold an existing native + * acceptor. + * + * @param context An execution context which provides the I/O executor that + * the acceptor will use, by default, to dispatch handlers for any + * asynchronous operations performed on the acceptor. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @param native_acceptor A native acceptor. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_socket_acceptor(ExecutionContext& context, + const protocol_type& protocol, const native_handle_type& native_acceptor, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + asio::error_code ec; + impl_.get_service().assign(impl_.get_implementation(), + protocol, native_acceptor, ec); + asio::detail::throw_error(ec, "assign"); + } + +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + /// Move-construct a basic_socket_acceptor from another. + /** + * This constructor moves an acceptor from one object to another. + * + * @param other The other basic_socket_acceptor object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_socket_acceptor(const executor_type&) + * constructor. + */ + basic_socket_acceptor(basic_socket_acceptor&& other) ASIO_NOEXCEPT + : impl_(std::move(other.impl_)) + { + } + + /// Move-assign a basic_socket_acceptor from another. + /** + * This assignment operator moves an acceptor from one object to another. + * + * @param other The other basic_socket_acceptor object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_socket_acceptor(const executor_type&) + * constructor. + */ + basic_socket_acceptor& operator=(basic_socket_acceptor&& other) + { + impl_ = std::move(other.impl_); + return *this; + } + + // All socket acceptors have access to each other's implementations. + template + friend class basic_socket_acceptor; + + /// Move-construct a basic_socket_acceptor from an acceptor of another + /// protocol type. + /** + * This constructor moves an acceptor from one object to another. + * + * @param other The other basic_socket_acceptor object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_socket_acceptor(const executor_type&) + * constructor. + */ + template + basic_socket_acceptor(basic_socket_acceptor&& other, + typename enable_if< + is_convertible::value + && is_convertible::value + >::type* = 0) + : impl_(std::move(other.impl_)) + { + } + + /// Move-assign a basic_socket_acceptor from an acceptor of another protocol + /// type. + /** + * This assignment operator moves an acceptor from one object to another. + * + * @param other The other basic_socket_acceptor object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_socket_acceptor(const executor_type&) + * constructor. + */ + template + typename enable_if< + is_convertible::value + && is_convertible::value, + basic_socket_acceptor& + >::type operator=(basic_socket_acceptor&& other) + { + basic_socket_acceptor tmp(std::move(other)); + impl_ = std::move(tmp.impl_); + return *this; + } +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + /// Destroys the acceptor. + /** + * This function destroys the acceptor, cancelling any outstanding + * asynchronous operations associated with the acceptor as if by calling + * @c cancel. + */ + ~basic_socket_acceptor() + { + } + + /// Get the executor associated with the object. + executor_type get_executor() ASIO_NOEXCEPT + { + return impl_.get_executor(); + } + + /// Open the acceptor using the specified protocol. + /** + * This function opens the socket acceptor so that it will use the specified + * protocol. + * + * @param protocol An object specifying which protocol is to be used. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * acceptor.open(asio::ip::tcp::v4()); + * @endcode + */ + void open(const protocol_type& protocol = protocol_type()) + { + asio::error_code ec; + impl_.get_service().open(impl_.get_implementation(), protocol, ec); + asio::detail::throw_error(ec, "open"); + } + + /// Open the acceptor using the specified protocol. + /** + * This function opens the socket acceptor so that it will use the specified + * protocol. + * + * @param protocol An object specifying which protocol is to be used. + * + * @param ec Set to indicate what error occurred, if any. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * asio::error_code ec; + * acceptor.open(asio::ip::tcp::v4(), ec); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + ASIO_SYNC_OP_VOID open(const protocol_type& protocol, + asio::error_code& ec) + { + impl_.get_service().open(impl_.get_implementation(), protocol, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Assigns an existing native acceptor to the acceptor. + /* + * This function opens the acceptor to hold an existing native acceptor. + * + * @param protocol An object specifying which protocol is to be used. + * + * @param native_acceptor A native acceptor. + * + * @throws asio::system_error Thrown on failure. + */ + void assign(const protocol_type& protocol, + const native_handle_type& native_acceptor) + { + asio::error_code ec; + impl_.get_service().assign(impl_.get_implementation(), + protocol, native_acceptor, ec); + asio::detail::throw_error(ec, "assign"); + } + + /// Assigns an existing native acceptor to the acceptor. + /* + * This function opens the acceptor to hold an existing native acceptor. + * + * @param protocol An object specifying which protocol is to be used. + * + * @param native_acceptor A native acceptor. + * + * @param ec Set to indicate what error occurred, if any. + */ + ASIO_SYNC_OP_VOID assign(const protocol_type& protocol, + const native_handle_type& native_acceptor, asio::error_code& ec) + { + impl_.get_service().assign(impl_.get_implementation(), + protocol, native_acceptor, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Determine whether the acceptor is open. + bool is_open() const + { + return impl_.get_service().is_open(impl_.get_implementation()); + } + + /// Bind the acceptor to the given local endpoint. + /** + * This function binds the socket acceptor to the specified endpoint on the + * local machine. + * + * @param endpoint An endpoint on the local machine to which the socket + * acceptor will be bound. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * asio::ip::tcp::endpoint endpoint(asio::ip::tcp::v4(), 12345); + * acceptor.open(endpoint.protocol()); + * acceptor.bind(endpoint); + * @endcode + */ + void bind(const endpoint_type& endpoint) + { + asio::error_code ec; + impl_.get_service().bind(impl_.get_implementation(), endpoint, ec); + asio::detail::throw_error(ec, "bind"); + } + + /// Bind the acceptor to the given local endpoint. + /** + * This function binds the socket acceptor to the specified endpoint on the + * local machine. + * + * @param endpoint An endpoint on the local machine to which the socket + * acceptor will be bound. + * + * @param ec Set to indicate what error occurred, if any. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * asio::ip::tcp::endpoint endpoint(asio::ip::tcp::v4(), 12345); + * acceptor.open(endpoint.protocol()); + * asio::error_code ec; + * acceptor.bind(endpoint, ec); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + ASIO_SYNC_OP_VOID bind(const endpoint_type& endpoint, + asio::error_code& ec) + { + impl_.get_service().bind(impl_.get_implementation(), endpoint, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Place the acceptor into the state where it will listen for new + /// connections. + /** + * This function puts the socket acceptor into the state where it may accept + * new connections. + * + * @param backlog The maximum length of the queue of pending connections. + * + * @throws asio::system_error Thrown on failure. + */ + void listen(int backlog = socket_base::max_listen_connections) + { + asio::error_code ec; + impl_.get_service().listen(impl_.get_implementation(), backlog, ec); + asio::detail::throw_error(ec, "listen"); + } + + /// Place the acceptor into the state where it will listen for new + /// connections. + /** + * This function puts the socket acceptor into the state where it may accept + * new connections. + * + * @param backlog The maximum length of the queue of pending connections. + * + * @param ec Set to indicate what error occurred, if any. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::error_code ec; + * acceptor.listen(asio::socket_base::max_listen_connections, ec); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + ASIO_SYNC_OP_VOID listen(int backlog, asio::error_code& ec) + { + impl_.get_service().listen(impl_.get_implementation(), backlog, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Close the acceptor. + /** + * This function is used to close the acceptor. Any asynchronous accept + * operations will be cancelled immediately. + * + * A subsequent call to open() is required before the acceptor can again be + * used to again perform socket accept operations. + * + * @throws asio::system_error Thrown on failure. + */ + void close() + { + asio::error_code ec; + impl_.get_service().close(impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "close"); + } + + /// Close the acceptor. + /** + * This function is used to close the acceptor. Any asynchronous accept + * operations will be cancelled immediately. + * + * A subsequent call to open() is required before the acceptor can again be + * used to again perform socket accept operations. + * + * @param ec Set to indicate what error occurred, if any. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::error_code ec; + * acceptor.close(ec); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + ASIO_SYNC_OP_VOID close(asio::error_code& ec) + { + impl_.get_service().close(impl_.get_implementation(), ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Release ownership of the underlying native acceptor. + /** + * This function causes all outstanding asynchronous accept operations to + * finish immediately, and the handlers for cancelled operations will be + * passed the asio::error::operation_aborted error. Ownership of the + * native acceptor is then transferred to the caller. + * + * @throws asio::system_error Thrown on failure. + * + * @note This function is unsupported on Windows versions prior to Windows + * 8.1, and will fail with asio::error::operation_not_supported on + * these platforms. + */ +#if defined(ASIO_MSVC) && (ASIO_MSVC >= 1400) \ + && (!defined(_WIN32_WINNT) || _WIN32_WINNT < 0x0603) + __declspec(deprecated("This function always fails with " + "operation_not_supported when used on Windows versions " + "prior to Windows 8.1.")) +#endif + native_handle_type release() + { + asio::error_code ec; + native_handle_type s = impl_.get_service().release( + impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "release"); + return s; + } + + /// Release ownership of the underlying native acceptor. + /** + * This function causes all outstanding asynchronous accept operations to + * finish immediately, and the handlers for cancelled operations will be + * passed the asio::error::operation_aborted error. Ownership of the + * native acceptor is then transferred to the caller. + * + * @param ec Set to indicate what error occurred, if any. + * + * @note This function is unsupported on Windows versions prior to Windows + * 8.1, and will fail with asio::error::operation_not_supported on + * these platforms. + */ +#if defined(ASIO_MSVC) && (ASIO_MSVC >= 1400) \ + && (!defined(_WIN32_WINNT) || _WIN32_WINNT < 0x0603) + __declspec(deprecated("This function always fails with " + "operation_not_supported when used on Windows versions " + "prior to Windows 8.1.")) +#endif + native_handle_type release(asio::error_code& ec) + { + return impl_.get_service().release(impl_.get_implementation(), ec); + } + + /// Get the native acceptor representation. + /** + * This function may be used to obtain the underlying representation of the + * acceptor. This is intended to allow access to native acceptor functionality + * that is not otherwise provided. + */ + native_handle_type native_handle() + { + return impl_.get_service().native_handle(impl_.get_implementation()); + } + + /// Cancel all asynchronous operations associated with the acceptor. + /** + * This function causes all outstanding asynchronous connect, send and receive + * operations to finish immediately, and the handlers for cancelled operations + * will be passed the asio::error::operation_aborted error. + * + * @throws asio::system_error Thrown on failure. + */ + void cancel() + { + asio::error_code ec; + impl_.get_service().cancel(impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "cancel"); + } + + /// Cancel all asynchronous operations associated with the acceptor. + /** + * This function causes all outstanding asynchronous connect, send and receive + * operations to finish immediately, and the handlers for cancelled operations + * will be passed the asio::error::operation_aborted error. + * + * @param ec Set to indicate what error occurred, if any. + */ + ASIO_SYNC_OP_VOID cancel(asio::error_code& ec) + { + impl_.get_service().cancel(impl_.get_implementation(), ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Set an option on the acceptor. + /** + * This function is used to set an option on the acceptor. + * + * @param option The new option value to be set on the acceptor. + * + * @throws asio::system_error Thrown on failure. + * + * @sa SettableSocketOption @n + * asio::socket_base::reuse_address + * asio::socket_base::enable_connection_aborted + * + * @par Example + * Setting the SOL_SOCKET/SO_REUSEADDR option: + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::acceptor::reuse_address option(true); + * acceptor.set_option(option); + * @endcode + */ + template + void set_option(const SettableSocketOption& option) + { + asio::error_code ec; + impl_.get_service().set_option(impl_.get_implementation(), option, ec); + asio::detail::throw_error(ec, "set_option"); + } + + /// Set an option on the acceptor. + /** + * This function is used to set an option on the acceptor. + * + * @param option The new option value to be set on the acceptor. + * + * @param ec Set to indicate what error occurred, if any. + * + * @sa SettableSocketOption @n + * asio::socket_base::reuse_address + * asio::socket_base::enable_connection_aborted + * + * @par Example + * Setting the SOL_SOCKET/SO_REUSEADDR option: + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::acceptor::reuse_address option(true); + * asio::error_code ec; + * acceptor.set_option(option, ec); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + template + ASIO_SYNC_OP_VOID set_option(const SettableSocketOption& option, + asio::error_code& ec) + { + impl_.get_service().set_option(impl_.get_implementation(), option, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Get an option from the acceptor. + /** + * This function is used to get the current value of an option on the + * acceptor. + * + * @param option The option value to be obtained from the acceptor. + * + * @throws asio::system_error Thrown on failure. + * + * @sa GettableSocketOption @n + * asio::socket_base::reuse_address + * + * @par Example + * Getting the value of the SOL_SOCKET/SO_REUSEADDR option: + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::acceptor::reuse_address option; + * acceptor.get_option(option); + * bool is_set = option.get(); + * @endcode + */ + template + void get_option(GettableSocketOption& option) const + { + asio::error_code ec; + impl_.get_service().get_option(impl_.get_implementation(), option, ec); + asio::detail::throw_error(ec, "get_option"); + } + + /// Get an option from the acceptor. + /** + * This function is used to get the current value of an option on the + * acceptor. + * + * @param option The option value to be obtained from the acceptor. + * + * @param ec Set to indicate what error occurred, if any. + * + * @sa GettableSocketOption @n + * asio::socket_base::reuse_address + * + * @par Example + * Getting the value of the SOL_SOCKET/SO_REUSEADDR option: + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::acceptor::reuse_address option; + * asio::error_code ec; + * acceptor.get_option(option, ec); + * if (ec) + * { + * // An error occurred. + * } + * bool is_set = option.get(); + * @endcode + */ + template + ASIO_SYNC_OP_VOID get_option(GettableSocketOption& option, + asio::error_code& ec) const + { + impl_.get_service().get_option(impl_.get_implementation(), option, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Perform an IO control command on the acceptor. + /** + * This function is used to execute an IO control command on the acceptor. + * + * @param command The IO control command to be performed on the acceptor. + * + * @throws asio::system_error Thrown on failure. + * + * @sa IoControlCommand @n + * asio::socket_base::non_blocking_io + * + * @par Example + * Getting the number of bytes ready to read: + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::acceptor::non_blocking_io command(true); + * socket.io_control(command); + * @endcode + */ + template + void io_control(IoControlCommand& command) + { + asio::error_code ec; + impl_.get_service().io_control(impl_.get_implementation(), command, ec); + asio::detail::throw_error(ec, "io_control"); + } + + /// Perform an IO control command on the acceptor. + /** + * This function is used to execute an IO control command on the acceptor. + * + * @param command The IO control command to be performed on the acceptor. + * + * @param ec Set to indicate what error occurred, if any. + * + * @sa IoControlCommand @n + * asio::socket_base::non_blocking_io + * + * @par Example + * Getting the number of bytes ready to read: + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::acceptor::non_blocking_io command(true); + * asio::error_code ec; + * socket.io_control(command, ec); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + template + ASIO_SYNC_OP_VOID io_control(IoControlCommand& command, + asio::error_code& ec) + { + impl_.get_service().io_control(impl_.get_implementation(), command, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Gets the non-blocking mode of the acceptor. + /** + * @returns @c true if the acceptor's synchronous operations will fail with + * asio::error::would_block if they are unable to perform the requested + * operation immediately. If @c false, synchronous operations will block + * until complete. + * + * @note The non-blocking mode has no effect on the behaviour of asynchronous + * operations. Asynchronous operations will never fail with the error + * asio::error::would_block. + */ + bool non_blocking() const + { + return impl_.get_service().non_blocking(impl_.get_implementation()); + } + + /// Sets the non-blocking mode of the acceptor. + /** + * @param mode If @c true, the acceptor's synchronous operations will fail + * with asio::error::would_block if they are unable to perform the + * requested operation immediately. If @c false, synchronous operations will + * block until complete. + * + * @throws asio::system_error Thrown on failure. + * + * @note The non-blocking mode has no effect on the behaviour of asynchronous + * operations. Asynchronous operations will never fail with the error + * asio::error::would_block. + */ + void non_blocking(bool mode) + { + asio::error_code ec; + impl_.get_service().non_blocking(impl_.get_implementation(), mode, ec); + asio::detail::throw_error(ec, "non_blocking"); + } + + /// Sets the non-blocking mode of the acceptor. + /** + * @param mode If @c true, the acceptor's synchronous operations will fail + * with asio::error::would_block if they are unable to perform the + * requested operation immediately. If @c false, synchronous operations will + * block until complete. + * + * @param ec Set to indicate what error occurred, if any. + * + * @note The non-blocking mode has no effect on the behaviour of asynchronous + * operations. Asynchronous operations will never fail with the error + * asio::error::would_block. + */ + ASIO_SYNC_OP_VOID non_blocking( + bool mode, asio::error_code& ec) + { + impl_.get_service().non_blocking(impl_.get_implementation(), mode, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Gets the non-blocking mode of the native acceptor implementation. + /** + * This function is used to retrieve the non-blocking mode of the underlying + * native acceptor. This mode has no effect on the behaviour of the acceptor + * object's synchronous operations. + * + * @returns @c true if the underlying acceptor is in non-blocking mode and + * direct system calls may fail with asio::error::would_block (or the + * equivalent system error). + * + * @note The current non-blocking mode is cached by the acceptor object. + * Consequently, the return value may be incorrect if the non-blocking mode + * was set directly on the native acceptor. + */ + bool native_non_blocking() const + { + return impl_.get_service().native_non_blocking(impl_.get_implementation()); + } + + /// Sets the non-blocking mode of the native acceptor implementation. + /** + * This function is used to modify the non-blocking mode of the underlying + * native acceptor. It has no effect on the behaviour of the acceptor object's + * synchronous operations. + * + * @param mode If @c true, the underlying acceptor is put into non-blocking + * mode and direct system calls may fail with asio::error::would_block + * (or the equivalent system error). + * + * @throws asio::system_error Thrown on failure. If the @c mode is + * @c false, but the current value of @c non_blocking() is @c true, this + * function fails with asio::error::invalid_argument, as the + * combination does not make sense. + */ + void native_non_blocking(bool mode) + { + asio::error_code ec; + impl_.get_service().native_non_blocking( + impl_.get_implementation(), mode, ec); + asio::detail::throw_error(ec, "native_non_blocking"); + } + + /// Sets the non-blocking mode of the native acceptor implementation. + /** + * This function is used to modify the non-blocking mode of the underlying + * native acceptor. It has no effect on the behaviour of the acceptor object's + * synchronous operations. + * + * @param mode If @c true, the underlying acceptor is put into non-blocking + * mode and direct system calls may fail with asio::error::would_block + * (or the equivalent system error). + * + * @param ec Set to indicate what error occurred, if any. If the @c mode is + * @c false, but the current value of @c non_blocking() is @c true, this + * function fails with asio::error::invalid_argument, as the + * combination does not make sense. + */ + ASIO_SYNC_OP_VOID native_non_blocking( + bool mode, asio::error_code& ec) + { + impl_.get_service().native_non_blocking( + impl_.get_implementation(), mode, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Get the local endpoint of the acceptor. + /** + * This function is used to obtain the locally bound endpoint of the acceptor. + * + * @returns An object that represents the local endpoint of the acceptor. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::endpoint endpoint = acceptor.local_endpoint(); + * @endcode + */ + endpoint_type local_endpoint() const + { + asio::error_code ec; + endpoint_type ep = impl_.get_service().local_endpoint( + impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "local_endpoint"); + return ep; + } + + /// Get the local endpoint of the acceptor. + /** + * This function is used to obtain the locally bound endpoint of the acceptor. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns An object that represents the local endpoint of the acceptor. + * Returns a default-constructed endpoint object if an error occurred and the + * error handler did not throw an exception. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::error_code ec; + * asio::ip::tcp::endpoint endpoint = acceptor.local_endpoint(ec); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + endpoint_type local_endpoint(asio::error_code& ec) const + { + return impl_.get_service().local_endpoint(impl_.get_implementation(), ec); + } + + /// Wait for the acceptor to become ready to read, ready to write, or to have + /// pending error conditions. + /** + * This function is used to perform a blocking wait for an acceptor to enter + * a ready to read, write or error condition state. + * + * @param w Specifies the desired acceptor state. + * + * @par Example + * Waiting for an acceptor to become readable. + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * acceptor.wait(asio::ip::tcp::acceptor::wait_read); + * @endcode + */ + void wait(wait_type w) + { + asio::error_code ec; + impl_.get_service().wait(impl_.get_implementation(), w, ec); + asio::detail::throw_error(ec, "wait"); + } + + /// Wait for the acceptor to become ready to read, ready to write, or to have + /// pending error conditions. + /** + * This function is used to perform a blocking wait for an acceptor to enter + * a ready to read, write or error condition state. + * + * @param w Specifies the desired acceptor state. + * + * @param ec Set to indicate what error occurred, if any. + * + * @par Example + * Waiting for an acceptor to become readable. + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::error_code ec; + * acceptor.wait(asio::ip::tcp::acceptor::wait_read, ec); + * @endcode + */ + ASIO_SYNC_OP_VOID wait(wait_type w, asio::error_code& ec) + { + impl_.get_service().wait(impl_.get_implementation(), w, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Asynchronously wait for the acceptor to become ready to read, ready to + /// write, or to have pending error conditions. + /** + * This function is used to perform an asynchronous wait for an acceptor to + * enter a ready to read, write or error condition state. + * + * @param w Specifies the desired acceptor state. + * + * @param handler The handler to be called when the wait operation completes. + * Copies will be made of the handler as required. The function signature of + * the handler must be: + * @code void handler( + * const asio::error_code& error // Result of operation + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * @code + * void wait_handler(const asio::error_code& error) + * { + * if (!error) + * { + * // Wait succeeded. + * } + * } + * + * ... + * + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * acceptor.async_wait( + * asio::ip::tcp::acceptor::wait_read, + * wait_handler); + * @endcode + */ + template < + ASIO_COMPLETION_TOKEN_FOR(void (asio::error_code)) + WaitHandler ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(executor_type)> + ASIO_INITFN_AUTO_RESULT_TYPE(WaitHandler, + void (asio::error_code)) + async_wait(wait_type w, + ASIO_MOVE_ARG(WaitHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_wait(this), handler, w); + } + +#if !defined(ASIO_NO_EXTENSIONS) + /// Accept a new connection. + /** + * This function is used to accept a new connection from a peer into the + * given socket. The function call will block until a new connection has been + * accepted successfully or an error occurs. + * + * @param peer The socket into which the new connection will be accepted. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::socket socket(my_context); + * acceptor.accept(socket); + * @endcode + */ + template + void accept(basic_socket& peer, + typename enable_if< + is_convertible::value + >::type* = 0) + { + asio::error_code ec; + impl_.get_service().accept(impl_.get_implementation(), + peer, static_cast(0), ec); + asio::detail::throw_error(ec, "accept"); + } + + /// Accept a new connection. + /** + * This function is used to accept a new connection from a peer into the + * given socket. The function call will block until a new connection has been + * accepted successfully or an error occurs. + * + * @param peer The socket into which the new connection will be accepted. + * + * @param ec Set to indicate what error occurred, if any. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::socket socket(my_context); + * asio::error_code ec; + * acceptor.accept(socket, ec); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + template + ASIO_SYNC_OP_VOID accept( + basic_socket& peer, asio::error_code& ec, + typename enable_if< + is_convertible::value + >::type* = 0) + { + impl_.get_service().accept(impl_.get_implementation(), + peer, static_cast(0), ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Start an asynchronous accept. + /** + * This function is used to asynchronously accept a new connection into a + * socket. The function call always returns immediately. + * + * @param peer The socket into which the new connection will be accepted. + * Ownership of the peer object is retained by the caller, which must + * guarantee that it is valid until the handler is called. + * + * @param handler The handler to be called when the accept operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error // Result of operation. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * @code + * void accept_handler(const asio::error_code& error) + * { + * if (!error) + * { + * // Accept succeeded. + * } + * } + * + * ... + * + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::socket socket(my_context); + * acceptor.async_accept(socket, accept_handler); + * @endcode + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(AcceptHandler, + void (asio::error_code)) + async_accept(basic_socket& peer, + ASIO_MOVE_ARG(AcceptHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type), + typename enable_if< + is_convertible::value + >::type* = 0) + { + return async_initiate( + initiate_async_accept(this), handler, + &peer, static_cast(0)); + } + + /// Accept a new connection and obtain the endpoint of the peer + /** + * This function is used to accept a new connection from a peer into the + * given socket, and additionally provide the endpoint of the remote peer. + * The function call will block until a new connection has been accepted + * successfully or an error occurs. + * + * @param peer The socket into which the new connection will be accepted. + * + * @param peer_endpoint An endpoint object which will receive the endpoint of + * the remote peer. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::socket socket(my_context); + * asio::ip::tcp::endpoint endpoint; + * acceptor.accept(socket, endpoint); + * @endcode + */ + template + void accept(basic_socket& peer, + endpoint_type& peer_endpoint) + { + asio::error_code ec; + impl_.get_service().accept(impl_.get_implementation(), + peer, &peer_endpoint, ec); + asio::detail::throw_error(ec, "accept"); + } + + /// Accept a new connection and obtain the endpoint of the peer + /** + * This function is used to accept a new connection from a peer into the + * given socket, and additionally provide the endpoint of the remote peer. + * The function call will block until a new connection has been accepted + * successfully or an error occurs. + * + * @param peer The socket into which the new connection will be accepted. + * + * @param peer_endpoint An endpoint object which will receive the endpoint of + * the remote peer. + * + * @param ec Set to indicate what error occurred, if any. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::socket socket(my_context); + * asio::ip::tcp::endpoint endpoint; + * asio::error_code ec; + * acceptor.accept(socket, endpoint, ec); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + template + ASIO_SYNC_OP_VOID accept(basic_socket& peer, + endpoint_type& peer_endpoint, asio::error_code& ec) + { + impl_.get_service().accept( + impl_.get_implementation(), peer, &peer_endpoint, ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Start an asynchronous accept. + /** + * This function is used to asynchronously accept a new connection into a + * socket, and additionally obtain the endpoint of the remote peer. The + * function call always returns immediately. + * + * @param peer The socket into which the new connection will be accepted. + * Ownership of the peer object is retained by the caller, which must + * guarantee that it is valid until the handler is called. + * + * @param peer_endpoint An endpoint object into which the endpoint of the + * remote peer will be written. Ownership of the peer_endpoint object is + * retained by the caller, which must guarantee that it is valid until the + * handler is called. + * + * @param handler The handler to be called when the accept operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error // Result of operation. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(AcceptHandler, + void (asio::error_code)) + async_accept(basic_socket& peer, + endpoint_type& peer_endpoint, + ASIO_MOVE_ARG(AcceptHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_accept(this), handler, &peer, &peer_endpoint); + } +#endif // !defined(ASIO_NO_EXTENSIONS) + +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + /// Accept a new connection. + /** + * This function is used to accept a new connection from a peer. The function + * call will block until a new connection has been accepted successfully or + * an error occurs. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @returns A socket object representing the newly accepted connection. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::socket socket(acceptor.accept()); + * @endcode + */ + typename Protocol::socket::template rebind_executor::other + accept() + { + asio::error_code ec; + typename Protocol::socket::template rebind_executor< + executor_type>::other peer(impl_.get_executor()); + impl_.get_service().accept(impl_.get_implementation(), peer, 0, ec); + asio::detail::throw_error(ec, "accept"); + return peer; + } + + /// Accept a new connection. + /** + * This function is used to accept a new connection from a peer. The function + * call will block until a new connection has been accepted successfully or + * an error occurs. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns On success, a socket object representing the newly accepted + * connection. On error, a socket object where is_open() is false. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::socket socket(acceptor.accept(ec)); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + typename Protocol::socket::template rebind_executor::other + accept(asio::error_code& ec) + { + typename Protocol::socket::template rebind_executor< + executor_type>::other peer(impl_.get_executor()); + impl_.get_service().accept(impl_.get_implementation(), peer, 0, ec); + return peer; + } + + /// Start an asynchronous accept. + /** + * This function is used to asynchronously accept a new connection. The + * function call always returns immediately. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @param handler The handler to be called when the accept operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * // Result of operation. + * const asio::error_code& error, + * // On success, the newly accepted socket. + * typename Protocol::socket::template + * rebind_executor::other peer + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * @code + * void accept_handler(const asio::error_code& error, + * asio::ip::tcp::socket peer) + * { + * if (!error) + * { + * // Accept succeeded. + * } + * } + * + * ... + * + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * acceptor.async_accept(accept_handler); + * @endcode + */ + template < + ASIO_COMPLETION_TOKEN_FOR(void (asio::error_code, + typename Protocol::socket::template rebind_executor< + executor_type>::other)) MoveAcceptHandler + ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(executor_type)> + ASIO_INITFN_AUTO_RESULT_TYPE(MoveAcceptHandler, + void (asio::error_code, + typename Protocol::socket::template + rebind_executor::other)) + async_accept( + ASIO_MOVE_ARG(MoveAcceptHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate::other)>( + initiate_async_move_accept(this), handler, + impl_.get_executor(), static_cast(0), + static_cast::other*>(0)); + } + + /// Accept a new connection. + /** + * This function is used to accept a new connection from a peer. The function + * call will block until a new connection has been accepted successfully or + * an error occurs. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @param ex The I/O executor object to be used for the newly + * accepted socket. + * + * @returns A socket object representing the newly accepted connection. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::socket socket(acceptor.accept()); + * @endcode + */ + template + typename Protocol::socket::template rebind_executor::other + accept(const Executor1& ex, + typename enable_if< + is_executor::value + || execution::is_executor::value + >::type* = 0) + { + asio::error_code ec; + typename Protocol::socket::template + rebind_executor::other peer(ex); + impl_.get_service().accept(impl_.get_implementation(), peer, 0, ec); + asio::detail::throw_error(ec, "accept"); + return peer; + } + + /// Accept a new connection. + /** + * This function is used to accept a new connection from a peer. The function + * call will block until a new connection has been accepted successfully or + * an error occurs. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @param context The I/O execution context object to be used for the newly + * accepted socket. + * + * @returns A socket object representing the newly accepted connection. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::socket socket(acceptor.accept()); + * @endcode + */ + template + typename Protocol::socket::template rebind_executor< + typename ExecutionContext::executor_type>::other + accept(ExecutionContext& context, + typename enable_if< + is_convertible::value + >::type* = 0) + { + asio::error_code ec; + typename Protocol::socket::template rebind_executor< + typename ExecutionContext::executor_type>::other peer(context); + impl_.get_service().accept(impl_.get_implementation(), peer, 0, ec); + asio::detail::throw_error(ec, "accept"); + return peer; + } + + /// Accept a new connection. + /** + * This function is used to accept a new connection from a peer. The function + * call will block until a new connection has been accepted successfully or + * an error occurs. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @param ex The I/O executor object to be used for the newly accepted + * socket. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns On success, a socket object representing the newly accepted + * connection. On error, a socket object where is_open() is false. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::socket socket(acceptor.accept(my_context2, ec)); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + template + typename Protocol::socket::template rebind_executor::other + accept(const Executor1& ex, asio::error_code& ec, + typename enable_if< + is_executor::value + || execution::is_executor::value + >::type* = 0) + { + typename Protocol::socket::template + rebind_executor::other peer(ex); + impl_.get_service().accept(impl_.get_implementation(), peer, 0, ec); + return peer; + } + + /// Accept a new connection. + /** + * This function is used to accept a new connection from a peer. The function + * call will block until a new connection has been accepted successfully or + * an error occurs. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @param context The I/O execution context object to be used for the newly + * accepted socket. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns On success, a socket object representing the newly accepted + * connection. On error, a socket object where is_open() is false. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::socket socket(acceptor.accept(my_context2, ec)); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + template + typename Protocol::socket::template rebind_executor< + typename ExecutionContext::executor_type>::other + accept(ExecutionContext& context, asio::error_code& ec, + typename enable_if< + is_convertible::value + >::type* = 0) + { + typename Protocol::socket::template rebind_executor< + typename ExecutionContext::executor_type>::other peer(context); + impl_.get_service().accept(impl_.get_implementation(), peer, 0, ec); + return peer; + } + + /// Start an asynchronous accept. + /** + * This function is used to asynchronously accept a new connection. The + * function call always returns immediately. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @param ex The I/O executor object to be used for the newly accepted + * socket. + * + * @param handler The handler to be called when the accept operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * typename Protocol::socket::template rebind_executor< + * Executor1>::other peer // On success, the newly accepted socket. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * @code + * void accept_handler(const asio::error_code& error, + * asio::ip::tcp::socket peer) + * { + * if (!error) + * { + * // Accept succeeded. + * } + * } + * + * ... + * + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * acceptor.async_accept(my_context2, accept_handler); + * @endcode + */ + template ::other)) MoveAcceptHandler + ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(executor_type)> + ASIO_INITFN_AUTO_RESULT_TYPE(MoveAcceptHandler, + void (asio::error_code, + typename Protocol::socket::template rebind_executor< + Executor1>::other)) + async_accept(const Executor1& ex, + ASIO_MOVE_ARG(MoveAcceptHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type), + typename enable_if< + is_executor::value + || execution::is_executor::value + >::type* = 0) + { + typedef typename Protocol::socket::template rebind_executor< + Executor1>::other other_socket_type; + + return async_initiate( + initiate_async_move_accept(this), handler, + ex, static_cast(0), + static_cast(0)); + } + + /// Start an asynchronous accept. + /** + * This function is used to asynchronously accept a new connection. The + * function call always returns immediately. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @param context The I/O execution context object to be used for the newly + * accepted socket. + * + * @param handler The handler to be called when the accept operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * typename Protocol::socket::template rebind_executor< + * typename ExecutionContext::executor_type>::other peer + * // On success, the newly accepted socket. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * @code + * void accept_handler(const asio::error_code& error, + * asio::ip::tcp::socket peer) + * { + * if (!error) + * { + * // Accept succeeded. + * } + * } + * + * ... + * + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * acceptor.async_accept(my_context2, accept_handler); + * @endcode + */ + template ::other)) MoveAcceptHandler + ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(executor_type)> + ASIO_INITFN_AUTO_RESULT_TYPE(MoveAcceptHandler, + void (asio::error_code, + typename Protocol::socket::template rebind_executor< + typename ExecutionContext::executor_type>::other)) + async_accept(ExecutionContext& context, + ASIO_MOVE_ARG(MoveAcceptHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type), + typename enable_if< + is_convertible::value + >::type* = 0) + { + typedef typename Protocol::socket::template rebind_executor< + typename ExecutionContext::executor_type>::other other_socket_type; + + return async_initiate( + initiate_async_move_accept(this), handler, + context.get_executor(), static_cast(0), + static_cast(0)); + } + + /// Accept a new connection. + /** + * This function is used to accept a new connection from a peer. The function + * call will block until a new connection has been accepted successfully or + * an error occurs. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @param peer_endpoint An endpoint object into which the endpoint of the + * remote peer will be written. + * + * @returns A socket object representing the newly accepted connection. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::endpoint endpoint; + * asio::ip::tcp::socket socket(acceptor.accept(endpoint)); + * @endcode + */ + typename Protocol::socket::template rebind_executor::other + accept(endpoint_type& peer_endpoint) + { + asio::error_code ec; + typename Protocol::socket::template rebind_executor< + executor_type>::other peer(impl_.get_executor()); + impl_.get_service().accept(impl_.get_implementation(), + peer, &peer_endpoint, ec); + asio::detail::throw_error(ec, "accept"); + return peer; + } + + /// Accept a new connection. + /** + * This function is used to accept a new connection from a peer. The function + * call will block until a new connection has been accepted successfully or + * an error occurs. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @param peer_endpoint An endpoint object into which the endpoint of the + * remote peer will be written. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns On success, a socket object representing the newly accepted + * connection. On error, a socket object where is_open() is false. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::endpoint endpoint; + * asio::ip::tcp::socket socket(acceptor.accept(endpoint, ec)); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + typename Protocol::socket::template rebind_executor::other + accept(endpoint_type& peer_endpoint, asio::error_code& ec) + { + typename Protocol::socket::template rebind_executor< + executor_type>::other peer(impl_.get_executor()); + impl_.get_service().accept(impl_.get_implementation(), + peer, &peer_endpoint, ec); + return peer; + } + + /// Start an asynchronous accept. + /** + * This function is used to asynchronously accept a new connection. The + * function call always returns immediately. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @param peer_endpoint An endpoint object into which the endpoint of the + * remote peer will be written. Ownership of the peer_endpoint object is + * retained by the caller, which must guarantee that it is valid until the + * handler is called. + * + * @param handler The handler to be called when the accept operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * // Result of operation. + * const asio::error_code& error, + * // On success, the newly accepted socket. + * typename Protocol::socket::template + * rebind_executor::other peer + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * @code + * void accept_handler(const asio::error_code& error, + * asio::ip::tcp::socket peer) + * { + * if (!error) + * { + * // Accept succeeded. + * } + * } + * + * ... + * + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::endpoint endpoint; + * acceptor.async_accept(endpoint, accept_handler); + * @endcode + */ + template < + ASIO_COMPLETION_TOKEN_FOR(void (asio::error_code, + typename Protocol::socket::template rebind_executor< + executor_type>::other)) MoveAcceptHandler + ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(executor_type)> + ASIO_INITFN_AUTO_RESULT_TYPE(MoveAcceptHandler, + void (asio::error_code, + typename Protocol::socket::template + rebind_executor::other)) + async_accept(endpoint_type& peer_endpoint, + ASIO_MOVE_ARG(MoveAcceptHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate::other)>( + initiate_async_move_accept(this), handler, + impl_.get_executor(), &peer_endpoint, + static_cast::other*>(0)); + } + + /// Accept a new connection. + /** + * This function is used to accept a new connection from a peer. The function + * call will block until a new connection has been accepted successfully or + * an error occurs. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @param ex The I/O executor object to be used for the newly accepted + * socket. + * + * @param peer_endpoint An endpoint object into which the endpoint of the + * remote peer will be written. + * + * @returns A socket object representing the newly accepted connection. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::endpoint endpoint; + * asio::ip::tcp::socket socket( + * acceptor.accept(my_context2, endpoint)); + * @endcode + */ + template + typename Protocol::socket::template rebind_executor::other + accept(const Executor1& ex, endpoint_type& peer_endpoint, + typename enable_if< + is_executor::value + || execution::is_executor::value + >::type* = 0) + { + asio::error_code ec; + typename Protocol::socket::template + rebind_executor::other peer(ex); + impl_.get_service().accept(impl_.get_implementation(), + peer, &peer_endpoint, ec); + asio::detail::throw_error(ec, "accept"); + return peer; + } + + /// Accept a new connection. + /** + * This function is used to accept a new connection from a peer. The function + * call will block until a new connection has been accepted successfully or + * an error occurs. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @param context The I/O execution context object to be used for the newly + * accepted socket. + * + * @param peer_endpoint An endpoint object into which the endpoint of the + * remote peer will be written. + * + * @returns A socket object representing the newly accepted connection. + * + * @throws asio::system_error Thrown on failure. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::endpoint endpoint; + * asio::ip::tcp::socket socket( + * acceptor.accept(my_context2, endpoint)); + * @endcode + */ + template + typename Protocol::socket::template rebind_executor< + typename ExecutionContext::executor_type>::other + accept(ExecutionContext& context, endpoint_type& peer_endpoint, + typename enable_if< + is_convertible::value + >::type* = 0) + { + asio::error_code ec; + typename Protocol::socket::template rebind_executor< + typename ExecutionContext::executor_type>::other peer(context); + impl_.get_service().accept(impl_.get_implementation(), + peer, &peer_endpoint, ec); + asio::detail::throw_error(ec, "accept"); + return peer; + } + + /// Accept a new connection. + /** + * This function is used to accept a new connection from a peer. The function + * call will block until a new connection has been accepted successfully or + * an error occurs. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @param ex The I/O executor object to be used for the newly accepted + * socket. + * + * @param peer_endpoint An endpoint object into which the endpoint of the + * remote peer will be written. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns On success, a socket object representing the newly accepted + * connection. On error, a socket object where is_open() is false. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::endpoint endpoint; + * asio::ip::tcp::socket socket( + * acceptor.accept(my_context2, endpoint, ec)); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + template + typename Protocol::socket::template rebind_executor::other + accept(const executor_type& ex, + endpoint_type& peer_endpoint, asio::error_code& ec, + typename enable_if< + is_executor::value + || execution::is_executor::value + >::type* = 0) + { + typename Protocol::socket::template + rebind_executor::other peer(ex); + impl_.get_service().accept(impl_.get_implementation(), + peer, &peer_endpoint, ec); + return peer; + } + + /// Accept a new connection. + /** + * This function is used to accept a new connection from a peer. The function + * call will block until a new connection has been accepted successfully or + * an error occurs. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @param context The I/O execution context object to be used for the newly + * accepted socket. + * + * @param peer_endpoint An endpoint object into which the endpoint of the + * remote peer will be written. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns On success, a socket object representing the newly accepted + * connection. On error, a socket object where is_open() is false. + * + * @par Example + * @code + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::endpoint endpoint; + * asio::ip::tcp::socket socket( + * acceptor.accept(my_context2, endpoint, ec)); + * if (ec) + * { + * // An error occurred. + * } + * @endcode + */ + template + typename Protocol::socket::template rebind_executor< + typename ExecutionContext::executor_type>::other + accept(ExecutionContext& context, + endpoint_type& peer_endpoint, asio::error_code& ec, + typename enable_if< + is_convertible::value + >::type* = 0) + { + typename Protocol::socket::template rebind_executor< + typename ExecutionContext::executor_type>::other peer(context); + impl_.get_service().accept(impl_.get_implementation(), + peer, &peer_endpoint, ec); + return peer; + } + + /// Start an asynchronous accept. + /** + * This function is used to asynchronously accept a new connection. The + * function call always returns immediately. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @param ex The I/O executor object to be used for the newly accepted + * socket. + * + * @param peer_endpoint An endpoint object into which the endpoint of the + * remote peer will be written. Ownership of the peer_endpoint object is + * retained by the caller, which must guarantee that it is valid until the + * handler is called. + * + * @param handler The handler to be called when the accept operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * typename Protocol::socket::template rebind_executor< + * Executor1>::other peer // On success, the newly accepted socket. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * @code + * void accept_handler(const asio::error_code& error, + * asio::ip::tcp::socket peer) + * { + * if (!error) + * { + * // Accept succeeded. + * } + * } + * + * ... + * + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::endpoint endpoint; + * acceptor.async_accept(my_context2, endpoint, accept_handler); + * @endcode + */ + template ::other)) MoveAcceptHandler + ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(executor_type)> + ASIO_INITFN_AUTO_RESULT_TYPE(MoveAcceptHandler, + void (asio::error_code, + typename Protocol::socket::template rebind_executor< + Executor1>::other)) + async_accept(const Executor1& ex, endpoint_type& peer_endpoint, + ASIO_MOVE_ARG(MoveAcceptHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type), + typename enable_if< + is_executor::value + || execution::is_executor::value + >::type* = 0) + { + typedef typename Protocol::socket::template rebind_executor< + Executor1>::other other_socket_type; + + return async_initiate( + initiate_async_move_accept(this), handler, + ex, &peer_endpoint, + static_cast(0)); + } + + /// Start an asynchronous accept. + /** + * This function is used to asynchronously accept a new connection. The + * function call always returns immediately. + * + * This overload requires that the Protocol template parameter satisfy the + * AcceptableProtocol type requirements. + * + * @param context The I/O execution context object to be used for the newly + * accepted socket. + * + * @param peer_endpoint An endpoint object into which the endpoint of the + * remote peer will be written. Ownership of the peer_endpoint object is + * retained by the caller, which must guarantee that it is valid until the + * handler is called. + * + * @param handler The handler to be called when the accept operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * typename Protocol::socket::template rebind_executor< + * typename ExecutionContext::executor_type>::other peer + * // On success, the newly accepted socket. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * @code + * void accept_handler(const asio::error_code& error, + * asio::ip::tcp::socket peer) + * { + * if (!error) + * { + * // Accept succeeded. + * } + * } + * + * ... + * + * asio::ip::tcp::acceptor acceptor(my_context); + * ... + * asio::ip::tcp::endpoint endpoint; + * acceptor.async_accept(my_context2, endpoint, accept_handler); + * @endcode + */ + template ::other)) MoveAcceptHandler + ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(executor_type)> + ASIO_INITFN_AUTO_RESULT_TYPE(MoveAcceptHandler, + void (asio::error_code, + typename Protocol::socket::template rebind_executor< + typename ExecutionContext::executor_type>::other)) + async_accept(ExecutionContext& context, + endpoint_type& peer_endpoint, + ASIO_MOVE_ARG(MoveAcceptHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type), + typename enable_if< + is_convertible::value + >::type* = 0) + { + typedef typename Protocol::socket::template rebind_executor< + typename ExecutionContext::executor_type>::other other_socket_type; + + return async_initiate( + initiate_async_move_accept(this), handler, + context.get_executor(), &peer_endpoint, + static_cast(0)); + } +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + +private: + // Disallow copying and assignment. + basic_socket_acceptor(const basic_socket_acceptor&) ASIO_DELETED; + basic_socket_acceptor& operator=( + const basic_socket_acceptor&) ASIO_DELETED; + + class initiate_async_wait + { + public: + typedef Executor executor_type; + + explicit initiate_async_wait(basic_socket_acceptor* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(WaitHandler) handler, wait_type w) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a WaitHandler. + ASIO_WAIT_HANDLER_CHECK(WaitHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_wait( + self_->impl_.get_implementation(), w, + handler2.value, self_->impl_.get_executor()); + } + + private: + basic_socket_acceptor* self_; + }; + + class initiate_async_accept + { + public: + typedef Executor executor_type; + + explicit initiate_async_accept(basic_socket_acceptor* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(AcceptHandler) handler, + basic_socket* peer, + endpoint_type* peer_endpoint) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a AcceptHandler. + ASIO_ACCEPT_HANDLER_CHECK(AcceptHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_accept( + self_->impl_.get_implementation(), *peer, peer_endpoint, + handler2.value, self_->impl_.get_executor()); + } + + private: + basic_socket_acceptor* self_; + }; + + class initiate_async_move_accept + { + public: + typedef Executor executor_type; + + explicit initiate_async_move_accept(basic_socket_acceptor* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(MoveAcceptHandler) handler, + const Executor1& peer_ex, endpoint_type* peer_endpoint, Socket*) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a MoveAcceptHandler. + ASIO_MOVE_ACCEPT_HANDLER_CHECK( + MoveAcceptHandler, handler, Socket) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_move_accept( + self_->impl_.get_implementation(), peer_ex, peer_endpoint, + handler2.value, self_->impl_.get_executor()); + } + + private: + basic_socket_acceptor* self_; + }; + +#if defined(ASIO_WINDOWS_RUNTIME) + detail::io_object_impl< + detail::null_socket_service, Executor> impl_; +#elif defined(ASIO_HAS_IOCP) + detail::io_object_impl< + detail::win_iocp_socket_service, Executor> impl_; +#else + detail::io_object_impl< + detail::reactive_socket_service, Executor> impl_; +#endif +}; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_BASIC_SOCKET_ACCEPTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_socket_iostream.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_socket_iostream.hpp new file mode 100644 index 000000000..abd35a6a5 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_socket_iostream.hpp @@ -0,0 +1,407 @@ +// +// basic_socket_iostream.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BASIC_SOCKET_IOSTREAM_HPP +#define ASIO_BASIC_SOCKET_IOSTREAM_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_NO_IOSTREAM) + +#include +#include +#include "asio/basic_socket_streambuf.hpp" + +#if !defined(ASIO_HAS_VARIADIC_TEMPLATES) + +# include "asio/detail/variadic_templates.hpp" + +// A macro that should expand to: +// template +// explicit basic_socket_iostream(T1 x1, ..., Tn xn) +// : std::basic_iostream( +// &this->detail::socket_iostream_base< +// Protocol, Clock, WaitTraits>::streambuf_) +// { +// if (rdbuf()->connect(x1, ..., xn) == 0) +// this->setstate(std::ios_base::failbit); +// } +// This macro should only persist within this file. + +# define ASIO_PRIVATE_CTR_DEF(n) \ + template \ + explicit basic_socket_iostream(ASIO_VARIADIC_BYVAL_PARAMS(n)) \ + : std::basic_iostream( \ + &this->detail::socket_iostream_base< \ + Protocol, Clock, WaitTraits>::streambuf_) \ + { \ + this->setf(std::ios_base::unitbuf); \ + if (rdbuf()->connect(ASIO_VARIADIC_BYVAL_ARGS(n)) == 0) \ + this->setstate(std::ios_base::failbit); \ + } \ + /**/ + +// A macro that should expand to: +// template +// void connect(T1 x1, ..., Tn xn) +// { +// if (rdbuf()->connect(x1, ..., xn) == 0) +// this->setstate(std::ios_base::failbit); +// } +// This macro should only persist within this file. + +# define ASIO_PRIVATE_CONNECT_DEF(n) \ + template \ + void connect(ASIO_VARIADIC_BYVAL_PARAMS(n)) \ + { \ + if (rdbuf()->connect(ASIO_VARIADIC_BYVAL_ARGS(n)) == 0) \ + this->setstate(std::ios_base::failbit); \ + } \ + /**/ + +#endif // !defined(ASIO_HAS_VARIADIC_TEMPLATES) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// A separate base class is used to ensure that the streambuf is initialised +// prior to the basic_socket_iostream's basic_iostream base class. +template +class socket_iostream_base +{ +protected: + socket_iostream_base() + { + } + +#if defined(ASIO_HAS_MOVE) + socket_iostream_base(socket_iostream_base&& other) + : streambuf_(std::move(other.streambuf_)) + { + } + + socket_iostream_base(basic_stream_socket s) + : streambuf_(std::move(s)) + { + } + + socket_iostream_base& operator=(socket_iostream_base&& other) + { + streambuf_ = std::move(other.streambuf_); + return *this; + } +#endif // defined(ASIO_HAS_MOVE) + + basic_socket_streambuf streambuf_; +}; + +} // namespace detail + +#if !defined(ASIO_BASIC_SOCKET_IOSTREAM_FWD_DECL) +#define ASIO_BASIC_SOCKET_IOSTREAM_FWD_DECL + +// Forward declaration with defaulted arguments. +template > +#else // defined(ASIO_HAS_BOOST_DATE_TIME) + // && defined(ASIO_USE_BOOST_DATE_TIME_FOR_SOCKET_IOSTREAM) + typename Clock = chrono::steady_clock, + typename WaitTraits = wait_traits > +#endif // defined(ASIO_HAS_BOOST_DATE_TIME) + // && defined(ASIO_USE_BOOST_DATE_TIME_FOR_SOCKET_IOSTREAM) +class basic_socket_iostream; + +#endif // !defined(ASIO_BASIC_SOCKET_IOSTREAM_FWD_DECL) + +/// Iostream interface for a socket. +#if defined(GENERATING_DOCUMENTATION) +template > +#else // defined(GENERATING_DOCUMENTATION) +template +#endif // defined(GENERATING_DOCUMENTATION) +class basic_socket_iostream + : private detail::socket_iostream_base, + public std::basic_iostream +{ +private: + // These typedefs are intended keep this class's implementation independent + // of whether it's using Boost.DateClock, Boost.Chrono or std::chrono. +#if defined(ASIO_HAS_BOOST_DATE_TIME) \ + && defined(ASIO_USE_BOOST_DATE_TIME_FOR_SOCKET_IOSTREAM) + typedef WaitTraits traits_helper; +#else // defined(ASIO_HAS_BOOST_DATE_TIME) + // && defined(ASIO_USE_BOOST_DATE_TIME_FOR_SOCKET_IOSTREAM) + typedef detail::chrono_time_traits traits_helper; +#endif // defined(ASIO_HAS_BOOST_DATE_TIME) + // && defined(ASIO_USE_BOOST_DATE_TIME_FOR_SOCKET_IOSTREAM) + +public: + /// The protocol type. + typedef Protocol protocol_type; + + /// The endpoint type. + typedef typename Protocol::endpoint endpoint_type; + + /// The clock type. + typedef Clock clock_type; + +#if defined(GENERATING_DOCUMENTATION) + /// (Deprecated: Use time_point.) The time type. + typedef typename WaitTraits::time_type time_type; + + /// The time type. + typedef typename WaitTraits::time_point time_point; + + /// (Deprecated: Use duration.) The duration type. + typedef typename WaitTraits::duration_type duration_type; + + /// The duration type. + typedef typename WaitTraits::duration duration; +#else +# if !defined(ASIO_NO_DEPRECATED) + typedef typename traits_helper::time_type time_type; + typedef typename traits_helper::duration_type duration_type; +# endif // !defined(ASIO_NO_DEPRECATED) + typedef typename traits_helper::time_type time_point; + typedef typename traits_helper::duration_type duration; +#endif + + /// Construct a basic_socket_iostream without establishing a connection. + basic_socket_iostream() + : std::basic_iostream( + &this->detail::socket_iostream_base< + Protocol, Clock, WaitTraits>::streambuf_) + { + this->setf(std::ios_base::unitbuf); + } + +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + /// Construct a basic_socket_iostream from the supplied socket. + explicit basic_socket_iostream(basic_stream_socket s) + : detail::socket_iostream_base< + Protocol, Clock, WaitTraits>(std::move(s)), + std::basic_iostream( + &this->detail::socket_iostream_base< + Protocol, Clock, WaitTraits>::streambuf_) + { + this->setf(std::ios_base::unitbuf); + } + +#if defined(ASIO_HAS_STD_IOSTREAM_MOVE) \ + || defined(GENERATING_DOCUMENTATION) + /// Move-construct a basic_socket_iostream from another. + basic_socket_iostream(basic_socket_iostream&& other) + : detail::socket_iostream_base< + Protocol, Clock, WaitTraits>(std::move(other)), + std::basic_iostream(std::move(other)) + { + this->set_rdbuf(&this->detail::socket_iostream_base< + Protocol, Clock, WaitTraits>::streambuf_); + } + + /// Move-assign a basic_socket_iostream from another. + basic_socket_iostream& operator=(basic_socket_iostream&& other) + { + std::basic_iostream::operator=(std::move(other)); + detail::socket_iostream_base< + Protocol, Clock, WaitTraits>::operator=(std::move(other)); + return *this; + } +#endif // defined(ASIO_HAS_STD_IOSTREAM_MOVE) + // || defined(GENERATING_DOCUMENTATION) +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + +#if defined(GENERATING_DOCUMENTATION) + /// Establish a connection to an endpoint corresponding to a resolver query. + /** + * This constructor automatically establishes a connection based on the + * supplied resolver query parameters. The arguments are used to construct + * a resolver query object. + */ + template + explicit basic_socket_iostream(T1 t1, ..., TN tn); +#elif defined(ASIO_HAS_VARIADIC_TEMPLATES) + template + explicit basic_socket_iostream(T... x) + : std::basic_iostream( + &this->detail::socket_iostream_base< + Protocol, Clock, WaitTraits>::streambuf_) + { + this->setf(std::ios_base::unitbuf); + if (rdbuf()->connect(x...) == 0) + this->setstate(std::ios_base::failbit); + } +#else + ASIO_VARIADIC_GENERATE(ASIO_PRIVATE_CTR_DEF) +#endif + +#if defined(GENERATING_DOCUMENTATION) + /// Establish a connection to an endpoint corresponding to a resolver query. + /** + * This function automatically establishes a connection based on the supplied + * resolver query parameters. The arguments are used to construct a resolver + * query object. + */ + template + void connect(T1 t1, ..., TN tn); +#elif defined(ASIO_HAS_VARIADIC_TEMPLATES) + template + void connect(T... x) + { + if (rdbuf()->connect(x...) == 0) + this->setstate(std::ios_base::failbit); + } +#else + ASIO_VARIADIC_GENERATE(ASIO_PRIVATE_CONNECT_DEF) +#endif + + /// Close the connection. + void close() + { + if (rdbuf()->close() == 0) + this->setstate(std::ios_base::failbit); + } + + /// Return a pointer to the underlying streambuf. + basic_socket_streambuf* rdbuf() const + { + return const_cast*>( + &this->detail::socket_iostream_base< + Protocol, Clock, WaitTraits>::streambuf_); + } + + /// Get a reference to the underlying socket. + basic_socket& socket() + { + return rdbuf()->socket(); + } + + /// Get the last error associated with the stream. + /** + * @return An \c error_code corresponding to the last error from the stream. + * + * @par Example + * To print the error associated with a failure to establish a connection: + * @code tcp::iostream s("www.boost.org", "http"); + * if (!s) + * { + * std::cout << "Error: " << s.error().message() << std::endl; + * } @endcode + */ + const asio::error_code& error() const + { + return rdbuf()->error(); + } + +#if !defined(ASIO_NO_DEPRECATED) + /// (Deprecated: Use expiry().) Get the stream's expiry time as an absolute + /// time. + /** + * @return An absolute time value representing the stream's expiry time. + */ + time_point expires_at() const + { + return rdbuf()->expires_at(); + } +#endif // !defined(ASIO_NO_DEPRECATED) + + /// Get the stream's expiry time as an absolute time. + /** + * @return An absolute time value representing the stream's expiry time. + */ + time_point expiry() const + { + return rdbuf()->expiry(); + } + + /// Set the stream's expiry time as an absolute time. + /** + * This function sets the expiry time associated with the stream. Stream + * operations performed after this time (where the operations cannot be + * completed using the internal buffers) will fail with the error + * asio::error::operation_aborted. + * + * @param expiry_time The expiry time to be used for the stream. + */ + void expires_at(const time_point& expiry_time) + { + rdbuf()->expires_at(expiry_time); + } + + /// Set the stream's expiry time relative to now. + /** + * This function sets the expiry time associated with the stream. Stream + * operations performed after this time (where the operations cannot be + * completed using the internal buffers) will fail with the error + * asio::error::operation_aborted. + * + * @param expiry_time The expiry time to be used for the timer. + */ + void expires_after(const duration& expiry_time) + { + rdbuf()->expires_after(expiry_time); + } + +#if !defined(ASIO_NO_DEPRECATED) + /// (Deprecated: Use expiry().) Get the stream's expiry time relative to now. + /** + * @return A relative time value representing the stream's expiry time. + */ + duration expires_from_now() const + { + return rdbuf()->expires_from_now(); + } + + /// (Deprecated: Use expires_after().) Set the stream's expiry time relative + /// to now. + /** + * This function sets the expiry time associated with the stream. Stream + * operations performed after this time (where the operations cannot be + * completed using the internal buffers) will fail with the error + * asio::error::operation_aborted. + * + * @param expiry_time The expiry time to be used for the timer. + */ + void expires_from_now(const duration& expiry_time) + { + rdbuf()->expires_from_now(expiry_time); + } +#endif // !defined(ASIO_NO_DEPRECATED) + +private: + // Disallow copying and assignment. + basic_socket_iostream(const basic_socket_iostream&) ASIO_DELETED; + basic_socket_iostream& operator=( + const basic_socket_iostream&) ASIO_DELETED; +}; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if !defined(ASIO_HAS_VARIADIC_TEMPLATES) +# undef ASIO_PRIVATE_CTR_DEF +# undef ASIO_PRIVATE_CONNECT_DEF +#endif // !defined(ASIO_HAS_VARIADIC_TEMPLATES) + +#endif // !defined(ASIO_NO_IOSTREAM) + +#endif // ASIO_BASIC_SOCKET_IOSTREAM_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_socket_streambuf.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_socket_streambuf.hpp new file mode 100644 index 000000000..2b5aad920 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_socket_streambuf.hpp @@ -0,0 +1,687 @@ +// +// basic_socket_streambuf.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BASIC_SOCKET_STREAMBUF_HPP +#define ASIO_BASIC_SOCKET_STREAMBUF_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_NO_IOSTREAM) + +#include +#include +#include "asio/basic_socket.hpp" +#include "asio/basic_stream_socket.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/io_context.hpp" + +#if defined(ASIO_HAS_BOOST_DATE_TIME) \ + && defined(ASIO_USE_BOOST_DATE_TIME_FOR_SOCKET_IOSTREAM) +# include "asio/detail/deadline_timer_service.hpp" +#else // defined(ASIO_HAS_BOOST_DATE_TIME) + // && defined(ASIO_USE_BOOST_DATE_TIME_FOR_SOCKET_IOSTREAM) +# include "asio/steady_timer.hpp" +#endif // defined(ASIO_HAS_BOOST_DATE_TIME) + // && defined(ASIO_USE_BOOST_DATE_TIME_FOR_SOCKET_IOSTREAM) + +#if !defined(ASIO_HAS_VARIADIC_TEMPLATES) + +# include "asio/detail/variadic_templates.hpp" + +// A macro that should expand to: +// template +// basic_socket_streambuf* connect(T1 x1, ..., Tn xn) +// { +// init_buffers(); +// typedef typename Protocol::resolver resolver_type; +// resolver_type resolver(socket().get_executor()); +// connect_to_endpoints( +// resolver.resolve(x1, ..., xn, ec_)); +// return !ec_ ? this : 0; +// } +// This macro should only persist within this file. + +# define ASIO_PRIVATE_CONNECT_DEF(n) \ + template \ + basic_socket_streambuf* connect(ASIO_VARIADIC_BYVAL_PARAMS(n)) \ + { \ + init_buffers(); \ + typedef typename Protocol::resolver resolver_type; \ + resolver_type resolver(socket().get_executor()); \ + connect_to_endpoints( \ + resolver.resolve(ASIO_VARIADIC_BYVAL_ARGS(n), ec_)); \ + return !ec_ ? this : 0; \ + } \ + /**/ + +#endif // !defined(ASIO_HAS_VARIADIC_TEMPLATES) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// A separate base class is used to ensure that the io_context member is +// initialised prior to the basic_socket_streambuf's basic_socket base class. +class socket_streambuf_io_context +{ +protected: + socket_streambuf_io_context(io_context* ctx) + : default_io_context_(ctx) + { + } + + shared_ptr default_io_context_; +}; + +// A separate base class is used to ensure that the dynamically allocated +// buffers are constructed prior to the basic_socket_streambuf's basic_socket +// base class. This makes moving the socket is the last potentially throwing +// step in the streambuf's move constructor, giving the constructor a strong +// exception safety guarantee. +class socket_streambuf_buffers +{ +protected: + socket_streambuf_buffers() + : get_buffer_(buffer_size), + put_buffer_(buffer_size) + { + } + + enum { buffer_size = 512 }; + std::vector get_buffer_; + std::vector put_buffer_; +}; + +} // namespace detail + +#if !defined(ASIO_BASIC_SOCKET_STREAMBUF_FWD_DECL) +#define ASIO_BASIC_SOCKET_STREAMBUF_FWD_DECL + +// Forward declaration with defaulted arguments. +template > +#else // defined(ASIO_HAS_BOOST_DATE_TIME) + // && defined(ASIO_USE_BOOST_DATE_TIME_FOR_SOCKET_IOSTREAM) + typename Clock = chrono::steady_clock, + typename WaitTraits = wait_traits > +#endif // defined(ASIO_HAS_BOOST_DATE_TIME) + // && defined(ASIO_USE_BOOST_DATE_TIME_FOR_SOCKET_IOSTREAM) +class basic_socket_streambuf; + +#endif // !defined(ASIO_BASIC_SOCKET_STREAMBUF_FWD_DECL) + +/// Iostream streambuf for a socket. +#if defined(GENERATING_DOCUMENTATION) +template > +#else // defined(GENERATING_DOCUMENTATION) +template +#endif // defined(GENERATING_DOCUMENTATION) +class basic_socket_streambuf + : public std::streambuf, + private detail::socket_streambuf_io_context, + private detail::socket_streambuf_buffers, +#if defined(ASIO_NO_DEPRECATED) || defined(GENERATING_DOCUMENTATION) + private basic_socket +#else // defined(ASIO_NO_DEPRECATED) || defined(GENERATING_DOCUMENTATION) + public basic_socket +#endif // defined(ASIO_NO_DEPRECATED) || defined(GENERATING_DOCUMENTATION) +{ +private: + // These typedefs are intended keep this class's implementation independent + // of whether it's using Boost.DateClock, Boost.Chrono or std::chrono. +#if defined(ASIO_HAS_BOOST_DATE_TIME) \ + && defined(ASIO_USE_BOOST_DATE_TIME_FOR_SOCKET_IOSTREAM) + typedef WaitTraits traits_helper; +#else // defined(ASIO_HAS_BOOST_DATE_TIME) + // && defined(ASIO_USE_BOOST_DATE_TIME_FOR_SOCKET_IOSTREAM) + typedef detail::chrono_time_traits traits_helper; +#endif // defined(ASIO_HAS_BOOST_DATE_TIME) + // && defined(ASIO_USE_BOOST_DATE_TIME_FOR_SOCKET_IOSTREAM) + +public: + /// The protocol type. + typedef Protocol protocol_type; + + /// The endpoint type. + typedef typename Protocol::endpoint endpoint_type; + + /// The clock type. + typedef Clock clock_type; + +#if defined(GENERATING_DOCUMENTATION) + /// (Deprecated: Use time_point.) The time type. + typedef typename WaitTraits::time_type time_type; + + /// The time type. + typedef typename WaitTraits::time_point time_point; + + /// (Deprecated: Use duration.) The duration type. + typedef typename WaitTraits::duration_type duration_type; + + /// The duration type. + typedef typename WaitTraits::duration duration; +#else +# if !defined(ASIO_NO_DEPRECATED) + typedef typename traits_helper::time_type time_type; + typedef typename traits_helper::duration_type duration_type; +# endif // !defined(ASIO_NO_DEPRECATED) + typedef typename traits_helper::time_type time_point; + typedef typename traits_helper::duration_type duration; +#endif + + /// Construct a basic_socket_streambuf without establishing a connection. + basic_socket_streambuf() + : detail::socket_streambuf_io_context(new io_context), + basic_socket(*default_io_context_), + expiry_time_(max_expiry_time()) + { + init_buffers(); + } + +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + /// Construct a basic_socket_streambuf from the supplied socket. + explicit basic_socket_streambuf(basic_stream_socket s) + : detail::socket_streambuf_io_context(0), + basic_socket(std::move(s)), + expiry_time_(max_expiry_time()) + { + init_buffers(); + } + + /// Move-construct a basic_socket_streambuf from another. + basic_socket_streambuf(basic_socket_streambuf&& other) + : detail::socket_streambuf_io_context(other), + basic_socket(std::move(other.socket())), + ec_(other.ec_), + expiry_time_(other.expiry_time_) + { + get_buffer_.swap(other.get_buffer_); + put_buffer_.swap(other.put_buffer_); + setg(other.eback(), other.gptr(), other.egptr()); + setp(other.pptr(), other.epptr()); + other.ec_ = asio::error_code(); + other.expiry_time_ = max_expiry_time(); + other.init_buffers(); + } + + /// Move-assign a basic_socket_streambuf from another. + basic_socket_streambuf& operator=(basic_socket_streambuf&& other) + { + this->close(); + socket() = std::move(other.socket()); + detail::socket_streambuf_io_context::operator=(other); + ec_ = other.ec_; + expiry_time_ = other.expiry_time_; + get_buffer_.swap(other.get_buffer_); + put_buffer_.swap(other.put_buffer_); + setg(other.eback(), other.gptr(), other.egptr()); + setp(other.pptr(), other.epptr()); + other.ec_ = asio::error_code(); + other.expiry_time_ = max_expiry_time(); + other.put_buffer_.resize(buffer_size); + other.init_buffers(); + return *this; + } +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + /// Destructor flushes buffered data. + virtual ~basic_socket_streambuf() + { + if (pptr() != pbase()) + overflow(traits_type::eof()); + } + + /// Establish a connection. + /** + * This function establishes a connection to the specified endpoint. + * + * @return \c this if a connection was successfully established, a null + * pointer otherwise. + */ + basic_socket_streambuf* connect(const endpoint_type& endpoint) + { + init_buffers(); + ec_ = asio::error_code(); + this->connect_to_endpoints(&endpoint, &endpoint + 1); + return !ec_ ? this : 0; + } + +#if defined(GENERATING_DOCUMENTATION) + /// Establish a connection. + /** + * This function automatically establishes a connection based on the supplied + * resolver query parameters. The arguments are used to construct a resolver + * query object. + * + * @return \c this if a connection was successfully established, a null + * pointer otherwise. + */ + template + basic_socket_streambuf* connect(T1 t1, ..., TN tn); +#elif defined(ASIO_HAS_VARIADIC_TEMPLATES) + template + basic_socket_streambuf* connect(T... x) + { + init_buffers(); + typedef typename Protocol::resolver resolver_type; + resolver_type resolver(socket().get_executor()); + connect_to_endpoints(resolver.resolve(x..., ec_)); + return !ec_ ? this : 0; + } +#else + ASIO_VARIADIC_GENERATE(ASIO_PRIVATE_CONNECT_DEF) +#endif + + /// Close the connection. + /** + * @return \c this if a connection was successfully established, a null + * pointer otherwise. + */ + basic_socket_streambuf* close() + { + sync(); + socket().close(ec_); + if (!ec_) + init_buffers(); + return !ec_ ? this : 0; + } + + /// Get a reference to the underlying socket. + basic_socket& socket() + { + return *this; + } + + /// Get the last error associated with the stream buffer. + /** + * @return An \c error_code corresponding to the last error from the stream + * buffer. + */ + const asio::error_code& error() const + { + return ec_; + } + +#if !defined(ASIO_NO_DEPRECATED) + /// (Deprecated: Use error().) Get the last error associated with the stream + /// buffer. + /** + * @return An \c error_code corresponding to the last error from the stream + * buffer. + */ + const asio::error_code& puberror() const + { + return error(); + } + + /// (Deprecated: Use expiry().) Get the stream buffer's expiry time as an + /// absolute time. + /** + * @return An absolute time value representing the stream buffer's expiry + * time. + */ + time_point expires_at() const + { + return expiry_time_; + } +#endif // !defined(ASIO_NO_DEPRECATED) + + /// Get the stream buffer's expiry time as an absolute time. + /** + * @return An absolute time value representing the stream buffer's expiry + * time. + */ + time_point expiry() const + { + return expiry_time_; + } + + /// Set the stream buffer's expiry time as an absolute time. + /** + * This function sets the expiry time associated with the stream. Stream + * operations performed after this time (where the operations cannot be + * completed using the internal buffers) will fail with the error + * asio::error::operation_aborted. + * + * @param expiry_time The expiry time to be used for the stream. + */ + void expires_at(const time_point& expiry_time) + { + expiry_time_ = expiry_time; + } + + /// Set the stream buffer's expiry time relative to now. + /** + * This function sets the expiry time associated with the stream. Stream + * operations performed after this time (where the operations cannot be + * completed using the internal buffers) will fail with the error + * asio::error::operation_aborted. + * + * @param expiry_time The expiry time to be used for the timer. + */ + void expires_after(const duration& expiry_time) + { + expiry_time_ = traits_helper::add(traits_helper::now(), expiry_time); + } + +#if !defined(ASIO_NO_DEPRECATED) + /// (Deprecated: Use expiry().) Get the stream buffer's expiry time relative + /// to now. + /** + * @return A relative time value representing the stream buffer's expiry time. + */ + duration expires_from_now() const + { + return traits_helper::subtract(expires_at(), traits_helper::now()); + } + + /// (Deprecated: Use expires_after().) Set the stream buffer's expiry time + /// relative to now. + /** + * This function sets the expiry time associated with the stream. Stream + * operations performed after this time (where the operations cannot be + * completed using the internal buffers) will fail with the error + * asio::error::operation_aborted. + * + * @param expiry_time The expiry time to be used for the timer. + */ + void expires_from_now(const duration& expiry_time) + { + expiry_time_ = traits_helper::add(traits_helper::now(), expiry_time); + } +#endif // !defined(ASIO_NO_DEPRECATED) + +protected: + int_type underflow() + { +#if defined(ASIO_WINDOWS_RUNTIME) + ec_ = asio::error::operation_not_supported; + return traits_type::eof(); +#else // defined(ASIO_WINDOWS_RUNTIME) + if (gptr() != egptr()) + return traits_type::eof(); + + for (;;) + { + // Check if we are past the expiry time. + if (traits_helper::less_than(expiry_time_, traits_helper::now())) + { + ec_ = asio::error::timed_out; + return traits_type::eof(); + } + + // Try to complete the operation without blocking. + if (!socket().native_non_blocking()) + socket().native_non_blocking(true, ec_); + detail::buffer_sequence_adapter + bufs(asio::buffer(get_buffer_) + putback_max); + detail::signed_size_type bytes = detail::socket_ops::recv( + socket().native_handle(), bufs.buffers(), bufs.count(), 0, ec_); + + // Check if operation succeeded. + if (bytes > 0) + { + setg(&get_buffer_[0], &get_buffer_[0] + putback_max, + &get_buffer_[0] + putback_max + bytes); + return traits_type::to_int_type(*gptr()); + } + + // Check for EOF. + if (bytes == 0) + { + ec_ = asio::error::eof; + return traits_type::eof(); + } + + // Operation failed. + if (ec_ != asio::error::would_block + && ec_ != asio::error::try_again) + return traits_type::eof(); + + // Wait for socket to become ready. + if (detail::socket_ops::poll_read( + socket().native_handle(), 0, timeout(), ec_) < 0) + return traits_type::eof(); + } +#endif // defined(ASIO_WINDOWS_RUNTIME) + } + + int_type overflow(int_type c) + { +#if defined(ASIO_WINDOWS_RUNTIME) + ec_ = asio::error::operation_not_supported; + return traits_type::eof(); +#else // defined(ASIO_WINDOWS_RUNTIME) + char_type ch = traits_type::to_char_type(c); + + // Determine what needs to be sent. + const_buffer output_buffer; + if (put_buffer_.empty()) + { + if (traits_type::eq_int_type(c, traits_type::eof())) + return traits_type::not_eof(c); // Nothing to do. + output_buffer = asio::buffer(&ch, sizeof(char_type)); + } + else + { + output_buffer = asio::buffer(pbase(), + (pptr() - pbase()) * sizeof(char_type)); + } + + while (output_buffer.size() > 0) + { + // Check if we are past the expiry time. + if (traits_helper::less_than(expiry_time_, traits_helper::now())) + { + ec_ = asio::error::timed_out; + return traits_type::eof(); + } + + // Try to complete the operation without blocking. + if (!socket().native_non_blocking()) + socket().native_non_blocking(true, ec_); + detail::buffer_sequence_adapter< + const_buffer, const_buffer> bufs(output_buffer); + detail::signed_size_type bytes = detail::socket_ops::send( + socket().native_handle(), bufs.buffers(), bufs.count(), 0, ec_); + + // Check if operation succeeded. + if (bytes > 0) + { + output_buffer += static_cast(bytes); + continue; + } + + // Operation failed. + if (ec_ != asio::error::would_block + && ec_ != asio::error::try_again) + return traits_type::eof(); + + // Wait for socket to become ready. + if (detail::socket_ops::poll_write( + socket().native_handle(), 0, timeout(), ec_) < 0) + return traits_type::eof(); + } + + if (!put_buffer_.empty()) + { + setp(&put_buffer_[0], &put_buffer_[0] + put_buffer_.size()); + + // If the new character is eof then our work here is done. + if (traits_type::eq_int_type(c, traits_type::eof())) + return traits_type::not_eof(c); + + // Add the new character to the output buffer. + *pptr() = ch; + pbump(1); + } + + return c; +#endif // defined(ASIO_WINDOWS_RUNTIME) + } + + int sync() + { + return overflow(traits_type::eof()); + } + + std::streambuf* setbuf(char_type* s, std::streamsize n) + { + if (pptr() == pbase() && s == 0 && n == 0) + { + put_buffer_.clear(); + setp(0, 0); + sync(); + return this; + } + + return 0; + } + +private: + // Disallow copying and assignment. + basic_socket_streambuf(const basic_socket_streambuf&) ASIO_DELETED; + basic_socket_streambuf& operator=( + const basic_socket_streambuf&) ASIO_DELETED; + + void init_buffers() + { + setg(&get_buffer_[0], + &get_buffer_[0] + putback_max, + &get_buffer_[0] + putback_max); + + if (put_buffer_.empty()) + setp(0, 0); + else + setp(&put_buffer_[0], &put_buffer_[0] + put_buffer_.size()); + } + + int timeout() const + { + int64_t msec = traits_helper::to_posix_duration( + traits_helper::subtract(expiry_time_, + traits_helper::now())).total_milliseconds(); + if (msec > (std::numeric_limits::max)()) + msec = (std::numeric_limits::max)(); + else if (msec < 0) + msec = 0; + return static_cast(msec); + } + + template + void connect_to_endpoints(const EndpointSequence& endpoints) + { + this->connect_to_endpoints(endpoints.begin(), endpoints.end()); + } + + template + void connect_to_endpoints(EndpointIterator begin, EndpointIterator end) + { +#if defined(ASIO_WINDOWS_RUNTIME) + ec_ = asio::error::operation_not_supported; +#else // defined(ASIO_WINDOWS_RUNTIME) + if (ec_) + return; + + ec_ = asio::error::not_found; + for (EndpointIterator i = begin; i != end; ++i) + { + // Check if we are past the expiry time. + if (traits_helper::less_than(expiry_time_, traits_helper::now())) + { + ec_ = asio::error::timed_out; + return; + } + + // Close and reopen the socket. + typename Protocol::endpoint ep(*i); + socket().close(ec_); + socket().open(ep.protocol(), ec_); + if (ec_) + continue; + + // Try to complete the operation without blocking. + if (!socket().native_non_blocking()) + socket().native_non_blocking(true, ec_); + detail::socket_ops::connect(socket().native_handle(), + ep.data(), ep.size(), ec_); + + // Check if operation succeeded. + if (!ec_) + return; + + // Operation failed. + if (ec_ != asio::error::in_progress + && ec_ != asio::error::would_block) + continue; + + // Wait for socket to become ready. + if (detail::socket_ops::poll_connect( + socket().native_handle(), timeout(), ec_) < 0) + continue; + + // Get the error code from the connect operation. + int connect_error = 0; + size_t connect_error_len = sizeof(connect_error); + if (detail::socket_ops::getsockopt(socket().native_handle(), 0, + SOL_SOCKET, SO_ERROR, &connect_error, &connect_error_len, ec_) + == detail::socket_error_retval) + return; + + // Check the result of the connect operation. + ec_ = asio::error_code(connect_error, + asio::error::get_system_category()); + if (!ec_) + return; + } +#endif // defined(ASIO_WINDOWS_RUNTIME) + } + + // Helper function to get the maximum expiry time. + static time_point max_expiry_time() + { +#if defined(ASIO_HAS_BOOST_DATE_TIME) \ + && defined(ASIO_USE_BOOST_DATE_TIME_FOR_SOCKET_IOSTREAM) + return boost::posix_time::pos_infin; +#else // defined(ASIO_HAS_BOOST_DATE_TIME) + // && defined(ASIO_USE_BOOST_DATE_TIME_FOR_SOCKET_IOSTREAM) + return (time_point::max)(); +#endif // defined(ASIO_HAS_BOOST_DATE_TIME) + // && defined(ASIO_USE_BOOST_DATE_TIME_FOR_SOCKET_IOSTREAM) + } + + enum { putback_max = 8 }; + asio::error_code ec_; + time_point expiry_time_; +}; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if !defined(ASIO_HAS_VARIADIC_TEMPLATES) +# undef ASIO_PRIVATE_CONNECT_DEF +#endif // !defined(ASIO_HAS_VARIADIC_TEMPLATES) + +#endif // !defined(ASIO_NO_IOSTREAM) + +#endif // ASIO_BASIC_SOCKET_STREAMBUF_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_stream_socket.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_stream_socket.hpp new file mode 100644 index 000000000..c31655ae0 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_stream_socket.hpp @@ -0,0 +1,1053 @@ +// +// basic_stream_socket.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BASIC_STREAM_SOCKET_HPP +#define ASIO_BASIC_STREAM_SOCKET_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include "asio/async_result.hpp" +#include "asio/basic_socket.hpp" +#include "asio/detail/handler_type_requirements.hpp" +#include "asio/detail/non_const_lvalue.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if !defined(ASIO_BASIC_STREAM_SOCKET_FWD_DECL) +#define ASIO_BASIC_STREAM_SOCKET_FWD_DECL + +// Forward declaration with defaulted arguments. +template +class basic_stream_socket; + +#endif // !defined(ASIO_BASIC_STREAM_SOCKET_FWD_DECL) + +/// Provides stream-oriented socket functionality. +/** + * The basic_stream_socket class template provides asynchronous and blocking + * stream-oriented socket functionality. + * + * @par Thread Safety + * @e Distinct @e objects: Safe.@n + * @e Shared @e objects: Unsafe. + * + * @par Concepts: + * AsyncReadStream, AsyncWriteStream, Stream, SyncReadStream, SyncWriteStream. + */ +template +class basic_stream_socket + : public basic_socket +{ +public: + /// The type of the executor associated with the object. + typedef Executor executor_type; + + /// Rebinds the socket type to another executor. + template + struct rebind_executor + { + /// The socket type when rebound to the specified executor. + typedef basic_stream_socket other; + }; + + /// The native representation of a socket. +#if defined(GENERATING_DOCUMENTATION) + typedef implementation_defined native_handle_type; +#else + typedef typename basic_socket::native_handle_type native_handle_type; +#endif + + /// The protocol type. + typedef Protocol protocol_type; + + /// The endpoint type. + typedef typename Protocol::endpoint endpoint_type; + + /// Construct a basic_stream_socket without opening it. + /** + * This constructor creates a stream socket without opening it. The socket + * needs to be opened and then connected or accepted before data can be sent + * or received on it. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + */ + explicit basic_stream_socket(const executor_type& ex) + : basic_socket(ex) + { + } + + /// Construct a basic_stream_socket without opening it. + /** + * This constructor creates a stream socket without opening it. The socket + * needs to be opened and then connected or accepted before data can be sent + * or received on it. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + */ + template + explicit basic_stream_socket(ExecutionContext& context, + typename enable_if< + is_convertible::value + >::type* = 0) + : basic_socket(context) + { + } + + /// Construct and open a basic_stream_socket. + /** + * This constructor creates and opens a stream socket. The socket needs to be + * connected or accepted before data can be sent or received on it. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @throws asio::system_error Thrown on failure. + */ + basic_stream_socket(const executor_type& ex, const protocol_type& protocol) + : basic_socket(ex, protocol) + { + } + + /// Construct and open a basic_stream_socket. + /** + * This constructor creates and opens a stream socket. The socket needs to be + * connected or accepted before data can be sent or received on it. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_stream_socket(ExecutionContext& context, const protocol_type& protocol, + typename enable_if< + is_convertible::value + >::type* = 0) + : basic_socket(context, protocol) + { + } + + /// Construct a basic_stream_socket, opening it and binding it to the given + /// local endpoint. + /** + * This constructor creates a stream socket and automatically opens it bound + * to the specified endpoint on the local machine. The protocol used is the + * protocol associated with the given endpoint. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + * + * @param endpoint An endpoint on the local machine to which the stream + * socket will be bound. + * + * @throws asio::system_error Thrown on failure. + */ + basic_stream_socket(const executor_type& ex, const endpoint_type& endpoint) + : basic_socket(ex, endpoint) + { + } + + /// Construct a basic_stream_socket, opening it and binding it to the given + /// local endpoint. + /** + * This constructor creates a stream socket and automatically opens it bound + * to the specified endpoint on the local machine. The protocol used is the + * protocol associated with the given endpoint. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + * + * @param endpoint An endpoint on the local machine to which the stream + * socket will be bound. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_stream_socket(ExecutionContext& context, const endpoint_type& endpoint, + typename enable_if< + is_convertible::value + >::type* = 0) + : basic_socket(context, endpoint) + { + } + + /// Construct a basic_stream_socket on an existing native socket. + /** + * This constructor creates a stream socket object to hold an existing native + * socket. + * + * @param ex The I/O executor that the socket will use, by default, to + * dispatch handlers for any asynchronous operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @param native_socket The new underlying socket implementation. + * + * @throws asio::system_error Thrown on failure. + */ + basic_stream_socket(const executor_type& ex, + const protocol_type& protocol, const native_handle_type& native_socket) + : basic_socket(ex, protocol, native_socket) + { + } + + /// Construct a basic_stream_socket on an existing native socket. + /** + * This constructor creates a stream socket object to hold an existing native + * socket. + * + * @param context An execution context which provides the I/O executor that + * the socket will use, by default, to dispatch handlers for any asynchronous + * operations performed on the socket. + * + * @param protocol An object specifying protocol parameters to be used. + * + * @param native_socket The new underlying socket implementation. + * + * @throws asio::system_error Thrown on failure. + */ + template + basic_stream_socket(ExecutionContext& context, + const protocol_type& protocol, const native_handle_type& native_socket, + typename enable_if< + is_convertible::value + >::type* = 0) + : basic_socket(context, protocol, native_socket) + { + } + +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + /// Move-construct a basic_stream_socket from another. + /** + * This constructor moves a stream socket from one object to another. + * + * @param other The other basic_stream_socket object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_stream_socket(const executor_type&) + * constructor. + */ + basic_stream_socket(basic_stream_socket&& other) ASIO_NOEXCEPT + : basic_socket(std::move(other)) + { + } + + /// Move-assign a basic_stream_socket from another. + /** + * This assignment operator moves a stream socket from one object to another. + * + * @param other The other basic_stream_socket object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_stream_socket(const executor_type&) + * constructor. + */ + basic_stream_socket& operator=(basic_stream_socket&& other) + { + basic_socket::operator=(std::move(other)); + return *this; + } + + /// Move-construct a basic_stream_socket from a socket of another protocol + /// type. + /** + * This constructor moves a stream socket from one object to another. + * + * @param other The other basic_stream_socket object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_stream_socket(const executor_type&) + * constructor. + */ + template + basic_stream_socket(basic_stream_socket&& other, + typename enable_if< + is_convertible::value + && is_convertible::value + >::type* = 0) + : basic_socket(std::move(other)) + { + } + + /// Move-assign a basic_stream_socket from a socket of another protocol type. + /** + * This assignment operator moves a stream socket from one object to another. + * + * @param other The other basic_stream_socket object from which the move + * will occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_stream_socket(const executor_type&) + * constructor. + */ + template + typename enable_if< + is_convertible::value + && is_convertible::value, + basic_stream_socket& + >::type operator=(basic_stream_socket&& other) + { + basic_socket::operator=(std::move(other)); + return *this; + } +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + /// Destroys the socket. + /** + * This function destroys the socket, cancelling any outstanding asynchronous + * operations associated with the socket as if by calling @c cancel. + */ + ~basic_stream_socket() + { + } + + /// Send some data on the socket. + /** + * This function is used to send data on the stream socket. The function + * call will block until one or more bytes of the data has been sent + * successfully, or an until error occurs. + * + * @param buffers One or more data buffers to be sent on the socket. + * + * @returns The number of bytes sent. + * + * @throws asio::system_error Thrown on failure. + * + * @note The send operation may not transmit all of the data to the peer. + * Consider using the @ref write function if you need to ensure that all data + * is written before the blocking operation completes. + * + * @par Example + * To send a single data buffer use the @ref buffer function as follows: + * @code + * socket.send(asio::buffer(data, size)); + * @endcode + * See the @ref buffer documentation for information on sending multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t send(const ConstBufferSequence& buffers) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().send( + this->impl_.get_implementation(), buffers, 0, ec); + asio::detail::throw_error(ec, "send"); + return s; + } + + /// Send some data on the socket. + /** + * This function is used to send data on the stream socket. The function + * call will block until one or more bytes of the data has been sent + * successfully, or an until error occurs. + * + * @param buffers One or more data buffers to be sent on the socket. + * + * @param flags Flags specifying how the send call is to be made. + * + * @returns The number of bytes sent. + * + * @throws asio::system_error Thrown on failure. + * + * @note The send operation may not transmit all of the data to the peer. + * Consider using the @ref write function if you need to ensure that all data + * is written before the blocking operation completes. + * + * @par Example + * To send a single data buffer use the @ref buffer function as follows: + * @code + * socket.send(asio::buffer(data, size), 0); + * @endcode + * See the @ref buffer documentation for information on sending multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t send(const ConstBufferSequence& buffers, + socket_base::message_flags flags) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().send( + this->impl_.get_implementation(), buffers, flags, ec); + asio::detail::throw_error(ec, "send"); + return s; + } + + /// Send some data on the socket. + /** + * This function is used to send data on the stream socket. The function + * call will block until one or more bytes of the data has been sent + * successfully, or an until error occurs. + * + * @param buffers One or more data buffers to be sent on the socket. + * + * @param flags Flags specifying how the send call is to be made. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns The number of bytes sent. Returns 0 if an error occurred. + * + * @note The send operation may not transmit all of the data to the peer. + * Consider using the @ref write function if you need to ensure that all data + * is written before the blocking operation completes. + */ + template + std::size_t send(const ConstBufferSequence& buffers, + socket_base::message_flags flags, asio::error_code& ec) + { + return this->impl_.get_service().send( + this->impl_.get_implementation(), buffers, flags, ec); + } + + /// Start an asynchronous send. + /** + * This function is used to asynchronously send data on the stream socket. + * The function call always returns immediately. + * + * @param buffers One or more data buffers to be sent on the socket. Although + * the buffers object may be copied as necessary, ownership of the underlying + * memory blocks is retained by the caller, which must guarantee that they + * remain valid until the handler is called. + * + * @param handler The handler to be called when the send operation completes. + * Copies will be made of the handler as required. The function signature of + * the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes sent. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note The send operation may not transmit all of the data to the peer. + * Consider using the @ref async_write function if you need to ensure that all + * data is written before the asynchronous operation completes. + * + * @par Example + * To send a single data buffer use the @ref buffer function as follows: + * @code + * socket.async_send(asio::buffer(data, size), handler); + * @endcode + * See the @ref buffer documentation for information on sending multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_send(const ConstBufferSequence& buffers, + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_send(this), handler, + buffers, socket_base::message_flags(0)); + } + + /// Start an asynchronous send. + /** + * This function is used to asynchronously send data on the stream socket. + * The function call always returns immediately. + * + * @param buffers One or more data buffers to be sent on the socket. Although + * the buffers object may be copied as necessary, ownership of the underlying + * memory blocks is retained by the caller, which must guarantee that they + * remain valid until the handler is called. + * + * @param flags Flags specifying how the send call is to be made. + * + * @param handler The handler to be called when the send operation completes. + * Copies will be made of the handler as required. The function signature of + * the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes sent. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note The send operation may not transmit all of the data to the peer. + * Consider using the @ref async_write function if you need to ensure that all + * data is written before the asynchronous operation completes. + * + * @par Example + * To send a single data buffer use the @ref buffer function as follows: + * @code + * socket.async_send(asio::buffer(data, size), 0, handler); + * @endcode + * See the @ref buffer documentation for information on sending multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_send(const ConstBufferSequence& buffers, + socket_base::message_flags flags, + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_send(this), handler, buffers, flags); + } + + /// Receive some data on the socket. + /** + * This function is used to receive data on the stream socket. The function + * call will block until one or more bytes of data has been received + * successfully, or until an error occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @returns The number of bytes received. + * + * @throws asio::system_error Thrown on failure. An error code of + * asio::error::eof indicates that the connection was closed by the + * peer. + * + * @note The receive operation may not receive all of the requested number of + * bytes. Consider using the @ref read function if you need to ensure that the + * requested amount of data is read before the blocking operation completes. + * + * @par Example + * To receive into a single data buffer use the @ref buffer function as + * follows: + * @code + * socket.receive(asio::buffer(data, size)); + * @endcode + * See the @ref buffer documentation for information on receiving into + * multiple buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t receive(const MutableBufferSequence& buffers) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().receive( + this->impl_.get_implementation(), buffers, 0, ec); + asio::detail::throw_error(ec, "receive"); + return s; + } + + /// Receive some data on the socket. + /** + * This function is used to receive data on the stream socket. The function + * call will block until one or more bytes of data has been received + * successfully, or until an error occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @param flags Flags specifying how the receive call is to be made. + * + * @returns The number of bytes received. + * + * @throws asio::system_error Thrown on failure. An error code of + * asio::error::eof indicates that the connection was closed by the + * peer. + * + * @note The receive operation may not receive all of the requested number of + * bytes. Consider using the @ref read function if you need to ensure that the + * requested amount of data is read before the blocking operation completes. + * + * @par Example + * To receive into a single data buffer use the @ref buffer function as + * follows: + * @code + * socket.receive(asio::buffer(data, size), 0); + * @endcode + * See the @ref buffer documentation for information on receiving into + * multiple buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t receive(const MutableBufferSequence& buffers, + socket_base::message_flags flags) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().receive( + this->impl_.get_implementation(), buffers, flags, ec); + asio::detail::throw_error(ec, "receive"); + return s; + } + + /// Receive some data on a connected socket. + /** + * This function is used to receive data on the stream socket. The function + * call will block until one or more bytes of data has been received + * successfully, or until an error occurs. + * + * @param buffers One or more buffers into which the data will be received. + * + * @param flags Flags specifying how the receive call is to be made. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns The number of bytes received. Returns 0 if an error occurred. + * + * @note The receive operation may not receive all of the requested number of + * bytes. Consider using the @ref read function if you need to ensure that the + * requested amount of data is read before the blocking operation completes. + */ + template + std::size_t receive(const MutableBufferSequence& buffers, + socket_base::message_flags flags, asio::error_code& ec) + { + return this->impl_.get_service().receive( + this->impl_.get_implementation(), buffers, flags, ec); + } + + /// Start an asynchronous receive. + /** + * This function is used to asynchronously receive data from the stream + * socket. The function call always returns immediately. + * + * @param buffers One or more buffers into which the data will be received. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param handler The handler to be called when the receive operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes received. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note The receive operation may not receive all of the requested number of + * bytes. Consider using the @ref async_read function if you need to ensure + * that the requested amount of data is received before the asynchronous + * operation completes. + * + * @par Example + * To receive into a single data buffer use the @ref buffer function as + * follows: + * @code + * socket.async_receive(asio::buffer(data, size), handler); + * @endcode + * See the @ref buffer documentation for information on receiving into + * multiple buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_receive(const MutableBufferSequence& buffers, + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_receive(this), handler, + buffers, socket_base::message_flags(0)); + } + + /// Start an asynchronous receive. + /** + * This function is used to asynchronously receive data from the stream + * socket. The function call always returns immediately. + * + * @param buffers One or more buffers into which the data will be received. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param flags Flags specifying how the receive call is to be made. + * + * @param handler The handler to be called when the receive operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes received. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note The receive operation may not receive all of the requested number of + * bytes. Consider using the @ref async_read function if you need to ensure + * that the requested amount of data is received before the asynchronous + * operation completes. + * + * @par Example + * To receive into a single data buffer use the @ref buffer function as + * follows: + * @code + * socket.async_receive(asio::buffer(data, size), 0, handler); + * @endcode + * See the @ref buffer documentation for information on receiving into + * multiple buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_receive(const MutableBufferSequence& buffers, + socket_base::message_flags flags, + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_receive(this), handler, buffers, flags); + } + + /// Write some data to the socket. + /** + * This function is used to write data to the stream socket. The function call + * will block until one or more bytes of the data has been written + * successfully, or until an error occurs. + * + * @param buffers One or more data buffers to be written to the socket. + * + * @returns The number of bytes written. + * + * @throws asio::system_error Thrown on failure. An error code of + * asio::error::eof indicates that the connection was closed by the + * peer. + * + * @note The write_some operation may not transmit all of the data to the + * peer. Consider using the @ref write function if you need to ensure that + * all data is written before the blocking operation completes. + * + * @par Example + * To write a single data buffer use the @ref buffer function as follows: + * @code + * socket.write_some(asio::buffer(data, size)); + * @endcode + * See the @ref buffer documentation for information on writing multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t write_some(const ConstBufferSequence& buffers) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().send( + this->impl_.get_implementation(), buffers, 0, ec); + asio::detail::throw_error(ec, "write_some"); + return s; + } + + /// Write some data to the socket. + /** + * This function is used to write data to the stream socket. The function call + * will block until one or more bytes of the data has been written + * successfully, or until an error occurs. + * + * @param buffers One or more data buffers to be written to the socket. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns The number of bytes written. Returns 0 if an error occurred. + * + * @note The write_some operation may not transmit all of the data to the + * peer. Consider using the @ref write function if you need to ensure that + * all data is written before the blocking operation completes. + */ + template + std::size_t write_some(const ConstBufferSequence& buffers, + asio::error_code& ec) + { + return this->impl_.get_service().send( + this->impl_.get_implementation(), buffers, 0, ec); + } + + /// Start an asynchronous write. + /** + * This function is used to asynchronously write data to the stream socket. + * The function call always returns immediately. + * + * @param buffers One or more data buffers to be written to the socket. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param handler The handler to be called when the write operation completes. + * Copies will be made of the handler as required. The function signature of + * the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes written. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note The write operation may not transmit all of the data to the peer. + * Consider using the @ref async_write function if you need to ensure that all + * data is written before the asynchronous operation completes. + * + * @par Example + * To write a single data buffer use the @ref buffer function as follows: + * @code + * socket.async_write_some(asio::buffer(data, size), handler); + * @endcode + * See the @ref buffer documentation for information on writing multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_write_some(const ConstBufferSequence& buffers, + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_send(this), handler, + buffers, socket_base::message_flags(0)); + } + + /// Read some data from the socket. + /** + * This function is used to read data from the stream socket. The function + * call will block until one or more bytes of data has been read successfully, + * or until an error occurs. + * + * @param buffers One or more buffers into which the data will be read. + * + * @returns The number of bytes read. + * + * @throws asio::system_error Thrown on failure. An error code of + * asio::error::eof indicates that the connection was closed by the + * peer. + * + * @note The read_some operation may not read all of the requested number of + * bytes. Consider using the @ref read function if you need to ensure that + * the requested amount of data is read before the blocking operation + * completes. + * + * @par Example + * To read into a single data buffer use the @ref buffer function as follows: + * @code + * socket.read_some(asio::buffer(data, size)); + * @endcode + * See the @ref buffer documentation for information on reading into multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + std::size_t read_some(const MutableBufferSequence& buffers) + { + asio::error_code ec; + std::size_t s = this->impl_.get_service().receive( + this->impl_.get_implementation(), buffers, 0, ec); + asio::detail::throw_error(ec, "read_some"); + return s; + } + + /// Read some data from the socket. + /** + * This function is used to read data from the stream socket. The function + * call will block until one or more bytes of data has been read successfully, + * or until an error occurs. + * + * @param buffers One or more buffers into which the data will be read. + * + * @param ec Set to indicate what error occurred, if any. + * + * @returns The number of bytes read. Returns 0 if an error occurred. + * + * @note The read_some operation may not read all of the requested number of + * bytes. Consider using the @ref read function if you need to ensure that + * the requested amount of data is read before the blocking operation + * completes. + */ + template + std::size_t read_some(const MutableBufferSequence& buffers, + asio::error_code& ec) + { + return this->impl_.get_service().receive( + this->impl_.get_implementation(), buffers, 0, ec); + } + + /// Start an asynchronous read. + /** + * This function is used to asynchronously read data from the stream socket. + * The function call always returns immediately. + * + * @param buffers One or more buffers into which the data will be read. + * Although the buffers object may be copied as necessary, ownership of the + * underlying memory blocks is retained by the caller, which must guarantee + * that they remain valid until the handler is called. + * + * @param handler The handler to be called when the read operation completes. + * Copies will be made of the handler as required. The function signature of + * the handler must be: + * @code void handler( + * const asio::error_code& error, // Result of operation. + * std::size_t bytes_transferred // Number of bytes read. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note The read operation may not read all of the requested number of bytes. + * Consider using the @ref async_read function if you need to ensure that the + * requested amount of data is read before the asynchronous operation + * completes. + * + * @par Example + * To read into a single data buffer use the @ref buffer function as follows: + * @code + * socket.async_read_some(asio::buffer(data, size), handler); + * @endcode + * See the @ref buffer documentation for information on reading into multiple + * buffers in one go, and how to use it with arrays, boost::array or + * std::vector. + */ + template + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_read_some(const MutableBufferSequence& buffers, + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_receive(this), handler, + buffers, socket_base::message_flags(0)); + } + +private: + // Disallow copying and assignment. + basic_stream_socket(const basic_stream_socket&) ASIO_DELETED; + basic_stream_socket& operator=(const basic_stream_socket&) ASIO_DELETED; + + class initiate_async_send + { + public: + typedef Executor executor_type; + + explicit initiate_async_send(basic_stream_socket* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(WriteHandler) handler, + const ConstBufferSequence& buffers, + socket_base::message_flags flags) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a WriteHandler. + ASIO_WRITE_HANDLER_CHECK(WriteHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_send( + self_->impl_.get_implementation(), buffers, flags, + handler2.value, self_->impl_.get_executor()); + } + + private: + basic_stream_socket* self_; + }; + + class initiate_async_receive + { + public: + typedef Executor executor_type; + + explicit initiate_async_receive(basic_stream_socket* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(ReadHandler) handler, + const MutableBufferSequence& buffers, + socket_base::message_flags flags) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a ReadHandler. + ASIO_READ_HANDLER_CHECK(ReadHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_receive( + self_->impl_.get_implementation(), buffers, flags, + handler2.value, self_->impl_.get_executor()); + } + + private: + basic_stream_socket* self_; + }; +}; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_BASIC_STREAM_SOCKET_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_streambuf.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_streambuf.hpp new file mode 100644 index 000000000..5b22070f1 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_streambuf.hpp @@ -0,0 +1,452 @@ +// +// basic_streambuf.hpp +// ~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BASIC_STREAMBUF_HPP +#define ASIO_BASIC_STREAMBUF_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_NO_IOSTREAM) + +#include +#include +#include +#include +#include +#include "asio/basic_streambuf_fwd.hpp" +#include "asio/buffer.hpp" +#include "asio/detail/limits.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/throw_exception.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +/// Automatically resizable buffer class based on std::streambuf. +/** + * The @c basic_streambuf class is derived from @c std::streambuf to associate + * the streambuf's input and output sequences with one or more character + * arrays. These character arrays are internal to the @c basic_streambuf + * object, but direct access to the array elements is provided to permit them + * to be used efficiently with I/O operations. Characters written to the output + * sequence of a @c basic_streambuf object are appended to the input sequence + * of the same object. + * + * The @c basic_streambuf class's public interface is intended to permit the + * following implementation strategies: + * + * @li A single contiguous character array, which is reallocated as necessary + * to accommodate changes in the size of the character sequence. This is the + * implementation approach currently used in Asio. + * + * @li A sequence of one or more character arrays, where each array is of the + * same size. Additional character array objects are appended to the sequence + * to accommodate changes in the size of the character sequence. + * + * @li A sequence of one or more character arrays of varying sizes. Additional + * character array objects are appended to the sequence to accommodate changes + * in the size of the character sequence. + * + * The constructor for basic_streambuf accepts a @c size_t argument specifying + * the maximum of the sum of the sizes of the input sequence and output + * sequence. During the lifetime of the @c basic_streambuf object, the following + * invariant holds: + * @code size() <= max_size()@endcode + * Any member function that would, if successful, cause the invariant to be + * violated shall throw an exception of class @c std::length_error. + * + * The constructor for @c basic_streambuf takes an Allocator argument. A copy + * of this argument is used for any memory allocation performed, by the + * constructor and by all member functions, during the lifetime of each @c + * basic_streambuf object. + * + * @par Examples + * Writing directly from an streambuf to a socket: + * @code + * asio::streambuf b; + * std::ostream os(&b); + * os << "Hello, World!\n"; + * + * // try sending some data in input sequence + * size_t n = sock.send(b.data()); + * + * b.consume(n); // sent data is removed from input sequence + * @endcode + * + * Reading from a socket directly into a streambuf: + * @code + * asio::streambuf b; + * + * // reserve 512 bytes in output sequence + * asio::streambuf::mutable_buffers_type bufs = b.prepare(512); + * + * size_t n = sock.receive(bufs); + * + * // received data is "committed" from output sequence to input sequence + * b.commit(n); + * + * std::istream is(&b); + * std::string s; + * is >> s; + * @endcode + */ +#if defined(GENERATING_DOCUMENTATION) +template > +#else +template +#endif +class basic_streambuf + : public std::streambuf, + private noncopyable +{ +public: +#if defined(GENERATING_DOCUMENTATION) + /// The type used to represent the input sequence as a list of buffers. + typedef implementation_defined const_buffers_type; + + /// The type used to represent the output sequence as a list of buffers. + typedef implementation_defined mutable_buffers_type; +#else + typedef ASIO_CONST_BUFFER const_buffers_type; + typedef ASIO_MUTABLE_BUFFER mutable_buffers_type; +#endif + + /// Construct a basic_streambuf object. + /** + * Constructs a streambuf with the specified maximum size. The initial size + * of the streambuf's input sequence is 0. + */ + explicit basic_streambuf( + std::size_t maximum_size = (std::numeric_limits::max)(), + const Allocator& allocator = Allocator()) + : max_size_(maximum_size), + buffer_(allocator) + { + std::size_t pend = (std::min)(max_size_, buffer_delta); + buffer_.resize((std::max)(pend, 1)); + setg(&buffer_[0], &buffer_[0], &buffer_[0]); + setp(&buffer_[0], &buffer_[0] + pend); + } + + /// Get the size of the input sequence. + /** + * @returns The size of the input sequence. The value is equal to that + * calculated for @c s in the following code: + * @code + * size_t s = 0; + * const_buffers_type bufs = data(); + * const_buffers_type::const_iterator i = bufs.begin(); + * while (i != bufs.end()) + * { + * const_buffer buf(*i++); + * s += buf.size(); + * } + * @endcode + */ + std::size_t size() const ASIO_NOEXCEPT + { + return pptr() - gptr(); + } + + /// Get the maximum size of the basic_streambuf. + /** + * @returns The allowed maximum of the sum of the sizes of the input sequence + * and output sequence. + */ + std::size_t max_size() const ASIO_NOEXCEPT + { + return max_size_; + } + + /// Get the current capacity of the basic_streambuf. + /** + * @returns The current total capacity of the streambuf, i.e. for both the + * input sequence and output sequence. + */ + std::size_t capacity() const ASIO_NOEXCEPT + { + return buffer_.capacity(); + } + + /// Get a list of buffers that represents the input sequence. + /** + * @returns An object of type @c const_buffers_type that satisfies + * ConstBufferSequence requirements, representing all character arrays in the + * input sequence. + * + * @note The returned object is invalidated by any @c basic_streambuf member + * function that modifies the input sequence or output sequence. + */ + const_buffers_type data() const ASIO_NOEXCEPT + { + return asio::buffer(asio::const_buffer(gptr(), + (pptr() - gptr()) * sizeof(char_type))); + } + + /// Get a list of buffers that represents the output sequence, with the given + /// size. + /** + * Ensures that the output sequence can accommodate @c n characters, + * reallocating character array objects as necessary. + * + * @returns An object of type @c mutable_buffers_type that satisfies + * MutableBufferSequence requirements, representing character array objects + * at the start of the output sequence such that the sum of the buffer sizes + * is @c n. + * + * @throws std::length_error If size() + n > max_size(). + * + * @note The returned object is invalidated by any @c basic_streambuf member + * function that modifies the input sequence or output sequence. + */ + mutable_buffers_type prepare(std::size_t n) + { + reserve(n); + return asio::buffer(asio::mutable_buffer( + pptr(), n * sizeof(char_type))); + } + + /// Move characters from the output sequence to the input sequence. + /** + * Appends @c n characters from the start of the output sequence to the input + * sequence. The beginning of the output sequence is advanced by @c n + * characters. + * + * Requires a preceding call prepare(x) where x >= n, and + * no intervening operations that modify the input or output sequence. + * + * @note If @c n is greater than the size of the output sequence, the entire + * output sequence is moved to the input sequence and no error is issued. + */ + void commit(std::size_t n) + { + n = std::min(n, epptr() - pptr()); + pbump(static_cast(n)); + setg(eback(), gptr(), pptr()); + } + + /// Remove characters from the input sequence. + /** + * Removes @c n characters from the beginning of the input sequence. + * + * @note If @c n is greater than the size of the input sequence, the entire + * input sequence is consumed and no error is issued. + */ + void consume(std::size_t n) + { + if (egptr() < pptr()) + setg(&buffer_[0], gptr(), pptr()); + if (gptr() + n > pptr()) + n = pptr() - gptr(); + gbump(static_cast(n)); + } + +protected: + enum { buffer_delta = 128 }; + + /// Override std::streambuf behaviour. + /** + * Behaves according to the specification of @c std::streambuf::underflow(). + */ + int_type underflow() + { + if (gptr() < pptr()) + { + setg(&buffer_[0], gptr(), pptr()); + return traits_type::to_int_type(*gptr()); + } + else + { + return traits_type::eof(); + } + } + + /// Override std::streambuf behaviour. + /** + * Behaves according to the specification of @c std::streambuf::overflow(), + * with the specialisation that @c std::length_error is thrown if appending + * the character to the input sequence would require the condition + * size() > max_size() to be true. + */ + int_type overflow(int_type c) + { + if (!traits_type::eq_int_type(c, traits_type::eof())) + { + if (pptr() == epptr()) + { + std::size_t buffer_size = pptr() - gptr(); + if (buffer_size < max_size_ && max_size_ - buffer_size < buffer_delta) + { + reserve(max_size_ - buffer_size); + } + else + { + reserve(buffer_delta); + } + } + + *pptr() = traits_type::to_char_type(c); + pbump(1); + return c; + } + + return traits_type::not_eof(c); + } + + void reserve(std::size_t n) + { + // Get current stream positions as offsets. + std::size_t gnext = gptr() - &buffer_[0]; + std::size_t pnext = pptr() - &buffer_[0]; + std::size_t pend = epptr() - &buffer_[0]; + + // Check if there is already enough space in the put area. + if (n <= pend - pnext) + { + return; + } + + // Shift existing contents of get area to start of buffer. + if (gnext > 0) + { + pnext -= gnext; + std::memmove(&buffer_[0], &buffer_[0] + gnext, pnext); + } + + // Ensure buffer is large enough to hold at least the specified size. + if (n > pend - pnext) + { + if (n <= max_size_ && pnext <= max_size_ - n) + { + pend = pnext + n; + buffer_.resize((std::max)(pend, 1)); + } + else + { + std::length_error ex("asio::streambuf too long"); + asio::detail::throw_exception(ex); + } + } + + // Update stream positions. + setg(&buffer_[0], &buffer_[0], &buffer_[0] + pnext); + setp(&buffer_[0] + pnext, &buffer_[0] + pend); + } + +private: + std::size_t max_size_; + std::vector buffer_; + + // Helper function to get the preferred size for reading data. + friend std::size_t read_size_helper( + basic_streambuf& sb, std::size_t max_size) + { + return std::min( + std::max(512, sb.buffer_.capacity() - sb.size()), + std::min(max_size, sb.max_size() - sb.size())); + } +}; + +/// Adapts basic_streambuf to the dynamic buffer sequence type requirements. +#if defined(GENERATING_DOCUMENTATION) +template > +#else +template +#endif +class basic_streambuf_ref +{ +public: + /// The type used to represent the input sequence as a list of buffers. + typedef typename basic_streambuf::const_buffers_type + const_buffers_type; + + /// The type used to represent the output sequence as a list of buffers. + typedef typename basic_streambuf::mutable_buffers_type + mutable_buffers_type; + + /// Construct a basic_streambuf_ref for the given basic_streambuf object. + explicit basic_streambuf_ref(basic_streambuf& sb) + : sb_(sb) + { + } + + /// Copy construct a basic_streambuf_ref. + basic_streambuf_ref(const basic_streambuf_ref& other) ASIO_NOEXCEPT + : sb_(other.sb_) + { + } + +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + /// Move construct a basic_streambuf_ref. + basic_streambuf_ref(basic_streambuf_ref&& other) ASIO_NOEXCEPT + : sb_(other.sb_) + { + } +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + /// Get the size of the input sequence. + std::size_t size() const ASIO_NOEXCEPT + { + return sb_.size(); + } + + /// Get the maximum size of the dynamic buffer. + std::size_t max_size() const ASIO_NOEXCEPT + { + return sb_.max_size(); + } + + /// Get the current capacity of the dynamic buffer. + std::size_t capacity() const ASIO_NOEXCEPT + { + return sb_.capacity(); + } + + /// Get a list of buffers that represents the input sequence. + const_buffers_type data() const ASIO_NOEXCEPT + { + return sb_.data(); + } + + /// Get a list of buffers that represents the output sequence, with the given + /// size. + mutable_buffers_type prepare(std::size_t n) + { + return sb_.prepare(n); + } + + /// Move bytes from the output sequence to the input sequence. + void commit(std::size_t n) + { + return sb_.commit(n); + } + + /// Remove characters from the input sequence. + void consume(std::size_t n) + { + return sb_.consume(n); + } + +private: + basic_streambuf& sb_; +}; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_NO_IOSTREAM) + +#endif // ASIO_BASIC_STREAMBUF_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_streambuf_fwd.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_streambuf_fwd.hpp new file mode 100644 index 000000000..df9961d91 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_streambuf_fwd.hpp @@ -0,0 +1,36 @@ +// +// basic_streambuf_fwd.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BASIC_STREAMBUF_FWD_HPP +#define ASIO_BASIC_STREAMBUF_FWD_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_NO_IOSTREAM) + +#include + +namespace asio { + +template > +class basic_streambuf; + +template > +class basic_streambuf_ref; + +} // namespace asio + +#endif // !defined(ASIO_NO_IOSTREAM) + +#endif // ASIO_BASIC_STREAMBUF_FWD_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_waitable_timer.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_waitable_timer.hpp new file mode 100644 index 000000000..28452ef1a --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/basic_waitable_timer.hpp @@ -0,0 +1,811 @@ +// +// basic_waitable_timer.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BASIC_WAITABLE_TIMER_HPP +#define ASIO_BASIC_WAITABLE_TIMER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include "asio/any_io_executor.hpp" +#include "asio/detail/chrono_time_traits.hpp" +#include "asio/detail/deadline_timer_service.hpp" +#include "asio/detail/handler_type_requirements.hpp" +#include "asio/detail/io_object_impl.hpp" +#include "asio/detail/non_const_lvalue.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" +#include "asio/wait_traits.hpp" + +#if defined(ASIO_HAS_MOVE) +# include +#endif // defined(ASIO_HAS_MOVE) + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if !defined(ASIO_BASIC_WAITABLE_TIMER_FWD_DECL) +#define ASIO_BASIC_WAITABLE_TIMER_FWD_DECL + +// Forward declaration with defaulted arguments. +template , + typename Executor = any_io_executor> +class basic_waitable_timer; + +#endif // !defined(ASIO_BASIC_WAITABLE_TIMER_FWD_DECL) + +/// Provides waitable timer functionality. +/** + * The basic_waitable_timer class template provides the ability to perform a + * blocking or asynchronous wait for a timer to expire. + * + * A waitable timer is always in one of two states: "expired" or "not expired". + * If the wait() or async_wait() function is called on an expired timer, the + * wait operation will complete immediately. + * + * Most applications will use one of the asio::steady_timer, + * asio::system_timer or asio::high_resolution_timer typedefs. + * + * @note This waitable timer functionality is for use with the C++11 standard + * library's @c <chrono> facility, or with the Boost.Chrono library. + * + * @par Thread Safety + * @e Distinct @e objects: Safe.@n + * @e Shared @e objects: Unsafe. + * + * @par Examples + * Performing a blocking wait (C++11): + * @code + * // Construct a timer without setting an expiry time. + * asio::steady_timer timer(my_context); + * + * // Set an expiry time relative to now. + * timer.expires_after(std::chrono::seconds(5)); + * + * // Wait for the timer to expire. + * timer.wait(); + * @endcode + * + * @par + * Performing an asynchronous wait (C++11): + * @code + * void handler(const asio::error_code& error) + * { + * if (!error) + * { + * // Timer expired. + * } + * } + * + * ... + * + * // Construct a timer with an absolute expiry time. + * asio::steady_timer timer(my_context, + * std::chrono::steady_clock::now() + std::chrono::seconds(60)); + * + * // Start an asynchronous wait. + * timer.async_wait(handler); + * @endcode + * + * @par Changing an active waitable timer's expiry time + * + * Changing the expiry time of a timer while there are pending asynchronous + * waits causes those wait operations to be cancelled. To ensure that the action + * associated with the timer is performed only once, use something like this: + * used: + * + * @code + * void on_some_event() + * { + * if (my_timer.expires_after(seconds(5)) > 0) + * { + * // We managed to cancel the timer. Start new asynchronous wait. + * my_timer.async_wait(on_timeout); + * } + * else + * { + * // Too late, timer has already expired! + * } + * } + * + * void on_timeout(const asio::error_code& e) + * { + * if (e != asio::error::operation_aborted) + * { + * // Timer was not cancelled, take necessary action. + * } + * } + * @endcode + * + * @li The asio::basic_waitable_timer::expires_after() function + * cancels any pending asynchronous waits, and returns the number of + * asynchronous waits that were cancelled. If it returns 0 then you were too + * late and the wait handler has already been executed, or will soon be + * executed. If it returns 1 then the wait handler was successfully cancelled. + * + * @li If a wait handler is cancelled, the asio::error_code passed to + * it contains the value asio::error::operation_aborted. + */ +template +class basic_waitable_timer +{ +public: + /// The type of the executor associated with the object. + typedef Executor executor_type; + + /// Rebinds the timer type to another executor. + template + struct rebind_executor + { + /// The timer type when rebound to the specified executor. + typedef basic_waitable_timer other; + }; + + /// The clock type. + typedef Clock clock_type; + + /// The duration type of the clock. + typedef typename clock_type::duration duration; + + /// The time point type of the clock. + typedef typename clock_type::time_point time_point; + + /// The wait traits type. + typedef WaitTraits traits_type; + + /// Constructor. + /** + * This constructor creates a timer without setting an expiry time. The + * expires_at() or expires_after() functions must be called to set an expiry + * time before the timer can be waited on. + * + * @param ex The I/O executor that the timer will use, by default, to + * dispatch handlers for any asynchronous operations performed on the timer. + */ + explicit basic_waitable_timer(const executor_type& ex) + : impl_(ex) + { + } + + /// Constructor. + /** + * This constructor creates a timer without setting an expiry time. The + * expires_at() or expires_after() functions must be called to set an expiry + * time before the timer can be waited on. + * + * @param context An execution context which provides the I/O executor that + * the timer will use, by default, to dispatch handlers for any asynchronous + * operations performed on the timer. + */ + template + explicit basic_waitable_timer(ExecutionContext& context, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + } + + /// Constructor to set a particular expiry time as an absolute time. + /** + * This constructor creates a timer and sets the expiry time. + * + * @param ex The I/O executor object that the timer will use, by default, to + * dispatch handlers for any asynchronous operations performed on the timer. + * + * @param expiry_time The expiry time to be used for the timer, expressed + * as an absolute time. + */ + basic_waitable_timer(const executor_type& ex, const time_point& expiry_time) + : impl_(ex) + { + asio::error_code ec; + impl_.get_service().expires_at(impl_.get_implementation(), expiry_time, ec); + asio::detail::throw_error(ec, "expires_at"); + } + + /// Constructor to set a particular expiry time as an absolute time. + /** + * This constructor creates a timer and sets the expiry time. + * + * @param context An execution context which provides the I/O executor that + * the timer will use, by default, to dispatch handlers for any asynchronous + * operations performed on the timer. + * + * @param expiry_time The expiry time to be used for the timer, expressed + * as an absolute time. + */ + template + explicit basic_waitable_timer(ExecutionContext& context, + const time_point& expiry_time, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + asio::error_code ec; + impl_.get_service().expires_at(impl_.get_implementation(), expiry_time, ec); + asio::detail::throw_error(ec, "expires_at"); + } + + /// Constructor to set a particular expiry time relative to now. + /** + * This constructor creates a timer and sets the expiry time. + * + * @param ex The I/O executor that the timer will use, by default, to + * dispatch handlers for any asynchronous operations performed on the timer. + * + * @param expiry_time The expiry time to be used for the timer, relative to + * now. + */ + basic_waitable_timer(const executor_type& ex, const duration& expiry_time) + : impl_(ex) + { + asio::error_code ec; + impl_.get_service().expires_after( + impl_.get_implementation(), expiry_time, ec); + asio::detail::throw_error(ec, "expires_after"); + } + + /// Constructor to set a particular expiry time relative to now. + /** + * This constructor creates a timer and sets the expiry time. + * + * @param context An execution context which provides the I/O executor that + * the timer will use, by default, to dispatch handlers for any asynchronous + * operations performed on the timer. + * + * @param expiry_time The expiry time to be used for the timer, relative to + * now. + */ + template + explicit basic_waitable_timer(ExecutionContext& context, + const duration& expiry_time, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(context) + { + asio::error_code ec; + impl_.get_service().expires_after( + impl_.get_implementation(), expiry_time, ec); + asio::detail::throw_error(ec, "expires_after"); + } + +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + /// Move-construct a basic_waitable_timer from another. + /** + * This constructor moves a timer from one object to another. + * + * @param other The other basic_waitable_timer object from which the move will + * occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_waitable_timer(const executor_type&) + * constructor. + */ + basic_waitable_timer(basic_waitable_timer&& other) + : impl_(std::move(other.impl_)) + { + } + + /// Move-assign a basic_waitable_timer from another. + /** + * This assignment operator moves a timer from one object to another. Cancels + * any outstanding asynchronous operations associated with the target object. + * + * @param other The other basic_waitable_timer object from which the move will + * occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_waitable_timer(const executor_type&) + * constructor. + */ + basic_waitable_timer& operator=(basic_waitable_timer&& other) + { + impl_ = std::move(other.impl_); + return *this; + } + + // All timers have access to each other's implementations. + template + friend class basic_waitable_timer; + + /// Move-construct a basic_waitable_timer from another. + /** + * This constructor moves a timer from one object to another. + * + * @param other The other basic_waitable_timer object from which the move will + * occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_waitable_timer(const executor_type&) + * constructor. + */ + template + basic_waitable_timer( + basic_waitable_timer&& other, + typename enable_if< + is_convertible::value + >::type* = 0) + : impl_(std::move(other.impl_)) + { + } + + /// Move-assign a basic_waitable_timer from another. + /** + * This assignment operator moves a timer from one object to another. Cancels + * any outstanding asynchronous operations associated with the target object. + * + * @param other The other basic_waitable_timer object from which the move will + * occur. + * + * @note Following the move, the moved-from object is in the same state as if + * constructed using the @c basic_waitable_timer(const executor_type&) + * constructor. + */ + template + typename enable_if< + is_convertible::value, + basic_waitable_timer& + >::type operator=(basic_waitable_timer&& other) + { + basic_waitable_timer tmp(std::move(other)); + impl_ = std::move(tmp.impl_); + return *this; + } +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + /// Destroys the timer. + /** + * This function destroys the timer, cancelling any outstanding asynchronous + * wait operations associated with the timer as if by calling @c cancel. + */ + ~basic_waitable_timer() + { + } + + /// Get the executor associated with the object. + executor_type get_executor() ASIO_NOEXCEPT + { + return impl_.get_executor(); + } + + /// Cancel any asynchronous operations that are waiting on the timer. + /** + * This function forces the completion of any pending asynchronous wait + * operations against the timer. The handler for each cancelled operation will + * be invoked with the asio::error::operation_aborted error code. + * + * Cancelling the timer does not change the expiry time. + * + * @return The number of asynchronous operations that were cancelled. + * + * @throws asio::system_error Thrown on failure. + * + * @note If the timer has already expired when cancel() is called, then the + * handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + std::size_t cancel() + { + asio::error_code ec; + std::size_t s = impl_.get_service().cancel(impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "cancel"); + return s; + } + +#if !defined(ASIO_NO_DEPRECATED) + /// (Deprecated: Use non-error_code overload.) Cancel any asynchronous + /// operations that are waiting on the timer. + /** + * This function forces the completion of any pending asynchronous wait + * operations against the timer. The handler for each cancelled operation will + * be invoked with the asio::error::operation_aborted error code. + * + * Cancelling the timer does not change the expiry time. + * + * @param ec Set to indicate what error occurred, if any. + * + * @return The number of asynchronous operations that were cancelled. + * + * @note If the timer has already expired when cancel() is called, then the + * handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + std::size_t cancel(asio::error_code& ec) + { + return impl_.get_service().cancel(impl_.get_implementation(), ec); + } +#endif // !defined(ASIO_NO_DEPRECATED) + + /// Cancels one asynchronous operation that is waiting on the timer. + /** + * This function forces the completion of one pending asynchronous wait + * operation against the timer. Handlers are cancelled in FIFO order. The + * handler for the cancelled operation will be invoked with the + * asio::error::operation_aborted error code. + * + * Cancelling the timer does not change the expiry time. + * + * @return The number of asynchronous operations that were cancelled. That is, + * either 0 or 1. + * + * @throws asio::system_error Thrown on failure. + * + * @note If the timer has already expired when cancel_one() is called, then + * the handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + std::size_t cancel_one() + { + asio::error_code ec; + std::size_t s = impl_.get_service().cancel_one( + impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "cancel_one"); + return s; + } + +#if !defined(ASIO_NO_DEPRECATED) + /// (Deprecated: Use non-error_code overload.) Cancels one asynchronous + /// operation that is waiting on the timer. + /** + * This function forces the completion of one pending asynchronous wait + * operation against the timer. Handlers are cancelled in FIFO order. The + * handler for the cancelled operation will be invoked with the + * asio::error::operation_aborted error code. + * + * Cancelling the timer does not change the expiry time. + * + * @param ec Set to indicate what error occurred, if any. + * + * @return The number of asynchronous operations that were cancelled. That is, + * either 0 or 1. + * + * @note If the timer has already expired when cancel_one() is called, then + * the handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + std::size_t cancel_one(asio::error_code& ec) + { + return impl_.get_service().cancel_one(impl_.get_implementation(), ec); + } + + /// (Deprecated: Use expiry().) Get the timer's expiry time as an absolute + /// time. + /** + * This function may be used to obtain the timer's current expiry time. + * Whether the timer has expired or not does not affect this value. + */ + time_point expires_at() const + { + return impl_.get_service().expires_at(impl_.get_implementation()); + } +#endif // !defined(ASIO_NO_DEPRECATED) + + /// Get the timer's expiry time as an absolute time. + /** + * This function may be used to obtain the timer's current expiry time. + * Whether the timer has expired or not does not affect this value. + */ + time_point expiry() const + { + return impl_.get_service().expiry(impl_.get_implementation()); + } + + /// Set the timer's expiry time as an absolute time. + /** + * This function sets the expiry time. Any pending asynchronous wait + * operations will be cancelled. The handler for each cancelled operation will + * be invoked with the asio::error::operation_aborted error code. + * + * @param expiry_time The expiry time to be used for the timer. + * + * @return The number of asynchronous operations that were cancelled. + * + * @throws asio::system_error Thrown on failure. + * + * @note If the timer has already expired when expires_at() is called, then + * the handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + std::size_t expires_at(const time_point& expiry_time) + { + asio::error_code ec; + std::size_t s = impl_.get_service().expires_at( + impl_.get_implementation(), expiry_time, ec); + asio::detail::throw_error(ec, "expires_at"); + return s; + } + +#if !defined(ASIO_NO_DEPRECATED) + /// (Deprecated: Use non-error_code overload.) Set the timer's expiry time as + /// an absolute time. + /** + * This function sets the expiry time. Any pending asynchronous wait + * operations will be cancelled. The handler for each cancelled operation will + * be invoked with the asio::error::operation_aborted error code. + * + * @param expiry_time The expiry time to be used for the timer. + * + * @param ec Set to indicate what error occurred, if any. + * + * @return The number of asynchronous operations that were cancelled. + * + * @note If the timer has already expired when expires_at() is called, then + * the handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + std::size_t expires_at(const time_point& expiry_time, + asio::error_code& ec) + { + return impl_.get_service().expires_at( + impl_.get_implementation(), expiry_time, ec); + } +#endif // !defined(ASIO_NO_DEPRECATED) + + /// Set the timer's expiry time relative to now. + /** + * This function sets the expiry time. Any pending asynchronous wait + * operations will be cancelled. The handler for each cancelled operation will + * be invoked with the asio::error::operation_aborted error code. + * + * @param expiry_time The expiry time to be used for the timer. + * + * @return The number of asynchronous operations that were cancelled. + * + * @throws asio::system_error Thrown on failure. + * + * @note If the timer has already expired when expires_after() is called, + * then the handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + std::size_t expires_after(const duration& expiry_time) + { + asio::error_code ec; + std::size_t s = impl_.get_service().expires_after( + impl_.get_implementation(), expiry_time, ec); + asio::detail::throw_error(ec, "expires_after"); + return s; + } + +#if !defined(ASIO_NO_DEPRECATED) + /// (Deprecated: Use expiry().) Get the timer's expiry time relative to now. + /** + * This function may be used to obtain the timer's current expiry time. + * Whether the timer has expired or not does not affect this value. + */ + duration expires_from_now() const + { + return impl_.get_service().expires_from_now(impl_.get_implementation()); + } + + /// (Deprecated: Use expires_after().) Set the timer's expiry time relative + /// to now. + /** + * This function sets the expiry time. Any pending asynchronous wait + * operations will be cancelled. The handler for each cancelled operation will + * be invoked with the asio::error::operation_aborted error code. + * + * @param expiry_time The expiry time to be used for the timer. + * + * @return The number of asynchronous operations that were cancelled. + * + * @throws asio::system_error Thrown on failure. + * + * @note If the timer has already expired when expires_from_now() is called, + * then the handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + std::size_t expires_from_now(const duration& expiry_time) + { + asio::error_code ec; + std::size_t s = impl_.get_service().expires_from_now( + impl_.get_implementation(), expiry_time, ec); + asio::detail::throw_error(ec, "expires_from_now"); + return s; + } + + /// (Deprecated: Use expires_after().) Set the timer's expiry time relative + /// to now. + /** + * This function sets the expiry time. Any pending asynchronous wait + * operations will be cancelled. The handler for each cancelled operation will + * be invoked with the asio::error::operation_aborted error code. + * + * @param expiry_time The expiry time to be used for the timer. + * + * @param ec Set to indicate what error occurred, if any. + * + * @return The number of asynchronous operations that were cancelled. + * + * @note If the timer has already expired when expires_from_now() is called, + * then the handlers for asynchronous wait operations will: + * + * @li have already been invoked; or + * + * @li have been queued for invocation in the near future. + * + * These handlers can no longer be cancelled, and therefore are passed an + * error code that indicates the successful completion of the wait operation. + */ + std::size_t expires_from_now(const duration& expiry_time, + asio::error_code& ec) + { + return impl_.get_service().expires_from_now( + impl_.get_implementation(), expiry_time, ec); + } +#endif // !defined(ASIO_NO_DEPRECATED) + + /// Perform a blocking wait on the timer. + /** + * This function is used to wait for the timer to expire. This function + * blocks and does not return until the timer has expired. + * + * @throws asio::system_error Thrown on failure. + */ + void wait() + { + asio::error_code ec; + impl_.get_service().wait(impl_.get_implementation(), ec); + asio::detail::throw_error(ec, "wait"); + } + + /// Perform a blocking wait on the timer. + /** + * This function is used to wait for the timer to expire. This function + * blocks and does not return until the timer has expired. + * + * @param ec Set to indicate what error occurred, if any. + */ + void wait(asio::error_code& ec) + { + impl_.get_service().wait(impl_.get_implementation(), ec); + } + + /// Start an asynchronous wait on the timer. + /** + * This function may be used to initiate an asynchronous wait against the + * timer. It always returns immediately. + * + * For each call to async_wait(), the supplied handler will be called exactly + * once. The handler will be called when: + * + * @li The timer has expired. + * + * @li The timer was cancelled, in which case the handler is passed the error + * code asio::error::operation_aborted. + * + * @param handler The handler to be called when the timer expires. Copies + * will be made of the handler as required. The function signature of the + * handler must be: + * @code void handler( + * const asio::error_code& error // Result of operation. + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + */ + template < + ASIO_COMPLETION_TOKEN_FOR(void (asio::error_code)) + WaitHandler ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(executor_type)> + ASIO_INITFN_AUTO_RESULT_TYPE(WaitHandler, + void (asio::error_code)) + async_wait( + ASIO_MOVE_ARG(WaitHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return async_initiate( + initiate_async_wait(this), handler); + } + +private: + // Disallow copying and assignment. + basic_waitable_timer(const basic_waitable_timer&) ASIO_DELETED; + basic_waitable_timer& operator=( + const basic_waitable_timer&) ASIO_DELETED; + + class initiate_async_wait + { + public: + typedef Executor executor_type; + + explicit initiate_async_wait(basic_waitable_timer* self) + : self_(self) + { + } + + executor_type get_executor() const ASIO_NOEXCEPT + { + return self_->get_executor(); + } + + template + void operator()(ASIO_MOVE_ARG(WaitHandler) handler) const + { + // If you get an error on the following line it means that your handler + // does not meet the documented type requirements for a WaitHandler. + ASIO_WAIT_HANDLER_CHECK(WaitHandler, handler) type_check; + + detail::non_const_lvalue handler2(handler); + self_->impl_.get_service().async_wait( + self_->impl_.get_implementation(), + handler2.value, self_->impl_.get_executor()); + } + + private: + basic_waitable_timer* self_; + }; + + detail::io_object_impl< + detail::deadline_timer_service< + detail::chrono_time_traits >, + executor_type > impl_; +}; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_BASIC_WAITABLE_TIMER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/bind_executor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/bind_executor.hpp new file mode 100644 index 000000000..db30db6ab --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/bind_executor.hpp @@ -0,0 +1,575 @@ +// +// bind_executor.hpp +// ~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BIND_EXECUTOR_HPP +#define ASIO_BIND_EXECUTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/detail/variadic_templates.hpp" +#include "asio/associated_executor.hpp" +#include "asio/associated_allocator.hpp" +#include "asio/async_result.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution_context.hpp" +#include "asio/is_executor.hpp" +#include "asio/uses_executor.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Helper to automatically define nested typedef result_type. + +template +struct executor_binder_result_type +{ +protected: + typedef void result_type_or_void; +}; + +template +struct executor_binder_result_type::type> +{ + typedef typename T::result_type result_type; +protected: + typedef result_type result_type_or_void; +}; + +template +struct executor_binder_result_type +{ + typedef R result_type; +protected: + typedef result_type result_type_or_void; +}; + +template +struct executor_binder_result_type +{ + typedef R result_type; +protected: + typedef result_type result_type_or_void; +}; + +template +struct executor_binder_result_type +{ + typedef R result_type; +protected: + typedef result_type result_type_or_void; +}; + +template +struct executor_binder_result_type +{ + typedef R result_type; +protected: + typedef result_type result_type_or_void; +}; + +template +struct executor_binder_result_type +{ + typedef R result_type; +protected: + typedef result_type result_type_or_void; +}; + +template +struct executor_binder_result_type +{ + typedef R result_type; +protected: + typedef result_type result_type_or_void; +}; + +// Helper to automatically define nested typedef argument_type. + +template +struct executor_binder_argument_type {}; + +template +struct executor_binder_argument_type::type> +{ + typedef typename T::argument_type argument_type; +}; + +template +struct executor_binder_argument_type +{ + typedef A1 argument_type; +}; + +template +struct executor_binder_argument_type +{ + typedef A1 argument_type; +}; + +// Helper to automatically define nested typedefs first_argument_type and +// second_argument_type. + +template +struct executor_binder_argument_types {}; + +template +struct executor_binder_argument_types::type> +{ + typedef typename T::first_argument_type first_argument_type; + typedef typename T::second_argument_type second_argument_type; +}; + +template +struct executor_binder_argument_type +{ + typedef A1 first_argument_type; + typedef A2 second_argument_type; +}; + +template +struct executor_binder_argument_type +{ + typedef A1 first_argument_type; + typedef A2 second_argument_type; +}; + +// Helper to perform uses_executor construction of the target type, if +// required. + +template +class executor_binder_base; + +template +class executor_binder_base +{ +protected: + template + executor_binder_base(ASIO_MOVE_ARG(E) e, ASIO_MOVE_ARG(U) u) + : executor_(ASIO_MOVE_CAST(E)(e)), + target_(executor_arg_t(), executor_, ASIO_MOVE_CAST(U)(u)) + { + } + + Executor executor_; + T target_; +}; + +template +class executor_binder_base +{ +protected: + template + executor_binder_base(ASIO_MOVE_ARG(E) e, ASIO_MOVE_ARG(U) u) + : executor_(ASIO_MOVE_CAST(E)(e)), + target_(ASIO_MOVE_CAST(U)(u)) + { + } + + Executor executor_; + T target_; +}; + +// Helper to enable SFINAE on zero-argument operator() below. + +template +struct executor_binder_result_of0 +{ + typedef void type; +}; + +template +struct executor_binder_result_of0::type>::type> +{ + typedef typename result_of::type type; +}; + +} // namespace detail + +/// A call wrapper type to bind an executor of type @c Executor to an object of +/// type @c T. +template +class executor_binder +#if !defined(GENERATING_DOCUMENTATION) + : public detail::executor_binder_result_type, + public detail::executor_binder_argument_type, + public detail::executor_binder_argument_types, + private detail::executor_binder_base< + T, Executor, uses_executor::value> +#endif // !defined(GENERATING_DOCUMENTATION) +{ +public: + /// The type of the target object. + typedef T target_type; + + /// The type of the associated executor. + typedef Executor executor_type; + +#if defined(GENERATING_DOCUMENTATION) + /// The return type if a function. + /** + * The type of @c result_type is based on the type @c T of the wrapper's + * target object: + * + * @li if @c T is a pointer to function type, @c result_type is a synonym for + * the return type of @c T; + * + * @li if @c T is a class type with a member type @c result_type, then @c + * result_type is a synonym for @c T::result_type; + * + * @li otherwise @c result_type is not defined. + */ + typedef see_below result_type; + + /// The type of the function's argument. + /** + * The type of @c argument_type is based on the type @c T of the wrapper's + * target object: + * + * @li if @c T is a pointer to a function type accepting a single argument, + * @c argument_type is a synonym for the return type of @c T; + * + * @li if @c T is a class type with a member type @c argument_type, then @c + * argument_type is a synonym for @c T::argument_type; + * + * @li otherwise @c argument_type is not defined. + */ + typedef see_below argument_type; + + /// The type of the function's first argument. + /** + * The type of @c first_argument_type is based on the type @c T of the + * wrapper's target object: + * + * @li if @c T is a pointer to a function type accepting two arguments, @c + * first_argument_type is a synonym for the return type of @c T; + * + * @li if @c T is a class type with a member type @c first_argument_type, + * then @c first_argument_type is a synonym for @c T::first_argument_type; + * + * @li otherwise @c first_argument_type is not defined. + */ + typedef see_below first_argument_type; + + /// The type of the function's second argument. + /** + * The type of @c second_argument_type is based on the type @c T of the + * wrapper's target object: + * + * @li if @c T is a pointer to a function type accepting two arguments, @c + * second_argument_type is a synonym for the return type of @c T; + * + * @li if @c T is a class type with a member type @c first_argument_type, + * then @c second_argument_type is a synonym for @c T::second_argument_type; + * + * @li otherwise @c second_argument_type is not defined. + */ + typedef see_below second_argument_type; +#endif // defined(GENERATING_DOCUMENTATION) + + /// Construct an executor wrapper for the specified object. + /** + * This constructor is only valid if the type @c T is constructible from type + * @c U. + */ + template + executor_binder(executor_arg_t, const executor_type& e, + ASIO_MOVE_ARG(U) u) + : base_type(e, ASIO_MOVE_CAST(U)(u)) + { + } + + /// Copy constructor. + executor_binder(const executor_binder& other) + : base_type(other.get_executor(), other.get()) + { + } + + /// Construct a copy, but specify a different executor. + executor_binder(executor_arg_t, const executor_type& e, + const executor_binder& other) + : base_type(e, other.get()) + { + } + + /// Construct a copy of a different executor wrapper type. + /** + * This constructor is only valid if the @c Executor type is constructible + * from type @c OtherExecutor, and the type @c T is constructible from type + * @c U. + */ + template + executor_binder(const executor_binder& other) + : base_type(other.get_executor(), other.get()) + { + } + + /// Construct a copy of a different executor wrapper type, but specify a + /// different executor. + /** + * This constructor is only valid if the type @c T is constructible from type + * @c U. + */ + template + executor_binder(executor_arg_t, const executor_type& e, + const executor_binder& other) + : base_type(e, other.get()) + { + } + +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + /// Move constructor. + executor_binder(executor_binder&& other) + : base_type(ASIO_MOVE_CAST(executor_type)(other.get_executor()), + ASIO_MOVE_CAST(T)(other.get())) + { + } + + /// Move construct the target object, but specify a different executor. + executor_binder(executor_arg_t, const executor_type& e, + executor_binder&& other) + : base_type(e, ASIO_MOVE_CAST(T)(other.get())) + { + } + + /// Move construct from a different executor wrapper type. + template + executor_binder(executor_binder&& other) + : base_type(ASIO_MOVE_CAST(OtherExecutor)(other.get_executor()), + ASIO_MOVE_CAST(U)(other.get())) + { + } + + /// Move construct from a different executor wrapper type, but specify a + /// different executor. + template + executor_binder(executor_arg_t, const executor_type& e, + executor_binder&& other) + : base_type(e, ASIO_MOVE_CAST(U)(other.get())) + { + } + +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + /// Destructor. + ~executor_binder() + { + } + + /// Obtain a reference to the target object. + target_type& get() ASIO_NOEXCEPT + { + return this->target_; + } + + /// Obtain a reference to the target object. + const target_type& get() const ASIO_NOEXCEPT + { + return this->target_; + } + + /// Obtain the associated executor. + executor_type get_executor() const ASIO_NOEXCEPT + { + return this->executor_; + } + +#if defined(GENERATING_DOCUMENTATION) + + template auto operator()(Args&& ...); + template auto operator()(Args&& ...) const; + +#elif defined(ASIO_HAS_VARIADIC_TEMPLATES) + + /// Forwarding function call operator. + template + typename result_of::type operator()( + ASIO_MOVE_ARG(Args)... args) + { + return this->target_(ASIO_MOVE_CAST(Args)(args)...); + } + + /// Forwarding function call operator. + template + typename result_of::type operator()( + ASIO_MOVE_ARG(Args)... args) const + { + return this->target_(ASIO_MOVE_CAST(Args)(args)...); + } + +#elif defined(ASIO_HAS_STD_TYPE_TRAITS) && !defined(_MSC_VER) + + typename detail::executor_binder_result_of0::type operator()() + { + return this->target_(); + } + + typename detail::executor_binder_result_of0::type operator()() const + { + return this->target_(); + } + +#define ASIO_PRIVATE_BIND_EXECUTOR_CALL_DEF(n) \ + template \ + typename result_of::type operator()( \ + ASIO_VARIADIC_MOVE_PARAMS(n)) \ + { \ + return this->target_(ASIO_VARIADIC_MOVE_ARGS(n)); \ + } \ + \ + template \ + typename result_of::type operator()( \ + ASIO_VARIADIC_MOVE_PARAMS(n)) const \ + { \ + return this->target_(ASIO_VARIADIC_MOVE_ARGS(n)); \ + } \ + /**/ + ASIO_VARIADIC_GENERATE(ASIO_PRIVATE_BIND_EXECUTOR_CALL_DEF) +#undef ASIO_PRIVATE_BIND_EXECUTOR_CALL_DEF + +#else // defined(ASIO_HAS_STD_TYPE_TRAITS) && !defined(_MSC_VER) + + typedef typename detail::executor_binder_result_type::result_type_or_void + result_type_or_void; + + result_type_or_void operator()() + { + return this->target_(); + } + + result_type_or_void operator()() const + { + return this->target_(); + } + +#define ASIO_PRIVATE_BIND_EXECUTOR_CALL_DEF(n) \ + template \ + result_type_or_void operator()( \ + ASIO_VARIADIC_MOVE_PARAMS(n)) \ + { \ + return this->target_(ASIO_VARIADIC_MOVE_ARGS(n)); \ + } \ + \ + template \ + result_type_or_void operator()( \ + ASIO_VARIADIC_MOVE_PARAMS(n)) const \ + { \ + return this->target_(ASIO_VARIADIC_MOVE_ARGS(n)); \ + } \ + /**/ + ASIO_VARIADIC_GENERATE(ASIO_PRIVATE_BIND_EXECUTOR_CALL_DEF) +#undef ASIO_PRIVATE_BIND_EXECUTOR_CALL_DEF + +#endif // defined(ASIO_HAS_STD_TYPE_TRAITS) && !defined(_MSC_VER) + +private: + typedef detail::executor_binder_base::value> base_type; +}; + +/// Associate an object of type @c T with an executor of type @c Executor. +template +inline executor_binder::type, Executor> +bind_executor(const Executor& ex, ASIO_MOVE_ARG(T) t, + typename enable_if< + is_executor::value || execution::is_executor::value + >::type* = 0) +{ + return executor_binder::type, Executor>( + executor_arg_t(), ex, ASIO_MOVE_CAST(T)(t)); +} + +/// Associate an object of type @c T with an execution context's executor. +template +inline executor_binder::type, + typename ExecutionContext::executor_type> +bind_executor(ExecutionContext& ctx, ASIO_MOVE_ARG(T) t, + typename enable_if::value>::type* = 0) +{ + return executor_binder::type, + typename ExecutionContext::executor_type>( + executor_arg_t(), ctx.get_executor(), ASIO_MOVE_CAST(T)(t)); +} + +#if !defined(GENERATING_DOCUMENTATION) + +template +struct uses_executor, Executor> + : true_type {}; + +template +class async_result, Signature> +{ +public: + typedef executor_binder< + typename async_result::completion_handler_type, Executor> + completion_handler_type; + + typedef typename async_result::return_type return_type; + + explicit async_result(executor_binder& b) + : target_(b.get()) + { + } + + return_type get() + { + return target_.get(); + } + +private: + async_result(const async_result&) ASIO_DELETED; + async_result& operator=(const async_result&) ASIO_DELETED; + + async_result target_; +}; + +template +struct associated_allocator, Allocator> +{ + typedef typename associated_allocator::type type; + + static type get(const executor_binder& b, + const Allocator& a = Allocator()) ASIO_NOEXCEPT + { + return associated_allocator::get(b.get(), a); + } +}; + +template +struct associated_executor, Executor1> +{ + typedef Executor type; + + static type get(const executor_binder& b, + const Executor1& = Executor1()) ASIO_NOEXCEPT + { + return b.get_executor(); + } +}; + +#endif // !defined(GENERATING_DOCUMENTATION) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_BIND_EXECUTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/buffer.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/buffer.hpp new file mode 100644 index 000000000..65e85c4bb --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/buffer.hpp @@ -0,0 +1,2496 @@ +// +// buffer.hpp +// ~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BUFFER_HPP +#define ASIO_BUFFER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include +#include +#include +#include +#include +#include "asio/detail/array_fwd.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/string_view.hpp" +#include "asio/detail/throw_exception.hpp" +#include "asio/detail/type_traits.hpp" + +#if defined(ASIO_MSVC) && (ASIO_MSVC >= 1700) +# if defined(_HAS_ITERATOR_DEBUGGING) && (_HAS_ITERATOR_DEBUGGING != 0) +# if !defined(ASIO_DISABLE_BUFFER_DEBUGGING) +# define ASIO_ENABLE_BUFFER_DEBUGGING +# endif // !defined(ASIO_DISABLE_BUFFER_DEBUGGING) +# endif // defined(_HAS_ITERATOR_DEBUGGING) +#endif // defined(ASIO_MSVC) && (ASIO_MSVC >= 1700) + +#if defined(__GNUC__) +# if defined(_GLIBCXX_DEBUG) +# if !defined(ASIO_DISABLE_BUFFER_DEBUGGING) +# define ASIO_ENABLE_BUFFER_DEBUGGING +# endif // !defined(ASIO_DISABLE_BUFFER_DEBUGGING) +# endif // defined(_GLIBCXX_DEBUG) +#endif // defined(__GNUC__) + +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) +# include "asio/detail/functional.hpp" +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + +#if defined(ASIO_HAS_BOOST_WORKAROUND) +# include +# if !defined(__clang__) +# if BOOST_WORKAROUND(__BORLANDC__, BOOST_TESTED_AT(0x582)) +# define ASIO_ENABLE_ARRAY_BUFFER_WORKAROUND +# endif // BOOST_WORKAROUND(__BORLANDC__, BOOST_TESTED_AT(0x582)) +# elif BOOST_WORKAROUND(__SUNPRO_CC, BOOST_TESTED_AT(0x590)) +# define ASIO_ENABLE_ARRAY_BUFFER_WORKAROUND +# endif // BOOST_WORKAROUND(__SUNPRO_CC, BOOST_TESTED_AT(0x590)) +#endif // defined(ASIO_HAS_BOOST_WORKAROUND) + +#if defined(ASIO_ENABLE_ARRAY_BUFFER_WORKAROUND) +# include "asio/detail/type_traits.hpp" +#endif // defined(ASIO_ENABLE_ARRAY_BUFFER_WORKAROUND) + +#include "asio/detail/push_options.hpp" + +namespace asio { + +class mutable_buffer; +class const_buffer; + +/// Holds a buffer that can be modified. +/** + * The mutable_buffer class provides a safe representation of a buffer that can + * be modified. It does not own the underlying data, and so is cheap to copy or + * assign. + * + * @par Accessing Buffer Contents + * + * The contents of a buffer may be accessed using the @c data() and @c size() + * member functions: + * + * @code asio::mutable_buffer b1 = ...; + * std::size_t s1 = b1.size(); + * unsigned char* p1 = static_cast(b1.data()); + * @endcode + * + * The @c data() member function permits violations of type safety, so uses of + * it in application code should be carefully considered. + */ +class mutable_buffer +{ +public: + /// Construct an empty buffer. + mutable_buffer() ASIO_NOEXCEPT + : data_(0), + size_(0) + { + } + + /// Construct a buffer to represent a given memory range. + mutable_buffer(void* data, std::size_t size) ASIO_NOEXCEPT + : data_(data), + size_(size) + { + } + +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + mutable_buffer(void* data, std::size_t size, + asio::detail::function debug_check) + : data_(data), + size_(size), + debug_check_(debug_check) + { + } + + const asio::detail::function& get_debug_check() const + { + return debug_check_; + } +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + + /// Get a pointer to the beginning of the memory range. + void* data() const ASIO_NOEXCEPT + { +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + if (size_ && debug_check_) + debug_check_(); +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + return data_; + } + + /// Get the size of the memory range. + std::size_t size() const ASIO_NOEXCEPT + { + return size_; + } + + /// Move the start of the buffer by the specified number of bytes. + mutable_buffer& operator+=(std::size_t n) ASIO_NOEXCEPT + { + std::size_t offset = n < size_ ? n : size_; + data_ = static_cast(data_) + offset; + size_ -= offset; + return *this; + } + +private: + void* data_; + std::size_t size_; + +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + asio::detail::function debug_check_; +#endif // ASIO_ENABLE_BUFFER_DEBUGGING +}; + +#if !defined(ASIO_NO_DEPRECATED) + +/// (Deprecated: Use mutable_buffer.) Adapts a single modifiable buffer so that +/// it meets the requirements of the MutableBufferSequence concept. +class mutable_buffers_1 + : public mutable_buffer +{ +public: + /// The type for each element in the list of buffers. + typedef mutable_buffer value_type; + + /// A random-access iterator type that may be used to read elements. + typedef const mutable_buffer* const_iterator; + + /// Construct to represent a given memory range. + mutable_buffers_1(void* data, std::size_t size) ASIO_NOEXCEPT + : mutable_buffer(data, size) + { + } + +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + mutable_buffers_1(void* data, std::size_t size, + asio::detail::function debug_check) + : mutable_buffer(data, size, debug_check) + { + } +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + + /// Construct to represent a single modifiable buffer. + explicit mutable_buffers_1(const mutable_buffer& b) ASIO_NOEXCEPT + : mutable_buffer(b) + { + } + + /// Get a random-access iterator to the first element. + const_iterator begin() const ASIO_NOEXCEPT + { + return this; + } + + /// Get a random-access iterator for one past the last element. + const_iterator end() const ASIO_NOEXCEPT + { + return begin() + 1; + } +}; + +#endif // !defined(ASIO_NO_DEPRECATED) + +/// Holds a buffer that cannot be modified. +/** + * The const_buffer class provides a safe representation of a buffer that cannot + * be modified. It does not own the underlying data, and so is cheap to copy or + * assign. + * + * @par Accessing Buffer Contents + * + * The contents of a buffer may be accessed using the @c data() and @c size() + * member functions: + * + * @code asio::const_buffer b1 = ...; + * std::size_t s1 = b1.size(); + * const unsigned char* p1 = static_cast(b1.data()); + * @endcode + * + * The @c data() member function permits violations of type safety, so uses of + * it in application code should be carefully considered. + */ +class const_buffer +{ +public: + /// Construct an empty buffer. + const_buffer() ASIO_NOEXCEPT + : data_(0), + size_(0) + { + } + + /// Construct a buffer to represent a given memory range. + const_buffer(const void* data, std::size_t size) ASIO_NOEXCEPT + : data_(data), + size_(size) + { + } + + /// Construct a non-modifiable buffer from a modifiable one. + const_buffer(const mutable_buffer& b) ASIO_NOEXCEPT + : data_(b.data()), + size_(b.size()) +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + , debug_check_(b.get_debug_check()) +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + { + } + +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + const_buffer(const void* data, std::size_t size, + asio::detail::function debug_check) + : data_(data), + size_(size), + debug_check_(debug_check) + { + } + + const asio::detail::function& get_debug_check() const + { + return debug_check_; + } +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + + /// Get a pointer to the beginning of the memory range. + const void* data() const ASIO_NOEXCEPT + { +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + if (size_ && debug_check_) + debug_check_(); +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + return data_; + } + + /// Get the size of the memory range. + std::size_t size() const ASIO_NOEXCEPT + { + return size_; + } + + /// Move the start of the buffer by the specified number of bytes. + const_buffer& operator+=(std::size_t n) ASIO_NOEXCEPT + { + std::size_t offset = n < size_ ? n : size_; + data_ = static_cast(data_) + offset; + size_ -= offset; + return *this; + } + +private: + const void* data_; + std::size_t size_; + +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + asio::detail::function debug_check_; +#endif // ASIO_ENABLE_BUFFER_DEBUGGING +}; + +#if !defined(ASIO_NO_DEPRECATED) + +/// (Deprecated: Use const_buffer.) Adapts a single non-modifiable buffer so +/// that it meets the requirements of the ConstBufferSequence concept. +class const_buffers_1 + : public const_buffer +{ +public: + /// The type for each element in the list of buffers. + typedef const_buffer value_type; + + /// A random-access iterator type that may be used to read elements. + typedef const const_buffer* const_iterator; + + /// Construct to represent a given memory range. + const_buffers_1(const void* data, std::size_t size) ASIO_NOEXCEPT + : const_buffer(data, size) + { + } + +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + const_buffers_1(const void* data, std::size_t size, + asio::detail::function debug_check) + : const_buffer(data, size, debug_check) + { + } +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + + /// Construct to represent a single non-modifiable buffer. + explicit const_buffers_1(const const_buffer& b) ASIO_NOEXCEPT + : const_buffer(b) + { + } + + /// Get a random-access iterator to the first element. + const_iterator begin() const ASIO_NOEXCEPT + { + return this; + } + + /// Get a random-access iterator for one past the last element. + const_iterator end() const ASIO_NOEXCEPT + { + return begin() + 1; + } +}; + +#endif // !defined(ASIO_NO_DEPRECATED) + +/// (Deprecated: Use the socket/descriptor wait() and async_wait() member +/// functions.) An implementation of both the ConstBufferSequence and +/// MutableBufferSequence concepts to represent a null buffer sequence. +class null_buffers +{ +public: + /// The type for each element in the list of buffers. + typedef mutable_buffer value_type; + + /// A random-access iterator type that may be used to read elements. + typedef const mutable_buffer* const_iterator; + + /// Get a random-access iterator to the first element. + const_iterator begin() const ASIO_NOEXCEPT + { + return &buf_; + } + + /// Get a random-access iterator for one past the last element. + const_iterator end() const ASIO_NOEXCEPT + { + return &buf_; + } + +private: + mutable_buffer buf_; +}; + +/** @defgroup buffer_sequence_begin asio::buffer_sequence_begin + * + * @brief The asio::buffer_sequence_begin function returns an iterator + * pointing to the first element in a buffer sequence. + */ +/*@{*/ + +/// Get an iterator to the first element in a buffer sequence. +template +inline const mutable_buffer* buffer_sequence_begin(const MutableBuffer& b, + typename enable_if< + is_convertible::value + >::type* = 0) ASIO_NOEXCEPT +{ + return static_cast(detail::addressof(b)); +} + +/// Get an iterator to the first element in a buffer sequence. +template +inline const const_buffer* buffer_sequence_begin(const ConstBuffer& b, + typename enable_if< + is_convertible::value + >::type* = 0) ASIO_NOEXCEPT +{ + return static_cast(detail::addressof(b)); +} + +#if defined(ASIO_HAS_DECLTYPE) || defined(GENERATING_DOCUMENTATION) + +/// Get an iterator to the first element in a buffer sequence. +template +inline auto buffer_sequence_begin(C& c, + typename enable_if< + !is_convertible::value + && !is_convertible::value + >::type* = 0) ASIO_NOEXCEPT -> decltype(c.begin()) +{ + return c.begin(); +} + +/// Get an iterator to the first element in a buffer sequence. +template +inline auto buffer_sequence_begin(const C& c, + typename enable_if< + !is_convertible::value + && !is_convertible::value + >::type* = 0) ASIO_NOEXCEPT -> decltype(c.begin()) +{ + return c.begin(); +} + +#else // defined(ASIO_HAS_DECLTYPE) || defined(GENERATING_DOCUMENTATION) + +template +inline typename C::iterator buffer_sequence_begin(C& c, + typename enable_if< + !is_convertible::value + && !is_convertible::value + >::type* = 0) ASIO_NOEXCEPT +{ + return c.begin(); +} + +template +inline typename C::const_iterator buffer_sequence_begin(const C& c, + typename enable_if< + !is_convertible::value + && !is_convertible::value + >::type* = 0) ASIO_NOEXCEPT +{ + return c.begin(); +} + +#endif // defined(ASIO_HAS_DECLTYPE) || defined(GENERATING_DOCUMENTATION) + +/*@}*/ + +/** @defgroup buffer_sequence_end asio::buffer_sequence_end + * + * @brief The asio::buffer_sequence_end function returns an iterator + * pointing to one past the end element in a buffer sequence. + */ +/*@{*/ + +/// Get an iterator to one past the end element in a buffer sequence. +template +inline const mutable_buffer* buffer_sequence_end(const MutableBuffer& b, + typename enable_if< + is_convertible::value + >::type* = 0) ASIO_NOEXCEPT +{ + return static_cast(detail::addressof(b)) + 1; +} + +/// Get an iterator to one past the end element in a buffer sequence. +template +inline const const_buffer* buffer_sequence_end(const ConstBuffer& b, + typename enable_if< + is_convertible::value + >::type* = 0) ASIO_NOEXCEPT +{ + return static_cast(detail::addressof(b)) + 1; +} + +#if defined(ASIO_HAS_DECLTYPE) || defined(GENERATING_DOCUMENTATION) + +/// Get an iterator to one past the end element in a buffer sequence. +template +inline auto buffer_sequence_end(C& c, + typename enable_if< + !is_convertible::value + && !is_convertible::value + >::type* = 0) ASIO_NOEXCEPT -> decltype(c.end()) +{ + return c.end(); +} + +/// Get an iterator to one past the end element in a buffer sequence. +template +inline auto buffer_sequence_end(const C& c, + typename enable_if< + !is_convertible::value + && !is_convertible::value + >::type* = 0) ASIO_NOEXCEPT -> decltype(c.end()) +{ + return c.end(); +} + +#else // defined(ASIO_HAS_DECLTYPE) || defined(GENERATING_DOCUMENTATION) + +template +inline typename C::iterator buffer_sequence_end(C& c, + typename enable_if< + !is_convertible::value + && !is_convertible::value + >::type* = 0) ASIO_NOEXCEPT +{ + return c.end(); +} + +template +inline typename C::const_iterator buffer_sequence_end(const C& c, + typename enable_if< + !is_convertible::value + && !is_convertible::value + >::type* = 0) ASIO_NOEXCEPT +{ + return c.end(); +} + +#endif // defined(ASIO_HAS_DECLTYPE) || defined(GENERATING_DOCUMENTATION) + +/*@}*/ + +namespace detail { + +// Tag types used to select appropriately optimised overloads. +struct one_buffer {}; +struct multiple_buffers {}; + +// Helper trait to detect single buffers. +template +struct buffer_sequence_cardinality : + conditional< + is_same::value +#if !defined(ASIO_NO_DEPRECATED) + || is_same::value + || is_same::value +#endif // !defined(ASIO_NO_DEPRECATED) + || is_same::value, + one_buffer, multiple_buffers>::type {}; + +template +inline std::size_t buffer_size(one_buffer, + Iterator begin, Iterator) ASIO_NOEXCEPT +{ + return const_buffer(*begin).size(); +} + +template +inline std::size_t buffer_size(multiple_buffers, + Iterator begin, Iterator end) ASIO_NOEXCEPT +{ + std::size_t total_buffer_size = 0; + + Iterator iter = begin; + for (; iter != end; ++iter) + { + const_buffer b(*iter); + total_buffer_size += b.size(); + } + + return total_buffer_size; +} + +} // namespace detail + +/// Get the total number of bytes in a buffer sequence. +/** + * The @c buffer_size function determines the total size of all buffers in the + * buffer sequence, as if computed as follows: + * + * @code size_t total_size = 0; + * auto i = asio::buffer_sequence_begin(buffers); + * auto end = asio::buffer_sequence_end(buffers); + * for (; i != end; ++i) + * { + * const_buffer b(*i); + * total_size += b.size(); + * } + * return total_size; @endcode + * + * The @c BufferSequence template parameter may meet either of the @c + * ConstBufferSequence or @c MutableBufferSequence type requirements. + */ +template +inline std::size_t buffer_size(const BufferSequence& b) ASIO_NOEXCEPT +{ + return detail::buffer_size( + detail::buffer_sequence_cardinality(), + asio::buffer_sequence_begin(b), + asio::buffer_sequence_end(b)); +} + +#if !defined(ASIO_NO_DEPRECATED) + +/** @defgroup buffer_cast asio::buffer_cast + * + * @brief (Deprecated: Use the @c data() member function.) The + * asio::buffer_cast function is used to obtain a pointer to the + * underlying memory region associated with a buffer. + * + * @par Examples: + * + * To access the memory of a non-modifiable buffer, use: + * @code asio::const_buffer b1 = ...; + * const unsigned char* p1 = asio::buffer_cast(b1); + * @endcode + * + * To access the memory of a modifiable buffer, use: + * @code asio::mutable_buffer b2 = ...; + * unsigned char* p2 = asio::buffer_cast(b2); + * @endcode + * + * The asio::buffer_cast function permits violations of type safety, so + * uses of it in application code should be carefully considered. + */ +/*@{*/ + +/// Cast a non-modifiable buffer to a specified pointer to POD type. +template +inline PointerToPodType buffer_cast(const mutable_buffer& b) ASIO_NOEXCEPT +{ + return static_cast(b.data()); +} + +/// Cast a non-modifiable buffer to a specified pointer to POD type. +template +inline PointerToPodType buffer_cast(const const_buffer& b) ASIO_NOEXCEPT +{ + return static_cast(b.data()); +} + +/*@}*/ + +#endif // !defined(ASIO_NO_DEPRECATED) + +/// Create a new modifiable buffer that is offset from the start of another. +/** + * @relates mutable_buffer + */ +inline mutable_buffer operator+(const mutable_buffer& b, + std::size_t n) ASIO_NOEXCEPT +{ + std::size_t offset = n < b.size() ? n : b.size(); + char* new_data = static_cast(b.data()) + offset; + std::size_t new_size = b.size() - offset; + return mutable_buffer(new_data, new_size +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + , b.get_debug_check() +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + ); +} + +/// Create a new modifiable buffer that is offset from the start of another. +/** + * @relates mutable_buffer + */ +inline mutable_buffer operator+(std::size_t n, + const mutable_buffer& b) ASIO_NOEXCEPT +{ + return b + n; +} + +/// Create a new non-modifiable buffer that is offset from the start of another. +/** + * @relates const_buffer + */ +inline const_buffer operator+(const const_buffer& b, + std::size_t n) ASIO_NOEXCEPT +{ + std::size_t offset = n < b.size() ? n : b.size(); + const char* new_data = static_cast(b.data()) + offset; + std::size_t new_size = b.size() - offset; + return const_buffer(new_data, new_size +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + , b.get_debug_check() +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + ); +} + +/// Create a new non-modifiable buffer that is offset from the start of another. +/** + * @relates const_buffer + */ +inline const_buffer operator+(std::size_t n, + const const_buffer& b) ASIO_NOEXCEPT +{ + return b + n; +} + +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) +namespace detail { + +template +class buffer_debug_check +{ +public: + buffer_debug_check(Iterator iter) + : iter_(iter) + { + } + + ~buffer_debug_check() + { +#if defined(ASIO_MSVC) && (ASIO_MSVC == 1400) + // MSVC 8's string iterator checking may crash in a std::string::iterator + // object's destructor when the iterator points to an already-destroyed + // std::string object, unless the iterator is cleared first. + iter_ = Iterator(); +#endif // defined(ASIO_MSVC) && (ASIO_MSVC == 1400) + } + + void operator()() + { + (void)*iter_; + } + +private: + Iterator iter_; +}; + +} // namespace detail +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + +/** @defgroup buffer asio::buffer + * + * @brief The asio::buffer function is used to create a buffer object to + * represent raw memory, an array of POD elements, a vector of POD elements, + * or a std::string. + * + * A buffer object represents a contiguous region of memory as a 2-tuple + * consisting of a pointer and size in bytes. A tuple of the form {void*, + * size_t} specifies a mutable (modifiable) region of memory. Similarly, a + * tuple of the form {const void*, size_t} specifies a const + * (non-modifiable) region of memory. These two forms correspond to the classes + * mutable_buffer and const_buffer, respectively. To mirror C++'s conversion + * rules, a mutable_buffer is implicitly convertible to a const_buffer, and the + * opposite conversion is not permitted. + * + * The simplest use case involves reading or writing a single buffer of a + * specified size: + * + * @code sock.send(asio::buffer(data, size)); @endcode + * + * In the above example, the return value of asio::buffer meets the + * requirements of the ConstBufferSequence concept so that it may be directly + * passed to the socket's write function. A buffer created for modifiable + * memory also meets the requirements of the MutableBufferSequence concept. + * + * An individual buffer may be created from a builtin array, std::vector, + * std::array or boost::array of POD elements. This helps prevent buffer + * overruns by automatically determining the size of the buffer: + * + * @code char d1[128]; + * size_t bytes_transferred = sock.receive(asio::buffer(d1)); + * + * std::vector d2(128); + * bytes_transferred = sock.receive(asio::buffer(d2)); + * + * std::array d3; + * bytes_transferred = sock.receive(asio::buffer(d3)); + * + * boost::array d4; + * bytes_transferred = sock.receive(asio::buffer(d4)); @endcode + * + * In all three cases above, the buffers created are exactly 128 bytes long. + * Note that a vector is @e never automatically resized when creating or using + * a buffer. The buffer size is determined using the vector's size() + * member function, and not its capacity. + * + * @par Accessing Buffer Contents + * + * The contents of a buffer may be accessed using the @c data() and @c size() + * member functions: + * + * @code asio::mutable_buffer b1 = ...; + * std::size_t s1 = b1.size(); + * unsigned char* p1 = static_cast(b1.data()); + * + * asio::const_buffer b2 = ...; + * std::size_t s2 = b2.size(); + * const void* p2 = b2.data(); @endcode + * + * The @c data() member function permits violations of type safety, so + * uses of it in application code should be carefully considered. + * + * For convenience, a @ref buffer_size function is provided that works with + * both buffers and buffer sequences (that is, types meeting the + * ConstBufferSequence or MutableBufferSequence type requirements). In this + * case, the function returns the total size of all buffers in the sequence. + * + * @par Buffer Copying + * + * The @ref buffer_copy function may be used to copy raw bytes between + * individual buffers and buffer sequences. +* + * In particular, when used with the @ref buffer_size function, the @ref + * buffer_copy function can be used to linearise a sequence of buffers. For + * example: + * + * @code vector buffers = ...; + * + * vector data(asio::buffer_size(buffers)); + * asio::buffer_copy(asio::buffer(data), buffers); @endcode + * + * Note that @ref buffer_copy is implemented in terms of @c memcpy, and + * consequently it cannot be used to copy between overlapping memory regions. + * + * @par Buffer Invalidation + * + * A buffer object does not have any ownership of the memory it refers to. It + * is the responsibility of the application to ensure the memory region remains + * valid until it is no longer required for an I/O operation. When the memory + * is no longer available, the buffer is said to have been invalidated. + * + * For the asio::buffer overloads that accept an argument of type + * std::vector, the buffer objects returned are invalidated by any vector + * operation that also invalidates all references, pointers and iterators + * referring to the elements in the sequence (C++ Std, 23.2.4) + * + * For the asio::buffer overloads that accept an argument of type + * std::basic_string, the buffer objects returned are invalidated according to + * the rules defined for invalidation of references, pointers and iterators + * referring to elements of the sequence (C++ Std, 21.3). + * + * @par Buffer Arithmetic + * + * Buffer objects may be manipulated using simple arithmetic in a safe way + * which helps prevent buffer overruns. Consider an array initialised as + * follows: + * + * @code boost::array a = { 'a', 'b', 'c', 'd', 'e' }; @endcode + * + * A buffer object @c b1 created using: + * + * @code b1 = asio::buffer(a); @endcode + * + * represents the entire array, { 'a', 'b', 'c', 'd', 'e' }. An + * optional second argument to the asio::buffer function may be used to + * limit the size, in bytes, of the buffer: + * + * @code b2 = asio::buffer(a, 3); @endcode + * + * such that @c b2 represents the data { 'a', 'b', 'c' }. Even if the + * size argument exceeds the actual size of the array, the size of the buffer + * object created will be limited to the array size. + * + * An offset may be applied to an existing buffer to create a new one: + * + * @code b3 = b1 + 2; @endcode + * + * where @c b3 will set to represent { 'c', 'd', 'e' }. If the offset + * exceeds the size of the existing buffer, the newly created buffer will be + * empty. + * + * Both an offset and size may be specified to create a buffer that corresponds + * to a specific range of bytes within an existing buffer: + * + * @code b4 = asio::buffer(b1 + 1, 3); @endcode + * + * so that @c b4 will refer to the bytes { 'b', 'c', 'd' }. + * + * @par Buffers and Scatter-Gather I/O + * + * To read or write using multiple buffers (i.e. scatter-gather I/O), multiple + * buffer objects may be assigned into a container that supports the + * MutableBufferSequence (for read) or ConstBufferSequence (for write) concepts: + * + * @code + * char d1[128]; + * std::vector d2(128); + * boost::array d3; + * + * boost::array bufs1 = { + * asio::buffer(d1), + * asio::buffer(d2), + * asio::buffer(d3) }; + * bytes_transferred = sock.receive(bufs1); + * + * std::vector bufs2; + * bufs2.push_back(asio::buffer(d1)); + * bufs2.push_back(asio::buffer(d2)); + * bufs2.push_back(asio::buffer(d3)); + * bytes_transferred = sock.send(bufs2); @endcode + */ +/*@{*/ + +#if defined(ASIO_NO_DEPRECATED) || defined(GENERATING_DOCUMENTATION) +# define ASIO_MUTABLE_BUFFER mutable_buffer +# define ASIO_CONST_BUFFER const_buffer +#else // defined(ASIO_NO_DEPRECATED) || defined(GENERATING_DOCUMENTATION) +# define ASIO_MUTABLE_BUFFER mutable_buffers_1 +# define ASIO_CONST_BUFFER const_buffers_1 +#endif // defined(ASIO_NO_DEPRECATED) || defined(GENERATING_DOCUMENTATION) + +/// Create a new modifiable buffer from an existing buffer. +/** + * @returns mutable_buffer(b). + */ +inline ASIO_MUTABLE_BUFFER buffer( + const mutable_buffer& b) ASIO_NOEXCEPT +{ + return ASIO_MUTABLE_BUFFER(b); +} + +/// Create a new modifiable buffer from an existing buffer. +/** + * @returns A mutable_buffer value equivalent to: + * @code mutable_buffer( + * b.data(), + * min(b.size(), max_size_in_bytes)); @endcode + */ +inline ASIO_MUTABLE_BUFFER buffer(const mutable_buffer& b, + std::size_t max_size_in_bytes) ASIO_NOEXCEPT +{ + return ASIO_MUTABLE_BUFFER( + mutable_buffer(b.data(), + b.size() < max_size_in_bytes + ? b.size() : max_size_in_bytes +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + , b.get_debug_check() +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + )); +} + +/// Create a new non-modifiable buffer from an existing buffer. +/** + * @returns const_buffer(b). + */ +inline ASIO_CONST_BUFFER buffer( + const const_buffer& b) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(b); +} + +/// Create a new non-modifiable buffer from an existing buffer. +/** + * @returns A const_buffer value equivalent to: + * @code const_buffer( + * b.data(), + * min(b.size(), max_size_in_bytes)); @endcode + */ +inline ASIO_CONST_BUFFER buffer(const const_buffer& b, + std::size_t max_size_in_bytes) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(b.data(), + b.size() < max_size_in_bytes + ? b.size() : max_size_in_bytes +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + , b.get_debug_check() +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + ); +} + +/// Create a new modifiable buffer that represents the given memory range. +/** + * @returns mutable_buffer(data, size_in_bytes). + */ +inline ASIO_MUTABLE_BUFFER buffer(void* data, + std::size_t size_in_bytes) ASIO_NOEXCEPT +{ + return ASIO_MUTABLE_BUFFER(data, size_in_bytes); +} + +/// Create a new non-modifiable buffer that represents the given memory range. +/** + * @returns const_buffer(data, size_in_bytes). + */ +inline ASIO_CONST_BUFFER buffer(const void* data, + std::size_t size_in_bytes) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(data, size_in_bytes); +} + +/// Create a new modifiable buffer that represents the given POD array. +/** + * @returns A mutable_buffer value equivalent to: + * @code mutable_buffer( + * static_cast(data), + * N * sizeof(PodType)); @endcode + */ +template +inline ASIO_MUTABLE_BUFFER buffer(PodType (&data)[N]) ASIO_NOEXCEPT +{ + return ASIO_MUTABLE_BUFFER(data, N * sizeof(PodType)); +} + +/// Create a new modifiable buffer that represents the given POD array. +/** + * @returns A mutable_buffer value equivalent to: + * @code mutable_buffer( + * static_cast(data), + * min(N * sizeof(PodType), max_size_in_bytes)); @endcode + */ +template +inline ASIO_MUTABLE_BUFFER buffer(PodType (&data)[N], + std::size_t max_size_in_bytes) ASIO_NOEXCEPT +{ + return ASIO_MUTABLE_BUFFER(data, + N * sizeof(PodType) < max_size_in_bytes + ? N * sizeof(PodType) : max_size_in_bytes); +} + +/// Create a new non-modifiable buffer that represents the given POD array. +/** + * @returns A const_buffer value equivalent to: + * @code const_buffer( + * static_cast(data), + * N * sizeof(PodType)); @endcode + */ +template +inline ASIO_CONST_BUFFER buffer( + const PodType (&data)[N]) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(data, N * sizeof(PodType)); +} + +/// Create a new non-modifiable buffer that represents the given POD array. +/** + * @returns A const_buffer value equivalent to: + * @code const_buffer( + * static_cast(data), + * min(N * sizeof(PodType), max_size_in_bytes)); @endcode + */ +template +inline ASIO_CONST_BUFFER buffer(const PodType (&data)[N], + std::size_t max_size_in_bytes) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(data, + N * sizeof(PodType) < max_size_in_bytes + ? N * sizeof(PodType) : max_size_in_bytes); +} + +#if defined(ASIO_ENABLE_ARRAY_BUFFER_WORKAROUND) + +// Borland C++ and Sun Studio think the overloads: +// +// unspecified buffer(boost::array& array ...); +// +// and +// +// unspecified buffer(boost::array& array ...); +// +// are ambiguous. This will be worked around by using a buffer_types traits +// class that contains typedefs for the appropriate buffer and container +// classes, based on whether PodType is const or non-const. + +namespace detail { + +template +struct buffer_types_base; + +template <> +struct buffer_types_base +{ + typedef mutable_buffer buffer_type; + typedef ASIO_MUTABLE_BUFFER container_type; +}; + +template <> +struct buffer_types_base +{ + typedef const_buffer buffer_type; + typedef ASIO_CONST_BUFFER container_type; +}; + +template +struct buffer_types + : public buffer_types_base::value> +{ +}; + +} // namespace detail + +template +inline typename detail::buffer_types::container_type +buffer(boost::array& data) ASIO_NOEXCEPT +{ + typedef typename asio::detail::buffer_types::buffer_type + buffer_type; + typedef typename asio::detail::buffer_types::container_type + container_type; + return container_type( + buffer_type(data.c_array(), data.size() * sizeof(PodType))); +} + +template +inline typename detail::buffer_types::container_type +buffer(boost::array& data, + std::size_t max_size_in_bytes) ASIO_NOEXCEPT +{ + typedef typename asio::detail::buffer_types::buffer_type + buffer_type; + typedef typename asio::detail::buffer_types::container_type + container_type; + return container_type( + buffer_type(data.c_array(), + data.size() * sizeof(PodType) < max_size_in_bytes + ? data.size() * sizeof(PodType) : max_size_in_bytes)); +} + +#else // defined(ASIO_ENABLE_ARRAY_BUFFER_WORKAROUND) + +/// Create a new modifiable buffer that represents the given POD array. +/** + * @returns A mutable_buffer value equivalent to: + * @code mutable_buffer( + * data.data(), + * data.size() * sizeof(PodType)); @endcode + */ +template +inline ASIO_MUTABLE_BUFFER buffer( + boost::array& data) ASIO_NOEXCEPT +{ + return ASIO_MUTABLE_BUFFER( + data.c_array(), data.size() * sizeof(PodType)); +} + +/// Create a new modifiable buffer that represents the given POD array. +/** + * @returns A mutable_buffer value equivalent to: + * @code mutable_buffer( + * data.data(), + * min(data.size() * sizeof(PodType), max_size_in_bytes)); @endcode + */ +template +inline ASIO_MUTABLE_BUFFER buffer(boost::array& data, + std::size_t max_size_in_bytes) ASIO_NOEXCEPT +{ + return ASIO_MUTABLE_BUFFER(data.c_array(), + data.size() * sizeof(PodType) < max_size_in_bytes + ? data.size() * sizeof(PodType) : max_size_in_bytes); +} + +/// Create a new non-modifiable buffer that represents the given POD array. +/** + * @returns A const_buffer value equivalent to: + * @code const_buffer( + * data.data(), + * data.size() * sizeof(PodType)); @endcode + */ +template +inline ASIO_CONST_BUFFER buffer( + boost::array& data) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(data.data(), data.size() * sizeof(PodType)); +} + +/// Create a new non-modifiable buffer that represents the given POD array. +/** + * @returns A const_buffer value equivalent to: + * @code const_buffer( + * data.data(), + * min(data.size() * sizeof(PodType), max_size_in_bytes)); @endcode + */ +template +inline ASIO_CONST_BUFFER buffer(boost::array& data, + std::size_t max_size_in_bytes) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(data.data(), + data.size() * sizeof(PodType) < max_size_in_bytes + ? data.size() * sizeof(PodType) : max_size_in_bytes); +} + +#endif // defined(ASIO_ENABLE_ARRAY_BUFFER_WORKAROUND) + +/// Create a new non-modifiable buffer that represents the given POD array. +/** + * @returns A const_buffer value equivalent to: + * @code const_buffer( + * data.data(), + * data.size() * sizeof(PodType)); @endcode + */ +template +inline ASIO_CONST_BUFFER buffer( + const boost::array& data) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(data.data(), data.size() * sizeof(PodType)); +} + +/// Create a new non-modifiable buffer that represents the given POD array. +/** + * @returns A const_buffer value equivalent to: + * @code const_buffer( + * data.data(), + * min(data.size() * sizeof(PodType), max_size_in_bytes)); @endcode + */ +template +inline ASIO_CONST_BUFFER buffer(const boost::array& data, + std::size_t max_size_in_bytes) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(data.data(), + data.size() * sizeof(PodType) < max_size_in_bytes + ? data.size() * sizeof(PodType) : max_size_in_bytes); +} + +#if defined(ASIO_HAS_STD_ARRAY) || defined(GENERATING_DOCUMENTATION) + +/// Create a new modifiable buffer that represents the given POD array. +/** + * @returns A mutable_buffer value equivalent to: + * @code mutable_buffer( + * data.data(), + * data.size() * sizeof(PodType)); @endcode + */ +template +inline ASIO_MUTABLE_BUFFER buffer( + std::array& data) ASIO_NOEXCEPT +{ + return ASIO_MUTABLE_BUFFER(data.data(), data.size() * sizeof(PodType)); +} + +/// Create a new modifiable buffer that represents the given POD array. +/** + * @returns A mutable_buffer value equivalent to: + * @code mutable_buffer( + * data.data(), + * min(data.size() * sizeof(PodType), max_size_in_bytes)); @endcode + */ +template +inline ASIO_MUTABLE_BUFFER buffer(std::array& data, + std::size_t max_size_in_bytes) ASIO_NOEXCEPT +{ + return ASIO_MUTABLE_BUFFER(data.data(), + data.size() * sizeof(PodType) < max_size_in_bytes + ? data.size() * sizeof(PodType) : max_size_in_bytes); +} + +/// Create a new non-modifiable buffer that represents the given POD array. +/** + * @returns A const_buffer value equivalent to: + * @code const_buffer( + * data.data(), + * data.size() * sizeof(PodType)); @endcode + */ +template +inline ASIO_CONST_BUFFER buffer( + std::array& data) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(data.data(), data.size() * sizeof(PodType)); +} + +/// Create a new non-modifiable buffer that represents the given POD array. +/** + * @returns A const_buffer value equivalent to: + * @code const_buffer( + * data.data(), + * min(data.size() * sizeof(PodType), max_size_in_bytes)); @endcode + */ +template +inline ASIO_CONST_BUFFER buffer(std::array& data, + std::size_t max_size_in_bytes) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(data.data(), + data.size() * sizeof(PodType) < max_size_in_bytes + ? data.size() * sizeof(PodType) : max_size_in_bytes); +} + +/// Create a new non-modifiable buffer that represents the given POD array. +/** + * @returns A const_buffer value equivalent to: + * @code const_buffer( + * data.data(), + * data.size() * sizeof(PodType)); @endcode + */ +template +inline ASIO_CONST_BUFFER buffer( + const std::array& data) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(data.data(), data.size() * sizeof(PodType)); +} + +/// Create a new non-modifiable buffer that represents the given POD array. +/** + * @returns A const_buffer value equivalent to: + * @code const_buffer( + * data.data(), + * min(data.size() * sizeof(PodType), max_size_in_bytes)); @endcode + */ +template +inline ASIO_CONST_BUFFER buffer(const std::array& data, + std::size_t max_size_in_bytes) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(data.data(), + data.size() * sizeof(PodType) < max_size_in_bytes + ? data.size() * sizeof(PodType) : max_size_in_bytes); +} + +#endif // defined(ASIO_HAS_STD_ARRAY) || defined(GENERATING_DOCUMENTATION) + +/// Create a new modifiable buffer that represents the given POD vector. +/** + * @returns A mutable_buffer value equivalent to: + * @code mutable_buffer( + * data.size() ? &data[0] : 0, + * data.size() * sizeof(PodType)); @endcode + * + * @note The buffer is invalidated by any vector operation that would also + * invalidate iterators. + */ +template +inline ASIO_MUTABLE_BUFFER buffer( + std::vector& data) ASIO_NOEXCEPT +{ + return ASIO_MUTABLE_BUFFER( + data.size() ? &data[0] : 0, data.size() * sizeof(PodType) +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + , detail::buffer_debug_check< + typename std::vector::iterator + >(data.begin()) +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + ); +} + +/// Create a new modifiable buffer that represents the given POD vector. +/** + * @returns A mutable_buffer value equivalent to: + * @code mutable_buffer( + * data.size() ? &data[0] : 0, + * min(data.size() * sizeof(PodType), max_size_in_bytes)); @endcode + * + * @note The buffer is invalidated by any vector operation that would also + * invalidate iterators. + */ +template +inline ASIO_MUTABLE_BUFFER buffer(std::vector& data, + std::size_t max_size_in_bytes) ASIO_NOEXCEPT +{ + return ASIO_MUTABLE_BUFFER(data.size() ? &data[0] : 0, + data.size() * sizeof(PodType) < max_size_in_bytes + ? data.size() * sizeof(PodType) : max_size_in_bytes +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + , detail::buffer_debug_check< + typename std::vector::iterator + >(data.begin()) +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + ); +} + +/// Create a new non-modifiable buffer that represents the given POD vector. +/** + * @returns A const_buffer value equivalent to: + * @code const_buffer( + * data.size() ? &data[0] : 0, + * data.size() * sizeof(PodType)); @endcode + * + * @note The buffer is invalidated by any vector operation that would also + * invalidate iterators. + */ +template +inline ASIO_CONST_BUFFER buffer( + const std::vector& data) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER( + data.size() ? &data[0] : 0, data.size() * sizeof(PodType) +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + , detail::buffer_debug_check< + typename std::vector::const_iterator + >(data.begin()) +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + ); +} + +/// Create a new non-modifiable buffer that represents the given POD vector. +/** + * @returns A const_buffer value equivalent to: + * @code const_buffer( + * data.size() ? &data[0] : 0, + * min(data.size() * sizeof(PodType), max_size_in_bytes)); @endcode + * + * @note The buffer is invalidated by any vector operation that would also + * invalidate iterators. + */ +template +inline ASIO_CONST_BUFFER buffer( + const std::vector& data, + std::size_t max_size_in_bytes) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(data.size() ? &data[0] : 0, + data.size() * sizeof(PodType) < max_size_in_bytes + ? data.size() * sizeof(PodType) : max_size_in_bytes +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + , detail::buffer_debug_check< + typename std::vector::const_iterator + >(data.begin()) +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + ); +} + +/// Create a new modifiable buffer that represents the given string. +/** + * @returns mutable_buffer(data.size() ? &data[0] : 0, + * data.size() * sizeof(Elem)). + * + * @note The buffer is invalidated by any non-const operation called on the + * given string object. + */ +template +inline ASIO_MUTABLE_BUFFER buffer( + std::basic_string& data) ASIO_NOEXCEPT +{ + return ASIO_MUTABLE_BUFFER(data.size() ? &data[0] : 0, + data.size() * sizeof(Elem) +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + , detail::buffer_debug_check< + typename std::basic_string::iterator + >(data.begin()) +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + ); +} + +/// Create a new modifiable buffer that represents the given string. +/** + * @returns A mutable_buffer value equivalent to: + * @code mutable_buffer( + * data.size() ? &data[0] : 0, + * min(data.size() * sizeof(Elem), max_size_in_bytes)); @endcode + * + * @note The buffer is invalidated by any non-const operation called on the + * given string object. + */ +template +inline ASIO_MUTABLE_BUFFER buffer( + std::basic_string& data, + std::size_t max_size_in_bytes) ASIO_NOEXCEPT +{ + return ASIO_MUTABLE_BUFFER(data.size() ? &data[0] : 0, + data.size() * sizeof(Elem) < max_size_in_bytes + ? data.size() * sizeof(Elem) : max_size_in_bytes +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + , detail::buffer_debug_check< + typename std::basic_string::iterator + >(data.begin()) +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + ); +} + +/// Create a new non-modifiable buffer that represents the given string. +/** + * @returns const_buffer(data.data(), data.size() * sizeof(Elem)). + * + * @note The buffer is invalidated by any non-const operation called on the + * given string object. + */ +template +inline ASIO_CONST_BUFFER buffer( + const std::basic_string& data) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(data.data(), data.size() * sizeof(Elem) +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + , detail::buffer_debug_check< + typename std::basic_string::const_iterator + >(data.begin()) +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + ); +} + +/// Create a new non-modifiable buffer that represents the given string. +/** + * @returns A const_buffer value equivalent to: + * @code const_buffer( + * data.data(), + * min(data.size() * sizeof(Elem), max_size_in_bytes)); @endcode + * + * @note The buffer is invalidated by any non-const operation called on the + * given string object. + */ +template +inline ASIO_CONST_BUFFER buffer( + const std::basic_string& data, + std::size_t max_size_in_bytes) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(data.data(), + data.size() * sizeof(Elem) < max_size_in_bytes + ? data.size() * sizeof(Elem) : max_size_in_bytes +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + , detail::buffer_debug_check< + typename std::basic_string::const_iterator + >(data.begin()) +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + ); +} + +#if defined(ASIO_HAS_STRING_VIEW) \ + || defined(GENERATING_DOCUMENTATION) + +/// Create a new modifiable buffer that represents the given string_view. +/** + * @returns mutable_buffer(data.size() ? &data[0] : 0, + * data.size() * sizeof(Elem)). + */ +template +inline ASIO_CONST_BUFFER buffer( + basic_string_view data) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(data.size() ? &data[0] : 0, + data.size() * sizeof(Elem) +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + , detail::buffer_debug_check< + typename basic_string_view::iterator + >(data.begin()) +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + ); +} + +/// Create a new non-modifiable buffer that represents the given string. +/** + * @returns A mutable_buffer value equivalent to: + * @code mutable_buffer( + * data.size() ? &data[0] : 0, + * min(data.size() * sizeof(Elem), max_size_in_bytes)); @endcode + */ +template +inline ASIO_CONST_BUFFER buffer( + basic_string_view data, + std::size_t max_size_in_bytes) ASIO_NOEXCEPT +{ + return ASIO_CONST_BUFFER(data.size() ? &data[0] : 0, + data.size() * sizeof(Elem) < max_size_in_bytes + ? data.size() * sizeof(Elem) : max_size_in_bytes +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + , detail::buffer_debug_check< + typename basic_string_view::iterator + >(data.begin()) +#endif // ASIO_ENABLE_BUFFER_DEBUGGING + ); +} + +#endif // defined(ASIO_HAS_STRING_VIEW) + // || defined(GENERATING_DOCUMENTATION) + +/*@}*/ + +/// Adapt a basic_string to the DynamicBuffer requirements. +/** + * Requires that sizeof(Elem) == 1. + */ +template +class dynamic_string_buffer +{ +public: + /// The type used to represent a sequence of constant buffers that refers to + /// the underlying memory. + typedef ASIO_CONST_BUFFER const_buffers_type; + + /// The type used to represent a sequence of mutable buffers that refers to + /// the underlying memory. + typedef ASIO_MUTABLE_BUFFER mutable_buffers_type; + + /// Construct a dynamic buffer from a string. + /** + * @param s The string to be used as backing storage for the dynamic buffer. + * The object stores a reference to the string and the user is responsible + * for ensuring that the string object remains valid while the + * dynamic_string_buffer object, and copies of the object, are in use. + * + * @b DynamicBuffer_v1: Any existing data in the string is treated as the + * dynamic buffer's input sequence. + * + * @param maximum_size Specifies a maximum size for the buffer, in bytes. + */ + explicit dynamic_string_buffer(std::basic_string& s, + std::size_t maximum_size = + (std::numeric_limits::max)()) ASIO_NOEXCEPT + : string_(s), +#if !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + size_((std::numeric_limits::max)()), +#endif // !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + max_size_(maximum_size) + { + } + + /// @b DynamicBuffer_v2: Copy construct a dynamic buffer. + dynamic_string_buffer(const dynamic_string_buffer& other) ASIO_NOEXCEPT + : string_(other.string_), +#if !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + size_(other.size_), +#endif // !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + max_size_(other.max_size_) + { + } + +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + /// Move construct a dynamic buffer. + dynamic_string_buffer(dynamic_string_buffer&& other) ASIO_NOEXCEPT + : string_(other.string_), +#if !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + size_(other.size_), +#endif // !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + max_size_(other.max_size_) + { + } +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + /// @b DynamicBuffer_v1: Get the size of the input sequence. + /// @b DynamicBuffer_v2: Get the current size of the underlying memory. + /** + * @returns @b DynamicBuffer_v1 The current size of the input sequence. + * @b DynamicBuffer_v2: The current size of the underlying string if less than + * max_size(). Otherwise returns max_size(). + */ + std::size_t size() const ASIO_NOEXCEPT + { +#if !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + if (size_ != (std::numeric_limits::max)()) + return size_; +#endif // !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + return (std::min)(string_.size(), max_size()); + } + + /// Get the maximum size of the dynamic buffer. + /** + * @returns The allowed maximum size of the underlying memory. + */ + std::size_t max_size() const ASIO_NOEXCEPT + { + return max_size_; + } + + /// Get the maximum size that the buffer may grow to without triggering + /// reallocation. + /** + * @returns The current capacity of the underlying string if less than + * max_size(). Otherwise returns max_size(). + */ + std::size_t capacity() const ASIO_NOEXCEPT + { + return (std::min)(string_.capacity(), max_size()); + } + +#if !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + /// @b DynamicBuffer_v1: Get a list of buffers that represents the input + /// sequence. + /** + * @returns An object of type @c const_buffers_type that satisfies + * ConstBufferSequence requirements, representing the basic_string memory in + * the input sequence. + * + * @note The returned object is invalidated by any @c dynamic_string_buffer + * or @c basic_string member function that resizes or erases the string. + */ + const_buffers_type data() const ASIO_NOEXCEPT + { + return const_buffers_type(asio::buffer(string_, size_)); + } +#endif // !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + + /// @b DynamicBuffer_v2: Get a sequence of buffers that represents the + /// underlying memory. + /** + * @param pos Position of the first byte to represent in the buffer sequence + * + * @param n The number of bytes to return in the buffer sequence. If the + * underlying memory is shorter, the buffer sequence represents as many bytes + * as are available. + * + * @returns An object of type @c mutable_buffers_type that satisfies + * MutableBufferSequence requirements, representing the basic_string memory. + * + * @note The returned object is invalidated by any @c dynamic_string_buffer + * or @c basic_string member function that resizes or erases the string. + */ + mutable_buffers_type data(std::size_t pos, std::size_t n) ASIO_NOEXCEPT + { + return mutable_buffers_type(asio::buffer( + asio::buffer(string_, max_size_) + pos, n)); + } + + /// @b DynamicBuffer_v2: Get a sequence of buffers that represents the + /// underlying memory. + /** + * @param pos Position of the first byte to represent in the buffer sequence + * + * @param n The number of bytes to return in the buffer sequence. If the + * underlying memory is shorter, the buffer sequence represents as many bytes + * as are available. + * + * @note The returned object is invalidated by any @c dynamic_string_buffer + * or @c basic_string member function that resizes or erases the string. + */ + const_buffers_type data(std::size_t pos, + std::size_t n) const ASIO_NOEXCEPT + { + return const_buffers_type(asio::buffer( + asio::buffer(string_, max_size_) + pos, n)); + } + +#if !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + /// @b DynamicBuffer_v1: Get a list of buffers that represents the output + /// sequence, with the given size. + /** + * Ensures that the output sequence can accommodate @c n bytes, resizing the + * basic_string object as necessary. + * + * @returns An object of type @c mutable_buffers_type that satisfies + * MutableBufferSequence requirements, representing basic_string memory + * at the start of the output sequence of size @c n. + * + * @throws std::length_error If size() + n > max_size(). + * + * @note The returned object is invalidated by any @c dynamic_string_buffer + * or @c basic_string member function that modifies the input sequence or + * output sequence. + */ + mutable_buffers_type prepare(std::size_t n) + { + if (size() > max_size() || max_size() - size() < n) + { + std::length_error ex("dynamic_string_buffer too long"); + asio::detail::throw_exception(ex); + } + + if (size_ == (std::numeric_limits::max)()) + size_ = string_.size(); // Enable v1 behaviour. + + string_.resize(size_ + n); + + return asio::buffer(asio::buffer(string_) + size_, n); + } + + /// @b DynamicBuffer_v1: Move bytes from the output sequence to the input + /// sequence. + /** + * @param n The number of bytes to append from the start of the output + * sequence to the end of the input sequence. The remainder of the output + * sequence is discarded. + * + * Requires a preceding call prepare(x) where x >= n, and + * no intervening operations that modify the input or output sequence. + * + * @note If @c n is greater than the size of the output sequence, the entire + * output sequence is moved to the input sequence and no error is issued. + */ + void commit(std::size_t n) + { + size_ += (std::min)(n, string_.size() - size_); + string_.resize(size_); + } +#endif // !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + + /// @b DynamicBuffer_v2: Grow the underlying memory by the specified number of + /// bytes. + /** + * Resizes the string to accommodate an additional @c n bytes at the end. + * + * @throws std::length_error If size() + n > max_size(). + */ + void grow(std::size_t n) + { + if (size() > max_size() || max_size() - size() < n) + { + std::length_error ex("dynamic_string_buffer too long"); + asio::detail::throw_exception(ex); + } + + string_.resize(size() + n); + } + + /// @b DynamicBuffer_v2: Shrink the underlying memory by the specified number + /// of bytes. + /** + * Erases @c n bytes from the end of the string by resizing the basic_string + * object. If @c n is greater than the current size of the string, the string + * is emptied. + */ + void shrink(std::size_t n) + { + string_.resize(n > size() ? 0 : size() - n); + } + + /// @b DynamicBuffer_v1: Remove characters from the input sequence. + /// @b DynamicBuffer_v2: Consume the specified number of bytes from the + /// beginning of the underlying memory. + /** + * @b DynamicBuffer_v1: Removes @c n characters from the beginning of the + * input sequence. @note If @c n is greater than the size of the input + * sequence, the entire input sequence is consumed and no error is issued. + * + * @b DynamicBuffer_v2: Erases @c n bytes from the beginning of the string. + * If @c n is greater than the current size of the string, the string is + * emptied. + */ + void consume(std::size_t n) + { +#if !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + if (size_ != (std::numeric_limits::max)()) + { + std::size_t consume_length = (std::min)(n, size_); + string_.erase(0, consume_length); + size_ -= consume_length; + return; + } +#endif // !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + string_.erase(0, n); + } + +private: + std::basic_string& string_; +#if !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + std::size_t size_; +#endif // !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + const std::size_t max_size_; +}; + +/// Adapt a vector to the DynamicBuffer requirements. +/** + * Requires that sizeof(Elem) == 1. + */ +template +class dynamic_vector_buffer +{ +public: + /// The type used to represent a sequence of constant buffers that refers to + /// the underlying memory. + typedef ASIO_CONST_BUFFER const_buffers_type; + + /// The type used to represent a sequence of mutable buffers that refers to + /// the underlying memory. + typedef ASIO_MUTABLE_BUFFER mutable_buffers_type; + + /// Construct a dynamic buffer from a vector. + /** + * @param v The vector to be used as backing storage for the dynamic buffer. + * The object stores a reference to the vector and the user is responsible + * for ensuring that the vector object remains valid while the + * dynamic_vector_buffer object, and copies of the object, are in use. + * + * @param maximum_size Specifies a maximum size for the buffer, in bytes. + */ + explicit dynamic_vector_buffer(std::vector& v, + std::size_t maximum_size = + (std::numeric_limits::max)()) ASIO_NOEXCEPT + : vector_(v), +#if !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + size_((std::numeric_limits::max)()), +#endif // !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + max_size_(maximum_size) + { + } + + /// @b DynamicBuffer_v2: Copy construct a dynamic buffer. + dynamic_vector_buffer(const dynamic_vector_buffer& other) ASIO_NOEXCEPT + : vector_(other.vector_), +#if !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + size_(other.size_), +#endif // !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + max_size_(other.max_size_) + { + } + +#if defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + /// Move construct a dynamic buffer. + dynamic_vector_buffer(dynamic_vector_buffer&& other) ASIO_NOEXCEPT + : vector_(other.vector_), +#if !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + size_(other.size_), +#endif // !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + max_size_(other.max_size_) + { + } +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + /// @b DynamicBuffer_v1: Get the size of the input sequence. + /// @b DynamicBuffer_v2: Get the current size of the underlying memory. + /** + * @returns @b DynamicBuffer_v1 The current size of the input sequence. + * @b DynamicBuffer_v2: The current size of the underlying vector if less than + * max_size(). Otherwise returns max_size(). + */ + std::size_t size() const ASIO_NOEXCEPT + { +#if !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + if (size_ != (std::numeric_limits::max)()) + return size_; +#endif // !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + return (std::min)(vector_.size(), max_size()); + } + + /// Get the maximum size of the dynamic buffer. + /** + * @returns @b DynamicBuffer_v1: The allowed maximum of the sum of the sizes + * of the input sequence and output sequence. @b DynamicBuffer_v2: The allowed + * maximum size of the underlying memory. + */ + std::size_t max_size() const ASIO_NOEXCEPT + { + return max_size_; + } + + /// Get the maximum size that the buffer may grow to without triggering + /// reallocation. + /** + * @returns @b DynamicBuffer_v1: The current total capacity of the buffer, + * i.e. for both the input sequence and output sequence. @b DynamicBuffer_v2: + * The current capacity of the underlying vector if less than max_size(). + * Otherwise returns max_size(). + */ + std::size_t capacity() const ASIO_NOEXCEPT + { + return (std::min)(vector_.capacity(), max_size()); + } + +#if !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + /// @b DynamicBuffer_v1: Get a list of buffers that represents the input + /// sequence. + /** + * @returns An object of type @c const_buffers_type that satisfies + * ConstBufferSequence requirements, representing the vector memory in the + * input sequence. + * + * @note The returned object is invalidated by any @c dynamic_vector_buffer + * or @c vector member function that modifies the input sequence or output + * sequence. + */ + const_buffers_type data() const ASIO_NOEXCEPT + { + return const_buffers_type(asio::buffer(vector_, size_)); + } +#endif // !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + + /// @b DynamicBuffer_v2: Get a sequence of buffers that represents the + /// underlying memory. + /** + * @param pos Position of the first byte to represent in the buffer sequence + * + * @param n The number of bytes to return in the buffer sequence. If the + * underlying memory is shorter, the buffer sequence represents as many bytes + * as are available. + * + * @returns An object of type @c mutable_buffers_type that satisfies + * MutableBufferSequence requirements, representing the vector memory. + * + * @note The returned object is invalidated by any @c dynamic_vector_buffer + * or @c vector member function that resizes or erases the vector. + */ + mutable_buffers_type data(std::size_t pos, std::size_t n) ASIO_NOEXCEPT + { + return mutable_buffers_type(asio::buffer( + asio::buffer(vector_, max_size_) + pos, n)); + } + + /// @b DynamicBuffer_v2: Get a sequence of buffers that represents the + /// underlying memory. + /** + * @param pos Position of the first byte to represent in the buffer sequence + * + * @param n The number of bytes to return in the buffer sequence. If the + * underlying memory is shorter, the buffer sequence represents as many bytes + * as are available. + * + * @note The returned object is invalidated by any @c dynamic_vector_buffer + * or @c vector member function that resizes or erases the vector. + */ + const_buffers_type data(std::size_t pos, + std::size_t n) const ASIO_NOEXCEPT + { + return const_buffers_type(asio::buffer( + asio::buffer(vector_, max_size_) + pos, n)); + } + +#if !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + /// @b DynamicBuffer_v1: Get a list of buffers that represents the output + /// sequence, with the given size. + /** + * Ensures that the output sequence can accommodate @c n bytes, resizing the + * vector object as necessary. + * + * @returns An object of type @c mutable_buffers_type that satisfies + * MutableBufferSequence requirements, representing vector memory at the + * start of the output sequence of size @c n. + * + * @throws std::length_error If size() + n > max_size(). + * + * @note The returned object is invalidated by any @c dynamic_vector_buffer + * or @c vector member function that modifies the input sequence or output + * sequence. + */ + mutable_buffers_type prepare(std::size_t n) + { + if (size () > max_size() || max_size() - size() < n) + { + std::length_error ex("dynamic_vector_buffer too long"); + asio::detail::throw_exception(ex); + } + + if (size_ == (std::numeric_limits::max)()) + size_ = vector_.size(); // Enable v1 behaviour. + + vector_.resize(size_ + n); + + return asio::buffer(asio::buffer(vector_) + size_, n); + } + + /// @b DynamicBuffer_v1: Move bytes from the output sequence to the input + /// sequence. + /** + * @param n The number of bytes to append from the start of the output + * sequence to the end of the input sequence. The remainder of the output + * sequence is discarded. + * + * Requires a preceding call prepare(x) where x >= n, and + * no intervening operations that modify the input or output sequence. + * + * @note If @c n is greater than the size of the output sequence, the entire + * output sequence is moved to the input sequence and no error is issued. + */ + void commit(std::size_t n) + { + size_ += (std::min)(n, vector_.size() - size_); + vector_.resize(size_); + } +#endif // !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + + /// @b DynamicBuffer_v2: Grow the underlying memory by the specified number of + /// bytes. + /** + * Resizes the vector to accommodate an additional @c n bytes at the end. + * + * @throws std::length_error If size() + n > max_size(). + */ + void grow(std::size_t n) + { + if (size() > max_size() || max_size() - size() < n) + { + std::length_error ex("dynamic_vector_buffer too long"); + asio::detail::throw_exception(ex); + } + + vector_.resize(size() + n); + } + + /// @b DynamicBuffer_v2: Shrink the underlying memory by the specified number + /// of bytes. + /** + * Erases @c n bytes from the end of the vector by resizing the vector + * object. If @c n is greater than the current size of the vector, the vector + * is emptied. + */ + void shrink(std::size_t n) + { + vector_.resize(n > size() ? 0 : size() - n); + } + + /// @b DynamicBuffer_v1: Remove characters from the input sequence. + /// @b DynamicBuffer_v2: Consume the specified number of bytes from the + /// beginning of the underlying memory. + /** + * @b DynamicBuffer_v1: Removes @c n characters from the beginning of the + * input sequence. @note If @c n is greater than the size of the input + * sequence, the entire input sequence is consumed and no error is issued. + * + * @b DynamicBuffer_v2: Erases @c n bytes from the beginning of the vector. + * If @c n is greater than the current size of the vector, the vector is + * emptied. + */ + void consume(std::size_t n) + { +#if !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + if (size_ != (std::numeric_limits::max)()) + { + std::size_t consume_length = (std::min)(n, size_); + vector_.erase(vector_.begin(), vector_.begin() + consume_length); + size_ -= consume_length; + return; + } +#endif // !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + vector_.erase(vector_.begin(), vector_.begin() + (std::min)(size(), n)); + } + +private: + std::vector& vector_; +#if !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + std::size_t size_; +#endif // !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + const std::size_t max_size_; +}; + +/** @defgroup dynamic_buffer asio::dynamic_buffer + * + * @brief The asio::dynamic_buffer function is used to create a + * dynamically resized buffer from a @c std::basic_string or @c std::vector. + */ +/*@{*/ + +/// Create a new dynamic buffer that represents the given string. +/** + * @returns dynamic_string_buffer(data). + */ +template +inline dynamic_string_buffer dynamic_buffer( + std::basic_string& data) ASIO_NOEXCEPT +{ + return dynamic_string_buffer(data); +} + +/// Create a new dynamic buffer that represents the given string. +/** + * @returns dynamic_string_buffer(data, + * max_size). + */ +template +inline dynamic_string_buffer dynamic_buffer( + std::basic_string& data, + std::size_t max_size) ASIO_NOEXCEPT +{ + return dynamic_string_buffer(data, max_size); +} + +/// Create a new dynamic buffer that represents the given vector. +/** + * @returns dynamic_vector_buffer(data). + */ +template +inline dynamic_vector_buffer dynamic_buffer( + std::vector& data) ASIO_NOEXCEPT +{ + return dynamic_vector_buffer(data); +} + +/// Create a new dynamic buffer that represents the given vector. +/** + * @returns dynamic_vector_buffer(data, max_size). + */ +template +inline dynamic_vector_buffer dynamic_buffer( + std::vector& data, + std::size_t max_size) ASIO_NOEXCEPT +{ + return dynamic_vector_buffer(data, max_size); +} + +/*@}*/ + +/** @defgroup buffer_copy asio::buffer_copy + * + * @brief The asio::buffer_copy function is used to copy bytes from a + * source buffer (or buffer sequence) to a target buffer (or buffer sequence). + * + * The @c buffer_copy function is available in two forms: + * + * @li A 2-argument form: @c buffer_copy(target, source) + * + * @li A 3-argument form: @c buffer_copy(target, source, max_bytes_to_copy) + * + * Both forms return the number of bytes actually copied. The number of bytes + * copied is the lesser of: + * + * @li @c buffer_size(target) + * + * @li @c buffer_size(source) + * + * @li @c If specified, @c max_bytes_to_copy. + * + * This prevents buffer overflow, regardless of the buffer sizes used in the + * copy operation. + * + * Note that @ref buffer_copy is implemented in terms of @c memcpy, and + * consequently it cannot be used to copy between overlapping memory regions. + */ +/*@{*/ + +namespace detail { + +inline std::size_t buffer_copy_1(const mutable_buffer& target, + const const_buffer& source) +{ + using namespace std; // For memcpy. + std::size_t target_size = target.size(); + std::size_t source_size = source.size(); + std::size_t n = target_size < source_size ? target_size : source_size; + if (n > 0) + memcpy(target.data(), source.data(), n); + return n; +} + +template +inline std::size_t buffer_copy(one_buffer, one_buffer, + TargetIterator target_begin, TargetIterator, + SourceIterator source_begin, SourceIterator) ASIO_NOEXCEPT +{ + return (buffer_copy_1)(*target_begin, *source_begin); +} + +template +inline std::size_t buffer_copy(one_buffer, one_buffer, + TargetIterator target_begin, TargetIterator, + SourceIterator source_begin, SourceIterator, + std::size_t max_bytes_to_copy) ASIO_NOEXCEPT +{ + return (buffer_copy_1)(*target_begin, + asio::buffer(*source_begin, max_bytes_to_copy)); +} + +template +std::size_t buffer_copy(one_buffer, multiple_buffers, + TargetIterator target_begin, TargetIterator, + SourceIterator source_begin, SourceIterator source_end, + std::size_t max_bytes_to_copy + = (std::numeric_limits::max)()) ASIO_NOEXCEPT +{ + std::size_t total_bytes_copied = 0; + SourceIterator source_iter = source_begin; + + for (mutable_buffer target_buffer( + asio::buffer(*target_begin, max_bytes_to_copy)); + target_buffer.size() && source_iter != source_end; ++source_iter) + { + const_buffer source_buffer(*source_iter); + std::size_t bytes_copied = (buffer_copy_1)(target_buffer, source_buffer); + total_bytes_copied += bytes_copied; + target_buffer += bytes_copied; + } + + return total_bytes_copied; +} + +template +std::size_t buffer_copy(multiple_buffers, one_buffer, + TargetIterator target_begin, TargetIterator target_end, + SourceIterator source_begin, SourceIterator, + std::size_t max_bytes_to_copy + = (std::numeric_limits::max)()) ASIO_NOEXCEPT +{ + std::size_t total_bytes_copied = 0; + TargetIterator target_iter = target_begin; + + for (const_buffer source_buffer( + asio::buffer(*source_begin, max_bytes_to_copy)); + source_buffer.size() && target_iter != target_end; ++target_iter) + { + mutable_buffer target_buffer(*target_iter); + std::size_t bytes_copied = (buffer_copy_1)(target_buffer, source_buffer); + total_bytes_copied += bytes_copied; + source_buffer += bytes_copied; + } + + return total_bytes_copied; +} + +template +std::size_t buffer_copy(multiple_buffers, multiple_buffers, + TargetIterator target_begin, TargetIterator target_end, + SourceIterator source_begin, SourceIterator source_end) ASIO_NOEXCEPT +{ + std::size_t total_bytes_copied = 0; + + TargetIterator target_iter = target_begin; + std::size_t target_buffer_offset = 0; + + SourceIterator source_iter = source_begin; + std::size_t source_buffer_offset = 0; + + while (target_iter != target_end && source_iter != source_end) + { + mutable_buffer target_buffer = + mutable_buffer(*target_iter) + target_buffer_offset; + + const_buffer source_buffer = + const_buffer(*source_iter) + source_buffer_offset; + + std::size_t bytes_copied = (buffer_copy_1)(target_buffer, source_buffer); + total_bytes_copied += bytes_copied; + + if (bytes_copied == target_buffer.size()) + { + ++target_iter; + target_buffer_offset = 0; + } + else + target_buffer_offset += bytes_copied; + + if (bytes_copied == source_buffer.size()) + { + ++source_iter; + source_buffer_offset = 0; + } + else + source_buffer_offset += bytes_copied; + } + + return total_bytes_copied; +} + +template +std::size_t buffer_copy(multiple_buffers, multiple_buffers, + TargetIterator target_begin, TargetIterator target_end, + SourceIterator source_begin, SourceIterator source_end, + std::size_t max_bytes_to_copy) ASIO_NOEXCEPT +{ + std::size_t total_bytes_copied = 0; + + TargetIterator target_iter = target_begin; + std::size_t target_buffer_offset = 0; + + SourceIterator source_iter = source_begin; + std::size_t source_buffer_offset = 0; + + while (total_bytes_copied != max_bytes_to_copy + && target_iter != target_end && source_iter != source_end) + { + mutable_buffer target_buffer = + mutable_buffer(*target_iter) + target_buffer_offset; + + const_buffer source_buffer = + const_buffer(*source_iter) + source_buffer_offset; + + std::size_t bytes_copied = (buffer_copy_1)( + target_buffer, asio::buffer(source_buffer, + max_bytes_to_copy - total_bytes_copied)); + total_bytes_copied += bytes_copied; + + if (bytes_copied == target_buffer.size()) + { + ++target_iter; + target_buffer_offset = 0; + } + else + target_buffer_offset += bytes_copied; + + if (bytes_copied == source_buffer.size()) + { + ++source_iter; + source_buffer_offset = 0; + } + else + source_buffer_offset += bytes_copied; + } + + return total_bytes_copied; +} + +} // namespace detail + +/// Copies bytes from a source buffer sequence to a target buffer sequence. +/** + * @param target A modifiable buffer sequence representing the memory regions to + * which the bytes will be copied. + * + * @param source A non-modifiable buffer sequence representing the memory + * regions from which the bytes will be copied. + * + * @returns The number of bytes copied. + * + * @note The number of bytes copied is the lesser of: + * + * @li @c buffer_size(target) + * + * @li @c buffer_size(source) + * + * This function is implemented in terms of @c memcpy, and consequently it + * cannot be used to copy between overlapping memory regions. + */ +template +inline std::size_t buffer_copy(const MutableBufferSequence& target, + const ConstBufferSequence& source) ASIO_NOEXCEPT +{ + return detail::buffer_copy( + detail::buffer_sequence_cardinality(), + detail::buffer_sequence_cardinality(), + asio::buffer_sequence_begin(target), + asio::buffer_sequence_end(target), + asio::buffer_sequence_begin(source), + asio::buffer_sequence_end(source)); +} + +/// Copies a limited number of bytes from a source buffer sequence to a target +/// buffer sequence. +/** + * @param target A modifiable buffer sequence representing the memory regions to + * which the bytes will be copied. + * + * @param source A non-modifiable buffer sequence representing the memory + * regions from which the bytes will be copied. + * + * @param max_bytes_to_copy The maximum number of bytes to be copied. + * + * @returns The number of bytes copied. + * + * @note The number of bytes copied is the lesser of: + * + * @li @c buffer_size(target) + * + * @li @c buffer_size(source) + * + * @li @c max_bytes_to_copy + * + * This function is implemented in terms of @c memcpy, and consequently it + * cannot be used to copy between overlapping memory regions. + */ +template +inline std::size_t buffer_copy(const MutableBufferSequence& target, + const ConstBufferSequence& source, + std::size_t max_bytes_to_copy) ASIO_NOEXCEPT +{ + return detail::buffer_copy( + detail::buffer_sequence_cardinality(), + detail::buffer_sequence_cardinality(), + asio::buffer_sequence_begin(target), + asio::buffer_sequence_end(target), + asio::buffer_sequence_begin(source), + asio::buffer_sequence_end(source), max_bytes_to_copy); +} + +/*@}*/ + +} // namespace asio + +#include "asio/detail/pop_options.hpp" +#include "asio/detail/is_buffer_sequence.hpp" +#include "asio/detail/push_options.hpp" + +namespace asio { + +/// Trait to determine whether a type satisfies the MutableBufferSequence +/// requirements. +template +struct is_mutable_buffer_sequence +#if defined(GENERATING_DOCUMENTATION) + : integral_constant +#else // defined(GENERATING_DOCUMENTATION) + : asio::detail::is_buffer_sequence +#endif // defined(GENERATING_DOCUMENTATION) +{ +}; + +/// Trait to determine whether a type satisfies the ConstBufferSequence +/// requirements. +template +struct is_const_buffer_sequence +#if defined(GENERATING_DOCUMENTATION) + : integral_constant +#else // defined(GENERATING_DOCUMENTATION) + : asio::detail::is_buffer_sequence +#endif // defined(GENERATING_DOCUMENTATION) +{ +}; + +#if !defined(ASIO_NO_DYNAMIC_BUFFER_V1) +/// Trait to determine whether a type satisfies the DynamicBuffer_v1 +/// requirements. +template +struct is_dynamic_buffer_v1 +#if defined(GENERATING_DOCUMENTATION) + : integral_constant +#else // defined(GENERATING_DOCUMENTATION) + : asio::detail::is_dynamic_buffer_v1 +#endif // defined(GENERATING_DOCUMENTATION) +{ +}; +#endif // !defined(ASIO_NO_DYNAMIC_BUFFER_V1) + +/// Trait to determine whether a type satisfies the DynamicBuffer_v2 +/// requirements. +template +struct is_dynamic_buffer_v2 +#if defined(GENERATING_DOCUMENTATION) + : integral_constant +#else // defined(GENERATING_DOCUMENTATION) + : asio::detail::is_dynamic_buffer_v2 +#endif // defined(GENERATING_DOCUMENTATION) +{ +}; + +/// Trait to determine whether a type satisfies the DynamicBuffer requirements. +/** + * If @c ASIO_NO_DYNAMIC_BUFFER_V1 is not defined, determines whether the + * type satisfies the DynamicBuffer_v1 requirements. Otherwise, if @c + * ASIO_NO_DYNAMIC_BUFFER_V1 is defined, determines whether the type + * satisfies the DynamicBuffer_v2 requirements. + */ +template +struct is_dynamic_buffer +#if defined(GENERATING_DOCUMENTATION) + : integral_constant +#elif defined(ASIO_NO_DYNAMIC_BUFFER_V1) + : asio::is_dynamic_buffer_v2 +#else // defined(ASIO_NO_DYNAMIC_BUFFER_V1) + : asio::is_dynamic_buffer_v1 +#endif // defined(ASIO_NO_DYNAMIC_BUFFER_V1) +{ +}; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_BUFFER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_read_stream.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_read_stream.hpp new file mode 100644 index 000000000..7280a5477 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_read_stream.hpp @@ -0,0 +1,253 @@ +// +// buffered_read_stream.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BUFFERED_READ_STREAM_HPP +#define ASIO_BUFFERED_READ_STREAM_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include "asio/async_result.hpp" +#include "asio/buffered_read_stream_fwd.hpp" +#include "asio/buffer.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_resize_guard.hpp" +#include "asio/detail/buffered_stream_storage.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +/// Adds buffering to the read-related operations of a stream. +/** + * The buffered_read_stream class template can be used to add buffering to the + * synchronous and asynchronous read operations of a stream. + * + * @par Thread Safety + * @e Distinct @e objects: Safe.@n + * @e Shared @e objects: Unsafe. + * + * @par Concepts: + * AsyncReadStream, AsyncWriteStream, Stream, SyncReadStream, SyncWriteStream. + */ +template +class buffered_read_stream + : private noncopyable +{ +public: + /// The type of the next layer. + typedef typename remove_reference::type next_layer_type; + + /// The type of the lowest layer. + typedef typename next_layer_type::lowest_layer_type lowest_layer_type; + + /// The type of the executor associated with the object. + typedef typename lowest_layer_type::executor_type executor_type; + +#if defined(GENERATING_DOCUMENTATION) + /// The default buffer size. + static const std::size_t default_buffer_size = implementation_defined; +#else + ASIO_STATIC_CONSTANT(std::size_t, default_buffer_size = 1024); +#endif + + /// Construct, passing the specified argument to initialise the next layer. + template + explicit buffered_read_stream(Arg& a) + : next_layer_(a), + storage_(default_buffer_size) + { + } + + /// Construct, passing the specified argument to initialise the next layer. + template + buffered_read_stream(Arg& a, std::size_t buffer_size) + : next_layer_(a), + storage_(buffer_size) + { + } + + /// Get a reference to the next layer. + next_layer_type& next_layer() + { + return next_layer_; + } + + /// Get a reference to the lowest layer. + lowest_layer_type& lowest_layer() + { + return next_layer_.lowest_layer(); + } + + /// Get a const reference to the lowest layer. + const lowest_layer_type& lowest_layer() const + { + return next_layer_.lowest_layer(); + } + + /// Get the executor associated with the object. + executor_type get_executor() ASIO_NOEXCEPT + { + return next_layer_.lowest_layer().get_executor(); + } + + /// Close the stream. + void close() + { + next_layer_.close(); + } + + /// Close the stream. + ASIO_SYNC_OP_VOID close(asio::error_code& ec) + { + next_layer_.close(ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Write the given data to the stream. Returns the number of bytes written. + /// Throws an exception on failure. + template + std::size_t write_some(const ConstBufferSequence& buffers) + { + return next_layer_.write_some(buffers); + } + + /// Write the given data to the stream. Returns the number of bytes written, + /// or 0 if an error occurred. + template + std::size_t write_some(const ConstBufferSequence& buffers, + asio::error_code& ec) + { + return next_layer_.write_some(buffers, ec); + } + + /// Start an asynchronous write. The data being written must be valid for the + /// lifetime of the asynchronous operation. + template + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_write_some(const ConstBufferSequence& buffers, + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return next_layer_.async_write_some(buffers, + ASIO_MOVE_CAST(WriteHandler)(handler)); + } + + /// Fill the buffer with some data. Returns the number of bytes placed in the + /// buffer as a result of the operation. Throws an exception on failure. + std::size_t fill(); + + /// Fill the buffer with some data. Returns the number of bytes placed in the + /// buffer as a result of the operation, or 0 if an error occurred. + std::size_t fill(asio::error_code& ec); + + /// Start an asynchronous fill. + template < + ASIO_COMPLETION_TOKEN_FOR(void (asio::error_code, + std::size_t)) ReadHandler + ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(executor_type)> + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_fill( + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)); + + /// Read some data from the stream. Returns the number of bytes read. Throws + /// an exception on failure. + template + std::size_t read_some(const MutableBufferSequence& buffers); + + /// Read some data from the stream. Returns the number of bytes read or 0 if + /// an error occurred. + template + std::size_t read_some(const MutableBufferSequence& buffers, + asio::error_code& ec); + + /// Start an asynchronous read. The buffer into which the data will be read + /// must be valid for the lifetime of the asynchronous operation. + template + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_read_some(const MutableBufferSequence& buffers, + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)); + + /// Peek at the incoming data on the stream. Returns the number of bytes read. + /// Throws an exception on failure. + template + std::size_t peek(const MutableBufferSequence& buffers); + + /// Peek at the incoming data on the stream. Returns the number of bytes read, + /// or 0 if an error occurred. + template + std::size_t peek(const MutableBufferSequence& buffers, + asio::error_code& ec); + + /// Determine the amount of data that may be read without blocking. + std::size_t in_avail() + { + return storage_.size(); + } + + /// Determine the amount of data that may be read without blocking. + std::size_t in_avail(asio::error_code& ec) + { + ec = asio::error_code(); + return storage_.size(); + } + +private: + /// Copy data out of the internal buffer to the specified target buffer. + /// Returns the number of bytes copied. + template + std::size_t copy(const MutableBufferSequence& buffers) + { + std::size_t bytes_copied = asio::buffer_copy( + buffers, storage_.data(), storage_.size()); + storage_.consume(bytes_copied); + return bytes_copied; + } + + /// Copy data from the internal buffer to the specified target buffer, without + /// removing the data from the internal buffer. Returns the number of bytes + /// copied. + template + std::size_t peek_copy(const MutableBufferSequence& buffers) + { + return asio::buffer_copy(buffers, storage_.data(), storage_.size()); + } + + /// The next layer. + Stream next_layer_; + + // The data in the buffer. + detail::buffered_stream_storage storage_; +}; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/impl/buffered_read_stream.hpp" + +#endif // ASIO_BUFFERED_READ_STREAM_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_read_stream_fwd.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_read_stream_fwd.hpp new file mode 100644 index 000000000..301f68a41 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_read_stream_fwd.hpp @@ -0,0 +1,25 @@ +// +// buffered_read_stream_fwd.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BUFFERED_READ_STREAM_FWD_HPP +#define ASIO_BUFFERED_READ_STREAM_FWD_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +namespace asio { + +template +class buffered_read_stream; + +} // namespace asio + +#endif // ASIO_BUFFERED_READ_STREAM_FWD_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_stream.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_stream.hpp new file mode 100644 index 000000000..63f8253a8 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_stream.hpp @@ -0,0 +1,279 @@ +// +// buffered_stream.hpp +// ~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BUFFERED_STREAM_HPP +#define ASIO_BUFFERED_STREAM_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include "asio/async_result.hpp" +#include "asio/buffered_read_stream.hpp" +#include "asio/buffered_write_stream.hpp" +#include "asio/buffered_stream_fwd.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +/// Adds buffering to the read- and write-related operations of a stream. +/** + * The buffered_stream class template can be used to add buffering to the + * synchronous and asynchronous read and write operations of a stream. + * + * @par Thread Safety + * @e Distinct @e objects: Safe.@n + * @e Shared @e objects: Unsafe. + * + * @par Concepts: + * AsyncReadStream, AsyncWriteStream, Stream, SyncReadStream, SyncWriteStream. + */ +template +class buffered_stream + : private noncopyable +{ +public: + /// The type of the next layer. + typedef typename remove_reference::type next_layer_type; + + /// The type of the lowest layer. + typedef typename next_layer_type::lowest_layer_type lowest_layer_type; + + /// The type of the executor associated with the object. + typedef typename lowest_layer_type::executor_type executor_type; + + /// Construct, passing the specified argument to initialise the next layer. + template + explicit buffered_stream(Arg& a) + : inner_stream_impl_(a), + stream_impl_(inner_stream_impl_) + { + } + + /// Construct, passing the specified argument to initialise the next layer. + template + explicit buffered_stream(Arg& a, std::size_t read_buffer_size, + std::size_t write_buffer_size) + : inner_stream_impl_(a, write_buffer_size), + stream_impl_(inner_stream_impl_, read_buffer_size) + { + } + + /// Get a reference to the next layer. + next_layer_type& next_layer() + { + return stream_impl_.next_layer().next_layer(); + } + + /// Get a reference to the lowest layer. + lowest_layer_type& lowest_layer() + { + return stream_impl_.lowest_layer(); + } + + /// Get a const reference to the lowest layer. + const lowest_layer_type& lowest_layer() const + { + return stream_impl_.lowest_layer(); + } + + /// Get the executor associated with the object. + executor_type get_executor() ASIO_NOEXCEPT + { + return stream_impl_.lowest_layer().get_executor(); + } + + /// Close the stream. + void close() + { + stream_impl_.close(); + } + + /// Close the stream. + ASIO_SYNC_OP_VOID close(asio::error_code& ec) + { + stream_impl_.close(ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Flush all data from the buffer to the next layer. Returns the number of + /// bytes written to the next layer on the last write operation. Throws an + /// exception on failure. + std::size_t flush() + { + return stream_impl_.next_layer().flush(); + } + + /// Flush all data from the buffer to the next layer. Returns the number of + /// bytes written to the next layer on the last write operation, or 0 if an + /// error occurred. + std::size_t flush(asio::error_code& ec) + { + return stream_impl_.next_layer().flush(ec); + } + + /// Start an asynchronous flush. + template < + ASIO_COMPLETION_TOKEN_FOR(void (asio::error_code, + std::size_t)) WriteHandler + ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(executor_type)> + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_flush( + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return stream_impl_.next_layer().async_flush( + ASIO_MOVE_CAST(WriteHandler)(handler)); + } + + /// Write the given data to the stream. Returns the number of bytes written. + /// Throws an exception on failure. + template + std::size_t write_some(const ConstBufferSequence& buffers) + { + return stream_impl_.write_some(buffers); + } + + /// Write the given data to the stream. Returns the number of bytes written, + /// or 0 if an error occurred. + template + std::size_t write_some(const ConstBufferSequence& buffers, + asio::error_code& ec) + { + return stream_impl_.write_some(buffers, ec); + } + + /// Start an asynchronous write. The data being written must be valid for the + /// lifetime of the asynchronous operation. + template + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_write_some(const ConstBufferSequence& buffers, + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return stream_impl_.async_write_some(buffers, + ASIO_MOVE_CAST(WriteHandler)(handler)); + } + + /// Fill the buffer with some data. Returns the number of bytes placed in the + /// buffer as a result of the operation. Throws an exception on failure. + std::size_t fill() + { + return stream_impl_.fill(); + } + + /// Fill the buffer with some data. Returns the number of bytes placed in the + /// buffer as a result of the operation, or 0 if an error occurred. + std::size_t fill(asio::error_code& ec) + { + return stream_impl_.fill(ec); + } + + /// Start an asynchronous fill. + template < + ASIO_COMPLETION_TOKEN_FOR(void (asio::error_code, + std::size_t)) ReadHandler + ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(executor_type)> + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_fill( + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return stream_impl_.async_fill(ASIO_MOVE_CAST(ReadHandler)(handler)); + } + + /// Read some data from the stream. Returns the number of bytes read. Throws + /// an exception on failure. + template + std::size_t read_some(const MutableBufferSequence& buffers) + { + return stream_impl_.read_some(buffers); + } + + /// Read some data from the stream. Returns the number of bytes read or 0 if + /// an error occurred. + template + std::size_t read_some(const MutableBufferSequence& buffers, + asio::error_code& ec) + { + return stream_impl_.read_some(buffers, ec); + } + + /// Start an asynchronous read. The buffer into which the data will be read + /// must be valid for the lifetime of the asynchronous operation. + template + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_read_some(const MutableBufferSequence& buffers, + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return stream_impl_.async_read_some(buffers, + ASIO_MOVE_CAST(ReadHandler)(handler)); + } + + /// Peek at the incoming data on the stream. Returns the number of bytes read. + /// Throws an exception on failure. + template + std::size_t peek(const MutableBufferSequence& buffers) + { + return stream_impl_.peek(buffers); + } + + /// Peek at the incoming data on the stream. Returns the number of bytes read, + /// or 0 if an error occurred. + template + std::size_t peek(const MutableBufferSequence& buffers, + asio::error_code& ec) + { + return stream_impl_.peek(buffers, ec); + } + + /// Determine the amount of data that may be read without blocking. + std::size_t in_avail() + { + return stream_impl_.in_avail(); + } + + /// Determine the amount of data that may be read without blocking. + std::size_t in_avail(asio::error_code& ec) + { + return stream_impl_.in_avail(ec); + } + +private: + // The buffered write stream. + typedef buffered_write_stream write_stream_type; + write_stream_type inner_stream_impl_; + + // The buffered read stream. + typedef buffered_read_stream read_stream_type; + read_stream_type stream_impl_; +}; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_BUFFERED_STREAM_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_stream_fwd.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_stream_fwd.hpp new file mode 100644 index 000000000..a9f350c56 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_stream_fwd.hpp @@ -0,0 +1,25 @@ +// +// buffered_stream_fwd.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BUFFERED_STREAM_FWD_HPP +#define ASIO_BUFFERED_STREAM_FWD_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +namespace asio { + +template +class buffered_stream; + +} // namespace asio + +#endif // ASIO_BUFFERED_STREAM_FWD_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_write_stream.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_write_stream.hpp new file mode 100644 index 000000000..96e0ec8a9 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_write_stream.hpp @@ -0,0 +1,245 @@ +// +// buffered_write_stream.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BUFFERED_WRITE_STREAM_HPP +#define ASIO_BUFFERED_WRITE_STREAM_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include "asio/buffered_write_stream_fwd.hpp" +#include "asio/buffer.hpp" +#include "asio/completion_condition.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffered_stream_storage.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/error.hpp" +#include "asio/write.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +/// Adds buffering to the write-related operations of a stream. +/** + * The buffered_write_stream class template can be used to add buffering to the + * synchronous and asynchronous write operations of a stream. + * + * @par Thread Safety + * @e Distinct @e objects: Safe.@n + * @e Shared @e objects: Unsafe. + * + * @par Concepts: + * AsyncReadStream, AsyncWriteStream, Stream, SyncReadStream, SyncWriteStream. + */ +template +class buffered_write_stream + : private noncopyable +{ +public: + /// The type of the next layer. + typedef typename remove_reference::type next_layer_type; + + /// The type of the lowest layer. + typedef typename next_layer_type::lowest_layer_type lowest_layer_type; + + /// The type of the executor associated with the object. + typedef typename lowest_layer_type::executor_type executor_type; + +#if defined(GENERATING_DOCUMENTATION) + /// The default buffer size. + static const std::size_t default_buffer_size = implementation_defined; +#else + ASIO_STATIC_CONSTANT(std::size_t, default_buffer_size = 1024); +#endif + + /// Construct, passing the specified argument to initialise the next layer. + template + explicit buffered_write_stream(Arg& a) + : next_layer_(a), + storage_(default_buffer_size) + { + } + + /// Construct, passing the specified argument to initialise the next layer. + template + buffered_write_stream(Arg& a, std::size_t buffer_size) + : next_layer_(a), + storage_(buffer_size) + { + } + + /// Get a reference to the next layer. + next_layer_type& next_layer() + { + return next_layer_; + } + + /// Get a reference to the lowest layer. + lowest_layer_type& lowest_layer() + { + return next_layer_.lowest_layer(); + } + + /// Get a const reference to the lowest layer. + const lowest_layer_type& lowest_layer() const + { + return next_layer_.lowest_layer(); + } + + /// Get the executor associated with the object. + executor_type get_executor() ASIO_NOEXCEPT + { + return next_layer_.lowest_layer().get_executor(); + } + + /// Close the stream. + void close() + { + next_layer_.close(); + } + + /// Close the stream. + ASIO_SYNC_OP_VOID close(asio::error_code& ec) + { + next_layer_.close(ec); + ASIO_SYNC_OP_VOID_RETURN(ec); + } + + /// Flush all data from the buffer to the next layer. Returns the number of + /// bytes written to the next layer on the last write operation. Throws an + /// exception on failure. + std::size_t flush(); + + /// Flush all data from the buffer to the next layer. Returns the number of + /// bytes written to the next layer on the last write operation, or 0 if an + /// error occurred. + std::size_t flush(asio::error_code& ec); + + /// Start an asynchronous flush. + template < + ASIO_COMPLETION_TOKEN_FOR(void (asio::error_code, + std::size_t)) WriteHandler + ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(executor_type)> + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_flush( + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)); + + /// Write the given data to the stream. Returns the number of bytes written. + /// Throws an exception on failure. + template + std::size_t write_some(const ConstBufferSequence& buffers); + + /// Write the given data to the stream. Returns the number of bytes written, + /// or 0 if an error occurred and the error handler did not throw. + template + std::size_t write_some(const ConstBufferSequence& buffers, + asio::error_code& ec); + + /// Start an asynchronous write. The data being written must be valid for the + /// lifetime of the asynchronous operation. + template + ASIO_INITFN_AUTO_RESULT_TYPE(WriteHandler, + void (asio::error_code, std::size_t)) + async_write_some(const ConstBufferSequence& buffers, + ASIO_MOVE_ARG(WriteHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)); + + /// Read some data from the stream. Returns the number of bytes read. Throws + /// an exception on failure. + template + std::size_t read_some(const MutableBufferSequence& buffers) + { + return next_layer_.read_some(buffers); + } + + /// Read some data from the stream. Returns the number of bytes read or 0 if + /// an error occurred. + template + std::size_t read_some(const MutableBufferSequence& buffers, + asio::error_code& ec) + { + return next_layer_.read_some(buffers, ec); + } + + /// Start an asynchronous read. The buffer into which the data will be read + /// must be valid for the lifetime of the asynchronous operation. + template + ASIO_INITFN_AUTO_RESULT_TYPE(ReadHandler, + void (asio::error_code, std::size_t)) + async_read_some(const MutableBufferSequence& buffers, + ASIO_MOVE_ARG(ReadHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(executor_type)) + { + return next_layer_.async_read_some(buffers, + ASIO_MOVE_CAST(ReadHandler)(handler)); + } + + /// Peek at the incoming data on the stream. Returns the number of bytes read. + /// Throws an exception on failure. + template + std::size_t peek(const MutableBufferSequence& buffers) + { + return next_layer_.peek(buffers); + } + + /// Peek at the incoming data on the stream. Returns the number of bytes read, + /// or 0 if an error occurred. + template + std::size_t peek(const MutableBufferSequence& buffers, + asio::error_code& ec) + { + return next_layer_.peek(buffers, ec); + } + + /// Determine the amount of data that may be read without blocking. + std::size_t in_avail() + { + return next_layer_.in_avail(); + } + + /// Determine the amount of data that may be read without blocking. + std::size_t in_avail(asio::error_code& ec) + { + return next_layer_.in_avail(ec); + } + +private: + /// Copy data into the internal buffer from the specified source buffer. + /// Returns the number of bytes copied. + template + std::size_t copy(const ConstBufferSequence& buffers); + + /// The next layer. + Stream next_layer_; + + // The data in the buffer. + detail::buffered_stream_storage storage_; +}; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/impl/buffered_write_stream.hpp" + +#endif // ASIO_BUFFERED_WRITE_STREAM_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_write_stream_fwd.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_write_stream_fwd.hpp new file mode 100644 index 000000000..0b3a4b0ed --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/buffered_write_stream_fwd.hpp @@ -0,0 +1,25 @@ +// +// buffered_write_stream_fwd.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BUFFERED_WRITE_STREAM_FWD_HPP +#define ASIO_BUFFERED_WRITE_STREAM_FWD_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +namespace asio { + +template +class buffered_write_stream; + +} // namespace asio + +#endif // ASIO_BUFFERED_WRITE_STREAM_FWD_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/buffers_iterator.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/buffers_iterator.hpp new file mode 100644 index 000000000..5cc7ba328 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/buffers_iterator.hpp @@ -0,0 +1,521 @@ +// +// buffers_iterator.hpp +// ~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_BUFFERS_ITERATOR_HPP +#define ASIO_BUFFERS_ITERATOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include +#include "asio/buffer.hpp" +#include "asio/detail/assert.hpp" +#include "asio/detail/type_traits.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +namespace detail +{ + template + struct buffers_iterator_types_helper; + + template <> + struct buffers_iterator_types_helper + { + typedef const_buffer buffer_type; + template + struct byte_type + { + typedef typename add_const::type type; + }; + }; + + template <> + struct buffers_iterator_types_helper + { + typedef mutable_buffer buffer_type; + template + struct byte_type + { + typedef ByteType type; + }; + }; + + template + struct buffers_iterator_types + { + enum + { + is_mutable = is_convertible< + typename BufferSequence::value_type, + mutable_buffer>::value + }; + typedef buffers_iterator_types_helper helper; + typedef typename helper::buffer_type buffer_type; + typedef typename helper::template byte_type::type byte_type; + typedef typename BufferSequence::const_iterator const_iterator; + }; + + template + struct buffers_iterator_types + { + typedef mutable_buffer buffer_type; + typedef ByteType byte_type; + typedef const mutable_buffer* const_iterator; + }; + + template + struct buffers_iterator_types + { + typedef const_buffer buffer_type; + typedef typename add_const::type byte_type; + typedef const const_buffer* const_iterator; + }; + +#if !defined(ASIO_NO_DEPRECATED) + + template + struct buffers_iterator_types + { + typedef mutable_buffer buffer_type; + typedef ByteType byte_type; + typedef const mutable_buffer* const_iterator; + }; + + template + struct buffers_iterator_types + { + typedef const_buffer buffer_type; + typedef typename add_const::type byte_type; + typedef const const_buffer* const_iterator; + }; + +#endif // !defined(ASIO_NO_DEPRECATED) +} + +/// A random access iterator over the bytes in a buffer sequence. +template +class buffers_iterator +{ +private: + typedef typename detail::buffers_iterator_types< + BufferSequence, ByteType>::buffer_type buffer_type; + + typedef typename detail::buffers_iterator_types::const_iterator buffer_sequence_iterator_type; + +public: + /// The type used for the distance between two iterators. + typedef std::ptrdiff_t difference_type; + + /// The type of the value pointed to by the iterator. + typedef ByteType value_type; + +#if defined(GENERATING_DOCUMENTATION) + /// The type of the result of applying operator->() to the iterator. + /** + * If the buffer sequence stores buffer objects that are convertible to + * mutable_buffer, this is a pointer to a non-const ByteType. Otherwise, a + * pointer to a const ByteType. + */ + typedef const_or_non_const_ByteType* pointer; +#else // defined(GENERATING_DOCUMENTATION) + typedef typename detail::buffers_iterator_types< + BufferSequence, ByteType>::byte_type* pointer; +#endif // defined(GENERATING_DOCUMENTATION) + +#if defined(GENERATING_DOCUMENTATION) + /// The type of the result of applying operator*() to the iterator. + /** + * If the buffer sequence stores buffer objects that are convertible to + * mutable_buffer, this is a reference to a non-const ByteType. Otherwise, a + * reference to a const ByteType. + */ + typedef const_or_non_const_ByteType& reference; +#else // defined(GENERATING_DOCUMENTATION) + typedef typename detail::buffers_iterator_types< + BufferSequence, ByteType>::byte_type& reference; +#endif // defined(GENERATING_DOCUMENTATION) + + /// The iterator category. + typedef std::random_access_iterator_tag iterator_category; + + /// Default constructor. Creates an iterator in an undefined state. + buffers_iterator() + : current_buffer_(), + current_buffer_position_(0), + begin_(), + current_(), + end_(), + position_(0) + { + } + + /// Construct an iterator representing the beginning of the buffers' data. + static buffers_iterator begin(const BufferSequence& buffers) +#if defined(__GNUC__) && (__GNUC__ == 4) && (__GNUC_MINOR__ == 3) + __attribute__ ((__noinline__)) +#endif // defined(__GNUC__) && (__GNUC__ == 4) && (__GNUC_MINOR__ == 3) + { + buffers_iterator new_iter; + new_iter.begin_ = asio::buffer_sequence_begin(buffers); + new_iter.current_ = asio::buffer_sequence_begin(buffers); + new_iter.end_ = asio::buffer_sequence_end(buffers); + while (new_iter.current_ != new_iter.end_) + { + new_iter.current_buffer_ = *new_iter.current_; + if (new_iter.current_buffer_.size() > 0) + break; + ++new_iter.current_; + } + return new_iter; + } + + /// Construct an iterator representing the end of the buffers' data. + static buffers_iterator end(const BufferSequence& buffers) +#if defined(__GNUC__) && (__GNUC__ == 4) && (__GNUC_MINOR__ == 3) + __attribute__ ((__noinline__)) +#endif // defined(__GNUC__) && (__GNUC__ == 4) && (__GNUC_MINOR__ == 3) + { + buffers_iterator new_iter; + new_iter.begin_ = asio::buffer_sequence_begin(buffers); + new_iter.current_ = asio::buffer_sequence_begin(buffers); + new_iter.end_ = asio::buffer_sequence_end(buffers); + while (new_iter.current_ != new_iter.end_) + { + buffer_type buffer = *new_iter.current_; + new_iter.position_ += buffer.size(); + ++new_iter.current_; + } + return new_iter; + } + + /// Dereference an iterator. + reference operator*() const + { + return dereference(); + } + + /// Dereference an iterator. + pointer operator->() const + { + return &dereference(); + } + + /// Access an individual element. + reference operator[](std::ptrdiff_t difference) const + { + buffers_iterator tmp(*this); + tmp.advance(difference); + return *tmp; + } + + /// Increment operator (prefix). + buffers_iterator& operator++() + { + increment(); + return *this; + } + + /// Increment operator (postfix). + buffers_iterator operator++(int) + { + buffers_iterator tmp(*this); + ++*this; + return tmp; + } + + /// Decrement operator (prefix). + buffers_iterator& operator--() + { + decrement(); + return *this; + } + + /// Decrement operator (postfix). + buffers_iterator operator--(int) + { + buffers_iterator tmp(*this); + --*this; + return tmp; + } + + /// Addition operator. + buffers_iterator& operator+=(std::ptrdiff_t difference) + { + advance(difference); + return *this; + } + + /// Subtraction operator. + buffers_iterator& operator-=(std::ptrdiff_t difference) + { + advance(-difference); + return *this; + } + + /// Addition operator. + friend buffers_iterator operator+(const buffers_iterator& iter, + std::ptrdiff_t difference) + { + buffers_iterator tmp(iter); + tmp.advance(difference); + return tmp; + } + + /// Addition operator. + friend buffers_iterator operator+(std::ptrdiff_t difference, + const buffers_iterator& iter) + { + buffers_iterator tmp(iter); + tmp.advance(difference); + return tmp; + } + + /// Subtraction operator. + friend buffers_iterator operator-(const buffers_iterator& iter, + std::ptrdiff_t difference) + { + buffers_iterator tmp(iter); + tmp.advance(-difference); + return tmp; + } + + /// Subtraction operator. + friend std::ptrdiff_t operator-(const buffers_iterator& a, + const buffers_iterator& b) + { + return b.distance_to(a); + } + + /// Test two iterators for equality. + friend bool operator==(const buffers_iterator& a, const buffers_iterator& b) + { + return a.equal(b); + } + + /// Test two iterators for inequality. + friend bool operator!=(const buffers_iterator& a, const buffers_iterator& b) + { + return !a.equal(b); + } + + /// Compare two iterators. + friend bool operator<(const buffers_iterator& a, const buffers_iterator& b) + { + return a.distance_to(b) > 0; + } + + /// Compare two iterators. + friend bool operator<=(const buffers_iterator& a, const buffers_iterator& b) + { + return !(b < a); + } + + /// Compare two iterators. + friend bool operator>(const buffers_iterator& a, const buffers_iterator& b) + { + return b < a; + } + + /// Compare two iterators. + friend bool operator>=(const buffers_iterator& a, const buffers_iterator& b) + { + return !(a < b); + } + +private: + // Dereference the iterator. + reference dereference() const + { + return static_cast( + current_buffer_.data())[current_buffer_position_]; + } + + // Compare two iterators for equality. + bool equal(const buffers_iterator& other) const + { + return position_ == other.position_; + } + + // Increment the iterator. + void increment() + { + ASIO_ASSERT(current_ != end_ && "iterator out of bounds"); + ++position_; + + // Check if the increment can be satisfied by the current buffer. + ++current_buffer_position_; + if (current_buffer_position_ != current_buffer_.size()) + return; + + // Find the next non-empty buffer. + ++current_; + current_buffer_position_ = 0; + while (current_ != end_) + { + current_buffer_ = *current_; + if (current_buffer_.size() > 0) + return; + ++current_; + } + } + + // Decrement the iterator. + void decrement() + { + ASIO_ASSERT(position_ > 0 && "iterator out of bounds"); + --position_; + + // Check if the decrement can be satisfied by the current buffer. + if (current_buffer_position_ != 0) + { + --current_buffer_position_; + return; + } + + // Find the previous non-empty buffer. + buffer_sequence_iterator_type iter = current_; + while (iter != begin_) + { + --iter; + buffer_type buffer = *iter; + std::size_t buffer_size = buffer.size(); + if (buffer_size > 0) + { + current_ = iter; + current_buffer_ = buffer; + current_buffer_position_ = buffer_size - 1; + return; + } + } + } + + // Advance the iterator by the specified distance. + void advance(std::ptrdiff_t n) + { + if (n > 0) + { + ASIO_ASSERT(current_ != end_ && "iterator out of bounds"); + for (;;) + { + std::ptrdiff_t current_buffer_balance + = current_buffer_.size() - current_buffer_position_; + + // Check if the advance can be satisfied by the current buffer. + if (current_buffer_balance > n) + { + position_ += n; + current_buffer_position_ += n; + return; + } + + // Update position. + n -= current_buffer_balance; + position_ += current_buffer_balance; + + // Move to next buffer. If it is empty then it will be skipped on the + // next iteration of this loop. + if (++current_ == end_) + { + ASIO_ASSERT(n == 0 && "iterator out of bounds"); + current_buffer_ = buffer_type(); + current_buffer_position_ = 0; + return; + } + current_buffer_ = *current_; + current_buffer_position_ = 0; + } + } + else if (n < 0) + { + std::size_t abs_n = -n; + ASIO_ASSERT(position_ >= abs_n && "iterator out of bounds"); + for (;;) + { + // Check if the advance can be satisfied by the current buffer. + if (current_buffer_position_ >= abs_n) + { + position_ -= abs_n; + current_buffer_position_ -= abs_n; + return; + } + + // Update position. + abs_n -= current_buffer_position_; + position_ -= current_buffer_position_; + + // Check if we've reached the beginning of the buffers. + if (current_ == begin_) + { + ASIO_ASSERT(abs_n == 0 && "iterator out of bounds"); + current_buffer_position_ = 0; + return; + } + + // Find the previous non-empty buffer. + buffer_sequence_iterator_type iter = current_; + while (iter != begin_) + { + --iter; + buffer_type buffer = *iter; + std::size_t buffer_size = buffer.size(); + if (buffer_size > 0) + { + current_ = iter; + current_buffer_ = buffer; + current_buffer_position_ = buffer_size; + break; + } + } + } + } + } + + // Determine the distance between two iterators. + std::ptrdiff_t distance_to(const buffers_iterator& other) const + { + return other.position_ - position_; + } + + buffer_type current_buffer_; + std::size_t current_buffer_position_; + buffer_sequence_iterator_type begin_; + buffer_sequence_iterator_type current_; + buffer_sequence_iterator_type end_; + std::size_t position_; +}; + +/// Construct an iterator representing the beginning of the buffers' data. +template +inline buffers_iterator buffers_begin( + const BufferSequence& buffers) +{ + return buffers_iterator::begin(buffers); +} + +/// Construct an iterator representing the end of the buffers' data. +template +inline buffers_iterator buffers_end( + const BufferSequence& buffers) +{ + return buffers_iterator::end(buffers); +} + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_BUFFERS_ITERATOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/co_spawn.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/co_spawn.hpp new file mode 100644 index 000000000..38ee7ff48 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/co_spawn.hpp @@ -0,0 +1,471 @@ +// +// co_spawn.hpp +// ~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_CO_SPAWN_HPP +#define ASIO_CO_SPAWN_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_CO_AWAIT) || defined(GENERATING_DOCUMENTATION) + +#include "asio/awaitable.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution_context.hpp" +#include "asio/is_executor.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +struct awaitable_signature; + +template +struct awaitable_signature> +{ + typedef void type(std::exception_ptr, T); +}; + +template +struct awaitable_signature> +{ + typedef void type(std::exception_ptr); +}; + +} // namespace detail + +/// Spawn a new coroutined-based thread of execution. +/** + * @param ex The executor that will be used to schedule the new thread of + * execution. + * + * @param a The asio::awaitable object that is the result of calling the + * coroutine's entry point function. + * + * @param token The completion token that will handle the notification that + * the thread of execution has completed. The function signature of the + * completion handler must be: + * @code void handler(std::exception_ptr, T); @endcode + * + * @par Example + * @code + * asio::awaitable echo(tcp::socket socket) + * { + * std::size_t bytes_transferred = 0; + * + * try + * { + * char data[1024]; + * for (;;) + * { + * std::size_t n = co_await socket.async_read_some( + * asio::buffer(data), asio::use_awaitable); + * + * co_await asio::async_write(socket, + * asio::buffer(data, n), asio::use_awaitable); + * + * bytes_transferred += n; + * } + * } + * catch (const std::exception&) + * { + * } + * + * co_return bytes_transferred; + * } + * + * // ... + * + * asio::co_spawn(my_executor, + * echo(std::move(my_tcp_socket)), + * [](std::exception_ptr e, std::size_t n) + * { + * std::cout << "transferred " << n << "\n"; + * }); + * @endcode + */ +template +inline ASIO_INITFN_AUTO_RESULT_TYPE( + CompletionToken, void(std::exception_ptr, T)) +co_spawn(const Executor& ex, awaitable a, + CompletionToken&& token + ASIO_DEFAULT_COMPLETION_TOKEN(Executor), + typename enable_if< + (is_executor::value || execution::is_executor::value) + && is_convertible::value + >::type* = 0); + +/// Spawn a new coroutined-based thread of execution. +/** + * @param ex The executor that will be used to schedule the new thread of + * execution. + * + * @param a The asio::awaitable object that is the result of calling the + * coroutine's entry point function. + * + * @param token The completion token that will handle the notification that + * the thread of execution has completed. The function signature of the + * completion handler must be: + * @code void handler(std::exception_ptr); @endcode + * + * @par Example + * @code + * asio::awaitable echo(tcp::socket socket) + * { + * try + * { + * char data[1024]; + * for (;;) + * { + * std::size_t n = co_await socket.async_read_some( + * asio::buffer(data), asio::use_awaitable); + * + * co_await asio::async_write(socket, + * asio::buffer(data, n), asio::use_awaitable); + * } + * } + * catch (const std::exception& e) + * { + * std::cerr << "Exception: " << e.what() << "\n"; + * } + * } + * + * // ... + * + * asio::co_spawn(my_executor, + * echo(std::move(my_tcp_socket)), + * asio::detached); + * @endcode + */ +template +inline ASIO_INITFN_AUTO_RESULT_TYPE( + CompletionToken, void(std::exception_ptr)) +co_spawn(const Executor& ex, awaitable a, + CompletionToken&& token + ASIO_DEFAULT_COMPLETION_TOKEN(Executor), + typename enable_if< + (is_executor::value || execution::is_executor::value) + && is_convertible::value + >::type* = 0); + +/// Spawn a new coroutined-based thread of execution. +/** + * @param ctx An execution context that will provide the executor to be used to + * schedule the new thread of execution. + * + * @param a The asio::awaitable object that is the result of calling the + * coroutine's entry point function. + * + * @param token The completion token that will handle the notification that + * the thread of execution has completed. The function signature of the + * completion handler must be: + * @code void handler(std::exception_ptr); @endcode + * + * @par Example + * @code + * asio::awaitable echo(tcp::socket socket) + * { + * std::size_t bytes_transferred = 0; + * + * try + * { + * char data[1024]; + * for (;;) + * { + * std::size_t n = co_await socket.async_read_some( + * asio::buffer(data), asio::use_awaitable); + * + * co_await asio::async_write(socket, + * asio::buffer(data, n), asio::use_awaitable); + * + * bytes_transferred += n; + * } + * } + * catch (const std::exception&) + * { + * } + * + * co_return bytes_transferred; + * } + * + * // ... + * + * asio::co_spawn(my_io_context, + * echo(std::move(my_tcp_socket)), + * [](std::exception_ptr e, std::size_t n) + * { + * std::cout << "transferred " << n << "\n"; + * }); + * @endcode + */ +template +inline ASIO_INITFN_AUTO_RESULT_TYPE( + CompletionToken, void(std::exception_ptr, T)) +co_spawn(ExecutionContext& ctx, awaitable a, + CompletionToken&& token + ASIO_DEFAULT_COMPLETION_TOKEN( + typename ExecutionContext::executor_type), + typename enable_if< + is_convertible::value + && is_convertible::value + >::type* = 0); + +/// Spawn a new coroutined-based thread of execution. +/** + * @param ctx An execution context that will provide the executor to be used to + * schedule the new thread of execution. + * + * @param a The asio::awaitable object that is the result of calling the + * coroutine's entry point function. + * + * @param token The completion token that will handle the notification that + * the thread of execution has completed. The function signature of the + * completion handler must be: + * @code void handler(std::exception_ptr); @endcode + * + * @par Example + * @code + * asio::awaitable echo(tcp::socket socket) + * { + * try + * { + * char data[1024]; + * for (;;) + * { + * std::size_t n = co_await socket.async_read_some( + * asio::buffer(data), asio::use_awaitable); + * + * co_await asio::async_write(socket, + * asio::buffer(data, n), asio::use_awaitable); + * } + * } + * catch (const std::exception& e) + * { + * std::cerr << "Exception: " << e.what() << "\n"; + * } + * } + * + * // ... + * + * asio::co_spawn(my_io_context, + * echo(std::move(my_tcp_socket)), + * asio::detached); + * @endcode + */ +template +inline ASIO_INITFN_AUTO_RESULT_TYPE( + CompletionToken, void(std::exception_ptr)) +co_spawn(ExecutionContext& ctx, awaitable a, + CompletionToken&& token + ASIO_DEFAULT_COMPLETION_TOKEN( + typename ExecutionContext::executor_type), + typename enable_if< + is_convertible::value + && is_convertible::value + >::type* = 0); + +/// Spawn a new coroutined-based thread of execution. +/** + * @param ex The executor that will be used to schedule the new thread of + * execution. + * + * @param f A nullary function object with a return type of the form + * @c asio::awaitable that will be used as the coroutine's entry + * point. + * + * @param token The completion token that will handle the notification that the + * thread of execution has completed. If @c R is @c void, the function + * signature of the completion handler must be: + * + * @code void handler(std::exception_ptr); @endcode + * Otherwise, the function signature of the completion handler must be: + * @code void handler(std::exception_ptr, R); @endcode + * + * + * @par Example + * @code + * asio::awaitable echo(tcp::socket socket) + * { + * std::size_t bytes_transferred = 0; + * + * try + * { + * char data[1024]; + * for (;;) + * { + * std::size_t n = co_await socket.async_read_some( + * asio::buffer(data), asio::use_awaitable); + * + * co_await asio::async_write(socket, + * asio::buffer(data, n), asio::use_awaitable); + * + * bytes_transferred += n; + * } + * } + * catch (const std::exception&) + * { + * } + * + * co_return bytes_transferred; + * } + * + * // ... + * + * asio::co_spawn(my_executor, + * [socket = std::move(my_tcp_socket)]() mutable + * -> asio::awaitable + * { + * try + * { + * char data[1024]; + * for (;;) + * { + * std::size_t n = co_await socket.async_read_some( + * asio::buffer(data), asio::use_awaitable); + * + * co_await asio::async_write(socket, + * asio::buffer(data, n), asio::use_awaitable); + * } + * } + * catch (const std::exception& e) + * { + * std::cerr << "Exception: " << e.what() << "\n"; + * } + * }, asio::detached); + * @endcode + */ +template ::type>::type) CompletionToken + ASIO_DEFAULT_COMPLETION_TOKEN_TYPE(Executor)> +ASIO_INITFN_AUTO_RESULT_TYPE(CompletionToken, + typename detail::awaitable_signature::type>::type) +co_spawn(const Executor& ex, F&& f, + CompletionToken&& token + ASIO_DEFAULT_COMPLETION_TOKEN(Executor), + typename enable_if< + is_executor::value || execution::is_executor::value + >::type* = 0); + +/// Spawn a new coroutined-based thread of execution. +/** + * @param ctx An execution context that will provide the executor to be used to + * schedule the new thread of execution. + * + * @param f A nullary function object with a return type of the form + * @c asio::awaitable that will be used as the coroutine's entry + * point. + * + * @param token The completion token that will handle the notification that the + * thread of execution has completed. If @c R is @c void, the function + * signature of the completion handler must be: + * + * @code void handler(std::exception_ptr); @endcode + * Otherwise, the function signature of the completion handler must be: + * @code void handler(std::exception_ptr, R); @endcode + * + * + * @par Example + * @code + * asio::awaitable echo(tcp::socket socket) + * { + * std::size_t bytes_transferred = 0; + * + * try + * { + * char data[1024]; + * for (;;) + * { + * std::size_t n = co_await socket.async_read_some( + * asio::buffer(data), asio::use_awaitable); + * + * co_await asio::async_write(socket, + * asio::buffer(data, n), asio::use_awaitable); + * + * bytes_transferred += n; + * } + * } + * catch (const std::exception&) + * { + * } + * + * co_return bytes_transferred; + * } + * + * // ... + * + * asio::co_spawn(my_io_context, + * [socket = std::move(my_tcp_socket)]() mutable + * -> asio::awaitable + * { + * try + * { + * char data[1024]; + * for (;;) + * { + * std::size_t n = co_await socket.async_read_some( + * asio::buffer(data), asio::use_awaitable); + * + * co_await asio::async_write(socket, + * asio::buffer(data, n), asio::use_awaitable); + * } + * } + * catch (const std::exception& e) + * { + * std::cerr << "Exception: " << e.what() << "\n"; + * } + * }, asio::detached); + * @endcode + */ +template ::type>::type) CompletionToken + ASIO_DEFAULT_COMPLETION_TOKEN_TYPE( + typename ExecutionContext::executor_type)> +ASIO_INITFN_AUTO_RESULT_TYPE(CompletionToken, + typename detail::awaitable_signature::type>::type) +co_spawn(ExecutionContext& ctx, F&& f, + CompletionToken&& token + ASIO_DEFAULT_COMPLETION_TOKEN( + typename ExecutionContext::executor_type), + typename enable_if< + is_convertible::value + >::type* = 0); + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/impl/co_spawn.hpp" + +#endif // defined(ASIO_HAS_CO_AWAIT) || defined(GENERATING_DOCUMENTATION) + +#endif // ASIO_CO_SPAWN_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/completion_condition.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/completion_condition.hpp new file mode 100644 index 000000000..3df578934 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/completion_condition.hpp @@ -0,0 +1,218 @@ +// +// completion_condition.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_COMPLETION_CONDITION_HPP +#define ASIO_COMPLETION_CONDITION_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include + +#include "asio/detail/push_options.hpp" + +namespace asio { + +namespace detail { + +// The default maximum number of bytes to transfer in a single operation. +enum default_max_transfer_size_t { default_max_transfer_size = 65536 }; + +// Adapt result of old-style completion conditions (which had a bool result +// where true indicated that the operation was complete). +inline std::size_t adapt_completion_condition_result(bool result) +{ + return result ? 0 : default_max_transfer_size; +} + +// Adapt result of current completion conditions (which have a size_t result +// where 0 means the operation is complete, and otherwise the result is the +// maximum number of bytes to transfer on the next underlying operation). +inline std::size_t adapt_completion_condition_result(std::size_t result) +{ + return result; +} + +class transfer_all_t +{ +public: + typedef std::size_t result_type; + + template + std::size_t operator()(const Error& err, std::size_t) + { + return !!err ? 0 : default_max_transfer_size; + } +}; + +class transfer_at_least_t +{ +public: + typedef std::size_t result_type; + + explicit transfer_at_least_t(std::size_t minimum) + : minimum_(minimum) + { + } + + template + std::size_t operator()(const Error& err, std::size_t bytes_transferred) + { + return (!!err || bytes_transferred >= minimum_) + ? 0 : default_max_transfer_size; + } + +private: + std::size_t minimum_; +}; + +class transfer_exactly_t +{ +public: + typedef std::size_t result_type; + + explicit transfer_exactly_t(std::size_t size) + : size_(size) + { + } + + template + std::size_t operator()(const Error& err, std::size_t bytes_transferred) + { + return (!!err || bytes_transferred >= size_) ? 0 : + (size_ - bytes_transferred < default_max_transfer_size + ? size_ - bytes_transferred : std::size_t(default_max_transfer_size)); + } + +private: + std::size_t size_; +}; + +} // namespace detail + +/** + * @defgroup completion_condition Completion Condition Function Objects + * + * Function objects used for determining when a read or write operation should + * complete. + */ +/*@{*/ + +/// Return a completion condition function object that indicates that a read or +/// write operation should continue until all of the data has been transferred, +/// or until an error occurs. +/** + * This function is used to create an object, of unspecified type, that meets + * CompletionCondition requirements. + * + * @par Example + * Reading until a buffer is full: + * @code + * boost::array buf; + * asio::error_code ec; + * std::size_t n = asio::read( + * sock, asio::buffer(buf), + * asio::transfer_all(), ec); + * if (ec) + * { + * // An error occurred. + * } + * else + * { + * // n == 128 + * } + * @endcode + */ +#if defined(GENERATING_DOCUMENTATION) +unspecified transfer_all(); +#else +inline detail::transfer_all_t transfer_all() +{ + return detail::transfer_all_t(); +} +#endif + +/// Return a completion condition function object that indicates that a read or +/// write operation should continue until a minimum number of bytes has been +/// transferred, or until an error occurs. +/** + * This function is used to create an object, of unspecified type, that meets + * CompletionCondition requirements. + * + * @par Example + * Reading until a buffer is full or contains at least 64 bytes: + * @code + * boost::array buf; + * asio::error_code ec; + * std::size_t n = asio::read( + * sock, asio::buffer(buf), + * asio::transfer_at_least(64), ec); + * if (ec) + * { + * // An error occurred. + * } + * else + * { + * // n >= 64 && n <= 128 + * } + * @endcode + */ +#if defined(GENERATING_DOCUMENTATION) +unspecified transfer_at_least(std::size_t minimum); +#else +inline detail::transfer_at_least_t transfer_at_least(std::size_t minimum) +{ + return detail::transfer_at_least_t(minimum); +} +#endif + +/// Return a completion condition function object that indicates that a read or +/// write operation should continue until an exact number of bytes has been +/// transferred, or until an error occurs. +/** + * This function is used to create an object, of unspecified type, that meets + * CompletionCondition requirements. + * + * @par Example + * Reading until a buffer is full or contains exactly 64 bytes: + * @code + * boost::array buf; + * asio::error_code ec; + * std::size_t n = asio::read( + * sock, asio::buffer(buf), + * asio::transfer_exactly(64), ec); + * if (ec) + * { + * // An error occurred. + * } + * else + * { + * // n == 64 + * } + * @endcode + */ +#if defined(GENERATING_DOCUMENTATION) +unspecified transfer_exactly(std::size_t size); +#else +inline detail::transfer_exactly_t transfer_exactly(std::size_t size) +{ + return detail::transfer_exactly_t(size); +} +#endif + +/*@}*/ + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_COMPLETION_CONDITION_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/compose.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/compose.hpp new file mode 100644 index 000000000..fbbb4fe46 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/compose.hpp @@ -0,0 +1,136 @@ +// +// compose.hpp +// ~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_COMPOSE_HPP +#define ASIO_COMPOSE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/async_result.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) \ + || defined(GENERATING_DOCUMENTATION) + +/// Launch an asynchronous operation with a stateful implementation. +/** + * The async_compose function simplifies the implementation of composed + * asynchronous operations automatically wrapping a stateful function object + * with a conforming intermediate completion handler. + * + * @param implementation A function object that contains the implementation of + * the composed asynchronous operation. The first argument to the function + * object is a non-const reference to the enclosing intermediate completion + * handler. The remaining arguments are any arguments that originate from the + * completion handlers of any asynchronous operations performed by the + * implementation. + + * @param token The completion token. + * + * @param io_objects_or_executors Zero or more I/O objects or I/O executors for + * which outstanding work must be maintained. + * + * @par Example: + * + * @code struct async_echo_implementation + * { + * tcp::socket& socket_; + * asio::mutable_buffer buffer_; + * enum { starting, reading, writing } state_; + * + * template + * void operator()(Self& self, + * asio::error_code error = {}, + * std::size_t n = 0) + * { + * switch (state_) + * { + * case starting: + * state_ = reading; + * socket_.async_read_some( + * buffer_, std::move(self)); + * break; + * case reading: + * if (error) + * { + * self.complete(error, 0); + * } + * else + * { + * state_ = writing; + * asio::async_write(socket_, buffer_, + * asio::transfer_exactly(n), + * std::move(self)); + * } + * break; + * case writing: + * self.complete(error, n); + * break; + * } + * } + * }; + * + * template + * auto async_echo(tcp::socket& socket, + * asio::mutable_buffer buffer, + * CompletionToken&& token) -> + * typename asio::async_result< + * typename std::decay::type, + * void(asio::error_code, std::size_t)>::return_type + * { + * return asio::async_compose( + * async_echo_implementation{socket, buffer, + * async_echo_implementation::starting}, + * token, socket); + * } @endcode + */ +template +ASIO_INITFN_AUTO_RESULT_TYPE(CompletionToken, Signature) +async_compose(ASIO_MOVE_ARG(Implementation) implementation, + ASIO_NONDEDUCED_MOVE_ARG(CompletionToken) token, + ASIO_MOVE_ARG(IoObjectsOrExecutors)... io_objects_or_executors); + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + // || defined(GENERATING_DOCUMENTATION) + +template +ASIO_INITFN_AUTO_RESULT_TYPE(CompletionToken, Signature) +async_compose(ASIO_MOVE_ARG(Implementation) implementation, + ASIO_NONDEDUCED_MOVE_ARG(CompletionToken) token); + +#define ASIO_PRIVATE_ASYNC_COMPOSE_DEF(n) \ + template \ + ASIO_INITFN_AUTO_RESULT_TYPE(CompletionToken, Signature) \ + async_compose(ASIO_MOVE_ARG(Implementation) implementation, \ + ASIO_NONDEDUCED_MOVE_ARG(CompletionToken) token, \ + ASIO_VARIADIC_MOVE_PARAMS(n)); + /**/ + ASIO_VARIADIC_GENERATE(ASIO_PRIVATE_ASYNC_COMPOSE_DEF) +#undef ASIO_PRIVATE_ASYNC_COMPOSE_DEF + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) + // || defined(GENERATING_DOCUMENTATION) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/impl/compose.hpp" + +#endif // ASIO_COMPOSE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/connect.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/connect.hpp new file mode 100644 index 000000000..46a890c52 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/connect.hpp @@ -0,0 +1,1076 @@ +// +// connect.hpp +// ~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_CONNECT_HPP +#define ASIO_CONNECT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/async_result.hpp" +#include "asio/basic_socket.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +namespace detail +{ + char (&has_iterator_helper(...))[2]; + + template + char has_iterator_helper(T*, typename T::iterator* = 0); + + template + struct has_iterator_typedef + { + enum { value = (sizeof((has_iterator_helper)((T*)(0))) == 1) }; + }; +} // namespace detail + +/// Type trait used to determine whether a type is an endpoint sequence that can +/// be used with with @c connect and @c async_connect. +template +struct is_endpoint_sequence +{ +#if defined(GENERATING_DOCUMENTATION) + /// The value member is true if the type may be used as an endpoint sequence. + static const bool value; +#else + enum + { + value = detail::has_iterator_typedef::value + }; +#endif +}; + +/** + * @defgroup connect asio::connect + * + * @brief The @c connect function is a composed operation that establishes a + * socket connection by trying each endpoint in a sequence. + */ +/*@{*/ + +/// Establishes a socket connection by trying each endpoint in a sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c connect member + * function, once for each endpoint in the sequence, until a connection is + * successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param endpoints A sequence of endpoints. + * + * @returns The successfully connected endpoint. + * + * @throws asio::system_error Thrown on failure. If the sequence is + * empty, the associated @c error_code is asio::error::not_found. + * Otherwise, contains the error from the last connection attempt. + * + * @par Example + * @code tcp::resolver r(my_context); + * tcp::resolver::query q("host", "service"); + * tcp::socket s(my_context); + * asio::connect(s, r.resolve(q)); @endcode + */ +template +typename Protocol::endpoint connect(basic_socket& s, + const EndpointSequence& endpoints, + typename enable_if::value>::type* = 0); + +/// Establishes a socket connection by trying each endpoint in a sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c connect member + * function, once for each endpoint in the sequence, until a connection is + * successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param endpoints A sequence of endpoints. + * + * @param ec Set to indicate what error occurred, if any. If the sequence is + * empty, set to asio::error::not_found. Otherwise, contains the error + * from the last connection attempt. + * + * @returns On success, the successfully connected endpoint. Otherwise, a + * default-constructed endpoint. + * + * @par Example + * @code tcp::resolver r(my_context); + * tcp::resolver::query q("host", "service"); + * tcp::socket s(my_context); + * asio::error_code ec; + * asio::connect(s, r.resolve(q), ec); + * if (ec) + * { + * // An error occurred. + * } @endcode + */ +template +typename Protocol::endpoint connect(basic_socket& s, + const EndpointSequence& endpoints, asio::error_code& ec, + typename enable_if::value>::type* = 0); + +#if !defined(ASIO_NO_DEPRECATED) +/// (Deprecated: Use range overload.) Establishes a socket connection by trying +/// each endpoint in a sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c connect member + * function, once for each endpoint in the sequence, until a connection is + * successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param begin An iterator pointing to the start of a sequence of endpoints. + * + * @returns On success, an iterator denoting the successfully connected + * endpoint. Otherwise, the end iterator. + * + * @throws asio::system_error Thrown on failure. If the sequence is + * empty, the associated @c error_code is asio::error::not_found. + * Otherwise, contains the error from the last connection attempt. + * + * @note This overload assumes that a default constructed object of type @c + * Iterator represents the end of the sequence. This is a valid assumption for + * iterator types such as @c asio::ip::tcp::resolver::iterator. + */ +template +Iterator connect(basic_socket& s, Iterator begin, + typename enable_if::value>::type* = 0); + +/// (Deprecated: Use range overload.) Establishes a socket connection by trying +/// each endpoint in a sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c connect member + * function, once for each endpoint in the sequence, until a connection is + * successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param begin An iterator pointing to the start of a sequence of endpoints. + * + * @param ec Set to indicate what error occurred, if any. If the sequence is + * empty, set to asio::error::not_found. Otherwise, contains the error + * from the last connection attempt. + * + * @returns On success, an iterator denoting the successfully connected + * endpoint. Otherwise, the end iterator. + * + * @note This overload assumes that a default constructed object of type @c + * Iterator represents the end of the sequence. This is a valid assumption for + * iterator types such as @c asio::ip::tcp::resolver::iterator. + */ +template +Iterator connect(basic_socket& s, + Iterator begin, asio::error_code& ec, + typename enable_if::value>::type* = 0); +#endif // !defined(ASIO_NO_DEPRECATED) + +/// Establishes a socket connection by trying each endpoint in a sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c connect member + * function, once for each endpoint in the sequence, until a connection is + * successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param begin An iterator pointing to the start of a sequence of endpoints. + * + * @param end An iterator pointing to the end of a sequence of endpoints. + * + * @returns An iterator denoting the successfully connected endpoint. + * + * @throws asio::system_error Thrown on failure. If the sequence is + * empty, the associated @c error_code is asio::error::not_found. + * Otherwise, contains the error from the last connection attempt. + * + * @par Example + * @code tcp::resolver r(my_context); + * tcp::resolver::query q("host", "service"); + * tcp::resolver::results_type e = r.resolve(q); + * tcp::socket s(my_context); + * asio::connect(s, e.begin(), e.end()); @endcode + */ +template +Iterator connect(basic_socket& s, + Iterator begin, Iterator end); + +/// Establishes a socket connection by trying each endpoint in a sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c connect member + * function, once for each endpoint in the sequence, until a connection is + * successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param begin An iterator pointing to the start of a sequence of endpoints. + * + * @param end An iterator pointing to the end of a sequence of endpoints. + * + * @param ec Set to indicate what error occurred, if any. If the sequence is + * empty, set to asio::error::not_found. Otherwise, contains the error + * from the last connection attempt. + * + * @returns On success, an iterator denoting the successfully connected + * endpoint. Otherwise, the end iterator. + * + * @par Example + * @code tcp::resolver r(my_context); + * tcp::resolver::query q("host", "service"); + * tcp::resolver::results_type e = r.resolve(q); + * tcp::socket s(my_context); + * asio::error_code ec; + * asio::connect(s, e.begin(), e.end(), ec); + * if (ec) + * { + * // An error occurred. + * } @endcode + */ +template +Iterator connect(basic_socket& s, + Iterator begin, Iterator end, asio::error_code& ec); + +/// Establishes a socket connection by trying each endpoint in a sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c connect member + * function, once for each endpoint in the sequence, until a connection is + * successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param endpoints A sequence of endpoints. + * + * @param connect_condition A function object that is called prior to each + * connection attempt. The signature of the function object must be: + * @code bool connect_condition( + * const asio::error_code& ec, + * const typename Protocol::endpoint& next); @endcode + * The @c ec parameter contains the result from the most recent connect + * operation. Before the first connection attempt, @c ec is always set to + * indicate success. The @c next parameter is the next endpoint to be tried. + * The function object should return true if the next endpoint should be tried, + * and false if it should be skipped. + * + * @returns The successfully connected endpoint. + * + * @throws asio::system_error Thrown on failure. If the sequence is + * empty, the associated @c error_code is asio::error::not_found. + * Otherwise, contains the error from the last connection attempt. + * + * @par Example + * The following connect condition function object can be used to output + * information about the individual connection attempts: + * @code struct my_connect_condition + * { + * bool operator()( + * const asio::error_code& ec, + * const::tcp::endpoint& next) + * { + * if (ec) std::cout << "Error: " << ec.message() << std::endl; + * std::cout << "Trying: " << next << std::endl; + * return true; + * } + * }; @endcode + * It would be used with the asio::connect function as follows: + * @code tcp::resolver r(my_context); + * tcp::resolver::query q("host", "service"); + * tcp::socket s(my_context); + * tcp::endpoint e = asio::connect(s, + * r.resolve(q), my_connect_condition()); + * std::cout << "Connected to: " << e << std::endl; @endcode + */ +template +typename Protocol::endpoint connect(basic_socket& s, + const EndpointSequence& endpoints, ConnectCondition connect_condition, + typename enable_if::value>::type* = 0); + +/// Establishes a socket connection by trying each endpoint in a sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c connect member + * function, once for each endpoint in the sequence, until a connection is + * successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param endpoints A sequence of endpoints. + * + * @param connect_condition A function object that is called prior to each + * connection attempt. The signature of the function object must be: + * @code bool connect_condition( + * const asio::error_code& ec, + * const typename Protocol::endpoint& next); @endcode + * The @c ec parameter contains the result from the most recent connect + * operation. Before the first connection attempt, @c ec is always set to + * indicate success. The @c next parameter is the next endpoint to be tried. + * The function object should return true if the next endpoint should be tried, + * and false if it should be skipped. + * + * @param ec Set to indicate what error occurred, if any. If the sequence is + * empty, set to asio::error::not_found. Otherwise, contains the error + * from the last connection attempt. + * + * @returns On success, the successfully connected endpoint. Otherwise, a + * default-constructed endpoint. + * + * @par Example + * The following connect condition function object can be used to output + * information about the individual connection attempts: + * @code struct my_connect_condition + * { + * bool operator()( + * const asio::error_code& ec, + * const::tcp::endpoint& next) + * { + * if (ec) std::cout << "Error: " << ec.message() << std::endl; + * std::cout << "Trying: " << next << std::endl; + * return true; + * } + * }; @endcode + * It would be used with the asio::connect function as follows: + * @code tcp::resolver r(my_context); + * tcp::resolver::query q("host", "service"); + * tcp::socket s(my_context); + * asio::error_code ec; + * tcp::endpoint e = asio::connect(s, + * r.resolve(q), my_connect_condition(), ec); + * if (ec) + * { + * // An error occurred. + * } + * else + * { + * std::cout << "Connected to: " << e << std::endl; + * } @endcode + */ +template +typename Protocol::endpoint connect(basic_socket& s, + const EndpointSequence& endpoints, ConnectCondition connect_condition, + asio::error_code& ec, + typename enable_if::value>::type* = 0); + +#if !defined(ASIO_NO_DEPRECATED) +/// (Deprecated: Use range overload.) Establishes a socket connection by trying +/// each endpoint in a sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c connect member + * function, once for each endpoint in the sequence, until a connection is + * successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param begin An iterator pointing to the start of a sequence of endpoints. + * + * @param connect_condition A function object that is called prior to each + * connection attempt. The signature of the function object must be: + * @code bool connect_condition( + * const asio::error_code& ec, + * const typename Protocol::endpoint& next); @endcode + * The @c ec parameter contains the result from the most recent connect + * operation. Before the first connection attempt, @c ec is always set to + * indicate success. The @c next parameter is the next endpoint to be tried. + * The function object should return true if the next endpoint should be tried, + * and false if it should be skipped. + * + * @returns On success, an iterator denoting the successfully connected + * endpoint. Otherwise, the end iterator. + * + * @throws asio::system_error Thrown on failure. If the sequence is + * empty, the associated @c error_code is asio::error::not_found. + * Otherwise, contains the error from the last connection attempt. + * + * @note This overload assumes that a default constructed object of type @c + * Iterator represents the end of the sequence. This is a valid assumption for + * iterator types such as @c asio::ip::tcp::resolver::iterator. + */ +template +Iterator connect(basic_socket& s, + Iterator begin, ConnectCondition connect_condition, + typename enable_if::value>::type* = 0); + +/// (Deprecated: Use range overload.) Establishes a socket connection by trying +/// each endpoint in a sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c connect member + * function, once for each endpoint in the sequence, until a connection is + * successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param begin An iterator pointing to the start of a sequence of endpoints. + * + * @param connect_condition A function object that is called prior to each + * connection attempt. The signature of the function object must be: + * @code bool connect_condition( + * const asio::error_code& ec, + * const typename Protocol::endpoint& next); @endcode + * The @c ec parameter contains the result from the most recent connect + * operation. Before the first connection attempt, @c ec is always set to + * indicate success. The @c next parameter is the next endpoint to be tried. + * The function object should return true if the next endpoint should be tried, + * and false if it should be skipped. + * + * @param ec Set to indicate what error occurred, if any. If the sequence is + * empty, set to asio::error::not_found. Otherwise, contains the error + * from the last connection attempt. + * + * @returns On success, an iterator denoting the successfully connected + * endpoint. Otherwise, the end iterator. + * + * @note This overload assumes that a default constructed object of type @c + * Iterator represents the end of the sequence. This is a valid assumption for + * iterator types such as @c asio::ip::tcp::resolver::iterator. + */ +template +Iterator connect(basic_socket& s, Iterator begin, + ConnectCondition connect_condition, asio::error_code& ec, + typename enable_if::value>::type* = 0); +#endif // !defined(ASIO_NO_DEPRECATED) + +/// Establishes a socket connection by trying each endpoint in a sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c connect member + * function, once for each endpoint in the sequence, until a connection is + * successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param begin An iterator pointing to the start of a sequence of endpoints. + * + * @param end An iterator pointing to the end of a sequence of endpoints. + * + * @param connect_condition A function object that is called prior to each + * connection attempt. The signature of the function object must be: + * @code bool connect_condition( + * const asio::error_code& ec, + * const typename Protocol::endpoint& next); @endcode + * The @c ec parameter contains the result from the most recent connect + * operation. Before the first connection attempt, @c ec is always set to + * indicate success. The @c next parameter is the next endpoint to be tried. + * The function object should return true if the next endpoint should be tried, + * and false if it should be skipped. + * + * @returns An iterator denoting the successfully connected endpoint. + * + * @throws asio::system_error Thrown on failure. If the sequence is + * empty, the associated @c error_code is asio::error::not_found. + * Otherwise, contains the error from the last connection attempt. + * + * @par Example + * The following connect condition function object can be used to output + * information about the individual connection attempts: + * @code struct my_connect_condition + * { + * bool operator()( + * const asio::error_code& ec, + * const::tcp::endpoint& next) + * { + * if (ec) std::cout << "Error: " << ec.message() << std::endl; + * std::cout << "Trying: " << next << std::endl; + * return true; + * } + * }; @endcode + * It would be used with the asio::connect function as follows: + * @code tcp::resolver r(my_context); + * tcp::resolver::query q("host", "service"); + * tcp::resolver::results_type e = r.resolve(q); + * tcp::socket s(my_context); + * tcp::resolver::results_type::iterator i = asio::connect( + * s, e.begin(), e.end(), my_connect_condition()); + * std::cout << "Connected to: " << i->endpoint() << std::endl; @endcode + */ +template +Iterator connect(basic_socket& s, Iterator begin, + Iterator end, ConnectCondition connect_condition); + +/// Establishes a socket connection by trying each endpoint in a sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c connect member + * function, once for each endpoint in the sequence, until a connection is + * successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param begin An iterator pointing to the start of a sequence of endpoints. + * + * @param end An iterator pointing to the end of a sequence of endpoints. + * + * @param connect_condition A function object that is called prior to each + * connection attempt. The signature of the function object must be: + * @code bool connect_condition( + * const asio::error_code& ec, + * const typename Protocol::endpoint& next); @endcode + * The @c ec parameter contains the result from the most recent connect + * operation. Before the first connection attempt, @c ec is always set to + * indicate success. The @c next parameter is the next endpoint to be tried. + * The function object should return true if the next endpoint should be tried, + * and false if it should be skipped. + * + * @param ec Set to indicate what error occurred, if any. If the sequence is + * empty, set to asio::error::not_found. Otherwise, contains the error + * from the last connection attempt. + * + * @returns On success, an iterator denoting the successfully connected + * endpoint. Otherwise, the end iterator. + * + * @par Example + * The following connect condition function object can be used to output + * information about the individual connection attempts: + * @code struct my_connect_condition + * { + * bool operator()( + * const asio::error_code& ec, + * const::tcp::endpoint& next) + * { + * if (ec) std::cout << "Error: " << ec.message() << std::endl; + * std::cout << "Trying: " << next << std::endl; + * return true; + * } + * }; @endcode + * It would be used with the asio::connect function as follows: + * @code tcp::resolver r(my_context); + * tcp::resolver::query q("host", "service"); + * tcp::resolver::results_type e = r.resolve(q); + * tcp::socket s(my_context); + * asio::error_code ec; + * tcp::resolver::results_type::iterator i = asio::connect( + * s, e.begin(), e.end(), my_connect_condition()); + * if (ec) + * { + * // An error occurred. + * } + * else + * { + * std::cout << "Connected to: " << i->endpoint() << std::endl; + * } @endcode + */ +template +Iterator connect(basic_socket& s, + Iterator begin, Iterator end, ConnectCondition connect_condition, + asio::error_code& ec); + +/*@}*/ + +/** + * @defgroup async_connect asio::async_connect + * + * @brief The @c async_connect function is a composed asynchronous operation + * that establishes a socket connection by trying each endpoint in a sequence. + */ +/*@{*/ + +/// Asynchronously establishes a socket connection by trying each endpoint in a +/// sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c async_connect + * member function, once for each endpoint in the sequence, until a connection + * is successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param endpoints A sequence of endpoints. + * + * @param handler The handler to be called when the connect operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * // Result of operation. if the sequence is empty, set to + * // asio::error::not_found. Otherwise, contains the + * // error from the last connection attempt. + * const asio::error_code& error, + * + * // On success, the successfully connected endpoint. + * // Otherwise, a default-constructed endpoint. + * const typename Protocol::endpoint& endpoint + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * @code tcp::resolver r(my_context); + * tcp::resolver::query q("host", "service"); + * tcp::socket s(my_context); + * + * // ... + * + * r.async_resolve(q, resolve_handler); + * + * // ... + * + * void resolve_handler( + * const asio::error_code& ec, + * tcp::resolver::results_type results) + * { + * if (!ec) + * { + * asio::async_connect(s, results, connect_handler); + * } + * } + * + * // ... + * + * void connect_handler( + * const asio::error_code& ec, + * const tcp::endpoint& endpoint) + * { + * // ... + * } @endcode + */ +template +ASIO_INITFN_AUTO_RESULT_TYPE(RangeConnectHandler, + void (asio::error_code, typename Protocol::endpoint)) +async_connect(basic_socket& s, + const EndpointSequence& endpoints, + ASIO_MOVE_ARG(RangeConnectHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(Executor), + typename enable_if::value>::type* = 0); + +#if !defined(ASIO_NO_DEPRECATED) +/// (Deprecated: Use range overload.) Asynchronously establishes a socket +/// connection by trying each endpoint in a sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c async_connect + * member function, once for each endpoint in the sequence, until a connection + * is successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param begin An iterator pointing to the start of a sequence of endpoints. + * + * @param handler The handler to be called when the connect operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * // Result of operation. if the sequence is empty, set to + * // asio::error::not_found. Otherwise, contains the + * // error from the last connection attempt. + * const asio::error_code& error, + * + * // On success, an iterator denoting the successfully + * // connected endpoint. Otherwise, the end iterator. + * Iterator iterator + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note This overload assumes that a default constructed object of type @c + * Iterator represents the end of the sequence. This is a valid assumption for + * iterator types such as @c asio::ip::tcp::resolver::iterator. + */ +template +ASIO_INITFN_AUTO_RESULT_TYPE(IteratorConnectHandler, + void (asio::error_code, Iterator)) +async_connect(basic_socket& s, Iterator begin, + ASIO_MOVE_ARG(IteratorConnectHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(Executor), + typename enable_if::value>::type* = 0); +#endif // !defined(ASIO_NO_DEPRECATED) + +/// Asynchronously establishes a socket connection by trying each endpoint in a +/// sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c async_connect + * member function, once for each endpoint in the sequence, until a connection + * is successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param begin An iterator pointing to the start of a sequence of endpoints. + * + * @param end An iterator pointing to the end of a sequence of endpoints. + * + * @param handler The handler to be called when the connect operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * // Result of operation. if the sequence is empty, set to + * // asio::error::not_found. Otherwise, contains the + * // error from the last connection attempt. + * const asio::error_code& error, + * + * // On success, an iterator denoting the successfully + * // connected endpoint. Otherwise, the end iterator. + * Iterator iterator + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * @code std::vector endpoints = ...; + * tcp::socket s(my_context); + * asio::async_connect(s, + * endpoints.begin(), endpoints.end(), + * connect_handler); + * + * // ... + * + * void connect_handler( + * const asio::error_code& ec, + * std::vector::iterator i) + * { + * // ... + * } @endcode + */ +template +ASIO_INITFN_AUTO_RESULT_TYPE(IteratorConnectHandler, + void (asio::error_code, Iterator)) +async_connect(basic_socket& s, Iterator begin, Iterator end, + ASIO_MOVE_ARG(IteratorConnectHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(Executor)); + +/// Asynchronously establishes a socket connection by trying each endpoint in a +/// sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c async_connect + * member function, once for each endpoint in the sequence, until a connection + * is successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param endpoints A sequence of endpoints. + * + * @param connect_condition A function object that is called prior to each + * connection attempt. The signature of the function object must be: + * @code bool connect_condition( + * const asio::error_code& ec, + * const typename Protocol::endpoint& next); @endcode + * The @c ec parameter contains the result from the most recent connect + * operation. Before the first connection attempt, @c ec is always set to + * indicate success. The @c next parameter is the next endpoint to be tried. + * The function object should return true if the next endpoint should be tried, + * and false if it should be skipped. + * + * @param handler The handler to be called when the connect operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * // Result of operation. if the sequence is empty, set to + * // asio::error::not_found. Otherwise, contains the + * // error from the last connection attempt. + * const asio::error_code& error, + * + * // On success, an iterator denoting the successfully + * // connected endpoint. Otherwise, the end iterator. + * Iterator iterator + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * The following connect condition function object can be used to output + * information about the individual connection attempts: + * @code struct my_connect_condition + * { + * bool operator()( + * const asio::error_code& ec, + * const::tcp::endpoint& next) + * { + * if (ec) std::cout << "Error: " << ec.message() << std::endl; + * std::cout << "Trying: " << next << std::endl; + * return true; + * } + * }; @endcode + * It would be used with the asio::connect function as follows: + * @code tcp::resolver r(my_context); + * tcp::resolver::query q("host", "service"); + * tcp::socket s(my_context); + * + * // ... + * + * r.async_resolve(q, resolve_handler); + * + * // ... + * + * void resolve_handler( + * const asio::error_code& ec, + * tcp::resolver::results_type results) + * { + * if (!ec) + * { + * asio::async_connect(s, results, + * my_connect_condition(), + * connect_handler); + * } + * } + * + * // ... + * + * void connect_handler( + * const asio::error_code& ec, + * const tcp::endpoint& endpoint) + * { + * if (ec) + * { + * // An error occurred. + * } + * else + * { + * std::cout << "Connected to: " << endpoint << std::endl; + * } + * } @endcode + */ +template +ASIO_INITFN_AUTO_RESULT_TYPE(RangeConnectHandler, + void (asio::error_code, typename Protocol::endpoint)) +async_connect(basic_socket& s, + const EndpointSequence& endpoints, ConnectCondition connect_condition, + ASIO_MOVE_ARG(RangeConnectHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(Executor), + typename enable_if::value>::type* = 0); + +#if !defined(ASIO_NO_DEPRECATED) +/// (Deprecated: Use range overload.) Asynchronously establishes a socket +/// connection by trying each endpoint in a sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c async_connect + * member function, once for each endpoint in the sequence, until a connection + * is successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param begin An iterator pointing to the start of a sequence of endpoints. + * + * @param connect_condition A function object that is called prior to each + * connection attempt. The signature of the function object must be: + * @code bool connect_condition( + * const asio::error_code& ec, + * const typename Protocol::endpoint& next); @endcode + * The @c ec parameter contains the result from the most recent connect + * operation. Before the first connection attempt, @c ec is always set to + * indicate success. The @c next parameter is the next endpoint to be tried. + * The function object should return true if the next endpoint should be tried, + * and false if it should be skipped. + * + * @param handler The handler to be called when the connect operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * // Result of operation. if the sequence is empty, set to + * // asio::error::not_found. Otherwise, contains the + * // error from the last connection attempt. + * const asio::error_code& error, + * + * // On success, an iterator denoting the successfully + * // connected endpoint. Otherwise, the end iterator. + * Iterator iterator + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @note This overload assumes that a default constructed object of type @c + * Iterator represents the end of the sequence. This is a valid assumption for + * iterator types such as @c asio::ip::tcp::resolver::iterator. + */ +template +ASIO_INITFN_AUTO_RESULT_TYPE(IteratorConnectHandler, + void (asio::error_code, Iterator)) +async_connect(basic_socket& s, Iterator begin, + ConnectCondition connect_condition, + ASIO_MOVE_ARG(IteratorConnectHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(Executor), + typename enable_if::value>::type* = 0); +#endif // !defined(ASIO_NO_DEPRECATED) + +/// Asynchronously establishes a socket connection by trying each endpoint in a +/// sequence. +/** + * This function attempts to connect a socket to one of a sequence of + * endpoints. It does this by repeated calls to the socket's @c async_connect + * member function, once for each endpoint in the sequence, until a connection + * is successfully established. + * + * @param s The socket to be connected. If the socket is already open, it will + * be closed. + * + * @param begin An iterator pointing to the start of a sequence of endpoints. + * + * @param end An iterator pointing to the end of a sequence of endpoints. + * + * @param connect_condition A function object that is called prior to each + * connection attempt. The signature of the function object must be: + * @code bool connect_condition( + * const asio::error_code& ec, + * const typename Protocol::endpoint& next); @endcode + * The @c ec parameter contains the result from the most recent connect + * operation. Before the first connection attempt, @c ec is always set to + * indicate success. The @c next parameter is the next endpoint to be tried. + * The function object should return true if the next endpoint should be tried, + * and false if it should be skipped. + * + * @param handler The handler to be called when the connect operation + * completes. Copies will be made of the handler as required. The function + * signature of the handler must be: + * @code void handler( + * // Result of operation. if the sequence is empty, set to + * // asio::error::not_found. Otherwise, contains the + * // error from the last connection attempt. + * const asio::error_code& error, + * + * // On success, an iterator denoting the successfully + * // connected endpoint. Otherwise, the end iterator. + * Iterator iterator + * ); @endcode + * Regardless of whether the asynchronous operation completes immediately or + * not, the handler will not be invoked from within this function. On + * immediate completion, invocation of the handler will be performed in a + * manner equivalent to using asio::post(). + * + * @par Example + * The following connect condition function object can be used to output + * information about the individual connection attempts: + * @code struct my_connect_condition + * { + * bool operator()( + * const asio::error_code& ec, + * const::tcp::endpoint& next) + * { + * if (ec) std::cout << "Error: " << ec.message() << std::endl; + * std::cout << "Trying: " << next << std::endl; + * return true; + * } + * }; @endcode + * It would be used with the asio::connect function as follows: + * @code tcp::resolver r(my_context); + * tcp::resolver::query q("host", "service"); + * tcp::socket s(my_context); + * + * // ... + * + * r.async_resolve(q, resolve_handler); + * + * // ... + * + * void resolve_handler( + * const asio::error_code& ec, + * tcp::resolver::iterator i) + * { + * if (!ec) + * { + * tcp::resolver::iterator end; + * asio::async_connect(s, i, end, + * my_connect_condition(), + * connect_handler); + * } + * } + * + * // ... + * + * void connect_handler( + * const asio::error_code& ec, + * tcp::resolver::iterator i) + * { + * if (ec) + * { + * // An error occurred. + * } + * else + * { + * std::cout << "Connected to: " << i->endpoint() << std::endl; + * } + * } @endcode + */ +template +ASIO_INITFN_AUTO_RESULT_TYPE(IteratorConnectHandler, + void (asio::error_code, Iterator)) +async_connect(basic_socket& s, Iterator begin, + Iterator end, ConnectCondition connect_condition, + ASIO_MOVE_ARG(IteratorConnectHandler) handler + ASIO_DEFAULT_COMPLETION_TOKEN(Executor)); + +/*@}*/ + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/impl/connect.hpp" + +#endif diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/coroutine.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/coroutine.hpp new file mode 100644 index 000000000..b970bbad3 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/coroutine.hpp @@ -0,0 +1,328 @@ +// +// coroutine.hpp +// ~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_COROUTINE_HPP +#define ASIO_COROUTINE_HPP + +namespace asio { +namespace detail { + +class coroutine_ref; + +} // namespace detail + +/// Provides support for implementing stackless coroutines. +/** + * The @c coroutine class may be used to implement stackless coroutines. The + * class itself is used to store the current state of the coroutine. + * + * Coroutines are copy-constructible and assignable, and the space overhead is + * a single int. They can be used as a base class: + * + * @code class session : coroutine + * { + * ... + * }; @endcode + * + * or as a data member: + * + * @code class session + * { + * ... + * coroutine coro_; + * }; @endcode + * + * or even bound in as a function argument using lambdas or @c bind(). The + * important thing is that as the application maintains a copy of the object + * for as long as the coroutine must be kept alive. + * + * @par Pseudo-keywords + * + * A coroutine is used in conjunction with certain "pseudo-keywords", which + * are implemented as macros. These macros are defined by a header file: + * + * @code #include @endcode + * + * and may conversely be undefined as follows: + * + * @code #include @endcode + * + * reenter + * + * The @c reenter macro is used to define the body of a coroutine. It takes a + * single argument: a pointer or reference to a coroutine object. For example, + * if the base class is a coroutine object you may write: + * + * @code reenter (this) + * { + * ... coroutine body ... + * } @endcode + * + * and if a data member or other variable you can write: + * + * @code reenter (coro_) + * { + * ... coroutine body ... + * } @endcode + * + * When @c reenter is executed at runtime, control jumps to the location of the + * last @c yield or @c fork. + * + * The coroutine body may also be a single statement, such as: + * + * @code reenter (this) for (;;) + * { + * ... + * } @endcode + * + * @b Limitation: The @c reenter macro is implemented using a switch. This + * means that you must take care when using local variables within the + * coroutine body. The local variable is not allowed in a position where + * reentering the coroutine could bypass the variable definition. + * + * yield statement + * + * This form of the @c yield keyword is often used with asynchronous operations: + * + * @code yield socket_->async_read_some(buffer(*buffer_), *this); @endcode + * + * This divides into four logical steps: + * + * @li @c yield saves the current state of the coroutine. + * @li The statement initiates the asynchronous operation. + * @li The resume point is defined immediately following the statement. + * @li Control is transferred to the end of the coroutine body. + * + * When the asynchronous operation completes, the function object is invoked + * and @c reenter causes control to transfer to the resume point. It is + * important to remember to carry the coroutine state forward with the + * asynchronous operation. In the above snippet, the current class is a + * function object object with a coroutine object as base class or data member. + * + * The statement may also be a compound statement, and this permits us to + * define local variables with limited scope: + * + * @code yield + * { + * mutable_buffers_1 b = buffer(*buffer_); + * socket_->async_read_some(b, *this); + * } @endcode + * + * yield return expression ; + * + * This form of @c yield is often used in generators or coroutine-based parsers. + * For example, the function object: + * + * @code struct interleave : coroutine + * { + * istream& is1; + * istream& is2; + * char operator()(char c) + * { + * reenter (this) for (;;) + * { + * yield return is1.get(); + * yield return is2.get(); + * } + * } + * }; @endcode + * + * defines a trivial coroutine that interleaves the characters from two input + * streams. + * + * This type of @c yield divides into three logical steps: + * + * @li @c yield saves the current state of the coroutine. + * @li The resume point is defined immediately following the semicolon. + * @li The value of the expression is returned from the function. + * + * yield ; + * + * This form of @c yield is equivalent to the following steps: + * + * @li @c yield saves the current state of the coroutine. + * @li The resume point is defined immediately following the semicolon. + * @li Control is transferred to the end of the coroutine body. + * + * This form might be applied when coroutines are used for cooperative + * threading and scheduling is explicitly managed. For example: + * + * @code struct task : coroutine + * { + * ... + * void operator()() + * { + * reenter (this) + * { + * while (... not finished ...) + * { + * ... do something ... + * yield; + * ... do some more ... + * yield; + * } + * } + * } + * ... + * }; + * ... + * task t1, t2; + * for (;;) + * { + * t1(); + * t2(); + * } @endcode + * + * yield break ; + * + * The final form of @c yield is used to explicitly terminate the coroutine. + * This form is comprised of two steps: + * + * @li @c yield sets the coroutine state to indicate termination. + * @li Control is transferred to the end of the coroutine body. + * + * Once terminated, calls to is_complete() return true and the coroutine cannot + * be reentered. + * + * Note that a coroutine may also be implicitly terminated if the coroutine + * body is exited without a yield, e.g. by return, throw or by running to the + * end of the body. + * + * fork statement + * + * The @c fork pseudo-keyword is used when "forking" a coroutine, i.e. splitting + * it into two (or more) copies. One use of @c fork is in a server, where a new + * coroutine is created to handle each client connection: + * + * @code reenter (this) + * { + * do + * { + * socket_.reset(new tcp::socket(my_context_)); + * yield acceptor->async_accept(*socket_, *this); + * fork server(*this)(); + * } while (is_parent()); + * ... client-specific handling follows ... + * } @endcode + * + * The logical steps involved in a @c fork are: + * + * @li @c fork saves the current state of the coroutine. + * @li The statement creates a copy of the coroutine and either executes it + * immediately or schedules it for later execution. + * @li The resume point is defined immediately following the semicolon. + * @li For the "parent", control immediately continues from the next line. + * + * The functions is_parent() and is_child() can be used to differentiate + * between parent and child. You would use these functions to alter subsequent + * control flow. + * + * Note that @c fork doesn't do the actual forking by itself. It is the + * application's responsibility to create a clone of the coroutine and call it. + * The clone can be called immediately, as above, or scheduled for delayed + * execution using something like asio::post(). + * + * @par Alternate macro names + * + * If preferred, an application can use macro names that follow a more typical + * naming convention, rather than the pseudo-keywords. These are: + * + * @li @c ASIO_CORO_REENTER instead of @c reenter + * @li @c ASIO_CORO_YIELD instead of @c yield + * @li @c ASIO_CORO_FORK instead of @c fork + */ +class coroutine +{ +public: + /// Constructs a coroutine in its initial state. + coroutine() : value_(0) {} + + /// Returns true if the coroutine is the child of a fork. + bool is_child() const { return value_ < 0; } + + /// Returns true if the coroutine is the parent of a fork. + bool is_parent() const { return !is_child(); } + + /// Returns true if the coroutine has reached its terminal state. + bool is_complete() const { return value_ == -1; } + +private: + friend class detail::coroutine_ref; + int value_; +}; + + +namespace detail { + +class coroutine_ref +{ +public: + coroutine_ref(coroutine& c) : value_(c.value_), modified_(false) {} + coroutine_ref(coroutine* c) : value_(c->value_), modified_(false) {} + ~coroutine_ref() { if (!modified_) value_ = -1; } + operator int() const { return value_; } + int& operator=(int v) { modified_ = true; return value_ = v; } +private: + void operator=(const coroutine_ref&); + int& value_; + bool modified_; +}; + +} // namespace detail +} // namespace asio + +#define ASIO_CORO_REENTER(c) \ + switch (::asio::detail::coroutine_ref _coro_value = c) \ + case -1: if (_coro_value) \ + { \ + goto terminate_coroutine; \ + terminate_coroutine: \ + _coro_value = -1; \ + goto bail_out_of_coroutine; \ + bail_out_of_coroutine: \ + break; \ + } \ + else /* fall-through */ case 0: + +#define ASIO_CORO_YIELD_IMPL(n) \ + for (_coro_value = (n);;) \ + if (_coro_value == 0) \ + { \ + case (n): ; \ + break; \ + } \ + else \ + switch (_coro_value ? 0 : 1) \ + for (;;) \ + /* fall-through */ case -1: if (_coro_value) \ + goto terminate_coroutine; \ + else for (;;) \ + /* fall-through */ case 1: if (_coro_value) \ + goto bail_out_of_coroutine; \ + else /* fall-through */ case 0: + +#define ASIO_CORO_FORK_IMPL(n) \ + for (_coro_value = -(n);; _coro_value = (n)) \ + if (_coro_value == (n)) \ + { \ + case -(n): ; \ + break; \ + } \ + else + +#if defined(_MSC_VER) +# define ASIO_CORO_YIELD ASIO_CORO_YIELD_IMPL(__COUNTER__ + 1) +# define ASIO_CORO_FORK ASIO_CORO_FORK_IMPL(__COUNTER__ + 1) +#else // defined(_MSC_VER) +# define ASIO_CORO_YIELD ASIO_CORO_YIELD_IMPL(__LINE__) +# define ASIO_CORO_FORK ASIO_CORO_FORK_IMPL(__LINE__) +#endif // defined(_MSC_VER) + +#endif // ASIO_COROUTINE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/deadline_timer.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/deadline_timer.hpp new file mode 100644 index 000000000..228802787 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/deadline_timer.hpp @@ -0,0 +1,38 @@ +// +// deadline_timer.hpp +// ~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DEADLINE_TIMER_HPP +#define ASIO_DEADLINE_TIMER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_BOOST_DATE_TIME) \ + || defined(GENERATING_DOCUMENTATION) + +#include "asio/detail/socket_types.hpp" // Must come before posix_time. +#include "asio/basic_deadline_timer.hpp" + +#include + +namespace asio { + +/// Typedef for the typical usage of timer. Uses a UTC clock. +typedef basic_deadline_timer deadline_timer; + +} // namespace asio + +#endif // defined(ASIO_HAS_BOOST_DATE_TIME) + // || defined(GENERATING_DOCUMENTATION) + +#endif // ASIO_DEADLINE_TIMER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/defer.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/defer.hpp new file mode 100644 index 000000000..a034ff0b9 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/defer.hpp @@ -0,0 +1,130 @@ +// +// defer.hpp +// ~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DEFER_HPP +#define ASIO_DEFER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/async_result.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution_context.hpp" +#include "asio/execution/executor.hpp" +#include "asio/is_executor.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +/// Submits a completion token or function object for execution. +/** + * This function submits an object for execution using the object's associated + * executor. The function object is queued for execution, and is never called + * from the current thread prior to returning from defer(). + * + * The use of @c defer(), rather than @ref post(), indicates the caller's + * preference that the executor defer the queueing of the function object. This + * may allow the executor to optimise queueing for cases when the function + * object represents a continuation of the current call context. + * + * This function has the following effects: + * + * @li Constructs a function object handler of type @c Handler, initialized + * with handler(forward(token)). + * + * @li Constructs an object @c result of type async_result, + * initializing the object as result(handler). + * + * @li Obtains the handler's associated executor object @c ex by performing + * get_associated_executor(handler). + * + * @li Obtains the handler's associated allocator object @c alloc by performing + * get_associated_allocator(handler). + * + * @li Performs ex.defer(std::move(handler), alloc). + * + * @li Returns result.get(). + */ +template +ASIO_INITFN_AUTO_RESULT_TYPE(CompletionToken, void()) defer( + ASIO_MOVE_ARG(CompletionToken) token); + +/// Submits a completion token or function object for execution. +/** + * This function submits an object for execution using the specified executor. + * The function object is queued for execution, and is never called from the + * current thread prior to returning from defer(). + * + * The use of @c defer(), rather than @ref post(), indicates the caller's + * preference that the executor defer the queueing of the function object. This + * may allow the executor to optimise queueing for cases when the function + * object represents a continuation of the current call context. + * + * This function has the following effects: + * + * @li Constructs a function object handler of type @c Handler, initialized + * with handler(forward(token)). + * + * @li Constructs an object @c result of type async_result, + * initializing the object as result(handler). + * + * @li Obtains the handler's associated executor object @c ex1 by performing + * get_associated_executor(handler). + * + * @li Creates a work object @c w by performing make_work(ex1). + * + * @li Obtains the handler's associated allocator object @c alloc by performing + * get_associated_allocator(handler). + * + * @li Constructs a function object @c f with a function call operator that + * performs ex1.dispatch(std::move(handler), alloc) followed by + * w.reset(). + * + * @li Performs Executor(ex).defer(std::move(f), alloc). + * + * @li Returns result.get(). + */ +template +ASIO_INITFN_AUTO_RESULT_TYPE(CompletionToken, void()) defer( + const Executor& ex, + ASIO_MOVE_ARG(CompletionToken) token + ASIO_DEFAULT_COMPLETION_TOKEN(Executor), + typename enable_if< + execution::is_executor::value || is_executor::value + >::type* = 0); + +/// Submits a completion token or function object for execution. +/** + * @returns defer(ctx.get_executor(), forward(token)). + */ +template +ASIO_INITFN_AUTO_RESULT_TYPE(CompletionToken, void()) defer( + ExecutionContext& ctx, + ASIO_MOVE_ARG(CompletionToken) token + ASIO_DEFAULT_COMPLETION_TOKEN( + typename ExecutionContext::executor_type), + typename enable_if::value>::type* = 0); + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/impl/defer.hpp" + +#endif // ASIO_DEFER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detached.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detached.hpp new file mode 100644 index 000000000..d53879d95 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detached.hpp @@ -0,0 +1,112 @@ +// +// detached.hpp +// ~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETACHED_HPP +#define ASIO_DETACHED_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include "asio/detail/type_traits.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +/// Class used to specify that an asynchronous operation is detached. +/** + + * The detached_t class is used to indicate that an asynchronous operation is + * detached. That is, there is no completion handler waiting for the + * operation's result. A detached_t object may be passed as a handler to an + * asynchronous operation, typically using the special value + * @c asio::detached. For example: + + * @code my_socket.async_send(my_buffer, asio::detached); + * @endcode + */ +class detached_t +{ +public: + /// Constructor. + ASIO_CONSTEXPR detached_t() + { + } + + /// Adapts an executor to add the @c detached_t completion token as the + /// default. + template + struct executor_with_default : InnerExecutor + { + /// Specify @c detached_t as the default completion token type. + typedef detached_t default_completion_token_type; + + /// Construct the adapted executor from the inner executor type. + executor_with_default(const InnerExecutor& ex) ASIO_NOEXCEPT + : InnerExecutor(ex) + { + } + + /// Convert the specified executor to the inner executor type, then use + /// that to construct the adapted executor. + template + executor_with_default(const OtherExecutor& ex, + typename enable_if< + is_convertible::value + >::type* = 0) ASIO_NOEXCEPT + : InnerExecutor(ex) + { + } + }; + + /// Type alias to adapt an I/O object to use @c detached_t as its + /// default completion token type. +#if defined(ASIO_HAS_ALIAS_TEMPLATES) \ + || defined(GENERATING_DOCUMENTATION) + template + using as_default_on_t = typename T::template rebind_executor< + executor_with_default >::other; +#endif // defined(ASIO_HAS_ALIAS_TEMPLATES) + // || defined(GENERATING_DOCUMENTATION) + + /// Function helper to adapt an I/O object to use @c detached_t as its + /// default completion token type. + template + static typename decay::type::template rebind_executor< + executor_with_default::type::executor_type> + >::other + as_default_on(ASIO_MOVE_ARG(T) object) + { + return typename decay::type::template rebind_executor< + executor_with_default::type::executor_type> + >::other(ASIO_MOVE_CAST(T)(object)); + } +}; + +/// A special value, similar to std::nothrow. +/** + * See the documentation for asio::detached_t for a usage example. + */ +#if defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +constexpr detached_t detached; +#elif defined(ASIO_MSVC) +__declspec(selectany) detached_t detached; +#endif + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/impl/detached.hpp" + +#endif // ASIO_DETACHED_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/array.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/array.hpp new file mode 100644 index 000000000..dbc9c30b9 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/array.hpp @@ -0,0 +1,38 @@ +// +// detail/array.hpp +// ~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_ARRAY_HPP +#define ASIO_DETAIL_ARRAY_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_STD_ARRAY) +# include +#else // defined(ASIO_HAS_STD_ARRAY) +# include +#endif // defined(ASIO_HAS_STD_ARRAY) + +namespace asio { +namespace detail { + +#if defined(ASIO_HAS_STD_ARRAY) +using std::array; +#else // defined(ASIO_HAS_STD_ARRAY) +using boost::array; +#endif // defined(ASIO_HAS_STD_ARRAY) + +} // namespace detail +} // namespace asio + +#endif // ASIO_DETAIL_ARRAY_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/array_fwd.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/array_fwd.hpp new file mode 100644 index 000000000..b7f81ecb0 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/array_fwd.hpp @@ -0,0 +1,34 @@ +// +// detail/array_fwd.hpp +// ~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_ARRAY_FWD_HPP +#define ASIO_DETAIL_ARRAY_FWD_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +namespace boost { + +template +class array; + +} // namespace boost + +// Standard library components can't be forward declared, so we'll have to +// include the array header. Fortunately, it's fairly lightweight and doesn't +// add significantly to the compile time. +#if defined(ASIO_HAS_STD_ARRAY) +# include +#endif // defined(ASIO_HAS_STD_ARRAY) + +#endif // ASIO_DETAIL_ARRAY_FWD_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/assert.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/assert.hpp new file mode 100644 index 000000000..6f93e3810 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/assert.hpp @@ -0,0 +1,32 @@ +// +// detail/assert.hpp +// ~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_ASSERT_HPP +#define ASIO_DETAIL_ASSERT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_BOOST_ASSERT) +# include +#else // defined(ASIO_HAS_BOOST_ASSERT) +# include +#endif // defined(ASIO_HAS_BOOST_ASSERT) + +#if defined(ASIO_HAS_BOOST_ASSERT) +# define ASIO_ASSERT(expr) BOOST_ASSERT(expr) +#else // defined(ASIO_HAS_BOOST_ASSERT) +# define ASIO_ASSERT(expr) assert(expr) +#endif // defined(ASIO_HAS_BOOST_ASSERT) + +#endif // ASIO_DETAIL_ASSERT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/atomic_count.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/atomic_count.hpp new file mode 100644 index 000000000..b1d257d13 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/atomic_count.hpp @@ -0,0 +1,64 @@ +// +// detail/atomic_count.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_ATOMIC_COUNT_HPP +#define ASIO_DETAIL_ATOMIC_COUNT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_THREADS) +// Nothing to include. +#elif defined(ASIO_HAS_STD_ATOMIC) +# include +#else // defined(ASIO_HAS_STD_ATOMIC) +# include +#endif // defined(ASIO_HAS_STD_ATOMIC) + +namespace asio { +namespace detail { + +#if !defined(ASIO_HAS_THREADS) +typedef long atomic_count; +inline void increment(atomic_count& a, long b) { a += b; } +inline void ref_count_up(atomic_count& a) { ++a; } +inline bool ref_count_down(atomic_count& a) { return --a == 0; } +#elif defined(ASIO_HAS_STD_ATOMIC) +typedef std::atomic atomic_count; +inline void increment(atomic_count& a, long b) { a += b; } + +inline void ref_count_up(atomic_count& a) +{ + a.fetch_add(1, std::memory_order_relaxed); +} + +inline bool ref_count_down(atomic_count& a) +{ + if (a.fetch_sub(1, std::memory_order_release) == 1) + { + std::atomic_thread_fence(std::memory_order_acquire); + return true; + } + return false; +} +#else // defined(ASIO_HAS_STD_ATOMIC) +typedef boost::detail::atomic_count atomic_count; +inline void increment(atomic_count& a, long b) { while (b > 0) ++a, --b; } +inline void ref_count_up(atomic_count& a) { ++a; } +inline bool ref_count_down(atomic_count& a) { return --a == 0; } +#endif // defined(ASIO_HAS_STD_ATOMIC) + +} // namespace detail +} // namespace asio + +#endif // ASIO_DETAIL_ATOMIC_COUNT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/base_from_completion_cond.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/base_from_completion_cond.hpp new file mode 100644 index 000000000..37b8626a1 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/base_from_completion_cond.hpp @@ -0,0 +1,69 @@ +// +// detail/base_from_completion_cond.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_BASE_FROM_COMPLETION_COND_HPP +#define ASIO_DETAIL_BASE_FROM_COMPLETION_COND_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/completion_condition.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class base_from_completion_cond +{ +protected: + explicit base_from_completion_cond(CompletionCondition& completion_condition) + : completion_condition_( + ASIO_MOVE_CAST(CompletionCondition)(completion_condition)) + { + } + + std::size_t check_for_completion( + const asio::error_code& ec, + std::size_t total_transferred) + { + return detail::adapt_completion_condition_result( + completion_condition_(ec, total_transferred)); + } + +private: + CompletionCondition completion_condition_; +}; + +template <> +class base_from_completion_cond +{ +protected: + explicit base_from_completion_cond(transfer_all_t) + { + } + + static std::size_t check_for_completion( + const asio::error_code& ec, + std::size_t total_transferred) + { + return transfer_all_t()(ec, total_transferred); + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_BASE_FROM_COMPLETION_COND_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/bind_handler.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/bind_handler.hpp new file mode 100644 index 000000000..51817889a --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/bind_handler.hpp @@ -0,0 +1,934 @@ +// +// detail/bind_handler.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_BIND_HANDLER_HPP +#define ASIO_DETAIL_BIND_HANDLER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/associated_allocator.hpp" +#include "asio/associated_executor.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_cont_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/type_traits.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class binder1 +{ +public: + template + binder1(int, ASIO_MOVE_ARG(T) handler, const Arg1& arg1) + : handler_(ASIO_MOVE_CAST(T)(handler)), + arg1_(arg1) + { + } + + binder1(Handler& handler, const Arg1& arg1) + : handler_(ASIO_MOVE_CAST(Handler)(handler)), + arg1_(arg1) + { + } + +#if defined(ASIO_HAS_MOVE) + binder1(const binder1& other) + : handler_(other.handler_), + arg1_(other.arg1_) + { + } + + binder1(binder1&& other) + : handler_(ASIO_MOVE_CAST(Handler)(other.handler_)), + arg1_(ASIO_MOVE_CAST(Arg1)(other.arg1_)) + { + } +#endif // defined(ASIO_HAS_MOVE) + + void operator()() + { + handler_(static_cast(arg1_)); + } + + void operator()() const + { + handler_(arg1_); + } + +//private: + Handler handler_; + Arg1 arg1_; +}; + +template +inline asio_handler_allocate_is_deprecated +asio_handler_allocate(std::size_t size, + binder1* this_handler) +{ +#if defined(ASIO_NO_DEPRECATED) + asio_handler_alloc_helpers::allocate(size, this_handler->handler_); + return asio_handler_allocate_is_no_longer_used(); +#else // defined(ASIO_NO_DEPRECATED) + return asio_handler_alloc_helpers::allocate( + size, this_handler->handler_); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline asio_handler_deallocate_is_deprecated +asio_handler_deallocate(void* pointer, std::size_t size, + binder1* this_handler) +{ + asio_handler_alloc_helpers::deallocate( + pointer, size, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_deallocate_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline bool asio_handler_is_continuation( + binder1* this_handler) +{ + return asio_handler_cont_helpers::is_continuation( + this_handler->handler_); +} + +template +inline asio_handler_invoke_is_deprecated +asio_handler_invoke(Function& function, + binder1* this_handler) +{ + asio_handler_invoke_helpers::invoke( + function, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_invoke_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline asio_handler_invoke_is_deprecated +asio_handler_invoke(const Function& function, + binder1* this_handler) +{ + asio_handler_invoke_helpers::invoke( + function, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_invoke_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline binder1::type, Arg1> bind_handler( + ASIO_MOVE_ARG(Handler) handler, const Arg1& arg1) +{ + return binder1::type, Arg1>(0, + ASIO_MOVE_CAST(Handler)(handler), arg1); +} + +template +class binder2 +{ +public: + template + binder2(int, ASIO_MOVE_ARG(T) handler, + const Arg1& arg1, const Arg2& arg2) + : handler_(ASIO_MOVE_CAST(T)(handler)), + arg1_(arg1), + arg2_(arg2) + { + } + + binder2(Handler& handler, const Arg1& arg1, const Arg2& arg2) + : handler_(ASIO_MOVE_CAST(Handler)(handler)), + arg1_(arg1), + arg2_(arg2) + { + } + +#if defined(ASIO_HAS_MOVE) + binder2(const binder2& other) + : handler_(other.handler_), + arg1_(other.arg1_), + arg2_(other.arg2_) + { + } + + binder2(binder2&& other) + : handler_(ASIO_MOVE_CAST(Handler)(other.handler_)), + arg1_(ASIO_MOVE_CAST(Arg1)(other.arg1_)), + arg2_(ASIO_MOVE_CAST(Arg2)(other.arg2_)) + { + } +#endif // defined(ASIO_HAS_MOVE) + + void operator()() + { + handler_(static_cast(arg1_), + static_cast(arg2_)); + } + + void operator()() const + { + handler_(arg1_, arg2_); + } + +//private: + Handler handler_; + Arg1 arg1_; + Arg2 arg2_; +}; + +template +inline asio_handler_allocate_is_deprecated +asio_handler_allocate(std::size_t size, + binder2* this_handler) +{ +#if defined(ASIO_NO_DEPRECATED) + asio_handler_alloc_helpers::allocate(size, this_handler->handler_); + return asio_handler_allocate_is_no_longer_used(); +#else // defined(ASIO_NO_DEPRECATED) + return asio_handler_alloc_helpers::allocate( + size, this_handler->handler_); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline asio_handler_deallocate_is_deprecated +asio_handler_deallocate(void* pointer, std::size_t size, + binder2* this_handler) +{ + asio_handler_alloc_helpers::deallocate( + pointer, size, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_deallocate_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline bool asio_handler_is_continuation( + binder2* this_handler) +{ + return asio_handler_cont_helpers::is_continuation( + this_handler->handler_); +} + +template +inline asio_handler_invoke_is_deprecated +asio_handler_invoke(Function& function, + binder2* this_handler) +{ + asio_handler_invoke_helpers::invoke( + function, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_invoke_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline asio_handler_invoke_is_deprecated +asio_handler_invoke(const Function& function, + binder2* this_handler) +{ + asio_handler_invoke_helpers::invoke( + function, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_invoke_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline binder2::type, Arg1, Arg2> bind_handler( + ASIO_MOVE_ARG(Handler) handler, const Arg1& arg1, const Arg2& arg2) +{ + return binder2::type, Arg1, Arg2>(0, + ASIO_MOVE_CAST(Handler)(handler), arg1, arg2); +} + +template +class binder3 +{ +public: + template + binder3(int, ASIO_MOVE_ARG(T) handler, const Arg1& arg1, + const Arg2& arg2, const Arg3& arg3) + : handler_(ASIO_MOVE_CAST(T)(handler)), + arg1_(arg1), + arg2_(arg2), + arg3_(arg3) + { + } + + binder3(Handler& handler, const Arg1& arg1, + const Arg2& arg2, const Arg3& arg3) + : handler_(ASIO_MOVE_CAST(Handler)(handler)), + arg1_(arg1), + arg2_(arg2), + arg3_(arg3) + { + } + +#if defined(ASIO_HAS_MOVE) + binder3(const binder3& other) + : handler_(other.handler_), + arg1_(other.arg1_), + arg2_(other.arg2_), + arg3_(other.arg3_) + { + } + + binder3(binder3&& other) + : handler_(ASIO_MOVE_CAST(Handler)(other.handler_)), + arg1_(ASIO_MOVE_CAST(Arg1)(other.arg1_)), + arg2_(ASIO_MOVE_CAST(Arg2)(other.arg2_)), + arg3_(ASIO_MOVE_CAST(Arg3)(other.arg3_)) + { + } +#endif // defined(ASIO_HAS_MOVE) + + void operator()() + { + handler_(static_cast(arg1_), + static_cast(arg2_), static_cast(arg3_)); + } + + void operator()() const + { + handler_(arg1_, arg2_, arg3_); + } + +//private: + Handler handler_; + Arg1 arg1_; + Arg2 arg2_; + Arg3 arg3_; +}; + +template +inline asio_handler_allocate_is_deprecated +asio_handler_allocate(std::size_t size, + binder3* this_handler) +{ +#if defined(ASIO_NO_DEPRECATED) + asio_handler_alloc_helpers::allocate(size, this_handler->handler_); + return asio_handler_allocate_is_no_longer_used(); +#else // defined(ASIO_NO_DEPRECATED) + return asio_handler_alloc_helpers::allocate( + size, this_handler->handler_); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline asio_handler_deallocate_is_deprecated +asio_handler_deallocate(void* pointer, std::size_t size, + binder3* this_handler) +{ + asio_handler_alloc_helpers::deallocate( + pointer, size, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_deallocate_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline bool asio_handler_is_continuation( + binder3* this_handler) +{ + return asio_handler_cont_helpers::is_continuation( + this_handler->handler_); +} + +template +inline asio_handler_invoke_is_deprecated +asio_handler_invoke(Function& function, + binder3* this_handler) +{ + asio_handler_invoke_helpers::invoke( + function, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_invoke_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline asio_handler_invoke_is_deprecated +asio_handler_invoke(const Function& function, + binder3* this_handler) +{ + asio_handler_invoke_helpers::invoke( + function, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_invoke_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline binder3::type, Arg1, Arg2, Arg3> bind_handler( + ASIO_MOVE_ARG(Handler) handler, const Arg1& arg1, const Arg2& arg2, + const Arg3& arg3) +{ + return binder3::type, Arg1, Arg2, Arg3>(0, + ASIO_MOVE_CAST(Handler)(handler), arg1, arg2, arg3); +} + +template +class binder4 +{ +public: + template + binder4(int, ASIO_MOVE_ARG(T) handler, const Arg1& arg1, + const Arg2& arg2, const Arg3& arg3, const Arg4& arg4) + : handler_(ASIO_MOVE_CAST(T)(handler)), + arg1_(arg1), + arg2_(arg2), + arg3_(arg3), + arg4_(arg4) + { + } + + binder4(Handler& handler, const Arg1& arg1, + const Arg2& arg2, const Arg3& arg3, const Arg4& arg4) + : handler_(ASIO_MOVE_CAST(Handler)(handler)), + arg1_(arg1), + arg2_(arg2), + arg3_(arg3), + arg4_(arg4) + { + } + +#if defined(ASIO_HAS_MOVE) + binder4(const binder4& other) + : handler_(other.handler_), + arg1_(other.arg1_), + arg2_(other.arg2_), + arg3_(other.arg3_), + arg4_(other.arg4_) + { + } + + binder4(binder4&& other) + : handler_(ASIO_MOVE_CAST(Handler)(other.handler_)), + arg1_(ASIO_MOVE_CAST(Arg1)(other.arg1_)), + arg2_(ASIO_MOVE_CAST(Arg2)(other.arg2_)), + arg3_(ASIO_MOVE_CAST(Arg3)(other.arg3_)), + arg4_(ASIO_MOVE_CAST(Arg4)(other.arg4_)) + { + } +#endif // defined(ASIO_HAS_MOVE) + + void operator()() + { + handler_(static_cast(arg1_), + static_cast(arg2_), static_cast(arg3_), + static_cast(arg4_)); + } + + void operator()() const + { + handler_(arg1_, arg2_, arg3_, arg4_); + } + +//private: + Handler handler_; + Arg1 arg1_; + Arg2 arg2_; + Arg3 arg3_; + Arg4 arg4_; +}; + +template +inline asio_handler_allocate_is_deprecated +asio_handler_allocate(std::size_t size, + binder4* this_handler) +{ +#if defined(ASIO_NO_DEPRECATED) + asio_handler_alloc_helpers::allocate(size, this_handler->handler_); + return asio_handler_allocate_is_no_longer_used(); +#else // defined(ASIO_NO_DEPRECATED) + return asio_handler_alloc_helpers::allocate( + size, this_handler->handler_); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline asio_handler_deallocate_is_deprecated +asio_handler_deallocate(void* pointer, std::size_t size, + binder4* this_handler) +{ + asio_handler_alloc_helpers::deallocate( + pointer, size, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_deallocate_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline bool asio_handler_is_continuation( + binder4* this_handler) +{ + return asio_handler_cont_helpers::is_continuation( + this_handler->handler_); +} + +template +inline asio_handler_invoke_is_deprecated +asio_handler_invoke(Function& function, + binder4* this_handler) +{ + asio_handler_invoke_helpers::invoke( + function, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_invoke_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline asio_handler_invoke_is_deprecated +asio_handler_invoke(const Function& function, + binder4* this_handler) +{ + asio_handler_invoke_helpers::invoke( + function, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_invoke_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline binder4::type, Arg1, Arg2, Arg3, Arg4> +bind_handler(ASIO_MOVE_ARG(Handler) handler, const Arg1& arg1, + const Arg2& arg2, const Arg3& arg3, const Arg4& arg4) +{ + return binder4::type, Arg1, Arg2, Arg3, Arg4>(0, + ASIO_MOVE_CAST(Handler)(handler), arg1, arg2, arg3, arg4); +} + +template +class binder5 +{ +public: + template + binder5(int, ASIO_MOVE_ARG(T) handler, const Arg1& arg1, + const Arg2& arg2, const Arg3& arg3, const Arg4& arg4, const Arg5& arg5) + : handler_(ASIO_MOVE_CAST(T)(handler)), + arg1_(arg1), + arg2_(arg2), + arg3_(arg3), + arg4_(arg4), + arg5_(arg5) + { + } + + binder5(Handler& handler, const Arg1& arg1, const Arg2& arg2, + const Arg3& arg3, const Arg4& arg4, const Arg5& arg5) + : handler_(ASIO_MOVE_CAST(Handler)(handler)), + arg1_(arg1), + arg2_(arg2), + arg3_(arg3), + arg4_(arg4), + arg5_(arg5) + { + } + +#if defined(ASIO_HAS_MOVE) + binder5(const binder5& other) + : handler_(other.handler_), + arg1_(other.arg1_), + arg2_(other.arg2_), + arg3_(other.arg3_), + arg4_(other.arg4_), + arg5_(other.arg5_) + { + } + + binder5(binder5&& other) + : handler_(ASIO_MOVE_CAST(Handler)(other.handler_)), + arg1_(ASIO_MOVE_CAST(Arg1)(other.arg1_)), + arg2_(ASIO_MOVE_CAST(Arg2)(other.arg2_)), + arg3_(ASIO_MOVE_CAST(Arg3)(other.arg3_)), + arg4_(ASIO_MOVE_CAST(Arg4)(other.arg4_)), + arg5_(ASIO_MOVE_CAST(Arg5)(other.arg5_)) + { + } +#endif // defined(ASIO_HAS_MOVE) + + void operator()() + { + handler_(static_cast(arg1_), + static_cast(arg2_), static_cast(arg3_), + static_cast(arg4_), static_cast(arg5_)); + } + + void operator()() const + { + handler_(arg1_, arg2_, arg3_, arg4_, arg5_); + } + +//private: + Handler handler_; + Arg1 arg1_; + Arg2 arg2_; + Arg3 arg3_; + Arg4 arg4_; + Arg5 arg5_; +}; + +template +inline asio_handler_allocate_is_deprecated +asio_handler_allocate(std::size_t size, + binder5* this_handler) +{ +#if defined(ASIO_NO_DEPRECATED) + asio_handler_alloc_helpers::allocate(size, this_handler->handler_); + return asio_handler_allocate_is_no_longer_used(); +#else // defined(ASIO_NO_DEPRECATED) + return asio_handler_alloc_helpers::allocate( + size, this_handler->handler_); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline asio_handler_deallocate_is_deprecated +asio_handler_deallocate(void* pointer, std::size_t size, + binder5* this_handler) +{ + asio_handler_alloc_helpers::deallocate( + pointer, size, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_deallocate_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline bool asio_handler_is_continuation( + binder5* this_handler) +{ + return asio_handler_cont_helpers::is_continuation( + this_handler->handler_); +} + +template +inline asio_handler_invoke_is_deprecated +asio_handler_invoke(Function& function, + binder5* this_handler) +{ + asio_handler_invoke_helpers::invoke( + function, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_invoke_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline asio_handler_invoke_is_deprecated +asio_handler_invoke(const Function& function, + binder5* this_handler) +{ + asio_handler_invoke_helpers::invoke( + function, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_invoke_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline binder5::type, Arg1, Arg2, Arg3, Arg4, Arg5> +bind_handler(ASIO_MOVE_ARG(Handler) handler, const Arg1& arg1, + const Arg2& arg2, const Arg3& arg3, const Arg4& arg4, const Arg5& arg5) +{ + return binder5::type, Arg1, Arg2, Arg3, Arg4, Arg5>(0, + ASIO_MOVE_CAST(Handler)(handler), arg1, arg2, arg3, arg4, arg5); +} + +#if defined(ASIO_HAS_MOVE) + +template +class move_binder1 +{ +public: + move_binder1(int, ASIO_MOVE_ARG(Handler) handler, + ASIO_MOVE_ARG(Arg1) arg1) + : handler_(ASIO_MOVE_CAST(Handler)(handler)), + arg1_(ASIO_MOVE_CAST(Arg1)(arg1)) + { + } + + move_binder1(move_binder1&& other) + : handler_(ASIO_MOVE_CAST(Handler)(other.handler_)), + arg1_(ASIO_MOVE_CAST(Arg1)(other.arg1_)) + { + } + + void operator()() + { + handler_(ASIO_MOVE_CAST(Arg1)(arg1_)); + } + +//private: + Handler handler_; + Arg1 arg1_; +}; + +template +inline asio_handler_allocate_is_deprecated +asio_handler_allocate(std::size_t size, + move_binder1* this_handler) +{ +#if defined(ASIO_NO_DEPRECATED) + asio_handler_alloc_helpers::allocate(size, this_handler->handler_); + return asio_handler_allocate_is_no_longer_used(); +#else // defined(ASIO_NO_DEPRECATED) + return asio_handler_alloc_helpers::allocate( + size, this_handler->handler_); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline asio_handler_deallocate_is_deprecated +asio_handler_deallocate(void* pointer, std::size_t size, + move_binder1* this_handler) +{ + asio_handler_alloc_helpers::deallocate( + pointer, size, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_deallocate_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline bool asio_handler_is_continuation( + move_binder1* this_handler) +{ + return asio_handler_cont_helpers::is_continuation( + this_handler->handler_); +} + +template +inline asio_handler_invoke_is_deprecated +asio_handler_invoke(ASIO_MOVE_ARG(Function) function, + move_binder1* this_handler) +{ + asio_handler_invoke_helpers::invoke( + ASIO_MOVE_CAST(Function)(function), this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_invoke_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +class move_binder2 +{ +public: + move_binder2(int, ASIO_MOVE_ARG(Handler) handler, + const Arg1& arg1, ASIO_MOVE_ARG(Arg2) arg2) + : handler_(ASIO_MOVE_CAST(Handler)(handler)), + arg1_(arg1), + arg2_(ASIO_MOVE_CAST(Arg2)(arg2)) + { + } + + move_binder2(move_binder2&& other) + : handler_(ASIO_MOVE_CAST(Handler)(other.handler_)), + arg1_(ASIO_MOVE_CAST(Arg1)(other.arg1_)), + arg2_(ASIO_MOVE_CAST(Arg2)(other.arg2_)) + { + } + + void operator()() + { + handler_(static_cast(arg1_), + ASIO_MOVE_CAST(Arg2)(arg2_)); + } + +//private: + Handler handler_; + Arg1 arg1_; + Arg2 arg2_; +}; + +template +inline asio_handler_allocate_is_deprecated +asio_handler_allocate(std::size_t size, + move_binder2* this_handler) +{ +#if defined(ASIO_NO_DEPRECATED) + asio_handler_alloc_helpers::allocate(size, this_handler->handler_); + return asio_handler_allocate_is_no_longer_used(); +#else // defined(ASIO_NO_DEPRECATED) + return asio_handler_alloc_helpers::allocate( + size, this_handler->handler_); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline asio_handler_deallocate_is_deprecated +asio_handler_deallocate(void* pointer, std::size_t size, + move_binder2* this_handler) +{ + asio_handler_alloc_helpers::deallocate( + pointer, size, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_deallocate_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline bool asio_handler_is_continuation( + move_binder2* this_handler) +{ + return asio_handler_cont_helpers::is_continuation( + this_handler->handler_); +} + +template +inline asio_handler_invoke_is_deprecated +asio_handler_invoke(ASIO_MOVE_ARG(Function) function, + move_binder2* this_handler) +{ + asio_handler_invoke_helpers::invoke( + ASIO_MOVE_CAST(Function)(function), this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_invoke_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +#endif // defined(ASIO_HAS_MOVE) + +} // namespace detail + +template +struct associated_allocator, Allocator> +{ + typedef typename associated_allocator::type type; + + static type get(const detail::binder1& h, + const Allocator& a = Allocator()) ASIO_NOEXCEPT + { + return associated_allocator::get(h.handler_, a); + } +}; + +template +struct associated_allocator, Allocator> +{ + typedef typename associated_allocator::type type; + + static type get(const detail::binder2& h, + const Allocator& a = Allocator()) ASIO_NOEXCEPT + { + return associated_allocator::get(h.handler_, a); + } +}; + +template +struct associated_executor, Executor> +{ + typedef typename associated_executor::type type; + + static type get(const detail::binder1& h, + const Executor& ex = Executor()) ASIO_NOEXCEPT + { + return associated_executor::get(h.handler_, ex); + } +}; + +template +struct associated_executor, Executor> +{ + typedef typename associated_executor::type type; + + static type get(const detail::binder2& h, + const Executor& ex = Executor()) ASIO_NOEXCEPT + { + return associated_executor::get(h.handler_, ex); + } +}; + +#if defined(ASIO_HAS_MOVE) + +template +struct associated_allocator, Allocator> +{ + typedef typename associated_allocator::type type; + + static type get(const detail::move_binder1& h, + const Allocator& a = Allocator()) ASIO_NOEXCEPT + { + return associated_allocator::get(h.handler_, a); + } +}; + +template +struct associated_allocator< + detail::move_binder2, Allocator> +{ + typedef typename associated_allocator::type type; + + static type get(const detail::move_binder2& h, + const Allocator& a = Allocator()) ASIO_NOEXCEPT + { + return associated_allocator::get(h.handler_, a); + } +}; + +template +struct associated_executor, Executor> +{ + typedef typename associated_executor::type type; + + static type get(const detail::move_binder1& h, + const Executor& ex = Executor()) ASIO_NOEXCEPT + { + return associated_executor::get(h.handler_, ex); + } +}; + +template +struct associated_executor, Executor> +{ + typedef typename associated_executor::type type; + + static type get(const detail::move_binder2& h, + const Executor& ex = Executor()) ASIO_NOEXCEPT + { + return associated_executor::get(h.handler_, ex); + } +}; + +#endif // defined(ASIO_HAS_MOVE) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_BIND_HANDLER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/blocking_executor_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/blocking_executor_op.hpp new file mode 100644 index 000000000..7ea3cc42f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/blocking_executor_op.hpp @@ -0,0 +1,107 @@ +// +// detail/blocking_executor_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_BLOCKING_EXECUTOR_OP_HPP +#define ASIO_DETAIL_BLOCKING_EXECUTOR_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/event.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/mutex.hpp" +#include "asio/detail/scheduler_operation.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class blocking_executor_op_base : public Operation +{ +public: + blocking_executor_op_base(typename Operation::func_type complete_func) + : Operation(complete_func), + is_complete_(false) + { + } + + void wait() + { + asio::detail::mutex::scoped_lock lock(mutex_); + while (!is_complete_) + event_.wait(lock); + } + +protected: + struct do_complete_cleanup + { + ~do_complete_cleanup() + { + asio::detail::mutex::scoped_lock lock(op_->mutex_); + op_->is_complete_ = true; + op_->event_.unlock_and_signal_one_for_destruction(lock); + } + + blocking_executor_op_base* op_; + }; + +private: + asio::detail::mutex mutex_; + asio::detail::event event_; + bool is_complete_; +}; + +template +class blocking_executor_op : public blocking_executor_op_base +{ +public: + blocking_executor_op(Handler& h) + : blocking_executor_op_base(&blocking_executor_op::do_complete), + handler_(h) + { + } + + static void do_complete(void* owner, Operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + blocking_executor_op* o(static_cast(base)); + + typename blocking_executor_op_base::do_complete_cleanup + on_exit = { o }; + (void)on_exit; + + ASIO_HANDLER_COMPLETION((*o)); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN(()); + asio_handler_invoke_helpers::invoke(o->handler_, o->handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler& handler_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_BLOCKING_EXECUTOR_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/buffer_resize_guard.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/buffer_resize_guard.hpp new file mode 100644 index 000000000..c44736852 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/buffer_resize_guard.hpp @@ -0,0 +1,66 @@ +// +// detail/buffer_resize_guard.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_BUFFER_RESIZE_GUARD_HPP +#define ASIO_DETAIL_BUFFER_RESIZE_GUARD_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/limits.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Helper class to manage buffer resizing in an exception safe way. +template +class buffer_resize_guard +{ +public: + // Constructor. + buffer_resize_guard(Buffer& buffer) + : buffer_(buffer), + old_size_(buffer.size()) + { + } + + // Destructor rolls back the buffer resize unless commit was called. + ~buffer_resize_guard() + { + if (old_size_ != (std::numeric_limits::max)()) + { + buffer_.resize(old_size_); + } + } + + // Commit the resize transaction. + void commit() + { + old_size_ = (std::numeric_limits::max)(); + } + +private: + // The buffer being managed. + Buffer& buffer_; + + // The size of the buffer at the time the guard was constructed. + size_t old_size_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_BUFFER_RESIZE_GUARD_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/buffer_sequence_adapter.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/buffer_sequence_adapter.hpp new file mode 100644 index 000000000..2044bd5d4 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/buffer_sequence_adapter.hpp @@ -0,0 +1,650 @@ +// +// detail/buffer_sequence_adapter.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_BUFFER_SEQUENCE_ADAPTER_HPP +#define ASIO_DETAIL_BUFFER_SEQUENCE_ADAPTER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/buffer.hpp" +#include "asio/detail/array_fwd.hpp" +#include "asio/detail/socket_types.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class buffer_sequence_adapter_base +{ +#if defined(ASIO_WINDOWS_RUNTIME) +public: + // The maximum number of buffers to support in a single operation. + enum { max_buffers = 1 }; + +protected: + typedef Windows::Storage::Streams::IBuffer^ native_buffer_type; + + ASIO_DECL static void init_native_buffer( + native_buffer_type& buf, + const asio::mutable_buffer& buffer); + + ASIO_DECL static void init_native_buffer( + native_buffer_type& buf, + const asio::const_buffer& buffer); +#elif defined(ASIO_WINDOWS) || defined(__CYGWIN__) +public: + // The maximum number of buffers to support in a single operation. + enum { max_buffers = 64 < max_iov_len ? 64 : max_iov_len }; + +protected: + typedef WSABUF native_buffer_type; + + static void init_native_buffer(WSABUF& buf, + const asio::mutable_buffer& buffer) + { + buf.buf = static_cast(buffer.data()); + buf.len = static_cast(buffer.size()); + } + + static void init_native_buffer(WSABUF& buf, + const asio::const_buffer& buffer) + { + buf.buf = const_cast(static_cast(buffer.data())); + buf.len = static_cast(buffer.size()); + } +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +public: + // The maximum number of buffers to support in a single operation. + enum { max_buffers = 64 < max_iov_len ? 64 : max_iov_len }; + +protected: + typedef iovec native_buffer_type; + + static void init_iov_base(void*& base, void* addr) + { + base = addr; + } + + template + static void init_iov_base(T& base, void* addr) + { + base = static_cast(addr); + } + + static void init_native_buffer(iovec& iov, + const asio::mutable_buffer& buffer) + { + init_iov_base(iov.iov_base, buffer.data()); + iov.iov_len = buffer.size(); + } + + static void init_native_buffer(iovec& iov, + const asio::const_buffer& buffer) + { + init_iov_base(iov.iov_base, const_cast(buffer.data())); + iov.iov_len = buffer.size(); + } +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +}; + +// Helper class to translate buffers into the native buffer representation. +template +class buffer_sequence_adapter + : buffer_sequence_adapter_base +{ +public: + enum { is_single_buffer = false }; + + explicit buffer_sequence_adapter(const Buffers& buffer_sequence) + : count_(0), total_buffer_size_(0) + { + buffer_sequence_adapter::init( + asio::buffer_sequence_begin(buffer_sequence), + asio::buffer_sequence_end(buffer_sequence)); + } + + native_buffer_type* buffers() + { + return buffers_; + } + + std::size_t count() const + { + return count_; + } + + std::size_t total_size() const + { + return total_buffer_size_; + } + + bool all_empty() const + { + return total_buffer_size_ == 0; + } + + static bool all_empty(const Buffers& buffer_sequence) + { + return buffer_sequence_adapter::all_empty( + asio::buffer_sequence_begin(buffer_sequence), + asio::buffer_sequence_end(buffer_sequence)); + } + + static void validate(const Buffers& buffer_sequence) + { + buffer_sequence_adapter::validate( + asio::buffer_sequence_begin(buffer_sequence), + asio::buffer_sequence_end(buffer_sequence)); + } + + static Buffer first(const Buffers& buffer_sequence) + { + return buffer_sequence_adapter::first( + asio::buffer_sequence_begin(buffer_sequence), + asio::buffer_sequence_end(buffer_sequence)); + } + + enum { linearisation_storage_size = 8192 }; + + static Buffer linearise(const Buffers& buffer_sequence, + const asio::mutable_buffer& storage) + { + return buffer_sequence_adapter::linearise( + asio::buffer_sequence_begin(buffer_sequence), + asio::buffer_sequence_end(buffer_sequence), storage); + } + +private: + template + void init(Iterator begin, Iterator end) + { + Iterator iter = begin; + for (; iter != end && count_ < max_buffers; ++iter, ++count_) + { + Buffer buffer(*iter); + init_native_buffer(buffers_[count_], buffer); + total_buffer_size_ += buffer.size(); + } + } + + template + static bool all_empty(Iterator begin, Iterator end) + { + Iterator iter = begin; + std::size_t i = 0; + for (; iter != end && i < max_buffers; ++iter, ++i) + if (Buffer(*iter).size() > 0) + return false; + return true; + } + + template + static void validate(Iterator begin, Iterator end) + { + Iterator iter = begin; + for (; iter != end; ++iter) + { + Buffer buffer(*iter); + buffer.data(); + } + } + + template + static Buffer first(Iterator begin, Iterator end) + { + Iterator iter = begin; + for (; iter != end; ++iter) + { + Buffer buffer(*iter); + if (buffer.size() != 0) + return buffer; + } + return Buffer(); + } + + template + static Buffer linearise(Iterator begin, Iterator end, + const asio::mutable_buffer& storage) + { + asio::mutable_buffer unused_storage = storage; + Iterator iter = begin; + while (iter != end && unused_storage.size() != 0) + { + Buffer buffer(*iter); + ++iter; + if (buffer.size() == 0) + continue; + if (unused_storage.size() == storage.size()) + { + if (iter == end) + return buffer; + if (buffer.size() >= unused_storage.size()) + return buffer; + } + unused_storage += asio::buffer_copy(unused_storage, buffer); + } + return Buffer(storage.data(), storage.size() - unused_storage.size()); + } + + native_buffer_type buffers_[max_buffers]; + std::size_t count_; + std::size_t total_buffer_size_; +}; + +template +class buffer_sequence_adapter + : buffer_sequence_adapter_base +{ +public: + enum { is_single_buffer = true }; + + explicit buffer_sequence_adapter( + const asio::mutable_buffer& buffer_sequence) + { + init_native_buffer(buffer_, Buffer(buffer_sequence)); + total_buffer_size_ = buffer_sequence.size(); + } + + native_buffer_type* buffers() + { + return &buffer_; + } + + std::size_t count() const + { + return 1; + } + + std::size_t total_size() const + { + return total_buffer_size_; + } + + bool all_empty() const + { + return total_buffer_size_ == 0; + } + + static bool all_empty(const asio::mutable_buffer& buffer_sequence) + { + return buffer_sequence.size() == 0; + } + + static void validate(const asio::mutable_buffer& buffer_sequence) + { + buffer_sequence.data(); + } + + static Buffer first(const asio::mutable_buffer& buffer_sequence) + { + return Buffer(buffer_sequence); + } + + enum { linearisation_storage_size = 1 }; + + static Buffer linearise(const asio::mutable_buffer& buffer_sequence, + const Buffer&) + { + return Buffer(buffer_sequence); + } + +private: + native_buffer_type buffer_; + std::size_t total_buffer_size_; +}; + +template +class buffer_sequence_adapter + : buffer_sequence_adapter_base +{ +public: + enum { is_single_buffer = true }; + + explicit buffer_sequence_adapter( + const asio::const_buffer& buffer_sequence) + { + init_native_buffer(buffer_, Buffer(buffer_sequence)); + total_buffer_size_ = buffer_sequence.size(); + } + + native_buffer_type* buffers() + { + return &buffer_; + } + + std::size_t count() const + { + return 1; + } + + std::size_t total_size() const + { + return total_buffer_size_; + } + + bool all_empty() const + { + return total_buffer_size_ == 0; + } + + static bool all_empty(const asio::const_buffer& buffer_sequence) + { + return buffer_sequence.size() == 0; + } + + static void validate(const asio::const_buffer& buffer_sequence) + { + buffer_sequence.data(); + } + + static Buffer first(const asio::const_buffer& buffer_sequence) + { + return Buffer(buffer_sequence); + } + + enum { linearisation_storage_size = 1 }; + + static Buffer linearise(const asio::const_buffer& buffer_sequence, + const Buffer&) + { + return Buffer(buffer_sequence); + } + +private: + native_buffer_type buffer_; + std::size_t total_buffer_size_; +}; + +#if !defined(ASIO_NO_DEPRECATED) + +template +class buffer_sequence_adapter + : buffer_sequence_adapter_base +{ +public: + enum { is_single_buffer = true }; + + explicit buffer_sequence_adapter( + const asio::mutable_buffers_1& buffer_sequence) + { + init_native_buffer(buffer_, Buffer(buffer_sequence)); + total_buffer_size_ = buffer_sequence.size(); + } + + native_buffer_type* buffers() + { + return &buffer_; + } + + std::size_t count() const + { + return 1; + } + + std::size_t total_size() const + { + return total_buffer_size_; + } + + bool all_empty() const + { + return total_buffer_size_ == 0; + } + + static bool all_empty(const asio::mutable_buffers_1& buffer_sequence) + { + return buffer_sequence.size() == 0; + } + + static void validate(const asio::mutable_buffers_1& buffer_sequence) + { + buffer_sequence.data(); + } + + static Buffer first(const asio::mutable_buffers_1& buffer_sequence) + { + return Buffer(buffer_sequence); + } + + enum { linearisation_storage_size = 1 }; + + static Buffer linearise(const asio::mutable_buffers_1& buffer_sequence, + const Buffer&) + { + return Buffer(buffer_sequence); + } + +private: + native_buffer_type buffer_; + std::size_t total_buffer_size_; +}; + +template +class buffer_sequence_adapter + : buffer_sequence_adapter_base +{ +public: + enum { is_single_buffer = true }; + + explicit buffer_sequence_adapter( + const asio::const_buffers_1& buffer_sequence) + { + init_native_buffer(buffer_, Buffer(buffer_sequence)); + total_buffer_size_ = buffer_sequence.size(); + } + + native_buffer_type* buffers() + { + return &buffer_; + } + + std::size_t count() const + { + return 1; + } + + std::size_t total_size() const + { + return total_buffer_size_; + } + + bool all_empty() const + { + return total_buffer_size_ == 0; + } + + static bool all_empty(const asio::const_buffers_1& buffer_sequence) + { + return buffer_sequence.size() == 0; + } + + static void validate(const asio::const_buffers_1& buffer_sequence) + { + buffer_sequence.data(); + } + + static Buffer first(const asio::const_buffers_1& buffer_sequence) + { + return Buffer(buffer_sequence); + } + + enum { linearisation_storage_size = 1 }; + + static Buffer linearise(const asio::const_buffers_1& buffer_sequence, + const Buffer&) + { + return Buffer(buffer_sequence); + } + +private: + native_buffer_type buffer_; + std::size_t total_buffer_size_; +}; + +#endif // !defined(ASIO_NO_DEPRECATED) + +template +class buffer_sequence_adapter > + : buffer_sequence_adapter_base +{ +public: + enum { is_single_buffer = false }; + + explicit buffer_sequence_adapter( + const boost::array& buffer_sequence) + { + init_native_buffer(buffers_[0], Buffer(buffer_sequence[0])); + init_native_buffer(buffers_[1], Buffer(buffer_sequence[1])); + total_buffer_size_ = buffer_sequence[0].size() + buffer_sequence[1].size(); + } + + native_buffer_type* buffers() + { + return buffers_; + } + + std::size_t count() const + { + return 2; + } + + std::size_t total_size() const + { + return total_buffer_size_; + } + + bool all_empty() const + { + return total_buffer_size_ == 0; + } + + static bool all_empty(const boost::array& buffer_sequence) + { + return buffer_sequence[0].size() == 0 && buffer_sequence[1].size() == 0; + } + + static void validate(const boost::array& buffer_sequence) + { + buffer_sequence[0].data(); + buffer_sequence[1].data(); + } + + static Buffer first(const boost::array& buffer_sequence) + { + return Buffer(buffer_sequence[0].size() != 0 + ? buffer_sequence[0] : buffer_sequence[1]); + } + + enum { linearisation_storage_size = 8192 }; + + static Buffer linearise(const boost::array& buffer_sequence, + const asio::mutable_buffer& storage) + { + if (buffer_sequence[0].size() == 0) + return Buffer(buffer_sequence[1]); + if (buffer_sequence[1].size() == 0) + return Buffer(buffer_sequence[0]); + return Buffer(storage.data(), + asio::buffer_copy(storage, buffer_sequence)); + } + +private: + native_buffer_type buffers_[2]; + std::size_t total_buffer_size_; +}; + +#if defined(ASIO_HAS_STD_ARRAY) + +template +class buffer_sequence_adapter > + : buffer_sequence_adapter_base +{ +public: + enum { is_single_buffer = false }; + + explicit buffer_sequence_adapter( + const std::array& buffer_sequence) + { + init_native_buffer(buffers_[0], Buffer(buffer_sequence[0])); + init_native_buffer(buffers_[1], Buffer(buffer_sequence[1])); + total_buffer_size_ = buffer_sequence[0].size() + buffer_sequence[1].size(); + } + + native_buffer_type* buffers() + { + return buffers_; + } + + std::size_t count() const + { + return 2; + } + + std::size_t total_size() const + { + return total_buffer_size_; + } + + bool all_empty() const + { + return total_buffer_size_ == 0; + } + + static bool all_empty(const std::array& buffer_sequence) + { + return buffer_sequence[0].size() == 0 && buffer_sequence[1].size() == 0; + } + + static void validate(const std::array& buffer_sequence) + { + buffer_sequence[0].data(); + buffer_sequence[1].data(); + } + + static Buffer first(const std::array& buffer_sequence) + { + return Buffer(buffer_sequence[0].size() != 0 + ? buffer_sequence[0] : buffer_sequence[1]); + } + + enum { linearisation_storage_size = 8192 }; + + static Buffer linearise(const std::array& buffer_sequence, + const asio::mutable_buffer& storage) + { + if (buffer_sequence[0].size() == 0) + return Buffer(buffer_sequence[1]); + if (buffer_sequence[1].size() == 0) + return Buffer(buffer_sequence[0]); + return Buffer(storage.data(), + asio::buffer_copy(storage, buffer_sequence)); + } + +private: + native_buffer_type buffers_[2]; + std::size_t total_buffer_size_; +}; + +#endif // defined(ASIO_HAS_STD_ARRAY) + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/buffer_sequence_adapter.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // ASIO_DETAIL_BUFFER_SEQUENCE_ADAPTER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/buffered_stream_storage.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/buffered_stream_storage.hpp new file mode 100644 index 000000000..ea5882db7 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/buffered_stream_storage.hpp @@ -0,0 +1,126 @@ +// +// detail/buffered_stream_storage.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_BUFFERED_STREAM_STORAGE_HPP +#define ASIO_DETAIL_BUFFERED_STREAM_STORAGE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/buffer.hpp" +#include "asio/detail/assert.hpp" +#include +#include +#include + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class buffered_stream_storage +{ +public: + // The type of the bytes stored in the buffer. + typedef unsigned char byte_type; + + // The type used for offsets into the buffer. + typedef std::size_t size_type; + + // Constructor. + explicit buffered_stream_storage(std::size_t buffer_capacity) + : begin_offset_(0), + end_offset_(0), + buffer_(buffer_capacity) + { + } + + /// Clear the buffer. + void clear() + { + begin_offset_ = 0; + end_offset_ = 0; + } + + // Return a pointer to the beginning of the unread data. + mutable_buffer data() + { + return asio::buffer(buffer_) + begin_offset_; + } + + // Return a pointer to the beginning of the unread data. + const_buffer data() const + { + return asio::buffer(buffer_) + begin_offset_; + } + + // Is there no unread data in the buffer. + bool empty() const + { + return begin_offset_ == end_offset_; + } + + // Return the amount of unread data the is in the buffer. + size_type size() const + { + return end_offset_ - begin_offset_; + } + + // Resize the buffer to the specified length. + void resize(size_type length) + { + ASIO_ASSERT(length <= capacity()); + if (begin_offset_ + length <= capacity()) + { + end_offset_ = begin_offset_ + length; + } + else + { + using namespace std; // For memmove. + memmove(&buffer_[0], &buffer_[0] + begin_offset_, size()); + end_offset_ = length; + begin_offset_ = 0; + } + } + + // Return the maximum size for data in the buffer. + size_type capacity() const + { + return buffer_.size(); + } + + // Consume multiple bytes from the beginning of the buffer. + void consume(size_type count) + { + ASIO_ASSERT(begin_offset_ + count <= end_offset_); + begin_offset_ += count; + if (empty()) + clear(); + } + +private: + // The offset to the beginning of the unread data. + size_type begin_offset_; + + // The offset to the end of the unread data. + size_type end_offset_; + + // The data in the buffer. + std::vector buffer_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_BUFFERED_STREAM_STORAGE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/bulk_executor_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/bulk_executor_op.hpp new file mode 100644 index 000000000..dc417533d --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/bulk_executor_op.hpp @@ -0,0 +1,88 @@ +// +// detail/bulk_executor_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_BULK_EXECUTOR_OP_HPP +#define ASIO_DETAIL_BULK_EXECUTOR_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/scheduler_operation.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class bulk_executor_op : public Operation +{ +public: + ASIO_DEFINE_HANDLER_ALLOCATOR_PTR(bulk_executor_op); + + template + bulk_executor_op(ASIO_MOVE_ARG(H) h, + const Alloc& allocator, std::size_t i) + : Operation(&bulk_executor_op::do_complete), + handler_(ASIO_MOVE_CAST(H)(h)), + allocator_(allocator), + index_(i) + { + } + + static void do_complete(void* owner, Operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the handler object. + bulk_executor_op* o(static_cast(base)); + Alloc allocator(o->allocator_); + ptr p = { detail::addressof(allocator), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder1 handler(o->handler_, o->index_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN(()); + asio_handler_invoke_helpers::invoke(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + Alloc allocator_; + std::size_t index_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_BULK_EXECUTOR_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/call_stack.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/call_stack.hpp new file mode 100644 index 000000000..159458958 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/call_stack.hpp @@ -0,0 +1,125 @@ +// +// detail/call_stack.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_CALL_STACK_HPP +#define ASIO_DETAIL_CALL_STACK_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/tss_ptr.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Helper class to determine whether or not the current thread is inside an +// invocation of io_context::run() for a specified io_context object. +template +class call_stack +{ +public: + // Context class automatically pushes the key/value pair on to the stack. + class context + : private noncopyable + { + public: + // Push the key on to the stack. + explicit context(Key* k) + : key_(k), + next_(call_stack::top_) + { + value_ = reinterpret_cast(this); + call_stack::top_ = this; + } + + // Push the key/value pair on to the stack. + context(Key* k, Value& v) + : key_(k), + value_(&v), + next_(call_stack::top_) + { + call_stack::top_ = this; + } + + // Pop the key/value pair from the stack. + ~context() + { + call_stack::top_ = next_; + } + + // Find the next context with the same key. + Value* next_by_key() const + { + context* elem = next_; + while (elem) + { + if (elem->key_ == key_) + return elem->value_; + elem = elem->next_; + } + return 0; + } + + private: + friend class call_stack; + + // The key associated with the context. + Key* key_; + + // The value associated with the context. + Value* value_; + + // The next element in the stack. + context* next_; + }; + + friend class context; + + // Determine whether the specified owner is on the stack. Returns address of + // key if present, 0 otherwise. + static Value* contains(Key* k) + { + context* elem = top_; + while (elem) + { + if (elem->key_ == k) + return elem->value_; + elem = elem->next_; + } + return 0; + } + + // Obtain the value at the top of the stack. + static Value* top() + { + context* elem = top_; + return elem ? elem->value_ : 0; + } + +private: + // The top of the stack of calls for the current thread. + static tss_ptr top_; +}; + +template +tss_ptr::context> +call_stack::top_; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_CALL_STACK_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/chrono.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/chrono.hpp new file mode 100644 index 000000000..f2df56f3a --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/chrono.hpp @@ -0,0 +1,66 @@ +// +// detail/chrono.hpp +// ~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_CHRONO_HPP +#define ASIO_DETAIL_CHRONO_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_STD_CHRONO) +# include +#elif defined(ASIO_HAS_BOOST_CHRONO) +# include +#endif // defined(ASIO_HAS_BOOST_CHRONO) + +namespace asio { +namespace chrono { + +#if defined(ASIO_HAS_STD_CHRONO) +using std::chrono::duration; +using std::chrono::time_point; +using std::chrono::duration_cast; +using std::chrono::nanoseconds; +using std::chrono::microseconds; +using std::chrono::milliseconds; +using std::chrono::seconds; +using std::chrono::minutes; +using std::chrono::hours; +using std::chrono::time_point_cast; +#if defined(ASIO_HAS_STD_CHRONO_MONOTONIC_CLOCK) +typedef std::chrono::monotonic_clock steady_clock; +#else // defined(ASIO_HAS_STD_CHRONO_MONOTONIC_CLOCK) +using std::chrono::steady_clock; +#endif // defined(ASIO_HAS_STD_CHRONO_MONOTONIC_CLOCK) +using std::chrono::system_clock; +using std::chrono::high_resolution_clock; +#elif defined(ASIO_HAS_BOOST_CHRONO) +using boost::chrono::duration; +using boost::chrono::time_point; +using boost::chrono::duration_cast; +using boost::chrono::nanoseconds; +using boost::chrono::microseconds; +using boost::chrono::milliseconds; +using boost::chrono::seconds; +using boost::chrono::minutes; +using boost::chrono::hours; +using boost::chrono::time_point_cast; +using boost::chrono::system_clock; +using boost::chrono::steady_clock; +using boost::chrono::high_resolution_clock; +#endif // defined(ASIO_HAS_BOOST_CHRONO) + +} // namespace chrono +} // namespace asio + +#endif // ASIO_DETAIL_CHRONO_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/chrono_time_traits.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/chrono_time_traits.hpp new file mode 100644 index 000000000..47355c9ff --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/chrono_time_traits.hpp @@ -0,0 +1,190 @@ +// +// detail/chrono_time_traits.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_CHRONO_TIME_TRAITS_HPP +#define ASIO_DETAIL_CHRONO_TIME_TRAITS_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/cstdint.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Helper template to compute the greatest common divisor. +template +struct gcd { enum { value = gcd::value }; }; + +template +struct gcd { enum { value = v1 }; }; + +// Adapts std::chrono clocks for use with a deadline timer. +template +struct chrono_time_traits +{ + // The clock type. + typedef Clock clock_type; + + // The duration type of the clock. + typedef typename clock_type::duration duration_type; + + // The time point type of the clock. + typedef typename clock_type::time_point time_type; + + // The period of the clock. + typedef typename duration_type::period period_type; + + // Get the current time. + static time_type now() + { + return clock_type::now(); + } + + // Add a duration to a time. + static time_type add(const time_type& t, const duration_type& d) + { + const time_type epoch; + if (t >= epoch) + { + if ((time_type::max)() - t < d) + return (time_type::max)(); + } + else // t < epoch + { + if (-(t - (time_type::min)()) > d) + return (time_type::min)(); + } + + return t + d; + } + + // Subtract one time from another. + static duration_type subtract(const time_type& t1, const time_type& t2) + { + const time_type epoch; + if (t1 >= epoch) + { + if (t2 >= epoch) + { + return t1 - t2; + } + else if (t2 == (time_type::min)()) + { + return (duration_type::max)(); + } + else if ((time_type::max)() - t1 < epoch - t2) + { + return (duration_type::max)(); + } + else + { + return t1 - t2; + } + } + else // t1 < epoch + { + if (t2 < epoch) + { + return t1 - t2; + } + else if (t1 == (time_type::min)()) + { + return (duration_type::min)(); + } + else if ((time_type::max)() - t2 < epoch - t1) + { + return (duration_type::min)(); + } + else + { + return -(t2 - t1); + } + } + } + + // Test whether one time is less than another. + static bool less_than(const time_type& t1, const time_type& t2) + { + return t1 < t2; + } + + // Implement just enough of the posix_time::time_duration interface to supply + // what the timer_queue requires. + class posix_time_duration + { + public: + explicit posix_time_duration(const duration_type& d) + : d_(d) + { + } + + int64_t ticks() const + { + return d_.count(); + } + + int64_t total_seconds() const + { + return duration_cast<1, 1>(); + } + + int64_t total_milliseconds() const + { + return duration_cast<1, 1000>(); + } + + int64_t total_microseconds() const + { + return duration_cast<1, 1000000>(); + } + + private: + template + int64_t duration_cast() const + { + const int64_t num1 = period_type::num / gcd::value; + const int64_t num2 = Num / gcd::value; + + const int64_t den1 = period_type::den / gcd::value; + const int64_t den2 = Den / gcd::value; + + const int64_t num = num1 * den2; + const int64_t den = num2 * den1; + + if (num == 1 && den == 1) + return ticks(); + else if (num != 1 && den == 1) + return ticks() * num; + else if (num == 1 && period_type::den != 1) + return ticks() / den; + else + return ticks() * num / den; + } + + duration_type d_; + }; + + // Convert to POSIX duration type. + static posix_time_duration to_posix_duration(const duration_type& d) + { + return posix_time_duration(WaitTraits::to_wait_duration(d)); + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_CHRONO_TIME_TRAITS_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/completion_handler.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/completion_handler.hpp new file mode 100644 index 000000000..1de45f871 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/completion_handler.hpp @@ -0,0 +1,88 @@ +// +// detail/completion_handler.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_COMPLETION_HANDLER_HPP +#define ASIO_DETAIL_COMPLETION_HANDLER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/operation.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class completion_handler : public operation +{ +public: + ASIO_DEFINE_HANDLER_PTR(completion_handler); + + completion_handler(Handler& h, const IoExecutor& io_ex) + : operation(&completion_handler::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(h)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the handler object. + completion_handler* h(static_cast(base)); + ptr p = { asio::detail::addressof(h->handler_), h, h }; + + ASIO_HANDLER_COMPLETION((*h)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + h->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + Handler handler(ASIO_MOVE_CAST(Handler)(h->handler_)); + p.h = asio::detail::addressof(handler); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN(()); + w.complete(handler, handler); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_COMPLETION_HANDLER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/concurrency_hint.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/concurrency_hint.hpp new file mode 100644 index 000000000..04eaa90e1 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/concurrency_hint.hpp @@ -0,0 +1,94 @@ +// +// detail/concurrency_hint.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_CONCURRENCY_HINT_HPP +#define ASIO_DETAIL_CONCURRENCY_HINT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/noncopyable.hpp" + +// The concurrency hint ID and mask are used to identify when a "well-known" +// concurrency hint value has been passed to the io_context. +#define ASIO_CONCURRENCY_HINT_ID 0xA5100000u +#define ASIO_CONCURRENCY_HINT_ID_MASK 0xFFFF0000u + +// If set, this bit indicates that the scheduler should perform locking. +#define ASIO_CONCURRENCY_HINT_LOCKING_SCHEDULER 0x1u + +// If set, this bit indicates that the reactor should perform locking when +// managing descriptor registrations. +#define ASIO_CONCURRENCY_HINT_LOCKING_REACTOR_REGISTRATION 0x2u + +// If set, this bit indicates that the reactor should perform locking for I/O. +#define ASIO_CONCURRENCY_HINT_LOCKING_REACTOR_IO 0x4u + +// Helper macro to determine if we have a special concurrency hint. +#define ASIO_CONCURRENCY_HINT_IS_SPECIAL(hint) \ + ((static_cast(hint) \ + & ASIO_CONCURRENCY_HINT_ID_MASK) \ + == ASIO_CONCURRENCY_HINT_ID) + +// Helper macro to determine if locking is enabled for a given facility. +#define ASIO_CONCURRENCY_HINT_IS_LOCKING(facility, hint) \ + (((static_cast(hint) \ + & (ASIO_CONCURRENCY_HINT_ID_MASK \ + | ASIO_CONCURRENCY_HINT_LOCKING_ ## facility)) \ + ^ ASIO_CONCURRENCY_HINT_ID) != 0) + +// This special concurrency hint disables locking in both the scheduler and +// reactor I/O. This hint has the following restrictions: +// +// - Care must be taken to ensure that all operations on the io_context and any +// of its associated I/O objects (such as sockets and timers) occur in only +// one thread at a time. +// +// - Asynchronous resolve operations fail with operation_not_supported. +// +// - If a signal_set is used with the io_context, signal_set objects cannot be +// used with any other io_context in the program. +#define ASIO_CONCURRENCY_HINT_UNSAFE \ + static_cast(ASIO_CONCURRENCY_HINT_ID) + +// This special concurrency hint disables locking in the reactor I/O. This hint +// has the following restrictions: +// +// - Care must be taken to ensure that run functions on the io_context, and all +// operations on the io_context's associated I/O objects (such as sockets and +// timers), occur in only one thread at a time. +#define ASIO_CONCURRENCY_HINT_UNSAFE_IO \ + static_cast(ASIO_CONCURRENCY_HINT_ID \ + | ASIO_CONCURRENCY_HINT_LOCKING_SCHEDULER \ + | ASIO_CONCURRENCY_HINT_LOCKING_REACTOR_REGISTRATION) + +// The special concurrency hint provides full thread safety. +#define ASIO_CONCURRENCY_HINT_SAFE \ + static_cast(ASIO_CONCURRENCY_HINT_ID \ + | ASIO_CONCURRENCY_HINT_LOCKING_SCHEDULER \ + | ASIO_CONCURRENCY_HINT_LOCKING_REACTOR_REGISTRATION \ + | ASIO_CONCURRENCY_HINT_LOCKING_REACTOR_IO) + +// This #define may be overridden at compile time to specify a program-wide +// default concurrency hint, used by the zero-argument io_context constructor. +#if !defined(ASIO_CONCURRENCY_HINT_DEFAULT) +# define ASIO_CONCURRENCY_HINT_DEFAULT -1 +#endif // !defined(ASIO_CONCURRENCY_HINT_DEFAULT) + +// This #define may be overridden at compile time to specify a program-wide +// concurrency hint, used by the one-argument io_context constructor when +// passed a value of 1. +#if !defined(ASIO_CONCURRENCY_HINT_1) +# define ASIO_CONCURRENCY_HINT_1 1 +#endif // !defined(ASIO_CONCURRENCY_HINT_DEFAULT) + +#endif // ASIO_DETAIL_CONCURRENCY_HINT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/conditionally_enabled_event.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/conditionally_enabled_event.hpp new file mode 100644 index 000000000..d40263e57 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/conditionally_enabled_event.hpp @@ -0,0 +1,120 @@ +// +// detail/conditionally_enabled_event.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_CONDITIONALLY_ENABLED_EVENT_HPP +#define ASIO_DETAIL_CONDITIONALLY_ENABLED_EVENT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/conditionally_enabled_mutex.hpp" +#include "asio/detail/event.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/null_event.hpp" +#include "asio/detail/scoped_lock.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Mutex adapter used to conditionally enable or disable locking. +class conditionally_enabled_event + : private noncopyable +{ +public: + // Constructor. + conditionally_enabled_event() + { + } + + // Destructor. + ~conditionally_enabled_event() + { + } + + // Signal the event. (Retained for backward compatibility.) + void signal(conditionally_enabled_mutex::scoped_lock& lock) + { + if (lock.mutex_.enabled_) + event_.signal(lock); + } + + // Signal all waiters. + void signal_all(conditionally_enabled_mutex::scoped_lock& lock) + { + if (lock.mutex_.enabled_) + event_.signal_all(lock); + } + + // Unlock the mutex and signal one waiter. + void unlock_and_signal_one( + conditionally_enabled_mutex::scoped_lock& lock) + { + if (lock.mutex_.enabled_) + event_.unlock_and_signal_one(lock); + } + + // Unlock the mutex and signal one waiter who may destroy us. + void unlock_and_signal_one_for_destruction( + conditionally_enabled_mutex::scoped_lock& lock) + { + if (lock.mutex_.enabled_) + event_.unlock_and_signal_one(lock); + } + + // If there's a waiter, unlock the mutex and signal it. + bool maybe_unlock_and_signal_one( + conditionally_enabled_mutex::scoped_lock& lock) + { + if (lock.mutex_.enabled_) + return event_.maybe_unlock_and_signal_one(lock); + else + return false; + } + + // Reset the event. + void clear(conditionally_enabled_mutex::scoped_lock& lock) + { + if (lock.mutex_.enabled_) + event_.clear(lock); + } + + // Wait for the event to become signalled. + void wait(conditionally_enabled_mutex::scoped_lock& lock) + { + if (lock.mutex_.enabled_) + event_.wait(lock); + else + null_event().wait(lock); + } + + // Timed wait for the event to become signalled. + bool wait_for_usec( + conditionally_enabled_mutex::scoped_lock& lock, long usec) + { + if (lock.mutex_.enabled_) + return event_.wait_for_usec(lock, usec); + else + return null_event().wait_for_usec(lock, usec); + } + +private: + asio::detail::event event_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_CONDITIONALLY_ENABLED_EVENT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/conditionally_enabled_mutex.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/conditionally_enabled_mutex.hpp new file mode 100644 index 000000000..185fbe97b --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/conditionally_enabled_mutex.hpp @@ -0,0 +1,149 @@ +// +// detail/conditionally_enabled_mutex.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_CONDITIONALLY_ENABLED_MUTEX_HPP +#define ASIO_DETAIL_CONDITIONALLY_ENABLED_MUTEX_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/mutex.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/scoped_lock.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Mutex adapter used to conditionally enable or disable locking. +class conditionally_enabled_mutex + : private noncopyable +{ +public: + // Helper class to lock and unlock a mutex automatically. + class scoped_lock + : private noncopyable + { + public: + // Tag type used to distinguish constructors. + enum adopt_lock_t { adopt_lock }; + + // Constructor adopts a lock that is already held. + scoped_lock(conditionally_enabled_mutex& m, adopt_lock_t) + : mutex_(m), + locked_(m.enabled_) + { + } + + // Constructor acquires the lock. + explicit scoped_lock(conditionally_enabled_mutex& m) + : mutex_(m) + { + if (m.enabled_) + { + mutex_.mutex_.lock(); + locked_ = true; + } + else + locked_ = false; + } + + // Destructor releases the lock. + ~scoped_lock() + { + if (locked_) + mutex_.mutex_.unlock(); + } + + // Explicitly acquire the lock. + void lock() + { + if (mutex_.enabled_ && !locked_) + { + mutex_.mutex_.lock(); + locked_ = true; + } + } + + // Explicitly release the lock. + void unlock() + { + if (locked_) + { + mutex_.unlock(); + locked_ = false; + } + } + + // Test whether the lock is held. + bool locked() const + { + return locked_; + } + + // Get the underlying mutex. + asio::detail::mutex& mutex() + { + return mutex_.mutex_; + } + + private: + friend class conditionally_enabled_event; + conditionally_enabled_mutex& mutex_; + bool locked_; + }; + + // Constructor. + explicit conditionally_enabled_mutex(bool enabled) + : enabled_(enabled) + { + } + + // Destructor. + ~conditionally_enabled_mutex() + { + } + + // Determine whether locking is enabled. + bool enabled() const + { + return enabled_; + } + + // Lock the mutex. + void lock() + { + if (enabled_) + mutex_.lock(); + } + + // Unlock the mutex. + void unlock() + { + if (enabled_) + mutex_.unlock(); + } + +private: + friend class scoped_lock; + friend class conditionally_enabled_event; + asio::detail::mutex mutex_; + const bool enabled_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_CONDITIONALLY_ENABLED_MUTEX_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/config.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/config.hpp new file mode 100644 index 000000000..f9faa6713 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/config.hpp @@ -0,0 +1,1822 @@ +// +// detail/config.hpp +// ~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_CONFIG_HPP +#define ASIO_DETAIL_CONFIG_HPP + +// boostify: non-boost code starts here +#if !defined(ASIO_STANDALONE) +# if !defined(ASIO_ENABLE_BOOST) +# if (__cplusplus >= 201103) +# define ASIO_STANDALONE 1 +# elif defined(_MSC_VER) && defined(_MSVC_LANG) +# if (_MSC_VER >= 1900) && (_MSVC_LANG >= 201103) +# define ASIO_STANDALONE 1 +# endif // (_MSC_VER >= 1900) && (_MSVC_LANG >= 201103) +# endif // defined(_MSC_VER) && defined(_MSVC_LANG) +# endif // !defined(ASIO_ENABLE_BOOST) +#endif // !defined(ASIO_STANDALONE) + +// boostify: non-boost code ends here +#if defined(ASIO_STANDALONE) +# define ASIO_DISABLE_BOOST_ARRAY 1 +# define ASIO_DISABLE_BOOST_ASSERT 1 +# define ASIO_DISABLE_BOOST_BIND 1 +# define ASIO_DISABLE_BOOST_CHRONO 1 +# define ASIO_DISABLE_BOOST_DATE_TIME 1 +# define ASIO_DISABLE_BOOST_LIMITS 1 +# define ASIO_DISABLE_BOOST_REGEX 1 +# define ASIO_DISABLE_BOOST_STATIC_CONSTANT 1 +# define ASIO_DISABLE_BOOST_THROW_EXCEPTION 1 +# define ASIO_DISABLE_BOOST_WORKAROUND 1 +#else // defined(ASIO_STANDALONE) +# include +# include +# define ASIO_HAS_BOOST_CONFIG 1 +#endif // defined(ASIO_STANDALONE) + +// Default to a header-only implementation. The user must specifically request +// separate compilation by defining either ASIO_SEPARATE_COMPILATION or +// ASIO_DYN_LINK (as a DLL/shared library implies separate compilation). +#if !defined(ASIO_HEADER_ONLY) +# if !defined(ASIO_SEPARATE_COMPILATION) +# if !defined(ASIO_DYN_LINK) +# define ASIO_HEADER_ONLY 1 +# endif // !defined(ASIO_DYN_LINK) +# endif // !defined(ASIO_SEPARATE_COMPILATION) +#endif // !defined(ASIO_HEADER_ONLY) + +#if defined(ASIO_HEADER_ONLY) +# define ASIO_DECL inline +#else // defined(ASIO_HEADER_ONLY) +# if defined(_MSC_VER) || defined(__BORLANDC__) || defined(__CODEGEARC__) +// We need to import/export our code only if the user has specifically asked +// for it by defining ASIO_DYN_LINK. +# if defined(ASIO_DYN_LINK) +// Export if this is our own source, otherwise import. +# if defined(ASIO_SOURCE) +# define ASIO_DECL __declspec(dllexport) +# else // defined(ASIO_SOURCE) +# define ASIO_DECL __declspec(dllimport) +# endif // defined(ASIO_SOURCE) +# endif // defined(ASIO_DYN_LINK) +# endif // defined(_MSC_VER) || defined(__BORLANDC__) || defined(__CODEGEARC__) +#endif // defined(ASIO_HEADER_ONLY) + +// If ASIO_DECL isn't defined yet define it now. +#if !defined(ASIO_DECL) +# define ASIO_DECL +#endif // !defined(ASIO_DECL) + +// Helper macro for documentation. +#define ASIO_UNSPECIFIED(e) e + +// Microsoft Visual C++ detection. +#if !defined(ASIO_MSVC) +# if defined(ASIO_HAS_BOOST_CONFIG) && defined(BOOST_MSVC) +# define ASIO_MSVC BOOST_MSVC +# elif defined(_MSC_VER) && (defined(__INTELLISENSE__) \ + || (!defined(__MWERKS__) && !defined(__EDG_VERSION__))) +# define ASIO_MSVC _MSC_VER +# endif // defined(ASIO_HAS_BOOST_CONFIG) && defined(BOOST_MSVC) +#endif // !defined(ASIO_MSVC) + +// Clang / libc++ detection. +#if defined(__clang__) +# if (__cplusplus >= 201103) +# if __has_include(<__config>) +# include <__config> +# if defined(_LIBCPP_VERSION) +# define ASIO_HAS_CLANG_LIBCXX 1 +# endif // defined(_LIBCPP_VERSION) +# endif // __has_include(<__config>) +# endif // (__cplusplus >= 201103) +#endif // defined(__clang__) + +// Android platform detection. +#if defined(__ANDROID__) +# include +#endif // defined(__ANDROID__) + +// Support move construction and assignment on compilers known to allow it. +#if !defined(ASIO_HAS_MOVE) +# if !defined(ASIO_DISABLE_MOVE) +# if defined(__clang__) +# if __has_feature(__cxx_rvalue_references__) +# define ASIO_HAS_MOVE 1 +# endif // __has_feature(__cxx_rvalue_references__) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 8)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_MOVE 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 8)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1700) +# define ASIO_HAS_MOVE 1 +# endif // (_MSC_VER >= 1700) +# endif // defined(ASIO_MSVC) +# if defined(__INTEL_CXX11_MODE__) +# if defined(__INTEL_COMPILER) && (__INTEL_COMPILER >= 1500) +# define ASIO_HAS_MOVE 1 +# endif // defined(__INTEL_COMPILER) && (__INTEL_COMPILER >= 1500) +# if defined(__ICL) && (__ICL >= 1500) +# define ASIO_HAS_MOVE 1 +# endif // defined(__ICL) && (__ICL >= 1500) +# endif // defined(__INTEL_CXX11_MODE__) +# endif // !defined(ASIO_DISABLE_MOVE) +#endif // !defined(ASIO_HAS_MOVE) + +// If ASIO_MOVE_CAST isn't defined, and move support is available, define +// * ASIO_MOVE_ARG, +// * ASIO_NONDEDUCED_MOVE_ARG, and +// * ASIO_MOVE_CAST +// to take advantage of rvalue references and perfect forwarding. +#if defined(ASIO_HAS_MOVE) && !defined(ASIO_MOVE_CAST) +# define ASIO_MOVE_ARG(type) type&& +# define ASIO_MOVE_ARG2(type1, type2) type1, type2&& +# define ASIO_NONDEDUCED_MOVE_ARG(type) type& +# define ASIO_MOVE_CAST(type) static_cast +# define ASIO_MOVE_CAST2(type1, type2) static_cast +# define ASIO_MOVE_OR_LVALUE(type) static_cast +# define ASIO_MOVE_OR_LVALUE_TYPE(type) type +#endif // defined(ASIO_HAS_MOVE) && !defined(ASIO_MOVE_CAST) + +// If ASIO_MOVE_CAST still isn't defined, default to a C++03-compatible +// implementation. Note that older g++ and MSVC versions don't like it when you +// pass a non-member function through a const reference, so for most compilers +// we'll play it safe and stick with the old approach of passing the handler by +// value. +#if !defined(ASIO_MOVE_CAST) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 1)) || (__GNUC__ > 4) +# define ASIO_MOVE_ARG(type) const type& +# else // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 1)) || (__GNUC__ > 4) +# define ASIO_MOVE_ARG(type) type +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 1)) || (__GNUC__ > 4) +# elif defined(ASIO_MSVC) +# if (_MSC_VER >= 1400) +# define ASIO_MOVE_ARG(type) const type& +# else // (_MSC_VER >= 1400) +# define ASIO_MOVE_ARG(type) type +# endif // (_MSC_VER >= 1400) +# else +# define ASIO_MOVE_ARG(type) type +# endif +# define ASIO_NONDEDUCED_MOVE_ARG(type) const type& +# define ASIO_MOVE_CAST(type) static_cast +# define ASIO_MOVE_CAST2(type1, type2) static_cast +# define ASIO_MOVE_OR_LVALUE(type) +# define ASIO_MOVE_OR_LVALUE_TYPE(type) type& +#endif // !defined(ASIO_MOVE_CAST) + +// Support variadic templates on compilers known to allow it. +#if !defined(ASIO_HAS_VARIADIC_TEMPLATES) +# if !defined(ASIO_DISABLE_VARIADIC_TEMPLATES) +# if defined(__clang__) +# if __has_feature(__cxx_variadic_templates__) +# define ASIO_HAS_VARIADIC_TEMPLATES 1 +# endif // __has_feature(__cxx_variadic_templates__) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 8)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_VARIADIC_TEMPLATES 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 8)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1900) +# define ASIO_HAS_VARIADIC_TEMPLATES 1 +# endif // (_MSC_VER >= 1900) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_VARIADIC_TEMPLATES) +#endif // !defined(ASIO_HAS_VARIADIC_TEMPLATES) +#if !defined(ASIO_ELLIPSIS) +# if defined(ASIO_HAS_VARIADIC_TEMPLATES) +# define ASIO_ELLIPSIS ... +# else // defined(ASIO_HAS_VARIADIC_TEMPLATES) +# define ASIO_ELLIPSIS +# endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) +#endif // !defined(ASIO_ELLIPSIS) + +// Support deleted functions on compilers known to allow it. +#if !defined(ASIO_DELETED) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_DELETED = delete +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(__clang__) +# if __has_feature(__cxx_deleted_functions__) +# define ASIO_DELETED = delete +# endif // __has_feature(__cxx_deleted_functions__) +# endif // defined(__clang__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1900) +# define ASIO_DELETED = delete +# endif // (_MSC_VER >= 1900) +# endif // defined(ASIO_MSVC) +# if !defined(ASIO_DELETED) +# define ASIO_DELETED +# endif // !defined(ASIO_DELETED) +#endif // !defined(ASIO_DELETED) + +// Support constexpr on compilers known to allow it. +#if !defined(ASIO_HAS_CONSTEXPR) +# if !defined(ASIO_DISABLE_CONSTEXPR) +# if defined(__clang__) +# if __has_feature(__cxx_constexpr__) +# define ASIO_HAS_CONSTEXPR 1 +# endif // __has_feature(__cxx_constexpr__) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 8)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_CONSTEXPR 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 8)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1900) +# define ASIO_HAS_CONSTEXPR 1 +# endif // (_MSC_VER >= 1900) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_CONSTEXPR) +#endif // !defined(ASIO_HAS_CONSTEXPR) +#if !defined(ASIO_CONSTEXPR) +# if defined(ASIO_HAS_CONSTEXPR) +# define ASIO_CONSTEXPR constexpr +# else // defined(ASIO_HAS_CONSTEXPR) +# define ASIO_CONSTEXPR +# endif // defined(ASIO_HAS_CONSTEXPR) +#endif // !defined(ASIO_CONSTEXPR) +#if !defined(ASIO_STATIC_CONSTEXPR) +# if defined(ASIO_HAS_CONSTEXPR) +# define ASIO_STATIC_CONSTEXPR(type, assignment) \ + static constexpr type assignment +# else // defined(ASIO_HAS_CONSTEXPR) +# define ASIO_STATIC_CONSTEXPR(type, assignment) \ + static const type assignment +# endif // defined(ASIO_HAS_CONSTEXPR) +#endif // !defined(ASIO_STATIC_CONSTEXPR) +#if !defined(ASIO_STATIC_CONSTEXPR_DEFAULT_INIT) +# if defined(ASIO_HAS_CONSTEXPR) +# if defined(__GNUC__) +# if (__GNUC__ >= 8) +# define ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(type, name) \ + static constexpr const type name{} +# else // (__GNUC__ >= 8) +# define ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(type, name) \ + static const type name +# endif // (__GNUC__ >= 8) +# elif defined(ASIO_MSVC) +# define ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(type, name) \ + static const type name +# else // defined(ASIO_MSVC) +# define ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(type, name) \ + static constexpr const type name{} +# endif // defined(ASIO_MSVC) +# else // defined(ASIO_HAS_CONSTEXPR) +# define ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(type, name) \ + static const type name +# endif // defined(ASIO_HAS_CONSTEXPR) +#endif // !defined(ASIO_STATIC_CONSTEXPR_DEFAULT_INIT) + +// Support noexcept on compilers known to allow it. +#if !defined(ASIO_HAS_NOEXCEPT) +# if !defined(ASIO_DISABLE_NOEXCEPT) +# if defined(ASIO_HAS_BOOST_CONFIG) && (BOOST_VERSION >= 105300) +# if !defined(BOOST_NO_NOEXCEPT) +# define ASIO_HAS_NOEXCEPT 1 +# endif // !defined(BOOST_NO_NOEXCEPT) +# define ASIO_NOEXCEPT BOOST_NOEXCEPT +# define ASIO_NOEXCEPT_OR_NOTHROW BOOST_NOEXCEPT_OR_NOTHROW +# define ASIO_NOEXCEPT_IF(c) BOOST_NOEXCEPT_IF(c) +# elif defined(__clang__) +# if __has_feature(__cxx_noexcept__) +# define ASIO_HAS_NOEXCEPT 1 +# endif // __has_feature(__cxx_noexcept__) +# elif defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_NOEXCEPT 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# elif defined(ASIO_MSVC) +# if (_MSC_VER >= 1900) +# define ASIO_HAS_NOEXCEPT 1 +# endif // (_MSC_VER >= 1900) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_NOEXCEPT) +# if !defined(ASIO_NOEXCEPT) +# endif // !defined(ASIO_NOEXCEPT) +# if !defined(ASIO_NOEXCEPT_OR_NOTHROW) +# endif // !defined(ASIO_NOEXCEPT_OR_NOTHROW) +#endif // !defined(ASIO_HAS_NOEXCEPT) +#if !defined(ASIO_NOEXCEPT) +# if defined(ASIO_HAS_NOEXCEPT) +# define ASIO_NOEXCEPT noexcept(true) +# else // defined(ASIO_HAS_NOEXCEPT) +# define ASIO_NOEXCEPT +# endif // defined(ASIO_HAS_NOEXCEPT) +#endif // !defined(ASIO_NOEXCEPT) +#if !defined(ASIO_NOEXCEPT_OR_NOTHROW) +# if defined(ASIO_HAS_NOEXCEPT) +# define ASIO_NOEXCEPT_OR_NOTHROW noexcept(true) +# else // defined(ASIO_HAS_NOEXCEPT) +# define ASIO_NOEXCEPT_OR_NOTHROW throw() +# endif // defined(ASIO_HAS_NOEXCEPT) +#endif // !defined(ASIO_NOEXCEPT_OR_NOTHROW) +#if !defined(ASIO_NOEXCEPT_IF) +# if defined(ASIO_HAS_NOEXCEPT) +# define ASIO_NOEXCEPT_IF(c) noexcept(c) +# else // defined(ASIO_HAS_NOEXCEPT) +# define ASIO_NOEXCEPT_IF(c) +# endif // defined(ASIO_HAS_NOEXCEPT) +#endif // !defined(ASIO_NOEXCEPT_IF) + +// Support automatic type deduction on compilers known to support it. +#if !defined(ASIO_HAS_DECLTYPE) +# if !defined(ASIO_DISABLE_DECLTYPE) +# if defined(__clang__) +# if __has_feature(__cxx_decltype__) +# define ASIO_HAS_DECLTYPE 1 +# endif // __has_feature(__cxx_decltype__) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 8)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_DECLTYPE 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 8)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1800) +# define ASIO_HAS_DECLTYPE 1 +# endif // (_MSC_VER >= 1800) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_DECLTYPE) +#endif // !defined(ASIO_HAS_DECLTYPE) + +// Support alias templates on compilers known to allow it. +#if !defined(ASIO_HAS_ALIAS_TEMPLATES) +# if !defined(ASIO_DISABLE_ALIAS_TEMPLATES) +# if defined(__clang__) +# if __has_feature(__cxx_alias_templates__) +# define ASIO_HAS_ALIAS_TEMPLATES 1 +# endif // __has_feature(__cxx_alias_templates__) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_ALIAS_TEMPLATES 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1900) +# define ASIO_HAS_ALIAS_TEMPLATES 1 +# endif // (_MSC_VER >= 1900) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_ALIAS_TEMPLATES) +#endif // !defined(ASIO_HAS_ALIAS_TEMPLATES) + +// Support return type deduction on compilers known to allow it. +#if !defined(ASIO_HAS_RETURN_TYPE_DEDUCTION) +# if !defined(ASIO_DISABLE_RETURN_TYPE_DEDUCTION) +# if defined(__clang__) +# if __has_feature(__cxx_return_type_deduction__) +# define ASIO_HAS_RETURN_TYPE_DEDUCTION 1 +# endif // __has_feature(__cxx_return_type_deduction__) +# elif (__cplusplus >= 201402) +# define ASIO_HAS_RETURN_TYPE_DEDUCTION 1 +# elif defined(__cpp_return_type_deduction) +# if (__cpp_return_type_deduction >= 201304) +# define ASIO_HAS_RETURN_TYPE_DEDUCTION 1 +# endif // (__cpp_return_type_deduction >= 201304) +# endif // defined(__cpp_return_type_deduction) +# endif // !defined(ASIO_DISABLE_RETURN_TYPE_DEDUCTION) +#endif // !defined(ASIO_HAS_RETURN_TYPE_DEDUCTION) + +// Support default function template arguments on compilers known to allow it. +#if !defined(ASIO_HAS_DEFAULT_FUNCTION_TEMPLATE_ARGUMENTS) +# if !defined(ASIO_DISABLE_DEFAULT_FUNCTION_TEMPLATE_ARGUMENTS) +# if (__cplusplus >= 201103) +# define ASIO_HAS_DEFAULT_FUNCTION_TEMPLATE_ARGUMENTS 1 +# endif // (__cplusplus >= 201103) +# endif // !defined(ASIO_DISABLE_DEFAULT_FUNCTION_TEMPLATE_ARGUMENTS) +#endif // !defined(ASIO_HAS_DEFAULT_FUNCTION_TEMPLATE_ARGUMENTS) + +// Support concepts on compilers known to allow them. +#if !defined(ASIO_HAS_CONCEPTS) +# if !defined(ASIO_DISABLE_CONCEPTS) +# if defined(__cpp_concepts) +# define ASIO_HAS_CONCEPTS 1 +# if (__cpp_concepts >= 201707) +# define ASIO_CONCEPT concept +# else // (__cpp_concepts >= 201707) +# define ASIO_CONCEPT concept bool +# endif // (__cpp_concepts >= 201707) +# endif // defined(__cpp_concepts) +# endif // !defined(ASIO_DISABLE_CONCEPTS) +#endif // !defined(ASIO_HAS_CONCEPTS) + +// Support template variables on compilers known to allow it. +#if !defined(ASIO_HAS_VARIABLE_TEMPLATES) +# if !defined(ASIO_DISABLE_VARIABLE_TEMPLATES) +# if defined(__clang__) +# if (__cplusplus >= 201402) +# if __has_feature(__cxx_variable_templates__) +# define ASIO_HAS_VARIABLE_TEMPLATES 1 +# endif // __has_feature(__cxx_variable_templates__) +# endif // (__cplusplus >= 201402) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if (__GNUC__ >= 6) +# if (__cplusplus >= 201402) +# define ASIO_HAS_VARIABLE_TEMPLATES 1 +# endif // (__cplusplus >= 201402) +# endif // (__GNUC__ >= 6) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1901) +# define ASIO_HAS_VARIABLE_TEMPLATES 1 +# endif // (_MSC_VER >= 1901) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_VARIABLE_TEMPLATES) +#endif // !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +// Support SFINAEd template variables on compilers known to allow it. +#if !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +# if !defined(ASIO_DISABLE_SFINAE_VARIABLE_TEMPLATES) +# if defined(__clang__) +# if (__cplusplus >= 201703) +# if __has_feature(__cxx_variable_templates__) +# define ASIO_HAS_SFINAE_VARIABLE_TEMPLATES 1 +# endif // __has_feature(__cxx_variable_templates__) +# endif // (__cplusplus >= 201703) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 8) && (__GNUC_MINOR__ >= 4)) || (__GNUC__ > 8) +# if (__cplusplus >= 201402) +# define ASIO_HAS_SFINAE_VARIABLE_TEMPLATES 1 +# endif // (__cplusplus >= 201402) +# endif // ((__GNUC__ == 8) && (__GNUC_MINOR__ >= 4)) || (__GNUC__ > 8) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1901) +# define ASIO_HAS_SFINAE_VARIABLE_TEMPLATES 1 +# endif // (_MSC_VER >= 1901) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_SFINAE_VARIABLE_TEMPLATES) +#endif // !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +// Support SFINAE use of constant expressions on compilers known to allow it. +#if !defined(ASIO_HAS_CONSTANT_EXPRESSION_SFINAE) +# if !defined(ASIO_DISABLE_CONSTANT_EXPRESSION_SFINAE) +# if defined(__clang__) +# if (__cplusplus >= 201402) +# define ASIO_HAS_CONSTANT_EXPRESSION_SFINAE 1 +# endif // (__cplusplus >= 201402) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if (__GNUC__ >= 7) +# if (__cplusplus >= 201402) +# define ASIO_HAS_CONSTANT_EXPRESSION_SFINAE 1 +# endif // (__cplusplus >= 201402) +# endif // (__GNUC__ >= 7) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1901) +# define ASIO_HAS_CONSTANT_EXPRESSION_SFINAE 1 +# endif // (_MSC_VER >= 1901) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_CONSTANT_EXPRESSION_SFINAE) +#endif // !defined(ASIO_HAS_CONSTANT_EXPRESSION_SFINAE) + +// Enable workarounds for lack of working expression SFINAE. +#if !defined(ASIO_HAS_WORKING_EXPRESSION_SFINAE) +# if !defined(ASIO_DISABLE_WORKING_EXPRESSION_SFINAE) +# if !defined(ASIO_MSVC) +# if (__cplusplus >= 201103) +# define ASIO_HAS_WORKING_EXPRESSION_SFINAE 1 +# endif // (__cplusplus >= 201103) +# endif // !defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_WORKING_EXPRESSION_SFINAE) +#endif // !defined(ASIO_HAS_WORKING_EXPRESSION_SFINAE) + +// Support ref-qualified functions on compilers known to allow it. +#if !defined(ASIO_HAS_REF_QUALIFIED_FUNCTIONS) +# if !defined(ASIO_DISABLE_REF_QUALIFIED_FUNCTIONS) +# if defined(__clang__) +# if __has_feature(__cxx_reference_qualified_functions__) +# define ASIO_HAS_REF_QUALIFIED_FUNCTIONS 1 +# endif // __has_feature(__cxx_reference_qualified_functions__) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 9)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_REF_QUALIFIED_FUNCTIONS 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 9)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1900) +# define ASIO_HAS_REF_QUALIFIED_FUNCTIONS 1 +# endif // (_MSC_VER >= 1900) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_REF_QUALIFIED_FUNCTIONS) +#endif // !defined(ASIO_HAS_REF_QUALIFIED_FUNCTIONS) +#if defined(ASIO_HAS_REF_QUALIFIED_FUNCTIONS) +# if !defined(ASIO_LVALUE_REF_QUAL) +# define ASIO_LVALUE_REF_QUAL & +# endif // !defined(ASIO_LVALUE_REF_QUAL) +# if !defined(ASIO_RVALUE_REF_QUAL) +# define ASIO_RVALUE_REF_QUAL && +# endif // !defined(ASIO_RVALUE_REF_QUAL) +#else // defined(ASIO_HAS_REF_QUALIFIED_FUNCTIONS) +# if !defined(ASIO_LVALUE_REF_QUAL) +# define ASIO_LVALUE_REF_QUAL +# endif // !defined(ASIO_LVALUE_REF_QUAL) +# if !defined(ASIO_RVALUE_REF_QUAL) +# define ASIO_RVALUE_REF_QUAL +# endif // !defined(ASIO_RVALUE_REF_QUAL) +#endif // defined(ASIO_HAS_REF_QUALIFIED_FUNCTIONS) + +// Standard library support for system errors. +#if !defined(ASIO_HAS_STD_SYSTEM_ERROR) +# if !defined(ASIO_DISABLE_STD_SYSTEM_ERROR) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_STD_SYSTEM_ERROR 1 +# elif (__cplusplus >= 201103) +# if __has_include() +# define ASIO_HAS_STD_SYSTEM_ERROR 1 +# endif // __has_include() +# endif // (__cplusplus >= 201103) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 6)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_STD_SYSTEM_ERROR 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 6)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1700) +# define ASIO_HAS_STD_SYSTEM_ERROR 1 +# endif // (_MSC_VER >= 1700) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_SYSTEM_ERROR) +#endif // !defined(ASIO_HAS_STD_SYSTEM_ERROR) + +// Compliant C++11 compilers put noexcept specifiers on error_category members. +#if !defined(ASIO_ERROR_CATEGORY_NOEXCEPT) +# if defined(ASIO_HAS_BOOST_CONFIG) && (BOOST_VERSION >= 105300) +# define ASIO_ERROR_CATEGORY_NOEXCEPT BOOST_NOEXCEPT +# elif defined(__clang__) +# if __has_feature(__cxx_noexcept__) +# define ASIO_ERROR_CATEGORY_NOEXCEPT noexcept(true) +# endif // __has_feature(__cxx_noexcept__) +# elif defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_ERROR_CATEGORY_NOEXCEPT noexcept(true) +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# elif defined(ASIO_MSVC) +# if (_MSC_VER >= 1900) +# define ASIO_ERROR_CATEGORY_NOEXCEPT noexcept(true) +# endif // (_MSC_VER >= 1900) +# endif // defined(ASIO_MSVC) +# if !defined(ASIO_ERROR_CATEGORY_NOEXCEPT) +# define ASIO_ERROR_CATEGORY_NOEXCEPT +# endif // !defined(ASIO_ERROR_CATEGORY_NOEXCEPT) +#endif // !defined(ASIO_ERROR_CATEGORY_NOEXCEPT) + +// Standard library support for arrays. +#if !defined(ASIO_HAS_STD_ARRAY) +# if !defined(ASIO_DISABLE_STD_ARRAY) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_STD_ARRAY 1 +# elif (__cplusplus >= 201103) +# if __has_include() +# define ASIO_HAS_STD_ARRAY 1 +# endif // __has_include() +# endif // (__cplusplus >= 201103) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 3)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_STD_ARRAY 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 3)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1600) +# define ASIO_HAS_STD_ARRAY 1 +# endif // (_MSC_VER >= 1600) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_ARRAY) +#endif // !defined(ASIO_HAS_STD_ARRAY) + +// Standard library support for shared_ptr and weak_ptr. +#if !defined(ASIO_HAS_STD_SHARED_PTR) +# if !defined(ASIO_DISABLE_STD_SHARED_PTR) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_STD_SHARED_PTR 1 +# elif (__cplusplus >= 201103) +# define ASIO_HAS_STD_SHARED_PTR 1 +# endif // (__cplusplus >= 201103) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 3)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_STD_SHARED_PTR 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 3)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1600) +# define ASIO_HAS_STD_SHARED_PTR 1 +# endif // (_MSC_VER >= 1600) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_SHARED_PTR) +#endif // !defined(ASIO_HAS_STD_SHARED_PTR) + +// Standard library support for allocator_arg_t. +#if !defined(ASIO_HAS_STD_ALLOCATOR_ARG) +# if !defined(ASIO_DISABLE_STD_ALLOCATOR_ARG) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_STD_ALLOCATOR_ARG 1 +# elif (__cplusplus >= 201103) +# define ASIO_HAS_STD_ALLOCATOR_ARG 1 +# endif // (__cplusplus >= 201103) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 6)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_STD_ALLOCATOR_ARG 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 6)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1600) +# define ASIO_HAS_STD_ALLOCATOR_ARG 1 +# endif // (_MSC_VER >= 1600) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_ALLOCATOR_ARG) +#endif // !defined(ASIO_HAS_STD_ALLOCATOR_ARG) + +// Standard library support for atomic operations. +#if !defined(ASIO_HAS_STD_ATOMIC) +# if !defined(ASIO_DISABLE_STD_ATOMIC) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_STD_ATOMIC 1 +# elif (__cplusplus >= 201103) +# if __has_include() +# define ASIO_HAS_STD_ATOMIC 1 +# endif // __has_include() +# elif defined(__apple_build_version__) && defined(_LIBCPP_VERSION) +# if (__clang_major__ >= 10) +# if __has_include() +# define ASIO_HAS_STD_ATOMIC 1 +# endif // __has_include() +# endif // (__clang_major__ >= 10) +# endif // defined(__apple_build_version__) && defined(_LIBCPP_VERSION) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_STD_ATOMIC 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1700) +# define ASIO_HAS_STD_ATOMIC 1 +# endif // (_MSC_VER >= 1700) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_ATOMIC) +#endif // !defined(ASIO_HAS_STD_ATOMIC) + +// Standard library support for chrono. Some standard libraries (such as the +// libstdc++ shipped with gcc 4.6) provide monotonic_clock as per early C++0x +// drafts, rather than the eventually standardised name of steady_clock. +#if !defined(ASIO_HAS_STD_CHRONO) +# if !defined(ASIO_DISABLE_STD_CHRONO) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_STD_CHRONO 1 +# elif (__cplusplus >= 201103) +# if __has_include() +# define ASIO_HAS_STD_CHRONO 1 +# endif // __has_include() +# endif // (__cplusplus >= 201103) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 6)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_STD_CHRONO 1 +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ == 6)) +# define ASIO_HAS_STD_CHRONO_MONOTONIC_CLOCK 1 +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ == 6)) +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 6)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1700) +# define ASIO_HAS_STD_CHRONO 1 +# endif // (_MSC_VER >= 1700) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_CHRONO) +#endif // !defined(ASIO_HAS_STD_CHRONO) + +// Boost support for chrono. +#if !defined(ASIO_HAS_BOOST_CHRONO) +# if !defined(ASIO_DISABLE_BOOST_CHRONO) +# if defined(ASIO_HAS_BOOST_CONFIG) && (BOOST_VERSION >= 104700) +# define ASIO_HAS_BOOST_CHRONO 1 +# endif // defined(ASIO_HAS_BOOST_CONFIG) && (BOOST_VERSION >= 104700) +# endif // !defined(ASIO_DISABLE_BOOST_CHRONO) +#endif // !defined(ASIO_HAS_BOOST_CHRONO) + +// Some form of chrono library is available. +#if !defined(ASIO_HAS_CHRONO) +# if defined(ASIO_HAS_STD_CHRONO) \ + || defined(ASIO_HAS_BOOST_CHRONO) +# define ASIO_HAS_CHRONO 1 +# endif // defined(ASIO_HAS_STD_CHRONO) + // || defined(ASIO_HAS_BOOST_CHRONO) +#endif // !defined(ASIO_HAS_CHRONO) + +// Boost support for the DateTime library. +#if !defined(ASIO_HAS_BOOST_DATE_TIME) +# if !defined(ASIO_DISABLE_BOOST_DATE_TIME) +# define ASIO_HAS_BOOST_DATE_TIME 1 +# endif // !defined(ASIO_DISABLE_BOOST_DATE_TIME) +#endif // !defined(ASIO_HAS_BOOST_DATE_TIME) + +// Standard library support for addressof. +#if !defined(ASIO_HAS_STD_ADDRESSOF) +# if !defined(ASIO_DISABLE_STD_ADDRESSOF) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_STD_ADDRESSOF 1 +# elif (__cplusplus >= 201103) +# define ASIO_HAS_STD_ADDRESSOF 1 +# endif // (__cplusplus >= 201103) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 6)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_STD_ADDRESSOF 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 6)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1700) +# define ASIO_HAS_STD_ADDRESSOF 1 +# endif // (_MSC_VER >= 1700) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_ADDRESSOF) +#endif // !defined(ASIO_HAS_STD_ADDRESSOF) + +// Standard library support for the function class. +#if !defined(ASIO_HAS_STD_FUNCTION) +# if !defined(ASIO_DISABLE_STD_FUNCTION) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_STD_FUNCTION 1 +# elif (__cplusplus >= 201103) +# define ASIO_HAS_STD_FUNCTION 1 +# endif // (__cplusplus >= 201103) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 5)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_STD_FUNCTION 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 5)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1700) +# define ASIO_HAS_STD_FUNCTION 1 +# endif // (_MSC_VER >= 1700) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_FUNCTION) +#endif // !defined(ASIO_HAS_STD_FUNCTION) + +// Standard library support for type traits. +#if !defined(ASIO_HAS_STD_TYPE_TRAITS) +# if !defined(ASIO_DISABLE_STD_TYPE_TRAITS) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_STD_TYPE_TRAITS 1 +# elif (__cplusplus >= 201103) +# if __has_include() +# define ASIO_HAS_STD_TYPE_TRAITS 1 +# endif // __has_include() +# endif // (__cplusplus >= 201103) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 8)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_STD_TYPE_TRAITS 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 8)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1700) +# define ASIO_HAS_STD_TYPE_TRAITS 1 +# endif // (_MSC_VER >= 1700) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_TYPE_TRAITS) +#endif // !defined(ASIO_HAS_STD_TYPE_TRAITS) + +// Standard library support for the nullptr_t type. +#if !defined(ASIO_HAS_NULLPTR) +# if !defined(ASIO_DISABLE_NULLPTR) +# if defined(__clang__) +# if __has_feature(__cxx_nullptr__) +# define ASIO_HAS_NULLPTR 1 +# endif // __has_feature(__cxx_nullptr__) +# elif defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 6)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_NULLPTR 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 6)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1700) +# define ASIO_HAS_NULLPTR 1 +# endif // (_MSC_VER >= 1700) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_NULLPTR) +#endif // !defined(ASIO_HAS_NULLPTR) + +// Standard library support for the C++11 allocator additions. +#if !defined(ASIO_HAS_CXX11_ALLOCATORS) +# if !defined(ASIO_DISABLE_CXX11_ALLOCATORS) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_CXX11_ALLOCATORS 1 +# elif (__cplusplus >= 201103) +# define ASIO_HAS_CXX11_ALLOCATORS 1 +# endif // (__cplusplus >= 201103) +# elif defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_CXX11_ALLOCATORS 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1800) +# define ASIO_HAS_CXX11_ALLOCATORS 1 +# endif // (_MSC_VER >= 1800) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_CXX11_ALLOCATORS) +#endif // !defined(ASIO_HAS_CXX11_ALLOCATORS) + +// Standard library support for the cstdint header. +#if !defined(ASIO_HAS_CSTDINT) +# if !defined(ASIO_DISABLE_CSTDINT) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_CSTDINT 1 +# elif (__cplusplus >= 201103) +# define ASIO_HAS_CSTDINT 1 +# endif // (__cplusplus >= 201103) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 5)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_CSTDINT 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 5)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1700) +# define ASIO_HAS_CSTDINT 1 +# endif // (_MSC_VER >= 1700) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_CSTDINT) +#endif // !defined(ASIO_HAS_CSTDINT) + +// Standard library support for the thread class. +#if !defined(ASIO_HAS_STD_THREAD) +# if !defined(ASIO_DISABLE_STD_THREAD) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_STD_THREAD 1 +# elif (__cplusplus >= 201103) +# if __has_include() +# define ASIO_HAS_STD_THREAD 1 +# endif // __has_include() +# endif // (__cplusplus >= 201103) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_STD_THREAD 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1700) +# define ASIO_HAS_STD_THREAD 1 +# endif // (_MSC_VER >= 1700) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_THREAD) +#endif // !defined(ASIO_HAS_STD_THREAD) + +// Standard library support for the mutex and condition variable classes. +#if !defined(ASIO_HAS_STD_MUTEX_AND_CONDVAR) +# if !defined(ASIO_DISABLE_STD_MUTEX_AND_CONDVAR) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_STD_MUTEX_AND_CONDVAR 1 +# elif (__cplusplus >= 201103) +# if __has_include() +# define ASIO_HAS_STD_MUTEX_AND_CONDVAR 1 +# endif // __has_include() +# endif // (__cplusplus >= 201103) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_STD_MUTEX_AND_CONDVAR 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1700) +# define ASIO_HAS_STD_MUTEX_AND_CONDVAR 1 +# endif // (_MSC_VER >= 1700) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_MUTEX_AND_CONDVAR) +#endif // !defined(ASIO_HAS_STD_MUTEX_AND_CONDVAR) + +// Standard library support for the call_once function. +#if !defined(ASIO_HAS_STD_CALL_ONCE) +# if !defined(ASIO_DISABLE_STD_CALL_ONCE) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_STD_CALL_ONCE 1 +# elif (__cplusplus >= 201103) +# if __has_include() +# define ASIO_HAS_STD_CALL_ONCE 1 +# endif // __has_include() +# endif // (__cplusplus >= 201103) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_STD_CALL_ONCE 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1700) +# define ASIO_HAS_STD_CALL_ONCE 1 +# endif // (_MSC_VER >= 1700) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_CALL_ONCE) +#endif // !defined(ASIO_HAS_STD_CALL_ONCE) + +// Standard library support for futures. +#if !defined(ASIO_HAS_STD_FUTURE) +# if !defined(ASIO_DISABLE_STD_FUTURE) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_STD_FUTURE 1 +# elif (__cplusplus >= 201103) +# if __has_include() +# define ASIO_HAS_STD_FUTURE 1 +# endif // __has_include() +# endif // (__cplusplus >= 201103) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_STD_FUTURE 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1700) +# define ASIO_HAS_STD_FUTURE 1 +# endif // (_MSC_VER >= 1700) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_FUTURE) +#endif // !defined(ASIO_HAS_STD_FUTURE) + +// Standard library support for std::string_view. +#if !defined(ASIO_HAS_STD_STRING_VIEW) +# if !defined(ASIO_DISABLE_STD_STRING_VIEW) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# if (__cplusplus >= 201402) +# if __has_include() +# define ASIO_HAS_STD_STRING_VIEW 1 +# endif // __has_include() +# endif // (__cplusplus >= 201402) +# else // defined(ASIO_HAS_CLANG_LIBCXX) +# if (__cplusplus >= 201703) +# if __has_include() +# define ASIO_HAS_STD_STRING_VIEW 1 +# endif // __has_include() +# endif // (__cplusplus >= 201703) +# endif // defined(ASIO_HAS_CLANG_LIBCXX) +# elif defined(__GNUC__) +# if (__GNUC__ >= 7) +# if (__cplusplus >= 201703) +# define ASIO_HAS_STD_STRING_VIEW 1 +# endif // (__cplusplus >= 201703) +# endif // (__GNUC__ >= 7) +# elif defined(ASIO_MSVC) +# if (_MSC_VER >= 1910 && _MSVC_LANG >= 201703) +# define ASIO_HAS_STD_STRING_VIEW 1 +# endif // (_MSC_VER >= 1910 && _MSVC_LANG >= 201703) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_STRING_VIEW) +#endif // !defined(ASIO_HAS_STD_STRING_VIEW) + +// Standard library support for std::experimental::string_view. +#if !defined(ASIO_HAS_STD_EXPERIMENTAL_STRING_VIEW) +# if !defined(ASIO_DISABLE_STD_EXPERIMENTAL_STRING_VIEW) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# if (_LIBCPP_VERSION < 7000) +# if (__cplusplus >= 201402) +# if __has_include() +# define ASIO_HAS_STD_EXPERIMENTAL_STRING_VIEW 1 +# endif // __has_include() +# endif // (__cplusplus >= 201402) +# endif // (_LIBCPP_VERSION < 7000) +# else // defined(ASIO_HAS_CLANG_LIBCXX) +# if (__cplusplus >= 201402) +# if __has_include() +# define ASIO_HAS_STD_EXPERIMENTAL_STRING_VIEW 1 +# endif // __has_include() +# endif // (__cplusplus >= 201402) +# endif // // defined(ASIO_HAS_CLANG_LIBCXX) +# endif // defined(__clang__) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 9)) || (__GNUC__ > 4) +# if (__cplusplus >= 201402) +# define ASIO_HAS_STD_EXPERIMENTAL_STRING_VIEW 1 +# endif // (__cplusplus >= 201402) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 9)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# endif // !defined(ASIO_DISABLE_STD_EXPERIMENTAL_STRING_VIEW) +#endif // !defined(ASIO_HAS_STD_EXPERIMENTAL_STRING_VIEW) + +// Standard library has a string_view that we can use. +#if !defined(ASIO_HAS_STRING_VIEW) +# if !defined(ASIO_DISABLE_STRING_VIEW) +# if defined(ASIO_HAS_STD_STRING_VIEW) +# define ASIO_HAS_STRING_VIEW 1 +# elif defined(ASIO_HAS_STD_EXPERIMENTAL_STRING_VIEW) +# define ASIO_HAS_STRING_VIEW 1 +# endif // defined(ASIO_HAS_STD_EXPERIMENTAL_STRING_VIEW) +# endif // !defined(ASIO_DISABLE_STRING_VIEW) +#endif // !defined(ASIO_HAS_STRING_VIEW) + +// Standard library support for iostream move construction and assignment. +#if !defined(ASIO_HAS_STD_IOSTREAM_MOVE) +# if !defined(ASIO_DISABLE_STD_IOSTREAM_MOVE) +# if defined(__GNUC__) +# if (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_STD_IOSTREAM_MOVE 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1700) +# define ASIO_HAS_STD_IOSTREAM_MOVE 1 +# endif // (_MSC_VER >= 1700) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_IOSTREAM_MOVE) +#endif // !defined(ASIO_HAS_STD_IOSTREAM_MOVE) + +// Standard library has invoke_result (which supersedes result_of). +#if !defined(ASIO_HAS_STD_INVOKE_RESULT) +# if !defined(ASIO_DISABLE_STD_INVOKE_RESULT) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1911 && _MSVC_LANG >= 201703) +# define ASIO_HAS_STD_INVOKE_RESULT 1 +# endif // (_MSC_VER >= 1911 && _MSVC_LANG >= 201703) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_INVOKE_RESULT) +#endif // !defined(ASIO_HAS_STD_INVOKE_RESULT) + +// Standard library support for std::exception_ptr and std::current_exception. +#if !defined(ASIO_HAS_STD_EXCEPTION_PTR) +# if !defined(ASIO_DISABLE_STD_EXCEPTION_PTR) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_STD_EXCEPTION_PTR 1 +# elif (__cplusplus >= 201103) +# define ASIO_HAS_STD_EXCEPTION_PTR 1 +# endif // (__cplusplus >= 201103) +# elif defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_STD_EXCEPTION_PTR 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1800) +# define ASIO_HAS_STD_EXCEPTION_PTR 1 +# endif // (_MSC_VER >= 1800) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_EXCEPTION_PTR) +#endif // !defined(ASIO_HAS_STD_EXCEPTION_PTR) + +// Standard library support for std::nested_exception. +#if !defined(ASIO_HAS_STD_NESTED_EXCEPTION) +# if !defined(ASIO_DISABLE_STD_NESTED_EXCEPTION) +# if defined(__clang__) +# if defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_STD_NESTED_EXCEPTION 1 +# elif (__cplusplus >= 201103) +# define ASIO_HAS_STD_NESTED_EXCEPTION 1 +# endif // (__cplusplus >= 201103) +# elif defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# if (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_HAS_STD_NESTED_EXCEPTION 1 +# endif // (__cplusplus >= 201103) || defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 7)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1900) +# define ASIO_HAS_STD_NESTED_EXCEPTION 1 +# endif // (_MSC_VER >= 1900) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_NESTED_EXCEPTION) +#endif // !defined(ASIO_HAS_STD_NESTED_EXCEPTION) + +// Standard library support for std::any. +#if !defined(ASIO_HAS_STD_ANY) +# if !defined(ASIO_DISABLE_STD_ANY) +# if defined(__clang__) +# if (__cplusplus >= 201703) +# if __has_include() +# define ASIO_HAS_STD_ANY 1 +# endif // __has_include() +# endif // (__cplusplus >= 201703) +# elif defined(__GNUC__) +# if (__GNUC__ >= 7) +# if (__cplusplus >= 201703) +# define ASIO_HAS_STD_ANY 1 +# endif // (__cplusplus >= 201703) +# endif // (__GNUC__ >= 7) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1910) && (_MSVC_LANG >= 201703) +# define ASIO_HAS_STD_ANY 1 +# endif // (_MSC_VER >= 1910) && (_MSVC_LANG >= 201703) +# endif // defined(ASIO_MSVC) +# endif // !defined(ASIO_DISABLE_STD_ANY) +#endif // !defined(ASIO_HAS_STD_ANY) + +// Standard library support for std::source_location. +#if !defined(ASIO_HAS_STD_SOURCE_LOCATION) +# if !defined(ASIO_DISABLE_STD_SOURCE_LOCATION) +// ... +# endif // !defined(ASIO_DISABLE_STD_SOURCE_LOCATION) +#endif // !defined(ASIO_HAS_STD_SOURCE_LOCATION) + +// Standard library support for std::experimental::source_location. +#if !defined(ASIO_HAS_STD_EXPERIMENTAL_SOURCE_LOCATION) +# if !defined(ASIO_DISABLE_STD_EXPERIMENTAL_SOURCE_LOCATION) +# if defined(__GNUC__) +# if (__cplusplus >= 201709) +# if __has_include() +# define ASIO_HAS_STD_EXPERIMENTAL_SOURCE_LOCATION 1 +# endif // __has_include() +# endif // (__cplusplus >= 201709) +# endif // defined(__GNUC__) +# endif // !defined(ASIO_DISABLE_STD_EXPERIMENTAL_SOURCE_LOCATION) +#endif // !defined(ASIO_HAS_STD_EXPERIMENTAL_SOURCE_LOCATION) + +// Standard library has a source_location that we can use. +#if !defined(ASIO_HAS_SOURCE_LOCATION) +# if !defined(ASIO_DISABLE_SOURCE_LOCATION) +# if defined(ASIO_HAS_STD_SOURCE_LOCATION) +# define ASIO_HAS_SOURCE_LOCATION 1 +# elif defined(ASIO_HAS_STD_EXPERIMENTAL_SOURCE_LOCATION) +# define ASIO_HAS_SOURCE_LOCATION 1 +# endif // defined(ASIO_HAS_STD_EXPERIMENTAL_SOURCE_LOCATION) +# endif // !defined(ASIO_DISABLE_SOURCE_LOCATION) +#endif // !defined(ASIO_HAS_SOURCE_LOCATION) + +// Windows App target. Windows but with a limited API. +#if !defined(ASIO_WINDOWS_APP) +# if defined(_WIN32_WINNT) && (_WIN32_WINNT >= 0x0603) +# include +# if (WINAPI_FAMILY_PARTITION(WINAPI_PARTITION_APP) \ + || WINAPI_FAMILY_PARTITION(WINAPI_PARTITION_TV_TITLE)) \ + && !WINAPI_FAMILY_PARTITION(WINAPI_PARTITION_DESKTOP) +# define ASIO_WINDOWS_APP 1 +# endif // WINAPI_FAMILY_PARTITION(WINAPI_PARTITION_APP) + // && !WINAPI_FAMILY_PARTITION(WINAPI_PARTITION_DESKTOP) +# endif // defined(_WIN32_WINNT) && (_WIN32_WINNT >= 0x0603) +#endif // !defined(ASIO_WINDOWS_APP) + +// Legacy WinRT target. Windows App is preferred. +#if !defined(ASIO_WINDOWS_RUNTIME) +# if !defined(ASIO_WINDOWS_APP) +# if defined(__cplusplus_winrt) +# include +# if WINAPI_FAMILY_PARTITION(WINAPI_PARTITION_APP) \ + && !WINAPI_FAMILY_PARTITION(WINAPI_PARTITION_DESKTOP) +# define ASIO_WINDOWS_RUNTIME 1 +# endif // WINAPI_FAMILY_PARTITION(WINAPI_PARTITION_APP) + // && !WINAPI_FAMILY_PARTITION(WINAPI_PARTITION_DESKTOP) +# endif // defined(__cplusplus_winrt) +# endif // !defined(ASIO_WINDOWS_APP) +#endif // !defined(ASIO_WINDOWS_RUNTIME) + +// Windows target. Excludes WinRT but includes Windows App targets. +#if !defined(ASIO_WINDOWS) +# if !defined(ASIO_WINDOWS_RUNTIME) +# if defined(ASIO_HAS_BOOST_CONFIG) && defined(BOOST_WINDOWS) +# define ASIO_WINDOWS 1 +# elif defined(WIN32) || defined(_WIN32) || defined(__WIN32__) +# define ASIO_WINDOWS 1 +# elif defined(ASIO_WINDOWS_APP) +# define ASIO_WINDOWS 1 +# endif // defined(ASIO_HAS_BOOST_CONFIG) && defined(BOOST_WINDOWS) +# endif // !defined(ASIO_WINDOWS_RUNTIME) +#endif // !defined(ASIO_WINDOWS) + +// Windows: target OS version. +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) +# if !defined(_WIN32_WINNT) && !defined(_WIN32_WINDOWS) +# if defined(_MSC_VER) || (defined(__BORLANDC__) && !defined(__clang__)) +# pragma message( \ + "Please define _WIN32_WINNT or _WIN32_WINDOWS appropriately. For example:\n"\ + "- add -D_WIN32_WINNT=0x0601 to the compiler command line; or\n"\ + "- add _WIN32_WINNT=0x0601 to your project's Preprocessor Definitions.\n"\ + "Assuming _WIN32_WINNT=0x0601 (i.e. Windows 7 target).") +# else // defined(_MSC_VER) || (defined(__BORLANDC__) && !defined(__clang__)) +# warning Please define _WIN32_WINNT or _WIN32_WINDOWS appropriately. +# warning For example, add -D_WIN32_WINNT=0x0601 to the compiler command line. +# warning Assuming _WIN32_WINNT=0x0601 (i.e. Windows 7 target). +# endif // defined(_MSC_VER) || (defined(__BORLANDC__) && !defined(__clang__)) +# define _WIN32_WINNT 0x0601 +# endif // !defined(_WIN32_WINNT) && !defined(_WIN32_WINDOWS) +# if defined(_MSC_VER) +# if defined(_WIN32) && !defined(WIN32) +# if !defined(_WINSOCK2API_) +# define WIN32 // Needed for correct types in winsock2.h +# else // !defined(_WINSOCK2API_) +# error Please define the macro WIN32 in your compiler options +# endif // !defined(_WINSOCK2API_) +# endif // defined(_WIN32) && !defined(WIN32) +# endif // defined(_MSC_VER) +# if defined(__BORLANDC__) +# if defined(__WIN32__) && !defined(WIN32) +# if !defined(_WINSOCK2API_) +# define WIN32 // Needed for correct types in winsock2.h +# else // !defined(_WINSOCK2API_) +# error Please define the macro WIN32 in your compiler options +# endif // !defined(_WINSOCK2API_) +# endif // defined(__WIN32__) && !defined(WIN32) +# endif // defined(__BORLANDC__) +# if defined(__CYGWIN__) +# if !defined(__USE_W32_SOCKETS) +# error You must add -D__USE_W32_SOCKETS to your compiler options. +# endif // !defined(__USE_W32_SOCKETS) +# endif // defined(__CYGWIN__) +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +// Windows: minimise header inclusion. +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) +# if !defined(ASIO_NO_WIN32_LEAN_AND_MEAN) +# if !defined(WIN32_LEAN_AND_MEAN) +# define WIN32_LEAN_AND_MEAN +# endif // !defined(WIN32_LEAN_AND_MEAN) +# endif // !defined(ASIO_NO_WIN32_LEAN_AND_MEAN) +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +// Windows: suppress definition of "min" and "max" macros. +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) +# if !defined(ASIO_NO_NOMINMAX) +# if !defined(NOMINMAX) +# define NOMINMAX 1 +# endif // !defined(NOMINMAX) +# endif // !defined(ASIO_NO_NOMINMAX) +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +// Windows: IO Completion Ports. +#if !defined(ASIO_HAS_IOCP) +# if defined(ASIO_WINDOWS) || defined(__CYGWIN__) +# if defined(_WIN32_WINNT) && (_WIN32_WINNT >= 0x0400) +# if !defined(UNDER_CE) && !defined(ASIO_WINDOWS_APP) +# if !defined(ASIO_DISABLE_IOCP) +# define ASIO_HAS_IOCP 1 +# endif // !defined(ASIO_DISABLE_IOCP) +# endif // !defined(UNDER_CE) && !defined(ASIO_WINDOWS_APP) +# endif // defined(_WIN32_WINNT) && (_WIN32_WINNT >= 0x0400) +# endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +#endif // !defined(ASIO_HAS_IOCP) + +// On POSIX (and POSIX-like) platforms we need to include unistd.h in order to +// get access to the various platform feature macros, e.g. to be able to test +// for threads support. +#if !defined(ASIO_HAS_UNISTD_H) +# if !defined(ASIO_HAS_BOOST_CONFIG) +# if defined(unix) \ + || defined(__unix) \ + || defined(_XOPEN_SOURCE) \ + || defined(_POSIX_SOURCE) \ + || (defined(__MACH__) && defined(__APPLE__)) \ + || defined(__FreeBSD__) \ + || defined(__NetBSD__) \ + || defined(__OpenBSD__) \ + || defined(__linux__) \ + || defined(__HAIKU__) +# define ASIO_HAS_UNISTD_H 1 +# endif +# endif // !defined(ASIO_HAS_BOOST_CONFIG) +#endif // !defined(ASIO_HAS_UNISTD_H) +#if defined(ASIO_HAS_UNISTD_H) +# include +#endif // defined(ASIO_HAS_UNISTD_H) + +// Linux: epoll, eventfd and timerfd. +#if defined(__linux__) +# include +# if !defined(ASIO_HAS_EPOLL) +# if !defined(ASIO_DISABLE_EPOLL) +# if LINUX_VERSION_CODE >= KERNEL_VERSION(2,5,45) +# define ASIO_HAS_EPOLL 1 +# endif // LINUX_VERSION_CODE >= KERNEL_VERSION(2,5,45) +# endif // !defined(ASIO_DISABLE_EPOLL) +# endif // !defined(ASIO_HAS_EPOLL) +# if !defined(ASIO_HAS_EVENTFD) +# if !defined(ASIO_DISABLE_EVENTFD) +# if LINUX_VERSION_CODE >= KERNEL_VERSION(2,6,22) +# define ASIO_HAS_EVENTFD 1 +# endif // LINUX_VERSION_CODE >= KERNEL_VERSION(2,6,22) +# endif // !defined(ASIO_DISABLE_EVENTFD) +# endif // !defined(ASIO_HAS_EVENTFD) +# if !defined(ASIO_HAS_TIMERFD) +# if defined(ASIO_HAS_EPOLL) +# if (__GLIBC__ > 2) || (__GLIBC__ == 2 && __GLIBC_MINOR__ >= 8) +# define ASIO_HAS_TIMERFD 1 +# endif // (__GLIBC__ > 2) || (__GLIBC__ == 2 && __GLIBC_MINOR__ >= 8) +# endif // defined(ASIO_HAS_EPOLL) +# endif // !defined(ASIO_HAS_TIMERFD) +#endif // defined(__linux__) + +// Mac OS X, FreeBSD, NetBSD, OpenBSD: kqueue. +#if (defined(__MACH__) && defined(__APPLE__)) \ + || defined(__FreeBSD__) \ + || defined(__NetBSD__) \ + || defined(__OpenBSD__) +# if !defined(ASIO_HAS_KQUEUE) +# if !defined(ASIO_DISABLE_KQUEUE) +# define ASIO_HAS_KQUEUE 1 +# endif // !defined(ASIO_DISABLE_KQUEUE) +# endif // !defined(ASIO_HAS_KQUEUE) +#endif // (defined(__MACH__) && defined(__APPLE__)) + // || defined(__FreeBSD__) + // || defined(__NetBSD__) + // || defined(__OpenBSD__) + +// Solaris: /dev/poll. +#if defined(__sun) +# if !defined(ASIO_HAS_DEV_POLL) +# if !defined(ASIO_DISABLE_DEV_POLL) +# define ASIO_HAS_DEV_POLL 1 +# endif // !defined(ASIO_DISABLE_DEV_POLL) +# endif // !defined(ASIO_HAS_DEV_POLL) +#endif // defined(__sun) + +// Serial ports. +#if !defined(ASIO_HAS_SERIAL_PORT) +# if defined(ASIO_HAS_IOCP) \ + || !defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_RUNTIME) \ + && !defined(__CYGWIN__) +# if !defined(__SYMBIAN32__) +# if !defined(ASIO_DISABLE_SERIAL_PORT) +# define ASIO_HAS_SERIAL_PORT 1 +# endif // !defined(ASIO_DISABLE_SERIAL_PORT) +# endif // !defined(__SYMBIAN32__) +# endif // defined(ASIO_HAS_IOCP) + // || !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) +#endif // !defined(ASIO_HAS_SERIAL_PORT) + +// Windows: stream handles. +#if !defined(ASIO_HAS_WINDOWS_STREAM_HANDLE) +# if !defined(ASIO_DISABLE_WINDOWS_STREAM_HANDLE) +# if defined(ASIO_HAS_IOCP) +# define ASIO_HAS_WINDOWS_STREAM_HANDLE 1 +# endif // defined(ASIO_HAS_IOCP) +# endif // !defined(ASIO_DISABLE_WINDOWS_STREAM_HANDLE) +#endif // !defined(ASIO_HAS_WINDOWS_STREAM_HANDLE) + +// Windows: random access handles. +#if !defined(ASIO_HAS_WINDOWS_RANDOM_ACCESS_HANDLE) +# if !defined(ASIO_DISABLE_WINDOWS_RANDOM_ACCESS_HANDLE) +# if defined(ASIO_HAS_IOCP) +# define ASIO_HAS_WINDOWS_RANDOM_ACCESS_HANDLE 1 +# endif // defined(ASIO_HAS_IOCP) +# endif // !defined(ASIO_DISABLE_WINDOWS_RANDOM_ACCESS_HANDLE) +#endif // !defined(ASIO_HAS_WINDOWS_RANDOM_ACCESS_HANDLE) + +// Windows: object handles. +#if !defined(ASIO_HAS_WINDOWS_OBJECT_HANDLE) +# if !defined(ASIO_DISABLE_WINDOWS_OBJECT_HANDLE) +# if defined(ASIO_WINDOWS) || defined(__CYGWIN__) +# if !defined(UNDER_CE) && !defined(ASIO_WINDOWS_APP) +# define ASIO_HAS_WINDOWS_OBJECT_HANDLE 1 +# endif // !defined(UNDER_CE) && !defined(ASIO_WINDOWS_APP) +# endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +# endif // !defined(ASIO_DISABLE_WINDOWS_OBJECT_HANDLE) +#endif // !defined(ASIO_HAS_WINDOWS_OBJECT_HANDLE) + +// Windows: OVERLAPPED wrapper. +#if !defined(ASIO_HAS_WINDOWS_OVERLAPPED_PTR) +# if !defined(ASIO_DISABLE_WINDOWS_OVERLAPPED_PTR) +# if defined(ASIO_HAS_IOCP) +# define ASIO_HAS_WINDOWS_OVERLAPPED_PTR 1 +# endif // defined(ASIO_HAS_IOCP) +# endif // !defined(ASIO_DISABLE_WINDOWS_OVERLAPPED_PTR) +#endif // !defined(ASIO_HAS_WINDOWS_OVERLAPPED_PTR) + +// POSIX: stream-oriented file descriptors. +#if !defined(ASIO_HAS_POSIX_STREAM_DESCRIPTOR) +# if !defined(ASIO_DISABLE_POSIX_STREAM_DESCRIPTOR) +# if !defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_RUNTIME) \ + && !defined(__CYGWIN__) +# define ASIO_HAS_POSIX_STREAM_DESCRIPTOR 1 +# endif // !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) +# endif // !defined(ASIO_DISABLE_POSIX_STREAM_DESCRIPTOR) +#endif // !defined(ASIO_HAS_POSIX_STREAM_DESCRIPTOR) + +// UNIX domain sockets. +#if !defined(ASIO_HAS_LOCAL_SOCKETS) +# if !defined(ASIO_DISABLE_LOCAL_SOCKETS) +# if !defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_RUNTIME) \ + && !defined(__CYGWIN__) +# define ASIO_HAS_LOCAL_SOCKETS 1 +# endif // !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) +# endif // !defined(ASIO_DISABLE_LOCAL_SOCKETS) +#endif // !defined(ASIO_HAS_LOCAL_SOCKETS) + +// Can use sigaction() instead of signal(). +#if !defined(ASIO_HAS_SIGACTION) +# if !defined(ASIO_DISABLE_SIGACTION) +# if !defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_RUNTIME) \ + && !defined(__CYGWIN__) +# define ASIO_HAS_SIGACTION 1 +# endif // !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) +# endif // !defined(ASIO_DISABLE_SIGACTION) +#endif // !defined(ASIO_HAS_SIGACTION) + +// Can use signal(). +#if !defined(ASIO_HAS_SIGNAL) +# if !defined(ASIO_DISABLE_SIGNAL) +# if !defined(UNDER_CE) +# define ASIO_HAS_SIGNAL 1 +# endif // !defined(UNDER_CE) +# endif // !defined(ASIO_DISABLE_SIGNAL) +#endif // !defined(ASIO_HAS_SIGNAL) + +// Can use getaddrinfo() and getnameinfo(). +#if !defined(ASIO_HAS_GETADDRINFO) +# if !defined(ASIO_DISABLE_GETADDRINFO) +# if defined(ASIO_WINDOWS) || defined(__CYGWIN__) +# if defined(_WIN32_WINNT) && (_WIN32_WINNT >= 0x0501) +# define ASIO_HAS_GETADDRINFO 1 +# elif defined(UNDER_CE) +# define ASIO_HAS_GETADDRINFO 1 +# endif // defined(UNDER_CE) +# elif defined(__MACH__) && defined(__APPLE__) +# if defined(__MAC_OS_X_VERSION_MIN_REQUIRED) +# if (__MAC_OS_X_VERSION_MIN_REQUIRED >= 1050) +# define ASIO_HAS_GETADDRINFO 1 +# endif // (__MAC_OS_X_VERSION_MIN_REQUIRED >= 1050) +# else // defined(__MAC_OS_X_VERSION_MIN_REQUIRED) +# define ASIO_HAS_GETADDRINFO 1 +# endif // defined(__MAC_OS_X_VERSION_MIN_REQUIRED) +# else // defined(__MACH__) && defined(__APPLE__) +# define ASIO_HAS_GETADDRINFO 1 +# endif // defined(__MACH__) && defined(__APPLE__) +# endif // !defined(ASIO_DISABLE_GETADDRINFO) +#endif // !defined(ASIO_HAS_GETADDRINFO) + +// Whether standard iostreams are disabled. +#if !defined(ASIO_NO_IOSTREAM) +# if defined(ASIO_HAS_BOOST_CONFIG) && defined(BOOST_NO_IOSTREAM) +# define ASIO_NO_IOSTREAM 1 +# endif // !defined(BOOST_NO_IOSTREAM) +#endif // !defined(ASIO_NO_IOSTREAM) + +// Whether exception handling is disabled. +#if !defined(ASIO_NO_EXCEPTIONS) +# if defined(ASIO_HAS_BOOST_CONFIG) && defined(BOOST_NO_EXCEPTIONS) +# define ASIO_NO_EXCEPTIONS 1 +# endif // !defined(BOOST_NO_EXCEPTIONS) +#endif // !defined(ASIO_NO_EXCEPTIONS) + +// Whether the typeid operator is supported. +#if !defined(ASIO_NO_TYPEID) +# if defined(ASIO_HAS_BOOST_CONFIG) && defined(BOOST_NO_TYPEID) +# define ASIO_NO_TYPEID 1 +# endif // !defined(BOOST_NO_TYPEID) +#endif // !defined(ASIO_NO_TYPEID) + +// Threads. +#if !defined(ASIO_HAS_THREADS) +# if !defined(ASIO_DISABLE_THREADS) +# if defined(ASIO_HAS_BOOST_CONFIG) && defined(BOOST_HAS_THREADS) +# define ASIO_HAS_THREADS 1 +# elif defined(__GNUC__) && !defined(__MINGW32__) \ + && !defined(linux) && !defined(__linux) && !defined(__linux__) +# define ASIO_HAS_THREADS 1 +# elif defined(_MT) || defined(__MT__) +# define ASIO_HAS_THREADS 1 +# elif defined(_REENTRANT) +# define ASIO_HAS_THREADS 1 +# elif defined(__APPLE__) +# define ASIO_HAS_THREADS 1 +# elif defined(__HAIKU__) +# define ASIO_HAS_THREADS 1 +# elif defined(_POSIX_THREADS) && (_POSIX_THREADS + 0 >= 0) +# define ASIO_HAS_THREADS 1 +# elif defined(_PTHREADS) +# define ASIO_HAS_THREADS 1 +# endif // defined(ASIO_HAS_BOOST_CONFIG) && defined(BOOST_HAS_THREADS) +# endif // !defined(ASIO_DISABLE_THREADS) +#endif // !defined(ASIO_HAS_THREADS) + +// POSIX threads. +#if !defined(ASIO_HAS_PTHREADS) +# if defined(ASIO_HAS_THREADS) +# if defined(ASIO_HAS_BOOST_CONFIG) && defined(BOOST_HAS_PTHREADS) +# define ASIO_HAS_PTHREADS 1 +# elif defined(_POSIX_THREADS) && (_POSIX_THREADS + 0 >= 0) +# define ASIO_HAS_PTHREADS 1 +# elif defined(__HAIKU__) +# define ASIO_HAS_PTHREADS 1 +# endif // defined(ASIO_HAS_BOOST_CONFIG) && defined(BOOST_HAS_PTHREADS) +# endif // defined(ASIO_HAS_THREADS) +#endif // !defined(ASIO_HAS_PTHREADS) + +// Helper to prevent macro expansion. +#define ASIO_PREVENT_MACRO_SUBSTITUTION + +// Helper to define in-class constants. +#if !defined(ASIO_STATIC_CONSTANT) +# if !defined(ASIO_DISABLE_BOOST_STATIC_CONSTANT) +# define ASIO_STATIC_CONSTANT(type, assignment) \ + BOOST_STATIC_CONSTANT(type, assignment) +# else // !defined(ASIO_DISABLE_BOOST_STATIC_CONSTANT) +# define ASIO_STATIC_CONSTANT(type, assignment) \ + static const type assignment +# endif // !defined(ASIO_DISABLE_BOOST_STATIC_CONSTANT) +#endif // !defined(ASIO_STATIC_CONSTANT) + +// Boost array library. +#if !defined(ASIO_HAS_BOOST_ARRAY) +# if !defined(ASIO_DISABLE_BOOST_ARRAY) +# define ASIO_HAS_BOOST_ARRAY 1 +# endif // !defined(ASIO_DISABLE_BOOST_ARRAY) +#endif // !defined(ASIO_HAS_BOOST_ARRAY) + +// Boost assert macro. +#if !defined(ASIO_HAS_BOOST_ASSERT) +# if !defined(ASIO_DISABLE_BOOST_ASSERT) +# define ASIO_HAS_BOOST_ASSERT 1 +# endif // !defined(ASIO_DISABLE_BOOST_ASSERT) +#endif // !defined(ASIO_HAS_BOOST_ASSERT) + +// Boost limits header. +#if !defined(ASIO_HAS_BOOST_LIMITS) +# if !defined(ASIO_DISABLE_BOOST_LIMITS) +# define ASIO_HAS_BOOST_LIMITS 1 +# endif // !defined(ASIO_DISABLE_BOOST_LIMITS) +#endif // !defined(ASIO_HAS_BOOST_LIMITS) + +// Boost throw_exception function. +#if !defined(ASIO_HAS_BOOST_THROW_EXCEPTION) +# if !defined(ASIO_DISABLE_BOOST_THROW_EXCEPTION) +# define ASIO_HAS_BOOST_THROW_EXCEPTION 1 +# endif // !defined(ASIO_DISABLE_BOOST_THROW_EXCEPTION) +#endif // !defined(ASIO_HAS_BOOST_THROW_EXCEPTION) + +// Boost regex library. +#if !defined(ASIO_HAS_BOOST_REGEX) +# if !defined(ASIO_DISABLE_BOOST_REGEX) +# define ASIO_HAS_BOOST_REGEX 1 +# endif // !defined(ASIO_DISABLE_BOOST_REGEX) +#endif // !defined(ASIO_HAS_BOOST_REGEX) + +// Boost bind function. +#if !defined(ASIO_HAS_BOOST_BIND) +# if !defined(ASIO_DISABLE_BOOST_BIND) +# define ASIO_HAS_BOOST_BIND 1 +# endif // !defined(ASIO_DISABLE_BOOST_BIND) +#endif // !defined(ASIO_HAS_BOOST_BIND) + +// Boost's BOOST_WORKAROUND macro. +#if !defined(ASIO_HAS_BOOST_WORKAROUND) +# if !defined(ASIO_DISABLE_BOOST_WORKAROUND) +# define ASIO_HAS_BOOST_WORKAROUND 1 +# endif // !defined(ASIO_DISABLE_BOOST_WORKAROUND) +#endif // !defined(ASIO_HAS_BOOST_WORKAROUND) + +// Microsoft Visual C++'s secure C runtime library. +#if !defined(ASIO_HAS_SECURE_RTL) +# if !defined(ASIO_DISABLE_SECURE_RTL) +# if defined(ASIO_MSVC) \ + && (ASIO_MSVC >= 1400) \ + && !defined(UNDER_CE) +# define ASIO_HAS_SECURE_RTL 1 +# endif // defined(ASIO_MSVC) + // && (ASIO_MSVC >= 1400) + // && !defined(UNDER_CE) +# endif // !defined(ASIO_DISABLE_SECURE_RTL) +#endif // !defined(ASIO_HAS_SECURE_RTL) + +// Handler hooking. Disabled for ancient Borland C++ and gcc compilers. +#if !defined(ASIO_HAS_HANDLER_HOOKS) +# if !defined(ASIO_DISABLE_HANDLER_HOOKS) +# if defined(__GNUC__) +# if (__GNUC__ >= 3) +# define ASIO_HAS_HANDLER_HOOKS 1 +# endif // (__GNUC__ >= 3) +# elif !defined(__BORLANDC__) || defined(__clang__) +# define ASIO_HAS_HANDLER_HOOKS 1 +# endif // !defined(__BORLANDC__) || defined(__clang__) +# endif // !defined(ASIO_DISABLE_HANDLER_HOOKS) +#endif // !defined(ASIO_HAS_HANDLER_HOOKS) + +// Support for the __thread keyword extension. +#if !defined(ASIO_DISABLE_THREAD_KEYWORD_EXTENSION) +# if defined(__linux__) +# if defined(__GNUC__) && (defined(__i386__) || defined(__x86_64__)) +# if ((__GNUC__ == 3) && (__GNUC_MINOR__ >= 3)) || (__GNUC__ > 3) +# if !defined(__INTEL_COMPILER) && !defined(__ICL) \ + && !(defined(__clang__) && defined(__ANDROID__)) +# define ASIO_HAS_THREAD_KEYWORD_EXTENSION 1 +# define ASIO_THREAD_KEYWORD __thread +# elif defined(__INTEL_COMPILER) && (__INTEL_COMPILER >= 1100) +# define ASIO_HAS_THREAD_KEYWORD_EXTENSION 1 +# endif // defined(__INTEL_COMPILER) && (__INTEL_COMPILER >= 1100) + // && !(defined(__clang__) && defined(__ANDROID__)) +# endif // ((__GNUC__ == 3) && (__GNUC_MINOR__ >= 3)) || (__GNUC__ > 3) +# endif // defined(__GNUC__) && (defined(__i386__) || defined(__x86_64__)) +# endif // defined(__linux__) +# if defined(ASIO_MSVC) && defined(ASIO_WINDOWS_RUNTIME) +# if (_MSC_VER >= 1700) +# define ASIO_HAS_THREAD_KEYWORD_EXTENSION 1 +# define ASIO_THREAD_KEYWORD __declspec(thread) +# endif // (_MSC_VER >= 1700) +# endif // defined(ASIO_MSVC) && defined(ASIO_WINDOWS_RUNTIME) +#endif // !defined(ASIO_DISABLE_THREAD_KEYWORD_EXTENSION) +#if !defined(ASIO_THREAD_KEYWORD) +# define ASIO_THREAD_KEYWORD __thread +#endif // !defined(ASIO_THREAD_KEYWORD) + +// Support for POSIX ssize_t typedef. +#if !defined(ASIO_DISABLE_SSIZE_T) +# if defined(__linux__) \ + || (defined(__MACH__) && defined(__APPLE__)) +# define ASIO_HAS_SSIZE_T 1 +# endif // defined(__linux__) + // || (defined(__MACH__) && defined(__APPLE__)) +#endif // !defined(ASIO_DISABLE_SSIZE_T) + +// Helper macros to manage transition away from error_code return values. +#if defined(ASIO_NO_DEPRECATED) +# define ASIO_SYNC_OP_VOID void +# define ASIO_SYNC_OP_VOID_RETURN(e) return +#else // defined(ASIO_NO_DEPRECATED) +# define ASIO_SYNC_OP_VOID asio::error_code +# define ASIO_SYNC_OP_VOID_RETURN(e) return e +#endif // defined(ASIO_NO_DEPRECATED) + +// Newer gcc, clang need special treatment to suppress unused typedef warnings. +#if defined(__clang__) +# if defined(__apple_build_version__) +# if (__clang_major__ >= 7) +# define ASIO_UNUSED_TYPEDEF __attribute__((__unused__)) +# endif // (__clang_major__ >= 7) +# elif ((__clang_major__ == 3) && (__clang_minor__ >= 6)) \ + || (__clang_major__ > 3) +# define ASIO_UNUSED_TYPEDEF __attribute__((__unused__)) +# endif // ((__clang_major__ == 3) && (__clang_minor__ >= 6)) + // || (__clang_major__ > 3) +#elif defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 8)) || (__GNUC__ > 4) +# define ASIO_UNUSED_TYPEDEF __attribute__((__unused__)) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 8)) || (__GNUC__ > 4) +#endif // defined(__GNUC__) +#if !defined(ASIO_UNUSED_TYPEDEF) +# define ASIO_UNUSED_TYPEDEF +#endif // !defined(ASIO_UNUSED_TYPEDEF) + +// Some versions of gcc generate spurious warnings about unused variables. +#if defined(__GNUC__) +# if (__GNUC__ >= 4) +# define ASIO_UNUSED_VARIABLE __attribute__((__unused__)) +# endif // (__GNUC__ >= 4) +#endif // defined(__GNUC__) +#if !defined(ASIO_UNUSED_VARIABLE) +# define ASIO_UNUSED_VARIABLE +#endif // !defined(ASIO_UNUSED_VARIABLE) + +// Support the co_await keyword on compilers known to allow it. +#if !defined(ASIO_HAS_CO_AWAIT) +# if !defined(ASIO_DISABLE_CO_AWAIT) +# if defined(ASIO_MSVC) +# if (_MSC_FULL_VER >= 190023506) +# if defined(_RESUMABLE_FUNCTIONS_SUPPORTED) +# define ASIO_HAS_CO_AWAIT 1 +# endif // defined(_RESUMABLE_FUNCTIONS_SUPPORTED) +# endif // (_MSC_FULL_VER >= 190023506) +# endif // defined(ASIO_MSVC) +# if defined(__clang__) +# if (__cplusplus >= 201703) && (__cpp_coroutines >= 201703) +# if __has_include() +# define ASIO_HAS_CO_AWAIT 1 +# endif // __has_include() +# endif // (__cplusplus >= 201703) && (__cpp_coroutines >= 201703) +# elif defined(__GNUC__) +# if (__cplusplus >= 201709) && (__cpp_impl_coroutine >= 201902) +# if __has_include() +# define ASIO_HAS_CO_AWAIT 1 +# endif // __has_include() +# endif // (__cplusplus >= 201709) && (__cpp_impl_coroutine >= 201902) +# endif // defined(__GNUC__) +# endif // !defined(ASIO_DISABLE_CO_AWAIT) +#endif // !defined(ASIO_HAS_CO_AWAIT) + +// Standard library support for coroutines. +#if !defined(ASIO_HAS_STD_COROUTINE) +# if !defined(ASIO_DISABLE_STD_COROUTINE) +# if defined(__GNUC__) +# if (__cplusplus >= 201709) && (__cpp_impl_coroutine >= 201902) +# if __has_include() +# define ASIO_HAS_STD_COROUTINE 1 +# endif // __has_include() +# endif // (__cplusplus >= 201709) && (__cpp_impl_coroutine >= 201902) +# endif // defined(__GNUC__) +# endif // !defined(ASIO_DISABLE_STD_COROUTINE) +#endif // !defined(ASIO_HAS_STD_COROUTINE) + +// Compiler support for the the [[nodiscard]] attribute. +#if !defined(ASIO_NODISCARD) +# if defined(__has_cpp_attribute) +# if __has_cpp_attribute(nodiscard) +# if (__cplusplus >= 201703) +# define ASIO_NODISCARD [[nodiscard]] +# endif // (__cplusplus >= 201703) +# endif // __has_cpp_attribute(nodiscard) +# endif // defined(__has_cpp_attribute) +#endif // !defined(ASIO_NODISCARD) +#if !defined(ASIO_NODISCARD) +# define ASIO_NODISCARD +#endif // !defined(ASIO_NODISCARD) + +#endif // ASIO_DETAIL_CONFIG_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/consuming_buffers.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/consuming_buffers.hpp new file mode 100644 index 000000000..0caf55742 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/consuming_buffers.hpp @@ -0,0 +1,414 @@ +// +// detail/consuming_buffers.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_CONSUMING_BUFFERS_HPP +#define ASIO_DETAIL_CONSUMING_BUFFERS_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include "asio/buffer.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/limits.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Helper template to determine the maximum number of prepared buffers. +template +struct prepared_buffers_max +{ + enum { value = buffer_sequence_adapter_base::max_buffers }; +}; + +template +struct prepared_buffers_max > +{ + enum { value = N }; +}; + +#if defined(ASIO_HAS_STD_ARRAY) + +template +struct prepared_buffers_max > +{ + enum { value = N }; +}; + +#endif // defined(ASIO_HAS_STD_ARRAY) + +// A buffer sequence used to represent a subsequence of the buffers. +template +struct prepared_buffers +{ + typedef Buffer value_type; + typedef const Buffer* const_iterator; + + enum { max_buffers = MaxBuffers < 16 ? MaxBuffers : 16 }; + + prepared_buffers() : count(0) {} + const_iterator begin() const { return elems; } + const_iterator end() const { return elems + count; } + + Buffer elems[max_buffers]; + std::size_t count; +}; + +// A proxy for a sub-range in a list of buffers. +template +class consuming_buffers +{ +public: + typedef prepared_buffers::value> + prepared_buffers_type; + + // Construct to represent the entire list of buffers. + explicit consuming_buffers(const Buffers& buffers) + : buffers_(buffers), + total_consumed_(0), + next_elem_(0), + next_elem_offset_(0) + { + using asio::buffer_size; + total_size_ = buffer_size(buffers); + } + + // Determine if we are at the end of the buffers. + bool empty() const + { + return total_consumed_ >= total_size_; + } + + // Get the buffer for a single transfer, with a size. + prepared_buffers_type prepare(std::size_t max_size) + { + prepared_buffers_type result; + + Buffer_Iterator next = asio::buffer_sequence_begin(buffers_); + Buffer_Iterator end = asio::buffer_sequence_end(buffers_); + + std::advance(next, next_elem_); + std::size_t elem_offset = next_elem_offset_; + while (next != end && max_size > 0 && (result.count) < result.max_buffers) + { + Buffer next_buf = Buffer(*next) + elem_offset; + result.elems[result.count] = asio::buffer(next_buf, max_size); + max_size -= result.elems[result.count].size(); + elem_offset = 0; + if (result.elems[result.count].size() > 0) + ++result.count; + ++next; + } + + return result; + } + + // Consume the specified number of bytes from the buffers. + void consume(std::size_t size) + { + total_consumed_ += size; + + Buffer_Iterator next = asio::buffer_sequence_begin(buffers_); + Buffer_Iterator end = asio::buffer_sequence_end(buffers_); + + std::advance(next, next_elem_); + while (next != end && size > 0) + { + Buffer next_buf = Buffer(*next) + next_elem_offset_; + if (size < next_buf.size()) + { + next_elem_offset_ += size; + size = 0; + } + else + { + size -= next_buf.size(); + next_elem_offset_ = 0; + ++next_elem_; + ++next; + } + } + } + + // Get the total number of bytes consumed from the buffers. + std::size_t total_consumed() const + { + return total_consumed_; + } + +private: + Buffers buffers_; + std::size_t total_size_; + std::size_t total_consumed_; + std::size_t next_elem_; + std::size_t next_elem_offset_; +}; + +// Base class of all consuming_buffers specialisations for single buffers. +template +class consuming_single_buffer +{ +public: + // Construct to represent the entire list of buffers. + template + explicit consuming_single_buffer(const Buffer1& buffer) + : buffer_(buffer), + total_consumed_(0) + { + } + + // Determine if we are at the end of the buffers. + bool empty() const + { + return total_consumed_ >= buffer_.size(); + } + + // Get the buffer for a single transfer, with a size. + Buffer prepare(std::size_t max_size) + { + return asio::buffer(buffer_ + total_consumed_, max_size); + } + + // Consume the specified number of bytes from the buffers. + void consume(std::size_t size) + { + total_consumed_ += size; + } + + // Get the total number of bytes consumed from the buffers. + std::size_t total_consumed() const + { + return total_consumed_; + } + +private: + Buffer buffer_; + std::size_t total_consumed_; +}; + +template <> +class consuming_buffers + : public consuming_single_buffer +{ +public: + explicit consuming_buffers(const mutable_buffer& buffer) + : consuming_single_buffer(buffer) + { + } +}; + +template <> +class consuming_buffers + : public consuming_single_buffer +{ +public: + explicit consuming_buffers(const mutable_buffer& buffer) + : consuming_single_buffer(buffer) + { + } +}; + +template <> +class consuming_buffers + : public consuming_single_buffer +{ +public: + explicit consuming_buffers(const const_buffer& buffer) + : consuming_single_buffer(buffer) + { + } +}; + +#if !defined(ASIO_NO_DEPRECATED) + +template <> +class consuming_buffers + : public consuming_single_buffer +{ +public: + explicit consuming_buffers(const mutable_buffers_1& buffer) + : consuming_single_buffer(buffer) + { + } +}; + +template <> +class consuming_buffers + : public consuming_single_buffer +{ +public: + explicit consuming_buffers(const mutable_buffers_1& buffer) + : consuming_single_buffer(buffer) + { + } +}; + +template <> +class consuming_buffers + : public consuming_single_buffer +{ +public: + explicit consuming_buffers(const const_buffers_1& buffer) + : consuming_single_buffer(buffer) + { + } +}; + +#endif // !defined(ASIO_NO_DEPRECATED) + +template +class consuming_buffers, + typename boost::array::const_iterator> +{ +public: + // Construct to represent the entire list of buffers. + explicit consuming_buffers(const boost::array& buffers) + : buffers_(buffers), + total_consumed_(0) + { + } + + // Determine if we are at the end of the buffers. + bool empty() const + { + return total_consumed_ >= + Buffer(buffers_[0]).size() + Buffer(buffers_[1]).size(); + } + + // Get the buffer for a single transfer, with a size. + boost::array prepare(std::size_t max_size) + { + boost::array result = {{ + Buffer(buffers_[0]), Buffer(buffers_[1]) }}; + std::size_t buffer0_size = result[0].size(); + result[0] = asio::buffer(result[0] + total_consumed_, max_size); + result[1] = asio::buffer( + result[1] + (total_consumed_ < buffer0_size + ? 0 : total_consumed_ - buffer0_size), + max_size - result[0].size()); + return result; + } + + // Consume the specified number of bytes from the buffers. + void consume(std::size_t size) + { + total_consumed_ += size; + } + + // Get the total number of bytes consumed from the buffers. + std::size_t total_consumed() const + { + return total_consumed_; + } + +private: + boost::array buffers_; + std::size_t total_consumed_; +}; + +#if defined(ASIO_HAS_STD_ARRAY) + +template +class consuming_buffers, + typename std::array::const_iterator> +{ +public: + // Construct to represent the entire list of buffers. + explicit consuming_buffers(const std::array& buffers) + : buffers_(buffers), + total_consumed_(0) + { + } + + // Determine if we are at the end of the buffers. + bool empty() const + { + return total_consumed_ >= + Buffer(buffers_[0]).size() + Buffer(buffers_[1]).size(); + } + + // Get the buffer for a single transfer, with a size. + std::array prepare(std::size_t max_size) + { + std::array result = {{ + Buffer(buffers_[0]), Buffer(buffers_[1]) }}; + std::size_t buffer0_size = result[0].size(); + result[0] = asio::buffer(result[0] + total_consumed_, max_size); + result[1] = asio::buffer( + result[1] + (total_consumed_ < buffer0_size + ? 0 : total_consumed_ - buffer0_size), + max_size - result[0].size()); + return result; + } + + // Consume the specified number of bytes from the buffers. + void consume(std::size_t size) + { + total_consumed_ += size; + } + + // Get the total number of bytes consumed from the buffers. + std::size_t total_consumed() const + { + return total_consumed_; + } + +private: + std::array buffers_; + std::size_t total_consumed_; +}; + +#endif // defined(ASIO_HAS_STD_ARRAY) + +// Specialisation for null_buffers to ensure that the null_buffers type is +// always passed through to the underlying read or write operation. +template +class consuming_buffers + : public asio::null_buffers +{ +public: + consuming_buffers(const null_buffers&) + { + // No-op. + } + + bool empty() + { + return false; + } + + null_buffers prepare(std::size_t) + { + return null_buffers(); + } + + void consume(std::size_t) + { + // No-op. + } + + std::size_t total_consumed() const + { + return 0; + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_CONSUMING_BUFFERS_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/cstddef.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/cstddef.hpp new file mode 100644 index 000000000..1b58be068 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/cstddef.hpp @@ -0,0 +1,31 @@ +// +// detail/cstddef.hpp +// ~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_CSTDDEF_HPP +#define ASIO_DETAIL_CSTDDEF_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include + +namespace asio { + +#if defined(ASIO_HAS_NULLPTR) +using std::nullptr_t; +#else // defined(ASIO_HAS_NULLPTR) +struct nullptr_t {}; +#endif // defined(ASIO_HAS_NULLPTR) + +} // namespace asio + +#endif // ASIO_DETAIL_CSTDDEF_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/cstdint.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/cstdint.hpp new file mode 100644 index 000000000..b65941aba --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/cstdint.hpp @@ -0,0 +1,60 @@ +// +// detail/cstdint.hpp +// ~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_CSTDINT_HPP +#define ASIO_DETAIL_CSTDINT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_CSTDINT) +# include +#else // defined(ASIO_HAS_CSTDINT) +# include +#endif // defined(ASIO_HAS_CSTDINT) + +namespace asio { + +#if defined(ASIO_HAS_CSTDINT) +using std::int16_t; +using std::int_least16_t; +using std::uint16_t; +using std::uint_least16_t; +using std::int32_t; +using std::int_least32_t; +using std::uint32_t; +using std::uint_least32_t; +using std::int64_t; +using std::int_least64_t; +using std::uint64_t; +using std::uint_least64_t; +using std::uintmax_t; +#else // defined(ASIO_HAS_CSTDINT) +using boost::int16_t; +using boost::int_least16_t; +using boost::uint16_t; +using boost::uint_least16_t; +using boost::int32_t; +using boost::int_least32_t; +using boost::uint32_t; +using boost::uint_least32_t; +using boost::int64_t; +using boost::int_least64_t; +using boost::uint64_t; +using boost::uint_least64_t; +using boost::uintmax_t; +#endif // defined(ASIO_HAS_CSTDINT) + +} // namespace asio + +#endif // ASIO_DETAIL_CSTDINT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/date_time_fwd.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/date_time_fwd.hpp new file mode 100644 index 000000000..f4a9ddef2 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/date_time_fwd.hpp @@ -0,0 +1,34 @@ +// +// detail/date_time_fwd.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_DATE_TIME_FWD_HPP +#define ASIO_DETAIL_DATE_TIME_FWD_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +namespace boost { +namespace date_time { + +template +class base_time; + +} // namespace date_time +namespace posix_time { + +class ptime; + +} // namespace posix_time +} // namespace boost + +#endif // ASIO_DETAIL_DATE_TIME_FWD_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/deadline_timer_service.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/deadline_timer_service.hpp new file mode 100644 index 000000000..dd03d09e2 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/deadline_timer_service.hpp @@ -0,0 +1,295 @@ +// +// detail/deadline_timer_service.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_DEADLINE_TIMER_SERVICE_HPP +#define ASIO_DETAIL_DEADLINE_TIMER_SERVICE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include "asio/error.hpp" +#include "asio/execution_context.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/detail/socket_types.hpp" +#include "asio/detail/timer_queue.hpp" +#include "asio/detail/timer_queue_ptime.hpp" +#include "asio/detail/timer_scheduler.hpp" +#include "asio/detail/wait_handler.hpp" +#include "asio/detail/wait_op.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) +# include +# include +#endif // defined(ASIO_WINDOWS_RUNTIME) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class deadline_timer_service + : public execution_context_service_base > +{ +public: + // The time type. + typedef typename Time_Traits::time_type time_type; + + // The duration type. + typedef typename Time_Traits::duration_type duration_type; + + // The implementation type of the timer. This type is dependent on the + // underlying implementation of the timer service. + struct implementation_type + : private asio::detail::noncopyable + { + time_type expiry; + bool might_have_pending_waits; + typename timer_queue::per_timer_data timer_data; + }; + + // Constructor. + deadline_timer_service(execution_context& context) + : execution_context_service_base< + deadline_timer_service >(context), + scheduler_(asio::use_service(context)) + { + scheduler_.init_task(); + scheduler_.add_timer_queue(timer_queue_); + } + + // Destructor. + ~deadline_timer_service() + { + scheduler_.remove_timer_queue(timer_queue_); + } + + // Destroy all user-defined handler objects owned by the service. + void shutdown() + { + } + + // Construct a new timer implementation. + void construct(implementation_type& impl) + { + impl.expiry = time_type(); + impl.might_have_pending_waits = false; + } + + // Destroy a timer implementation. + void destroy(implementation_type& impl) + { + asio::error_code ec; + cancel(impl, ec); + } + + // Move-construct a new timer implementation. + void move_construct(implementation_type& impl, + implementation_type& other_impl) + { + scheduler_.move_timer(timer_queue_, impl.timer_data, other_impl.timer_data); + + impl.expiry = other_impl.expiry; + other_impl.expiry = time_type(); + + impl.might_have_pending_waits = other_impl.might_have_pending_waits; + other_impl.might_have_pending_waits = false; + } + + // Move-assign from another timer implementation. + void move_assign(implementation_type& impl, + deadline_timer_service& other_service, + implementation_type& other_impl) + { + if (this != &other_service) + if (impl.might_have_pending_waits) + scheduler_.cancel_timer(timer_queue_, impl.timer_data); + + other_service.scheduler_.move_timer(other_service.timer_queue_, + impl.timer_data, other_impl.timer_data); + + impl.expiry = other_impl.expiry; + other_impl.expiry = time_type(); + + impl.might_have_pending_waits = other_impl.might_have_pending_waits; + other_impl.might_have_pending_waits = false; + } + + // Move-construct a new timer implementation. + void converting_move_construct(implementation_type& impl, + deadline_timer_service&, implementation_type& other_impl) + { + move_construct(impl, other_impl); + } + + // Move-assign from another timer implementation. + void converting_move_assign(implementation_type& impl, + deadline_timer_service& other_service, + implementation_type& other_impl) + { + move_assign(impl, other_service, other_impl); + } + + // Cancel any asynchronous wait operations associated with the timer. + std::size_t cancel(implementation_type& impl, asio::error_code& ec) + { + if (!impl.might_have_pending_waits) + { + ec = asio::error_code(); + return 0; + } + + ASIO_HANDLER_OPERATION((scheduler_.context(), + "deadline_timer", &impl, 0, "cancel")); + + std::size_t count = scheduler_.cancel_timer(timer_queue_, impl.timer_data); + impl.might_have_pending_waits = false; + ec = asio::error_code(); + return count; + } + + // Cancels one asynchronous wait operation associated with the timer. + std::size_t cancel_one(implementation_type& impl, + asio::error_code& ec) + { + if (!impl.might_have_pending_waits) + { + ec = asio::error_code(); + return 0; + } + + ASIO_HANDLER_OPERATION((scheduler_.context(), + "deadline_timer", &impl, 0, "cancel_one")); + + std::size_t count = scheduler_.cancel_timer( + timer_queue_, impl.timer_data, 1); + if (count == 0) + impl.might_have_pending_waits = false; + ec = asio::error_code(); + return count; + } + + // Get the expiry time for the timer as an absolute time. + time_type expiry(const implementation_type& impl) const + { + return impl.expiry; + } + + // Get the expiry time for the timer as an absolute time. + time_type expires_at(const implementation_type& impl) const + { + return impl.expiry; + } + + // Get the expiry time for the timer relative to now. + duration_type expires_from_now(const implementation_type& impl) const + { + return Time_Traits::subtract(this->expiry(impl), Time_Traits::now()); + } + + // Set the expiry time for the timer as an absolute time. + std::size_t expires_at(implementation_type& impl, + const time_type& expiry_time, asio::error_code& ec) + { + std::size_t count = cancel(impl, ec); + impl.expiry = expiry_time; + ec = asio::error_code(); + return count; + } + + // Set the expiry time for the timer relative to now. + std::size_t expires_after(implementation_type& impl, + const duration_type& expiry_time, asio::error_code& ec) + { + return expires_at(impl, + Time_Traits::add(Time_Traits::now(), expiry_time), ec); + } + + // Set the expiry time for the timer relative to now. + std::size_t expires_from_now(implementation_type& impl, + const duration_type& expiry_time, asio::error_code& ec) + { + return expires_at(impl, + Time_Traits::add(Time_Traits::now(), expiry_time), ec); + } + + // Perform a blocking wait on the timer. + void wait(implementation_type& impl, asio::error_code& ec) + { + time_type now = Time_Traits::now(); + ec = asio::error_code(); + while (Time_Traits::less_than(now, impl.expiry) && !ec) + { + this->do_wait(Time_Traits::to_posix_duration( + Time_Traits::subtract(impl.expiry, now)), ec); + now = Time_Traits::now(); + } + } + + // Start an asynchronous wait on the timer. + template + void async_wait(implementation_type& impl, + Handler& handler, const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef wait_handler op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(handler, io_ex); + + impl.might_have_pending_waits = true; + + ASIO_HANDLER_CREATION((scheduler_.context(), + *p.p, "deadline_timer", &impl, 0, "async_wait")); + + scheduler_.schedule_timer(timer_queue_, impl.expiry, impl.timer_data, p.p); + p.v = p.p = 0; + } + +private: + // Helper function to wait given a duration type. The duration type should + // either be of type boost::posix_time::time_duration, or implement the + // required subset of its interface. + template + void do_wait(const Duration& timeout, asio::error_code& ec) + { +#if defined(ASIO_WINDOWS_RUNTIME) + std::this_thread::sleep_for( + std::chrono::seconds(timeout.total_seconds()) + + std::chrono::microseconds(timeout.total_microseconds())); + ec = asio::error_code(); +#else // defined(ASIO_WINDOWS_RUNTIME) + ::timeval tv; + tv.tv_sec = timeout.total_seconds(); + tv.tv_usec = timeout.total_microseconds() % 1000000; + socket_ops::select(0, 0, 0, 0, &tv, ec); +#endif // defined(ASIO_WINDOWS_RUNTIME) + } + + // The queue of timers. + timer_queue timer_queue_; + + // The object that schedules and executes timers. Usually a reactor. + timer_scheduler& scheduler_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_DEADLINE_TIMER_SERVICE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/dependent_type.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/dependent_type.hpp new file mode 100644 index 000000000..0c00db592 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/dependent_type.hpp @@ -0,0 +1,36 @@ +// +// detail/dependent_type.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_DEPENDENT_TYPE_HPP +#define ASIO_DETAIL_DEPENDENT_TYPE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +struct dependent_type +{ + typedef T type; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_DEPENDENT_TYPE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/descriptor_ops.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/descriptor_ops.hpp new file mode 100644 index 000000000..dfe2f8c2a --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/descriptor_ops.hpp @@ -0,0 +1,139 @@ +// +// detail/descriptor_ops.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_DESCRIPTOR_OPS_HPP +#define ASIO_DETAIL_DESCRIPTOR_OPS_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_RUNTIME) \ + && !defined(__CYGWIN__) + +#include +#include "asio/error.hpp" +#include "asio/error_code.hpp" +#include "asio/detail/socket_types.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { +namespace descriptor_ops { + +// Descriptor state bits. +enum +{ + // The user wants a non-blocking descriptor. + user_set_non_blocking = 1, + + // The descriptor has been set non-blocking. + internal_non_blocking = 2, + + // Helper "state" used to determine whether the descriptor is non-blocking. + non_blocking = user_set_non_blocking | internal_non_blocking, + + // The descriptor may have been dup()-ed. + possible_dup = 4 +}; + +typedef unsigned char state_type; + +inline void get_last_error( + asio::error_code& ec, bool is_error_condition) +{ + if (!is_error_condition) + { + ec.assign(0, ec.category()); + } + else + { + ec = asio::error_code(errno, + asio::error::get_system_category()); + } +} + +ASIO_DECL int open(const char* path, int flags, + asio::error_code& ec); + +ASIO_DECL int close(int d, state_type& state, + asio::error_code& ec); + +ASIO_DECL bool set_user_non_blocking(int d, + state_type& state, bool value, asio::error_code& ec); + +ASIO_DECL bool set_internal_non_blocking(int d, + state_type& state, bool value, asio::error_code& ec); + +typedef iovec buf; + +ASIO_DECL std::size_t sync_read(int d, state_type state, buf* bufs, + std::size_t count, bool all_empty, asio::error_code& ec); + +ASIO_DECL std::size_t sync_read1(int d, state_type state, void* data, + std::size_t size, asio::error_code& ec); + +ASIO_DECL bool non_blocking_read(int d, buf* bufs, std::size_t count, + asio::error_code& ec, std::size_t& bytes_transferred); + +ASIO_DECL bool non_blocking_read1(int d, void* data, std::size_t size, + asio::error_code& ec, std::size_t& bytes_transferred); + +ASIO_DECL std::size_t sync_write(int d, state_type state, + const buf* bufs, std::size_t count, bool all_empty, + asio::error_code& ec); + +ASIO_DECL std::size_t sync_write1(int d, state_type state, + const void* data, std::size_t size, asio::error_code& ec); + +ASIO_DECL bool non_blocking_write(int d, + const buf* bufs, std::size_t count, + asio::error_code& ec, std::size_t& bytes_transferred); + +ASIO_DECL bool non_blocking_write1(int d, + const void* data, std::size_t size, + asio::error_code& ec, std::size_t& bytes_transferred); + +ASIO_DECL int ioctl(int d, state_type& state, long cmd, + ioctl_arg_type* arg, asio::error_code& ec); + +ASIO_DECL int fcntl(int d, int cmd, asio::error_code& ec); + +ASIO_DECL int fcntl(int d, int cmd, + long arg, asio::error_code& ec); + +ASIO_DECL int poll_read(int d, + state_type state, asio::error_code& ec); + +ASIO_DECL int poll_write(int d, + state_type state, asio::error_code& ec); + +ASIO_DECL int poll_error(int d, + state_type state, asio::error_code& ec); + +} // namespace descriptor_ops +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/descriptor_ops.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) + +#endif // ASIO_DETAIL_DESCRIPTOR_OPS_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/descriptor_read_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/descriptor_read_op.hpp new file mode 100644 index 000000000..bb4bc6d6a --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/descriptor_read_op.hpp @@ -0,0 +1,148 @@ +// +// detail/descriptor_read_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_DESCRIPTOR_READ_OP_HPP +#define ASIO_DETAIL_DESCRIPTOR_READ_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/descriptor_ops.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/reactor_op.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class descriptor_read_op_base : public reactor_op +{ +public: + descriptor_read_op_base(const asio::error_code& success_ec, + int descriptor, const MutableBufferSequence& buffers, + func_type complete_func) + : reactor_op(success_ec, + &descriptor_read_op_base::do_perform, complete_func), + descriptor_(descriptor), + buffers_(buffers) + { + } + + static status do_perform(reactor_op* base) + { + descriptor_read_op_base* o(static_cast(base)); + + typedef buffer_sequence_adapter bufs_type; + + status result; + if (bufs_type::is_single_buffer) + { + result = descriptor_ops::non_blocking_read1(o->descriptor_, + bufs_type::first(o->buffers_).data(), + bufs_type::first(o->buffers_).size(), + o->ec_, o->bytes_transferred_) ? done : not_done; + } + else + { + bufs_type bufs(o->buffers_); + result = descriptor_ops::non_blocking_read(o->descriptor_, + bufs.buffers(), bufs.count(), o->ec_, o->bytes_transferred_) + ? done : not_done; + } + + ASIO_HANDLER_REACTOR_OPERATION((*o, "non_blocking_read", + o->ec_, o->bytes_transferred_)); + + return result; + } + +private: + int descriptor_; + MutableBufferSequence buffers_; +}; + +template +class descriptor_read_op + : public descriptor_read_op_base +{ +public: + ASIO_DEFINE_HANDLER_PTR(descriptor_read_op); + + descriptor_read_op(const asio::error_code& success_ec, + int descriptor, const MutableBufferSequence& buffers, + Handler& handler, const IoExecutor& io_ex) + : descriptor_read_op_base(success_ec, + descriptor, buffers, &descriptor_read_op::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the handler object. + descriptor_read_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, o->ec_, o->bytes_transferred_); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) + +#endif // ASIO_DETAIL_DESCRIPTOR_READ_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/descriptor_write_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/descriptor_write_op.hpp new file mode 100644 index 000000000..15d98df00 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/descriptor_write_op.hpp @@ -0,0 +1,148 @@ +// +// detail/descriptor_write_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_DESCRIPTOR_WRITE_OP_HPP +#define ASIO_DETAIL_DESCRIPTOR_WRITE_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/descriptor_ops.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/reactor_op.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class descriptor_write_op_base : public reactor_op +{ +public: + descriptor_write_op_base(const asio::error_code& success_ec, + int descriptor, const ConstBufferSequence& buffers, + func_type complete_func) + : reactor_op(success_ec, + &descriptor_write_op_base::do_perform, complete_func), + descriptor_(descriptor), + buffers_(buffers) + { + } + + static status do_perform(reactor_op* base) + { + descriptor_write_op_base* o(static_cast(base)); + + typedef buffer_sequence_adapter bufs_type; + + status result; + if (bufs_type::is_single_buffer) + { + result = descriptor_ops::non_blocking_write1(o->descriptor_, + bufs_type::first(o->buffers_).data(), + bufs_type::first(o->buffers_).size(), + o->ec_, o->bytes_transferred_) ? done : not_done; + } + else + { + bufs_type bufs(o->buffers_); + result = descriptor_ops::non_blocking_write(o->descriptor_, + bufs.buffers(), bufs.count(), o->ec_, o->bytes_transferred_) + ? done : not_done; + } + + ASIO_HANDLER_REACTOR_OPERATION((*o, "non_blocking_write", + o->ec_, o->bytes_transferred_)); + + return result; + } + +private: + int descriptor_; + ConstBufferSequence buffers_; +}; + +template +class descriptor_write_op + : public descriptor_write_op_base +{ +public: + ASIO_DEFINE_HANDLER_PTR(descriptor_write_op); + + descriptor_write_op(const asio::error_code& success_ec, + int descriptor, const ConstBufferSequence& buffers, + Handler& handler, const IoExecutor& io_ex) + : descriptor_write_op_base(success_ec, + descriptor, buffers, &descriptor_write_op::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the handler object. + descriptor_write_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, o->ec_, o->bytes_transferred_); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) + +#endif // ASIO_DETAIL_DESCRIPTOR_WRITE_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/dev_poll_reactor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/dev_poll_reactor.hpp new file mode 100644 index 000000000..0d6215357 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/dev_poll_reactor.hpp @@ -0,0 +1,218 @@ +// +// detail/dev_poll_reactor.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_DEV_POLL_REACTOR_HPP +#define ASIO_DETAIL_DEV_POLL_REACTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_DEV_POLL) + +#include +#include +#include +#include "asio/detail/hash_map.hpp" +#include "asio/detail/limits.hpp" +#include "asio/detail/mutex.hpp" +#include "asio/detail/op_queue.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/reactor_op_queue.hpp" +#include "asio/detail/select_interrupter.hpp" +#include "asio/detail/socket_types.hpp" +#include "asio/detail/timer_queue_base.hpp" +#include "asio/detail/timer_queue_set.hpp" +#include "asio/detail/wait_op.hpp" +#include "asio/execution_context.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class dev_poll_reactor + : public execution_context_service_base +{ +public: + enum op_types { read_op = 0, write_op = 1, + connect_op = 1, except_op = 2, max_ops = 3 }; + + // Per-descriptor data. + struct per_descriptor_data + { + }; + + // Constructor. + ASIO_DECL dev_poll_reactor(asio::execution_context& ctx); + + // Destructor. + ASIO_DECL ~dev_poll_reactor(); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void shutdown(); + + // Recreate internal descriptors following a fork. + ASIO_DECL void notify_fork( + asio::execution_context::fork_event fork_ev); + + // Initialise the task. + ASIO_DECL void init_task(); + + // Register a socket with the reactor. Returns 0 on success, system error + // code on failure. + ASIO_DECL int register_descriptor(socket_type, per_descriptor_data&); + + // Register a descriptor with an associated single operation. Returns 0 on + // success, system error code on failure. + ASIO_DECL int register_internal_descriptor( + int op_type, socket_type descriptor, + per_descriptor_data& descriptor_data, reactor_op* op); + + // Move descriptor registration from one descriptor_data object to another. + ASIO_DECL void move_descriptor(socket_type descriptor, + per_descriptor_data& target_descriptor_data, + per_descriptor_data& source_descriptor_data); + + // Post a reactor operation for immediate completion. + void post_immediate_completion(reactor_op* op, bool is_continuation) + { + scheduler_.post_immediate_completion(op, is_continuation); + } + + // Start a new operation. The reactor operation will be performed when the + // given descriptor is flagged as ready, or an error has occurred. + ASIO_DECL void start_op(int op_type, socket_type descriptor, + per_descriptor_data&, reactor_op* op, + bool is_continuation, bool allow_speculative); + + // Cancel all operations associated with the given descriptor. The + // handlers associated with the descriptor will be invoked with the + // operation_aborted error. + ASIO_DECL void cancel_ops(socket_type descriptor, per_descriptor_data&); + + // Cancel any operations that are running against the descriptor and remove + // its registration from the reactor. The reactor resources associated with + // the descriptor must be released by calling cleanup_descriptor_data. + ASIO_DECL void deregister_descriptor(socket_type descriptor, + per_descriptor_data&, bool closing); + + // Remove the descriptor's registration from the reactor. The reactor + // resources associated with the descriptor must be released by calling + // cleanup_descriptor_data. + ASIO_DECL void deregister_internal_descriptor( + socket_type descriptor, per_descriptor_data&); + + // Perform any post-deregistration cleanup tasks associated with the + // descriptor data. + ASIO_DECL void cleanup_descriptor_data(per_descriptor_data&); + + // Add a new timer queue to the reactor. + template + void add_timer_queue(timer_queue& queue); + + // Remove a timer queue from the reactor. + template + void remove_timer_queue(timer_queue& queue); + + // Schedule a new operation in the given timer queue to expire at the + // specified absolute time. + template + void schedule_timer(timer_queue& queue, + const typename Time_Traits::time_type& time, + typename timer_queue::per_timer_data& timer, wait_op* op); + + // Cancel the timer operations associated with the given token. Returns the + // number of operations that have been posted or dispatched. + template + std::size_t cancel_timer(timer_queue& queue, + typename timer_queue::per_timer_data& timer, + std::size_t max_cancelled = (std::numeric_limits::max)()); + + // Move the timer operations associated with the given timer. + template + void move_timer(timer_queue& queue, + typename timer_queue::per_timer_data& target, + typename timer_queue::per_timer_data& source); + + // Run /dev/poll once until interrupted or events are ready to be dispatched. + ASIO_DECL void run(long usec, op_queue& ops); + + // Interrupt the select loop. + ASIO_DECL void interrupt(); + +private: + // Create the /dev/poll file descriptor. Throws an exception if the descriptor + // cannot be created. + ASIO_DECL static int do_dev_poll_create(); + + // Helper function to add a new timer queue. + ASIO_DECL void do_add_timer_queue(timer_queue_base& queue); + + // Helper function to remove a timer queue. + ASIO_DECL void do_remove_timer_queue(timer_queue_base& queue); + + // Get the timeout value for the /dev/poll DP_POLL operation. The timeout + // value is returned as a number of milliseconds. A return value of -1 + // indicates that the poll should block indefinitely. + ASIO_DECL int get_timeout(int msec); + + // Cancel all operations associated with the given descriptor. The do_cancel + // function of the handler objects will be invoked. This function does not + // acquire the dev_poll_reactor's mutex. + ASIO_DECL void cancel_ops_unlocked(socket_type descriptor, + const asio::error_code& ec); + + // Add a pending event entry for the given descriptor. + ASIO_DECL ::pollfd& add_pending_event_change(int descriptor); + + // The scheduler implementation used to post completions. + scheduler& scheduler_; + + // Mutex to protect access to internal data. + asio::detail::mutex mutex_; + + // The /dev/poll file descriptor. + int dev_poll_fd_; + + // Vector of /dev/poll events waiting to be written to the descriptor. + std::vector< ::pollfd> pending_event_changes_; + + // Hash map to associate a descriptor with a pending event change index. + hash_map pending_event_change_index_; + + // The interrupter is used to break a blocking DP_POLL operation. + select_interrupter interrupter_; + + // The queues of read, write and except operations. + reactor_op_queue op_queue_[max_ops]; + + // The timer queues. + timer_queue_set timer_queues_; + + // Whether the service has been shut down. + bool shutdown_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/detail/impl/dev_poll_reactor.hpp" +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/dev_poll_reactor.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_HAS_DEV_POLL) + +#endif // ASIO_DETAIL_DEV_POLL_REACTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/epoll_reactor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/epoll_reactor.hpp new file mode 100644 index 000000000..032fc8515 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/epoll_reactor.hpp @@ -0,0 +1,266 @@ +// +// detail/epoll_reactor.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_EPOLL_REACTOR_HPP +#define ASIO_DETAIL_EPOLL_REACTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_EPOLL) + +#include "asio/detail/atomic_count.hpp" +#include "asio/detail/conditionally_enabled_mutex.hpp" +#include "asio/detail/limits.hpp" +#include "asio/detail/object_pool.hpp" +#include "asio/detail/op_queue.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/select_interrupter.hpp" +#include "asio/detail/socket_types.hpp" +#include "asio/detail/timer_queue_base.hpp" +#include "asio/detail/timer_queue_set.hpp" +#include "asio/detail/wait_op.hpp" +#include "asio/execution_context.hpp" + +#if defined(ASIO_HAS_TIMERFD) +# include +#endif // defined(ASIO_HAS_TIMERFD) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class epoll_reactor + : public execution_context_service_base +{ +private: + // The mutex type used by this reactor. + typedef conditionally_enabled_mutex mutex; + +public: + enum op_types { read_op = 0, write_op = 1, + connect_op = 1, except_op = 2, max_ops = 3 }; + + // Per-descriptor queues. + class descriptor_state : operation + { + friend class epoll_reactor; + friend class object_pool_access; + + descriptor_state* next_; + descriptor_state* prev_; + + mutex mutex_; + epoll_reactor* reactor_; + int descriptor_; + uint32_t registered_events_; + op_queue op_queue_[max_ops]; + bool try_speculative_[max_ops]; + bool shutdown_; + + ASIO_DECL descriptor_state(bool locking); + void set_ready_events(uint32_t events) { task_result_ = events; } + void add_ready_events(uint32_t events) { task_result_ |= events; } + ASIO_DECL operation* perform_io(uint32_t events); + ASIO_DECL static void do_complete( + void* owner, operation* base, + const asio::error_code& ec, std::size_t bytes_transferred); + }; + + // Per-descriptor data. + typedef descriptor_state* per_descriptor_data; + + // Constructor. + ASIO_DECL epoll_reactor(asio::execution_context& ctx); + + // Destructor. + ASIO_DECL ~epoll_reactor(); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void shutdown(); + + // Recreate internal descriptors following a fork. + ASIO_DECL void notify_fork( + asio::execution_context::fork_event fork_ev); + + // Initialise the task. + ASIO_DECL void init_task(); + + // Register a socket with the reactor. Returns 0 on success, system error + // code on failure. + ASIO_DECL int register_descriptor(socket_type descriptor, + per_descriptor_data& descriptor_data); + + // Register a descriptor with an associated single operation. Returns 0 on + // success, system error code on failure. + ASIO_DECL int register_internal_descriptor( + int op_type, socket_type descriptor, + per_descriptor_data& descriptor_data, reactor_op* op); + + // Move descriptor registration from one descriptor_data object to another. + ASIO_DECL void move_descriptor(socket_type descriptor, + per_descriptor_data& target_descriptor_data, + per_descriptor_data& source_descriptor_data); + + // Post a reactor operation for immediate completion. + void post_immediate_completion(reactor_op* op, bool is_continuation) + { + scheduler_.post_immediate_completion(op, is_continuation); + } + + // Start a new operation. The reactor operation will be performed when the + // given descriptor is flagged as ready, or an error has occurred. + ASIO_DECL void start_op(int op_type, socket_type descriptor, + per_descriptor_data& descriptor_data, reactor_op* op, + bool is_continuation, bool allow_speculative); + + // Cancel all operations associated with the given descriptor. The + // handlers associated with the descriptor will be invoked with the + // operation_aborted error. + ASIO_DECL void cancel_ops(socket_type descriptor, + per_descriptor_data& descriptor_data); + + // Cancel any operations that are running against the descriptor and remove + // its registration from the reactor. The reactor resources associated with + // the descriptor must be released by calling cleanup_descriptor_data. + ASIO_DECL void deregister_descriptor(socket_type descriptor, + per_descriptor_data& descriptor_data, bool closing); + + // Remove the descriptor's registration from the reactor. The reactor + // resources associated with the descriptor must be released by calling + // cleanup_descriptor_data. + ASIO_DECL void deregister_internal_descriptor( + socket_type descriptor, per_descriptor_data& descriptor_data); + + // Perform any post-deregistration cleanup tasks associated with the + // descriptor data. + ASIO_DECL void cleanup_descriptor_data( + per_descriptor_data& descriptor_data); + + // Add a new timer queue to the reactor. + template + void add_timer_queue(timer_queue& timer_queue); + + // Remove a timer queue from the reactor. + template + void remove_timer_queue(timer_queue& timer_queue); + + // Schedule a new operation in the given timer queue to expire at the + // specified absolute time. + template + void schedule_timer(timer_queue& queue, + const typename Time_Traits::time_type& time, + typename timer_queue::per_timer_data& timer, wait_op* op); + + // Cancel the timer operations associated with the given token. Returns the + // number of operations that have been posted or dispatched. + template + std::size_t cancel_timer(timer_queue& queue, + typename timer_queue::per_timer_data& timer, + std::size_t max_cancelled = (std::numeric_limits::max)()); + + // Move the timer operations associated with the given timer. + template + void move_timer(timer_queue& queue, + typename timer_queue::per_timer_data& target, + typename timer_queue::per_timer_data& source); + + // Run epoll once until interrupted or events are ready to be dispatched. + ASIO_DECL void run(long usec, op_queue& ops); + + // Interrupt the select loop. + ASIO_DECL void interrupt(); + +private: + // The hint to pass to epoll_create to size its data structures. + enum { epoll_size = 20000 }; + + // Create the epoll file descriptor. Throws an exception if the descriptor + // cannot be created. + ASIO_DECL static int do_epoll_create(); + + // Create the timerfd file descriptor. Does not throw. + ASIO_DECL static int do_timerfd_create(); + + // Allocate a new descriptor state object. + ASIO_DECL descriptor_state* allocate_descriptor_state(); + + // Free an existing descriptor state object. + ASIO_DECL void free_descriptor_state(descriptor_state* s); + + // Helper function to add a new timer queue. + ASIO_DECL void do_add_timer_queue(timer_queue_base& queue); + + // Helper function to remove a timer queue. + ASIO_DECL void do_remove_timer_queue(timer_queue_base& queue); + + // Called to recalculate and update the timeout. + ASIO_DECL void update_timeout(); + + // Get the timeout value for the epoll_wait call. The timeout value is + // returned as a number of milliseconds. A return value of -1 indicates + // that epoll_wait should block indefinitely. + ASIO_DECL int get_timeout(int msec); + +#if defined(ASIO_HAS_TIMERFD) + // Get the timeout value for the timer descriptor. The return value is the + // flag argument to be used when calling timerfd_settime. + ASIO_DECL int get_timeout(itimerspec& ts); +#endif // defined(ASIO_HAS_TIMERFD) + + // The scheduler implementation used to post completions. + scheduler& scheduler_; + + // Mutex to protect access to internal data. + mutex mutex_; + + // The interrupter is used to break a blocking epoll_wait call. + select_interrupter interrupter_; + + // The epoll file descriptor. + int epoll_fd_; + + // The timer file descriptor. + int timer_fd_; + + // The timer queues. + timer_queue_set timer_queues_; + + // Whether the service has been shut down. + bool shutdown_; + + // Mutex to protect access to the registered descriptors. + mutex registered_descriptors_mutex_; + + // Keep track of all registered descriptors. + object_pool registered_descriptors_; + + // Helper class to do post-perform_io cleanup. + struct perform_io_cleanup_on_block_exit; + friend struct perform_io_cleanup_on_block_exit; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/detail/impl/epoll_reactor.hpp" +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/epoll_reactor.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_HAS_EPOLL) + +#endif // ASIO_DETAIL_EPOLL_REACTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/event.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/event.hpp new file mode 100644 index 000000000..92682786f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/event.hpp @@ -0,0 +1,48 @@ +// +// detail/event.hpp +// ~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_EVENT_HPP +#define ASIO_DETAIL_EVENT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_THREADS) +# include "asio/detail/null_event.hpp" +#elif defined(ASIO_WINDOWS) +# include "asio/detail/win_event.hpp" +#elif defined(ASIO_HAS_PTHREADS) +# include "asio/detail/posix_event.hpp" +#elif defined(ASIO_HAS_STD_MUTEX_AND_CONDVAR) +# include "asio/detail/std_event.hpp" +#else +# error Only Windows, POSIX and std::condition_variable are supported! +#endif + +namespace asio { +namespace detail { + +#if !defined(ASIO_HAS_THREADS) +typedef null_event event; +#elif defined(ASIO_WINDOWS) +typedef win_event event; +#elif defined(ASIO_HAS_PTHREADS) +typedef posix_event event; +#elif defined(ASIO_HAS_STD_MUTEX_AND_CONDVAR) +typedef std_event event; +#endif + +} // namespace detail +} // namespace asio + +#endif // ASIO_DETAIL_EVENT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/eventfd_select_interrupter.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/eventfd_select_interrupter.hpp new file mode 100644 index 000000000..9e2505638 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/eventfd_select_interrupter.hpp @@ -0,0 +1,83 @@ +// +// detail/eventfd_select_interrupter.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// Copyright (c) 2008 Roelof Naude (roelof.naude at gmail dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_EVENTFD_SELECT_INTERRUPTER_HPP +#define ASIO_DETAIL_EVENTFD_SELECT_INTERRUPTER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_EVENTFD) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class eventfd_select_interrupter +{ +public: + // Constructor. + ASIO_DECL eventfd_select_interrupter(); + + // Destructor. + ASIO_DECL ~eventfd_select_interrupter(); + + // Recreate the interrupter's descriptors. Used after a fork. + ASIO_DECL void recreate(); + + // Interrupt the select call. + ASIO_DECL void interrupt(); + + // Reset the select interrupter. Returns true if the reset was successful. + ASIO_DECL bool reset(); + + // Get the read descriptor to be passed to select. + int read_descriptor() const + { + return read_descriptor_; + } + +private: + // Open the descriptors. Throws on error. + ASIO_DECL void open_descriptors(); + + // Close the descriptors. + ASIO_DECL void close_descriptors(); + + // The read end of a connection used to interrupt the select call. This file + // descriptor is passed to select such that when it is time to stop, a single + // 64bit value will be written on the other end of the connection and this + // descriptor will become readable. + int read_descriptor_; + + // The write end of a connection used to interrupt the select call. A single + // 64bit non-zero value may be written to this to wake up the select which is + // waiting for the other end to become readable. This descriptor will only + // differ from the read descriptor when a pipe is used. + int write_descriptor_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/eventfd_select_interrupter.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_HAS_EVENTFD) + +#endif // ASIO_DETAIL_EVENTFD_SELECT_INTERRUPTER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/executor_function.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/executor_function.hpp new file mode 100644 index 000000000..af7631693 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/executor_function.hpp @@ -0,0 +1,203 @@ +// +// detail/executor_function.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_EXECUTOR_FUNCTION_HPP +#define ASIO_DETAIL_EXECUTOR_FUNCTION_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/memory.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +#if defined(ASIO_HAS_MOVE) + +// Lightweight, move-only function object wrapper. +class executor_function +{ +public: + template + explicit executor_function(F f, const Alloc& a) + { + // Allocate and construct an object to wrap the function. + typedef impl impl_type; + typename impl_type::ptr p = { + detail::addressof(a), impl_type::ptr::allocate(a), 0 }; + impl_ = new (p.v) impl_type(ASIO_MOVE_CAST(F)(f), a); + p.v = 0; + } + + executor_function(executor_function&& other) ASIO_NOEXCEPT + : impl_(other.impl_) + { + other.impl_ = 0; + } + + ~executor_function() + { + if (impl_) + impl_->complete_(impl_, false); + } + + void operator()() + { + if (impl_) + { + impl_base* i = impl_; + impl_ = 0; + i->complete_(i, true); + } + } + +private: + // Base class for polymorphic function implementations. + struct impl_base + { + void (*complete_)(impl_base*, bool); + }; + + // Polymorphic function implementation. + template + struct impl : impl_base + { + ASIO_DEFINE_TAGGED_HANDLER_ALLOCATOR_PTR( + thread_info_base::executor_function_tag, impl); + + template + impl(ASIO_MOVE_ARG(F) f, const Alloc& a) + : function_(ASIO_MOVE_CAST(F)(f)), + allocator_(a) + { + complete_ = &executor_function::complete; + } + + Function function_; + Alloc allocator_; + }; + + // Helper to complete function invocation. + template + static void complete(impl_base* base, bool call) + { + // Take ownership of the function object. + impl* i(static_cast*>(base)); + Alloc allocator(i->allocator_); + typename impl::ptr p = { + detail::addressof(allocator), i, i }; + + // Make a copy of the function so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the function may be the true owner of the memory + // associated with the function. Consequently, a local copy of the function + // is required to ensure that any owning sub-object remains valid until + // after we have deallocated the memory here. + Function function(ASIO_MOVE_CAST(Function)(i->function_)); + p.reset(); + + // Make the upcall if required. + if (call) + { + function(); + } + } + + impl_base* impl_; +}; + +#else // defined(ASIO_HAS_MOVE) + +// Not so lightweight, copyable function object wrapper. +class executor_function +{ +public: + template + explicit executor_function(const F& f, const Alloc&) + : impl_(new impl::type>(f)) + { + } + + void operator()() + { + impl_->complete_(impl_.get()); + } + +private: + // Base class for polymorphic function implementations. + struct impl_base + { + void (*complete_)(impl_base*); + }; + + // Polymorphic function implementation. + template + struct impl : impl_base + { + impl(const F& f) + : function_(f) + { + complete_ = &executor_function::complete; + } + + F function_; + }; + + // Helper to complete function invocation. + template + static void complete(impl_base* i) + { + static_cast*>(i)->function_(); + } + + shared_ptr impl_; +}; + +#endif // defined(ASIO_HAS_MOVE) + +// Lightweight, non-owning, copyable function object wrapper. +class executor_function_view +{ +public: + template + explicit executor_function_view(F& f) ASIO_NOEXCEPT + : complete_(&executor_function_view::complete), + function_(&f) + { + } + + void operator()() + { + complete_(function_); + } + +private: + // Helper to complete function invocation. + template + static void complete(void* f) + { + (*static_cast(f))(); + } + + void (*complete_)(void*); + void* function_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_EXECUTOR_FUNCTION_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/executor_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/executor_op.hpp new file mode 100644 index 000000000..c2acdb6ac --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/executor_op.hpp @@ -0,0 +1,84 @@ +// +// detail/executor_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_EXECUTOR_OP_HPP +#define ASIO_DETAIL_EXECUTOR_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/scheduler_operation.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class executor_op : public Operation +{ +public: + ASIO_DEFINE_HANDLER_ALLOCATOR_PTR(executor_op); + + template + executor_op(ASIO_MOVE_ARG(H) h, const Alloc& allocator) + : Operation(&executor_op::do_complete), + handler_(ASIO_MOVE_CAST(H)(h)), + allocator_(allocator) + { + } + + static void do_complete(void* owner, Operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the handler object. + executor_op* o(static_cast(base)); + Alloc allocator(o->allocator_); + ptr p = { detail::addressof(allocator), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + Handler handler(ASIO_MOVE_CAST(Handler)(o->handler_)); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN(()); + asio_handler_invoke_helpers::invoke(handler, handler); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + Alloc allocator_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_EXECUTOR_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/fd_set_adapter.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/fd_set_adapter.hpp new file mode 100644 index 000000000..4fe7b27de --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/fd_set_adapter.hpp @@ -0,0 +1,39 @@ +// +// detail/fd_set_adapter.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_FD_SET_ADAPTER_HPP +#define ASIO_DETAIL_FD_SET_ADAPTER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_WINDOWS_RUNTIME) + +#include "asio/detail/posix_fd_set_adapter.hpp" +#include "asio/detail/win_fd_set_adapter.hpp" + +namespace asio { +namespace detail { + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) +typedef win_fd_set_adapter fd_set_adapter; +#else +typedef posix_fd_set_adapter fd_set_adapter; +#endif + +} // namespace detail +} // namespace asio + +#endif // !defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_FD_SET_ADAPTER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/fenced_block.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/fenced_block.hpp new file mode 100644 index 000000000..17550ff5f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/fenced_block.hpp @@ -0,0 +1,80 @@ +// +// detail/fenced_block.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_FENCED_BLOCK_HPP +#define ASIO_DETAIL_FENCED_BLOCK_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_THREADS) \ + || defined(ASIO_DISABLE_FENCED_BLOCK) +# include "asio/detail/null_fenced_block.hpp" +#elif defined(ASIO_HAS_STD_ATOMIC) +# include "asio/detail/std_fenced_block.hpp" +#elif defined(__MACH__) && defined(__APPLE__) +# include "asio/detail/macos_fenced_block.hpp" +#elif defined(__sun) +# include "asio/detail/solaris_fenced_block.hpp" +#elif defined(__GNUC__) && defined(__arm__) \ + && !defined(__GCC_HAVE_SYNC_COMPARE_AND_SWAP_4) +# include "asio/detail/gcc_arm_fenced_block.hpp" +#elif defined(__GNUC__) && (defined(__hppa) || defined(__hppa__)) +# include "asio/detail/gcc_hppa_fenced_block.hpp" +#elif defined(__GNUC__) && (defined(__i386__) || defined(__x86_64__)) +# include "asio/detail/gcc_x86_fenced_block.hpp" +#elif defined(__GNUC__) \ + && ((__GNUC__ == 4 && __GNUC_MINOR__ >= 1) || (__GNUC__ > 4)) \ + && !defined(__INTEL_COMPILER) && !defined(__ICL) \ + && !defined(__ICC) && !defined(__ECC) && !defined(__PATHSCALE__) +# include "asio/detail/gcc_sync_fenced_block.hpp" +#elif defined(ASIO_WINDOWS) && !defined(UNDER_CE) +# include "asio/detail/win_fenced_block.hpp" +#else +# include "asio/detail/null_fenced_block.hpp" +#endif + +namespace asio { +namespace detail { + +#if !defined(ASIO_HAS_THREADS) \ + || defined(ASIO_DISABLE_FENCED_BLOCK) +typedef null_fenced_block fenced_block; +#elif defined(ASIO_HAS_STD_ATOMIC) +typedef std_fenced_block fenced_block; +#elif defined(__MACH__) && defined(__APPLE__) +typedef macos_fenced_block fenced_block; +#elif defined(__sun) +typedef solaris_fenced_block fenced_block; +#elif defined(__GNUC__) && defined(__arm__) \ + && !defined(__GCC_HAVE_SYNC_COMPARE_AND_SWAP_4) +typedef gcc_arm_fenced_block fenced_block; +#elif defined(__GNUC__) && (defined(__hppa) || defined(__hppa__)) +typedef gcc_hppa_fenced_block fenced_block; +#elif defined(__GNUC__) && (defined(__i386__) || defined(__x86_64__)) +typedef gcc_x86_fenced_block fenced_block; +#elif defined(__GNUC__) \ + && ((__GNUC__ == 4 && __GNUC_MINOR__ >= 1) || (__GNUC__ > 4)) \ + && !defined(__INTEL_COMPILER) && !defined(__ICL) \ + && !defined(__ICC) && !defined(__ECC) && !defined(__PATHSCALE__) +typedef gcc_sync_fenced_block fenced_block; +#elif defined(ASIO_WINDOWS) && !defined(UNDER_CE) +typedef win_fenced_block fenced_block; +#else +typedef null_fenced_block fenced_block; +#endif + +} // namespace detail +} // namespace asio + +#endif // ASIO_DETAIL_FENCED_BLOCK_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/functional.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/functional.hpp new file mode 100644 index 000000000..ed73ce650 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/functional.hpp @@ -0,0 +1,38 @@ +// +// detail/functional.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_FUNCTIONAL_HPP +#define ASIO_DETAIL_FUNCTIONAL_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#include + +#if !defined(ASIO_HAS_STD_FUNCTION) +# include +#endif // !defined(ASIO_HAS_STD_FUNCTION) + +namespace asio { +namespace detail { + +#if defined(ASIO_HAS_STD_FUNCTION) +using std::function; +#else // defined(ASIO_HAS_STD_FUNCTION) +using boost::function; +#endif // defined(ASIO_HAS_STD_FUNCTION) + +} // namespace detail +} // namespace asio + +#endif // ASIO_DETAIL_FUNCTIONAL_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/future.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/future.hpp new file mode 100644 index 000000000..4a2a0807d --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/future.hpp @@ -0,0 +1,33 @@ +// +// detail/future.hpp +// ~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_FUTURE_HPP +#define ASIO_DETAIL_FUTURE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#if defined(ASIO_HAS_STD_FUTURE) +# include +// Even though the future header is available, libstdc++ may not implement the +// std::future class itself. However, we need to have already included the +// future header to reliably test for _GLIBCXX_HAS_GTHREADS. +# if defined(__GNUC__) && !defined(ASIO_HAS_CLANG_LIBCXX) +# if defined(_GLIBCXX_HAS_GTHREADS) +# define ASIO_HAS_STD_FUTURE_CLASS 1 +# endif // defined(_GLIBCXX_HAS_GTHREADS) +# else // defined(__GNUC__) && !defined(ASIO_HAS_CLANG_LIBCXX) +# define ASIO_HAS_STD_FUTURE_CLASS 1 +# endif // defined(__GNUC__) && !defined(ASIO_HAS_CLANG_LIBCXX) +#endif // defined(ASIO_HAS_STD_FUTURE) + +#endif // ASIO_DETAIL_FUTURE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/gcc_arm_fenced_block.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/gcc_arm_fenced_block.hpp new file mode 100644 index 000000000..d032324c9 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/gcc_arm_fenced_block.hpp @@ -0,0 +1,91 @@ +// +// detail/gcc_arm_fenced_block.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_GCC_ARM_FENCED_BLOCK_HPP +#define ASIO_DETAIL_GCC_ARM_FENCED_BLOCK_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(__GNUC__) && defined(__arm__) + +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class gcc_arm_fenced_block + : private noncopyable +{ +public: + enum half_t { half }; + enum full_t { full }; + + // Constructor for a half fenced block. + explicit gcc_arm_fenced_block(half_t) + { + } + + // Constructor for a full fenced block. + explicit gcc_arm_fenced_block(full_t) + { + barrier(); + } + + // Destructor. + ~gcc_arm_fenced_block() + { + barrier(); + } + +private: + static void barrier() + { +#if defined(__ARM_ARCH_4__) \ + || defined(__ARM_ARCH_4T__) \ + || defined(__ARM_ARCH_5__) \ + || defined(__ARM_ARCH_5E__) \ + || defined(__ARM_ARCH_5T__) \ + || defined(__ARM_ARCH_5TE__) \ + || defined(__ARM_ARCH_5TEJ__) \ + || defined(__ARM_ARCH_6__) \ + || defined(__ARM_ARCH_6J__) \ + || defined(__ARM_ARCH_6K__) \ + || defined(__ARM_ARCH_6Z__) \ + || defined(__ARM_ARCH_6ZK__) \ + || defined(__ARM_ARCH_6T2__) +# if defined(__thumb__) + // This is just a placeholder and almost certainly not sufficient. + __asm__ __volatile__ ("" : : : "memory"); +# else // defined(__thumb__) + int a = 0, b = 0; + __asm__ __volatile__ ("swp %0, %1, [%2]" + : "=&r"(a) : "r"(1), "r"(&b) : "memory", "cc"); +# endif // defined(__thumb__) +#else + // ARMv7 and later. + __asm__ __volatile__ ("dmb" : : : "memory"); +#endif + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(__GNUC__) && defined(__arm__) + +#endif // ASIO_DETAIL_GCC_ARM_FENCED_BLOCK_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/gcc_hppa_fenced_block.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/gcc_hppa_fenced_block.hpp new file mode 100644 index 000000000..68f36295f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/gcc_hppa_fenced_block.hpp @@ -0,0 +1,68 @@ +// +// detail/gcc_hppa_fenced_block.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_GCC_HPPA_FENCED_BLOCK_HPP +#define ASIO_DETAIL_GCC_HPPA_FENCED_BLOCK_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(__GNUC__) && (defined(__hppa) || defined(__hppa__)) + +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class gcc_hppa_fenced_block + : private noncopyable +{ +public: + enum half_t { half }; + enum full_t { full }; + + // Constructor for a half fenced block. + explicit gcc_hppa_fenced_block(half_t) + { + } + + // Constructor for a full fenced block. + explicit gcc_hppa_fenced_block(full_t) + { + barrier(); + } + + // Destructor. + ~gcc_hppa_fenced_block() + { + barrier(); + } + +private: + static void barrier() + { + // This is just a placeholder and almost certainly not sufficient. + __asm__ __volatile__ ("" : : : "memory"); + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(__GNUC__) && (defined(__hppa) || defined(__hppa__)) + +#endif // ASIO_DETAIL_GCC_HPPA_FENCED_BLOCK_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/gcc_sync_fenced_block.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/gcc_sync_fenced_block.hpp new file mode 100644 index 000000000..c0c814b33 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/gcc_sync_fenced_block.hpp @@ -0,0 +1,65 @@ +// +// detail/gcc_sync_fenced_block.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_GCC_SYNC_FENCED_BLOCK_HPP +#define ASIO_DETAIL_GCC_SYNC_FENCED_BLOCK_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(__GNUC__) \ + && ((__GNUC__ == 4 && __GNUC_MINOR__ >= 1) || (__GNUC__ > 4)) \ + && !defined(__INTEL_COMPILER) && !defined(__ICL) \ + && !defined(__ICC) && !defined(__ECC) && !defined(__PATHSCALE__) + +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class gcc_sync_fenced_block + : private noncopyable +{ +public: + enum half_or_full_t { half, full }; + + // Constructor. + explicit gcc_sync_fenced_block(half_or_full_t) + : value_(0) + { + __sync_lock_test_and_set(&value_, 1); + } + + // Destructor. + ~gcc_sync_fenced_block() + { + __sync_lock_release(&value_); + } + +private: + int value_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(__GNUC__) + // && ((__GNUC__ == 4 && __GNUC_MINOR__ >= 1) || (__GNUC__ > 4)) + // && !defined(__INTEL_COMPILER) && !defined(__ICL) + // && !defined(__ICC) && !defined(__ECC) && !defined(__PATHSCALE__) + +#endif // ASIO_DETAIL_GCC_SYNC_FENCED_BLOCK_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/gcc_x86_fenced_block.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/gcc_x86_fenced_block.hpp new file mode 100644 index 000000000..422482c87 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/gcc_x86_fenced_block.hpp @@ -0,0 +1,99 @@ +// +// detail/gcc_x86_fenced_block.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_GCC_X86_FENCED_BLOCK_HPP +#define ASIO_DETAIL_GCC_X86_FENCED_BLOCK_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(__GNUC__) && (defined(__i386__) || defined(__x86_64__)) + +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class gcc_x86_fenced_block + : private noncopyable +{ +public: + enum half_t { half }; + enum full_t { full }; + + // Constructor for a half fenced block. + explicit gcc_x86_fenced_block(half_t) + { + } + + // Constructor for a full fenced block. + explicit gcc_x86_fenced_block(full_t) + { + lbarrier(); + } + + // Destructor. + ~gcc_x86_fenced_block() + { + sbarrier(); + } + +private: + static int barrier() + { + int r = 0, m = 1; + __asm__ __volatile__ ( + "xchgl %0, %1" : + "=r"(r), "=m"(m) : + "0"(1), "m"(m) : + "memory", "cc"); + return r; + } + + static void lbarrier() + { +#if defined(__SSE2__) +# if (__GNUC__ >= 4) && !defined(__INTEL_COMPILER) && !defined(__ICL) + __builtin_ia32_lfence(); +# else // (__GNUC__ >= 4) && !defined(__INTEL_COMPILER) && !defined(__ICL) + __asm__ __volatile__ ("lfence" ::: "memory"); +# endif // (__GNUC__ >= 4) && !defined(__INTEL_COMPILER) && !defined(__ICL) +#else // defined(__SSE2__) + barrier(); +#endif // defined(__SSE2__) + } + + static void sbarrier() + { +#if defined(__SSE2__) +# if (__GNUC__ >= 4) && !defined(__INTEL_COMPILER) && !defined(__ICL) + __builtin_ia32_sfence(); +# else // (__GNUC__ >= 4) && !defined(__INTEL_COMPILER) && !defined(__ICL) + __asm__ __volatile__ ("sfence" ::: "memory"); +# endif // (__GNUC__ >= 4) && !defined(__INTEL_COMPILER) && !defined(__ICL) +#else // defined(__SSE2__) + barrier(); +#endif // defined(__SSE2__) + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(__GNUC__) && (defined(__i386__) || defined(__x86_64__)) + +#endif // ASIO_DETAIL_GCC_X86_FENCED_BLOCK_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/global.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/global.hpp new file mode 100644 index 000000000..fad2959fa --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/global.hpp @@ -0,0 +1,52 @@ +// +// detail/global.hpp +// ~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_GLOBAL_HPP +#define ASIO_DETAIL_GLOBAL_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_THREADS) +# include "asio/detail/null_global.hpp" +#elif defined(ASIO_WINDOWS) +# include "asio/detail/win_global.hpp" +#elif defined(ASIO_HAS_PTHREADS) +# include "asio/detail/posix_global.hpp" +#elif defined(ASIO_HAS_STD_CALL_ONCE) +# include "asio/detail/std_global.hpp" +#else +# error Only Windows, POSIX and std::call_once are supported! +#endif + +namespace asio { +namespace detail { + +template +inline T& global() +{ +#if !defined(ASIO_HAS_THREADS) + return null_global(); +#elif defined(ASIO_WINDOWS) + return win_global(); +#elif defined(ASIO_HAS_PTHREADS) + return posix_global(); +#elif defined(ASIO_HAS_STD_CALL_ONCE) + return std_global(); +#endif +} + +} // namespace detail +} // namespace asio + +#endif // ASIO_DETAIL_GLOBAL_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_alloc_helpers.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_alloc_helpers.hpp new file mode 100644 index 000000000..4ddaf93cd --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_alloc_helpers.hpp @@ -0,0 +1,284 @@ +// +// detail/handler_alloc_helpers.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_HANDLER_ALLOC_HELPERS_HPP +#define ASIO_DETAIL_HANDLER_ALLOC_HELPERS_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/recycling_allocator.hpp" +#include "asio/detail/thread_info_base.hpp" +#include "asio/associated_allocator.hpp" +#include "asio/handler_alloc_hook.hpp" + +#include "asio/detail/push_options.hpp" + +// Calls to asio_handler_allocate and asio_handler_deallocate must be made from +// a namespace that does not contain any overloads of these functions. The +// asio_handler_alloc_helpers namespace is defined here for that purpose. +namespace asio_handler_alloc_helpers { + +#if defined(ASIO_NO_DEPRECATED) +template +inline void error_if_hooks_are_defined(Handler& h) +{ + using asio::asio_handler_allocate; + // If you get an error here it is because some of your handlers still + // overload asio_handler_allocate, but this hook is no longer used. + (void)static_cast( + asio_handler_allocate(static_cast(0), + asio::detail::addressof(h))); + + using asio::asio_handler_deallocate; + // If you get an error here it is because some of your handlers still + // overload asio_handler_deallocate, but this hook is no longer used. + (void)static_cast( + asio_handler_deallocate(static_cast(0), + static_cast(0), asio::detail::addressof(h))); +} +#endif // defined(ASIO_NO_DEPRECATED) + +template +inline void* allocate(std::size_t s, Handler& h) +{ +#if !defined(ASIO_HAS_HANDLER_HOOKS) + return ::operator new(s); +#elif defined(ASIO_NO_DEPRECATED) + // The asio_handler_allocate hook is no longer used to obtain memory. + (void)&error_if_hooks_are_defined; + (void)h; +#if !defined(ASIO_DISABLE_SMALL_BLOCK_RECYCLING) + return asio::detail::thread_info_base::allocate( + asio::detail::thread_context::thread_call_stack::top(), s); +#else // !defined(ASIO_DISABLE_SMALL_BLOCK_RECYCLING) + return ::operator new(size); +#endif // !defined(ASIO_DISABLE_SMALL_BLOCK_RECYCLING) +#else + using asio::asio_handler_allocate; + return asio_handler_allocate(s, asio::detail::addressof(h)); +#endif +} + +template +inline void deallocate(void* p, std::size_t s, Handler& h) +{ +#if !defined(ASIO_HAS_HANDLER_HOOKS) + ::operator delete(p); +#elif defined(ASIO_NO_DEPRECATED) + // The asio_handler_allocate hook is no longer used to obtain memory. + (void)&error_if_hooks_are_defined; + (void)h; +#if !defined(ASIO_DISABLE_SMALL_BLOCK_RECYCLING) + asio::detail::thread_info_base::deallocate( + asio::detail::thread_context::thread_call_stack::top(), p, s); +#else // !defined(ASIO_DISABLE_SMALL_BLOCK_RECYCLING) + (void)s; + ::operator delete(p); +#endif // !defined(ASIO_DISABLE_SMALL_BLOCK_RECYCLING) +#else + using asio::asio_handler_deallocate; + asio_handler_deallocate(p, s, asio::detail::addressof(h)); +#endif +} + +} // namespace asio_handler_alloc_helpers + +namespace asio { +namespace detail { + +template +class hook_allocator +{ +public: + typedef T value_type; + + template + struct rebind + { + typedef hook_allocator other; + }; + + explicit hook_allocator(Handler& h) + : handler_(h) + { + } + + template + hook_allocator(const hook_allocator& a) + : handler_(a.handler_) + { + } + + T* allocate(std::size_t n) + { + return static_cast( + asio_handler_alloc_helpers::allocate(sizeof(T) * n, handler_)); + } + + void deallocate(T* p, std::size_t n) + { + asio_handler_alloc_helpers::deallocate(p, sizeof(T) * n, handler_); + } + +//private: + Handler& handler_; +}; + +template +class hook_allocator +{ +public: + typedef void value_type; + + template + struct rebind + { + typedef hook_allocator other; + }; + + explicit hook_allocator(Handler& h) + : handler_(h) + { + } + + template + hook_allocator(const hook_allocator& a) + : handler_(a.handler_) + { + } + +//private: + Handler& handler_; +}; + +template +struct get_hook_allocator +{ + typedef Allocator type; + + static type get(Handler&, const Allocator& a) + { + return a; + } +}; + +template +struct get_hook_allocator > +{ + typedef hook_allocator type; + + static type get(Handler& handler, const std::allocator&) + { + return type(handler); + } +}; + +} // namespace detail +} // namespace asio + +#define ASIO_DEFINE_HANDLER_PTR(op) \ + struct ptr \ + { \ + Handler* h; \ + op* v; \ + op* p; \ + ~ptr() \ + { \ + reset(); \ + } \ + static op* allocate(Handler& handler) \ + { \ + typedef typename ::asio::associated_allocator< \ + Handler>::type associated_allocator_type; \ + typedef typename ::asio::detail::get_hook_allocator< \ + Handler, associated_allocator_type>::type hook_allocator_type; \ + ASIO_REBIND_ALLOC(hook_allocator_type, op) a( \ + ::asio::detail::get_hook_allocator< \ + Handler, associated_allocator_type>::get( \ + handler, ::asio::get_associated_allocator(handler))); \ + return a.allocate(1); \ + } \ + void reset() \ + { \ + if (p) \ + { \ + p->~op(); \ + p = 0; \ + } \ + if (v) \ + { \ + typedef typename ::asio::associated_allocator< \ + Handler>::type associated_allocator_type; \ + typedef typename ::asio::detail::get_hook_allocator< \ + Handler, associated_allocator_type>::type hook_allocator_type; \ + ASIO_REBIND_ALLOC(hook_allocator_type, op) a( \ + ::asio::detail::get_hook_allocator< \ + Handler, associated_allocator_type>::get( \ + *h, ::asio::get_associated_allocator(*h))); \ + a.deallocate(static_cast(v), 1); \ + v = 0; \ + } \ + } \ + } \ + /**/ + +#define ASIO_DEFINE_TAGGED_HANDLER_ALLOCATOR_PTR(purpose, op) \ + struct ptr \ + { \ + const Alloc* a; \ + void* v; \ + op* p; \ + ~ptr() \ + { \ + reset(); \ + } \ + static op* allocate(const Alloc& a) \ + { \ + typedef typename ::asio::detail::get_recycling_allocator< \ + Alloc, purpose>::type recycling_allocator_type; \ + ASIO_REBIND_ALLOC(recycling_allocator_type, op) a1( \ + ::asio::detail::get_recycling_allocator< \ + Alloc, purpose>::get(a)); \ + return a1.allocate(1); \ + } \ + void reset() \ + { \ + if (p) \ + { \ + p->~op(); \ + p = 0; \ + } \ + if (v) \ + { \ + typedef typename ::asio::detail::get_recycling_allocator< \ + Alloc, purpose>::type recycling_allocator_type; \ + ASIO_REBIND_ALLOC(recycling_allocator_type, op) a1( \ + ::asio::detail::get_recycling_allocator< \ + Alloc, purpose>::get(*a)); \ + a1.deallocate(static_cast(v), 1); \ + v = 0; \ + } \ + } \ + } \ + /**/ + +#define ASIO_DEFINE_HANDLER_ALLOCATOR_PTR(op) \ + ASIO_DEFINE_TAGGED_HANDLER_ALLOCATOR_PTR( \ + ::asio::detail::thread_info_base::default_tag, op ) \ + /**/ + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_HANDLER_ALLOC_HELPERS_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_cont_helpers.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_cont_helpers.hpp new file mode 100644 index 000000000..1aaa7e54f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_cont_helpers.hpp @@ -0,0 +1,45 @@ +// +// detail/handler_cont_helpers.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_HANDLER_CONT_HELPERS_HPP +#define ASIO_DETAIL_HANDLER_CONT_HELPERS_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/memory.hpp" +#include "asio/handler_continuation_hook.hpp" + +#include "asio/detail/push_options.hpp" + +// Calls to asio_handler_is_continuation must be made from a namespace that +// does not contain overloads of this function. This namespace is defined here +// for that purpose. +namespace asio_handler_cont_helpers { + +template +inline bool is_continuation(Context& context) +{ +#if !defined(ASIO_HAS_HANDLER_HOOKS) + return false; +#else + using asio::asio_handler_is_continuation; + return asio_handler_is_continuation( + asio::detail::addressof(context)); +#endif +} + +} // namespace asio_handler_cont_helpers + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_HANDLER_CONT_HELPERS_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_invoke_helpers.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_invoke_helpers.hpp new file mode 100644 index 000000000..f2967a986 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_invoke_helpers.hpp @@ -0,0 +1,80 @@ +// +// detail/handler_invoke_helpers.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_HANDLER_INVOKE_HELPERS_HPP +#define ASIO_DETAIL_HANDLER_INVOKE_HELPERS_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/memory.hpp" +#include "asio/handler_invoke_hook.hpp" + +#include "asio/detail/push_options.hpp" + +// Calls to asio_handler_invoke must be made from a namespace that does not +// contain overloads of this function. The asio_handler_invoke_helpers +// namespace is defined here for that purpose. +namespace asio_handler_invoke_helpers { + +#if defined(ASIO_NO_DEPRECATED) +template +inline void error_if_hook_is_defined(Function& function, Context& context) +{ + using asio::asio_handler_invoke; + // If you get an error here it is because some of your handlers still + // overload asio_handler_invoke, but this hook is no longer used. + (void)static_cast( + asio_handler_invoke(function, asio::detail::addressof(context))); +} +#endif // defined(ASIO_NO_DEPRECATED) + +template +inline void invoke(Function& function, Context& context) +{ +#if !defined(ASIO_HAS_HANDLER_HOOKS) + Function tmp(function); + tmp(); +#elif defined(ASIO_NO_DEPRECATED) + // The asio_handler_invoke hook is no longer used to invoke the function. + (void)&error_if_hook_is_defined; + (void)context; + function(); +#else + using asio::asio_handler_invoke; + asio_handler_invoke(function, asio::detail::addressof(context)); +#endif +} + +template +inline void invoke(const Function& function, Context& context) +{ +#if !defined(ASIO_HAS_HANDLER_HOOKS) + Function tmp(function); + tmp(); +#elif defined(ASIO_NO_DEPRECATED) + // The asio_handler_invoke hook is no longer used to invoke the function. + (void)&error_if_hook_is_defined; + (void)context; + Function tmp(function); + tmp(); +#else + using asio::asio_handler_invoke; + asio_handler_invoke(function, asio::detail::addressof(context)); +#endif +} + +} // namespace asio_handler_invoke_helpers + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_HANDLER_INVOKE_HELPERS_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_tracking.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_tracking.hpp new file mode 100644 index 000000000..95cb96f39 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_tracking.hpp @@ -0,0 +1,264 @@ +// +// detail/handler_tracking.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_HANDLER_TRACKING_HPP +#define ASIO_DETAIL_HANDLER_TRACKING_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +namespace asio { + +class execution_context; + +} // namespace asio + +#if defined(ASIO_CUSTOM_HANDLER_TRACKING) +# include ASIO_CUSTOM_HANDLER_TRACKING +#elif defined(ASIO_ENABLE_HANDLER_TRACKING) +# include "asio/error_code.hpp" +# include "asio/detail/cstdint.hpp" +# include "asio/detail/static_mutex.hpp" +# include "asio/detail/tss_ptr.hpp" +#endif // defined(ASIO_ENABLE_HANDLER_TRACKING) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +#if defined(ASIO_CUSTOM_HANDLER_TRACKING) + +// The user-specified header must define the following macros: +// - ASIO_INHERIT_TRACKED_HANDLER +// - ASIO_ALSO_INHERIT_TRACKED_HANDLER +// - ASIO_HANDLER_TRACKING_INIT +// - ASIO_HANDLER_CREATION(args) +// - ASIO_HANDLER_COMPLETION(args) +// - ASIO_HANDLER_INVOCATION_BEGIN(args) +// - ASIO_HANDLER_INVOCATION_END +// - ASIO_HANDLER_OPERATION(args) +// - ASIO_HANDLER_REACTOR_REGISTRATION(args) +// - ASIO_HANDLER_REACTOR_DEREGISTRATION(args) +// - ASIO_HANDLER_REACTOR_READ_EVENT +// - ASIO_HANDLER_REACTOR_WRITE_EVENT +// - ASIO_HANDLER_REACTOR_ERROR_EVENT +// - ASIO_HANDLER_REACTOR_EVENTS(args) +// - ASIO_HANDLER_REACTOR_OPERATION(args) + +# if !defined(ASIO_ENABLE_HANDLER_TRACKING) +# define ASIO_ENABLE_HANDLER_TRACKING 1 +# endif /// !defined(ASIO_ENABLE_HANDLER_TRACKING) + +#elif defined(ASIO_ENABLE_HANDLER_TRACKING) + +class handler_tracking +{ +public: + class completion; + + // Base class for objects containing tracked handlers. + class tracked_handler + { + private: + // Only the handler_tracking class will have access to the id. + friend class handler_tracking; + friend class completion; + uint64_t id_; + + protected: + // Constructor initialises with no id. + tracked_handler() : id_(0) {} + + // Prevent deletion through this type. + ~tracked_handler() {} + }; + + // Initialise the tracking system. + ASIO_DECL static void init(); + + class location + { + public: + // Constructor adds a location to the stack. + ASIO_DECL explicit location(const char* file, + int line, const char* func); + + // Destructor removes a location from the stack. + ASIO_DECL ~location(); + + private: + // Disallow copying and assignment. + location(const location&) ASIO_DELETED; + location& operator=(const location&) ASIO_DELETED; + + friend class handler_tracking; + const char* file_; + int line_; + const char* func_; + location* next_; + }; + + // Record the creation of a tracked handler. + ASIO_DECL static void creation( + execution_context& context, tracked_handler& h, + const char* object_type, void* object, + uintmax_t native_handle, const char* op_name); + + class completion + { + public: + // Constructor records that handler is to be invoked with no arguments. + ASIO_DECL explicit completion(const tracked_handler& h); + + // Destructor records only when an exception is thrown from the handler, or + // if the memory is being freed without the handler having been invoked. + ASIO_DECL ~completion(); + + // Records that handler is to be invoked with no arguments. + ASIO_DECL void invocation_begin(); + + // Records that handler is to be invoked with one arguments. + ASIO_DECL void invocation_begin(const asio::error_code& ec); + + // Constructor records that handler is to be invoked with two arguments. + ASIO_DECL void invocation_begin( + const asio::error_code& ec, std::size_t bytes_transferred); + + // Constructor records that handler is to be invoked with two arguments. + ASIO_DECL void invocation_begin( + const asio::error_code& ec, int signal_number); + + // Constructor records that handler is to be invoked with two arguments. + ASIO_DECL void invocation_begin( + const asio::error_code& ec, const char* arg); + + // Record that handler invocation has ended. + ASIO_DECL void invocation_end(); + + private: + friend class handler_tracking; + uint64_t id_; + bool invoked_; + completion* next_; + }; + + // Record an operation that is not directly associated with a handler. + ASIO_DECL static void operation(execution_context& context, + const char* object_type, void* object, + uintmax_t native_handle, const char* op_name); + + // Record that a descriptor has been registered with the reactor. + ASIO_DECL static void reactor_registration(execution_context& context, + uintmax_t native_handle, uintmax_t registration); + + // Record that a descriptor has been deregistered from the reactor. + ASIO_DECL static void reactor_deregistration(execution_context& context, + uintmax_t native_handle, uintmax_t registration); + + // Record a reactor-based operation that is associated with a handler. + ASIO_DECL static void reactor_events(execution_context& context, + uintmax_t registration, unsigned events); + + // Record a reactor-based operation that is associated with a handler. + ASIO_DECL static void reactor_operation( + const tracked_handler& h, const char* op_name, + const asio::error_code& ec); + + // Record a reactor-based operation that is associated with a handler. + ASIO_DECL static void reactor_operation( + const tracked_handler& h, const char* op_name, + const asio::error_code& ec, std::size_t bytes_transferred); + + // Write a line of output. + ASIO_DECL static void write_line(const char* format, ...); + +private: + struct tracking_state; + ASIO_DECL static tracking_state* get_state(); +}; + +# define ASIO_INHERIT_TRACKED_HANDLER \ + : public asio::detail::handler_tracking::tracked_handler + +# define ASIO_ALSO_INHERIT_TRACKED_HANDLER \ + , public asio::detail::handler_tracking::tracked_handler + +# define ASIO_HANDLER_TRACKING_INIT \ + asio::detail::handler_tracking::init() + +# define ASIO_HANDLER_LOCATION(args) \ + asio::detail::handler_tracking::location tracked_location args + +# define ASIO_HANDLER_CREATION(args) \ + asio::detail::handler_tracking::creation args + +# define ASIO_HANDLER_COMPLETION(args) \ + asio::detail::handler_tracking::completion tracked_completion args + +# define ASIO_HANDLER_INVOCATION_BEGIN(args) \ + tracked_completion.invocation_begin args + +# define ASIO_HANDLER_INVOCATION_END \ + tracked_completion.invocation_end() + +# define ASIO_HANDLER_OPERATION(args) \ + asio::detail::handler_tracking::operation args + +# define ASIO_HANDLER_REACTOR_REGISTRATION(args) \ + asio::detail::handler_tracking::reactor_registration args + +# define ASIO_HANDLER_REACTOR_DEREGISTRATION(args) \ + asio::detail::handler_tracking::reactor_deregistration args + +# define ASIO_HANDLER_REACTOR_READ_EVENT 1 +# define ASIO_HANDLER_REACTOR_WRITE_EVENT 2 +# define ASIO_HANDLER_REACTOR_ERROR_EVENT 4 + +# define ASIO_HANDLER_REACTOR_EVENTS(args) \ + asio::detail::handler_tracking::reactor_events args + +# define ASIO_HANDLER_REACTOR_OPERATION(args) \ + asio::detail::handler_tracking::reactor_operation args + +#else // defined(ASIO_ENABLE_HANDLER_TRACKING) + +# define ASIO_INHERIT_TRACKED_HANDLER +# define ASIO_ALSO_INHERIT_TRACKED_HANDLER +# define ASIO_HANDLER_TRACKING_INIT (void)0 +# define ASIO_HANDLER_LOCATION(loc) (void)0 +# define ASIO_HANDLER_CREATION(args) (void)0 +# define ASIO_HANDLER_COMPLETION(args) (void)0 +# define ASIO_HANDLER_INVOCATION_BEGIN(args) (void)0 +# define ASIO_HANDLER_INVOCATION_END (void)0 +# define ASIO_HANDLER_OPERATION(args) (void)0 +# define ASIO_HANDLER_REACTOR_REGISTRATION(args) (void)0 +# define ASIO_HANDLER_REACTOR_DEREGISTRATION(args) (void)0 +# define ASIO_HANDLER_REACTOR_READ_EVENT 0 +# define ASIO_HANDLER_REACTOR_WRITE_EVENT 0 +# define ASIO_HANDLER_REACTOR_ERROR_EVENT 0 +# define ASIO_HANDLER_REACTOR_EVENTS(args) (void)0 +# define ASIO_HANDLER_REACTOR_OPERATION(args) (void)0 + +#endif // defined(ASIO_ENABLE_HANDLER_TRACKING) + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/handler_tracking.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // ASIO_DETAIL_HANDLER_TRACKING_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_type_requirements.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_type_requirements.hpp new file mode 100644 index 000000000..420b0abe5 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_type_requirements.hpp @@ -0,0 +1,556 @@ +// +// detail/handler_type_requirements.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_HANDLER_TYPE_REQUIREMENTS_HPP +#define ASIO_DETAIL_HANDLER_TYPE_REQUIREMENTS_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +// Older versions of gcc have difficulty compiling the sizeof expressions where +// we test the handler type requirements. We'll disable checking of handler type +// requirements for those compilers, but otherwise enable it by default. +#if !defined(ASIO_DISABLE_HANDLER_TYPE_REQUIREMENTS) +# if !defined(__GNUC__) || (__GNUC__ >= 4) +# define ASIO_ENABLE_HANDLER_TYPE_REQUIREMENTS 1 +# endif // !defined(__GNUC__) || (__GNUC__ >= 4) +#endif // !defined(ASIO_DISABLE_HANDLER_TYPE_REQUIREMENTS) + +// With C++0x we can use a combination of enhanced SFINAE and static_assert to +// generate better template error messages. As this technique is not yet widely +// portable, we'll only enable it for tested compilers. +#if !defined(ASIO_DISABLE_HANDLER_TYPE_REQUIREMENTS_ASSERT) +# if defined(__GNUC__) +# if ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 5)) || (__GNUC__ > 4) +# if defined(__GXX_EXPERIMENTAL_CXX0X__) +# define ASIO_ENABLE_HANDLER_TYPE_REQUIREMENTS_ASSERT 1 +# endif // defined(__GXX_EXPERIMENTAL_CXX0X__) +# endif // ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 5)) || (__GNUC__ > 4) +# endif // defined(__GNUC__) +# if defined(ASIO_MSVC) +# if (_MSC_VER >= 1600) +# define ASIO_ENABLE_HANDLER_TYPE_REQUIREMENTS_ASSERT 1 +# endif // (_MSC_VER >= 1600) +# endif // defined(ASIO_MSVC) +# if defined(__clang__) +# if __has_feature(__cxx_static_assert__) +# define ASIO_ENABLE_HANDLER_TYPE_REQUIREMENTS_ASSERT 1 +# endif // __has_feature(cxx_static_assert) +# endif // defined(__clang__) +#endif // !defined(ASIO_DISABLE_HANDLER_TYPE_REQUIREMENTS) + +#if defined(ASIO_ENABLE_HANDLER_TYPE_REQUIREMENTS) +# include "asio/async_result.hpp" +#endif // defined(ASIO_ENABLE_HANDLER_TYPE_REQUIREMENTS) + +namespace asio { +namespace detail { + +#if defined(ASIO_ENABLE_HANDLER_TYPE_REQUIREMENTS) + +# if defined(ASIO_ENABLE_HANDLER_TYPE_REQUIREMENTS_ASSERT) + +template +auto zero_arg_copyable_handler_test(Handler h, void*) + -> decltype( + sizeof(Handler(static_cast(h))), + ((h)()), + char(0)); + +template +char (&zero_arg_copyable_handler_test(Handler, ...))[2]; + +template +auto one_arg_handler_test(Handler h, Arg1* a1) + -> decltype( + sizeof(Handler(ASIO_MOVE_CAST(Handler)(h))), + ((h)(*a1)), + char(0)); + +template +char (&one_arg_handler_test(Handler h, ...))[2]; + +template +auto two_arg_handler_test(Handler h, Arg1* a1, Arg2* a2) + -> decltype( + sizeof(Handler(ASIO_MOVE_CAST(Handler)(h))), + ((h)(*a1, *a2)), + char(0)); + +template +char (&two_arg_handler_test(Handler, ...))[2]; + +template +auto two_arg_move_handler_test(Handler h, Arg1* a1, Arg2* a2) + -> decltype( + sizeof(Handler(ASIO_MOVE_CAST(Handler)(h))), + ((h)(*a1, ASIO_MOVE_CAST(Arg2)(*a2))), + char(0)); + +template +char (&two_arg_move_handler_test(Handler, ...))[2]; + +# define ASIO_HANDLER_TYPE_REQUIREMENTS_ASSERT(expr, msg) \ + static_assert(expr, msg); + +# else // defined(ASIO_ENABLE_HANDLER_TYPE_REQUIREMENTS_ASSERT) + +# define ASIO_HANDLER_TYPE_REQUIREMENTS_ASSERT(expr, msg) + +# endif // defined(ASIO_ENABLE_HANDLER_TYPE_REQUIREMENTS_ASSERT) + +template T& lvref(); +template T& lvref(T); +template const T& clvref(); +template const T& clvref(T); +#if defined(ASIO_HAS_MOVE) +template T rvref(); +template T rvref(T); +#else // defined(ASIO_HAS_MOVE) +template const T& rvref(); +template const T& rvref(T); +#endif // defined(ASIO_HAS_MOVE) +template char argbyv(T); + +template +struct handler_type_requirements +{ +}; + +#define ASIO_LEGACY_COMPLETION_HANDLER_CHECK( \ + handler_type, handler) \ + \ + typedef ASIO_HANDLER_TYPE(handler_type, \ + void()) asio_true_handler_type; \ + \ + ASIO_HANDLER_TYPE_REQUIREMENTS_ASSERT( \ + sizeof(asio::detail::zero_arg_copyable_handler_test( \ + asio::detail::clvref< \ + asio_true_handler_type>(), 0)) == 1, \ + "CompletionHandler type requirements not met") \ + \ + typedef asio::detail::handler_type_requirements< \ + sizeof( \ + asio::detail::argbyv( \ + asio::detail::clvref< \ + asio_true_handler_type>())) + \ + sizeof( \ + asio::detail::lvref< \ + asio_true_handler_type>()(), \ + char(0))> ASIO_UNUSED_TYPEDEF + +#define ASIO_READ_HANDLER_CHECK( \ + handler_type, handler) \ + \ + typedef ASIO_HANDLER_TYPE(handler_type, \ + void(asio::error_code, std::size_t)) \ + asio_true_handler_type; \ + \ + ASIO_HANDLER_TYPE_REQUIREMENTS_ASSERT( \ + sizeof(asio::detail::two_arg_handler_test( \ + asio::detail::rvref< \ + asio_true_handler_type>(), \ + static_cast(0), \ + static_cast(0))) == 1, \ + "ReadHandler type requirements not met") \ + \ + typedef asio::detail::handler_type_requirements< \ + sizeof( \ + asio::detail::argbyv( \ + asio::detail::rvref< \ + asio_true_handler_type>())) + \ + sizeof( \ + asio::detail::lvref< \ + asio_true_handler_type>()( \ + asio::detail::lvref(), \ + asio::detail::lvref()), \ + char(0))> ASIO_UNUSED_TYPEDEF + +#define ASIO_WRITE_HANDLER_CHECK( \ + handler_type, handler) \ + \ + typedef ASIO_HANDLER_TYPE(handler_type, \ + void(asio::error_code, std::size_t)) \ + asio_true_handler_type; \ + \ + ASIO_HANDLER_TYPE_REQUIREMENTS_ASSERT( \ + sizeof(asio::detail::two_arg_handler_test( \ + asio::detail::rvref< \ + asio_true_handler_type>(), \ + static_cast(0), \ + static_cast(0))) == 1, \ + "WriteHandler type requirements not met") \ + \ + typedef asio::detail::handler_type_requirements< \ + sizeof( \ + asio::detail::argbyv( \ + asio::detail::rvref< \ + asio_true_handler_type>())) + \ + sizeof( \ + asio::detail::lvref< \ + asio_true_handler_type>()( \ + asio::detail::lvref(), \ + asio::detail::lvref()), \ + char(0))> ASIO_UNUSED_TYPEDEF + +#define ASIO_ACCEPT_HANDLER_CHECK( \ + handler_type, handler) \ + \ + typedef ASIO_HANDLER_TYPE(handler_type, \ + void(asio::error_code)) \ + asio_true_handler_type; \ + \ + ASIO_HANDLER_TYPE_REQUIREMENTS_ASSERT( \ + sizeof(asio::detail::one_arg_handler_test( \ + asio::detail::rvref< \ + asio_true_handler_type>(), \ + static_cast(0))) == 1, \ + "AcceptHandler type requirements not met") \ + \ + typedef asio::detail::handler_type_requirements< \ + sizeof( \ + asio::detail::argbyv( \ + asio::detail::rvref< \ + asio_true_handler_type>())) + \ + sizeof( \ + asio::detail::lvref< \ + asio_true_handler_type>()( \ + asio::detail::lvref()), \ + char(0))> ASIO_UNUSED_TYPEDEF + +#define ASIO_MOVE_ACCEPT_HANDLER_CHECK( \ + handler_type, handler, socket_type) \ + \ + typedef ASIO_HANDLER_TYPE(handler_type, \ + void(asio::error_code, socket_type)) \ + asio_true_handler_type; \ + \ + ASIO_HANDLER_TYPE_REQUIREMENTS_ASSERT( \ + sizeof(asio::detail::two_arg_move_handler_test( \ + asio::detail::rvref< \ + asio_true_handler_type>(), \ + static_cast(0), \ + static_cast(0))) == 1, \ + "MoveAcceptHandler type requirements not met") \ + \ + typedef asio::detail::handler_type_requirements< \ + sizeof( \ + asio::detail::argbyv( \ + asio::detail::rvref< \ + asio_true_handler_type>())) + \ + sizeof( \ + asio::detail::lvref< \ + asio_true_handler_type>()( \ + asio::detail::lvref(), \ + asio::detail::rvref()), \ + char(0))> ASIO_UNUSED_TYPEDEF + +#define ASIO_CONNECT_HANDLER_CHECK( \ + handler_type, handler) \ + \ + typedef ASIO_HANDLER_TYPE(handler_type, \ + void(asio::error_code)) \ + asio_true_handler_type; \ + \ + ASIO_HANDLER_TYPE_REQUIREMENTS_ASSERT( \ + sizeof(asio::detail::one_arg_handler_test( \ + asio::detail::rvref< \ + asio_true_handler_type>(), \ + static_cast(0))) == 1, \ + "ConnectHandler type requirements not met") \ + \ + typedef asio::detail::handler_type_requirements< \ + sizeof( \ + asio::detail::argbyv( \ + asio::detail::rvref< \ + asio_true_handler_type>())) + \ + sizeof( \ + asio::detail::lvref< \ + asio_true_handler_type>()( \ + asio::detail::lvref()), \ + char(0))> ASIO_UNUSED_TYPEDEF + +#define ASIO_RANGE_CONNECT_HANDLER_CHECK( \ + handler_type, handler, endpoint_type) \ + \ + typedef ASIO_HANDLER_TYPE(handler_type, \ + void(asio::error_code, endpoint_type)) \ + asio_true_handler_type; \ + \ + ASIO_HANDLER_TYPE_REQUIREMENTS_ASSERT( \ + sizeof(asio::detail::two_arg_handler_test( \ + asio::detail::rvref< \ + asio_true_handler_type>(), \ + static_cast(0), \ + static_cast(0))) == 1, \ + "RangeConnectHandler type requirements not met") \ + \ + typedef asio::detail::handler_type_requirements< \ + sizeof( \ + asio::detail::argbyv( \ + asio::detail::rvref< \ + asio_true_handler_type>())) + \ + sizeof( \ + asio::detail::lvref< \ + asio_true_handler_type>()( \ + asio::detail::lvref(), \ + asio::detail::lvref()), \ + char(0))> ASIO_UNUSED_TYPEDEF + +#define ASIO_ITERATOR_CONNECT_HANDLER_CHECK( \ + handler_type, handler, iter_type) \ + \ + typedef ASIO_HANDLER_TYPE(handler_type, \ + void(asio::error_code, iter_type)) \ + asio_true_handler_type; \ + \ + ASIO_HANDLER_TYPE_REQUIREMENTS_ASSERT( \ + sizeof(asio::detail::two_arg_handler_test( \ + asio::detail::rvref< \ + asio_true_handler_type>(), \ + static_cast(0), \ + static_cast(0))) == 1, \ + "IteratorConnectHandler type requirements not met") \ + \ + typedef asio::detail::handler_type_requirements< \ + sizeof( \ + asio::detail::argbyv( \ + asio::detail::rvref< \ + asio_true_handler_type>())) + \ + sizeof( \ + asio::detail::lvref< \ + asio_true_handler_type>()( \ + asio::detail::lvref(), \ + asio::detail::lvref()), \ + char(0))> ASIO_UNUSED_TYPEDEF + +#define ASIO_RESOLVE_HANDLER_CHECK( \ + handler_type, handler, range_type) \ + \ + typedef ASIO_HANDLER_TYPE(handler_type, \ + void(asio::error_code, range_type)) \ + asio_true_handler_type; \ + \ + ASIO_HANDLER_TYPE_REQUIREMENTS_ASSERT( \ + sizeof(asio::detail::two_arg_handler_test( \ + asio::detail::rvref< \ + asio_true_handler_type>(), \ + static_cast(0), \ + static_cast(0))) == 1, \ + "ResolveHandler type requirements not met") \ + \ + typedef asio::detail::handler_type_requirements< \ + sizeof( \ + asio::detail::argbyv( \ + asio::detail::rvref< \ + asio_true_handler_type>())) + \ + sizeof( \ + asio::detail::lvref< \ + asio_true_handler_type>()( \ + asio::detail::lvref(), \ + asio::detail::lvref()), \ + char(0))> ASIO_UNUSED_TYPEDEF + +#define ASIO_WAIT_HANDLER_CHECK( \ + handler_type, handler) \ + \ + typedef ASIO_HANDLER_TYPE(handler_type, \ + void(asio::error_code)) \ + asio_true_handler_type; \ + \ + ASIO_HANDLER_TYPE_REQUIREMENTS_ASSERT( \ + sizeof(asio::detail::one_arg_handler_test( \ + asio::detail::rvref< \ + asio_true_handler_type>(), \ + static_cast(0))) == 1, \ + "WaitHandler type requirements not met") \ + \ + typedef asio::detail::handler_type_requirements< \ + sizeof( \ + asio::detail::argbyv( \ + asio::detail::rvref< \ + asio_true_handler_type>())) + \ + sizeof( \ + asio::detail::lvref< \ + asio_true_handler_type>()( \ + asio::detail::lvref()), \ + char(0))> ASIO_UNUSED_TYPEDEF + +#define ASIO_SIGNAL_HANDLER_CHECK( \ + handler_type, handler) \ + \ + typedef ASIO_HANDLER_TYPE(handler_type, \ + void(asio::error_code, int)) \ + asio_true_handler_type; \ + \ + ASIO_HANDLER_TYPE_REQUIREMENTS_ASSERT( \ + sizeof(asio::detail::two_arg_handler_test( \ + asio::detail::rvref< \ + asio_true_handler_type>(), \ + static_cast(0), \ + static_cast(0))) == 1, \ + "SignalHandler type requirements not met") \ + \ + typedef asio::detail::handler_type_requirements< \ + sizeof( \ + asio::detail::argbyv( \ + asio::detail::rvref< \ + asio_true_handler_type>())) + \ + sizeof( \ + asio::detail::lvref< \ + asio_true_handler_type>()( \ + asio::detail::lvref(), \ + asio::detail::lvref()), \ + char(0))> ASIO_UNUSED_TYPEDEF + +#define ASIO_HANDSHAKE_HANDLER_CHECK( \ + handler_type, handler) \ + \ + typedef ASIO_HANDLER_TYPE(handler_type, \ + void(asio::error_code)) \ + asio_true_handler_type; \ + \ + ASIO_HANDLER_TYPE_REQUIREMENTS_ASSERT( \ + sizeof(asio::detail::one_arg_handler_test( \ + asio::detail::rvref< \ + asio_true_handler_type>(), \ + static_cast(0))) == 1, \ + "HandshakeHandler type requirements not met") \ + \ + typedef asio::detail::handler_type_requirements< \ + sizeof( \ + asio::detail::argbyv( \ + asio::detail::rvref< \ + asio_true_handler_type>())) + \ + sizeof( \ + asio::detail::lvref< \ + asio_true_handler_type>()( \ + asio::detail::lvref()), \ + char(0))> ASIO_UNUSED_TYPEDEF + +#define ASIO_BUFFERED_HANDSHAKE_HANDLER_CHECK( \ + handler_type, handler) \ + \ + typedef ASIO_HANDLER_TYPE(handler_type, \ + void(asio::error_code, std::size_t)) \ + asio_true_handler_type; \ + \ + ASIO_HANDLER_TYPE_REQUIREMENTS_ASSERT( \ + sizeof(asio::detail::two_arg_handler_test( \ + asio::detail::rvref< \ + asio_true_handler_type>(), \ + static_cast(0), \ + static_cast(0))) == 1, \ + "BufferedHandshakeHandler type requirements not met") \ + \ + typedef asio::detail::handler_type_requirements< \ + sizeof( \ + asio::detail::argbyv( \ + asio::detail::rvref< \ + asio_true_handler_type>())) + \ + sizeof( \ + asio::detail::lvref< \ + asio_true_handler_type>()( \ + asio::detail::lvref(), \ + asio::detail::lvref()), \ + char(0))> ASIO_UNUSED_TYPEDEF + +#define ASIO_SHUTDOWN_HANDLER_CHECK( \ + handler_type, handler) \ + \ + typedef ASIO_HANDLER_TYPE(handler_type, \ + void(asio::error_code)) \ + asio_true_handler_type; \ + \ + ASIO_HANDLER_TYPE_REQUIREMENTS_ASSERT( \ + sizeof(asio::detail::one_arg_handler_test( \ + asio::detail::rvref< \ + asio_true_handler_type>(), \ + static_cast(0))) == 1, \ + "ShutdownHandler type requirements not met") \ + \ + typedef asio::detail::handler_type_requirements< \ + sizeof( \ + asio::detail::argbyv( \ + asio::detail::rvref< \ + asio_true_handler_type>())) + \ + sizeof( \ + asio::detail::lvref< \ + asio_true_handler_type>()( \ + asio::detail::lvref()), \ + char(0))> ASIO_UNUSED_TYPEDEF + +#else // !defined(ASIO_ENABLE_HANDLER_TYPE_REQUIREMENTS) + +#define ASIO_LEGACY_COMPLETION_HANDLER_CHECK( \ + handler_type, handler) \ + typedef int ASIO_UNUSED_TYPEDEF + +#define ASIO_READ_HANDLER_CHECK( \ + handler_type, handler) \ + typedef int ASIO_UNUSED_TYPEDEF + +#define ASIO_WRITE_HANDLER_CHECK( \ + handler_type, handler) \ + typedef int ASIO_UNUSED_TYPEDEF + +#define ASIO_ACCEPT_HANDLER_CHECK( \ + handler_type, handler) \ + typedef int ASIO_UNUSED_TYPEDEF + +#define ASIO_MOVE_ACCEPT_HANDLER_CHECK( \ + handler_type, handler, socket_type) \ + typedef int ASIO_UNUSED_TYPEDEF + +#define ASIO_CONNECT_HANDLER_CHECK( \ + handler_type, handler) \ + typedef int ASIO_UNUSED_TYPEDEF + +#define ASIO_RANGE_CONNECT_HANDLER_CHECK( \ + handler_type, handler, iter_type) \ + typedef int ASIO_UNUSED_TYPEDEF + +#define ASIO_ITERATOR_CONNECT_HANDLER_CHECK( \ + handler_type, handler, iter_type) \ + typedef int ASIO_UNUSED_TYPEDEF + +#define ASIO_RESOLVE_HANDLER_CHECK( \ + handler_type, handler, iter_type) \ + typedef int ASIO_UNUSED_TYPEDEF + +#define ASIO_WAIT_HANDLER_CHECK( \ + handler_type, handler) \ + typedef int ASIO_UNUSED_TYPEDEF + +#define ASIO_SIGNAL_HANDLER_CHECK( \ + handler_type, handler) \ + typedef int ASIO_UNUSED_TYPEDEF + +#define ASIO_HANDSHAKE_HANDLER_CHECK( \ + handler_type, handler) \ + typedef int ASIO_UNUSED_TYPEDEF + +#define ASIO_BUFFERED_HANDSHAKE_HANDLER_CHECK( \ + handler_type, handler) \ + typedef int ASIO_UNUSED_TYPEDEF + +#define ASIO_SHUTDOWN_HANDLER_CHECK( \ + handler_type, handler) \ + typedef int ASIO_UNUSED_TYPEDEF + +#endif // !defined(ASIO_ENABLE_HANDLER_TYPE_REQUIREMENTS) + +} // namespace detail +} // namespace asio + +#endif // ASIO_DETAIL_HANDLER_TYPE_REQUIREMENTS_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_work.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_work.hpp new file mode 100644 index 000000000..2475aa849 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/handler_work.hpp @@ -0,0 +1,438 @@ +// +// detail/handler_work.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_HANDLER_WORK_HPP +#define ASIO_DETAIL_HANDLER_WORK_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/associated_executor.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/allocator.hpp" +#include "asio/execution/blocking.hpp" +#include "asio/execution/execute.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/outstanding_work.hpp" +#include "asio/executor_work_guard.hpp" +#include "asio/prefer.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +class executor; +class io_context; + +namespace execution { + +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template class any_executor; + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template class any_executor; + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +} // namespace execution +namespace detail { + +template +class handler_work_base +{ +public: + explicit handler_work_base(const Executor& ex) ASIO_NOEXCEPT + : executor_(asio::prefer(ex, execution::outstanding_work.tracked)) + { + } + + template + handler_work_base(const Executor& ex, + const OtherExecutor&) ASIO_NOEXCEPT + : executor_(asio::prefer(ex, execution::outstanding_work.tracked)) + { + } + + handler_work_base(const handler_work_base& other) ASIO_NOEXCEPT + : executor_(other.executor_) + { + } + +#if defined(ASIO_HAS_MOVE) + handler_work_base(handler_work_base&& other) ASIO_NOEXCEPT + : executor_(ASIO_MOVE_CAST(executor_type)(other.executor_)) + { + } +#endif // defined(ASIO_HAS_MOVE) + + bool owns_work() const ASIO_NOEXCEPT + { + return true; + } + + template + void dispatch(Function& function, Handler& handler) + { + execution::execute( + asio::prefer(executor_, + execution::blocking.possibly, + execution::allocator((get_associated_allocator)(handler))), + ASIO_MOVE_CAST(Function)(function)); + } + +private: + typedef typename decay< + typename prefer_result::type + >::type executor_type; + + executor_type executor_; +}; + +template +class handler_work_base::value + && (!is_same::value + || !is_same::value) + >::type> +{ +public: + explicit handler_work_base(const Executor& ex) ASIO_NOEXCEPT + : executor_(ex), + owns_work_(true) + { + executor_.on_work_started(); + } + + handler_work_base(const Executor& ex, + const Executor& candidate) ASIO_NOEXCEPT + : executor_(ex), + owns_work_(ex != candidate) + { + if (owns_work_) + executor_.on_work_started(); + } + + template + handler_work_base(const Executor& ex, + const OtherExecutor&) ASIO_NOEXCEPT + : executor_(ex), + owns_work_(true) + { + executor_.on_work_started(); + } + + handler_work_base(const handler_work_base& other) ASIO_NOEXCEPT + : executor_(other.executor_), + owns_work_(other.owns_work_) + { + if (owns_work_) + executor_.on_work_started(); + } + +#if defined(ASIO_HAS_MOVE) + handler_work_base(handler_work_base&& other) ASIO_NOEXCEPT + : executor_(ASIO_MOVE_CAST(Executor)(other.executor_)), + owns_work_(other.owns_work_) + { + other.owns_work_ = false; + } +#endif // defined(ASIO_HAS_MOVE) + + ~handler_work_base() + { + if (owns_work_) + executor_.on_work_finished(); + } + + bool owns_work() const ASIO_NOEXCEPT + { + return owns_work_; + } + + template + void dispatch(Function& function, Handler& handler) + { + executor_.dispatch(ASIO_MOVE_CAST(Function)(function), + asio::get_associated_allocator(handler)); + } + +private: + Executor executor_; + bool owns_work_; +}; + +template +class handler_work_base::value + >::type> +{ +public: + explicit handler_work_base(const Executor&) + { + } + + bool owns_work() const ASIO_NOEXCEPT + { + return false; + } + + template + void dispatch(Function& function, Handler& handler) + { + // When using a native implementation, I/O completion handlers are + // already dispatched according to the execution context's executor's + // rules. We can call the function directly. + asio_handler_invoke_helpers::invoke(function, handler); + } +}; + +template +class handler_work_base +{ +public: + explicit handler_work_base(const Executor& ex) ASIO_NOEXCEPT +#if !defined(ASIO_NO_TYPEID) + : executor_( + ex.target_type() == typeid(typename IoContext::executor_type) + ? Executor() : ex) +#else // !defined(ASIO_NO_TYPEID) + : executor_(ex) +#endif // !defined(ASIO_NO_TYPEID) + { + if (executor_) + executor_.on_work_started(); + } + + handler_work_base(const Executor& ex, + const Executor& candidate) ASIO_NOEXCEPT + : executor_(ex != candidate ? ex : Executor()) + { + if (executor_) + executor_.on_work_started(); + } + + template + handler_work_base(const Executor& ex, + const OtherExecutor&) ASIO_NOEXCEPT + : executor_(ex) + { + executor_.on_work_started(); + } + + handler_work_base(const handler_work_base& other) ASIO_NOEXCEPT + : executor_(other.executor_) + { + if (executor_) + executor_.on_work_started(); + } + +#if defined(ASIO_HAS_MOVE) + handler_work_base(handler_work_base&& other) ASIO_NOEXCEPT + : executor_(ASIO_MOVE_CAST(Executor)(other.executor_)) + { + } +#endif // defined(ASIO_HAS_MOVE) + + ~handler_work_base() + { + if (executor_) + executor_.on_work_finished(); + } + + bool owns_work() const ASIO_NOEXCEPT + { + return !!executor_; + } + + template + void dispatch(Function& function, Handler& handler) + { + executor_.dispatch(ASIO_MOVE_CAST(Function)(function), + asio::get_associated_allocator(handler)); + } + +private: + Executor executor_; +}; + +template < +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) + typename... SupportableProperties, +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + typename T1, typename T2, typename T3, typename T4, typename T5, + typename T6, typename T7, typename T8, typename T9, +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) + typename IoContext, typename PolymorphicExecutor> +class handler_work_base< +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) + execution::any_executor, +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + execution::any_executor, +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) + void, IoContext, PolymorphicExecutor> +{ +public: + typedef +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) + execution::any_executor +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + execution::any_executor +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) + executor_type; + + explicit handler_work_base(const executor_type& ex) ASIO_NOEXCEPT +#if !defined(ASIO_NO_TYPEID) + : executor_( + ex.target_type() == typeid(typename IoContext::executor_type) + ? executor_type() + : asio::prefer(ex, execution::outstanding_work.tracked)) +#else // !defined(ASIO_NO_TYPEID) + : executor_(asio::prefer(ex, execution::outstanding_work.tracked)) +#endif // !defined(ASIO_NO_TYPEID) + { + } + + handler_work_base(const executor_type& ex, + const executor_type& candidate) ASIO_NOEXCEPT + : executor_(ex != candidate ? ex : executor_type()) + { + } + + template + handler_work_base(const executor_type& ex, + const OtherExecutor&) ASIO_NOEXCEPT + : executor_(asio::prefer(ex, execution::outstanding_work.tracked)) + { + } + + handler_work_base(const handler_work_base& other) ASIO_NOEXCEPT + : executor_(other.executor_) + { + } + +#if defined(ASIO_HAS_MOVE) + handler_work_base(handler_work_base&& other) ASIO_NOEXCEPT + : executor_(ASIO_MOVE_CAST(executor_type)(other.executor_)) + { + } +#endif // defined(ASIO_HAS_MOVE) + + bool owns_work() const ASIO_NOEXCEPT + { + return !!executor_; + } + + template + void dispatch(Function& function, Handler& handler) + { + execution::execute( + asio::prefer(executor_, + execution::blocking.possibly, + execution::allocator((get_associated_allocator)(handler))), + ASIO_MOVE_CAST(Function)(function)); + } + +private: + executor_type executor_; +}; + +template +class handler_work : + handler_work_base, + handler_work_base::type, IoExecutor> +{ +public: + typedef handler_work_base base1_type; + typedef handler_work_base::type, IoExecutor> base2_type; + + handler_work(Handler& handler, const IoExecutor& io_ex) ASIO_NOEXCEPT + : base1_type(io_ex), + base2_type(asio::get_associated_executor(handler, io_ex), io_ex) + { + } + + template + void complete(Function& function, Handler& handler) + { + if (!base1_type::owns_work() && !base2_type::owns_work()) + { + // When using a native implementation, I/O completion handlers are + // already dispatched according to the execution context's executor's + // rules. We can call the function directly. + asio_handler_invoke_helpers::invoke(function, handler); + } + else + { + base2_type::dispatch(function, handler); + } + } +}; + +template +class handler_work< + Handler, IoExecutor, + typename enable_if< + is_same< + typename associated_executor::asio_associated_executor_is_unspecialised, + void + >::value + >::type> : handler_work_base +{ +public: + typedef handler_work_base base1_type; + + handler_work(Handler&, const IoExecutor& io_ex) ASIO_NOEXCEPT + : base1_type(io_ex) + { + } + + template + void complete(Function& function, Handler& handler) + { + if (!base1_type::owns_work()) + { + // When using a native implementation, I/O completion handlers are + // already dispatched according to the execution context's executor's + // rules. We can call the function directly. + asio_handler_invoke_helpers::invoke(function, handler); + } + else + { + base1_type::dispatch(function, handler); + } + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_HANDLER_WORK_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/hash_map.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/hash_map.hpp new file mode 100644 index 000000000..2fdc473c0 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/hash_map.hpp @@ -0,0 +1,331 @@ +// +// detail/hash_map.hpp +// ~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_HASH_MAP_HPP +#define ASIO_DETAIL_HASH_MAP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include +#include "asio/detail/assert.hpp" +#include "asio/detail/noncopyable.hpp" + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) +# include "asio/detail/socket_types.hpp" +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +inline std::size_t calculate_hash_value(int i) +{ + return static_cast(i); +} + +inline std::size_t calculate_hash_value(void* p) +{ + return reinterpret_cast(p) + + (reinterpret_cast(p) >> 3); +} + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) +inline std::size_t calculate_hash_value(SOCKET s) +{ + return static_cast(s); +} +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +// Note: assumes K and V are POD types. +template +class hash_map + : private noncopyable +{ +public: + // The type of a value in the map. + typedef std::pair value_type; + + // The type of a non-const iterator over the hash map. + typedef typename std::list::iterator iterator; + + // The type of a const iterator over the hash map. + typedef typename std::list::const_iterator const_iterator; + + // Constructor. + hash_map() + : size_(0), + buckets_(0), + num_buckets_(0) + { + } + + // Destructor. + ~hash_map() + { + delete[] buckets_; + } + + // Get an iterator for the beginning of the map. + iterator begin() + { + return values_.begin(); + } + + // Get an iterator for the beginning of the map. + const_iterator begin() const + { + return values_.begin(); + } + + // Get an iterator for the end of the map. + iterator end() + { + return values_.end(); + } + + // Get an iterator for the end of the map. + const_iterator end() const + { + return values_.end(); + } + + // Check whether the map is empty. + bool empty() const + { + return values_.empty(); + } + + // Find an entry in the map. + iterator find(const K& k) + { + if (num_buckets_) + { + size_t bucket = calculate_hash_value(k) % num_buckets_; + iterator it = buckets_[bucket].first; + if (it == values_.end()) + return values_.end(); + iterator end_it = buckets_[bucket].last; + ++end_it; + while (it != end_it) + { + if (it->first == k) + return it; + ++it; + } + } + return values_.end(); + } + + // Find an entry in the map. + const_iterator find(const K& k) const + { + if (num_buckets_) + { + size_t bucket = calculate_hash_value(k) % num_buckets_; + const_iterator it = buckets_[bucket].first; + if (it == values_.end()) + return it; + const_iterator end_it = buckets_[bucket].last; + ++end_it; + while (it != end_it) + { + if (it->first == k) + return it; + ++it; + } + } + return values_.end(); + } + + // Insert a new entry into the map. + std::pair insert(const value_type& v) + { + if (size_ + 1 >= num_buckets_) + rehash(hash_size(size_ + 1)); + size_t bucket = calculate_hash_value(v.first) % num_buckets_; + iterator it = buckets_[bucket].first; + if (it == values_.end()) + { + buckets_[bucket].first = buckets_[bucket].last = + values_insert(values_.end(), v); + ++size_; + return std::pair(buckets_[bucket].last, true); + } + iterator end_it = buckets_[bucket].last; + ++end_it; + while (it != end_it) + { + if (it->first == v.first) + return std::pair(it, false); + ++it; + } + buckets_[bucket].last = values_insert(end_it, v); + ++size_; + return std::pair(buckets_[bucket].last, true); + } + + // Erase an entry from the map. + void erase(iterator it) + { + ASIO_ASSERT(it != values_.end()); + ASIO_ASSERT(num_buckets_ != 0); + + size_t bucket = calculate_hash_value(it->first) % num_buckets_; + bool is_first = (it == buckets_[bucket].first); + bool is_last = (it == buckets_[bucket].last); + if (is_first && is_last) + buckets_[bucket].first = buckets_[bucket].last = values_.end(); + else if (is_first) + ++buckets_[bucket].first; + else if (is_last) + --buckets_[bucket].last; + + values_erase(it); + --size_; + } + + // Erase a key from the map. + void erase(const K& k) + { + iterator it = find(k); + if (it != values_.end()) + erase(it); + } + + // Remove all entries from the map. + void clear() + { + // Clear the values. + values_.clear(); + size_ = 0; + + // Initialise all buckets to empty. + iterator end_it = values_.end(); + for (size_t i = 0; i < num_buckets_; ++i) + buckets_[i].first = buckets_[i].last = end_it; + } + +private: + // Calculate the hash size for the specified number of elements. + static std::size_t hash_size(std::size_t num_elems) + { + static std::size_t sizes[] = + { +#if defined(ASIO_HASH_MAP_BUCKETS) + ASIO_HASH_MAP_BUCKETS +#else // ASIO_HASH_MAP_BUCKETS + 3, 13, 23, 53, 97, 193, 389, 769, 1543, 3079, 6151, 12289, 24593, + 49157, 98317, 196613, 393241, 786433, 1572869, 3145739, 6291469, + 12582917, 25165843 +#endif // ASIO_HASH_MAP_BUCKETS + }; + const std::size_t nth_size = sizeof(sizes) / sizeof(std::size_t) - 1; + for (std::size_t i = 0; i < nth_size; ++i) + if (num_elems < sizes[i]) + return sizes[i]; + return sizes[nth_size]; + } + + // Re-initialise the hash from the values already contained in the list. + void rehash(std::size_t num_buckets) + { + if (num_buckets == num_buckets_) + return; + ASIO_ASSERT(num_buckets != 0); + + iterator end_iter = values_.end(); + + // Update number of buckets and initialise all buckets to empty. + bucket_type* tmp = new bucket_type[num_buckets]; + delete[] buckets_; + buckets_ = tmp; + num_buckets_ = num_buckets; + for (std::size_t i = 0; i < num_buckets_; ++i) + buckets_[i].first = buckets_[i].last = end_iter; + + // Put all values back into the hash. + iterator iter = values_.begin(); + while (iter != end_iter) + { + std::size_t bucket = calculate_hash_value(iter->first) % num_buckets_; + if (buckets_[bucket].last == end_iter) + { + buckets_[bucket].first = buckets_[bucket].last = iter++; + } + else if (++buckets_[bucket].last == iter) + { + ++iter; + } + else + { + values_.splice(buckets_[bucket].last, values_, iter++); + --buckets_[bucket].last; + } + } + } + + // Insert an element into the values list by splicing from the spares list, + // if a spare is available, and otherwise by inserting a new element. + iterator values_insert(iterator it, const value_type& v) + { + if (spares_.empty()) + { + return values_.insert(it, v); + } + else + { + spares_.front() = v; + values_.splice(it, spares_, spares_.begin()); + return --it; + } + } + + // Erase an element from the values list by splicing it to the spares list. + void values_erase(iterator it) + { + *it = value_type(); + spares_.splice(spares_.begin(), values_, it); + } + + // The number of elements in the hash. + std::size_t size_; + + // The list of all values in the hash map. + std::list values_; + + // The list of spare nodes waiting to be recycled. Assumes that POD types only + // are stored in the hash map. + std::list spares_; + + // The type for a bucket in the hash table. + struct bucket_type + { + iterator first; + iterator last; + }; + + // The buckets in the hash. + bucket_type* buckets_; + + // The number of buckets in the hash. + std::size_t num_buckets_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_HASH_MAP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/buffer_sequence_adapter.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/buffer_sequence_adapter.ipp new file mode 100644 index 000000000..7bf2b0a91 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/buffer_sequence_adapter.ipp @@ -0,0 +1,118 @@ +// +// detail/impl/buffer_sequence_adapter.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_BUFFER_SEQUENCE_ADAPTER_IPP +#define ASIO_DETAIL_IMPL_BUFFER_SEQUENCE_ADAPTER_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) + +#include +#include +#include +#include "asio/detail/buffer_sequence_adapter.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class winrt_buffer_impl : + public Microsoft::WRL::RuntimeClass< + Microsoft::WRL::RuntimeClassFlags< + Microsoft::WRL::RuntimeClassType::WinRtClassicComMix>, + ABI::Windows::Storage::Streams::IBuffer, + Windows::Storage::Streams::IBufferByteAccess> +{ +public: + explicit winrt_buffer_impl(const asio::const_buffer& b) + { + bytes_ = const_cast(static_cast(b.data())); + length_ = b.size(); + capacity_ = b.size(); + } + + explicit winrt_buffer_impl(const asio::mutable_buffer& b) + { + bytes_ = static_cast(b.data()); + length_ = 0; + capacity_ = b.size(); + } + + ~winrt_buffer_impl() + { + } + + STDMETHODIMP Buffer(byte** value) + { + *value = bytes_; + return S_OK; + } + + STDMETHODIMP get_Capacity(UINT32* value) + { + *value = capacity_; + return S_OK; + } + + STDMETHODIMP get_Length(UINT32 *value) + { + *value = length_; + return S_OK; + } + + STDMETHODIMP put_Length(UINT32 value) + { + if (value > capacity_) + return E_INVALIDARG; + length_ = value; + return S_OK; + } + +private: + byte* bytes_; + UINT32 length_; + UINT32 capacity_; +}; + +void buffer_sequence_adapter_base::init_native_buffer( + buffer_sequence_adapter_base::native_buffer_type& buf, + const asio::mutable_buffer& buffer) +{ + std::memset(&buf, 0, sizeof(native_buffer_type)); + Microsoft::WRL::ComPtr insp + = Microsoft::WRL::Make(buffer); + buf = reinterpret_cast(insp.Get()); +} + +void buffer_sequence_adapter_base::init_native_buffer( + buffer_sequence_adapter_base::native_buffer_type& buf, + const asio::const_buffer& buffer) +{ + std::memset(&buf, 0, sizeof(native_buffer_type)); + Microsoft::WRL::ComPtr insp + = Microsoft::WRL::Make(buffer); + Platform::Object^ buf_obj = reinterpret_cast(insp.Get()); + buf = reinterpret_cast(insp.Get()); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_IMPL_BUFFER_SEQUENCE_ADAPTER_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/descriptor_ops.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/descriptor_ops.ipp new file mode 100644 index 000000000..a146ed523 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/descriptor_ops.ipp @@ -0,0 +1,608 @@ +// +// detail/impl/descriptor_ops.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_DESCRIPTOR_OPS_IPP +#define ASIO_DETAIL_IMPL_DESCRIPTOR_OPS_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include "asio/detail/descriptor_ops.hpp" +#include "asio/error.hpp" + +#if !defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_RUNTIME) \ + && !defined(__CYGWIN__) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { +namespace descriptor_ops { + +int open(const char* path, int flags, asio::error_code& ec) +{ + int result = ::open(path, flags); + get_last_error(ec, result < 0); + return result; +} + +int close(int d, state_type& state, asio::error_code& ec) +{ + int result = 0; + if (d != -1) + { + result = ::close(d); + get_last_error(ec, result < 0); + + if (result != 0 + && (ec == asio::error::would_block + || ec == asio::error::try_again)) + { + // According to UNIX Network Programming Vol. 1, it is possible for + // close() to fail with EWOULDBLOCK under certain circumstances. What + // isn't clear is the state of the descriptor after this error. The one + // current OS where this behaviour is seen, Windows, says that the socket + // remains open. Therefore we'll put the descriptor back into blocking + // mode and have another attempt at closing it. +#if defined(__SYMBIAN32__) || defined(__EMSCRIPTEN__) + int flags = ::fcntl(d, F_GETFL, 0); + if (flags >= 0) + ::fcntl(d, F_SETFL, flags & ~O_NONBLOCK); +#else // defined(__SYMBIAN32__) || defined(__EMSCRIPTEN__) + ioctl_arg_type arg = 0; + ::ioctl(d, FIONBIO, &arg); +#endif // defined(__SYMBIAN32__) || defined(__EMSCRIPTEN__) + state &= ~non_blocking; + + result = ::close(d); + get_last_error(ec, result < 0); + } + } + + return result; +} + +bool set_user_non_blocking(int d, state_type& state, + bool value, asio::error_code& ec) +{ + if (d == -1) + { + ec = asio::error::bad_descriptor; + return false; + } + +#if defined(__SYMBIAN32__) || defined(__EMSCRIPTEN__) + int result = ::fcntl(d, F_GETFL, 0); + get_last_error(ec, result < 0); + if (result >= 0) + { + int flag = (value ? (result | O_NONBLOCK) : (result & ~O_NONBLOCK)); + result = ::fcntl(d, F_SETFL, flag); + get_last_error(ec, result < 0); + } +#else // defined(__SYMBIAN32__) || defined(__EMSCRIPTEN__) + ioctl_arg_type arg = (value ? 1 : 0); + int result = ::ioctl(d, FIONBIO, &arg); + get_last_error(ec, result < 0); +#endif // defined(__SYMBIAN32__) || defined(__EMSCRIPTEN__) + + if (result >= 0) + { + if (value) + state |= user_set_non_blocking; + else + { + // Clearing the user-set non-blocking mode always overrides any + // internally-set non-blocking flag. Any subsequent asynchronous + // operations will need to re-enable non-blocking I/O. + state &= ~(user_set_non_blocking | internal_non_blocking); + } + return true; + } + + return false; +} + +bool set_internal_non_blocking(int d, state_type& state, + bool value, asio::error_code& ec) +{ + if (d == -1) + { + ec = asio::error::bad_descriptor; + return false; + } + + if (!value && (state & user_set_non_blocking)) + { + // It does not make sense to clear the internal non-blocking flag if the + // user still wants non-blocking behaviour. Return an error and let the + // caller figure out whether to update the user-set non-blocking flag. + ec = asio::error::invalid_argument; + return false; + } + +#if defined(__SYMBIAN32__) || defined(__EMSCRIPTEN__) + int result = ::fcntl(d, F_GETFL, 0); + get_last_error(ec, result < 0); + if (result >= 0) + { + int flag = (value ? (result | O_NONBLOCK) : (result & ~O_NONBLOCK)); + result = ::fcntl(d, F_SETFL, flag); + get_last_error(ec, result < 0); + } +#else // defined(__SYMBIAN32__) || defined(__EMSCRIPTEN__) + ioctl_arg_type arg = (value ? 1 : 0); + int result = ::ioctl(d, FIONBIO, &arg); + get_last_error(ec, result < 0); +#endif // defined(__SYMBIAN32__) || defined(__EMSCRIPTEN__) + + if (result >= 0) + { + if (value) + state |= internal_non_blocking; + else + state &= ~internal_non_blocking; + return true; + } + + return false; +} + +std::size_t sync_read(int d, state_type state, buf* bufs, + std::size_t count, bool all_empty, asio::error_code& ec) +{ + if (d == -1) + { + ec = asio::error::bad_descriptor; + return 0; + } + + // A request to read 0 bytes on a stream is a no-op. + if (all_empty) + { + ec.assign(0, ec.category()); + return 0; + } + + // Read some data. + for (;;) + { + // Try to complete the operation without blocking. + signed_size_type bytes = ::readv(d, bufs, static_cast(count)); + get_last_error(ec, bytes < 0); + + // Check if operation succeeded. + if (bytes > 0) + return bytes; + + // Check for EOF. + if (bytes == 0) + { + ec = asio::error::eof; + return 0; + } + + // Operation failed. + if ((state & user_set_non_blocking) + || (ec != asio::error::would_block + && ec != asio::error::try_again)) + return 0; + + // Wait for descriptor to become ready. + if (descriptor_ops::poll_read(d, 0, ec) < 0) + return 0; + } +} + +std::size_t sync_read1(int d, state_type state, void* data, + std::size_t size, asio::error_code& ec) +{ + if (d == -1) + { + ec = asio::error::bad_descriptor; + return 0; + } + + // A request to read 0 bytes on a stream is a no-op. + if (size == 0) + { + ec.assign(0, ec.category()); + return 0; + } + + // Read some data. + for (;;) + { + // Try to complete the operation without blocking. + signed_size_type bytes = ::read(d, data, size); + get_last_error(ec, bytes < 0); + + // Check if operation succeeded. + if (bytes > 0) + return bytes; + + // Check for EOF. + if (bytes == 0) + { + ec = asio::error::eof; + return 0; + } + + // Operation failed. + if ((state & user_set_non_blocking) + || (ec != asio::error::would_block + && ec != asio::error::try_again)) + return 0; + + // Wait for descriptor to become ready. + if (descriptor_ops::poll_read(d, 0, ec) < 0) + return 0; + } +} + +bool non_blocking_read(int d, buf* bufs, std::size_t count, + asio::error_code& ec, std::size_t& bytes_transferred) +{ + for (;;) + { + // Read some data. + signed_size_type bytes = ::readv(d, bufs, static_cast(count)); + get_last_error(ec, bytes < 0); + + // Check for end of stream. + if (bytes == 0) + { + ec = asio::error::eof; + return true; + } + + // Check if operation succeeded. + if (bytes > 0) + { + bytes_transferred = bytes; + return true; + } + + // Retry operation if interrupted by signal. + if (ec == asio::error::interrupted) + continue; + + // Check if we need to run the operation again. + if (ec == asio::error::would_block + || ec == asio::error::try_again) + return false; + + // Operation failed. + bytes_transferred = 0; + return true; + } +} + +bool non_blocking_read1(int d, void* data, std::size_t size, + asio::error_code& ec, std::size_t& bytes_transferred) +{ + for (;;) + { + // Read some data. + signed_size_type bytes = ::read(d, data, size); + get_last_error(ec, bytes < 0); + + // Check for end of stream. + if (bytes == 0) + { + ec = asio::error::eof; + return true; + } + + // Check if operation succeeded. + if (bytes > 0) + { + bytes_transferred = bytes; + return true; + } + + // Retry operation if interrupted by signal. + if (ec == asio::error::interrupted) + continue; + + // Check if we need to run the operation again. + if (ec == asio::error::would_block + || ec == asio::error::try_again) + return false; + + // Operation failed. + bytes_transferred = 0; + return true; + } +} + +std::size_t sync_write(int d, state_type state, const buf* bufs, + std::size_t count, bool all_empty, asio::error_code& ec) +{ + if (d == -1) + { + ec = asio::error::bad_descriptor; + return 0; + } + + // A request to write 0 bytes on a stream is a no-op. + if (all_empty) + { + ec.assign(0, ec.category()); + return 0; + } + + // Write some data. + for (;;) + { + // Try to complete the operation without blocking. + signed_size_type bytes = ::writev(d, bufs, static_cast(count)); + get_last_error(ec, bytes < 0); + + // Check if operation succeeded. + if (bytes > 0) + return bytes; + + // Operation failed. + if ((state & user_set_non_blocking) + || (ec != asio::error::would_block + && ec != asio::error::try_again)) + return 0; + + // Wait for descriptor to become ready. + if (descriptor_ops::poll_write(d, 0, ec) < 0) + return 0; + } +} + +std::size_t sync_write1(int d, state_type state, const void* data, + std::size_t size, asio::error_code& ec) +{ + if (d == -1) + { + ec = asio::error::bad_descriptor; + return 0; + } + + // A request to write 0 bytes on a stream is a no-op. + if (size == 0) + { + ec.assign(0, ec.category()); + return 0; + } + + // Write some data. + for (;;) + { + // Try to complete the operation without blocking. + signed_size_type bytes = ::write(d, data, size); + get_last_error(ec, bytes < 0); + + // Check if operation succeeded. + if (bytes > 0) + return bytes; + + // Operation failed. + if ((state & user_set_non_blocking) + || (ec != asio::error::would_block + && ec != asio::error::try_again)) + return 0; + + // Wait for descriptor to become ready. + if (descriptor_ops::poll_write(d, 0, ec) < 0) + return 0; + } +} + +bool non_blocking_write(int d, const buf* bufs, std::size_t count, + asio::error_code& ec, std::size_t& bytes_transferred) +{ + for (;;) + { + // Write some data. + signed_size_type bytes = ::writev(d, bufs, static_cast(count)); + get_last_error(ec, bytes < 0); + + // Check if operation succeeded. + if (bytes >= 0) + { + bytes_transferred = bytes; + return true; + } + + // Retry operation if interrupted by signal. + if (ec == asio::error::interrupted) + continue; + + // Check if we need to run the operation again. + if (ec == asio::error::would_block + || ec == asio::error::try_again) + return false; + + // Operation failed. + bytes_transferred = 0; + return true; + } +} + +bool non_blocking_write1(int d, const void* data, std::size_t size, + asio::error_code& ec, std::size_t& bytes_transferred) +{ + for (;;) + { + // Write some data. + signed_size_type bytes = ::write(d, data, size); + get_last_error(ec, bytes < 0); + + // Check if operation succeeded. + if (bytes >= 0) + { + bytes_transferred = bytes; + return true; + } + + // Retry operation if interrupted by signal. + if (ec == asio::error::interrupted) + continue; + + // Check if we need to run the operation again. + if (ec == asio::error::would_block + || ec == asio::error::try_again) + return false; + + // Operation failed. + bytes_transferred = 0; + return true; + } +} + +int ioctl(int d, state_type& state, long cmd, + ioctl_arg_type* arg, asio::error_code& ec) +{ + if (d == -1) + { + ec = asio::error::bad_descriptor; + return -1; + } + + int result = ::ioctl(d, cmd, arg); + get_last_error(ec, result < 0); + + if (result >= 0) + { + // When updating the non-blocking mode we always perform the ioctl syscall, + // even if the flags would otherwise indicate that the descriptor is + // already in the correct state. This ensures that the underlying + // descriptor is put into the state that has been requested by the user. If + // the ioctl syscall was successful then we need to update the flags to + // match. + if (cmd == static_cast(FIONBIO)) + { + if (*arg) + { + state |= user_set_non_blocking; + } + else + { + // Clearing the non-blocking mode always overrides any internally-set + // non-blocking flag. Any subsequent asynchronous operations will need + // to re-enable non-blocking I/O. + state &= ~(user_set_non_blocking | internal_non_blocking); + } + } + } + + return result; +} + +int fcntl(int d, int cmd, asio::error_code& ec) +{ + if (d == -1) + { + ec = asio::error::bad_descriptor; + return -1; + } + + int result = ::fcntl(d, cmd); + get_last_error(ec, result < 0); + return result; +} + +int fcntl(int d, int cmd, long arg, asio::error_code& ec) +{ + if (d == -1) + { + ec = asio::error::bad_descriptor; + return -1; + } + + int result = ::fcntl(d, cmd, arg); + get_last_error(ec, result < 0); + return result; +} + +int poll_read(int d, state_type state, asio::error_code& ec) +{ + if (d == -1) + { + ec = asio::error::bad_descriptor; + return -1; + } + + pollfd fds; + fds.fd = d; + fds.events = POLLIN; + fds.revents = 0; + int timeout = (state & user_set_non_blocking) ? 0 : -1; + int result = ::poll(&fds, 1, timeout); + get_last_error(ec, result < 0); + if (result == 0) + if (state & user_set_non_blocking) + ec = asio::error::would_block; + return result; +} + +int poll_write(int d, state_type state, asio::error_code& ec) +{ + if (d == -1) + { + ec = asio::error::bad_descriptor; + return -1; + } + + pollfd fds; + fds.fd = d; + fds.events = POLLOUT; + fds.revents = 0; + int timeout = (state & user_set_non_blocking) ? 0 : -1; + int result = ::poll(&fds, 1, timeout); + get_last_error(ec, result < 0); + if (result == 0) + if (state & user_set_non_blocking) + ec = asio::error::would_block; + return result; +} + +int poll_error(int d, state_type state, asio::error_code& ec) +{ + if (d == -1) + { + ec = asio::error::bad_descriptor; + return -1; + } + + pollfd fds; + fds.fd = d; + fds.events = POLLPRI | POLLERR | POLLHUP; + fds.revents = 0; + int timeout = (state & user_set_non_blocking) ? 0 : -1; + int result = ::poll(&fds, 1, timeout); + get_last_error(ec, result < 0); + if (result == 0) + if (state & user_set_non_blocking) + ec = asio::error::would_block; + return result; +} + +} // namespace descriptor_ops +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) + +#endif // ASIO_DETAIL_IMPL_DESCRIPTOR_OPS_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/dev_poll_reactor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/dev_poll_reactor.hpp new file mode 100644 index 000000000..31cd71969 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/dev_poll_reactor.hpp @@ -0,0 +1,91 @@ +// +// detail/impl/dev_poll_reactor.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_DEV_POLL_REACTOR_HPP +#define ASIO_DETAIL_IMPL_DEV_POLL_REACTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_DEV_POLL) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +void dev_poll_reactor::add_timer_queue(timer_queue& queue) +{ + do_add_timer_queue(queue); +} + +template +void dev_poll_reactor::remove_timer_queue(timer_queue& queue) +{ + do_remove_timer_queue(queue); +} + +template +void dev_poll_reactor::schedule_timer(timer_queue& queue, + const typename Time_Traits::time_type& time, + typename timer_queue::per_timer_data& timer, wait_op* op) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + + if (shutdown_) + { + scheduler_.post_immediate_completion(op, false); + return; + } + + bool earliest = queue.enqueue_timer(time, timer, op); + scheduler_.work_started(); + if (earliest) + interrupter_.interrupt(); +} + +template +std::size_t dev_poll_reactor::cancel_timer(timer_queue& queue, + typename timer_queue::per_timer_data& timer, + std::size_t max_cancelled) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + op_queue ops; + std::size_t n = queue.cancel_timer(timer, ops, max_cancelled); + lock.unlock(); + scheduler_.post_deferred_completions(ops); + return n; +} + +template +void dev_poll_reactor::move_timer(timer_queue& queue, + typename timer_queue::per_timer_data& target, + typename timer_queue::per_timer_data& source) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + op_queue ops; + queue.cancel_timer(target, ops); + queue.move_timer(target, source); + lock.unlock(); + scheduler_.post_deferred_completions(ops); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_DEV_POLL) + +#endif // ASIO_DETAIL_IMPL_DEV_POLL_REACTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/dev_poll_reactor.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/dev_poll_reactor.ipp new file mode 100644 index 000000000..c7ad0cd32 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/dev_poll_reactor.ipp @@ -0,0 +1,446 @@ +// +// detail/impl/dev_poll_reactor.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_DEV_POLL_REACTOR_IPP +#define ASIO_DETAIL_IMPL_DEV_POLL_REACTOR_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_DEV_POLL) + +#include "asio/detail/dev_poll_reactor.hpp" +#include "asio/detail/assert.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +dev_poll_reactor::dev_poll_reactor(asio::execution_context& ctx) + : asio::detail::execution_context_service_base(ctx), + scheduler_(use_service(ctx)), + mutex_(), + dev_poll_fd_(do_dev_poll_create()), + interrupter_(), + shutdown_(false) +{ + // Add the interrupter's descriptor to /dev/poll. + ::pollfd ev = { 0, 0, 0 }; + ev.fd = interrupter_.read_descriptor(); + ev.events = POLLIN | POLLERR; + ev.revents = 0; + ::write(dev_poll_fd_, &ev, sizeof(ev)); +} + +dev_poll_reactor::~dev_poll_reactor() +{ + shutdown(); + ::close(dev_poll_fd_); +} + +void dev_poll_reactor::shutdown() +{ + asio::detail::mutex::scoped_lock lock(mutex_); + shutdown_ = true; + lock.unlock(); + + op_queue ops; + + for (int i = 0; i < max_ops; ++i) + op_queue_[i].get_all_operations(ops); + + timer_queues_.get_all_timers(ops); + + scheduler_.abandon_operations(ops); +} + +void dev_poll_reactor::notify_fork( + asio::execution_context::fork_event fork_ev) +{ + if (fork_ev == asio::execution_context::fork_child) + { + detail::mutex::scoped_lock lock(mutex_); + + if (dev_poll_fd_ != -1) + ::close(dev_poll_fd_); + dev_poll_fd_ = -1; + dev_poll_fd_ = do_dev_poll_create(); + + interrupter_.recreate(); + + // Add the interrupter's descriptor to /dev/poll. + ::pollfd ev = { 0, 0, 0 }; + ev.fd = interrupter_.read_descriptor(); + ev.events = POLLIN | POLLERR; + ev.revents = 0; + ::write(dev_poll_fd_, &ev, sizeof(ev)); + + // Re-register all descriptors with /dev/poll. The changes will be written + // to the /dev/poll descriptor the next time the reactor is run. + for (int i = 0; i < max_ops; ++i) + { + reactor_op_queue::iterator iter = op_queue_[i].begin(); + reactor_op_queue::iterator end = op_queue_[i].end(); + for (; iter != end; ++iter) + { + ::pollfd& pending_ev = add_pending_event_change(iter->first); + pending_ev.events |= POLLERR | POLLHUP; + switch (i) + { + case read_op: pending_ev.events |= POLLIN; break; + case write_op: pending_ev.events |= POLLOUT; break; + case except_op: pending_ev.events |= POLLPRI; break; + default: break; + } + } + } + interrupter_.interrupt(); + } +} + +void dev_poll_reactor::init_task() +{ + scheduler_.init_task(); +} + +int dev_poll_reactor::register_descriptor(socket_type, per_descriptor_data&) +{ + return 0; +} + +int dev_poll_reactor::register_internal_descriptor(int op_type, + socket_type descriptor, per_descriptor_data&, reactor_op* op) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + + op_queue_[op_type].enqueue_operation(descriptor, op); + ::pollfd& ev = add_pending_event_change(descriptor); + ev.events = POLLERR | POLLHUP; + switch (op_type) + { + case read_op: ev.events |= POLLIN; break; + case write_op: ev.events |= POLLOUT; break; + case except_op: ev.events |= POLLPRI; break; + default: break; + } + interrupter_.interrupt(); + + return 0; +} + +void dev_poll_reactor::move_descriptor(socket_type, + dev_poll_reactor::per_descriptor_data&, + dev_poll_reactor::per_descriptor_data&) +{ +} + +void dev_poll_reactor::start_op(int op_type, socket_type descriptor, + dev_poll_reactor::per_descriptor_data&, reactor_op* op, + bool is_continuation, bool allow_speculative) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + + if (shutdown_) + { + post_immediate_completion(op, is_continuation); + return; + } + + if (allow_speculative) + { + if (op_type != read_op || !op_queue_[except_op].has_operation(descriptor)) + { + if (!op_queue_[op_type].has_operation(descriptor)) + { + if (op->perform()) + { + lock.unlock(); + scheduler_.post_immediate_completion(op, is_continuation); + return; + } + } + } + } + + bool first = op_queue_[op_type].enqueue_operation(descriptor, op); + scheduler_.work_started(); + if (first) + { + ::pollfd& ev = add_pending_event_change(descriptor); + ev.events = POLLERR | POLLHUP; + if (op_type == read_op + || op_queue_[read_op].has_operation(descriptor)) + ev.events |= POLLIN; + if (op_type == write_op + || op_queue_[write_op].has_operation(descriptor)) + ev.events |= POLLOUT; + if (op_type == except_op + || op_queue_[except_op].has_operation(descriptor)) + ev.events |= POLLPRI; + interrupter_.interrupt(); + } +} + +void dev_poll_reactor::cancel_ops(socket_type descriptor, + dev_poll_reactor::per_descriptor_data&) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + cancel_ops_unlocked(descriptor, asio::error::operation_aborted); +} + +void dev_poll_reactor::deregister_descriptor(socket_type descriptor, + dev_poll_reactor::per_descriptor_data&, bool) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + + // Remove the descriptor from /dev/poll. + ::pollfd& ev = add_pending_event_change(descriptor); + ev.events = POLLREMOVE; + interrupter_.interrupt(); + + // Cancel any outstanding operations associated with the descriptor. + cancel_ops_unlocked(descriptor, asio::error::operation_aborted); +} + +void dev_poll_reactor::deregister_internal_descriptor( + socket_type descriptor, dev_poll_reactor::per_descriptor_data&) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + + // Remove the descriptor from /dev/poll. Since this function is only called + // during a fork, we can apply the change immediately. + ::pollfd ev = { 0, 0, 0 }; + ev.fd = descriptor; + ev.events = POLLREMOVE; + ev.revents = 0; + ::write(dev_poll_fd_, &ev, sizeof(ev)); + + // Destroy all operations associated with the descriptor. + op_queue ops; + asio::error_code ec; + for (int i = 0; i < max_ops; ++i) + op_queue_[i].cancel_operations(descriptor, ops, ec); +} + +void dev_poll_reactor::cleanup_descriptor_data( + dev_poll_reactor::per_descriptor_data&) +{ +} + +void dev_poll_reactor::run(long usec, op_queue& ops) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + + // We can return immediately if there's no work to do and the reactor is + // not supposed to block. + if (usec == 0 && op_queue_[read_op].empty() && op_queue_[write_op].empty() + && op_queue_[except_op].empty() && timer_queues_.all_empty()) + return; + + // Write the pending event registration changes to the /dev/poll descriptor. + std::size_t events_size = sizeof(::pollfd) * pending_event_changes_.size(); + if (events_size > 0) + { + errno = 0; + int result = ::write(dev_poll_fd_, + &pending_event_changes_[0], events_size); + if (result != static_cast(events_size)) + { + asio::error_code ec = asio::error_code( + errno, asio::error::get_system_category()); + for (std::size_t i = 0; i < pending_event_changes_.size(); ++i) + { + int descriptor = pending_event_changes_[i].fd; + for (int j = 0; j < max_ops; ++j) + op_queue_[j].cancel_operations(descriptor, ops, ec); + } + } + pending_event_changes_.clear(); + pending_event_change_index_.clear(); + } + + // Calculate timeout. + int timeout; + if (usec == 0) + timeout = 0; + else + { + timeout = (usec < 0) ? -1 : ((usec - 1) / 1000 + 1); + timeout = get_timeout(timeout); + } + lock.unlock(); + + // Block on the /dev/poll descriptor. + ::pollfd events[128] = { { 0, 0, 0 } }; + ::dvpoll dp = { 0, 0, 0 }; + dp.dp_fds = events; + dp.dp_nfds = 128; + dp.dp_timeout = timeout; + int num_events = ::ioctl(dev_poll_fd_, DP_POLL, &dp); + + lock.lock(); + + // Dispatch the waiting events. + for (int i = 0; i < num_events; ++i) + { + int descriptor = events[i].fd; + if (descriptor == interrupter_.read_descriptor()) + { + interrupter_.reset(); + } + else + { + bool more_reads = false; + bool more_writes = false; + bool more_except = false; + + // Exception operations must be processed first to ensure that any + // out-of-band data is read before normal data. + if (events[i].events & (POLLPRI | POLLERR | POLLHUP)) + more_except = + op_queue_[except_op].perform_operations(descriptor, ops); + else + more_except = op_queue_[except_op].has_operation(descriptor); + + if (events[i].events & (POLLIN | POLLERR | POLLHUP)) + more_reads = op_queue_[read_op].perform_operations(descriptor, ops); + else + more_reads = op_queue_[read_op].has_operation(descriptor); + + if (events[i].events & (POLLOUT | POLLERR | POLLHUP)) + more_writes = op_queue_[write_op].perform_operations(descriptor, ops); + else + more_writes = op_queue_[write_op].has_operation(descriptor); + + if ((events[i].events & (POLLERR | POLLHUP)) != 0 + && !more_except && !more_reads && !more_writes) + { + // If we have an event and no operations associated with the + // descriptor then we need to delete the descriptor from /dev/poll. + // The poll operation can produce POLLHUP or POLLERR events when there + // is no operation pending, so if we do not remove the descriptor we + // can end up in a tight polling loop. + ::pollfd ev = { 0, 0, 0 }; + ev.fd = descriptor; + ev.events = POLLREMOVE; + ev.revents = 0; + ::write(dev_poll_fd_, &ev, sizeof(ev)); + } + else + { + ::pollfd ev = { 0, 0, 0 }; + ev.fd = descriptor; + ev.events = POLLERR | POLLHUP; + if (more_reads) + ev.events |= POLLIN; + if (more_writes) + ev.events |= POLLOUT; + if (more_except) + ev.events |= POLLPRI; + ev.revents = 0; + int result = ::write(dev_poll_fd_, &ev, sizeof(ev)); + if (result != sizeof(ev)) + { + asio::error_code ec(errno, + asio::error::get_system_category()); + for (int j = 0; j < max_ops; ++j) + op_queue_[j].cancel_operations(descriptor, ops, ec); + } + } + } + } + timer_queues_.get_ready_timers(ops); +} + +void dev_poll_reactor::interrupt() +{ + interrupter_.interrupt(); +} + +int dev_poll_reactor::do_dev_poll_create() +{ + int fd = ::open("/dev/poll", O_RDWR); + if (fd == -1) + { + asio::error_code ec(errno, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "/dev/poll"); + } + return fd; +} + +void dev_poll_reactor::do_add_timer_queue(timer_queue_base& queue) +{ + mutex::scoped_lock lock(mutex_); + timer_queues_.insert(&queue); +} + +void dev_poll_reactor::do_remove_timer_queue(timer_queue_base& queue) +{ + mutex::scoped_lock lock(mutex_); + timer_queues_.erase(&queue); +} + +int dev_poll_reactor::get_timeout(int msec) +{ + // By default we will wait no longer than 5 minutes. This will ensure that + // any changes to the system clock are detected after no longer than this. + const int max_msec = 5 * 60 * 1000; + return timer_queues_.wait_duration_msec( + (msec < 0 || max_msec < msec) ? max_msec : msec); +} + +void dev_poll_reactor::cancel_ops_unlocked(socket_type descriptor, + const asio::error_code& ec) +{ + bool need_interrupt = false; + op_queue ops; + for (int i = 0; i < max_ops; ++i) + need_interrupt = op_queue_[i].cancel_operations( + descriptor, ops, ec) || need_interrupt; + scheduler_.post_deferred_completions(ops); + if (need_interrupt) + interrupter_.interrupt(); +} + +::pollfd& dev_poll_reactor::add_pending_event_change(int descriptor) +{ + hash_map::iterator iter + = pending_event_change_index_.find(descriptor); + if (iter == pending_event_change_index_.end()) + { + std::size_t index = pending_event_changes_.size(); + pending_event_changes_.reserve(pending_event_changes_.size() + 1); + pending_event_change_index_.insert(std::make_pair(descriptor, index)); + pending_event_changes_.push_back(::pollfd()); + pending_event_changes_[index].fd = descriptor; + pending_event_changes_[index].revents = 0; + return pending_event_changes_[index]; + } + else + { + return pending_event_changes_[iter->second]; + } +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_DEV_POLL) + +#endif // ASIO_DETAIL_IMPL_DEV_POLL_REACTOR_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/epoll_reactor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/epoll_reactor.hpp new file mode 100644 index 000000000..42d52a798 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/epoll_reactor.hpp @@ -0,0 +1,89 @@ +// +// detail/impl/epoll_reactor.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_EPOLL_REACTOR_HPP +#define ASIO_DETAIL_IMPL_EPOLL_REACTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#if defined(ASIO_HAS_EPOLL) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +void epoll_reactor::add_timer_queue(timer_queue& queue) +{ + do_add_timer_queue(queue); +} + +template +void epoll_reactor::remove_timer_queue(timer_queue& queue) +{ + do_remove_timer_queue(queue); +} + +template +void epoll_reactor::schedule_timer(timer_queue& queue, + const typename Time_Traits::time_type& time, + typename timer_queue::per_timer_data& timer, wait_op* op) +{ + mutex::scoped_lock lock(mutex_); + + if (shutdown_) + { + scheduler_.post_immediate_completion(op, false); + return; + } + + bool earliest = queue.enqueue_timer(time, timer, op); + scheduler_.work_started(); + if (earliest) + update_timeout(); +} + +template +std::size_t epoll_reactor::cancel_timer(timer_queue& queue, + typename timer_queue::per_timer_data& timer, + std::size_t max_cancelled) +{ + mutex::scoped_lock lock(mutex_); + op_queue ops; + std::size_t n = queue.cancel_timer(timer, ops, max_cancelled); + lock.unlock(); + scheduler_.post_deferred_completions(ops); + return n; +} + +template +void epoll_reactor::move_timer(timer_queue& queue, + typename timer_queue::per_timer_data& target, + typename timer_queue::per_timer_data& source) +{ + mutex::scoped_lock lock(mutex_); + op_queue ops; + queue.cancel_timer(target, ops); + queue.move_timer(target, source); + lock.unlock(); + scheduler_.post_deferred_completions(ops); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_EPOLL) + +#endif // ASIO_DETAIL_IMPL_EPOLL_REACTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/epoll_reactor.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/epoll_reactor.ipp new file mode 100644 index 000000000..528968d20 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/epoll_reactor.ipp @@ -0,0 +1,787 @@ +// +// detail/impl/epoll_reactor.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_EPOLL_REACTOR_IPP +#define ASIO_DETAIL_IMPL_EPOLL_REACTOR_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_EPOLL) + +#include +#include +#include "asio/detail/epoll_reactor.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" + +#if defined(ASIO_HAS_TIMERFD) +# include +#endif // defined(ASIO_HAS_TIMERFD) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +epoll_reactor::epoll_reactor(asio::execution_context& ctx) + : execution_context_service_base(ctx), + scheduler_(use_service(ctx)), + mutex_(ASIO_CONCURRENCY_HINT_IS_LOCKING( + REACTOR_REGISTRATION, scheduler_.concurrency_hint())), + interrupter_(), + epoll_fd_(do_epoll_create()), + timer_fd_(do_timerfd_create()), + shutdown_(false), + registered_descriptors_mutex_(mutex_.enabled()) +{ + // Add the interrupter's descriptor to epoll. + epoll_event ev = { 0, { 0 } }; + ev.events = EPOLLIN | EPOLLERR | EPOLLET; + ev.data.ptr = &interrupter_; + epoll_ctl(epoll_fd_, EPOLL_CTL_ADD, interrupter_.read_descriptor(), &ev); + interrupter_.interrupt(); + + // Add the timer descriptor to epoll. + if (timer_fd_ != -1) + { + ev.events = EPOLLIN | EPOLLERR; + ev.data.ptr = &timer_fd_; + epoll_ctl(epoll_fd_, EPOLL_CTL_ADD, timer_fd_, &ev); + } +} + +epoll_reactor::~epoll_reactor() +{ + if (epoll_fd_ != -1) + close(epoll_fd_); + if (timer_fd_ != -1) + close(timer_fd_); +} + +void epoll_reactor::shutdown() +{ + mutex::scoped_lock lock(mutex_); + shutdown_ = true; + lock.unlock(); + + op_queue ops; + + while (descriptor_state* state = registered_descriptors_.first()) + { + for (int i = 0; i < max_ops; ++i) + ops.push(state->op_queue_[i]); + state->shutdown_ = true; + registered_descriptors_.free(state); + } + + timer_queues_.get_all_timers(ops); + + scheduler_.abandon_operations(ops); +} + +void epoll_reactor::notify_fork( + asio::execution_context::fork_event fork_ev) +{ + if (fork_ev == asio::execution_context::fork_child) + { + if (epoll_fd_ != -1) + ::close(epoll_fd_); + epoll_fd_ = -1; + epoll_fd_ = do_epoll_create(); + + if (timer_fd_ != -1) + ::close(timer_fd_); + timer_fd_ = -1; + timer_fd_ = do_timerfd_create(); + + interrupter_.recreate(); + + // Add the interrupter's descriptor to epoll. + epoll_event ev = { 0, { 0 } }; + ev.events = EPOLLIN | EPOLLERR | EPOLLET; + ev.data.ptr = &interrupter_; + epoll_ctl(epoll_fd_, EPOLL_CTL_ADD, interrupter_.read_descriptor(), &ev); + interrupter_.interrupt(); + + // Add the timer descriptor to epoll. + if (timer_fd_ != -1) + { + ev.events = EPOLLIN | EPOLLERR; + ev.data.ptr = &timer_fd_; + epoll_ctl(epoll_fd_, EPOLL_CTL_ADD, timer_fd_, &ev); + } + + update_timeout(); + + // Re-register all descriptors with epoll. + mutex::scoped_lock descriptors_lock(registered_descriptors_mutex_); + for (descriptor_state* state = registered_descriptors_.first(); + state != 0; state = state->next_) + { + ev.events = state->registered_events_; + ev.data.ptr = state; + int result = epoll_ctl(epoll_fd_, EPOLL_CTL_ADD, state->descriptor_, &ev); + if (result != 0) + { + asio::error_code ec(errno, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "epoll re-registration"); + } + } + } +} + +void epoll_reactor::init_task() +{ + scheduler_.init_task(); +} + +int epoll_reactor::register_descriptor(socket_type descriptor, + epoll_reactor::per_descriptor_data& descriptor_data) +{ + descriptor_data = allocate_descriptor_state(); + + ASIO_HANDLER_REACTOR_REGISTRATION(( + context(), static_cast(descriptor), + reinterpret_cast(descriptor_data))); + + { + mutex::scoped_lock descriptor_lock(descriptor_data->mutex_); + + descriptor_data->reactor_ = this; + descriptor_data->descriptor_ = descriptor; + descriptor_data->shutdown_ = false; + for (int i = 0; i < max_ops; ++i) + descriptor_data->try_speculative_[i] = true; + } + + epoll_event ev = { 0, { 0 } }; + ev.events = EPOLLIN | EPOLLERR | EPOLLHUP | EPOLLPRI | EPOLLET; + descriptor_data->registered_events_ = ev.events; + ev.data.ptr = descriptor_data; + int result = epoll_ctl(epoll_fd_, EPOLL_CTL_ADD, descriptor, &ev); + if (result != 0) + { + if (errno == EPERM) + { + // This file descriptor type is not supported by epoll. However, if it is + // a regular file then operations on it will not block. We will allow + // this descriptor to be used and fail later if an operation on it would + // otherwise require a trip through the reactor. + descriptor_data->registered_events_ = 0; + return 0; + } + return errno; + } + + return 0; +} + +int epoll_reactor::register_internal_descriptor( + int op_type, socket_type descriptor, + epoll_reactor::per_descriptor_data& descriptor_data, reactor_op* op) +{ + descriptor_data = allocate_descriptor_state(); + + ASIO_HANDLER_REACTOR_REGISTRATION(( + context(), static_cast(descriptor), + reinterpret_cast(descriptor_data))); + + { + mutex::scoped_lock descriptor_lock(descriptor_data->mutex_); + + descriptor_data->reactor_ = this; + descriptor_data->descriptor_ = descriptor; + descriptor_data->shutdown_ = false; + descriptor_data->op_queue_[op_type].push(op); + for (int i = 0; i < max_ops; ++i) + descriptor_data->try_speculative_[i] = true; + } + + epoll_event ev = { 0, { 0 } }; + ev.events = EPOLLIN | EPOLLERR | EPOLLHUP | EPOLLPRI | EPOLLET; + descriptor_data->registered_events_ = ev.events; + ev.data.ptr = descriptor_data; + int result = epoll_ctl(epoll_fd_, EPOLL_CTL_ADD, descriptor, &ev); + if (result != 0) + return errno; + + return 0; +} + +void epoll_reactor::move_descriptor(socket_type, + epoll_reactor::per_descriptor_data& target_descriptor_data, + epoll_reactor::per_descriptor_data& source_descriptor_data) +{ + target_descriptor_data = source_descriptor_data; + source_descriptor_data = 0; +} + +void epoll_reactor::start_op(int op_type, socket_type descriptor, + epoll_reactor::per_descriptor_data& descriptor_data, reactor_op* op, + bool is_continuation, bool allow_speculative) +{ + if (!descriptor_data) + { + op->ec_ = asio::error::bad_descriptor; + post_immediate_completion(op, is_continuation); + return; + } + + mutex::scoped_lock descriptor_lock(descriptor_data->mutex_); + + if (descriptor_data->shutdown_) + { + post_immediate_completion(op, is_continuation); + return; + } + + if (descriptor_data->op_queue_[op_type].empty()) + { + if (allow_speculative + && (op_type != read_op + || descriptor_data->op_queue_[except_op].empty())) + { + if (descriptor_data->try_speculative_[op_type]) + { + if (reactor_op::status status = op->perform()) + { + if (status == reactor_op::done_and_exhausted) + if (descriptor_data->registered_events_ != 0) + descriptor_data->try_speculative_[op_type] = false; + descriptor_lock.unlock(); + scheduler_.post_immediate_completion(op, is_continuation); + return; + } + } + + if (descriptor_data->registered_events_ == 0) + { + op->ec_ = asio::error::operation_not_supported; + scheduler_.post_immediate_completion(op, is_continuation); + return; + } + + if (op_type == write_op) + { + if ((descriptor_data->registered_events_ & EPOLLOUT) == 0) + { + epoll_event ev = { 0, { 0 } }; + ev.events = descriptor_data->registered_events_ | EPOLLOUT; + ev.data.ptr = descriptor_data; + if (epoll_ctl(epoll_fd_, EPOLL_CTL_MOD, descriptor, &ev) == 0) + { + descriptor_data->registered_events_ |= ev.events; + } + else + { + op->ec_ = asio::error_code(errno, + asio::error::get_system_category()); + scheduler_.post_immediate_completion(op, is_continuation); + return; + } + } + } + } + else if (descriptor_data->registered_events_ == 0) + { + op->ec_ = asio::error::operation_not_supported; + scheduler_.post_immediate_completion(op, is_continuation); + return; + } + else + { + if (op_type == write_op) + { + descriptor_data->registered_events_ |= EPOLLOUT; + } + + epoll_event ev = { 0, { 0 } }; + ev.events = descriptor_data->registered_events_; + ev.data.ptr = descriptor_data; + epoll_ctl(epoll_fd_, EPOLL_CTL_MOD, descriptor, &ev); + } + } + + descriptor_data->op_queue_[op_type].push(op); + scheduler_.work_started(); +} + +void epoll_reactor::cancel_ops(socket_type, + epoll_reactor::per_descriptor_data& descriptor_data) +{ + if (!descriptor_data) + return; + + mutex::scoped_lock descriptor_lock(descriptor_data->mutex_); + + op_queue ops; + for (int i = 0; i < max_ops; ++i) + { + while (reactor_op* op = descriptor_data->op_queue_[i].front()) + { + op->ec_ = asio::error::operation_aborted; + descriptor_data->op_queue_[i].pop(); + ops.push(op); + } + } + + descriptor_lock.unlock(); + + scheduler_.post_deferred_completions(ops); +} + +void epoll_reactor::deregister_descriptor(socket_type descriptor, + epoll_reactor::per_descriptor_data& descriptor_data, bool closing) +{ + if (!descriptor_data) + return; + + mutex::scoped_lock descriptor_lock(descriptor_data->mutex_); + + if (!descriptor_data->shutdown_) + { + if (closing) + { + // The descriptor will be automatically removed from the epoll set when + // it is closed. + } + else if (descriptor_data->registered_events_ != 0) + { + epoll_event ev = { 0, { 0 } }; + epoll_ctl(epoll_fd_, EPOLL_CTL_DEL, descriptor, &ev); + } + + op_queue ops; + for (int i = 0; i < max_ops; ++i) + { + while (reactor_op* op = descriptor_data->op_queue_[i].front()) + { + op->ec_ = asio::error::operation_aborted; + descriptor_data->op_queue_[i].pop(); + ops.push(op); + } + } + + descriptor_data->descriptor_ = -1; + descriptor_data->shutdown_ = true; + + descriptor_lock.unlock(); + + ASIO_HANDLER_REACTOR_DEREGISTRATION(( + context(), static_cast(descriptor), + reinterpret_cast(descriptor_data))); + + scheduler_.post_deferred_completions(ops); + + // Leave descriptor_data set so that it will be freed by the subsequent + // call to cleanup_descriptor_data. + } + else + { + // We are shutting down, so prevent cleanup_descriptor_data from freeing + // the descriptor_data object and let the destructor free it instead. + descriptor_data = 0; + } +} + +void epoll_reactor::deregister_internal_descriptor(socket_type descriptor, + epoll_reactor::per_descriptor_data& descriptor_data) +{ + if (!descriptor_data) + return; + + mutex::scoped_lock descriptor_lock(descriptor_data->mutex_); + + if (!descriptor_data->shutdown_) + { + epoll_event ev = { 0, { 0 } }; + epoll_ctl(epoll_fd_, EPOLL_CTL_DEL, descriptor, &ev); + + op_queue ops; + for (int i = 0; i < max_ops; ++i) + ops.push(descriptor_data->op_queue_[i]); + + descriptor_data->descriptor_ = -1; + descriptor_data->shutdown_ = true; + + descriptor_lock.unlock(); + + ASIO_HANDLER_REACTOR_DEREGISTRATION(( + context(), static_cast(descriptor), + reinterpret_cast(descriptor_data))); + + // Leave descriptor_data set so that it will be freed by the subsequent + // call to cleanup_descriptor_data. + } + else + { + // We are shutting down, so prevent cleanup_descriptor_data from freeing + // the descriptor_data object and let the destructor free it instead. + descriptor_data = 0; + } +} + +void epoll_reactor::cleanup_descriptor_data( + per_descriptor_data& descriptor_data) +{ + if (descriptor_data) + { + free_descriptor_state(descriptor_data); + descriptor_data = 0; + } +} + +void epoll_reactor::run(long usec, op_queue& ops) +{ + // This code relies on the fact that the scheduler queues the reactor task + // behind all descriptor operations generated by this function. This means, + // that by the time we reach this point, any previously returned descriptor + // operations have already been dequeued. Therefore it is now safe for us to + // reuse and return them for the scheduler to queue again. + + // Calculate timeout. Check the timer queues only if timerfd is not in use. + int timeout; + if (usec == 0) + timeout = 0; + else + { + timeout = (usec < 0) ? -1 : ((usec - 1) / 1000 + 1); + if (timer_fd_ == -1) + { + mutex::scoped_lock lock(mutex_); + timeout = get_timeout(timeout); + } + } + + // Block on the epoll descriptor. + epoll_event events[128]; + int num_events = epoll_wait(epoll_fd_, events, 128, timeout); + +#if defined(ASIO_ENABLE_HANDLER_TRACKING) + // Trace the waiting events. + for (int i = 0; i < num_events; ++i) + { + void* ptr = events[i].data.ptr; + if (ptr == &interrupter_) + { + // Ignore. + } +# if defined(ASIO_HAS_TIMERFD) + else if (ptr == &timer_fd_) + { + // Ignore. + } +# endif // defined(ASIO_HAS_TIMERFD) + else + { + unsigned event_mask = 0; + if ((events[i].events & EPOLLIN) != 0) + event_mask |= ASIO_HANDLER_REACTOR_READ_EVENT; + if ((events[i].events & EPOLLOUT)) + event_mask |= ASIO_HANDLER_REACTOR_WRITE_EVENT; + if ((events[i].events & (EPOLLERR | EPOLLHUP)) != 0) + event_mask |= ASIO_HANDLER_REACTOR_ERROR_EVENT; + ASIO_HANDLER_REACTOR_EVENTS((context(), + reinterpret_cast(ptr), event_mask)); + } + } +#endif // defined(ASIO_ENABLE_HANDLER_TRACKING) + +#if defined(ASIO_HAS_TIMERFD) + bool check_timers = (timer_fd_ == -1); +#else // defined(ASIO_HAS_TIMERFD) + bool check_timers = true; +#endif // defined(ASIO_HAS_TIMERFD) + + // Dispatch the waiting events. + for (int i = 0; i < num_events; ++i) + { + void* ptr = events[i].data.ptr; + if (ptr == &interrupter_) + { + // No need to reset the interrupter since we're leaving the descriptor + // in a ready-to-read state and relying on edge-triggered notifications + // to make it so that we only get woken up when the descriptor's epoll + // registration is updated. + +#if defined(ASIO_HAS_TIMERFD) + if (timer_fd_ == -1) + check_timers = true; +#else // defined(ASIO_HAS_TIMERFD) + check_timers = true; +#endif // defined(ASIO_HAS_TIMERFD) + } +#if defined(ASIO_HAS_TIMERFD) + else if (ptr == &timer_fd_) + { + check_timers = true; + } +#endif // defined(ASIO_HAS_TIMERFD) + else + { + // The descriptor operation doesn't count as work in and of itself, so we + // don't call work_started() here. This still allows the scheduler to + // stop if the only remaining operations are descriptor operations. + descriptor_state* descriptor_data = static_cast(ptr); + if (!ops.is_enqueued(descriptor_data)) + { + descriptor_data->set_ready_events(events[i].events); + ops.push(descriptor_data); + } + else + { + descriptor_data->add_ready_events(events[i].events); + } + } + } + + if (check_timers) + { + mutex::scoped_lock common_lock(mutex_); + timer_queues_.get_ready_timers(ops); + +#if defined(ASIO_HAS_TIMERFD) + if (timer_fd_ != -1) + { + itimerspec new_timeout; + itimerspec old_timeout; + int flags = get_timeout(new_timeout); + timerfd_settime(timer_fd_, flags, &new_timeout, &old_timeout); + } +#endif // defined(ASIO_HAS_TIMERFD) + } +} + +void epoll_reactor::interrupt() +{ + epoll_event ev = { 0, { 0 } }; + ev.events = EPOLLIN | EPOLLERR | EPOLLET; + ev.data.ptr = &interrupter_; + epoll_ctl(epoll_fd_, EPOLL_CTL_MOD, interrupter_.read_descriptor(), &ev); +} + +int epoll_reactor::do_epoll_create() +{ +#if defined(EPOLL_CLOEXEC) + int fd = epoll_create1(EPOLL_CLOEXEC); +#else // defined(EPOLL_CLOEXEC) + int fd = -1; + errno = EINVAL; +#endif // defined(EPOLL_CLOEXEC) + + if (fd == -1 && (errno == EINVAL || errno == ENOSYS)) + { + fd = epoll_create(epoll_size); + if (fd != -1) + ::fcntl(fd, F_SETFD, FD_CLOEXEC); + } + + if (fd == -1) + { + asio::error_code ec(errno, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "epoll"); + } + + return fd; +} + +int epoll_reactor::do_timerfd_create() +{ +#if defined(ASIO_HAS_TIMERFD) +# if defined(TFD_CLOEXEC) + int fd = timerfd_create(CLOCK_MONOTONIC, TFD_CLOEXEC); +# else // defined(TFD_CLOEXEC) + int fd = -1; + errno = EINVAL; +# endif // defined(TFD_CLOEXEC) + + if (fd == -1 && errno == EINVAL) + { + fd = timerfd_create(CLOCK_MONOTONIC, 0); + if (fd != -1) + ::fcntl(fd, F_SETFD, FD_CLOEXEC); + } + + return fd; +#else // defined(ASIO_HAS_TIMERFD) + return -1; +#endif // defined(ASIO_HAS_TIMERFD) +} + +epoll_reactor::descriptor_state* epoll_reactor::allocate_descriptor_state() +{ + mutex::scoped_lock descriptors_lock(registered_descriptors_mutex_); + return registered_descriptors_.alloc(ASIO_CONCURRENCY_HINT_IS_LOCKING( + REACTOR_IO, scheduler_.concurrency_hint())); +} + +void epoll_reactor::free_descriptor_state(epoll_reactor::descriptor_state* s) +{ + mutex::scoped_lock descriptors_lock(registered_descriptors_mutex_); + registered_descriptors_.free(s); +} + +void epoll_reactor::do_add_timer_queue(timer_queue_base& queue) +{ + mutex::scoped_lock lock(mutex_); + timer_queues_.insert(&queue); +} + +void epoll_reactor::do_remove_timer_queue(timer_queue_base& queue) +{ + mutex::scoped_lock lock(mutex_); + timer_queues_.erase(&queue); +} + +void epoll_reactor::update_timeout() +{ +#if defined(ASIO_HAS_TIMERFD) + if (timer_fd_ != -1) + { + itimerspec new_timeout; + itimerspec old_timeout; + int flags = get_timeout(new_timeout); + timerfd_settime(timer_fd_, flags, &new_timeout, &old_timeout); + return; + } +#endif // defined(ASIO_HAS_TIMERFD) + interrupt(); +} + +int epoll_reactor::get_timeout(int msec) +{ + // By default we will wait no longer than 5 minutes. This will ensure that + // any changes to the system clock are detected after no longer than this. + const int max_msec = 5 * 60 * 1000; + return timer_queues_.wait_duration_msec( + (msec < 0 || max_msec < msec) ? max_msec : msec); +} + +#if defined(ASIO_HAS_TIMERFD) +int epoll_reactor::get_timeout(itimerspec& ts) +{ + ts.it_interval.tv_sec = 0; + ts.it_interval.tv_nsec = 0; + + long usec = timer_queues_.wait_duration_usec(5 * 60 * 1000 * 1000); + ts.it_value.tv_sec = usec / 1000000; + ts.it_value.tv_nsec = usec ? (usec % 1000000) * 1000 : 1; + + return usec ? 0 : TFD_TIMER_ABSTIME; +} +#endif // defined(ASIO_HAS_TIMERFD) + +struct epoll_reactor::perform_io_cleanup_on_block_exit +{ + explicit perform_io_cleanup_on_block_exit(epoll_reactor* r) + : reactor_(r), first_op_(0) + { + } + + ~perform_io_cleanup_on_block_exit() + { + if (first_op_) + { + // Post the remaining completed operations for invocation. + if (!ops_.empty()) + reactor_->scheduler_.post_deferred_completions(ops_); + + // A user-initiated operation has completed, but there's no need to + // explicitly call work_finished() here. Instead, we'll take advantage of + // the fact that the scheduler will call work_finished() once we return. + } + else + { + // No user-initiated operations have completed, so we need to compensate + // for the work_finished() call that the scheduler will make once this + // operation returns. + reactor_->scheduler_.compensating_work_started(); + } + } + + epoll_reactor* reactor_; + op_queue ops_; + operation* first_op_; +}; + +epoll_reactor::descriptor_state::descriptor_state(bool locking) + : operation(&epoll_reactor::descriptor_state::do_complete), + mutex_(locking) +{ +} + +operation* epoll_reactor::descriptor_state::perform_io(uint32_t events) +{ + mutex_.lock(); + perform_io_cleanup_on_block_exit io_cleanup(reactor_); + mutex::scoped_lock descriptor_lock(mutex_, mutex::scoped_lock::adopt_lock); + + // Exception operations must be processed first to ensure that any + // out-of-band data is read before normal data. + static const int flag[max_ops] = { EPOLLIN, EPOLLOUT, EPOLLPRI }; + for (int j = max_ops - 1; j >= 0; --j) + { + if (events & (flag[j] | EPOLLERR | EPOLLHUP)) + { + try_speculative_[j] = true; + while (reactor_op* op = op_queue_[j].front()) + { + if (reactor_op::status status = op->perform()) + { + op_queue_[j].pop(); + io_cleanup.ops_.push(op); + if (status == reactor_op::done_and_exhausted) + { + try_speculative_[j] = false; + break; + } + } + else + break; + } + } + } + + // The first operation will be returned for completion now. The others will + // be posted for later by the io_cleanup object's destructor. + io_cleanup.first_op_ = io_cleanup.ops_.front(); + io_cleanup.ops_.pop(); + return io_cleanup.first_op_; +} + +void epoll_reactor::descriptor_state::do_complete( + void* owner, operation* base, + const asio::error_code& ec, std::size_t bytes_transferred) +{ + if (owner) + { + descriptor_state* descriptor_data = static_cast(base); + uint32_t events = static_cast(bytes_transferred); + if (operation* op = descriptor_data->perform_io(events)) + { + op->complete(owner, ec, 0); + } + } +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_EPOLL) + +#endif // ASIO_DETAIL_IMPL_EPOLL_REACTOR_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/eventfd_select_interrupter.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/eventfd_select_interrupter.ipp new file mode 100644 index 000000000..6f9fdb9cc --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/eventfd_select_interrupter.ipp @@ -0,0 +1,169 @@ +// +// detail/impl/eventfd_select_interrupter.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// Copyright (c) 2008 Roelof Naude (roelof.naude at gmail dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_EVENTFD_SELECT_INTERRUPTER_IPP +#define ASIO_DETAIL_IMPL_EVENTFD_SELECT_INTERRUPTER_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_EVENTFD) + +#include +#include +#include +#if __GLIBC__ == 2 && __GLIBC_MINOR__ < 8 +# include +#else // __GLIBC__ == 2 && __GLIBC_MINOR__ < 8 +# include +#endif // __GLIBC__ == 2 && __GLIBC_MINOR__ < 8 +#include "asio/detail/cstdint.hpp" +#include "asio/detail/eventfd_select_interrupter.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +eventfd_select_interrupter::eventfd_select_interrupter() +{ + open_descriptors(); +} + +void eventfd_select_interrupter::open_descriptors() +{ +#if __GLIBC__ == 2 && __GLIBC_MINOR__ < 8 + write_descriptor_ = read_descriptor_ = syscall(__NR_eventfd, 0); + if (read_descriptor_ != -1) + { + ::fcntl(read_descriptor_, F_SETFL, O_NONBLOCK); + ::fcntl(read_descriptor_, F_SETFD, FD_CLOEXEC); + } +#else // __GLIBC__ == 2 && __GLIBC_MINOR__ < 8 +# if defined(EFD_CLOEXEC) && defined(EFD_NONBLOCK) + write_descriptor_ = read_descriptor_ = + ::eventfd(0, EFD_CLOEXEC | EFD_NONBLOCK); +# else // defined(EFD_CLOEXEC) && defined(EFD_NONBLOCK) + errno = EINVAL; + write_descriptor_ = read_descriptor_ = -1; +# endif // defined(EFD_CLOEXEC) && defined(EFD_NONBLOCK) + if (read_descriptor_ == -1 && errno == EINVAL) + { + write_descriptor_ = read_descriptor_ = ::eventfd(0, 0); + if (read_descriptor_ != -1) + { + ::fcntl(read_descriptor_, F_SETFL, O_NONBLOCK); + ::fcntl(read_descriptor_, F_SETFD, FD_CLOEXEC); + } + } +#endif // __GLIBC__ == 2 && __GLIBC_MINOR__ < 8 + + if (read_descriptor_ == -1) + { + int pipe_fds[2]; + if (pipe(pipe_fds) == 0) + { + read_descriptor_ = pipe_fds[0]; + ::fcntl(read_descriptor_, F_SETFL, O_NONBLOCK); + ::fcntl(read_descriptor_, F_SETFD, FD_CLOEXEC); + write_descriptor_ = pipe_fds[1]; + ::fcntl(write_descriptor_, F_SETFL, O_NONBLOCK); + ::fcntl(write_descriptor_, F_SETFD, FD_CLOEXEC); + } + else + { + asio::error_code ec(errno, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "eventfd_select_interrupter"); + } + } +} + +eventfd_select_interrupter::~eventfd_select_interrupter() +{ + close_descriptors(); +} + +void eventfd_select_interrupter::close_descriptors() +{ + if (write_descriptor_ != -1 && write_descriptor_ != read_descriptor_) + ::close(write_descriptor_); + if (read_descriptor_ != -1) + ::close(read_descriptor_); +} + +void eventfd_select_interrupter::recreate() +{ + close_descriptors(); + + write_descriptor_ = -1; + read_descriptor_ = -1; + + open_descriptors(); +} + +void eventfd_select_interrupter::interrupt() +{ + uint64_t counter(1UL); + int result = ::write(write_descriptor_, &counter, sizeof(uint64_t)); + (void)result; +} + +bool eventfd_select_interrupter::reset() +{ + if (write_descriptor_ == read_descriptor_) + { + for (;;) + { + // Only perform one read. The kernel maintains an atomic counter. + uint64_t counter(0); + errno = 0; + int bytes_read = ::read(read_descriptor_, &counter, sizeof(uint64_t)); + if (bytes_read < 0 && errno == EINTR) + continue; + return true; + } + } + else + { + for (;;) + { + // Clear all data from the pipe. + char data[1024]; + int bytes_read = ::read(read_descriptor_, data, sizeof(data)); + if (bytes_read == sizeof(data)) + continue; + if (bytes_read > 0) + return true; + if (bytes_read == 0) + return false; + if (errno == EINTR) + continue; + if (errno == EWOULDBLOCK || errno == EAGAIN) + return true; + return false; + } + } +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_EVENTFD) + +#endif // ASIO_DETAIL_IMPL_EVENTFD_SELECT_INTERRUPTER_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/handler_tracking.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/handler_tracking.ipp new file mode 100644 index 000000000..14f64abe5 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/handler_tracking.ipp @@ -0,0 +1,396 @@ +// +// detail/impl/handler_tracking.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_HANDLER_TRACKING_IPP +#define ASIO_DETAIL_IMPL_HANDLER_TRACKING_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_CUSTOM_HANDLER_TRACKING) + +// The handler tracking implementation is provided by the user-specified header. + +#elif defined(ASIO_ENABLE_HANDLER_TRACKING) + +#include +#include +#include "asio/detail/handler_tracking.hpp" + +#if defined(ASIO_HAS_BOOST_DATE_TIME) +# include "asio/time_traits.hpp" +#elif defined(ASIO_HAS_CHRONO) +# include "asio/detail/chrono.hpp" +# include "asio/detail/chrono_time_traits.hpp" +# include "asio/wait_traits.hpp" +#endif // defined(ASIO_HAS_BOOST_DATE_TIME) + +#if defined(ASIO_WINDOWS_RUNTIME) +# include "asio/detail/socket_types.hpp" +#elif !defined(ASIO_WINDOWS) +# include +#endif // !defined(ASIO_WINDOWS) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +struct handler_tracking_timestamp +{ + uint64_t seconds; + uint64_t microseconds; + + handler_tracking_timestamp() + { +#if defined(ASIO_HAS_BOOST_DATE_TIME) + boost::posix_time::ptime epoch(boost::gregorian::date(1970, 1, 1)); + boost::posix_time::time_duration now = + boost::posix_time::microsec_clock::universal_time() - epoch; +#elif defined(ASIO_HAS_CHRONO) + typedef chrono_time_traits > traits_helper; + traits_helper::posix_time_duration now( + chrono::system_clock::now().time_since_epoch()); +#endif + seconds = static_cast(now.total_seconds()); + microseconds = static_cast(now.total_microseconds() % 1000000); + } +}; + +struct handler_tracking::tracking_state +{ + static_mutex mutex_; + uint64_t next_id_; + tss_ptr* current_completion_; + tss_ptr* current_location_; +}; + +handler_tracking::tracking_state* handler_tracking::get_state() +{ + static tracking_state state = { ASIO_STATIC_MUTEX_INIT, 1, 0, 0 }; + return &state; +} + +void handler_tracking::init() +{ + static tracking_state* state = get_state(); + + state->mutex_.init(); + + static_mutex::scoped_lock lock(state->mutex_); + if (state->current_completion_ == 0) + state->current_completion_ = new tss_ptr; + if (state->current_location_ == 0) + state->current_location_ = new tss_ptr; +} + +handler_tracking::location::location( + const char* file, int line, const char* func) + : file_(file), + line_(line), + func_(func), + next_(*get_state()->current_location_) +{ + if (file_) + *get_state()->current_location_ = this; +} + +handler_tracking::location::~location() +{ + if (file_) + *get_state()->current_location_ = next_; +} + +void handler_tracking::creation(execution_context&, + handler_tracking::tracked_handler& h, + const char* object_type, void* object, + uintmax_t /*native_handle*/, const char* op_name) +{ + static tracking_state* state = get_state(); + + static_mutex::scoped_lock lock(state->mutex_); + h.id_ = state->next_id_++; + lock.unlock(); + + handler_tracking_timestamp timestamp; + + uint64_t current_id = 0; + if (completion* current_completion = *state->current_completion_) + current_id = current_completion->id_; + + for (location* current_location = *state->current_location_; + current_location; current_location = current_location->next_) + { + write_line( +#if defined(ASIO_WINDOWS) + "@asio|%I64u.%06I64u|%I64u^%I64u|%s%s%.80s%s(%.80s:%d)\n", +#else // defined(ASIO_WINDOWS) + "@asio|%llu.%06llu|%llu^%llu|%s%s%.80s%s(%.80s:%d)\n", +#endif // defined(ASIO_WINDOWS) + timestamp.seconds, timestamp.microseconds, + current_id, h.id_, + current_location == *state->current_location_ ? "in " : "called from ", + current_location->func_ ? "'" : "", + current_location->func_ ? current_location->func_ : "", + current_location->func_ ? "' " : "", + current_location->file_, current_location->line_); + } + + write_line( +#if defined(ASIO_WINDOWS) + "@asio|%I64u.%06I64u|%I64u*%I64u|%.20s@%p.%.50s\n", +#else // defined(ASIO_WINDOWS) + "@asio|%llu.%06llu|%llu*%llu|%.20s@%p.%.50s\n", +#endif // defined(ASIO_WINDOWS) + timestamp.seconds, timestamp.microseconds, + current_id, h.id_, object_type, object, op_name); +} + +handler_tracking::completion::completion( + const handler_tracking::tracked_handler& h) + : id_(h.id_), + invoked_(false), + next_(*get_state()->current_completion_) +{ + *get_state()->current_completion_ = this; +} + +handler_tracking::completion::~completion() +{ + if (id_) + { + handler_tracking_timestamp timestamp; + + write_line( +#if defined(ASIO_WINDOWS) + "@asio|%I64u.%06I64u|%c%I64u|\n", +#else // defined(ASIO_WINDOWS) + "@asio|%llu.%06llu|%c%llu|\n", +#endif // defined(ASIO_WINDOWS) + timestamp.seconds, timestamp.microseconds, + invoked_ ? '!' : '~', id_); + } + + *get_state()->current_completion_ = next_; +} + +void handler_tracking::completion::invocation_begin() +{ + handler_tracking_timestamp timestamp; + + write_line( +#if defined(ASIO_WINDOWS) + "@asio|%I64u.%06I64u|>%I64u|\n", +#else // defined(ASIO_WINDOWS) + "@asio|%llu.%06llu|>%llu|\n", +#endif // defined(ASIO_WINDOWS) + timestamp.seconds, timestamp.microseconds, id_); + + invoked_ = true; +} + +void handler_tracking::completion::invocation_begin( + const asio::error_code& ec) +{ + handler_tracking_timestamp timestamp; + + write_line( +#if defined(ASIO_WINDOWS) + "@asio|%I64u.%06I64u|>%I64u|ec=%.20s:%d\n", +#else // defined(ASIO_WINDOWS) + "@asio|%llu.%06llu|>%llu|ec=%.20s:%d\n", +#endif // defined(ASIO_WINDOWS) + timestamp.seconds, timestamp.microseconds, + id_, ec.category().name(), ec.value()); + + invoked_ = true; +} + +void handler_tracking::completion::invocation_begin( + const asio::error_code& ec, std::size_t bytes_transferred) +{ + handler_tracking_timestamp timestamp; + + write_line( +#if defined(ASIO_WINDOWS) + "@asio|%I64u.%06I64u|>%I64u|ec=%.20s:%d,bytes_transferred=%I64u\n", +#else // defined(ASIO_WINDOWS) + "@asio|%llu.%06llu|>%llu|ec=%.20s:%d,bytes_transferred=%llu\n", +#endif // defined(ASIO_WINDOWS) + timestamp.seconds, timestamp.microseconds, + id_, ec.category().name(), ec.value(), + static_cast(bytes_transferred)); + + invoked_ = true; +} + +void handler_tracking::completion::invocation_begin( + const asio::error_code& ec, int signal_number) +{ + handler_tracking_timestamp timestamp; + + write_line( +#if defined(ASIO_WINDOWS) + "@asio|%I64u.%06I64u|>%I64u|ec=%.20s:%d,signal_number=%d\n", +#else // defined(ASIO_WINDOWS) + "@asio|%llu.%06llu|>%llu|ec=%.20s:%d,signal_number=%d\n", +#endif // defined(ASIO_WINDOWS) + timestamp.seconds, timestamp.microseconds, + id_, ec.category().name(), ec.value(), signal_number); + + invoked_ = true; +} + +void handler_tracking::completion::invocation_begin( + const asio::error_code& ec, const char* arg) +{ + handler_tracking_timestamp timestamp; + + write_line( +#if defined(ASIO_WINDOWS) + "@asio|%I64u.%06I64u|>%I64u|ec=%.20s:%d,%.50s\n", +#else // defined(ASIO_WINDOWS) + "@asio|%llu.%06llu|>%llu|ec=%.20s:%d,%.50s\n", +#endif // defined(ASIO_WINDOWS) + timestamp.seconds, timestamp.microseconds, + id_, ec.category().name(), ec.value(), arg); + + invoked_ = true; +} + +void handler_tracking::completion::invocation_end() +{ + if (id_) + { + handler_tracking_timestamp timestamp; + + write_line( +#if defined(ASIO_WINDOWS) + "@asio|%I64u.%06I64u|<%I64u|\n", +#else // defined(ASIO_WINDOWS) + "@asio|%llu.%06llu|<%llu|\n", +#endif // defined(ASIO_WINDOWS) + timestamp.seconds, timestamp.microseconds, id_); + + id_ = 0; + } +} + +void handler_tracking::operation(execution_context&, + const char* object_type, void* object, + uintmax_t /*native_handle*/, const char* op_name) +{ + static tracking_state* state = get_state(); + + handler_tracking_timestamp timestamp; + + unsigned long long current_id = 0; + if (completion* current_completion = *state->current_completion_) + current_id = current_completion->id_; + + write_line( +#if defined(ASIO_WINDOWS) + "@asio|%I64u.%06I64u|%I64u|%.20s@%p.%.50s\n", +#else // defined(ASIO_WINDOWS) + "@asio|%llu.%06llu|%llu|%.20s@%p.%.50s\n", +#endif // defined(ASIO_WINDOWS) + timestamp.seconds, timestamp.microseconds, + current_id, object_type, object, op_name); +} + +void handler_tracking::reactor_registration(execution_context& /*context*/, + uintmax_t /*native_handle*/, uintmax_t /*registration*/) +{ +} + +void handler_tracking::reactor_deregistration(execution_context& /*context*/, + uintmax_t /*native_handle*/, uintmax_t /*registration*/) +{ +} + +void handler_tracking::reactor_events(execution_context& /*context*/, + uintmax_t /*native_handle*/, unsigned /*events*/) +{ +} + +void handler_tracking::reactor_operation( + const tracked_handler& h, const char* op_name, + const asio::error_code& ec) +{ + handler_tracking_timestamp timestamp; + + write_line( +#if defined(ASIO_WINDOWS) + "@asio|%I64u.%06I64u|.%I64u|%s,ec=%.20s:%d\n", +#else // defined(ASIO_WINDOWS) + "@asio|%llu.%06llu|.%llu|%s,ec=%.20s:%d\n", +#endif // defined(ASIO_WINDOWS) + timestamp.seconds, timestamp.microseconds, + h.id_, op_name, ec.category().name(), ec.value()); +} + +void handler_tracking::reactor_operation( + const tracked_handler& h, const char* op_name, + const asio::error_code& ec, std::size_t bytes_transferred) +{ + handler_tracking_timestamp timestamp; + + write_line( +#if defined(ASIO_WINDOWS) + "@asio|%I64u.%06I64u|.%I64u|%s,ec=%.20s:%d,bytes_transferred=%I64u\n", +#else // defined(ASIO_WINDOWS) + "@asio|%llu.%06llu|.%llu|%s,ec=%.20s:%d,bytes_transferred=%llu\n", +#endif // defined(ASIO_WINDOWS) + timestamp.seconds, timestamp.microseconds, + h.id_, op_name, ec.category().name(), ec.value(), + static_cast(bytes_transferred)); +} + +void handler_tracking::write_line(const char* format, ...) +{ + using namespace std; // For sprintf (or equivalent). + + va_list args; + va_start(args, format); + + char line[256] = ""; +#if defined(ASIO_HAS_SECURE_RTL) + int length = vsprintf_s(line, sizeof(line), format, args); +#else // defined(ASIO_HAS_SECURE_RTL) + int length = vsprintf(line, format, args); +#endif // defined(ASIO_HAS_SECURE_RTL) + + va_end(args); + +#if defined(ASIO_WINDOWS_RUNTIME) + wchar_t wline[256] = L""; + mbstowcs_s(0, wline, sizeof(wline) / sizeof(wchar_t), line, length); + ::OutputDebugStringW(wline); +#elif defined(ASIO_WINDOWS) + HANDLE stderr_handle = ::GetStdHandle(STD_ERROR_HANDLE); + DWORD bytes_written = 0; + ::WriteFile(stderr_handle, line, length, &bytes_written, 0); +#else // defined(ASIO_WINDOWS) + ::write(STDERR_FILENO, line, length); +#endif // defined(ASIO_WINDOWS) +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_ENABLE_HANDLER_TRACKING) + +#endif // ASIO_DETAIL_IMPL_HANDLER_TRACKING_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/kqueue_reactor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/kqueue_reactor.hpp new file mode 100644 index 000000000..6897dc219 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/kqueue_reactor.hpp @@ -0,0 +1,93 @@ +// +// detail/impl/kqueue_reactor.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// Copyright (c) 2005 Stefan Arentz (stefan at soze dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_KQUEUE_REACTOR_HPP +#define ASIO_DETAIL_IMPL_KQUEUE_REACTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_KQUEUE) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +void kqueue_reactor::add_timer_queue(timer_queue& queue) +{ + do_add_timer_queue(queue); +} + +// Remove a timer queue from the reactor. +template +void kqueue_reactor::remove_timer_queue(timer_queue& queue) +{ + do_remove_timer_queue(queue); +} + +template +void kqueue_reactor::schedule_timer(timer_queue& queue, + const typename Time_Traits::time_type& time, + typename timer_queue::per_timer_data& timer, wait_op* op) +{ + mutex::scoped_lock lock(mutex_); + + if (shutdown_) + { + scheduler_.post_immediate_completion(op, false); + return; + } + + bool earliest = queue.enqueue_timer(time, timer, op); + scheduler_.work_started(); + if (earliest) + interrupt(); +} + +template +std::size_t kqueue_reactor::cancel_timer(timer_queue& queue, + typename timer_queue::per_timer_data& timer, + std::size_t max_cancelled) +{ + mutex::scoped_lock lock(mutex_); + op_queue ops; + std::size_t n = queue.cancel_timer(timer, ops, max_cancelled); + lock.unlock(); + scheduler_.post_deferred_completions(ops); + return n; +} + +template +void kqueue_reactor::move_timer(timer_queue& queue, + typename timer_queue::per_timer_data& target, + typename timer_queue::per_timer_data& source) +{ + mutex::scoped_lock lock(mutex_); + op_queue ops; + queue.cancel_timer(target, ops); + queue.move_timer(target, source); + lock.unlock(); + scheduler_.post_deferred_completions(ops); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_KQUEUE) + +#endif // ASIO_DETAIL_IMPL_KQUEUE_REACTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/kqueue_reactor.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/kqueue_reactor.ipp new file mode 100644 index 000000000..74de09197 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/kqueue_reactor.ipp @@ -0,0 +1,570 @@ +// +// detail/impl/kqueue_reactor.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// Copyright (c) 2005 Stefan Arentz (stefan at soze dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_KQUEUE_REACTOR_IPP +#define ASIO_DETAIL_IMPL_KQUEUE_REACTOR_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_KQUEUE) + +#include "asio/detail/kqueue_reactor.hpp" +#include "asio/detail/scheduler.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" + +#if defined(__NetBSD__) +# include +#endif + +#include "asio/detail/push_options.hpp" + +#if defined(__NetBSD__) && __NetBSD_Version__ < 999001500 +# define ASIO_KQUEUE_EV_SET(ev, ident, filt, flags, fflags, data, udata) \ + EV_SET(ev, ident, filt, flags, fflags, data, \ + reinterpret_cast(static_cast(udata))) +#else +# define ASIO_KQUEUE_EV_SET(ev, ident, filt, flags, fflags, data, udata) \ + EV_SET(ev, ident, filt, flags, fflags, data, udata) +#endif + +namespace asio { +namespace detail { + +kqueue_reactor::kqueue_reactor(asio::execution_context& ctx) + : execution_context_service_base(ctx), + scheduler_(use_service(ctx)), + mutex_(ASIO_CONCURRENCY_HINT_IS_LOCKING( + REACTOR_REGISTRATION, scheduler_.concurrency_hint())), + kqueue_fd_(do_kqueue_create()), + interrupter_(), + shutdown_(false), + registered_descriptors_mutex_(mutex_.enabled()) +{ + struct kevent events[1]; + ASIO_KQUEUE_EV_SET(&events[0], interrupter_.read_descriptor(), + EVFILT_READ, EV_ADD, 0, 0, &interrupter_); + if (::kevent(kqueue_fd_, events, 1, 0, 0, 0) == -1) + { + asio::error_code error(errno, + asio::error::get_system_category()); + asio::detail::throw_error(error); + } +} + +kqueue_reactor::~kqueue_reactor() +{ + close(kqueue_fd_); +} + +void kqueue_reactor::shutdown() +{ + mutex::scoped_lock lock(mutex_); + shutdown_ = true; + lock.unlock(); + + op_queue ops; + + while (descriptor_state* state = registered_descriptors_.first()) + { + for (int i = 0; i < max_ops; ++i) + ops.push(state->op_queue_[i]); + state->shutdown_ = true; + registered_descriptors_.free(state); + } + + timer_queues_.get_all_timers(ops); + + scheduler_.abandon_operations(ops); +} + +void kqueue_reactor::notify_fork( + asio::execution_context::fork_event fork_ev) +{ + if (fork_ev == asio::execution_context::fork_child) + { + // The kqueue descriptor is automatically closed in the child. + kqueue_fd_ = -1; + kqueue_fd_ = do_kqueue_create(); + + interrupter_.recreate(); + + struct kevent events[2]; + ASIO_KQUEUE_EV_SET(&events[0], interrupter_.read_descriptor(), + EVFILT_READ, EV_ADD, 0, 0, &interrupter_); + if (::kevent(kqueue_fd_, events, 1, 0, 0, 0) == -1) + { + asio::error_code ec(errno, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "kqueue interrupter registration"); + } + + // Re-register all descriptors with kqueue. + mutex::scoped_lock descriptors_lock(registered_descriptors_mutex_); + for (descriptor_state* state = registered_descriptors_.first(); + state != 0; state = state->next_) + { + if (state->num_kevents_ > 0) + { + ASIO_KQUEUE_EV_SET(&events[0], state->descriptor_, + EVFILT_READ, EV_ADD | EV_CLEAR, 0, 0, state); + ASIO_KQUEUE_EV_SET(&events[1], state->descriptor_, + EVFILT_WRITE, EV_ADD | EV_CLEAR, 0, 0, state); + if (::kevent(kqueue_fd_, events, state->num_kevents_, 0, 0, 0) == -1) + { + asio::error_code ec(errno, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "kqueue re-registration"); + } + } + } + } +} + +void kqueue_reactor::init_task() +{ + scheduler_.init_task(); +} + +int kqueue_reactor::register_descriptor(socket_type descriptor, + kqueue_reactor::per_descriptor_data& descriptor_data) +{ + descriptor_data = allocate_descriptor_state(); + + ASIO_HANDLER_REACTOR_REGISTRATION(( + context(), static_cast(descriptor), + reinterpret_cast(descriptor_data))); + + mutex::scoped_lock lock(descriptor_data->mutex_); + + descriptor_data->descriptor_ = descriptor; + descriptor_data->num_kevents_ = 0; + descriptor_data->shutdown_ = false; + + return 0; +} + +int kqueue_reactor::register_internal_descriptor( + int op_type, socket_type descriptor, + kqueue_reactor::per_descriptor_data& descriptor_data, reactor_op* op) +{ + descriptor_data = allocate_descriptor_state(); + + ASIO_HANDLER_REACTOR_REGISTRATION(( + context(), static_cast(descriptor), + reinterpret_cast(descriptor_data))); + + mutex::scoped_lock lock(descriptor_data->mutex_); + + descriptor_data->descriptor_ = descriptor; + descriptor_data->num_kevents_ = 1; + descriptor_data->shutdown_ = false; + descriptor_data->op_queue_[op_type].push(op); + + struct kevent events[1]; + ASIO_KQUEUE_EV_SET(&events[0], descriptor, EVFILT_READ, + EV_ADD | EV_CLEAR, 0, 0, descriptor_data); + if (::kevent(kqueue_fd_, events, 1, 0, 0, 0) == -1) + return errno; + + return 0; +} + +void kqueue_reactor::move_descriptor(socket_type, + kqueue_reactor::per_descriptor_data& target_descriptor_data, + kqueue_reactor::per_descriptor_data& source_descriptor_data) +{ + target_descriptor_data = source_descriptor_data; + source_descriptor_data = 0; +} + +void kqueue_reactor::start_op(int op_type, socket_type descriptor, + kqueue_reactor::per_descriptor_data& descriptor_data, reactor_op* op, + bool is_continuation, bool allow_speculative) +{ + if (!descriptor_data) + { + op->ec_ = asio::error::bad_descriptor; + post_immediate_completion(op, is_continuation); + return; + } + + mutex::scoped_lock descriptor_lock(descriptor_data->mutex_); + + if (descriptor_data->shutdown_) + { + post_immediate_completion(op, is_continuation); + return; + } + + if (descriptor_data->op_queue_[op_type].empty()) + { + static const int num_kevents[max_ops] = { 1, 2, 1 }; + + if (allow_speculative + && (op_type != read_op + || descriptor_data->op_queue_[except_op].empty())) + { + if (op->perform()) + { + descriptor_lock.unlock(); + scheduler_.post_immediate_completion(op, is_continuation); + return; + } + + if (descriptor_data->num_kevents_ < num_kevents[op_type]) + { + struct kevent events[2]; + ASIO_KQUEUE_EV_SET(&events[0], descriptor, EVFILT_READ, + EV_ADD | EV_CLEAR, 0, 0, descriptor_data); + ASIO_KQUEUE_EV_SET(&events[1], descriptor, EVFILT_WRITE, + EV_ADD | EV_CLEAR, 0, 0, descriptor_data); + if (::kevent(kqueue_fd_, events, num_kevents[op_type], 0, 0, 0) != -1) + { + descriptor_data->num_kevents_ = num_kevents[op_type]; + } + else + { + op->ec_ = asio::error_code(errno, + asio::error::get_system_category()); + scheduler_.post_immediate_completion(op, is_continuation); + return; + } + } + } + else + { + if (descriptor_data->num_kevents_ < num_kevents[op_type]) + descriptor_data->num_kevents_ = num_kevents[op_type]; + + struct kevent events[2]; + ASIO_KQUEUE_EV_SET(&events[0], descriptor, EVFILT_READ, + EV_ADD | EV_CLEAR, 0, 0, descriptor_data); + ASIO_KQUEUE_EV_SET(&events[1], descriptor, EVFILT_WRITE, + EV_ADD | EV_CLEAR, 0, 0, descriptor_data); + ::kevent(kqueue_fd_, events, descriptor_data->num_kevents_, 0, 0, 0); + } + } + + descriptor_data->op_queue_[op_type].push(op); + scheduler_.work_started(); +} + +void kqueue_reactor::cancel_ops(socket_type, + kqueue_reactor::per_descriptor_data& descriptor_data) +{ + if (!descriptor_data) + return; + + mutex::scoped_lock descriptor_lock(descriptor_data->mutex_); + + op_queue ops; + for (int i = 0; i < max_ops; ++i) + { + while (reactor_op* op = descriptor_data->op_queue_[i].front()) + { + op->ec_ = asio::error::operation_aborted; + descriptor_data->op_queue_[i].pop(); + ops.push(op); + } + } + + descriptor_lock.unlock(); + + scheduler_.post_deferred_completions(ops); +} + +void kqueue_reactor::deregister_descriptor(socket_type descriptor, + kqueue_reactor::per_descriptor_data& descriptor_data, bool closing) +{ + if (!descriptor_data) + return; + + mutex::scoped_lock descriptor_lock(descriptor_data->mutex_); + + if (!descriptor_data->shutdown_) + { + if (closing) + { + // The descriptor will be automatically removed from the kqueue when it + // is closed. + } + else + { + struct kevent events[2]; + ASIO_KQUEUE_EV_SET(&events[0], descriptor, + EVFILT_READ, EV_DELETE, 0, 0, 0); + ASIO_KQUEUE_EV_SET(&events[1], descriptor, + EVFILT_WRITE, EV_DELETE, 0, 0, 0); + ::kevent(kqueue_fd_, events, descriptor_data->num_kevents_, 0, 0, 0); + } + + op_queue ops; + for (int i = 0; i < max_ops; ++i) + { + while (reactor_op* op = descriptor_data->op_queue_[i].front()) + { + op->ec_ = asio::error::operation_aborted; + descriptor_data->op_queue_[i].pop(); + ops.push(op); + } + } + + descriptor_data->descriptor_ = -1; + descriptor_data->shutdown_ = true; + + descriptor_lock.unlock(); + + ASIO_HANDLER_REACTOR_DEREGISTRATION(( + context(), static_cast(descriptor), + reinterpret_cast(descriptor_data))); + + scheduler_.post_deferred_completions(ops); + + // Leave descriptor_data set so that it will be freed by the subsequent + // call to cleanup_descriptor_data. + } + else + { + // We are shutting down, so prevent cleanup_descriptor_data from freeing + // the descriptor_data object and let the destructor free it instead. + descriptor_data = 0; + } +} + +void kqueue_reactor::deregister_internal_descriptor(socket_type descriptor, + kqueue_reactor::per_descriptor_data& descriptor_data) +{ + if (!descriptor_data) + return; + + mutex::scoped_lock descriptor_lock(descriptor_data->mutex_); + + if (!descriptor_data->shutdown_) + { + struct kevent events[2]; + ASIO_KQUEUE_EV_SET(&events[0], descriptor, + EVFILT_READ, EV_DELETE, 0, 0, 0); + ASIO_KQUEUE_EV_SET(&events[1], descriptor, + EVFILT_WRITE, EV_DELETE, 0, 0, 0); + ::kevent(kqueue_fd_, events, descriptor_data->num_kevents_, 0, 0, 0); + + op_queue ops; + for (int i = 0; i < max_ops; ++i) + ops.push(descriptor_data->op_queue_[i]); + + descriptor_data->descriptor_ = -1; + descriptor_data->shutdown_ = true; + + descriptor_lock.unlock(); + + ASIO_HANDLER_REACTOR_DEREGISTRATION(( + context(), static_cast(descriptor), + reinterpret_cast(descriptor_data))); + + // Leave descriptor_data set so that it will be freed by the subsequent + // call to cleanup_descriptor_data. + } + else + { + // We are shutting down, so prevent cleanup_descriptor_data from freeing + // the descriptor_data object and let the destructor free it instead. + descriptor_data = 0; + } +} + +void kqueue_reactor::cleanup_descriptor_data( + per_descriptor_data& descriptor_data) +{ + if (descriptor_data) + { + free_descriptor_state(descriptor_data); + descriptor_data = 0; + } +} + +void kqueue_reactor::run(long usec, op_queue& ops) +{ + mutex::scoped_lock lock(mutex_); + + // Determine how long to block while waiting for events. + timespec timeout_buf = { 0, 0 }; + timespec* timeout = usec ? get_timeout(usec, timeout_buf) : &timeout_buf; + + lock.unlock(); + + // Block on the kqueue descriptor. + struct kevent events[128]; + int num_events = kevent(kqueue_fd_, 0, 0, events, 128, timeout); + +#if defined(ASIO_ENABLE_HANDLER_TRACKING) + // Trace the waiting events. + for (int i = 0; i < num_events; ++i) + { + void* ptr = reinterpret_cast(events[i].udata); + if (ptr != &interrupter_) + { + unsigned event_mask = 0; + switch (events[i].filter) + { + case EVFILT_READ: + event_mask |= ASIO_HANDLER_REACTOR_READ_EVENT; + break; + case EVFILT_WRITE: + event_mask |= ASIO_HANDLER_REACTOR_WRITE_EVENT; + break; + } + if ((events[i].flags & (EV_ERROR | EV_OOBAND)) != 0) + event_mask |= ASIO_HANDLER_REACTOR_ERROR_EVENT; + ASIO_HANDLER_REACTOR_EVENTS((context(), + reinterpret_cast(ptr), event_mask)); + } + } +#endif // defined(ASIO_ENABLE_HANDLER_TRACKING) + + // Dispatch the waiting events. + for (int i = 0; i < num_events; ++i) + { + void* ptr = reinterpret_cast(events[i].udata); + if (ptr == &interrupter_) + { + interrupter_.reset(); + } + else + { + descriptor_state* descriptor_data = static_cast(ptr); + mutex::scoped_lock descriptor_lock(descriptor_data->mutex_); + + if (events[i].filter == EVFILT_WRITE + && descriptor_data->num_kevents_ == 2 + && descriptor_data->op_queue_[write_op].empty()) + { + // Some descriptor types, like serial ports, don't seem to support + // EV_CLEAR with EVFILT_WRITE. Since we have no pending write + // operations we'll remove the EVFILT_WRITE registration here so that + // we don't end up in a tight spin. + struct kevent delete_events[1]; + ASIO_KQUEUE_EV_SET(&delete_events[0], + descriptor_data->descriptor_, EVFILT_WRITE, EV_DELETE, 0, 0, 0); + ::kevent(kqueue_fd_, delete_events, 1, 0, 0, 0); + descriptor_data->num_kevents_ = 1; + } + + // Exception operations must be processed first to ensure that any + // out-of-band data is read before normal data. +#if defined(__NetBSD__) + static const unsigned int filter[max_ops] = +#else + static const int filter[max_ops] = +#endif + { EVFILT_READ, EVFILT_WRITE, EVFILT_READ }; + for (int j = max_ops - 1; j >= 0; --j) + { + if (events[i].filter == filter[j]) + { + if (j != except_op || events[i].flags & EV_OOBAND) + { + while (reactor_op* op = descriptor_data->op_queue_[j].front()) + { + if (events[i].flags & EV_ERROR) + { + op->ec_ = asio::error_code( + static_cast(events[i].data), + asio::error::get_system_category()); + descriptor_data->op_queue_[j].pop(); + ops.push(op); + } + if (op->perform()) + { + descriptor_data->op_queue_[j].pop(); + ops.push(op); + } + else + break; + } + } + } + } + } + } + + lock.lock(); + timer_queues_.get_ready_timers(ops); +} + +void kqueue_reactor::interrupt() +{ + interrupter_.interrupt(); +} + +int kqueue_reactor::do_kqueue_create() +{ + int fd = ::kqueue(); + if (fd == -1) + { + asio::error_code ec(errno, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "kqueue"); + } + return fd; +} + +kqueue_reactor::descriptor_state* kqueue_reactor::allocate_descriptor_state() +{ + mutex::scoped_lock descriptors_lock(registered_descriptors_mutex_); + return registered_descriptors_.alloc(ASIO_CONCURRENCY_HINT_IS_LOCKING( + REACTOR_IO, scheduler_.concurrency_hint())); +} + +void kqueue_reactor::free_descriptor_state(kqueue_reactor::descriptor_state* s) +{ + mutex::scoped_lock descriptors_lock(registered_descriptors_mutex_); + registered_descriptors_.free(s); +} + +void kqueue_reactor::do_add_timer_queue(timer_queue_base& queue) +{ + mutex::scoped_lock lock(mutex_); + timer_queues_.insert(&queue); +} + +void kqueue_reactor::do_remove_timer_queue(timer_queue_base& queue) +{ + mutex::scoped_lock lock(mutex_); + timer_queues_.erase(&queue); +} + +timespec* kqueue_reactor::get_timeout(long usec, timespec& ts) +{ + // By default we will wait no longer than 5 minutes. This will ensure that + // any changes to the system clock are detected after no longer than this. + const long max_usec = 5 * 60 * 1000 * 1000; + usec = timer_queues_.wait_duration_usec( + (usec < 0 || max_usec < usec) ? max_usec : usec); + ts.tv_sec = usec / 1000000; + ts.tv_nsec = (usec % 1000000) * 1000; + return &ts; +} + +} // namespace detail +} // namespace asio + +#undef ASIO_KQUEUE_EV_SET + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_KQUEUE) + +#endif // ASIO_DETAIL_IMPL_KQUEUE_REACTOR_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/null_event.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/null_event.ipp new file mode 100644 index 000000000..3f47e599b --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/null_event.ipp @@ -0,0 +1,74 @@ +// +// detail/impl/null_event.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_NULL_EVENT_IPP +#define ASIO_DETAIL_IMPL_NULL_EVENT_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) +# include +#elif defined(ASIO_WINDOWS) || defined(__CYGWIN__) +# include "asio/detail/socket_types.hpp" +#else +# include +# if defined(__hpux) +# include +# endif +# if !defined(__hpux) || defined(__SELECT) +# include +# endif +#endif + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +void null_event::do_wait() +{ +#if defined(ASIO_WINDOWS_RUNTIME) + std::this_thread::sleep_until((std::chrono::steady_clock::time_point::max)()); +#elif defined(ASIO_WINDOWS) || defined(__CYGWIN__) + ::Sleep(INFINITE); +#else + ::pause(); +#endif +} + +void null_event::do_wait_for_usec(long usec) +{ +#if defined(ASIO_WINDOWS_RUNTIME) + std::this_thread::sleep_for(std::chrono::microseconds(usec)); +#elif defined(ASIO_WINDOWS) || defined(__CYGWIN__) + ::Sleep(usec / 1000); +#elif defined(__hpux) && defined(__SELECT) + timespec ts; + ts.tv_sec = usec / 1000000; + ts.tv_nsec = (usec % 1000000) * 1000; + ::pselect(0, 0, 0, 0, &ts, 0); +#else + timeval tv; + tv.tv_sec = usec / 1000000; + tv.tv_usec = usec % 1000000; + ::select(0, 0, 0, 0, &tv); +#endif +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_IMPL_NULL_EVENT_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/pipe_select_interrupter.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/pipe_select_interrupter.ipp new file mode 100644 index 000000000..ddbbe61ee --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/pipe_select_interrupter.ipp @@ -0,0 +1,129 @@ +// +// detail/impl/pipe_select_interrupter.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_PIPE_SELECT_INTERRUPTER_IPP +#define ASIO_DETAIL_IMPL_PIPE_SELECT_INTERRUPTER_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_WINDOWS_RUNTIME) +#if !defined(ASIO_WINDOWS) +#if !defined(__CYGWIN__) +#if !defined(__SYMBIAN32__) +#if !defined(ASIO_HAS_EVENTFD) + +#include +#include +#include +#include +#include "asio/detail/pipe_select_interrupter.hpp" +#include "asio/detail/socket_types.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +pipe_select_interrupter::pipe_select_interrupter() +{ + open_descriptors(); +} + +void pipe_select_interrupter::open_descriptors() +{ + int pipe_fds[2]; + if (pipe(pipe_fds) == 0) + { + read_descriptor_ = pipe_fds[0]; + ::fcntl(read_descriptor_, F_SETFL, O_NONBLOCK); + write_descriptor_ = pipe_fds[1]; + ::fcntl(write_descriptor_, F_SETFL, O_NONBLOCK); + +#if defined(FD_CLOEXEC) + ::fcntl(read_descriptor_, F_SETFD, FD_CLOEXEC); + ::fcntl(write_descriptor_, F_SETFD, FD_CLOEXEC); +#endif // defined(FD_CLOEXEC) + } + else + { + asio::error_code ec(errno, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "pipe_select_interrupter"); + } +} + +pipe_select_interrupter::~pipe_select_interrupter() +{ + close_descriptors(); +} + +void pipe_select_interrupter::close_descriptors() +{ + if (read_descriptor_ != -1) + ::close(read_descriptor_); + if (write_descriptor_ != -1) + ::close(write_descriptor_); +} + +void pipe_select_interrupter::recreate() +{ + close_descriptors(); + + write_descriptor_ = -1; + read_descriptor_ = -1; + + open_descriptors(); +} + +void pipe_select_interrupter::interrupt() +{ + char byte = 0; + signed_size_type result = ::write(write_descriptor_, &byte, 1); + (void)result; +} + +bool pipe_select_interrupter::reset() +{ + for (;;) + { + char data[1024]; + signed_size_type bytes_read = ::read(read_descriptor_, data, sizeof(data)); + if (bytes_read == sizeof(data)) + continue; + if (bytes_read > 0) + return true; + if (bytes_read == 0) + return false; + if (errno == EINTR) + continue; + if (errno == EWOULDBLOCK || errno == EAGAIN) + return true; + return false; + } +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_HAS_EVENTFD) +#endif // !defined(__SYMBIAN32__) +#endif // !defined(__CYGWIN__) +#endif // !defined(ASIO_WINDOWS) +#endif // !defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_IMPL_PIPE_SELECT_INTERRUPTER_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/posix_event.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/posix_event.ipp new file mode 100644 index 000000000..6d2b5e0a5 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/posix_event.ipp @@ -0,0 +1,59 @@ +// +// detail/impl/posix_event.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_POSIX_EVENT_IPP +#define ASIO_DETAIL_IMPL_POSIX_EVENT_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_PTHREADS) + +#include "asio/detail/posix_event.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +posix_event::posix_event() + : state_(0) +{ +#if (defined(__MACH__) && defined(__APPLE__)) \ + || (defined(__ANDROID__) && (__ANDROID_API__ < 21)) + int error = ::pthread_cond_init(&cond_, 0); +#else // (defined(__MACH__) && defined(__APPLE__)) + // || (defined(__ANDROID__) && (__ANDROID_API__ < 21)) + ::pthread_condattr_t attr; + ::pthread_condattr_init(&attr); + int error = ::pthread_condattr_setclock(&attr, CLOCK_MONOTONIC); + if (error == 0) + error = ::pthread_cond_init(&cond_, &attr); +#endif // (defined(__MACH__) && defined(__APPLE__)) + // || (defined(__ANDROID__) && (__ANDROID_API__ < 21)) + + asio::error_code ec(error, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "event"); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_PTHREADS) + +#endif // ASIO_DETAIL_IMPL_POSIX_EVENT_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/posix_mutex.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/posix_mutex.ipp new file mode 100644 index 000000000..03161d1f3 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/posix_mutex.ipp @@ -0,0 +1,46 @@ +// +// detail/impl/posix_mutex.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_POSIX_MUTEX_IPP +#define ASIO_DETAIL_IMPL_POSIX_MUTEX_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_PTHREADS) + +#include "asio/detail/posix_mutex.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +posix_mutex::posix_mutex() +{ + int error = ::pthread_mutex_init(&mutex_, 0); + asio::error_code ec(error, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "mutex"); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_PTHREADS) + +#endif // ASIO_DETAIL_IMPL_POSIX_MUTEX_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/posix_thread.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/posix_thread.ipp new file mode 100644 index 000000000..e401766c7 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/posix_thread.ipp @@ -0,0 +1,84 @@ +// +// detail/impl/posix_thread.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_POSIX_THREAD_IPP +#define ASIO_DETAIL_IMPL_POSIX_THREAD_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_PTHREADS) + +#include "asio/detail/posix_thread.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +posix_thread::~posix_thread() +{ + if (!joined_) + ::pthread_detach(thread_); +} + +void posix_thread::join() +{ + if (!joined_) + { + ::pthread_join(thread_, 0); + joined_ = true; + } +} + +std::size_t posix_thread::hardware_concurrency() +{ +#if defined(_SC_NPROCESSORS_ONLN) + long result = sysconf(_SC_NPROCESSORS_ONLN); + if (result > 0) + return result; +#endif // defined(_SC_NPROCESSORS_ONLN) + return 0; +} + +void posix_thread::start_thread(func_base* arg) +{ + int error = ::pthread_create(&thread_, 0, + asio_detail_posix_thread_function, arg); + if (error != 0) + { + delete arg; + asio::error_code ec(error, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "thread"); + } +} + +void* asio_detail_posix_thread_function(void* arg) +{ + posix_thread::auto_func_base_ptr func = { + static_cast(arg) }; + func.ptr->run(); + return 0; +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_PTHREADS) + +#endif // ASIO_DETAIL_IMPL_POSIX_THREAD_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/posix_tss_ptr.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/posix_tss_ptr.ipp new file mode 100644 index 000000000..f3284de3a --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/posix_tss_ptr.ipp @@ -0,0 +1,46 @@ +// +// detail/impl/posix_tss_ptr.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_POSIX_TSS_PTR_IPP +#define ASIO_DETAIL_IMPL_POSIX_TSS_PTR_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_PTHREADS) + +#include "asio/detail/posix_tss_ptr.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +void posix_tss_ptr_create(pthread_key_t& key) +{ + int error = ::pthread_key_create(&key, 0); + asio::error_code ec(error, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "tss"); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_PTHREADS) + +#endif // ASIO_DETAIL_IMPL_POSIX_TSS_PTR_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/reactive_descriptor_service.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/reactive_descriptor_service.ipp new file mode 100644 index 000000000..1fe86573b --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/reactive_descriptor_service.ipp @@ -0,0 +1,223 @@ +// +// detail/impl/reactive_descriptor_service.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_REACTIVE_DESCRIPTOR_SERVICE_IPP +#define ASIO_DETAIL_IMPL_REACTIVE_DESCRIPTOR_SERVICE_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_RUNTIME) \ + && !defined(__CYGWIN__) + +#include "asio/error.hpp" +#include "asio/detail/reactive_descriptor_service.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +reactive_descriptor_service::reactive_descriptor_service( + execution_context& context) + : execution_context_service_base(context), + reactor_(asio::use_service(context)) +{ + reactor_.init_task(); +} + +void reactive_descriptor_service::shutdown() +{ +} + +void reactive_descriptor_service::construct( + reactive_descriptor_service::implementation_type& impl) +{ + impl.descriptor_ = -1; + impl.state_ = 0; +} + +void reactive_descriptor_service::move_construct( + reactive_descriptor_service::implementation_type& impl, + reactive_descriptor_service::implementation_type& other_impl) + ASIO_NOEXCEPT +{ + impl.descriptor_ = other_impl.descriptor_; + other_impl.descriptor_ = -1; + + impl.state_ = other_impl.state_; + other_impl.state_ = 0; + + reactor_.move_descriptor(impl.descriptor_, + impl.reactor_data_, other_impl.reactor_data_); +} + +void reactive_descriptor_service::move_assign( + reactive_descriptor_service::implementation_type& impl, + reactive_descriptor_service& other_service, + reactive_descriptor_service::implementation_type& other_impl) +{ + destroy(impl); + + impl.descriptor_ = other_impl.descriptor_; + other_impl.descriptor_ = -1; + + impl.state_ = other_impl.state_; + other_impl.state_ = 0; + + other_service.reactor_.move_descriptor(impl.descriptor_, + impl.reactor_data_, other_impl.reactor_data_); +} + +void reactive_descriptor_service::destroy( + reactive_descriptor_service::implementation_type& impl) +{ + if (is_open(impl)) + { + ASIO_HANDLER_OPERATION((reactor_.context(), + "descriptor", &impl, impl.descriptor_, "close")); + + reactor_.deregister_descriptor(impl.descriptor_, impl.reactor_data_, + (impl.state_ & descriptor_ops::possible_dup) == 0); + + asio::error_code ignored_ec; + descriptor_ops::close(impl.descriptor_, impl.state_, ignored_ec); + + reactor_.cleanup_descriptor_data(impl.reactor_data_); + } +} + +asio::error_code reactive_descriptor_service::assign( + reactive_descriptor_service::implementation_type& impl, + const native_handle_type& native_descriptor, asio::error_code& ec) +{ + if (is_open(impl)) + { + ec = asio::error::already_open; + return ec; + } + + if (int err = reactor_.register_descriptor( + native_descriptor, impl.reactor_data_)) + { + ec = asio::error_code(err, + asio::error::get_system_category()); + return ec; + } + + impl.descriptor_ = native_descriptor; + impl.state_ = descriptor_ops::possible_dup; + ec = asio::error_code(); + return ec; +} + +asio::error_code reactive_descriptor_service::close( + reactive_descriptor_service::implementation_type& impl, + asio::error_code& ec) +{ + if (is_open(impl)) + { + ASIO_HANDLER_OPERATION((reactor_.context(), + "descriptor", &impl, impl.descriptor_, "close")); + + reactor_.deregister_descriptor(impl.descriptor_, impl.reactor_data_, + (impl.state_ & descriptor_ops::possible_dup) == 0); + + descriptor_ops::close(impl.descriptor_, impl.state_, ec); + + reactor_.cleanup_descriptor_data(impl.reactor_data_); + } + else + { + ec = asio::error_code(); + } + + // The descriptor is closed by the OS even if close() returns an error. + // + // (Actually, POSIX says the state of the descriptor is unspecified. On + // Linux the descriptor is apparently closed anyway; e.g. see + // http://lkml.org/lkml/2005/9/10/129 + // We'll just have to assume that other OSes follow the same behaviour.) + construct(impl); + + return ec; +} + +reactive_descriptor_service::native_handle_type +reactive_descriptor_service::release( + reactive_descriptor_service::implementation_type& impl) +{ + native_handle_type descriptor = impl.descriptor_; + + if (is_open(impl)) + { + ASIO_HANDLER_OPERATION((reactor_.context(), + "descriptor", &impl, impl.descriptor_, "release")); + + reactor_.deregister_descriptor(impl.descriptor_, impl.reactor_data_, false); + reactor_.cleanup_descriptor_data(impl.reactor_data_); + construct(impl); + } + + return descriptor; +} + +asio::error_code reactive_descriptor_service::cancel( + reactive_descriptor_service::implementation_type& impl, + asio::error_code& ec) +{ + if (!is_open(impl)) + { + ec = asio::error::bad_descriptor; + return ec; + } + + ASIO_HANDLER_OPERATION((reactor_.context(), + "descriptor", &impl, impl.descriptor_, "cancel")); + + reactor_.cancel_ops(impl.descriptor_, impl.reactor_data_); + ec = asio::error_code(); + return ec; +} + +void reactive_descriptor_service::start_op( + reactive_descriptor_service::implementation_type& impl, + int op_type, reactor_op* op, bool is_continuation, + bool is_non_blocking, bool noop) +{ + if (!noop) + { + if ((impl.state_ & descriptor_ops::non_blocking) || + descriptor_ops::set_internal_non_blocking( + impl.descriptor_, impl.state_, true, op->ec_)) + { + reactor_.start_op(op_type, impl.descriptor_, + impl.reactor_data_, op, is_continuation, is_non_blocking); + return; + } + } + + reactor_.post_immediate_completion(op, is_continuation); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) + +#endif // ASIO_DETAIL_IMPL_REACTIVE_DESCRIPTOR_SERVICE_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/reactive_serial_port_service.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/reactive_serial_port_service.ipp new file mode 100644 index 000000000..296608220 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/reactive_serial_port_service.ipp @@ -0,0 +1,149 @@ +// +// detail/impl/reactive_serial_port_service.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// Copyright (c) 2008 Rep Invariant Systems, Inc. (info@repinvariant.com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_REACTIVE_SERIAL_PORT_SERVICE_IPP +#define ASIO_DETAIL_IMPL_REACTIVE_SERIAL_PORT_SERVICE_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_SERIAL_PORT) +#if !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) + +#include +#include "asio/detail/reactive_serial_port_service.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +reactive_serial_port_service::reactive_serial_port_service( + execution_context& context) + : execution_context_service_base(context), + descriptor_service_(context) +{ +} + +void reactive_serial_port_service::shutdown() +{ + descriptor_service_.shutdown(); +} + +asio::error_code reactive_serial_port_service::open( + reactive_serial_port_service::implementation_type& impl, + const std::string& device, asio::error_code& ec) +{ + if (is_open(impl)) + { + ec = asio::error::already_open; + return ec; + } + + descriptor_ops::state_type state = 0; + int fd = descriptor_ops::open(device.c_str(), + O_RDWR | O_NONBLOCK | O_NOCTTY, ec); + if (fd < 0) + return ec; + + int s = descriptor_ops::fcntl(fd, F_GETFL, ec); + if (s >= 0) + s = descriptor_ops::fcntl(fd, F_SETFL, s | O_NONBLOCK, ec); + if (s < 0) + { + asio::error_code ignored_ec; + descriptor_ops::close(fd, state, ignored_ec); + return ec; + } + + // Set up default serial port options. + termios ios; + s = ::tcgetattr(fd, &ios); + descriptor_ops::get_last_error(ec, s < 0); + if (s >= 0) + { +#if defined(_BSD_SOURCE) || defined(_DEFAULT_SOURCE) + ::cfmakeraw(&ios); +#else + ios.c_iflag &= ~(IGNBRK | BRKINT | PARMRK + | ISTRIP | INLCR | IGNCR | ICRNL | IXON); + ios.c_oflag &= ~OPOST; + ios.c_lflag &= ~(ECHO | ECHONL | ICANON | ISIG | IEXTEN); + ios.c_cflag &= ~(CSIZE | PARENB); + ios.c_cflag |= CS8; +#endif + ios.c_iflag |= IGNPAR; + ios.c_cflag |= CREAD | CLOCAL; + s = ::tcsetattr(fd, TCSANOW, &ios); + descriptor_ops::get_last_error(ec, s < 0); + } + if (s < 0) + { + asio::error_code ignored_ec; + descriptor_ops::close(fd, state, ignored_ec); + return ec; + } + + // We're done. Take ownership of the serial port descriptor. + if (descriptor_service_.assign(impl, fd, ec)) + { + asio::error_code ignored_ec; + descriptor_ops::close(fd, state, ignored_ec); + } + + return ec; +} + +asio::error_code reactive_serial_port_service::do_set_option( + reactive_serial_port_service::implementation_type& impl, + reactive_serial_port_service::store_function_type store, + const void* option, asio::error_code& ec) +{ + termios ios; + int s = ::tcgetattr(descriptor_service_.native_handle(impl), &ios); + descriptor_ops::get_last_error(ec, s < 0); + if (s < 0) + return ec; + + if (store(option, ios, ec)) + return ec; + + s = ::tcsetattr(descriptor_service_.native_handle(impl), TCSANOW, &ios); + descriptor_ops::get_last_error(ec, s < 0); + return ec; +} + +asio::error_code reactive_serial_port_service::do_get_option( + const reactive_serial_port_service::implementation_type& impl, + reactive_serial_port_service::load_function_type load, + void* option, asio::error_code& ec) const +{ + termios ios; + int s = ::tcgetattr(descriptor_service_.native_handle(impl), &ios); + descriptor_ops::get_last_error(ec, s < 0); + if (s < 0) + return ec; + + return load(option, ios, ec); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) +#endif // defined(ASIO_HAS_SERIAL_PORT) + +#endif // ASIO_DETAIL_IMPL_REACTIVE_SERIAL_PORT_SERVICE_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/reactive_socket_service_base.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/reactive_socket_service_base.ipp new file mode 100644 index 000000000..6c01c5eb9 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/reactive_socket_service_base.ipp @@ -0,0 +1,300 @@ +// +// detail/reactive_socket_service_base.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_REACTIVE_SOCKET_SERVICE_BASE_IPP +#define ASIO_DETAIL_IMPL_REACTIVE_SOCKET_SERVICE_BASE_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_IOCP) \ + && !defined(ASIO_WINDOWS_RUNTIME) + +#include "asio/detail/reactive_socket_service_base.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +reactive_socket_service_base::reactive_socket_service_base( + execution_context& context) + : reactor_(use_service(context)) +{ + reactor_.init_task(); +} + +void reactive_socket_service_base::base_shutdown() +{ +} + +void reactive_socket_service_base::construct( + reactive_socket_service_base::base_implementation_type& impl) +{ + impl.socket_ = invalid_socket; + impl.state_ = 0; +} + +void reactive_socket_service_base::base_move_construct( + reactive_socket_service_base::base_implementation_type& impl, + reactive_socket_service_base::base_implementation_type& other_impl) + ASIO_NOEXCEPT +{ + impl.socket_ = other_impl.socket_; + other_impl.socket_ = invalid_socket; + + impl.state_ = other_impl.state_; + other_impl.state_ = 0; + + reactor_.move_descriptor(impl.socket_, + impl.reactor_data_, other_impl.reactor_data_); +} + +void reactive_socket_service_base::base_move_assign( + reactive_socket_service_base::base_implementation_type& impl, + reactive_socket_service_base& other_service, + reactive_socket_service_base::base_implementation_type& other_impl) +{ + destroy(impl); + + impl.socket_ = other_impl.socket_; + other_impl.socket_ = invalid_socket; + + impl.state_ = other_impl.state_; + other_impl.state_ = 0; + + other_service.reactor_.move_descriptor(impl.socket_, + impl.reactor_data_, other_impl.reactor_data_); +} + +void reactive_socket_service_base::destroy( + reactive_socket_service_base::base_implementation_type& impl) +{ + if (impl.socket_ != invalid_socket) + { + ASIO_HANDLER_OPERATION((reactor_.context(), + "socket", &impl, impl.socket_, "close")); + + reactor_.deregister_descriptor(impl.socket_, impl.reactor_data_, + (impl.state_ & socket_ops::possible_dup) == 0); + + asio::error_code ignored_ec; + socket_ops::close(impl.socket_, impl.state_, true, ignored_ec); + + reactor_.cleanup_descriptor_data(impl.reactor_data_); + } +} + +asio::error_code reactive_socket_service_base::close( + reactive_socket_service_base::base_implementation_type& impl, + asio::error_code& ec) +{ + if (is_open(impl)) + { + ASIO_HANDLER_OPERATION((reactor_.context(), + "socket", &impl, impl.socket_, "close")); + + reactor_.deregister_descriptor(impl.socket_, impl.reactor_data_, + (impl.state_ & socket_ops::possible_dup) == 0); + + socket_ops::close(impl.socket_, impl.state_, false, ec); + + reactor_.cleanup_descriptor_data(impl.reactor_data_); + } + else + { + ec = asio::error_code(); + } + + // The descriptor is closed by the OS even if close() returns an error. + // + // (Actually, POSIX says the state of the descriptor is unspecified. On + // Linux the descriptor is apparently closed anyway; e.g. see + // http://lkml.org/lkml/2005/9/10/129 + // We'll just have to assume that other OSes follow the same behaviour. The + // known exception is when Windows's closesocket() function fails with + // WSAEWOULDBLOCK, but this case is handled inside socket_ops::close(). + construct(impl); + + return ec; +} + +socket_type reactive_socket_service_base::release( + reactive_socket_service_base::base_implementation_type& impl, + asio::error_code& ec) +{ + if (!is_open(impl)) + { + ec = asio::error::bad_descriptor; + return invalid_socket; + } + + ASIO_HANDLER_OPERATION((reactor_.context(), + "socket", &impl, impl.socket_, "release")); + + reactor_.deregister_descriptor(impl.socket_, impl.reactor_data_, false); + reactor_.cleanup_descriptor_data(impl.reactor_data_); + socket_type sock = impl.socket_; + construct(impl); + ec = asio::error_code(); + return sock; +} + +asio::error_code reactive_socket_service_base::cancel( + reactive_socket_service_base::base_implementation_type& impl, + asio::error_code& ec) +{ + if (!is_open(impl)) + { + ec = asio::error::bad_descriptor; + return ec; + } + + ASIO_HANDLER_OPERATION((reactor_.context(), + "socket", &impl, impl.socket_, "cancel")); + + reactor_.cancel_ops(impl.socket_, impl.reactor_data_); + ec = asio::error_code(); + return ec; +} + +asio::error_code reactive_socket_service_base::do_open( + reactive_socket_service_base::base_implementation_type& impl, + int af, int type, int protocol, asio::error_code& ec) +{ + if (is_open(impl)) + { + ec = asio::error::already_open; + return ec; + } + + socket_holder sock(socket_ops::socket(af, type, protocol, ec)); + if (sock.get() == invalid_socket) + return ec; + + if (int err = reactor_.register_descriptor(sock.get(), impl.reactor_data_)) + { + ec = asio::error_code(err, + asio::error::get_system_category()); + return ec; + } + + impl.socket_ = sock.release(); + switch (type) + { + case SOCK_STREAM: impl.state_ = socket_ops::stream_oriented; break; + case SOCK_DGRAM: impl.state_ = socket_ops::datagram_oriented; break; + default: impl.state_ = 0; break; + } + ec = asio::error_code(); + return ec; +} + +asio::error_code reactive_socket_service_base::do_assign( + reactive_socket_service_base::base_implementation_type& impl, int type, + const reactive_socket_service_base::native_handle_type& native_socket, + asio::error_code& ec) +{ + if (is_open(impl)) + { + ec = asio::error::already_open; + return ec; + } + + if (int err = reactor_.register_descriptor( + native_socket, impl.reactor_data_)) + { + ec = asio::error_code(err, + asio::error::get_system_category()); + return ec; + } + + impl.socket_ = native_socket; + switch (type) + { + case SOCK_STREAM: impl.state_ = socket_ops::stream_oriented; break; + case SOCK_DGRAM: impl.state_ = socket_ops::datagram_oriented; break; + default: impl.state_ = 0; break; + } + impl.state_ |= socket_ops::possible_dup; + ec = asio::error_code(); + return ec; +} + +void reactive_socket_service_base::start_op( + reactive_socket_service_base::base_implementation_type& impl, + int op_type, reactor_op* op, bool is_continuation, + bool is_non_blocking, bool noop) +{ + if (!noop) + { + if ((impl.state_ & socket_ops::non_blocking) + || socket_ops::set_internal_non_blocking( + impl.socket_, impl.state_, true, op->ec_)) + { + reactor_.start_op(op_type, impl.socket_, + impl.reactor_data_, op, is_continuation, is_non_blocking); + return; + } + } + + reactor_.post_immediate_completion(op, is_continuation); +} + +void reactive_socket_service_base::start_accept_op( + reactive_socket_service_base::base_implementation_type& impl, + reactor_op* op, bool is_continuation, bool peer_is_open) +{ + if (!peer_is_open) + start_op(impl, reactor::read_op, op, is_continuation, true, false); + else + { + op->ec_ = asio::error::already_open; + reactor_.post_immediate_completion(op, is_continuation); + } +} + +void reactive_socket_service_base::start_connect_op( + reactive_socket_service_base::base_implementation_type& impl, + reactor_op* op, bool is_continuation, + const socket_addr_type* addr, size_t addrlen) +{ + if ((impl.state_ & socket_ops::non_blocking) + || socket_ops::set_internal_non_blocking( + impl.socket_, impl.state_, true, op->ec_)) + { + if (socket_ops::connect(impl.socket_, addr, addrlen, op->ec_) != 0) + { + if (op->ec_ == asio::error::in_progress + || op->ec_ == asio::error::would_block) + { + op->ec_ = asio::error_code(); + reactor_.start_op(reactor::connect_op, impl.socket_, + impl.reactor_data_, op, is_continuation, false); + return; + } + } + } + + reactor_.post_immediate_completion(op, is_continuation); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_HAS_IOCP) + // && !defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_IMPL_REACTIVE_SOCKET_SERVICE_BASE_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/resolver_service_base.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/resolver_service_base.ipp new file mode 100644 index 000000000..a86588f1f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/resolver_service_base.ipp @@ -0,0 +1,158 @@ +// +// detail/impl/resolver_service_base.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_RESOLVER_SERVICE_BASE_IPP +#define ASIO_DETAIL_IMPL_RESOLVER_SERVICE_BASE_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/resolver_service_base.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class resolver_service_base::work_scheduler_runner +{ +public: + work_scheduler_runner(scheduler_impl& work_scheduler) + : work_scheduler_(work_scheduler) + { + } + + void operator()() + { + asio::error_code ec; + work_scheduler_.run(ec); + } + +private: + scheduler_impl& work_scheduler_; +}; + +resolver_service_base::resolver_service_base(execution_context& context) + : scheduler_(asio::use_service(context)), + work_scheduler_(new scheduler_impl(context, -1, false)), + work_thread_(0) +{ + work_scheduler_->work_started(); +} + +resolver_service_base::~resolver_service_base() +{ + base_shutdown(); +} + +void resolver_service_base::base_shutdown() +{ + if (work_scheduler_.get()) + { + work_scheduler_->work_finished(); + work_scheduler_->stop(); + if (work_thread_.get()) + { + work_thread_->join(); + work_thread_.reset(); + } + work_scheduler_.reset(); + } +} + +void resolver_service_base::base_notify_fork( + execution_context::fork_event fork_ev) +{ + if (work_thread_.get()) + { + if (fork_ev == execution_context::fork_prepare) + { + work_scheduler_->stop(); + work_thread_->join(); + work_thread_.reset(); + } + } + else if (fork_ev != execution_context::fork_prepare) + { + work_scheduler_->restart(); + } +} + +void resolver_service_base::construct( + resolver_service_base::implementation_type& impl) +{ + impl.reset(static_cast(0), socket_ops::noop_deleter()); +} + +void resolver_service_base::destroy( + resolver_service_base::implementation_type& impl) +{ + ASIO_HANDLER_OPERATION((scheduler_.context(), + "resolver", &impl, 0, "cancel")); + + impl.reset(); +} + +void resolver_service_base::move_construct(implementation_type& impl, + implementation_type& other_impl) +{ + impl = ASIO_MOVE_CAST(implementation_type)(other_impl); +} + +void resolver_service_base::move_assign(implementation_type& impl, + resolver_service_base&, implementation_type& other_impl) +{ + destroy(impl); + impl = ASIO_MOVE_CAST(implementation_type)(other_impl); +} + +void resolver_service_base::cancel( + resolver_service_base::implementation_type& impl) +{ + ASIO_HANDLER_OPERATION((scheduler_.context(), + "resolver", &impl, 0, "cancel")); + + impl.reset(static_cast(0), socket_ops::noop_deleter()); +} + +void resolver_service_base::start_resolve_op(resolve_op* op) +{ + if (ASIO_CONCURRENCY_HINT_IS_LOCKING(SCHEDULER, + scheduler_.concurrency_hint())) + { + start_work_thread(); + scheduler_.work_started(); + work_scheduler_->post_immediate_completion(op, false); + } + else + { + op->ec_ = asio::error::operation_not_supported; + scheduler_.post_immediate_completion(op, false); + } +} + +void resolver_service_base::start_work_thread() +{ + asio::detail::mutex::scoped_lock lock(mutex_); + if (!work_thread_.get()) + { + work_thread_.reset(new asio::detail::thread( + work_scheduler_runner(*work_scheduler_))); + } +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_IMPL_RESOLVER_SERVICE_BASE_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/scheduler.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/scheduler.ipp new file mode 100644 index 000000000..707eee97a --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/scheduler.ipp @@ -0,0 +1,654 @@ +// +// detail/impl/scheduler.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_SCHEDULER_IPP +#define ASIO_DETAIL_IMPL_SCHEDULER_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#include "asio/detail/concurrency_hint.hpp" +#include "asio/detail/event.hpp" +#include "asio/detail/limits.hpp" +#include "asio/detail/reactor.hpp" +#include "asio/detail/scheduler.hpp" +#include "asio/detail/scheduler_thread_info.hpp" +#include "asio/detail/signal_blocker.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class scheduler::thread_function +{ +public: + explicit thread_function(scheduler* s) + : this_(s) + { + } + + void operator()() + { + asio::error_code ec; + this_->run(ec); + } + +private: + scheduler* this_; +}; + +struct scheduler::task_cleanup +{ + ~task_cleanup() + { + if (this_thread_->private_outstanding_work > 0) + { + asio::detail::increment( + scheduler_->outstanding_work_, + this_thread_->private_outstanding_work); + } + this_thread_->private_outstanding_work = 0; + + // Enqueue the completed operations and reinsert the task at the end of + // the operation queue. + lock_->lock(); + scheduler_->task_interrupted_ = true; + scheduler_->op_queue_.push(this_thread_->private_op_queue); + scheduler_->op_queue_.push(&scheduler_->task_operation_); + } + + scheduler* scheduler_; + mutex::scoped_lock* lock_; + thread_info* this_thread_; +}; + +struct scheduler::work_cleanup +{ + ~work_cleanup() + { + if (this_thread_->private_outstanding_work > 1) + { + asio::detail::increment( + scheduler_->outstanding_work_, + this_thread_->private_outstanding_work - 1); + } + else if (this_thread_->private_outstanding_work < 1) + { + scheduler_->work_finished(); + } + this_thread_->private_outstanding_work = 0; + +#if defined(ASIO_HAS_THREADS) + if (!this_thread_->private_op_queue.empty()) + { + lock_->lock(); + scheduler_->op_queue_.push(this_thread_->private_op_queue); + } +#endif // defined(ASIO_HAS_THREADS) + } + + scheduler* scheduler_; + mutex::scoped_lock* lock_; + thread_info* this_thread_; +}; + +scheduler::scheduler(asio::execution_context& ctx, + int concurrency_hint, bool own_thread) + : asio::detail::execution_context_service_base(ctx), + one_thread_(concurrency_hint == 1 + || !ASIO_CONCURRENCY_HINT_IS_LOCKING( + SCHEDULER, concurrency_hint) + || !ASIO_CONCURRENCY_HINT_IS_LOCKING( + REACTOR_IO, concurrency_hint)), + mutex_(ASIO_CONCURRENCY_HINT_IS_LOCKING( + SCHEDULER, concurrency_hint)), + task_(0), + task_interrupted_(true), + outstanding_work_(0), + stopped_(false), + shutdown_(false), + concurrency_hint_(concurrency_hint), + thread_(0) +{ + ASIO_HANDLER_TRACKING_INIT; + + if (own_thread) + { + ++outstanding_work_; + asio::detail::signal_blocker sb; + thread_ = new asio::detail::thread(thread_function(this)); + } +} + +scheduler::~scheduler() +{ + if (thread_) + { + mutex::scoped_lock lock(mutex_); + shutdown_ = true; + stop_all_threads(lock); + lock.unlock(); + thread_->join(); + delete thread_; + } +} + +void scheduler::shutdown() +{ + mutex::scoped_lock lock(mutex_); + shutdown_ = true; + if (thread_) + stop_all_threads(lock); + lock.unlock(); + + // Join thread to ensure task operation is returned to queue. + if (thread_) + { + thread_->join(); + delete thread_; + thread_ = 0; + } + + // Destroy handler objects. + while (!op_queue_.empty()) + { + operation* o = op_queue_.front(); + op_queue_.pop(); + if (o != &task_operation_) + o->destroy(); + } + + // Reset to initial state. + task_ = 0; +} + +void scheduler::init_task() +{ + mutex::scoped_lock lock(mutex_); + if (!shutdown_ && !task_) + { + task_ = &use_service(this->context()); + op_queue_.push(&task_operation_); + wake_one_thread_and_unlock(lock); + } +} + +std::size_t scheduler::run(asio::error_code& ec) +{ + ec = asio::error_code(); + if (outstanding_work_ == 0) + { + stop(); + return 0; + } + + thread_info this_thread; + this_thread.private_outstanding_work = 0; + thread_call_stack::context ctx(this, this_thread); + + mutex::scoped_lock lock(mutex_); + + std::size_t n = 0; + for (; do_run_one(lock, this_thread, ec); lock.lock()) + if (n != (std::numeric_limits::max)()) + ++n; + return n; +} + +std::size_t scheduler::run_one(asio::error_code& ec) +{ + ec = asio::error_code(); + if (outstanding_work_ == 0) + { + stop(); + return 0; + } + + thread_info this_thread; + this_thread.private_outstanding_work = 0; + thread_call_stack::context ctx(this, this_thread); + + mutex::scoped_lock lock(mutex_); + + return do_run_one(lock, this_thread, ec); +} + +std::size_t scheduler::wait_one(long usec, asio::error_code& ec) +{ + ec = asio::error_code(); + if (outstanding_work_ == 0) + { + stop(); + return 0; + } + + thread_info this_thread; + this_thread.private_outstanding_work = 0; + thread_call_stack::context ctx(this, this_thread); + + mutex::scoped_lock lock(mutex_); + + return do_wait_one(lock, this_thread, usec, ec); +} + +std::size_t scheduler::poll(asio::error_code& ec) +{ + ec = asio::error_code(); + if (outstanding_work_ == 0) + { + stop(); + return 0; + } + + thread_info this_thread; + this_thread.private_outstanding_work = 0; + thread_call_stack::context ctx(this, this_thread); + + mutex::scoped_lock lock(mutex_); + +#if defined(ASIO_HAS_THREADS) + // We want to support nested calls to poll() and poll_one(), so any handlers + // that are already on a thread-private queue need to be put on to the main + // queue now. + if (one_thread_) + if (thread_info* outer_info = static_cast(ctx.next_by_key())) + op_queue_.push(outer_info->private_op_queue); +#endif // defined(ASIO_HAS_THREADS) + + std::size_t n = 0; + for (; do_poll_one(lock, this_thread, ec); lock.lock()) + if (n != (std::numeric_limits::max)()) + ++n; + return n; +} + +std::size_t scheduler::poll_one(asio::error_code& ec) +{ + ec = asio::error_code(); + if (outstanding_work_ == 0) + { + stop(); + return 0; + } + + thread_info this_thread; + this_thread.private_outstanding_work = 0; + thread_call_stack::context ctx(this, this_thread); + + mutex::scoped_lock lock(mutex_); + +#if defined(ASIO_HAS_THREADS) + // We want to support nested calls to poll() and poll_one(), so any handlers + // that are already on a thread-private queue need to be put on to the main + // queue now. + if (one_thread_) + if (thread_info* outer_info = static_cast(ctx.next_by_key())) + op_queue_.push(outer_info->private_op_queue); +#endif // defined(ASIO_HAS_THREADS) + + return do_poll_one(lock, this_thread, ec); +} + +void scheduler::stop() +{ + mutex::scoped_lock lock(mutex_); + stop_all_threads(lock); +} + +bool scheduler::stopped() const +{ + mutex::scoped_lock lock(mutex_); + return stopped_; +} + +void scheduler::restart() +{ + mutex::scoped_lock lock(mutex_); + stopped_ = false; +} + +void scheduler::compensating_work_started() +{ + thread_info_base* this_thread = thread_call_stack::contains(this); + ++static_cast(this_thread)->private_outstanding_work; +} + +void scheduler::capture_current_exception() +{ + if (thread_info_base* this_thread = thread_call_stack::contains(this)) + this_thread->capture_current_exception(); +} + +void scheduler::post_immediate_completion( + scheduler::operation* op, bool is_continuation) +{ +#if defined(ASIO_HAS_THREADS) + if (one_thread_ || is_continuation) + { + if (thread_info_base* this_thread = thread_call_stack::contains(this)) + { + ++static_cast(this_thread)->private_outstanding_work; + static_cast(this_thread)->private_op_queue.push(op); + return; + } + } +#else // defined(ASIO_HAS_THREADS) + (void)is_continuation; +#endif // defined(ASIO_HAS_THREADS) + + work_started(); + mutex::scoped_lock lock(mutex_); + op_queue_.push(op); + wake_one_thread_and_unlock(lock); +} + +void scheduler::post_immediate_completions(std::size_t n, + op_queue& ops, bool is_continuation) +{ +#if defined(ASIO_HAS_THREADS) + if (one_thread_ || is_continuation) + { + if (thread_info_base* this_thread = thread_call_stack::contains(this)) + { + static_cast(this_thread)->private_outstanding_work + += static_cast(n); + static_cast(this_thread)->private_op_queue.push(ops); + return; + } + } +#else // defined(ASIO_HAS_THREADS) + (void)is_continuation; +#endif // defined(ASIO_HAS_THREADS) + + increment(outstanding_work_, static_cast(n)); + mutex::scoped_lock lock(mutex_); + op_queue_.push(ops); + wake_one_thread_and_unlock(lock); +} + +void scheduler::post_deferred_completion(scheduler::operation* op) +{ +#if defined(ASIO_HAS_THREADS) + if (one_thread_) + { + if (thread_info_base* this_thread = thread_call_stack::contains(this)) + { + static_cast(this_thread)->private_op_queue.push(op); + return; + } + } +#endif // defined(ASIO_HAS_THREADS) + + mutex::scoped_lock lock(mutex_); + op_queue_.push(op); + wake_one_thread_and_unlock(lock); +} + +void scheduler::post_deferred_completions( + op_queue& ops) +{ + if (!ops.empty()) + { +#if defined(ASIO_HAS_THREADS) + if (one_thread_) + { + if (thread_info_base* this_thread = thread_call_stack::contains(this)) + { + static_cast(this_thread)->private_op_queue.push(ops); + return; + } + } +#endif // defined(ASIO_HAS_THREADS) + + mutex::scoped_lock lock(mutex_); + op_queue_.push(ops); + wake_one_thread_and_unlock(lock); + } +} + +void scheduler::do_dispatch( + scheduler::operation* op) +{ + work_started(); + mutex::scoped_lock lock(mutex_); + op_queue_.push(op); + wake_one_thread_and_unlock(lock); +} + +void scheduler::abandon_operations( + op_queue& ops) +{ + op_queue ops2; + ops2.push(ops); +} + +std::size_t scheduler::do_run_one(mutex::scoped_lock& lock, + scheduler::thread_info& this_thread, + const asio::error_code& ec) +{ + while (!stopped_) + { + if (!op_queue_.empty()) + { + // Prepare to execute first handler from queue. + operation* o = op_queue_.front(); + op_queue_.pop(); + bool more_handlers = (!op_queue_.empty()); + + if (o == &task_operation_) + { + task_interrupted_ = more_handlers; + + if (more_handlers && !one_thread_) + wakeup_event_.unlock_and_signal_one(lock); + else + lock.unlock(); + + task_cleanup on_exit = { this, &lock, &this_thread }; + (void)on_exit; + + // Run the task. May throw an exception. Only block if the operation + // queue is empty and we're not polling, otherwise we want to return + // as soon as possible. + task_->run(more_handlers ? 0 : -1, this_thread.private_op_queue); + } + else + { + std::size_t task_result = o->task_result_; + + if (more_handlers && !one_thread_) + wake_one_thread_and_unlock(lock); + else + lock.unlock(); + + // Ensure the count of outstanding work is decremented on block exit. + work_cleanup on_exit = { this, &lock, &this_thread }; + (void)on_exit; + + // Complete the operation. May throw an exception. Deletes the object. + o->complete(this, ec, task_result); + this_thread.rethrow_pending_exception(); + + return 1; + } + } + else + { + wakeup_event_.clear(lock); + wakeup_event_.wait(lock); + } + } + + return 0; +} + +std::size_t scheduler::do_wait_one(mutex::scoped_lock& lock, + scheduler::thread_info& this_thread, long usec, + const asio::error_code& ec) +{ + if (stopped_) + return 0; + + operation* o = op_queue_.front(); + if (o == 0) + { + wakeup_event_.clear(lock); + wakeup_event_.wait_for_usec(lock, usec); + usec = 0; // Wait at most once. + o = op_queue_.front(); + } + + if (o == &task_operation_) + { + op_queue_.pop(); + bool more_handlers = (!op_queue_.empty()); + + task_interrupted_ = more_handlers; + + if (more_handlers && !one_thread_) + wakeup_event_.unlock_and_signal_one(lock); + else + lock.unlock(); + + { + task_cleanup on_exit = { this, &lock, &this_thread }; + (void)on_exit; + + // Run the task. May throw an exception. Only block if the operation + // queue is empty and we're not polling, otherwise we want to return + // as soon as possible. + task_->run(more_handlers ? 0 : usec, this_thread.private_op_queue); + } + + o = op_queue_.front(); + if (o == &task_operation_) + { + if (!one_thread_) + wakeup_event_.maybe_unlock_and_signal_one(lock); + return 0; + } + } + + if (o == 0) + return 0; + + op_queue_.pop(); + bool more_handlers = (!op_queue_.empty()); + + std::size_t task_result = o->task_result_; + + if (more_handlers && !one_thread_) + wake_one_thread_and_unlock(lock); + else + lock.unlock(); + + // Ensure the count of outstanding work is decremented on block exit. + work_cleanup on_exit = { this, &lock, &this_thread }; + (void)on_exit; + + // Complete the operation. May throw an exception. Deletes the object. + o->complete(this, ec, task_result); + this_thread.rethrow_pending_exception(); + + return 1; +} + +std::size_t scheduler::do_poll_one(mutex::scoped_lock& lock, + scheduler::thread_info& this_thread, + const asio::error_code& ec) +{ + if (stopped_) + return 0; + + operation* o = op_queue_.front(); + if (o == &task_operation_) + { + op_queue_.pop(); + lock.unlock(); + + { + task_cleanup c = { this, &lock, &this_thread }; + (void)c; + + // Run the task. May throw an exception. Only block if the operation + // queue is empty and we're not polling, otherwise we want to return + // as soon as possible. + task_->run(0, this_thread.private_op_queue); + } + + o = op_queue_.front(); + if (o == &task_operation_) + { + wakeup_event_.maybe_unlock_and_signal_one(lock); + return 0; + } + } + + if (o == 0) + return 0; + + op_queue_.pop(); + bool more_handlers = (!op_queue_.empty()); + + std::size_t task_result = o->task_result_; + + if (more_handlers && !one_thread_) + wake_one_thread_and_unlock(lock); + else + lock.unlock(); + + // Ensure the count of outstanding work is decremented on block exit. + work_cleanup on_exit = { this, &lock, &this_thread }; + (void)on_exit; + + // Complete the operation. May throw an exception. Deletes the object. + o->complete(this, ec, task_result); + this_thread.rethrow_pending_exception(); + + return 1; +} + +void scheduler::stop_all_threads( + mutex::scoped_lock& lock) +{ + stopped_ = true; + wakeup_event_.signal_all(lock); + + if (!task_interrupted_ && task_) + { + task_interrupted_ = true; + task_->interrupt(); + } +} + +void scheduler::wake_one_thread_and_unlock( + mutex::scoped_lock& lock) +{ + if (!wakeup_event_.maybe_unlock_and_signal_one(lock)) + { + if (!task_interrupted_ && task_) + { + task_interrupted_ = true; + task_->interrupt(); + } + lock.unlock(); + } +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_IMPL_SCHEDULER_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/select_reactor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/select_reactor.hpp new file mode 100644 index 000000000..dd4418f87 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/select_reactor.hpp @@ -0,0 +1,100 @@ +// +// detail/impl/select_reactor.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_SELECT_REACTOR_HPP +#define ASIO_DETAIL_IMPL_SELECT_REACTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) \ + || (!defined(ASIO_HAS_DEV_POLL) \ + && !defined(ASIO_HAS_EPOLL) \ + && !defined(ASIO_HAS_KQUEUE) \ + && !defined(ASIO_WINDOWS_RUNTIME)) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +void select_reactor::add_timer_queue(timer_queue& queue) +{ + do_add_timer_queue(queue); +} + +// Remove a timer queue from the reactor. +template +void select_reactor::remove_timer_queue(timer_queue& queue) +{ + do_remove_timer_queue(queue); +} + +template +void select_reactor::schedule_timer(timer_queue& queue, + const typename Time_Traits::time_type& time, + typename timer_queue::per_timer_data& timer, wait_op* op) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + + if (shutdown_) + { + scheduler_.post_immediate_completion(op, false); + return; + } + + bool earliest = queue.enqueue_timer(time, timer, op); + scheduler_.work_started(); + if (earliest) + interrupter_.interrupt(); +} + +template +std::size_t select_reactor::cancel_timer(timer_queue& queue, + typename timer_queue::per_timer_data& timer, + std::size_t max_cancelled) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + op_queue ops; + std::size_t n = queue.cancel_timer(timer, ops, max_cancelled); + lock.unlock(); + scheduler_.post_deferred_completions(ops); + return n; +} + +template +void select_reactor::move_timer(timer_queue& queue, + typename timer_queue::per_timer_data& target, + typename timer_queue::per_timer_data& source) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + op_queue ops; + queue.cancel_timer(target, ops); + queue.move_timer(target, source); + lock.unlock(); + scheduler_.post_deferred_completions(ops); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + // || (!defined(ASIO_HAS_DEV_POLL) + // && !defined(ASIO_HAS_EPOLL) + // && !defined(ASIO_HAS_KQUEUE) + // && !defined(ASIO_WINDOWS_RUNTIME)) + +#endif // ASIO_DETAIL_IMPL_SELECT_REACTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/select_reactor.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/select_reactor.ipp new file mode 100644 index 000000000..1e321a037 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/select_reactor.ipp @@ -0,0 +1,338 @@ +// +// detail/impl/select_reactor.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_SELECT_REACTOR_IPP +#define ASIO_DETAIL_IMPL_SELECT_REACTOR_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) \ + || (!defined(ASIO_HAS_DEV_POLL) \ + && !defined(ASIO_HAS_EPOLL) \ + && !defined(ASIO_HAS_KQUEUE) \ + && !defined(ASIO_WINDOWS_RUNTIME)) + +#include "asio/detail/fd_set_adapter.hpp" +#include "asio/detail/select_reactor.hpp" +#include "asio/detail/signal_blocker.hpp" +#include "asio/detail/socket_ops.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +#if defined(ASIO_HAS_IOCP) +class select_reactor::thread_function +{ +public: + explicit thread_function(select_reactor* r) + : this_(r) + { + } + + void operator()() + { + this_->run_thread(); + } + +private: + select_reactor* this_; +}; +#endif // defined(ASIO_HAS_IOCP) + +select_reactor::select_reactor(asio::execution_context& ctx) + : execution_context_service_base(ctx), + scheduler_(use_service(ctx)), + mutex_(), + interrupter_(), +#if defined(ASIO_HAS_IOCP) + stop_thread_(false), + thread_(0), +#endif // defined(ASIO_HAS_IOCP) + shutdown_(false) +{ +#if defined(ASIO_HAS_IOCP) + asio::detail::signal_blocker sb; + thread_ = new asio::detail::thread(thread_function(this)); +#endif // defined(ASIO_HAS_IOCP) +} + +select_reactor::~select_reactor() +{ + shutdown(); +} + +void select_reactor::shutdown() +{ + asio::detail::mutex::scoped_lock lock(mutex_); + shutdown_ = true; +#if defined(ASIO_HAS_IOCP) + stop_thread_ = true; + if (thread_) + interrupter_.interrupt(); +#endif // defined(ASIO_HAS_IOCP) + lock.unlock(); + +#if defined(ASIO_HAS_IOCP) + if (thread_) + { + thread_->join(); + delete thread_; + thread_ = 0; + } +#endif // defined(ASIO_HAS_IOCP) + + op_queue ops; + + for (int i = 0; i < max_ops; ++i) + op_queue_[i].get_all_operations(ops); + + timer_queues_.get_all_timers(ops); + + scheduler_.abandon_operations(ops); +} + +void select_reactor::notify_fork( + asio::execution_context::fork_event fork_ev) +{ + if (fork_ev == asio::execution_context::fork_child) + interrupter_.recreate(); +} + +void select_reactor::init_task() +{ + scheduler_.init_task(); +} + +int select_reactor::register_descriptor(socket_type, + select_reactor::per_descriptor_data&) +{ + return 0; +} + +int select_reactor::register_internal_descriptor( + int op_type, socket_type descriptor, + select_reactor::per_descriptor_data&, reactor_op* op) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + + op_queue_[op_type].enqueue_operation(descriptor, op); + interrupter_.interrupt(); + + return 0; +} + +void select_reactor::move_descriptor(socket_type, + select_reactor::per_descriptor_data&, + select_reactor::per_descriptor_data&) +{ +} + +void select_reactor::start_op(int op_type, socket_type descriptor, + select_reactor::per_descriptor_data&, reactor_op* op, + bool is_continuation, bool) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + + if (shutdown_) + { + post_immediate_completion(op, is_continuation); + return; + } + + bool first = op_queue_[op_type].enqueue_operation(descriptor, op); + scheduler_.work_started(); + if (first) + interrupter_.interrupt(); +} + +void select_reactor::cancel_ops(socket_type descriptor, + select_reactor::per_descriptor_data&) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + cancel_ops_unlocked(descriptor, asio::error::operation_aborted); +} + +void select_reactor::deregister_descriptor(socket_type descriptor, + select_reactor::per_descriptor_data&, bool) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + cancel_ops_unlocked(descriptor, asio::error::operation_aborted); +} + +void select_reactor::deregister_internal_descriptor( + socket_type descriptor, select_reactor::per_descriptor_data&) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + op_queue ops; + for (int i = 0; i < max_ops; ++i) + op_queue_[i].cancel_operations(descriptor, ops); +} + +void select_reactor::cleanup_descriptor_data( + select_reactor::per_descriptor_data&) +{ +} + +void select_reactor::run(long usec, op_queue& ops) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + +#if defined(ASIO_HAS_IOCP) + // Check if the thread is supposed to stop. + if (stop_thread_) + return; +#endif // defined(ASIO_HAS_IOCP) + + // Set up the descriptor sets. + for (int i = 0; i < max_select_ops; ++i) + fd_sets_[i].reset(); + fd_sets_[read_op].set(interrupter_.read_descriptor()); + socket_type max_fd = 0; + bool have_work_to_do = !timer_queues_.all_empty(); + for (int i = 0; i < max_select_ops; ++i) + { + have_work_to_do = have_work_to_do || !op_queue_[i].empty(); + fd_sets_[i].set(op_queue_[i], ops); + if (fd_sets_[i].max_descriptor() > max_fd) + max_fd = fd_sets_[i].max_descriptor(); + } + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + // Connection operations on Windows use both except and write fd_sets. + have_work_to_do = have_work_to_do || !op_queue_[connect_op].empty(); + fd_sets_[write_op].set(op_queue_[connect_op], ops); + if (fd_sets_[write_op].max_descriptor() > max_fd) + max_fd = fd_sets_[write_op].max_descriptor(); + fd_sets_[except_op].set(op_queue_[connect_op], ops); + if (fd_sets_[except_op].max_descriptor() > max_fd) + max_fd = fd_sets_[except_op].max_descriptor(); +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + + // We can return immediately if there's no work to do and the reactor is + // not supposed to block. + if (!usec && !have_work_to_do) + return; + + // Determine how long to block while waiting for events. + timeval tv_buf = { 0, 0 }; + timeval* tv = usec ? get_timeout(usec, tv_buf) : &tv_buf; + + lock.unlock(); + + // Block on the select call until descriptors become ready. + asio::error_code ec; + int retval = socket_ops::select(static_cast(max_fd + 1), + fd_sets_[read_op], fd_sets_[write_op], fd_sets_[except_op], tv, ec); + + // Reset the interrupter. + if (retval > 0 && fd_sets_[read_op].is_set(interrupter_.read_descriptor())) + { + if (!interrupter_.reset()) + { + lock.lock(); + interrupter_.recreate(); + } + --retval; + } + + lock.lock(); + + // Dispatch all ready operations. + if (retval > 0) + { +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + // Connection operations on Windows use both except and write fd_sets. + fd_sets_[except_op].perform(op_queue_[connect_op], ops); + fd_sets_[write_op].perform(op_queue_[connect_op], ops); +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + + // Exception operations must be processed first to ensure that any + // out-of-band data is read before normal data. + for (int i = max_select_ops - 1; i >= 0; --i) + fd_sets_[i].perform(op_queue_[i], ops); + } + timer_queues_.get_ready_timers(ops); +} + +void select_reactor::interrupt() +{ + interrupter_.interrupt(); +} + +#if defined(ASIO_HAS_IOCP) +void select_reactor::run_thread() +{ + asio::detail::mutex::scoped_lock lock(mutex_); + while (!stop_thread_) + { + lock.unlock(); + op_queue ops; + run(true, ops); + scheduler_.post_deferred_completions(ops); + lock.lock(); + } +} +#endif // defined(ASIO_HAS_IOCP) + +void select_reactor::do_add_timer_queue(timer_queue_base& queue) +{ + mutex::scoped_lock lock(mutex_); + timer_queues_.insert(&queue); +} + +void select_reactor::do_remove_timer_queue(timer_queue_base& queue) +{ + mutex::scoped_lock lock(mutex_); + timer_queues_.erase(&queue); +} + +timeval* select_reactor::get_timeout(long usec, timeval& tv) +{ + // By default we will wait no longer than 5 minutes. This will ensure that + // any changes to the system clock are detected after no longer than this. + const long max_usec = 5 * 60 * 1000 * 1000; + usec = timer_queues_.wait_duration_usec( + (usec < 0 || max_usec < usec) ? max_usec : usec); + tv.tv_sec = usec / 1000000; + tv.tv_usec = usec % 1000000; + return &tv; +} + +void select_reactor::cancel_ops_unlocked(socket_type descriptor, + const asio::error_code& ec) +{ + bool need_interrupt = false; + op_queue ops; + for (int i = 0; i < max_ops; ++i) + need_interrupt = op_queue_[i].cancel_operations( + descriptor, ops, ec) || need_interrupt; + scheduler_.post_deferred_completions(ops); + if (need_interrupt) + interrupter_.interrupt(); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + // || (!defined(ASIO_HAS_DEV_POLL) + // && !defined(ASIO_HAS_EPOLL) + // && !defined(ASIO_HAS_KQUEUE)) + // && !defined(ASIO_WINDOWS_RUNTIME)) + +#endif // ASIO_DETAIL_IMPL_SELECT_REACTOR_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/service_registry.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/service_registry.hpp new file mode 100644 index 000000000..ca73d2fe8 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/service_registry.hpp @@ -0,0 +1,94 @@ +// +// detail/impl/service_registry.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_SERVICE_REGISTRY_HPP +#define ASIO_DETAIL_IMPL_SERVICE_REGISTRY_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +Service& service_registry::use_service() +{ + execution_context::service::key key; + init_key(key, 0); + factory_type factory = &service_registry::create; + return *static_cast(do_use_service(key, factory, &owner_)); +} + +template +Service& service_registry::use_service(io_context& owner) +{ + execution_context::service::key key; + init_key(key, 0); + factory_type factory = &service_registry::create; + return *static_cast(do_use_service(key, factory, &owner)); +} + +template +void service_registry::add_service(Service* new_service) +{ + execution_context::service::key key; + init_key(key, 0); + return do_add_service(key, new_service); +} + +template +bool service_registry::has_service() const +{ + execution_context::service::key key; + init_key(key, 0); + return do_has_service(key); +} + +template +inline void service_registry::init_key( + execution_context::service::key& key, ...) +{ + init_key_from_id(key, Service::id); +} + +#if !defined(ASIO_NO_TYPEID) +template +void service_registry::init_key(execution_context::service::key& key, + typename enable_if< + is_base_of::value>::type*) +{ + key.type_info_ = &typeid(typeid_wrapper); + key.id_ = 0; +} + +template +void service_registry::init_key_from_id(execution_context::service::key& key, + const service_id& /*id*/) +{ + key.type_info_ = &typeid(typeid_wrapper); + key.id_ = 0; +} +#endif // !defined(ASIO_NO_TYPEID) + +template +execution_context::service* service_registry::create(void* owner) +{ + return new Service(*static_cast(owner)); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_IMPL_SERVICE_REGISTRY_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/service_registry.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/service_registry.ipp new file mode 100644 index 000000000..e9a14fec9 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/service_registry.ipp @@ -0,0 +1,197 @@ +// +// detail/impl/service_registry.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_SERVICE_REGISTRY_IPP +#define ASIO_DETAIL_IMPL_SERVICE_REGISTRY_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include "asio/detail/service_registry.hpp" +#include "asio/detail/throw_exception.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +service_registry::service_registry(execution_context& owner) + : owner_(owner), + first_service_(0) +{ +} + +service_registry::~service_registry() +{ +} + +void service_registry::shutdown_services() +{ + execution_context::service* service = first_service_; + while (service) + { + service->shutdown(); + service = service->next_; + } +} + +void service_registry::destroy_services() +{ + while (first_service_) + { + execution_context::service* next_service = first_service_->next_; + destroy(first_service_); + first_service_ = next_service; + } +} + +void service_registry::notify_fork(execution_context::fork_event fork_ev) +{ + // Make a copy of all of the services while holding the lock. We don't want + // to hold the lock while calling into each service, as it may try to call + // back into this class. + std::vector services; + { + asio::detail::mutex::scoped_lock lock(mutex_); + execution_context::service* service = first_service_; + while (service) + { + services.push_back(service); + service = service->next_; + } + } + + // If processing the fork_prepare event, we want to go in reverse order of + // service registration, which happens to be the existing order of the + // services in the vector. For the other events we want to go in the other + // direction. + std::size_t num_services = services.size(); + if (fork_ev == execution_context::fork_prepare) + for (std::size_t i = 0; i < num_services; ++i) + services[i]->notify_fork(fork_ev); + else + for (std::size_t i = num_services; i > 0; --i) + services[i - 1]->notify_fork(fork_ev); +} + +void service_registry::init_key_from_id(execution_context::service::key& key, + const execution_context::id& id) +{ + key.type_info_ = 0; + key.id_ = &id; +} + +bool service_registry::keys_match( + const execution_context::service::key& key1, + const execution_context::service::key& key2) +{ + if (key1.id_ && key2.id_) + if (key1.id_ == key2.id_) + return true; + if (key1.type_info_ && key2.type_info_) + if (*key1.type_info_ == *key2.type_info_) + return true; + return false; +} + +void service_registry::destroy(execution_context::service* service) +{ + delete service; +} + +execution_context::service* service_registry::do_use_service( + const execution_context::service::key& key, + factory_type factory, void* owner) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + + // First see if there is an existing service object with the given key. + execution_context::service* service = first_service_; + while (service) + { + if (keys_match(service->key_, key)) + return service; + service = service->next_; + } + + // Create a new service object. The service registry's mutex is not locked + // at this time to allow for nested calls into this function from the new + // service's constructor. + lock.unlock(); + auto_service_ptr new_service = { factory(owner) }; + new_service.ptr_->key_ = key; + lock.lock(); + + // Check that nobody else created another service object of the same type + // while the lock was released. + service = first_service_; + while (service) + { + if (keys_match(service->key_, key)) + return service; + service = service->next_; + } + + // Service was successfully initialised, pass ownership to registry. + new_service.ptr_->next_ = first_service_; + first_service_ = new_service.ptr_; + new_service.ptr_ = 0; + return first_service_; +} + +void service_registry::do_add_service( + const execution_context::service::key& key, + execution_context::service* new_service) +{ + if (&owner_ != &new_service->context()) + asio::detail::throw_exception(invalid_service_owner()); + + asio::detail::mutex::scoped_lock lock(mutex_); + + // Check if there is an existing service object with the given key. + execution_context::service* service = first_service_; + while (service) + { + if (keys_match(service->key_, key)) + asio::detail::throw_exception(service_already_exists()); + service = service->next_; + } + + // Take ownership of the service object. + new_service->key_ = key; + new_service->next_ = first_service_; + first_service_ = new_service; +} + +bool service_registry::do_has_service( + const execution_context::service::key& key) const +{ + asio::detail::mutex::scoped_lock lock(mutex_); + + execution_context::service* service = first_service_; + while (service) + { + if (keys_match(service->key_, key)) + return true; + service = service->next_; + } + + return false; +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_IMPL_SERVICE_REGISTRY_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/signal_set_service.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/signal_set_service.ipp new file mode 100644 index 000000000..b99060c1f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/signal_set_service.ipp @@ -0,0 +1,668 @@ +// +// detail/impl/signal_set_service.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_SIGNAL_SET_SERVICE_IPP +#define ASIO_DETAIL_IMPL_SIGNAL_SET_SERVICE_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#include +#include +#include "asio/detail/reactor.hpp" +#include "asio/detail/signal_blocker.hpp" +#include "asio/detail/signal_set_service.hpp" +#include "asio/detail/static_mutex.hpp" +#include "asio/detail/throw_exception.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +struct signal_state +{ + // Mutex used for protecting global state. + static_mutex mutex_; + + // The read end of the pipe used for signal notifications. + int read_descriptor_; + + // The write end of the pipe used for signal notifications. + int write_descriptor_; + + // Whether the signal state has been prepared for a fork. + bool fork_prepared_; + + // The head of a linked list of all signal_set_service instances. + class signal_set_service* service_list_; + + // A count of the number of objects that are registered for each signal. + std::size_t registration_count_[max_signal_number]; +}; + +signal_state* get_signal_state() +{ + static signal_state state = { + ASIO_STATIC_MUTEX_INIT, -1, -1, false, 0, { 0 } }; + return &state; +} + +void asio_signal_handler(int signal_number) +{ +#if defined(ASIO_WINDOWS) \ + || defined(ASIO_WINDOWS_RUNTIME) \ + || defined(__CYGWIN__) + signal_set_service::deliver_signal(signal_number); +#else // defined(ASIO_WINDOWS) + // || defined(ASIO_WINDOWS_RUNTIME) + // || defined(__CYGWIN__) + int saved_errno = errno; + signal_state* state = get_signal_state(); + signed_size_type result = ::write(state->write_descriptor_, + &signal_number, sizeof(signal_number)); + (void)result; + errno = saved_errno; +#endif // defined(ASIO_WINDOWS) + // || defined(ASIO_WINDOWS_RUNTIME) + // || defined(__CYGWIN__) + +#if defined(ASIO_HAS_SIGNAL) && !defined(ASIO_HAS_SIGACTION) + ::signal(signal_number, asio_signal_handler); +#endif // defined(ASIO_HAS_SIGNAL) && !defined(ASIO_HAS_SIGACTION) +} + +#if !defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_RUNTIME) \ + && !defined(__CYGWIN__) +class signal_set_service::pipe_read_op : public reactor_op +{ +public: + pipe_read_op() + : reactor_op(asio::error_code(), + &pipe_read_op::do_perform, pipe_read_op::do_complete) + { + } + + static status do_perform(reactor_op*) + { + signal_state* state = get_signal_state(); + + int fd = state->read_descriptor_; + int signal_number = 0; + while (::read(fd, &signal_number, sizeof(int)) == sizeof(int)) + if (signal_number >= 0 && signal_number < max_signal_number) + signal_set_service::deliver_signal(signal_number); + + return not_done; + } + + static void do_complete(void* /*owner*/, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + pipe_read_op* o(static_cast(base)); + delete o; + } +}; +#endif // !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) + +signal_set_service::signal_set_service(execution_context& context) + : execution_context_service_base(context), + scheduler_(asio::use_service(context)), +#if !defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_RUNTIME) \ + && !defined(__CYGWIN__) + reactor_(asio::use_service(context)), +#endif // !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) + next_(0), + prev_(0) +{ + get_signal_state()->mutex_.init(); + +#if !defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_RUNTIME) \ + && !defined(__CYGWIN__) + reactor_.init_task(); +#endif // !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) + + for (int i = 0; i < max_signal_number; ++i) + registrations_[i] = 0; + + add_service(this); +} + +signal_set_service::~signal_set_service() +{ + remove_service(this); +} + +void signal_set_service::shutdown() +{ + remove_service(this); + + op_queue ops; + + for (int i = 0; i < max_signal_number; ++i) + { + registration* reg = registrations_[i]; + while (reg) + { + ops.push(*reg->queue_); + reg = reg->next_in_table_; + } + } + + scheduler_.abandon_operations(ops); +} + +void signal_set_service::notify_fork(execution_context::fork_event fork_ev) +{ +#if !defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_RUNTIME) \ + && !defined(__CYGWIN__) + signal_state* state = get_signal_state(); + static_mutex::scoped_lock lock(state->mutex_); + + switch (fork_ev) + { + case execution_context::fork_prepare: + { + int read_descriptor = state->read_descriptor_; + state->fork_prepared_ = true; + lock.unlock(); + reactor_.deregister_internal_descriptor(read_descriptor, reactor_data_); + reactor_.cleanup_descriptor_data(reactor_data_); + } + break; + case execution_context::fork_parent: + if (state->fork_prepared_) + { + int read_descriptor = state->read_descriptor_; + state->fork_prepared_ = false; + lock.unlock(); + reactor_.register_internal_descriptor(reactor::read_op, + read_descriptor, reactor_data_, new pipe_read_op); + } + break; + case execution_context::fork_child: + if (state->fork_prepared_) + { + asio::detail::signal_blocker blocker; + close_descriptors(); + open_descriptors(); + int read_descriptor = state->read_descriptor_; + state->fork_prepared_ = false; + lock.unlock(); + reactor_.register_internal_descriptor(reactor::read_op, + read_descriptor, reactor_data_, new pipe_read_op); + } + break; + default: + break; + } +#else // !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) + (void)fork_ev; +#endif // !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) +} + +void signal_set_service::construct( + signal_set_service::implementation_type& impl) +{ + impl.signals_ = 0; +} + +void signal_set_service::destroy( + signal_set_service::implementation_type& impl) +{ + asio::error_code ignored_ec; + clear(impl, ignored_ec); + cancel(impl, ignored_ec); +} + +asio::error_code signal_set_service::add( + signal_set_service::implementation_type& impl, + int signal_number, asio::error_code& ec) +{ + // Check that the signal number is valid. + if (signal_number < 0 || signal_number >= max_signal_number) + { + ec = asio::error::invalid_argument; + return ec; + } + + signal_state* state = get_signal_state(); + static_mutex::scoped_lock lock(state->mutex_); + + // Find the appropriate place to insert the registration. + registration** insertion_point = &impl.signals_; + registration* next = impl.signals_; + while (next && next->signal_number_ < signal_number) + { + insertion_point = &next->next_in_set_; + next = next->next_in_set_; + } + + // Only do something if the signal is not already registered. + if (next == 0 || next->signal_number_ != signal_number) + { + registration* new_registration = new registration; + +#if defined(ASIO_HAS_SIGNAL) || defined(ASIO_HAS_SIGACTION) + // Register for the signal if we're the first. + if (state->registration_count_[signal_number] == 0) + { +# if defined(ASIO_HAS_SIGACTION) + using namespace std; // For memset. + struct sigaction sa; + memset(&sa, 0, sizeof(sa)); + sa.sa_handler = asio_signal_handler; + sigfillset(&sa.sa_mask); + if (::sigaction(signal_number, &sa, 0) == -1) +# else // defined(ASIO_HAS_SIGACTION) + if (::signal(signal_number, asio_signal_handler) == SIG_ERR) +# endif // defined(ASIO_HAS_SIGACTION) + { +# if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + ec = asio::error::invalid_argument; +# else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + ec = asio::error_code(errno, + asio::error::get_system_category()); +# endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + delete new_registration; + return ec; + } + } +#endif // defined(ASIO_HAS_SIGNAL) || defined(ASIO_HAS_SIGACTION) + + // Record the new registration in the set. + new_registration->signal_number_ = signal_number; + new_registration->queue_ = &impl.queue_; + new_registration->next_in_set_ = next; + *insertion_point = new_registration; + + // Insert registration into the registration table. + new_registration->next_in_table_ = registrations_[signal_number]; + if (registrations_[signal_number]) + registrations_[signal_number]->prev_in_table_ = new_registration; + registrations_[signal_number] = new_registration; + + ++state->registration_count_[signal_number]; + } + + ec = asio::error_code(); + return ec; +} + +asio::error_code signal_set_service::remove( + signal_set_service::implementation_type& impl, + int signal_number, asio::error_code& ec) +{ + // Check that the signal number is valid. + if (signal_number < 0 || signal_number >= max_signal_number) + { + ec = asio::error::invalid_argument; + return ec; + } + + signal_state* state = get_signal_state(); + static_mutex::scoped_lock lock(state->mutex_); + + // Find the signal number in the list of registrations. + registration** deletion_point = &impl.signals_; + registration* reg = impl.signals_; + while (reg && reg->signal_number_ < signal_number) + { + deletion_point = ®->next_in_set_; + reg = reg->next_in_set_; + } + + if (reg != 0 && reg->signal_number_ == signal_number) + { +#if defined(ASIO_HAS_SIGNAL) || defined(ASIO_HAS_SIGACTION) + // Set signal handler back to the default if we're the last. + if (state->registration_count_[signal_number] == 1) + { +# if defined(ASIO_HAS_SIGACTION) + using namespace std; // For memset. + struct sigaction sa; + memset(&sa, 0, sizeof(sa)); + sa.sa_handler = SIG_DFL; + if (::sigaction(signal_number, &sa, 0) == -1) +# else // defined(ASIO_HAS_SIGACTION) + if (::signal(signal_number, SIG_DFL) == SIG_ERR) +# endif // defined(ASIO_HAS_SIGACTION) + { +# if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + ec = asio::error::invalid_argument; +# else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + ec = asio::error_code(errno, + asio::error::get_system_category()); +# endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + return ec; + } + } +#endif // defined(ASIO_HAS_SIGNAL) || defined(ASIO_HAS_SIGACTION) + + // Remove the registration from the set. + *deletion_point = reg->next_in_set_; + + // Remove the registration from the registration table. + if (registrations_[signal_number] == reg) + registrations_[signal_number] = reg->next_in_table_; + if (reg->prev_in_table_) + reg->prev_in_table_->next_in_table_ = reg->next_in_table_; + if (reg->next_in_table_) + reg->next_in_table_->prev_in_table_ = reg->prev_in_table_; + + --state->registration_count_[signal_number]; + + delete reg; + } + + ec = asio::error_code(); + return ec; +} + +asio::error_code signal_set_service::clear( + signal_set_service::implementation_type& impl, + asio::error_code& ec) +{ + signal_state* state = get_signal_state(); + static_mutex::scoped_lock lock(state->mutex_); + + while (registration* reg = impl.signals_) + { +#if defined(ASIO_HAS_SIGNAL) || defined(ASIO_HAS_SIGACTION) + // Set signal handler back to the default if we're the last. + if (state->registration_count_[reg->signal_number_] == 1) + { +# if defined(ASIO_HAS_SIGACTION) + using namespace std; // For memset. + struct sigaction sa; + memset(&sa, 0, sizeof(sa)); + sa.sa_handler = SIG_DFL; + if (::sigaction(reg->signal_number_, &sa, 0) == -1) +# else // defined(ASIO_HAS_SIGACTION) + if (::signal(reg->signal_number_, SIG_DFL) == SIG_ERR) +# endif // defined(ASIO_HAS_SIGACTION) + { +# if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + ec = asio::error::invalid_argument; +# else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + ec = asio::error_code(errno, + asio::error::get_system_category()); +# endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + return ec; + } + } +#endif // defined(ASIO_HAS_SIGNAL) || defined(ASIO_HAS_SIGACTION) + + // Remove the registration from the registration table. + if (registrations_[reg->signal_number_] == reg) + registrations_[reg->signal_number_] = reg->next_in_table_; + if (reg->prev_in_table_) + reg->prev_in_table_->next_in_table_ = reg->next_in_table_; + if (reg->next_in_table_) + reg->next_in_table_->prev_in_table_ = reg->prev_in_table_; + + --state->registration_count_[reg->signal_number_]; + + impl.signals_ = reg->next_in_set_; + delete reg; + } + + ec = asio::error_code(); + return ec; +} + +asio::error_code signal_set_service::cancel( + signal_set_service::implementation_type& impl, + asio::error_code& ec) +{ + ASIO_HANDLER_OPERATION((scheduler_.context(), + "signal_set", &impl, 0, "cancel")); + + op_queue ops; + { + signal_state* state = get_signal_state(); + static_mutex::scoped_lock lock(state->mutex_); + + while (signal_op* op = impl.queue_.front()) + { + op->ec_ = asio::error::operation_aborted; + impl.queue_.pop(); + ops.push(op); + } + } + + scheduler_.post_deferred_completions(ops); + + ec = asio::error_code(); + return ec; +} + +void signal_set_service::deliver_signal(int signal_number) +{ + signal_state* state = get_signal_state(); + static_mutex::scoped_lock lock(state->mutex_); + + signal_set_service* service = state->service_list_; + while (service) + { + op_queue ops; + + registration* reg = service->registrations_[signal_number]; + while (reg) + { + if (reg->queue_->empty()) + { + ++reg->undelivered_; + } + else + { + while (signal_op* op = reg->queue_->front()) + { + op->signal_number_ = signal_number; + reg->queue_->pop(); + ops.push(op); + } + } + + reg = reg->next_in_table_; + } + + service->scheduler_.post_deferred_completions(ops); + + service = service->next_; + } +} + +void signal_set_service::add_service(signal_set_service* service) +{ + signal_state* state = get_signal_state(); + static_mutex::scoped_lock lock(state->mutex_); + +#if !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) + // If this is the first service to be created, open a new pipe. + if (state->service_list_ == 0) + open_descriptors(); +#endif // !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) + + // If a scheduler_ object is thread-unsafe then it must be the only + // scheduler used to create signal_set objects. + if (state->service_list_ != 0) + { + if (!ASIO_CONCURRENCY_HINT_IS_LOCKING(SCHEDULER, + service->scheduler_.concurrency_hint()) + || !ASIO_CONCURRENCY_HINT_IS_LOCKING(SCHEDULER, + state->service_list_->scheduler_.concurrency_hint())) + { + std::logic_error ex( + "Thread-unsafe execution context objects require " + "exclusive access to signal handling."); + asio::detail::throw_exception(ex); + } + } + + // Insert service into linked list of all services. + service->next_ = state->service_list_; + service->prev_ = 0; + if (state->service_list_) + state->service_list_->prev_ = service; + state->service_list_ = service; + +#if !defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_RUNTIME) \ + && !defined(__CYGWIN__) + // Register for pipe readiness notifications. + int read_descriptor = state->read_descriptor_; + lock.unlock(); + service->reactor_.register_internal_descriptor(reactor::read_op, + read_descriptor, service->reactor_data_, new pipe_read_op); +#endif // !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) +} + +void signal_set_service::remove_service(signal_set_service* service) +{ + signal_state* state = get_signal_state(); + static_mutex::scoped_lock lock(state->mutex_); + + if (service->next_ || service->prev_ || state->service_list_ == service) + { +#if !defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_RUNTIME) \ + && !defined(__CYGWIN__) + // Disable the pipe readiness notifications. + int read_descriptor = state->read_descriptor_; + lock.unlock(); + service->reactor_.deregister_internal_descriptor( + read_descriptor, service->reactor_data_); + service->reactor_.cleanup_descriptor_data(service->reactor_data_); + lock.lock(); +#endif // !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) + + // Remove service from linked list of all services. + if (state->service_list_ == service) + state->service_list_ = service->next_; + if (service->prev_) + service->prev_->next_ = service->next_; + if (service->next_) + service->next_->prev_= service->prev_; + service->next_ = 0; + service->prev_ = 0; + +#if !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) + // If this is the last service to be removed, close the pipe. + if (state->service_list_ == 0) + close_descriptors(); +#endif // !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) + } +} + +void signal_set_service::open_descriptors() +{ +#if !defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_RUNTIME) \ + && !defined(__CYGWIN__) + signal_state* state = get_signal_state(); + + int pipe_fds[2]; + if (::pipe(pipe_fds) == 0) + { + state->read_descriptor_ = pipe_fds[0]; + ::fcntl(state->read_descriptor_, F_SETFL, O_NONBLOCK); + + state->write_descriptor_ = pipe_fds[1]; + ::fcntl(state->write_descriptor_, F_SETFL, O_NONBLOCK); + +#if defined(FD_CLOEXEC) + ::fcntl(state->read_descriptor_, F_SETFD, FD_CLOEXEC); + ::fcntl(state->write_descriptor_, F_SETFD, FD_CLOEXEC); +#endif // defined(FD_CLOEXEC) + } + else + { + asio::error_code ec(errno, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "signal_set_service pipe"); + } +#endif // !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) +} + +void signal_set_service::close_descriptors() +{ +#if !defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_RUNTIME) \ + && !defined(__CYGWIN__) + signal_state* state = get_signal_state(); + + if (state->read_descriptor_ != -1) + ::close(state->read_descriptor_); + state->read_descriptor_ = -1; + + if (state->write_descriptor_ != -1) + ::close(state->write_descriptor_); + state->write_descriptor_ = -1; +#endif // !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) +} + +void signal_set_service::start_wait_op( + signal_set_service::implementation_type& impl, signal_op* op) +{ + scheduler_.work_started(); + + signal_state* state = get_signal_state(); + static_mutex::scoped_lock lock(state->mutex_); + + registration* reg = impl.signals_; + while (reg) + { + if (reg->undelivered_ > 0) + { + --reg->undelivered_; + op->signal_number_ = reg->signal_number_; + scheduler_.post_deferred_completion(op); + return; + } + + reg = reg->next_in_set_; + } + + impl.queue_.push(op); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_IMPL_SIGNAL_SET_SERVICE_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/socket_ops.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/socket_ops.ipp new file mode 100644 index 000000000..4bf06ee5f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/socket_ops.ipp @@ -0,0 +1,3962 @@ +// +// detail/impl/socket_ops.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SOCKET_OPS_IPP +#define ASIO_DETAIL_SOCKET_OPS_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#include +#include +#include +#include +#include +#include +#include "asio/detail/assert.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/error.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) +# include +# include +# include +#endif // defined(ASIO_WINDOWS_RUNTIME) + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) \ + || defined(__MACH__) && defined(__APPLE__) +# if defined(ASIO_HAS_PTHREADS) +# include +# endif // defined(ASIO_HAS_PTHREADS) +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + // || defined(__MACH__) && defined(__APPLE__) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { +namespace socket_ops { + +#if !defined(ASIO_WINDOWS_RUNTIME) + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) +struct msghdr { int msg_namelen; }; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +#if defined(__hpux) +// HP-UX doesn't declare these functions extern "C", so they are declared again +// here to avoid linker errors about undefined symbols. +extern "C" char* if_indextoname(unsigned int, char*); +extern "C" unsigned int if_nametoindex(const char*); +#endif // defined(__hpux) + +#endif // !defined(ASIO_WINDOWS_RUNTIME) + +inline void clear_last_error() +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + WSASetLastError(0); +#else + errno = 0; +#endif +} + +#if !defined(ASIO_WINDOWS_RUNTIME) + +inline void get_last_error( + asio::error_code& ec, bool is_error_condition) +{ + if (!is_error_condition) + { + ec.assign(0, ec.category()); + } + else + { +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + ec = asio::error_code(WSAGetLastError(), + asio::error::get_system_category()); +#else + ec = asio::error_code(errno, + asio::error::get_system_category()); +#endif + } +} + +template +inline socket_type call_accept(SockLenType msghdr::*, + socket_type s, socket_addr_type* addr, std::size_t* addrlen) +{ + SockLenType tmp_addrlen = addrlen ? (SockLenType)*addrlen : 0; + socket_type result = ::accept(s, addr, addrlen ? &tmp_addrlen : 0); + if (addrlen) + *addrlen = (std::size_t)tmp_addrlen; + return result; +} + +socket_type accept(socket_type s, socket_addr_type* addr, + std::size_t* addrlen, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return invalid_socket; + } + + socket_type new_s = call_accept(&msghdr::msg_namelen, s, addr, addrlen); + get_last_error(ec, new_s == invalid_socket); + if (new_s == invalid_socket) + return new_s; + +#if defined(__MACH__) && defined(__APPLE__) || defined(__FreeBSD__) + int optval = 1; + int result = ::setsockopt(new_s, SOL_SOCKET, + SO_NOSIGPIPE, &optval, sizeof(optval)); + get_last_error(ec, result != 0); + if (result != 0) + { + ::close(new_s); + return invalid_socket; + } +#endif + + ec.assign(0, ec.category()); + return new_s; +} + +socket_type sync_accept(socket_type s, state_type state, + socket_addr_type* addr, std::size_t* addrlen, asio::error_code& ec) +{ + // Accept a socket. + for (;;) + { + // Try to complete the operation without blocking. + socket_type new_socket = socket_ops::accept(s, addr, addrlen, ec); + + // Check if operation succeeded. + if (new_socket != invalid_socket) + return new_socket; + + // Operation failed. + if (ec == asio::error::would_block + || ec == asio::error::try_again) + { + if (state & user_set_non_blocking) + return invalid_socket; + // Fall through to retry operation. + } + else if (ec == asio::error::connection_aborted) + { + if (state & enable_connection_aborted) + return invalid_socket; + // Fall through to retry operation. + } +#if defined(EPROTO) + else if (ec.value() == EPROTO) + { + if (state & enable_connection_aborted) + return invalid_socket; + // Fall through to retry operation. + } +#endif // defined(EPROTO) + else + return invalid_socket; + + // Wait for socket to become ready. + if (socket_ops::poll_read(s, 0, -1, ec) < 0) + return invalid_socket; + } +} + +#if defined(ASIO_HAS_IOCP) + +void complete_iocp_accept(socket_type s, + void* output_buffer, DWORD address_length, + socket_addr_type* addr, std::size_t* addrlen, + socket_type new_socket, asio::error_code& ec) +{ + // Map non-portable errors to their portable counterparts. + if (ec.value() == ERROR_NETNAME_DELETED) + ec = asio::error::connection_aborted; + + if (!ec) + { + // Get the address of the peer. + if (addr && addrlen) + { + LPSOCKADDR local_addr = 0; + int local_addr_length = 0; + LPSOCKADDR remote_addr = 0; + int remote_addr_length = 0; + GetAcceptExSockaddrs(output_buffer, 0, address_length, + address_length, &local_addr, &local_addr_length, + &remote_addr, &remote_addr_length); + if (static_cast(remote_addr_length) > *addrlen) + { + ec = asio::error::invalid_argument; + } + else + { + using namespace std; // For memcpy. + memcpy(addr, remote_addr, remote_addr_length); + *addrlen = static_cast(remote_addr_length); + } + } + + // Need to set the SO_UPDATE_ACCEPT_CONTEXT option so that getsockname + // and getpeername will work on the accepted socket. + SOCKET update_ctx_param = s; + socket_ops::state_type state = 0; + socket_ops::setsockopt(new_socket, state, + SOL_SOCKET, SO_UPDATE_ACCEPT_CONTEXT, + &update_ctx_param, sizeof(SOCKET), ec); + } +} + +#else // defined(ASIO_HAS_IOCP) + +bool non_blocking_accept(socket_type s, + state_type state, socket_addr_type* addr, std::size_t* addrlen, + asio::error_code& ec, socket_type& new_socket) +{ + for (;;) + { + // Accept the waiting connection. + new_socket = socket_ops::accept(s, addr, addrlen, ec); + + // Check if operation succeeded. + if (new_socket != invalid_socket) + return true; + + // Retry operation if interrupted by signal. + if (ec == asio::error::interrupted) + continue; + + // Operation failed. + if (ec == asio::error::would_block + || ec == asio::error::try_again) + { + // Fall through to retry operation. + } + else if (ec == asio::error::connection_aborted) + { + if (state & enable_connection_aborted) + return true; + // Fall through to retry operation. + } +#if defined(EPROTO) + else if (ec.value() == EPROTO) + { + if (state & enable_connection_aborted) + return true; + // Fall through to retry operation. + } +#endif // defined(EPROTO) + else + return true; + + return false; + } +} + +#endif // defined(ASIO_HAS_IOCP) + +template +inline int call_bind(SockLenType msghdr::*, + socket_type s, const socket_addr_type* addr, std::size_t addrlen) +{ + return ::bind(s, addr, (SockLenType)addrlen); +} + +int bind(socket_type s, const socket_addr_type* addr, + std::size_t addrlen, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return socket_error_retval; + } + + int result = call_bind(&msghdr::msg_namelen, s, addr, addrlen); + get_last_error(ec, result != 0); + return result; +} + +int close(socket_type s, state_type& state, + bool destruction, asio::error_code& ec) +{ + int result = 0; + if (s != invalid_socket) + { + // We don't want the destructor to block, so set the socket to linger in + // the background. If the user doesn't like this behaviour then they need + // to explicitly close the socket. + if (destruction && (state & user_set_linger)) + { + ::linger opt; + opt.l_onoff = 0; + opt.l_linger = 0; + asio::error_code ignored_ec; + socket_ops::setsockopt(s, state, SOL_SOCKET, + SO_LINGER, &opt, sizeof(opt), ignored_ec); + } + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + result = ::closesocket(s); +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + result = ::close(s); +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + get_last_error(ec, result != 0); + + if (result != 0 + && (ec == asio::error::would_block + || ec == asio::error::try_again)) + { + // According to UNIX Network Programming Vol. 1, it is possible for + // close() to fail with EWOULDBLOCK under certain circumstances. What + // isn't clear is the state of the descriptor after this error. The one + // current OS where this behaviour is seen, Windows, says that the socket + // remains open. Therefore we'll put the descriptor back into blocking + // mode and have another attempt at closing it. +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + ioctl_arg_type arg = 0; + ::ioctlsocket(s, FIONBIO, &arg); +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +# if defined(__SYMBIAN32__) || defined(__EMSCRIPTEN__) + int flags = ::fcntl(s, F_GETFL, 0); + if (flags >= 0) + ::fcntl(s, F_SETFL, flags & ~O_NONBLOCK); +# else // defined(__SYMBIAN32__) || defined(__EMSCRIPTEN__) + ioctl_arg_type arg = 0; + ::ioctl(s, FIONBIO, &arg); +# endif // defined(__SYMBIAN32__) || defined(__EMSCRIPTEN__) +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + state &= ~non_blocking; + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + result = ::closesocket(s); +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + result = ::close(s); +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + get_last_error(ec, result != 0); + } + } + + return result; +} + +bool set_user_non_blocking(socket_type s, + state_type& state, bool value, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return false; + } + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + ioctl_arg_type arg = (value ? 1 : 0); + int result = ::ioctlsocket(s, FIONBIO, &arg); + get_last_error(ec, result < 0); +#elif defined(__SYMBIAN32__) || defined(__EMSCRIPTEN__) + int result = ::fcntl(s, F_GETFL, 0); + get_last_error(ec, result < 0); + if (result >= 0) + { + int flag = (value ? (result | O_NONBLOCK) : (result & ~O_NONBLOCK)); + result = ::fcntl(s, F_SETFL, flag); + get_last_error(ec, result < 0); + } +#else + ioctl_arg_type arg = (value ? 1 : 0); + int result = ::ioctl(s, FIONBIO, &arg); + get_last_error(ec, result < 0); +#endif + + if (result >= 0) + { + if (value) + state |= user_set_non_blocking; + else + { + // Clearing the user-set non-blocking mode always overrides any + // internally-set non-blocking flag. Any subsequent asynchronous + // operations will need to re-enable non-blocking I/O. + state &= ~(user_set_non_blocking | internal_non_blocking); + } + return true; + } + + return false; +} + +bool set_internal_non_blocking(socket_type s, + state_type& state, bool value, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return false; + } + + if (!value && (state & user_set_non_blocking)) + { + // It does not make sense to clear the internal non-blocking flag if the + // user still wants non-blocking behaviour. Return an error and let the + // caller figure out whether to update the user-set non-blocking flag. + ec = asio::error::invalid_argument; + return false; + } + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + ioctl_arg_type arg = (value ? 1 : 0); + int result = ::ioctlsocket(s, FIONBIO, &arg); + get_last_error(ec, result < 0); +#elif defined(__SYMBIAN32__) || defined(__EMSCRIPTEN__) + int result = ::fcntl(s, F_GETFL, 0); + get_last_error(ec, result < 0); + if (result >= 0) + { + int flag = (value ? (result | O_NONBLOCK) : (result & ~O_NONBLOCK)); + result = ::fcntl(s, F_SETFL, flag); + get_last_error(ec, result < 0); + } +#else + ioctl_arg_type arg = (value ? 1 : 0); + int result = ::ioctl(s, FIONBIO, &arg); + get_last_error(ec, result < 0); +#endif + + if (result >= 0) + { + if (value) + state |= internal_non_blocking; + else + state &= ~internal_non_blocking; + return true; + } + + return false; +} + +int shutdown(socket_type s, int what, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return socket_error_retval; + } + + int result = ::shutdown(s, what); + get_last_error(ec, result != 0); + return result; +} + +template +inline int call_connect(SockLenType msghdr::*, + socket_type s, const socket_addr_type* addr, std::size_t addrlen) +{ + return ::connect(s, addr, (SockLenType)addrlen); +} + +int connect(socket_type s, const socket_addr_type* addr, + std::size_t addrlen, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return socket_error_retval; + } + + int result = call_connect(&msghdr::msg_namelen, s, addr, addrlen); + get_last_error(ec, result != 0); +#if defined(__linux__) + if (result != 0 && ec == asio::error::try_again) + ec = asio::error::no_buffer_space; +#endif // defined(__linux__) + return result; +} + +void sync_connect(socket_type s, const socket_addr_type* addr, + std::size_t addrlen, asio::error_code& ec) +{ + // Perform the connect operation. + socket_ops::connect(s, addr, addrlen, ec); + if (ec != asio::error::in_progress + && ec != asio::error::would_block) + { + // The connect operation finished immediately. + return; + } + + // Wait for socket to become ready. + if (socket_ops::poll_connect(s, -1, ec) < 0) + return; + + // Get the error code from the connect operation. + int connect_error = 0; + size_t connect_error_len = sizeof(connect_error); + if (socket_ops::getsockopt(s, 0, SOL_SOCKET, SO_ERROR, + &connect_error, &connect_error_len, ec) == socket_error_retval) + return; + + // Return the result of the connect operation. + ec = asio::error_code(connect_error, + asio::error::get_system_category()); +} + +#if defined(ASIO_HAS_IOCP) + +void complete_iocp_connect(socket_type s, asio::error_code& ec) +{ + // Map non-portable errors to their portable counterparts. + switch (ec.value()) + { + case ERROR_CONNECTION_REFUSED: + ec = asio::error::connection_refused; + break; + case ERROR_NETWORK_UNREACHABLE: + ec = asio::error::network_unreachable; + break; + case ERROR_HOST_UNREACHABLE: + ec = asio::error::host_unreachable; + break; + case ERROR_SEM_TIMEOUT: + ec = asio::error::timed_out; + break; + default: + break; + } + + if (!ec) + { + // Need to set the SO_UPDATE_CONNECT_CONTEXT option so that getsockname + // and getpeername will work on the connected socket. + socket_ops::state_type state = 0; + const int so_update_connect_context = 0x7010; + socket_ops::setsockopt(s, state, SOL_SOCKET, + so_update_connect_context, 0, 0, ec); + } +} + +#endif // defined(ASIO_HAS_IOCP) + +bool non_blocking_connect(socket_type s, asio::error_code& ec) +{ + // Check if the connect operation has finished. This is required since we may + // get spurious readiness notifications from the reactor. +#if defined(ASIO_WINDOWS) \ + || defined(__CYGWIN__) \ + || defined(__SYMBIAN32__) + fd_set write_fds; + FD_ZERO(&write_fds); + FD_SET(s, &write_fds); + fd_set except_fds; + FD_ZERO(&except_fds); + FD_SET(s, &except_fds); + timeval zero_timeout; + zero_timeout.tv_sec = 0; + zero_timeout.tv_usec = 0; + int ready = ::select(s + 1, 0, &write_fds, &except_fds, &zero_timeout); +#else // defined(ASIO_WINDOWS) + // || defined(__CYGWIN__) + // || defined(__SYMBIAN32__) + pollfd fds; + fds.fd = s; + fds.events = POLLOUT; + fds.revents = 0; + int ready = ::poll(&fds, 1, 0); +#endif // defined(ASIO_WINDOWS) + // || defined(__CYGWIN__) + // || defined(__SYMBIAN32__) + if (ready == 0) + { + // The asynchronous connect operation is still in progress. + return false; + } + + // Get the error code from the connect operation. + int connect_error = 0; + size_t connect_error_len = sizeof(connect_error); + if (socket_ops::getsockopt(s, 0, SOL_SOCKET, SO_ERROR, + &connect_error, &connect_error_len, ec) == 0) + { + if (connect_error) + { + ec = asio::error_code(connect_error, + asio::error::get_system_category()); + } + else + ec.assign(0, ec.category()); + } + + return true; +} + +int socketpair(int af, int type, int protocol, + socket_type sv[2], asio::error_code& ec) +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + (void)(af); + (void)(type); + (void)(protocol); + (void)(sv); + ec = asio::error::operation_not_supported; + return socket_error_retval; +#else + int result = ::socketpair(af, type, protocol, sv); + get_last_error(ec, result != 0); + return result; +#endif +} + +bool sockatmark(socket_type s, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return false; + } + +#if defined(SIOCATMARK) + ioctl_arg_type value = 0; +# if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + int result = ::ioctlsocket(s, SIOCATMARK, &value); +# else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + int result = ::ioctl(s, SIOCATMARK, &value); +# endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + get_last_error(ec, result < 0); +# if defined(ENOTTY) + if (ec.value() == ENOTTY) + ec = asio::error::not_socket; +# endif // defined(ENOTTY) +#else // defined(SIOCATMARK) + int value = ::sockatmark(s); + get_last_error(ec, result < 0); +#endif // defined(SIOCATMARK) + + return ec ? false : value != 0; +} + +size_t available(socket_type s, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return 0; + } + + ioctl_arg_type value = 0; +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + int result = ::ioctlsocket(s, FIONREAD, &value); +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + int result = ::ioctl(s, FIONREAD, &value); +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + get_last_error(ec, result < 0); +#if defined(ENOTTY) + if (ec.value() == ENOTTY) + ec = asio::error::not_socket; +#endif // defined(ENOTTY) + + return ec ? static_cast(0) : static_cast(value); +} + +int listen(socket_type s, int backlog, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return socket_error_retval; + } + + int result = ::listen(s, backlog); + get_last_error(ec, result != 0); + return result; +} + +inline void init_buf_iov_base(void*& base, void* addr) +{ + base = addr; +} + +template +inline void init_buf_iov_base(T& base, void* addr) +{ + base = static_cast(addr); +} + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) +typedef WSABUF buf; +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +typedef iovec buf; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +void init_buf(buf& b, void* data, size_t size) +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + b.buf = static_cast(data); + b.len = static_cast(size); +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + init_buf_iov_base(b.iov_base, data); + b.iov_len = size; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +} + +void init_buf(buf& b, const void* data, size_t size) +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + b.buf = static_cast(const_cast(data)); + b.len = static_cast(size); +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + init_buf_iov_base(b.iov_base, const_cast(data)); + b.iov_len = size; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +} + +inline void init_msghdr_msg_name(void*& name, socket_addr_type* addr) +{ + name = addr; +} + +inline void init_msghdr_msg_name(void*& name, const socket_addr_type* addr) +{ + name = const_cast(addr); +} + +template +inline void init_msghdr_msg_name(T& name, socket_addr_type* addr) +{ + name = reinterpret_cast(addr); +} + +template +inline void init_msghdr_msg_name(T& name, const socket_addr_type* addr) +{ + name = reinterpret_cast(const_cast(addr)); +} + +signed_size_type recv(socket_type s, buf* bufs, size_t count, + int flags, asio::error_code& ec) +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + // Receive some data. + DWORD recv_buf_count = static_cast(count); + DWORD bytes_transferred = 0; + DWORD recv_flags = flags; + int result = ::WSARecv(s, bufs, recv_buf_count, + &bytes_transferred, &recv_flags, 0, 0); + get_last_error(ec, true); + if (ec.value() == ERROR_NETNAME_DELETED) + ec = asio::error::connection_reset; + else if (ec.value() == ERROR_PORT_UNREACHABLE) + ec = asio::error::connection_refused; + else if (ec.value() == WSAEMSGSIZE || ec.value() == ERROR_MORE_DATA) + result = 0; + if (result != 0) + return socket_error_retval; + ec.assign(0, ec.category()); + return bytes_transferred; +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + msghdr msg = msghdr(); + msg.msg_iov = bufs; + msg.msg_iovlen = static_cast(count); + signed_size_type result = ::recvmsg(s, &msg, flags); + get_last_error(ec, result < 0); + return result; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +} + +signed_size_type recv1(socket_type s, void* data, size_t size, + int flags, asio::error_code& ec) +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + // Receive some data. + WSABUF buf; + buf.buf = const_cast(static_cast(data)); + buf.len = static_cast(size); + DWORD bytes_transferred = 0; + DWORD recv_flags = flags; + int result = ::WSARecv(s, &buf, 1, + &bytes_transferred, &recv_flags, 0, 0); + get_last_error(ec, true); + if (ec.value() == ERROR_NETNAME_DELETED) + ec = asio::error::connection_reset; + else if (ec.value() == ERROR_PORT_UNREACHABLE) + ec = asio::error::connection_refused; + else if (ec.value() == WSAEMSGSIZE || ec.value() == ERROR_MORE_DATA) + result = 0; + if (result != 0) + return socket_error_retval; + ec.assign(0, ec.category()); + return bytes_transferred; +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + signed_size_type result = ::recv(s, static_cast(data), size, flags); + get_last_error(ec, result < 0); + return result; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +} + +size_t sync_recv(socket_type s, state_type state, buf* bufs, + size_t count, int flags, bool all_empty, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return 0; + } + + // A request to read 0 bytes on a stream is a no-op. + if (all_empty && (state & stream_oriented)) + { + ec.assign(0, ec.category()); + return 0; + } + + // Read some data. + for (;;) + { + // Try to complete the operation without blocking. + signed_size_type bytes = socket_ops::recv(s, bufs, count, flags, ec); + + // Check for EOF. + if ((state & stream_oriented) && bytes == 0) + { + ec = asio::error::eof; + return 0; + } + + // Check if operation succeeded. + if (bytes >= 0) + return bytes; + + // Operation failed. + if ((state & user_set_non_blocking) + || (ec != asio::error::would_block + && ec != asio::error::try_again)) + return 0; + + // Wait for socket to become ready. + if (socket_ops::poll_read(s, 0, -1, ec) < 0) + return 0; + } +} + +size_t sync_recv1(socket_type s, state_type state, void* data, + size_t size, int flags, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return 0; + } + + // A request to read 0 bytes on a stream is a no-op. + if (size == 0 && (state & stream_oriented)) + { + ec.assign(0, ec.category()); + return 0; + } + + // Read some data. + for (;;) + { + // Try to complete the operation without blocking. + signed_size_type bytes = socket_ops::recv1(s, data, size, flags, ec); + + // Check for EOF. + if ((state & stream_oriented) && bytes == 0) + { + ec = asio::error::eof; + return 0; + } + + // Check if operation succeeded. + if (bytes >= 0) + return bytes; + + // Operation failed. + if ((state & user_set_non_blocking) + || (ec != asio::error::would_block + && ec != asio::error::try_again)) + return 0; + + // Wait for socket to become ready. + if (socket_ops::poll_read(s, 0, -1, ec) < 0) + return 0; + } +} + +#if defined(ASIO_HAS_IOCP) + +void complete_iocp_recv(state_type state, + const weak_cancel_token_type& cancel_token, bool all_empty, + asio::error_code& ec, size_t bytes_transferred) +{ + // Map non-portable errors to their portable counterparts. + if (ec.value() == ERROR_NETNAME_DELETED) + { + if (cancel_token.expired()) + ec = asio::error::operation_aborted; + else + ec = asio::error::connection_reset; + } + else if (ec.value() == ERROR_PORT_UNREACHABLE) + { + ec = asio::error::connection_refused; + } + else if (ec.value() == WSAEMSGSIZE || ec.value() == ERROR_MORE_DATA) + { + ec.assign(0, ec.category()); + } + + // Check for connection closed. + else if (!ec && bytes_transferred == 0 + && (state & stream_oriented) != 0 + && !all_empty) + { + ec = asio::error::eof; + } +} + +#else // defined(ASIO_HAS_IOCP) + +bool non_blocking_recv(socket_type s, + buf* bufs, size_t count, int flags, bool is_stream, + asio::error_code& ec, size_t& bytes_transferred) +{ + for (;;) + { + // Read some data. + signed_size_type bytes = socket_ops::recv(s, bufs, count, flags, ec); + + // Check for end of stream. + if (is_stream && bytes == 0) + { + ec = asio::error::eof; + return true; + } + + // Check if operation succeeded. + if (bytes >= 0) + { + bytes_transferred = bytes; + return true; + } + + // Retry operation if interrupted by signal. + if (ec == asio::error::interrupted) + continue; + + // Check if we need to run the operation again. + if (ec == asio::error::would_block + || ec == asio::error::try_again) + return false; + + // Operation failed. + bytes_transferred = 0; + return true; + } +} + +bool non_blocking_recv1(socket_type s, + void* data, size_t size, int flags, bool is_stream, + asio::error_code& ec, size_t& bytes_transferred) +{ + for (;;) + { + // Read some data. + signed_size_type bytes = socket_ops::recv1(s, data, size, flags, ec); + + // Check for end of stream. + if (is_stream && bytes == 0) + { + ec = asio::error::eof; + return true; + } + + // Check if operation succeeded. + if (bytes >= 0) + { + bytes_transferred = bytes; + return true; + } + + // Retry operation if interrupted by signal. + if (ec == asio::error::interrupted) + continue; + + // Check if we need to run the operation again. + if (ec == asio::error::would_block + || ec == asio::error::try_again) + return false; + + // Operation failed. + bytes_transferred = 0; + return true; + } +} + +#endif // defined(ASIO_HAS_IOCP) + +signed_size_type recvfrom(socket_type s, buf* bufs, size_t count, + int flags, socket_addr_type* addr, std::size_t* addrlen, + asio::error_code& ec) +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + // Receive some data. + DWORD recv_buf_count = static_cast(count); + DWORD bytes_transferred = 0; + DWORD recv_flags = flags; + int tmp_addrlen = (int)*addrlen; + int result = ::WSARecvFrom(s, bufs, recv_buf_count, + &bytes_transferred, &recv_flags, addr, &tmp_addrlen, 0, 0); + get_last_error(ec, true); + *addrlen = (std::size_t)tmp_addrlen; + if (ec.value() == ERROR_NETNAME_DELETED) + ec = asio::error::connection_reset; + else if (ec.value() == ERROR_PORT_UNREACHABLE) + ec = asio::error::connection_refused; + else if (ec.value() == WSAEMSGSIZE || ec.value() == ERROR_MORE_DATA) + result = 0; + if (result != 0) + return socket_error_retval; + ec.assign(0, ec.category()); + return bytes_transferred; +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + msghdr msg = msghdr(); + init_msghdr_msg_name(msg.msg_name, addr); + msg.msg_namelen = static_cast(*addrlen); + msg.msg_iov = bufs; + msg.msg_iovlen = static_cast(count); + signed_size_type result = ::recvmsg(s, &msg, flags); + get_last_error(ec, result < 0); + *addrlen = msg.msg_namelen; + return result; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +} + +template +inline signed_size_type call_recvfrom(SockLenType msghdr::*, + socket_type s, void* data, size_t size, int flags, + socket_addr_type* addr, std::size_t* addrlen) +{ + SockLenType tmp_addrlen = addrlen ? (SockLenType)*addrlen : 0; + signed_size_type result = ::recvfrom(s, static_cast(data), + size, flags, addr, addrlen ? &tmp_addrlen : 0); + if (addrlen) + *addrlen = (std::size_t)tmp_addrlen; + return result; +} + +signed_size_type recvfrom1(socket_type s, void* data, size_t size, + int flags, socket_addr_type* addr, std::size_t* addrlen, + asio::error_code& ec) +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + // Receive some data. + WSABUF buf; + buf.buf = static_cast(data); + buf.len = static_cast(size); + DWORD bytes_transferred = 0; + DWORD recv_flags = flags; + int tmp_addrlen = (int)*addrlen; + int result = ::WSARecvFrom(s, &buf, 1, &bytes_transferred, + &recv_flags, addr, &tmp_addrlen, 0, 0); + get_last_error(ec, true); + *addrlen = (std::size_t)tmp_addrlen; + if (ec.value() == ERROR_NETNAME_DELETED) + ec = asio::error::connection_reset; + else if (ec.value() == ERROR_PORT_UNREACHABLE) + ec = asio::error::connection_refused; + else if (ec.value() == WSAEMSGSIZE || ec.value() == ERROR_MORE_DATA) + result = 0; + if (result != 0) + return socket_error_retval; + ec.assign(0, ec.category()); + return bytes_transferred; +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + signed_size_type result = call_recvfrom(&msghdr::msg_namelen, + s, data, size, flags, addr, addrlen); + get_last_error(ec, result < 0); + return result; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +} + +size_t sync_recvfrom(socket_type s, state_type state, buf* bufs, + size_t count, int flags, socket_addr_type* addr, + std::size_t* addrlen, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return 0; + } + + // Read some data. + for (;;) + { + // Try to complete the operation without blocking. + signed_size_type bytes = socket_ops::recvfrom( + s, bufs, count, flags, addr, addrlen, ec); + + // Check if operation succeeded. + if (bytes >= 0) + return bytes; + + // Operation failed. + if ((state & user_set_non_blocking) + || (ec != asio::error::would_block + && ec != asio::error::try_again)) + return 0; + + // Wait for socket to become ready. + if (socket_ops::poll_read(s, 0, -1, ec) < 0) + return 0; + } +} + +size_t sync_recvfrom1(socket_type s, state_type state, void* data, + size_t size, int flags, socket_addr_type* addr, + std::size_t* addrlen, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return 0; + } + + // Read some data. + for (;;) + { + // Try to complete the operation without blocking. + signed_size_type bytes = socket_ops::recvfrom1( + s, data, size, flags, addr, addrlen, ec); + + // Check if operation succeeded. + if (bytes >= 0) + return bytes; + + // Operation failed. + if ((state & user_set_non_blocking) + || (ec != asio::error::would_block + && ec != asio::error::try_again)) + return 0; + + // Wait for socket to become ready. + if (socket_ops::poll_read(s, 0, -1, ec) < 0) + return 0; + } +} + +#if defined(ASIO_HAS_IOCP) + +void complete_iocp_recvfrom( + const weak_cancel_token_type& cancel_token, + asio::error_code& ec) +{ + // Map non-portable errors to their portable counterparts. + if (ec.value() == ERROR_NETNAME_DELETED) + { + if (cancel_token.expired()) + ec = asio::error::operation_aborted; + else + ec = asio::error::connection_reset; + } + else if (ec.value() == ERROR_PORT_UNREACHABLE) + { + ec = asio::error::connection_refused; + } + else if (ec.value() == WSAEMSGSIZE || ec.value() == ERROR_MORE_DATA) + { + ec.assign(0, ec.category()); + } +} + +#else // defined(ASIO_HAS_IOCP) + +bool non_blocking_recvfrom(socket_type s, + buf* bufs, size_t count, int flags, + socket_addr_type* addr, std::size_t* addrlen, + asio::error_code& ec, size_t& bytes_transferred) +{ + for (;;) + { + // Read some data. + signed_size_type bytes = socket_ops::recvfrom( + s, bufs, count, flags, addr, addrlen, ec); + + // Check if operation succeeded. + if (bytes >= 0) + { + bytes_transferred = bytes; + return true; + } + + // Retry operation if interrupted by signal. + if (ec == asio::error::interrupted) + continue; + + // Check if we need to run the operation again. + if (ec == asio::error::would_block + || ec == asio::error::try_again) + return false; + + // Operation failed. + bytes_transferred = 0; + return true; + } +} + +bool non_blocking_recvfrom1(socket_type s, + void* data, size_t size, int flags, + socket_addr_type* addr, std::size_t* addrlen, + asio::error_code& ec, size_t& bytes_transferred) +{ + for (;;) + { + // Read some data. + signed_size_type bytes = socket_ops::recvfrom1( + s, data, size, flags, addr, addrlen, ec); + + // Check if operation succeeded. + if (bytes >= 0) + { + bytes_transferred = bytes; + return true; + } + + // Retry operation if interrupted by signal. + if (ec == asio::error::interrupted) + continue; + + // Check if we need to run the operation again. + if (ec == asio::error::would_block + || ec == asio::error::try_again) + return false; + + // Operation failed. + bytes_transferred = 0; + return true; + } +} + +#endif // defined(ASIO_HAS_IOCP) + +signed_size_type recvmsg(socket_type s, buf* bufs, size_t count, + int in_flags, int& out_flags, asio::error_code& ec) +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + out_flags = 0; + return socket_ops::recv(s, bufs, count, in_flags, ec); +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + msghdr msg = msghdr(); + msg.msg_iov = bufs; + msg.msg_iovlen = static_cast(count); + signed_size_type result = ::recvmsg(s, &msg, in_flags); + get_last_error(ec, result < 0); + if (result >= 0) + out_flags = msg.msg_flags; + else + out_flags = 0; + return result; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +} + +size_t sync_recvmsg(socket_type s, state_type state, + buf* bufs, size_t count, int in_flags, int& out_flags, + asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return 0; + } + + // Read some data. + for (;;) + { + // Try to complete the operation without blocking. + signed_size_type bytes = socket_ops::recvmsg( + s, bufs, count, in_flags, out_flags, ec); + + // Check if operation succeeded. + if (bytes >= 0) + return bytes; + + // Operation failed. + if ((state & user_set_non_blocking) + || (ec != asio::error::would_block + && ec != asio::error::try_again)) + return 0; + + // Wait for socket to become ready. + if (socket_ops::poll_read(s, 0, -1, ec) < 0) + return 0; + } +} + +#if defined(ASIO_HAS_IOCP) + +void complete_iocp_recvmsg( + const weak_cancel_token_type& cancel_token, + asio::error_code& ec) +{ + // Map non-portable errors to their portable counterparts. + if (ec.value() == ERROR_NETNAME_DELETED) + { + if (cancel_token.expired()) + ec = asio::error::operation_aborted; + else + ec = asio::error::connection_reset; + } + else if (ec.value() == ERROR_PORT_UNREACHABLE) + { + ec = asio::error::connection_refused; + } + else if (ec.value() == WSAEMSGSIZE || ec.value() == ERROR_MORE_DATA) + { + ec.assign(0, ec.category()); + } +} + +#else // defined(ASIO_HAS_IOCP) + +bool non_blocking_recvmsg(socket_type s, + buf* bufs, size_t count, int in_flags, int& out_flags, + asio::error_code& ec, size_t& bytes_transferred) +{ + for (;;) + { + // Read some data. + signed_size_type bytes = socket_ops::recvmsg( + s, bufs, count, in_flags, out_flags, ec); + + // Check if operation succeeded. + if (bytes >= 0) + { + bytes_transferred = bytes; + return true; + } + + // Retry operation if interrupted by signal. + if (ec == asio::error::interrupted) + continue; + + // Check if we need to run the operation again. + if (ec == asio::error::would_block + || ec == asio::error::try_again) + return false; + + // Operation failed. + bytes_transferred = 0; + return true; + } +} + +#endif // defined(ASIO_HAS_IOCP) + +signed_size_type send(socket_type s, const buf* bufs, size_t count, + int flags, asio::error_code& ec) +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + // Send the data. + DWORD send_buf_count = static_cast(count); + DWORD bytes_transferred = 0; + DWORD send_flags = flags; + int result = ::WSASend(s, const_cast(bufs), + send_buf_count, &bytes_transferred, send_flags, 0, 0); + get_last_error(ec, true); + if (ec.value() == ERROR_NETNAME_DELETED) + ec = asio::error::connection_reset; + else if (ec.value() == ERROR_PORT_UNREACHABLE) + ec = asio::error::connection_refused; + if (result != 0) + return socket_error_retval; + ec.assign(0, ec.category()); + return bytes_transferred; +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + msghdr msg = msghdr(); + msg.msg_iov = const_cast(bufs); + msg.msg_iovlen = static_cast(count); +#if defined(__linux__) + flags |= MSG_NOSIGNAL; +#endif // defined(__linux__) + signed_size_type result = ::sendmsg(s, &msg, flags); + get_last_error(ec, result < 0); + return result; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +} + +signed_size_type send1(socket_type s, const void* data, size_t size, + int flags, asio::error_code& ec) +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + // Send the data. + WSABUF buf; + buf.buf = const_cast(static_cast(data)); + buf.len = static_cast(size); + DWORD bytes_transferred = 0; + DWORD send_flags = flags; + int result = ::WSASend(s, &buf, 1, + &bytes_transferred, send_flags, 0, 0); + get_last_error(ec, true); + if (ec.value() == ERROR_NETNAME_DELETED) + ec = asio::error::connection_reset; + else if (ec.value() == ERROR_PORT_UNREACHABLE) + ec = asio::error::connection_refused; + if (result != 0) + return socket_error_retval; + ec.assign(0, ec.category()); + return bytes_transferred; +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +#if defined(__linux__) + flags |= MSG_NOSIGNAL; +#endif // defined(__linux__) + signed_size_type result = ::send(s, + static_cast(data), size, flags); + get_last_error(ec, result < 0); + return result; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +} + +size_t sync_send(socket_type s, state_type state, const buf* bufs, + size_t count, int flags, bool all_empty, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return 0; + } + + // A request to write 0 bytes to a stream is a no-op. + if (all_empty && (state & stream_oriented)) + { + ec.assign(0, ec.category()); + return 0; + } + + // Read some data. + for (;;) + { + // Try to complete the operation without blocking. + signed_size_type bytes = socket_ops::send(s, bufs, count, flags, ec); + + // Check if operation succeeded. + if (bytes >= 0) + return bytes; + + // Operation failed. + if ((state & user_set_non_blocking) + || (ec != asio::error::would_block + && ec != asio::error::try_again)) + return 0; + + // Wait for socket to become ready. + if (socket_ops::poll_write(s, 0, -1, ec) < 0) + return 0; + } +} + +size_t sync_send1(socket_type s, state_type state, const void* data, + size_t size, int flags, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return 0; + } + + // A request to write 0 bytes to a stream is a no-op. + if (size == 0 && (state & stream_oriented)) + { + ec.assign(0, ec.category()); + return 0; + } + + // Read some data. + for (;;) + { + // Try to complete the operation without blocking. + signed_size_type bytes = socket_ops::send1(s, data, size, flags, ec); + + // Check if operation succeeded. + if (bytes >= 0) + return bytes; + + // Operation failed. + if ((state & user_set_non_blocking) + || (ec != asio::error::would_block + && ec != asio::error::try_again)) + return 0; + + // Wait for socket to become ready. + if (socket_ops::poll_write(s, 0, -1, ec) < 0) + return 0; + } +} + +#if defined(ASIO_HAS_IOCP) + +void complete_iocp_send( + const weak_cancel_token_type& cancel_token, + asio::error_code& ec) +{ + // Map non-portable errors to their portable counterparts. + if (ec.value() == ERROR_NETNAME_DELETED) + { + if (cancel_token.expired()) + ec = asio::error::operation_aborted; + else + ec = asio::error::connection_reset; + } + else if (ec.value() == ERROR_PORT_UNREACHABLE) + { + ec = asio::error::connection_refused; + } +} + +#else // defined(ASIO_HAS_IOCP) + +bool non_blocking_send(socket_type s, + const buf* bufs, size_t count, int flags, + asio::error_code& ec, size_t& bytes_transferred) +{ + for (;;) + { + // Write some data. + signed_size_type bytes = socket_ops::send(s, bufs, count, flags, ec); + + // Check if operation succeeded. + if (bytes >= 0) + { + bytes_transferred = bytes; + return true; + } + + // Retry operation if interrupted by signal. + if (ec == asio::error::interrupted) + continue; + + // Check if we need to run the operation again. + if (ec == asio::error::would_block + || ec == asio::error::try_again) + return false; + + // Operation failed. + bytes_transferred = 0; + return true; + } +} + +bool non_blocking_send1(socket_type s, + const void* data, size_t size, int flags, + asio::error_code& ec, size_t& bytes_transferred) +{ + for (;;) + { + // Write some data. + signed_size_type bytes = socket_ops::send1(s, data, size, flags, ec); + + // Check if operation succeeded. + if (bytes >= 0) + { + bytes_transferred = bytes; + return true; + } + + // Retry operation if interrupted by signal. + if (ec == asio::error::interrupted) + continue; + + // Check if we need to run the operation again. + if (ec == asio::error::would_block + || ec == asio::error::try_again) + return false; + + // Operation failed. + bytes_transferred = 0; + return true; + } +} + +#endif // defined(ASIO_HAS_IOCP) + +signed_size_type sendto(socket_type s, const buf* bufs, size_t count, + int flags, const socket_addr_type* addr, std::size_t addrlen, + asio::error_code& ec) +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + // Send the data. + DWORD send_buf_count = static_cast(count); + DWORD bytes_transferred = 0; + int result = ::WSASendTo(s, const_cast(bufs), + send_buf_count, &bytes_transferred, flags, addr, + static_cast(addrlen), 0, 0); + get_last_error(ec, true); + if (ec.value() == ERROR_NETNAME_DELETED) + ec = asio::error::connection_reset; + else if (ec.value() == ERROR_PORT_UNREACHABLE) + ec = asio::error::connection_refused; + if (result != 0) + return socket_error_retval; + ec.assign(0, ec.category()); + return bytes_transferred; +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + msghdr msg = msghdr(); + init_msghdr_msg_name(msg.msg_name, addr); + msg.msg_namelen = static_cast(addrlen); + msg.msg_iov = const_cast(bufs); + msg.msg_iovlen = static_cast(count); +#if defined(__linux__) + flags |= MSG_NOSIGNAL; +#endif // defined(__linux__) + signed_size_type result = ::sendmsg(s, &msg, flags); + get_last_error(ec, result < 0); + return result; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +} + +template +inline signed_size_type call_sendto(SockLenType msghdr::*, + socket_type s, const void* data, size_t size, int flags, + const socket_addr_type* addr, std::size_t addrlen) +{ + return ::sendto(s, static_cast(const_cast(data)), + size, flags, addr, (SockLenType)addrlen); +} + +signed_size_type sendto1(socket_type s, const void* data, size_t size, + int flags, const socket_addr_type* addr, std::size_t addrlen, + asio::error_code& ec) +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + // Send the data. + WSABUF buf; + buf.buf = const_cast(static_cast(data)); + buf.len = static_cast(size); + DWORD bytes_transferred = 0; + int result = ::WSASendTo(s, &buf, 1, &bytes_transferred, + flags, addr, static_cast(addrlen), 0, 0); + get_last_error(ec, true); + if (ec.value() == ERROR_NETNAME_DELETED) + ec = asio::error::connection_reset; + else if (ec.value() == ERROR_PORT_UNREACHABLE) + ec = asio::error::connection_refused; + if (result != 0) + return socket_error_retval; + ec.assign(0, ec.category()); + return bytes_transferred; +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +#if defined(__linux__) + flags |= MSG_NOSIGNAL; +#endif // defined(__linux__) + signed_size_type result = call_sendto(&msghdr::msg_namelen, + s, data, size, flags, addr, addrlen); + get_last_error(ec, result < 0); + return result; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +} + +size_t sync_sendto(socket_type s, state_type state, const buf* bufs, + size_t count, int flags, const socket_addr_type* addr, + std::size_t addrlen, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return 0; + } + + // Write some data. + for (;;) + { + // Try to complete the operation without blocking. + signed_size_type bytes = socket_ops::sendto( + s, bufs, count, flags, addr, addrlen, ec); + + // Check if operation succeeded. + if (bytes >= 0) + return bytes; + + // Operation failed. + if ((state & user_set_non_blocking) + || (ec != asio::error::would_block + && ec != asio::error::try_again)) + return 0; + + // Wait for socket to become ready. + if (socket_ops::poll_write(s, 0, -1, ec) < 0) + return 0; + } +} + +size_t sync_sendto1(socket_type s, state_type state, const void* data, + size_t size, int flags, const socket_addr_type* addr, + std::size_t addrlen, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return 0; + } + + // Write some data. + for (;;) + { + // Try to complete the operation without blocking. + signed_size_type bytes = socket_ops::sendto1( + s, data, size, flags, addr, addrlen, ec); + + // Check if operation succeeded. + if (bytes >= 0) + return bytes; + + // Operation failed. + if ((state & user_set_non_blocking) + || (ec != asio::error::would_block + && ec != asio::error::try_again)) + return 0; + + // Wait for socket to become ready. + if (socket_ops::poll_write(s, 0, -1, ec) < 0) + return 0; + } +} + +#if !defined(ASIO_HAS_IOCP) + +bool non_blocking_sendto(socket_type s, + const buf* bufs, size_t count, int flags, + const socket_addr_type* addr, std::size_t addrlen, + asio::error_code& ec, size_t& bytes_transferred) +{ + for (;;) + { + // Write some data. + signed_size_type bytes = socket_ops::sendto( + s, bufs, count, flags, addr, addrlen, ec); + + // Check if operation succeeded. + if (bytes >= 0) + { + bytes_transferred = bytes; + return true; + } + + // Retry operation if interrupted by signal. + if (ec == asio::error::interrupted) + continue; + + // Check if we need to run the operation again. + if (ec == asio::error::would_block + || ec == asio::error::try_again) + return false; + + // Operation failed. + bytes_transferred = 0; + return true; + } +} + +bool non_blocking_sendto1(socket_type s, + const void* data, size_t size, int flags, + const socket_addr_type* addr, std::size_t addrlen, + asio::error_code& ec, size_t& bytes_transferred) +{ + for (;;) + { + // Write some data. + signed_size_type bytes = socket_ops::sendto1( + s, data, size, flags, addr, addrlen, ec); + + // Check if operation succeeded. + if (bytes >= 0) + { + bytes_transferred = bytes; + return true; + } + + // Retry operation if interrupted by signal. + if (ec == asio::error::interrupted) + continue; + + // Check if we need to run the operation again. + if (ec == asio::error::would_block + || ec == asio::error::try_again) + return false; + + // Operation failed. + bytes_transferred = 0; + return true; + } +} + +#endif // !defined(ASIO_HAS_IOCP) + +socket_type socket(int af, int type, int protocol, + asio::error_code& ec) +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + socket_type s = ::WSASocketW(af, type, protocol, 0, 0, WSA_FLAG_OVERLAPPED); + get_last_error(ec, s == invalid_socket); + if (s == invalid_socket) + return s; + + if (af == ASIO_OS_DEF(AF_INET6)) + { + // Try to enable the POSIX default behaviour of having IPV6_V6ONLY set to + // false. This will only succeed on Windows Vista and later versions of + // Windows, where a dual-stack IPv4/v6 implementation is available. + DWORD optval = 0; + ::setsockopt(s, IPPROTO_IPV6, IPV6_V6ONLY, + reinterpret_cast(&optval), sizeof(optval)); + } + + return s; +#elif defined(__MACH__) && defined(__APPLE__) || defined(__FreeBSD__) + socket_type s = ::socket(af, type, protocol); + get_last_error(ec, s < 0); + + int optval = 1; + int result = ::setsockopt(s, SOL_SOCKET, + SO_NOSIGPIPE, &optval, sizeof(optval)); + get_last_error(ec, result != 0); + if (result != 0) + { + ::close(s); + return invalid_socket; + } + + return s; +#else + int s = ::socket(af, type, protocol); + get_last_error(ec, s < 0); + return s; +#endif +} + +template +inline int call_setsockopt(SockLenType msghdr::*, + socket_type s, int level, int optname, + const void* optval, std::size_t optlen) +{ + return ::setsockopt(s, level, optname, + (const char*)optval, (SockLenType)optlen); +} + +int setsockopt(socket_type s, state_type& state, int level, int optname, + const void* optval, std::size_t optlen, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return socket_error_retval; + } + + if (level == custom_socket_option_level && optname == always_fail_option) + { + ec = asio::error::invalid_argument; + return socket_error_retval; + } + + if (level == custom_socket_option_level + && optname == enable_connection_aborted_option) + { + if (optlen != sizeof(int)) + { + ec = asio::error::invalid_argument; + return socket_error_retval; + } + + if (*static_cast(optval)) + state |= enable_connection_aborted; + else + state &= ~enable_connection_aborted; + ec.assign(0, ec.category()); + return 0; + } + + if (level == SOL_SOCKET && optname == SO_LINGER) + state |= user_set_linger; + +#if defined(__BORLANDC__) + // Mysteriously, using the getsockopt and setsockopt functions directly with + // Borland C++ results in incorrect values being set and read. The bug can be + // worked around by using function addresses resolved with GetProcAddress. + if (HMODULE winsock_module = ::GetModuleHandleA("ws2_32")) + { + typedef int (WSAAPI *sso_t)(SOCKET, int, int, const char*, int); + if (sso_t sso = (sso_t)::GetProcAddress(winsock_module, "setsockopt")) + { + int result = sso(s, level, optname, + reinterpret_cast(optval), + static_cast(optlen)); + get_last_error(ec, result != 0); + return result; + } + } + ec = asio::error::fault; + return socket_error_retval; +#else // defined(__BORLANDC__) + int result = call_setsockopt(&msghdr::msg_namelen, + s, level, optname, optval, optlen); + get_last_error(ec, result != 0); + if (result == 0) + { +#if defined(__MACH__) && defined(__APPLE__) \ + || defined(__NetBSD__) || defined(__FreeBSD__) \ + || defined(__OpenBSD__) || defined(__QNX__) + // To implement portable behaviour for SO_REUSEADDR with UDP sockets we + // need to also set SO_REUSEPORT on BSD-based platforms. + if ((state & datagram_oriented) + && level == SOL_SOCKET && optname == SO_REUSEADDR) + { + call_setsockopt(&msghdr::msg_namelen, s, + SOL_SOCKET, SO_REUSEPORT, optval, optlen); + } +#endif + } + + return result; +#endif // defined(__BORLANDC__) +} + +template +inline int call_getsockopt(SockLenType msghdr::*, + socket_type s, int level, int optname, + void* optval, std::size_t* optlen) +{ + SockLenType tmp_optlen = (SockLenType)*optlen; + int result = ::getsockopt(s, level, optname, (char*)optval, &tmp_optlen); + *optlen = (std::size_t)tmp_optlen; + return result; +} + +int getsockopt(socket_type s, state_type state, int level, int optname, + void* optval, size_t* optlen, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return socket_error_retval; + } + + if (level == custom_socket_option_level && optname == always_fail_option) + { + ec = asio::error::invalid_argument; + return socket_error_retval; + } + + if (level == custom_socket_option_level + && optname == enable_connection_aborted_option) + { + if (*optlen != sizeof(int)) + { + ec = asio::error::invalid_argument; + return socket_error_retval; + } + + *static_cast(optval) = (state & enable_connection_aborted) ? 1 : 0; + ec.assign(0, ec.category()); + return 0; + } + +#if defined(__BORLANDC__) + // Mysteriously, using the getsockopt and setsockopt functions directly with + // Borland C++ results in incorrect values being set and read. The bug can be + // worked around by using function addresses resolved with GetProcAddress. + if (HMODULE winsock_module = ::GetModuleHandleA("ws2_32")) + { + typedef int (WSAAPI *gso_t)(SOCKET, int, int, char*, int*); + if (gso_t gso = (gso_t)::GetProcAddress(winsock_module, "getsockopt")) + { + int tmp_optlen = static_cast(*optlen); + int result = gso(s, level, optname, + reinterpret_cast(optval), &tmp_optlen); + get_last_error(ec, result != 0); + *optlen = static_cast(tmp_optlen); + if (result != 0 && level == IPPROTO_IPV6 && optname == IPV6_V6ONLY + && ec.value() == WSAENOPROTOOPT && *optlen == sizeof(DWORD)) + { + // Dual-stack IPv4/v6 sockets, and the IPV6_V6ONLY socket option, are + // only supported on Windows Vista and later. To simplify program logic + // we will fake success of getting this option and specify that the + // value is non-zero (i.e. true). This corresponds to the behavior of + // IPv6 sockets on Windows platforms pre-Vista. + *static_cast(optval) = 1; + ec.assign(0, ec.category()); + } + return result; + } + } + ec = asio::error::fault; + return socket_error_retval; +#elif defined(ASIO_WINDOWS) || defined(__CYGWIN__) + int result = call_getsockopt(&msghdr::msg_namelen, + s, level, optname, optval, optlen); + get_last_error(ec, result != 0); + if (result != 0 && level == IPPROTO_IPV6 && optname == IPV6_V6ONLY + && ec.value() == WSAENOPROTOOPT && *optlen == sizeof(DWORD)) + { + // Dual-stack IPv4/v6 sockets, and the IPV6_V6ONLY socket option, are only + // supported on Windows Vista and later. To simplify program logic we will + // fake success of getting this option and specify that the value is + // non-zero (i.e. true). This corresponds to the behavior of IPv6 sockets + // on Windows platforms pre-Vista. + *static_cast(optval) = 1; + ec.assign(0, ec.category()); + } + return result; +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + int result = call_getsockopt(&msghdr::msg_namelen, + s, level, optname, optval, optlen); + get_last_error(ec, result != 0); +#if defined(__linux__) + if (result == 0 && level == SOL_SOCKET && *optlen == sizeof(int) + && (optname == SO_SNDBUF || optname == SO_RCVBUF)) + { + // On Linux, setting SO_SNDBUF or SO_RCVBUF to N actually causes the kernel + // to set the buffer size to N*2. Linux puts additional stuff into the + // buffers so that only about half is actually available to the application. + // The retrieved value is divided by 2 here to make it appear as though the + // correct value has been set. + *static_cast(optval) /= 2; + } +#endif // defined(__linux__) + return result; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +} + +template +inline int call_getpeername(SockLenType msghdr::*, + socket_type s, socket_addr_type* addr, std::size_t* addrlen) +{ + SockLenType tmp_addrlen = (SockLenType)*addrlen; + int result = ::getpeername(s, addr, &tmp_addrlen); + *addrlen = (std::size_t)tmp_addrlen; + return result; +} + +int getpeername(socket_type s, socket_addr_type* addr, + std::size_t* addrlen, bool cached, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return socket_error_retval; + } + +#if defined(ASIO_WINDOWS) && !defined(ASIO_WINDOWS_APP) \ + || defined(__CYGWIN__) + if (cached) + { + // Check if socket is still connected. + DWORD connect_time = 0; + size_t connect_time_len = sizeof(connect_time); + if (socket_ops::getsockopt(s, 0, SOL_SOCKET, SO_CONNECT_TIME, + &connect_time, &connect_time_len, ec) == socket_error_retval) + { + return socket_error_retval; + } + if (connect_time == 0xFFFFFFFF) + { + ec = asio::error::not_connected; + return socket_error_retval; + } + + // The cached value is still valid. + ec.assign(0, ec.category()); + return 0; + } +#else // defined(ASIO_WINDOWS) && !defined(ASIO_WINDOWS_APP) + // || defined(__CYGWIN__) + (void)cached; +#endif // defined(ASIO_WINDOWS) && !defined(ASIO_WINDOWS_APP) + // || defined(__CYGWIN__) + + int result = call_getpeername(&msghdr::msg_namelen, s, addr, addrlen); + get_last_error(ec, result != 0); + return result; +} + +template +inline int call_getsockname(SockLenType msghdr::*, + socket_type s, socket_addr_type* addr, std::size_t* addrlen) +{ + SockLenType tmp_addrlen = (SockLenType)*addrlen; + int result = ::getsockname(s, addr, &tmp_addrlen); + *addrlen = (std::size_t)tmp_addrlen; + return result; +} + +int getsockname(socket_type s, socket_addr_type* addr, + std::size_t* addrlen, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return socket_error_retval; + } + + int result = call_getsockname(&msghdr::msg_namelen, s, addr, addrlen); + get_last_error(ec, result != 0); + return result; +} + +int ioctl(socket_type s, state_type& state, int cmd, + ioctl_arg_type* arg, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return socket_error_retval; + } + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + int result = ::ioctlsocket(s, cmd, arg); +#elif defined(__MACH__) && defined(__APPLE__) \ + || defined(__NetBSD__) || defined(__FreeBSD__) || defined(__OpenBSD__) + int result = ::ioctl(s, static_cast(cmd), arg); +#else + int result = ::ioctl(s, cmd, arg); +#endif + get_last_error(ec, result < 0); + if (result >= 0) + { + // When updating the non-blocking mode we always perform the ioctl syscall, + // even if the flags would otherwise indicate that the socket is already in + // the correct state. This ensures that the underlying socket is put into + // the state that has been requested by the user. If the ioctl syscall was + // successful then we need to update the flags to match. + if (cmd == static_cast(FIONBIO)) + { + if (*arg) + { + state |= user_set_non_blocking; + } + else + { + // Clearing the non-blocking mode always overrides any internally-set + // non-blocking flag. Any subsequent asynchronous operations will need + // to re-enable non-blocking I/O. + state &= ~(user_set_non_blocking | internal_non_blocking); + } + } + } + + return result; +} + +int select(int nfds, fd_set* readfds, fd_set* writefds, + fd_set* exceptfds, timeval* timeout, asio::error_code& ec) +{ +#if defined(__EMSCRIPTEN__) + exceptfds = 0; +#endif // defined(__EMSCRIPTEN__) +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + if (!readfds && !writefds && !exceptfds && timeout) + { + DWORD milliseconds = timeout->tv_sec * 1000 + timeout->tv_usec / 1000; + if (milliseconds == 0) + milliseconds = 1; // Force context switch. + ::Sleep(milliseconds); + ec.assign(0, ec.category()); + return 0; + } + + // The select() call allows timeout values measured in microseconds, but the + // system clock (as wrapped by boost::posix_time::microsec_clock) typically + // has a resolution of 10 milliseconds. This can lead to a spinning select + // reactor, meaning increased CPU usage, when waiting for the earliest + // scheduled timeout if it's less than 10 milliseconds away. To avoid a tight + // spin we'll use a minimum timeout of 1 millisecond. + if (timeout && timeout->tv_sec == 0 + && timeout->tv_usec > 0 && timeout->tv_usec < 1000) + timeout->tv_usec = 1000; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +#if defined(__hpux) && defined(__SELECT) + timespec ts; + ts.tv_sec = timeout ? timeout->tv_sec : 0; + ts.tv_nsec = timeout ? timeout->tv_usec * 1000 : 0; + int result = ::pselect(nfds, readfds, + writefds, exceptfds, timeout ? &ts : 0, 0); +#else + int result = ::select(nfds, readfds, writefds, exceptfds, timeout); +#endif + get_last_error(ec, result < 0); + return result; +} + +int poll_read(socket_type s, state_type state, + int msec, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return socket_error_retval; + } + +#if defined(ASIO_WINDOWS) \ + || defined(__CYGWIN__) \ + || defined(__SYMBIAN32__) + fd_set fds; + FD_ZERO(&fds); + FD_SET(s, &fds); + timeval timeout_obj; + timeval* timeout; + if (state & user_set_non_blocking) + { + timeout_obj.tv_sec = 0; + timeout_obj.tv_usec = 0; + timeout = &timeout_obj; + } + else if (msec >= 0) + { + timeout_obj.tv_sec = msec / 1000; + timeout_obj.tv_usec = (msec % 1000) * 1000; + timeout = &timeout_obj; + } + else + timeout = 0; + int result = ::select(s + 1, &fds, 0, 0, timeout); + get_last_error(ec, result < 0); +#else // defined(ASIO_WINDOWS) + // || defined(__CYGWIN__) + // || defined(__SYMBIAN32__) + pollfd fds; + fds.fd = s; + fds.events = POLLIN; + fds.revents = 0; + int timeout = (state & user_set_non_blocking) ? 0 : msec; + int result = ::poll(&fds, 1, timeout); + get_last_error(ec, result < 0); +#endif // defined(ASIO_WINDOWS) + // || defined(__CYGWIN__) + // || defined(__SYMBIAN32__) + if (result == 0) + if (state & user_set_non_blocking) + ec = asio::error::would_block; + return result; +} + +int poll_write(socket_type s, state_type state, + int msec, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return socket_error_retval; + } + +#if defined(ASIO_WINDOWS) \ + || defined(__CYGWIN__) \ + || defined(__SYMBIAN32__) + fd_set fds; + FD_ZERO(&fds); + FD_SET(s, &fds); + timeval timeout_obj; + timeval* timeout; + if (state & user_set_non_blocking) + { + timeout_obj.tv_sec = 0; + timeout_obj.tv_usec = 0; + timeout = &timeout_obj; + } + else if (msec >= 0) + { + timeout_obj.tv_sec = msec / 1000; + timeout_obj.tv_usec = (msec % 1000) * 1000; + timeout = &timeout_obj; + } + else + timeout = 0; + int result = ::select(s + 1, 0, &fds, 0, timeout); + get_last_error(ec, result < 0); +#else // defined(ASIO_WINDOWS) + // || defined(__CYGWIN__) + // || defined(__SYMBIAN32__) + pollfd fds; + fds.fd = s; + fds.events = POLLOUT; + fds.revents = 0; + int timeout = (state & user_set_non_blocking) ? 0 : msec; + int result = ::poll(&fds, 1, timeout); + get_last_error(ec, result < 0); +#endif // defined(ASIO_WINDOWS) + // || defined(__CYGWIN__) + // || defined(__SYMBIAN32__) + if (result == 0) + if (state & user_set_non_blocking) + ec = asio::error::would_block; + return result; +} + +int poll_error(socket_type s, state_type state, + int msec, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return socket_error_retval; + } + +#if defined(ASIO_WINDOWS) \ + || defined(__CYGWIN__) \ + || defined(__SYMBIAN32__) + fd_set fds; + FD_ZERO(&fds); + FD_SET(s, &fds); + timeval timeout_obj; + timeval* timeout; + if (state & user_set_non_blocking) + { + timeout_obj.tv_sec = 0; + timeout_obj.tv_usec = 0; + timeout = &timeout_obj; + } + else if (msec >= 0) + { + timeout_obj.tv_sec = msec / 1000; + timeout_obj.tv_usec = (msec % 1000) * 1000; + timeout = &timeout_obj; + } + else + timeout = 0; + int result = ::select(s + 1, 0, 0, &fds, timeout); + get_last_error(ec, result < 0); +#else // defined(ASIO_WINDOWS) + // || defined(__CYGWIN__) + // || defined(__SYMBIAN32__) + pollfd fds; + fds.fd = s; + fds.events = POLLPRI | POLLERR | POLLHUP; + fds.revents = 0; + int timeout = (state & user_set_non_blocking) ? 0 : msec; + int result = ::poll(&fds, 1, timeout); + get_last_error(ec, result < 0); +#endif // defined(ASIO_WINDOWS) + // || defined(__CYGWIN__) + // || defined(__SYMBIAN32__) + if (result == 0) + if (state & user_set_non_blocking) + ec = asio::error::would_block; + return result; +} + +int poll_connect(socket_type s, int msec, asio::error_code& ec) +{ + if (s == invalid_socket) + { + ec = asio::error::bad_descriptor; + return socket_error_retval; + } + +#if defined(ASIO_WINDOWS) \ + || defined(__CYGWIN__) \ + || defined(__SYMBIAN32__) + fd_set write_fds; + FD_ZERO(&write_fds); + FD_SET(s, &write_fds); + fd_set except_fds; + FD_ZERO(&except_fds); + FD_SET(s, &except_fds); + timeval timeout_obj; + timeval* timeout; + if (msec >= 0) + { + timeout_obj.tv_sec = msec / 1000; + timeout_obj.tv_usec = (msec % 1000) * 1000; + timeout = &timeout_obj; + } + else + timeout = 0; + int result = ::select(s + 1, 0, &write_fds, &except_fds, timeout); + get_last_error(ec, result < 0); + return result; +#else // defined(ASIO_WINDOWS) + // || defined(__CYGWIN__) + // || defined(__SYMBIAN32__) + pollfd fds; + fds.fd = s; + fds.events = POLLOUT; + fds.revents = 0; + int result = ::poll(&fds, 1, msec); + get_last_error(ec, result < 0); + return result; +#endif // defined(ASIO_WINDOWS) + // || defined(__CYGWIN__) + // || defined(__SYMBIAN32__) +} + +#endif // !defined(ASIO_WINDOWS_RUNTIME) + +const char* inet_ntop(int af, const void* src, char* dest, size_t length, + unsigned long scope_id, asio::error_code& ec) +{ + clear_last_error(); +#if defined(ASIO_WINDOWS_RUNTIME) + using namespace std; // For sprintf. + const unsigned char* bytes = static_cast(src); + if (af == ASIO_OS_DEF(AF_INET)) + { + sprintf_s(dest, length, "%u.%u.%u.%u", + bytes[0], bytes[1], bytes[2], bytes[3]); + return dest; + } + else if (af == ASIO_OS_DEF(AF_INET6)) + { + size_t n = 0, b = 0, z = 0; + while (n < length && b < 16) + { + if (bytes[b] == 0 && bytes[b + 1] == 0 && z == 0) + { + do b += 2; while (b < 16 && bytes[b] == 0 && bytes[b + 1] == 0); + n += sprintf_s(dest + n, length - n, ":%s", b < 16 ? "" : ":"), ++z; + } + else + { + n += sprintf_s(dest + n, length - n, "%s%x", b ? ":" : "", + (static_cast(bytes[b]) << 8) | bytes[b + 1]); + b += 2; + } + } + if (scope_id) + n += sprintf_s(dest + n, length - n, "%%%lu", scope_id); + return dest; + } + else + { + ec = asio::error::address_family_not_supported; + return 0; + } +#elif defined(ASIO_WINDOWS) || defined(__CYGWIN__) + using namespace std; // For memcpy. + + if (af != ASIO_OS_DEF(AF_INET) && af != ASIO_OS_DEF(AF_INET6)) + { + ec = asio::error::address_family_not_supported; + return 0; + } + + union + { + socket_addr_type base; + sockaddr_storage_type storage; + sockaddr_in4_type v4; + sockaddr_in6_type v6; + } address; + DWORD address_length; + if (af == ASIO_OS_DEF(AF_INET)) + { + address_length = sizeof(sockaddr_in4_type); + address.v4.sin_family = ASIO_OS_DEF(AF_INET); + address.v4.sin_port = 0; + memcpy(&address.v4.sin_addr, src, sizeof(in4_addr_type)); + } + else // AF_INET6 + { + address_length = sizeof(sockaddr_in6_type); + address.v6.sin6_family = ASIO_OS_DEF(AF_INET6); + address.v6.sin6_port = 0; + address.v6.sin6_flowinfo = 0; + address.v6.sin6_scope_id = scope_id; + memcpy(&address.v6.sin6_addr, src, sizeof(in6_addr_type)); + } + + DWORD string_length = static_cast(length); +#if defined(BOOST_NO_ANSI_APIS) || (defined(_MSC_VER) && (_MSC_VER >= 1800)) + LPWSTR string_buffer = (LPWSTR)_alloca(length * sizeof(WCHAR)); + int result = ::WSAAddressToStringW(&address.base, + address_length, 0, string_buffer, &string_length); + get_last_error(ec, true); + ::WideCharToMultiByte(CP_ACP, 0, string_buffer, -1, + dest, static_cast(length), 0, 0); +#else + int result = ::WSAAddressToStringA(&address.base, + address_length, 0, dest, &string_length); + get_last_error(ec, true); +#endif + + // Windows may set error code on success. + if (result != socket_error_retval) + ec.assign(0, ec.category()); + + // Windows may not set an error code on failure. + else if (result == socket_error_retval && !ec) + ec = asio::error::invalid_argument; + + return result == socket_error_retval ? 0 : dest; +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + const char* result = ::inet_ntop(af, src, dest, static_cast(length)); + get_last_error(ec, true); + if (result == 0 && !ec) + ec = asio::error::invalid_argument; + if (result != 0 && af == ASIO_OS_DEF(AF_INET6) && scope_id != 0) + { + using namespace std; // For strcat and sprintf. + char if_name[(IF_NAMESIZE > 21 ? IF_NAMESIZE : 21) + 1] = "%"; + const in6_addr_type* ipv6_address = static_cast(src); + bool is_link_local = ((ipv6_address->s6_addr[0] == 0xfe) + && ((ipv6_address->s6_addr[1] & 0xc0) == 0x80)); + bool is_multicast_link_local = ((ipv6_address->s6_addr[0] == 0xff) + && ((ipv6_address->s6_addr[1] & 0x0f) == 0x02)); + if ((!is_link_local && !is_multicast_link_local) + || if_indextoname(static_cast(scope_id), if_name + 1) == 0) + sprintf(if_name + 1, "%lu", scope_id); + strcat(dest, if_name); + } + return result; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +} + +int inet_pton(int af, const char* src, void* dest, + unsigned long* scope_id, asio::error_code& ec) +{ + clear_last_error(); +#if defined(ASIO_WINDOWS_RUNTIME) + using namespace std; // For sscanf. + unsigned char* bytes = static_cast(dest); + if (af == ASIO_OS_DEF(AF_INET)) + { + unsigned int b0, b1, b2, b3; + if (sscanf_s(src, "%u.%u.%u.%u", &b0, &b1, &b2, &b3) != 4) + { + ec = asio::error::invalid_argument; + return -1; + } + if (b0 > 255 || b1 > 255 || b2 > 255 || b3 > 255) + { + ec = asio::error::invalid_argument; + return -1; + } + bytes[0] = static_cast(b0); + bytes[1] = static_cast(b1); + bytes[2] = static_cast(b2); + bytes[3] = static_cast(b3); + ec.assign(), ec.category()); + return 1; + } + else if (af == ASIO_OS_DEF(AF_INET6)) + { + unsigned char* bytes = static_cast(dest); + std::memset(bytes, 0, 16); + unsigned char back_bytes[16] = { 0 }; + int num_front_bytes = 0, num_back_bytes = 0; + const char* p = src; + + enum { fword, fcolon, bword, scope, done } state = fword; + unsigned long current_word = 0; + while (state != done) + { + if (current_word > 0xFFFF) + { + ec = asio::error::invalid_argument; + return -1; + } + + switch (state) + { + case fword: + if (*p >= '0' && *p <= '9') + current_word = current_word * 16 + *p++ - '0'; + else if (*p >= 'a' && *p <= 'f') + current_word = current_word * 16 + *p++ - 'a' + 10; + else if (*p >= 'A' && *p <= 'F') + current_word = current_word * 16 + *p++ - 'A' + 10; + else + { + if (num_front_bytes == 16) + { + ec = asio::error::invalid_argument; + return -1; + } + + bytes[num_front_bytes++] = (current_word >> 8) & 0xFF; + bytes[num_front_bytes++] = current_word & 0xFF; + current_word = 0; + + if (*p == ':') + state = fcolon, ++p; + else if (*p == '%') + state = scope, ++p; + else if (*p == 0) + state = done; + else + { + ec = asio::error::invalid_argument; + return -1; + } + } + break; + + case fcolon: + if (*p == ':') + state = bword, ++p; + else + state = fword; + break; + + case bword: + if (*p >= '0' && *p <= '9') + current_word = current_word * 16 + *p++ - '0'; + else if (*p >= 'a' && *p <= 'f') + current_word = current_word * 16 + *p++ - 'a' + 10; + else if (*p >= 'A' && *p <= 'F') + current_word = current_word * 16 + *p++ - 'A' + 10; + else + { + if (num_front_bytes + num_back_bytes == 16) + { + ec = asio::error::invalid_argument; + return -1; + } + + back_bytes[num_back_bytes++] = (current_word >> 8) & 0xFF; + back_bytes[num_back_bytes++] = current_word & 0xFF; + current_word = 0; + + if (*p == ':') + state = bword, ++p; + else if (*p == '%') + state = scope, ++p; + else if (*p == 0) + state = done; + else + { + ec = asio::error::invalid_argument; + return -1; + } + } + break; + + case scope: + if (*p >= '0' && *p <= '9') + current_word = current_word * 10 + *p++ - '0'; + else if (*p == 0) + *scope_id = current_word, state = done; + else + { + ec = asio::error::invalid_argument; + return -1; + } + break; + + default: + break; + } + } + + for (int i = 0; i < num_back_bytes; ++i) + bytes[16 - num_back_bytes + i] = back_bytes[i]; + + ec.assign(0, ec.category()); + return 1; + } + else + { + ec = asio::error::address_family_not_supported; + return -1; + } +#elif defined(ASIO_WINDOWS) || defined(__CYGWIN__) + using namespace std; // For memcpy and strcmp. + + if (af != ASIO_OS_DEF(AF_INET) && af != ASIO_OS_DEF(AF_INET6)) + { + ec = asio::error::address_family_not_supported; + return -1; + } + + union + { + socket_addr_type base; + sockaddr_storage_type storage; + sockaddr_in4_type v4; + sockaddr_in6_type v6; + } address; + int address_length = sizeof(sockaddr_storage_type); +#if defined(BOOST_NO_ANSI_APIS) || (defined(_MSC_VER) && (_MSC_VER >= 1800)) + int num_wide_chars = static_cast(strlen(src)) + 1; + LPWSTR wide_buffer = (LPWSTR)_alloca(num_wide_chars * sizeof(WCHAR)); + ::MultiByteToWideChar(CP_ACP, 0, src, -1, wide_buffer, num_wide_chars); + int result = ::WSAStringToAddressW(wide_buffer, + af, 0, &address.base, &address_length); + get_last_error(ec, true); +#else + int result = ::WSAStringToAddressA(const_cast(src), + af, 0, &address.base, &address_length); + get_last_error(ec, true); +#endif + + if (af == ASIO_OS_DEF(AF_INET)) + { + if (result != socket_error_retval) + { + memcpy(dest, &address.v4.sin_addr, sizeof(in4_addr_type)); + ec.assign(0, ec.category()); + } + else if (strcmp(src, "255.255.255.255") == 0) + { + static_cast(dest)->s_addr = INADDR_NONE; + ec.assign(0, ec.category()); + } + } + else // AF_INET6 + { + if (result != socket_error_retval) + { + memcpy(dest, &address.v6.sin6_addr, sizeof(in6_addr_type)); + if (scope_id) + *scope_id = address.v6.sin6_scope_id; + ec.assign(0, ec.category()); + } + } + + // Windows may not set an error code on failure. + if (result == socket_error_retval && !ec) + ec = asio::error::invalid_argument; + + if (result != socket_error_retval) + ec.assign(0, ec.category()); + + return result == socket_error_retval ? -1 : 1; +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + using namespace std; // For strchr, memcpy and atoi. + + // On some platforms, inet_pton fails if an address string contains a scope + // id. Detect and remove the scope id before passing the string to inet_pton. + const bool is_v6 = (af == ASIO_OS_DEF(AF_INET6)); + const char* if_name = is_v6 ? strchr(src, '%') : 0; + char src_buf[max_addr_v6_str_len + 1]; + const char* src_ptr = src; + if (if_name != 0) + { + if (if_name - src > max_addr_v6_str_len) + { + ec = asio::error::invalid_argument; + return 0; + } + memcpy(src_buf, src, if_name - src); + src_buf[if_name - src] = 0; + src_ptr = src_buf; + } + + int result = ::inet_pton(af, src_ptr, dest); + get_last_error(ec, true); + if (result <= 0 && !ec) + ec = asio::error::invalid_argument; + if (result > 0 && is_v6 && scope_id) + { + using namespace std; // For strchr and atoi. + *scope_id = 0; + if (if_name != 0) + { + in6_addr_type* ipv6_address = static_cast(dest); + bool is_link_local = ((ipv6_address->s6_addr[0] == 0xfe) + && ((ipv6_address->s6_addr[1] & 0xc0) == 0x80)); + bool is_multicast_link_local = ((ipv6_address->s6_addr[0] == 0xff) + && ((ipv6_address->s6_addr[1] & 0x0f) == 0x02)); + if (is_link_local || is_multicast_link_local) + *scope_id = if_nametoindex(if_name + 1); + if (*scope_id == 0) + *scope_id = atoi(if_name + 1); + } + } + return result; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +} + +int gethostname(char* name, int namelen, asio::error_code& ec) +{ +#if defined(ASIO_WINDOWS_RUNTIME) + try + { + using namespace Windows::Foundation::Collections; + using namespace Windows::Networking; + using namespace Windows::Networking::Connectivity; + IVectorView^ hostnames = NetworkInformation::GetHostNames(); + for (unsigned i = 0; i < hostnames->Size; ++i) + { + HostName^ hostname = hostnames->GetAt(i); + if (hostname->Type == HostNameType::DomainName) + { + std::wstring_convert> converter; + std::string raw_name = converter.to_bytes(hostname->RawName->Data()); + if (namelen > 0 && raw_name.size() < static_cast(namelen)) + { + strcpy_s(name, namelen, raw_name.c_str()); + return 0; + } + } + } + return -1; + } + catch (Platform::Exception^ e) + { + ec = asio::error_code(e->HResult, + asio::system_category()); + return -1; + } +#else // defined(ASIO_WINDOWS_RUNTIME) + int result = ::gethostname(name, namelen); + get_last_error(ec, result != 0); + return result; +#endif // defined(ASIO_WINDOWS_RUNTIME) +} + +#if !defined(ASIO_WINDOWS_RUNTIME) + +#if !defined(ASIO_HAS_GETADDRINFO) + +// The following functions are only needed for emulation of getaddrinfo and +// getnameinfo. + +inline asio::error_code translate_netdb_error(int error) +{ + switch (error) + { + case 0: + return asio::error_code(); + case HOST_NOT_FOUND: + return asio::error::host_not_found; + case TRY_AGAIN: + return asio::error::host_not_found_try_again; + case NO_RECOVERY: + return asio::error::no_recovery; + case NO_DATA: + return asio::error::no_data; + default: + ASIO_ASSERT(false); + return asio::error::invalid_argument; + } +} + +inline hostent* gethostbyaddr(const char* addr, int length, int af, + hostent* result, char* buffer, int buflength, asio::error_code& ec) +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + (void)(buffer); + (void)(buflength); + hostent* retval = ::gethostbyaddr(addr, length, af); + get_last_error(ec, !retval); + if (!retval) + return 0; + *result = *retval; + return retval; +#elif defined(__sun) || defined(__QNX__) + int error = 0; + hostent* retval = ::gethostbyaddr_r(addr, length, + af, result, buffer, buflength, &error); + get_last_error(ec, !retval); + if (error) + ec = translate_netdb_error(error); + return retval; +#elif defined(__MACH__) && defined(__APPLE__) + (void)(buffer); + (void)(buflength); + int error = 0; + hostent* retval = ::getipnodebyaddr(addr, length, af, &error); + get_last_error(ec, !retval); + if (error) + ec = translate_netdb_error(error); + if (!retval) + return 0; + *result = *retval; + return retval; +#else + hostent* retval = 0; + int error = 0; + clear_last_error(); + ::gethostbyaddr_r(addr, length, af, result, + buffer, buflength, &retval, &error); + get_last_error(ec, true); + if (error) + ec = translate_netdb_error(error); + return retval; +#endif +} + +inline hostent* gethostbyname(const char* name, int af, struct hostent* result, + char* buffer, int buflength, int ai_flags, asio::error_code& ec) +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + (void)(buffer); + (void)(buflength); + (void)(ai_flags); + if (af != ASIO_OS_DEF(AF_INET)) + { + ec = asio::error::address_family_not_supported; + return 0; + } + hostent* retval = ::gethostbyname(name); + get_last_error(ec, !retval); + if (!retval) + return 0; + *result = *retval; + return result; +#elif defined(__sun) || defined(__QNX__) + (void)(ai_flags); + if (af != ASIO_OS_DEF(AF_INET)) + { + ec = asio::error::address_family_not_supported; + return 0; + } + int error = 0; + hostent* retval = ::gethostbyname_r(name, result, buffer, buflength, &error); + get_last_error(ec, !retval); + if (error) + ec = translate_netdb_error(error); + return retval; +#elif defined(__MACH__) && defined(__APPLE__) + (void)(buffer); + (void)(buflength); + int error = 0; + hostent* retval = ::getipnodebyname(name, af, ai_flags, &error); + get_last_error(ec, !retval); + if (error) + ec = translate_netdb_error(error); + if (!retval) + return 0; + *result = *retval; + return retval; +#else + (void)(ai_flags); + if (af != ASIO_OS_DEF(AF_INET)) + { + ec = asio::error::address_family_not_supported; + return 0; + } + hostent* retval = 0; + int error = 0; + clear_last_error(); + ::gethostbyname_r(name, result, buffer, buflength, &retval, &error); + get_last_error(ec, true); + if (error) + ec = translate_netdb_error(error); + return retval; +#endif +} + +inline void freehostent(hostent* h) +{ +#if defined(__MACH__) && defined(__APPLE__) + if (h) + ::freehostent(h); +#else + (void)(h); +#endif +} + +// Emulation of getaddrinfo based on implementation in: +// Stevens, W. R., UNIX Network Programming Vol. 1, 2nd Ed., Prentice-Hall 1998. + +struct gai_search +{ + const char* host; + int family; +}; + +inline int gai_nsearch(const char* host, + const addrinfo_type* hints, gai_search (&search)[2]) +{ + int search_count = 0; + if (host == 0 || host[0] == '\0') + { + if (hints->ai_flags & AI_PASSIVE) + { + // No host and AI_PASSIVE implies wildcard bind. + switch (hints->ai_family) + { + case ASIO_OS_DEF(AF_INET): + search[search_count].host = "0.0.0.0"; + search[search_count].family = ASIO_OS_DEF(AF_INET); + ++search_count; + break; + case ASIO_OS_DEF(AF_INET6): + search[search_count].host = "0::0"; + search[search_count].family = ASIO_OS_DEF(AF_INET6); + ++search_count; + break; + case ASIO_OS_DEF(AF_UNSPEC): + search[search_count].host = "0::0"; + search[search_count].family = ASIO_OS_DEF(AF_INET6); + ++search_count; + search[search_count].host = "0.0.0.0"; + search[search_count].family = ASIO_OS_DEF(AF_INET); + ++search_count; + break; + default: + break; + } + } + else + { + // No host and not AI_PASSIVE means connect to local host. + switch (hints->ai_family) + { + case ASIO_OS_DEF(AF_INET): + search[search_count].host = "localhost"; + search[search_count].family = ASIO_OS_DEF(AF_INET); + ++search_count; + break; + case ASIO_OS_DEF(AF_INET6): + search[search_count].host = "localhost"; + search[search_count].family = ASIO_OS_DEF(AF_INET6); + ++search_count; + break; + case ASIO_OS_DEF(AF_UNSPEC): + search[search_count].host = "localhost"; + search[search_count].family = ASIO_OS_DEF(AF_INET6); + ++search_count; + search[search_count].host = "localhost"; + search[search_count].family = ASIO_OS_DEF(AF_INET); + ++search_count; + break; + default: + break; + } + } + } + else + { + // Host is specified. + switch (hints->ai_family) + { + case ASIO_OS_DEF(AF_INET): + search[search_count].host = host; + search[search_count].family = ASIO_OS_DEF(AF_INET); + ++search_count; + break; + case ASIO_OS_DEF(AF_INET6): + search[search_count].host = host; + search[search_count].family = ASIO_OS_DEF(AF_INET6); + ++search_count; + break; + case ASIO_OS_DEF(AF_UNSPEC): + search[search_count].host = host; + search[search_count].family = ASIO_OS_DEF(AF_INET6); + ++search_count; + search[search_count].host = host; + search[search_count].family = ASIO_OS_DEF(AF_INET); + ++search_count; + break; + default: + break; + } + } + return search_count; +} + +template +inline T* gai_alloc(std::size_t size = sizeof(T)) +{ + using namespace std; + T* p = static_cast(::operator new(size, std::nothrow)); + if (p) + memset(p, 0, size); + return p; +} + +inline void gai_free(void* p) +{ + ::operator delete(p); +} + +inline void gai_strcpy(char* target, const char* source, std::size_t max_size) +{ + using namespace std; +#if defined(ASIO_HAS_SECURE_RTL) + strcpy_s(target, max_size, source); +#else // defined(ASIO_HAS_SECURE_RTL) + *target = 0; + if (max_size > 0) + strncat(target, source, max_size - 1); +#endif // defined(ASIO_HAS_SECURE_RTL) +} + +enum { gai_clone_flag = 1 << 30 }; + +inline int gai_aistruct(addrinfo_type*** next, const addrinfo_type* hints, + const void* addr, int family) +{ + using namespace std; + + addrinfo_type* ai = gai_alloc(); + if (ai == 0) + return EAI_MEMORY; + + ai->ai_next = 0; + **next = ai; + *next = &ai->ai_next; + + ai->ai_canonname = 0; + ai->ai_socktype = hints->ai_socktype; + if (ai->ai_socktype == 0) + ai->ai_flags |= gai_clone_flag; + ai->ai_protocol = hints->ai_protocol; + ai->ai_family = family; + + switch (ai->ai_family) + { + case ASIO_OS_DEF(AF_INET): + { + sockaddr_in4_type* sinptr = gai_alloc(); + if (sinptr == 0) + return EAI_MEMORY; + sinptr->sin_family = ASIO_OS_DEF(AF_INET); + memcpy(&sinptr->sin_addr, addr, sizeof(in4_addr_type)); + ai->ai_addr = reinterpret_cast(sinptr); + ai->ai_addrlen = sizeof(sockaddr_in4_type); + break; + } + case ASIO_OS_DEF(AF_INET6): + { + sockaddr_in6_type* sin6ptr = gai_alloc(); + if (sin6ptr == 0) + return EAI_MEMORY; + sin6ptr->sin6_family = ASIO_OS_DEF(AF_INET6); + memcpy(&sin6ptr->sin6_addr, addr, sizeof(in6_addr_type)); + ai->ai_addr = reinterpret_cast(sin6ptr); + ai->ai_addrlen = sizeof(sockaddr_in6_type); + break; + } + default: + break; + } + + return 0; +} + +inline addrinfo_type* gai_clone(addrinfo_type* ai) +{ + using namespace std; + + addrinfo_type* new_ai = gai_alloc(); + if (new_ai == 0) + return new_ai; + + new_ai->ai_next = ai->ai_next; + ai->ai_next = new_ai; + + new_ai->ai_flags = 0; + new_ai->ai_family = ai->ai_family; + new_ai->ai_socktype = ai->ai_socktype; + new_ai->ai_protocol = ai->ai_protocol; + new_ai->ai_canonname = 0; + new_ai->ai_addrlen = ai->ai_addrlen; + new_ai->ai_addr = gai_alloc(ai->ai_addrlen); + memcpy(new_ai->ai_addr, ai->ai_addr, ai->ai_addrlen); + + return new_ai; +} + +inline int gai_port(addrinfo_type* aihead, int port, int socktype) +{ + int num_found = 0; + + for (addrinfo_type* ai = aihead; ai; ai = ai->ai_next) + { + if (ai->ai_flags & gai_clone_flag) + { + if (ai->ai_socktype != 0) + { + ai = gai_clone(ai); + if (ai == 0) + return -1; + // ai now points to newly cloned entry. + } + } + else if (ai->ai_socktype != socktype) + { + // Ignore if mismatch on socket type. + continue; + } + + ai->ai_socktype = socktype; + + switch (ai->ai_family) + { + case ASIO_OS_DEF(AF_INET): + { + sockaddr_in4_type* sinptr = + reinterpret_cast(ai->ai_addr); + sinptr->sin_port = port; + ++num_found; + break; + } + case ASIO_OS_DEF(AF_INET6): + { + sockaddr_in6_type* sin6ptr = + reinterpret_cast(ai->ai_addr); + sin6ptr->sin6_port = port; + ++num_found; + break; + } + default: + break; + } + } + + return num_found; +} + +inline int gai_serv(addrinfo_type* aihead, + const addrinfo_type* hints, const char* serv) +{ + using namespace std; + + int num_found = 0; + + if ( +#if defined(AI_NUMERICSERV) + (hints->ai_flags & AI_NUMERICSERV) || +#endif + isdigit(static_cast(serv[0]))) + { + int port = htons(atoi(serv)); + if (hints->ai_socktype) + { + // Caller specifies socket type. + int rc = gai_port(aihead, port, hints->ai_socktype); + if (rc < 0) + return EAI_MEMORY; + num_found += rc; + } + else + { + // Caller does not specify socket type. + int rc = gai_port(aihead, port, SOCK_STREAM); + if (rc < 0) + return EAI_MEMORY; + num_found += rc; + rc = gai_port(aihead, port, SOCK_DGRAM); + if (rc < 0) + return EAI_MEMORY; + num_found += rc; + } + } + else + { + // Try service name with TCP first, then UDP. + if (hints->ai_socktype == 0 || hints->ai_socktype == SOCK_STREAM) + { + servent* sptr = getservbyname(serv, "tcp"); + if (sptr != 0) + { + int rc = gai_port(aihead, sptr->s_port, SOCK_STREAM); + if (rc < 0) + return EAI_MEMORY; + num_found += rc; + } + } + if (hints->ai_socktype == 0 || hints->ai_socktype == SOCK_DGRAM) + { + servent* sptr = getservbyname(serv, "udp"); + if (sptr != 0) + { + int rc = gai_port(aihead, sptr->s_port, SOCK_DGRAM); + if (rc < 0) + return EAI_MEMORY; + num_found += rc; + } + } + } + + if (num_found == 0) + { + if (hints->ai_socktype == 0) + { + // All calls to getservbyname() failed. + return EAI_NONAME; + } + else + { + // Service not supported for socket type. + return EAI_SERVICE; + } + } + + return 0; +} + +inline int gai_echeck(const char* host, const char* service, + int flags, int family, int socktype, int protocol) +{ + (void)(flags); + (void)(protocol); + + // Host or service must be specified. + if (host == 0 || host[0] == '\0') + if (service == 0 || service[0] == '\0') + return EAI_NONAME; + + // Check combination of family and socket type. + switch (family) + { + case ASIO_OS_DEF(AF_UNSPEC): + break; + case ASIO_OS_DEF(AF_INET): + case ASIO_OS_DEF(AF_INET6): + if (service != 0 && service[0] != '\0') + if (socktype != 0 && socktype != SOCK_STREAM && socktype != SOCK_DGRAM) + return EAI_SOCKTYPE; + break; + default: + return EAI_FAMILY; + } + + return 0; +} + +inline void freeaddrinfo_emulation(addrinfo_type* aihead) +{ + addrinfo_type* ai = aihead; + while (ai) + { + gai_free(ai->ai_addr); + gai_free(ai->ai_canonname); + addrinfo_type* ainext = ai->ai_next; + gai_free(ai); + ai = ainext; + } +} + +inline int getaddrinfo_emulation(const char* host, const char* service, + const addrinfo_type* hintsp, addrinfo_type** result) +{ + // Set up linked list of addrinfo structures. + addrinfo_type* aihead = 0; + addrinfo_type** ainext = &aihead; + char* canon = 0; + + // Supply default hints if not specified by caller. + addrinfo_type hints = addrinfo_type(); + hints.ai_family = ASIO_OS_DEF(AF_UNSPEC); + if (hintsp) + hints = *hintsp; + + // If the resolution is not specifically for AF_INET6, remove the AI_V4MAPPED + // and AI_ALL flags. +#if defined(AI_V4MAPPED) + if (hints.ai_family != ASIO_OS_DEF(AF_INET6)) + hints.ai_flags &= ~AI_V4MAPPED; +#endif +#if defined(AI_ALL) + if (hints.ai_family != ASIO_OS_DEF(AF_INET6)) + hints.ai_flags &= ~AI_ALL; +#endif + + // Basic error checking. + int rc = gai_echeck(host, service, hints.ai_flags, hints.ai_family, + hints.ai_socktype, hints.ai_protocol); + if (rc != 0) + { + freeaddrinfo_emulation(aihead); + return rc; + } + + gai_search search[2]; + int search_count = gai_nsearch(host, &hints, search); + for (gai_search* sptr = search; sptr < search + search_count; ++sptr) + { + // Check for IPv4 dotted decimal string. + in4_addr_type inaddr; + asio::error_code ec; + if (socket_ops::inet_pton(ASIO_OS_DEF(AF_INET), + sptr->host, &inaddr, 0, ec) == 1) + { + if (hints.ai_family != ASIO_OS_DEF(AF_UNSPEC) + && hints.ai_family != ASIO_OS_DEF(AF_INET)) + { + freeaddrinfo_emulation(aihead); + gai_free(canon); + return EAI_FAMILY; + } + if (sptr->family == ASIO_OS_DEF(AF_INET)) + { + rc = gai_aistruct(&ainext, &hints, &inaddr, ASIO_OS_DEF(AF_INET)); + if (rc != 0) + { + freeaddrinfo_emulation(aihead); + gai_free(canon); + return rc; + } + } + continue; + } + + // Check for IPv6 hex string. + in6_addr_type in6addr; + if (socket_ops::inet_pton(ASIO_OS_DEF(AF_INET6), + sptr->host, &in6addr, 0, ec) == 1) + { + if (hints.ai_family != ASIO_OS_DEF(AF_UNSPEC) + && hints.ai_family != ASIO_OS_DEF(AF_INET6)) + { + freeaddrinfo_emulation(aihead); + gai_free(canon); + return EAI_FAMILY; + } + if (sptr->family == ASIO_OS_DEF(AF_INET6)) + { + rc = gai_aistruct(&ainext, &hints, &in6addr, + ASIO_OS_DEF(AF_INET6)); + if (rc != 0) + { + freeaddrinfo_emulation(aihead); + gai_free(canon); + return rc; + } + } + continue; + } + + // Look up hostname. + hostent hent; + char hbuf[8192] = ""; + hostent* hptr = socket_ops::gethostbyname(sptr->host, + sptr->family, &hent, hbuf, sizeof(hbuf), hints.ai_flags, ec); + if (hptr == 0) + { + if (search_count == 2) + { + // Failure is OK if there are multiple searches. + continue; + } + freeaddrinfo_emulation(aihead); + gai_free(canon); + if (ec == asio::error::host_not_found) + return EAI_NONAME; + if (ec == asio::error::host_not_found_try_again) + return EAI_AGAIN; + if (ec == asio::error::no_recovery) + return EAI_FAIL; + if (ec == asio::error::no_data) + return EAI_NONAME; + return EAI_NONAME; + } + + // Check for address family mismatch if one was specified. + if (hints.ai_family != ASIO_OS_DEF(AF_UNSPEC) + && hints.ai_family != hptr->h_addrtype) + { + freeaddrinfo_emulation(aihead); + gai_free(canon); + socket_ops::freehostent(hptr); + return EAI_FAMILY; + } + + // Save canonical name first time. + if (host != 0 && host[0] != '\0' && hptr->h_name && hptr->h_name[0] + && (hints.ai_flags & AI_CANONNAME) && canon == 0) + { + std::size_t canon_len = strlen(hptr->h_name) + 1; + canon = gai_alloc(canon_len); + if (canon == 0) + { + freeaddrinfo_emulation(aihead); + socket_ops::freehostent(hptr); + return EAI_MEMORY; + } + gai_strcpy(canon, hptr->h_name, canon_len); + } + + // Create an addrinfo structure for each returned address. + for (char** ap = hptr->h_addr_list; *ap; ++ap) + { + rc = gai_aistruct(&ainext, &hints, *ap, hptr->h_addrtype); + if (rc != 0) + { + freeaddrinfo_emulation(aihead); + gai_free(canon); + socket_ops::freehostent(hptr); + return EAI_FAMILY; + } + } + + socket_ops::freehostent(hptr); + } + + // Check if we found anything. + if (aihead == 0) + { + gai_free(canon); + return EAI_NONAME; + } + + // Return canonical name in first entry. + if (host != 0 && host[0] != '\0' && (hints.ai_flags & AI_CANONNAME)) + { + if (canon) + { + aihead->ai_canonname = canon; + canon = 0; + } + else + { + std::size_t canonname_len = strlen(search[0].host) + 1; + aihead->ai_canonname = gai_alloc(canonname_len); + if (aihead->ai_canonname == 0) + { + freeaddrinfo_emulation(aihead); + return EAI_MEMORY; + } + gai_strcpy(aihead->ai_canonname, search[0].host, canonname_len); + } + } + gai_free(canon); + + // Process the service name. + if (service != 0 && service[0] != '\0') + { + rc = gai_serv(aihead, &hints, service); + if (rc != 0) + { + freeaddrinfo_emulation(aihead); + return rc; + } + } + + // Return result to caller. + *result = aihead; + return 0; +} + +inline asio::error_code getnameinfo_emulation( + const socket_addr_type* sa, std::size_t salen, char* host, + std::size_t hostlen, char* serv, std::size_t servlen, int flags, + asio::error_code& ec) +{ + using namespace std; + + const char* addr; + size_t addr_len; + unsigned short port; + switch (sa->sa_family) + { + case ASIO_OS_DEF(AF_INET): + if (salen != sizeof(sockaddr_in4_type)) + { + return ec = asio::error::invalid_argument; + } + addr = reinterpret_cast( + &reinterpret_cast(sa)->sin_addr); + addr_len = sizeof(in4_addr_type); + port = reinterpret_cast(sa)->sin_port; + break; + case ASIO_OS_DEF(AF_INET6): + if (salen != sizeof(sockaddr_in6_type)) + { + return ec = asio::error::invalid_argument; + } + addr = reinterpret_cast( + &reinterpret_cast(sa)->sin6_addr); + addr_len = sizeof(in6_addr_type); + port = reinterpret_cast(sa)->sin6_port; + break; + default: + return ec = asio::error::address_family_not_supported; + } + + if (host && hostlen > 0) + { + if (flags & NI_NUMERICHOST) + { + if (socket_ops::inet_ntop(sa->sa_family, addr, host, hostlen, 0, ec) == 0) + { + return ec; + } + } + else + { + hostent hent; + char hbuf[8192] = ""; + hostent* hptr = socket_ops::gethostbyaddr(addr, + static_cast(addr_len), sa->sa_family, + &hent, hbuf, sizeof(hbuf), ec); + if (hptr && hptr->h_name && hptr->h_name[0] != '\0') + { + if (flags & NI_NOFQDN) + { + char* dot = strchr(hptr->h_name, '.'); + if (dot) + { + *dot = 0; + } + } + gai_strcpy(host, hptr->h_name, hostlen); + socket_ops::freehostent(hptr); + } + else + { + socket_ops::freehostent(hptr); + if (flags & NI_NAMEREQD) + { + return ec = asio::error::host_not_found; + } + if (socket_ops::inet_ntop(sa->sa_family, + addr, host, hostlen, 0, ec) == 0) + { + return ec; + } + } + } + } + + if (serv && servlen > 0) + { + if (flags & NI_NUMERICSERV) + { + if (servlen < 6) + { + return ec = asio::error::no_buffer_space; + } +#if defined(ASIO_HAS_SECURE_RTL) + sprintf_s(serv, servlen, "%u", ntohs(port)); +#else // defined(ASIO_HAS_SECURE_RTL) + sprintf(serv, "%u", ntohs(port)); +#endif // defined(ASIO_HAS_SECURE_RTL) + } + else + { +#if defined(ASIO_HAS_PTHREADS) + static ::pthread_mutex_t mutex = PTHREAD_MUTEX_INITIALIZER; + ::pthread_mutex_lock(&mutex); +#endif // defined(ASIO_HAS_PTHREADS) + servent* sptr = ::getservbyport(port, (flags & NI_DGRAM) ? "udp" : 0); + if (sptr && sptr->s_name && sptr->s_name[0] != '\0') + { + gai_strcpy(serv, sptr->s_name, servlen); + } + else + { + if (servlen < 6) + { + return ec = asio::error::no_buffer_space; + } +#if defined(ASIO_HAS_SECURE_RTL) + sprintf_s(serv, servlen, "%u", ntohs(port)); +#else // defined(ASIO_HAS_SECURE_RTL) + sprintf(serv, "%u", ntohs(port)); +#endif // defined(ASIO_HAS_SECURE_RTL) + } +#if defined(ASIO_HAS_PTHREADS) + ::pthread_mutex_unlock(&mutex); +#endif // defined(ASIO_HAS_PTHREADS) + } + } + + ec.assign(0, ec.category()); + return ec; +} + +#endif // !defined(ASIO_HAS_GETADDRINFO) + +inline asio::error_code translate_addrinfo_error(int error) +{ + switch (error) + { + case 0: + return asio::error_code(); + case EAI_AGAIN: + return asio::error::host_not_found_try_again; + case EAI_BADFLAGS: + return asio::error::invalid_argument; + case EAI_FAIL: + return asio::error::no_recovery; + case EAI_FAMILY: + return asio::error::address_family_not_supported; + case EAI_MEMORY: + return asio::error::no_memory; + case EAI_NONAME: +#if defined(EAI_ADDRFAMILY) + case EAI_ADDRFAMILY: +#endif +#if defined(EAI_NODATA) && (EAI_NODATA != EAI_NONAME) + case EAI_NODATA: +#endif + return asio::error::host_not_found; + case EAI_SERVICE: + return asio::error::service_not_found; + case EAI_SOCKTYPE: + return asio::error::socket_type_not_supported; + default: // Possibly the non-portable EAI_SYSTEM. +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + return asio::error_code( + WSAGetLastError(), asio::error::get_system_category()); +#else + return asio::error_code( + errno, asio::error::get_system_category()); +#endif + } +} + +asio::error_code getaddrinfo(const char* host, + const char* service, const addrinfo_type& hints, + addrinfo_type** result, asio::error_code& ec) +{ + host = (host && *host) ? host : 0; + service = (service && *service) ? service : 0; + clear_last_error(); +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) +# if defined(ASIO_HAS_GETADDRINFO) + // Building for Windows XP, Windows Server 2003, or later. + int error = ::getaddrinfo(host, service, &hints, result); + return ec = translate_addrinfo_error(error); +# else + // Building for Windows 2000 or earlier. + typedef int (WSAAPI *gai_t)(const char*, + const char*, const addrinfo_type*, addrinfo_type**); + if (HMODULE winsock_module = ::GetModuleHandleA("ws2_32")) + { + if (gai_t gai = (gai_t)::GetProcAddress(winsock_module, "getaddrinfo")) + { + int error = gai(host, service, &hints, result); + return ec = translate_addrinfo_error(error); + } + } + int error = getaddrinfo_emulation(host, service, &hints, result); + return ec = translate_addrinfo_error(error); +# endif +#elif !defined(ASIO_HAS_GETADDRINFO) + int error = getaddrinfo_emulation(host, service, &hints, result); + return ec = translate_addrinfo_error(error); +#else + int error = ::getaddrinfo(host, service, &hints, result); +#if defined(__MACH__) && defined(__APPLE__) + using namespace std; // For isdigit and atoi. + if (error == 0 && service && isdigit(static_cast(service[0]))) + { + u_short_type port = host_to_network_short(atoi(service)); + for (addrinfo_type* ai = *result; ai; ai = ai->ai_next) + { + switch (ai->ai_family) + { + case ASIO_OS_DEF(AF_INET): + { + sockaddr_in4_type* sinptr = + reinterpret_cast(ai->ai_addr); + if (sinptr->sin_port == 0) + sinptr->sin_port = port; + break; + } + case ASIO_OS_DEF(AF_INET6): + { + sockaddr_in6_type* sin6ptr = + reinterpret_cast(ai->ai_addr); + if (sin6ptr->sin6_port == 0) + sin6ptr->sin6_port = port; + break; + } + default: + break; + } + } + } +#endif + return ec = translate_addrinfo_error(error); +#endif +} + +asio::error_code background_getaddrinfo( + const weak_cancel_token_type& cancel_token, const char* host, + const char* service, const addrinfo_type& hints, + addrinfo_type** result, asio::error_code& ec) +{ + if (cancel_token.expired()) + ec = asio::error::operation_aborted; + else + socket_ops::getaddrinfo(host, service, hints, result, ec); + return ec; +} + +void freeaddrinfo(addrinfo_type* ai) +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) +# if defined(ASIO_HAS_GETADDRINFO) + // Building for Windows XP, Windows Server 2003, or later. + ::freeaddrinfo(ai); +# else + // Building for Windows 2000 or earlier. + typedef int (WSAAPI *fai_t)(addrinfo_type*); + if (HMODULE winsock_module = ::GetModuleHandleA("ws2_32")) + { + if (fai_t fai = (fai_t)::GetProcAddress(winsock_module, "freeaddrinfo")) + { + fai(ai); + return; + } + } + freeaddrinfo_emulation(ai); +# endif +#elif !defined(ASIO_HAS_GETADDRINFO) + freeaddrinfo_emulation(ai); +#else + ::freeaddrinfo(ai); +#endif +} + +asio::error_code getnameinfo(const socket_addr_type* addr, + std::size_t addrlen, char* host, std::size_t hostlen, + char* serv, std::size_t servlen, int flags, asio::error_code& ec) +{ +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) +# if defined(ASIO_HAS_GETADDRINFO) + // Building for Windows XP, Windows Server 2003, or later. + clear_last_error(); + int error = ::getnameinfo(addr, static_cast(addrlen), + host, static_cast(hostlen), + serv, static_cast(servlen), flags); + return ec = translate_addrinfo_error(error); +# else + // Building for Windows 2000 or earlier. + typedef int (WSAAPI *gni_t)(const socket_addr_type*, + int, char*, DWORD, char*, DWORD, int); + if (HMODULE winsock_module = ::GetModuleHandleA("ws2_32")) + { + if (gni_t gni = (gni_t)::GetProcAddress(winsock_module, "getnameinfo")) + { + clear_last_error(); + int error = gni(addr, static_cast(addrlen), + host, static_cast(hostlen), + serv, static_cast(servlen), flags); + return ec = translate_addrinfo_error(error); + } + } + clear_last_error(); + return getnameinfo_emulation(addr, addrlen, + host, hostlen, serv, servlen, flags, ec); +# endif +#elif !defined(ASIO_HAS_GETADDRINFO) + using namespace std; // For memcpy. + sockaddr_storage_type tmp_addr; + memcpy(&tmp_addr, addr, addrlen); + addr = reinterpret_cast(&tmp_addr); + clear_last_error(); + return getnameinfo_emulation(addr, addrlen, + host, hostlen, serv, servlen, flags, ec); +#else + clear_last_error(); + int error = ::getnameinfo(addr, addrlen, host, hostlen, serv, servlen, flags); + return ec = translate_addrinfo_error(error); +#endif +} + +asio::error_code sync_getnameinfo( + const socket_addr_type* addr, std::size_t addrlen, + char* host, std::size_t hostlen, char* serv, + std::size_t servlen, int sock_type, asio::error_code& ec) +{ + // First try resolving with the service name. If that fails try resolving + // but allow the service to be returned as a number. + int flags = (sock_type == SOCK_DGRAM) ? NI_DGRAM : 0; + socket_ops::getnameinfo(addr, addrlen, host, + hostlen, serv, servlen, flags, ec); + if (ec) + { + socket_ops::getnameinfo(addr, addrlen, host, hostlen, + serv, servlen, flags | NI_NUMERICSERV, ec); + } + + return ec; +} + +asio::error_code background_getnameinfo( + const weak_cancel_token_type& cancel_token, + const socket_addr_type* addr, std::size_t addrlen, + char* host, std::size_t hostlen, char* serv, + std::size_t servlen, int sock_type, asio::error_code& ec) +{ + if (cancel_token.expired()) + { + ec = asio::error::operation_aborted; + } + else + { + // First try resolving with the service name. If that fails try resolving + // but allow the service to be returned as a number. + int flags = (sock_type == SOCK_DGRAM) ? NI_DGRAM : 0; + socket_ops::getnameinfo(addr, addrlen, host, + hostlen, serv, servlen, flags, ec); + if (ec) + { + socket_ops::getnameinfo(addr, addrlen, host, hostlen, + serv, servlen, flags | NI_NUMERICSERV, ec); + } + } + + return ec; +} + +#endif // !defined(ASIO_WINDOWS_RUNTIME) + +u_long_type network_to_host_long(u_long_type value) +{ +#if defined(ASIO_WINDOWS_RUNTIME) + unsigned char* value_p = reinterpret_cast(&value); + u_long_type result = (static_cast(value_p[0]) << 24) + | (static_cast(value_p[1]) << 16) + | (static_cast(value_p[2]) << 8) + | static_cast(value_p[3]); + return result; +#else // defined(ASIO_WINDOWS_RUNTIME) + return ntohl(value); +#endif // defined(ASIO_WINDOWS_RUNTIME) +} + +u_long_type host_to_network_long(u_long_type value) +{ +#if defined(ASIO_WINDOWS_RUNTIME) + u_long_type result; + unsigned char* result_p = reinterpret_cast(&result); + result_p[0] = static_cast((value >> 24) & 0xFF); + result_p[1] = static_cast((value >> 16) & 0xFF); + result_p[2] = static_cast((value >> 8) & 0xFF); + result_p[3] = static_cast(value & 0xFF); + return result; +#else // defined(ASIO_WINDOWS_RUNTIME) + return htonl(value); +#endif // defined(ASIO_WINDOWS_RUNTIME) +} + +u_short_type network_to_host_short(u_short_type value) +{ +#if defined(ASIO_WINDOWS_RUNTIME) + unsigned char* value_p = reinterpret_cast(&value); + u_short_type result = (static_cast(value_p[0]) << 8) + | static_cast(value_p[1]); + return result; +#else // defined(ASIO_WINDOWS_RUNTIME) + return ntohs(value); +#endif // defined(ASIO_WINDOWS_RUNTIME) +} + +u_short_type host_to_network_short(u_short_type value) +{ +#if defined(ASIO_WINDOWS_RUNTIME) + u_short_type result; + unsigned char* result_p = reinterpret_cast(&result); + result_p[0] = static_cast((value >> 8) & 0xFF); + result_p[1] = static_cast(value & 0xFF); + return result; +#else // defined(ASIO_WINDOWS_RUNTIME) + return htons(value); +#endif // defined(ASIO_WINDOWS_RUNTIME) +} + +} // namespace socket_ops +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_SOCKET_OPS_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/socket_select_interrupter.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/socket_select_interrupter.ipp new file mode 100644 index 000000000..69a6c061d --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/socket_select_interrupter.ipp @@ -0,0 +1,185 @@ +// +// detail/impl/socket_select_interrupter.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_SOCKET_SELECT_INTERRUPTER_IPP +#define ASIO_DETAIL_IMPL_SOCKET_SELECT_INTERRUPTER_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_WINDOWS_RUNTIME) + +#if defined(ASIO_WINDOWS) \ + || defined(__CYGWIN__) \ + || defined(__SYMBIAN32__) + +#include +#include "asio/detail/socket_holder.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/detail/socket_select_interrupter.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +socket_select_interrupter::socket_select_interrupter() +{ + open_descriptors(); +} + +void socket_select_interrupter::open_descriptors() +{ + asio::error_code ec; + socket_holder acceptor(socket_ops::socket( + AF_INET, SOCK_STREAM, IPPROTO_TCP, ec)); + if (acceptor.get() == invalid_socket) + asio::detail::throw_error(ec, "socket_select_interrupter"); + + int opt = 1; + socket_ops::state_type acceptor_state = 0; + socket_ops::setsockopt(acceptor.get(), acceptor_state, + SOL_SOCKET, SO_REUSEADDR, &opt, sizeof(opt), ec); + + using namespace std; // For memset. + sockaddr_in4_type addr; + std::size_t addr_len = sizeof(addr); + memset(&addr, 0, sizeof(addr)); + addr.sin_family = AF_INET; + addr.sin_addr.s_addr = socket_ops::host_to_network_long(INADDR_LOOPBACK); + addr.sin_port = 0; + if (socket_ops::bind(acceptor.get(), (const socket_addr_type*)&addr, + addr_len, ec) == socket_error_retval) + asio::detail::throw_error(ec, "socket_select_interrupter"); + + if (socket_ops::getsockname(acceptor.get(), (socket_addr_type*)&addr, + &addr_len, ec) == socket_error_retval) + asio::detail::throw_error(ec, "socket_select_interrupter"); + + // Some broken firewalls on Windows will intermittently cause getsockname to + // return 0.0.0.0 when the socket is actually bound to 127.0.0.1. We + // explicitly specify the target address here to work around this problem. + if (addr.sin_addr.s_addr == socket_ops::host_to_network_long(INADDR_ANY)) + addr.sin_addr.s_addr = socket_ops::host_to_network_long(INADDR_LOOPBACK); + + if (socket_ops::listen(acceptor.get(), + SOMAXCONN, ec) == socket_error_retval) + asio::detail::throw_error(ec, "socket_select_interrupter"); + + socket_holder client(socket_ops::socket( + AF_INET, SOCK_STREAM, IPPROTO_TCP, ec)); + if (client.get() == invalid_socket) + asio::detail::throw_error(ec, "socket_select_interrupter"); + + if (socket_ops::connect(client.get(), (const socket_addr_type*)&addr, + addr_len, ec) == socket_error_retval) + asio::detail::throw_error(ec, "socket_select_interrupter"); + + socket_holder server(socket_ops::accept(acceptor.get(), 0, 0, ec)); + if (server.get() == invalid_socket) + asio::detail::throw_error(ec, "socket_select_interrupter"); + + ioctl_arg_type non_blocking = 1; + socket_ops::state_type client_state = 0; + if (socket_ops::ioctl(client.get(), client_state, + FIONBIO, &non_blocking, ec)) + asio::detail::throw_error(ec, "socket_select_interrupter"); + + opt = 1; + socket_ops::setsockopt(client.get(), client_state, + IPPROTO_TCP, TCP_NODELAY, &opt, sizeof(opt), ec); + + non_blocking = 1; + socket_ops::state_type server_state = 0; + if (socket_ops::ioctl(server.get(), server_state, + FIONBIO, &non_blocking, ec)) + asio::detail::throw_error(ec, "socket_select_interrupter"); + + opt = 1; + socket_ops::setsockopt(server.get(), server_state, + IPPROTO_TCP, TCP_NODELAY, &opt, sizeof(opt), ec); + + read_descriptor_ = server.release(); + write_descriptor_ = client.release(); +} + +socket_select_interrupter::~socket_select_interrupter() +{ + close_descriptors(); +} + +void socket_select_interrupter::close_descriptors() +{ + asio::error_code ec; + socket_ops::state_type state = socket_ops::internal_non_blocking; + if (read_descriptor_ != invalid_socket) + socket_ops::close(read_descriptor_, state, true, ec); + if (write_descriptor_ != invalid_socket) + socket_ops::close(write_descriptor_, state, true, ec); +} + +void socket_select_interrupter::recreate() +{ + close_descriptors(); + + write_descriptor_ = invalid_socket; + read_descriptor_ = invalid_socket; + + open_descriptors(); +} + +void socket_select_interrupter::interrupt() +{ + char byte = 0; + socket_ops::buf b; + socket_ops::init_buf(b, &byte, 1); + asio::error_code ec; + socket_ops::send(write_descriptor_, &b, 1, 0, ec); +} + +bool socket_select_interrupter::reset() +{ + char data[1024]; + socket_ops::buf b; + socket_ops::init_buf(b, data, sizeof(data)); + asio::error_code ec; + for (;;) + { + int bytes_read = socket_ops::recv(read_descriptor_, &b, 1, 0, ec); + if (bytes_read == sizeof(data)) + continue; + if (bytes_read > 0) + return true; + if (bytes_read == 0) + return false; + if (ec == asio::error::would_block + || ec == asio::error::try_again) + return true; + return false; + } +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS) + // || defined(__CYGWIN__) + // || defined(__SYMBIAN32__) + +#endif // !defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_IMPL_SOCKET_SELECT_INTERRUPTER_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/strand_executor_service.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/strand_executor_service.hpp new file mode 100644 index 000000000..8fe14545d --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/strand_executor_service.hpp @@ -0,0 +1,385 @@ +// +// detail/impl/strand_executor_service.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_STRAND_EXECUTOR_SERVICE_HPP +#define ASIO_DETAIL_IMPL_STRAND_EXECUTOR_SERVICE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/call_stack.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/recycling_allocator.hpp" +#include "asio/executor_work_guard.hpp" +#include "asio/defer.hpp" +#include "asio/dispatch.hpp" +#include "asio/post.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class strand_executor_service::allocator_binder +{ +public: + typedef Allocator allocator_type; + + allocator_binder(ASIO_MOVE_ARG(F) f, const Allocator& a) + : f_(ASIO_MOVE_CAST(F)(f)), + allocator_(a) + { + } + + allocator_binder(const allocator_binder& other) + : f_(other.f_), + allocator_(other.allocator_) + { + } + +#if defined(ASIO_HAS_MOVE) + allocator_binder(allocator_binder&& other) + : f_(ASIO_MOVE_CAST(F)(other.f_)), + allocator_(ASIO_MOVE_CAST(allocator_type)(other.allocator_)) + { + } +#endif // defined(ASIO_HAS_MOVE) + + allocator_type get_allocator() const ASIO_NOEXCEPT + { + return allocator_; + } + + void operator()() + { + f_(); + } + +private: + F f_; + allocator_type allocator_; +}; + +template +class strand_executor_service::invoker::value + >::type> +{ +public: + invoker(const implementation_type& impl, Executor& ex) + : impl_(impl), + executor_(asio::prefer(ex, execution::outstanding_work.tracked)) + { + } + + invoker(const invoker& other) + : impl_(other.impl_), + executor_(other.executor_) + { + } + +#if defined(ASIO_HAS_MOVE) + invoker(invoker&& other) + : impl_(ASIO_MOVE_CAST(implementation_type)(other.impl_)), + executor_(ASIO_MOVE_CAST(executor_type)(other.executor_)) + { + } +#endif // defined(ASIO_HAS_MOVE) + + struct on_invoker_exit + { + invoker* this_; + + ~on_invoker_exit() + { + this_->impl_->mutex_->lock(); + this_->impl_->ready_queue_.push(this_->impl_->waiting_queue_); + bool more_handlers = this_->impl_->locked_ = + !this_->impl_->ready_queue_.empty(); + this_->impl_->mutex_->unlock(); + + if (more_handlers) + { + recycling_allocator allocator; + execution::execute( + asio::prefer( + asio::require(this_->executor_, + execution::blocking.never), + execution::allocator(allocator)), + ASIO_MOVE_CAST(invoker)(*this_)); + } + } + }; + + void operator()() + { + // Indicate that this strand is executing on the current thread. + call_stack::context ctx(impl_.get()); + + // Ensure the next handler, if any, is scheduled on block exit. + on_invoker_exit on_exit = { this }; + (void)on_exit; + + // Run all ready handlers. No lock is required since the ready queue is + // accessed only within the strand. + asio::error_code ec; + while (scheduler_operation* o = impl_->ready_queue_.front()) + { + impl_->ready_queue_.pop(); + o->complete(impl_.get(), ec, 0); + } + } + +private: + typedef typename decay< + typename prefer_result< + Executor, + execution::outstanding_work_t::tracked_t + >::type + >::type executor_type; + + implementation_type impl_; + executor_type executor_; +}; + +#if !defined(ASIO_NO_TS_EXECUTORS) + +template +class strand_executor_service::invoker::value + >::type> +{ +public: + invoker(const implementation_type& impl, Executor& ex) + : impl_(impl), + work_(ex) + { + } + + invoker(const invoker& other) + : impl_(other.impl_), + work_(other.work_) + { + } + +#if defined(ASIO_HAS_MOVE) + invoker(invoker&& other) + : impl_(ASIO_MOVE_CAST(implementation_type)(other.impl_)), + work_(ASIO_MOVE_CAST(executor_work_guard)(other.work_)) + { + } +#endif // defined(ASIO_HAS_MOVE) + + struct on_invoker_exit + { + invoker* this_; + + ~on_invoker_exit() + { + this_->impl_->mutex_->lock(); + this_->impl_->ready_queue_.push(this_->impl_->waiting_queue_); + bool more_handlers = this_->impl_->locked_ = + !this_->impl_->ready_queue_.empty(); + this_->impl_->mutex_->unlock(); + + if (more_handlers) + { + Executor ex(this_->work_.get_executor()); + recycling_allocator allocator; + ex.post(ASIO_MOVE_CAST(invoker)(*this_), allocator); + } + } + }; + + void operator()() + { + // Indicate that this strand is executing on the current thread. + call_stack::context ctx(impl_.get()); + + // Ensure the next handler, if any, is scheduled on block exit. + on_invoker_exit on_exit = { this }; + (void)on_exit; + + // Run all ready handlers. No lock is required since the ready queue is + // accessed only within the strand. + asio::error_code ec; + while (scheduler_operation* o = impl_->ready_queue_.front()) + { + impl_->ready_queue_.pop(); + o->complete(impl_.get(), ec, 0); + } + } + +private: + implementation_type impl_; + executor_work_guard work_; +}; + +#endif // !defined(ASIO_NO_TS_EXECUTORS) + +template +inline void strand_executor_service::execute(const implementation_type& impl, + Executor& ex, ASIO_MOVE_ARG(Function) function, + typename enable_if< + can_query >::value + >::type*) +{ + return strand_executor_service::do_execute(impl, ex, + ASIO_MOVE_CAST(Function)(function), + asio::query(ex, execution::allocator)); +} + +template +inline void strand_executor_service::execute(const implementation_type& impl, + Executor& ex, ASIO_MOVE_ARG(Function) function, + typename enable_if< + !can_query >::value + >::type*) +{ + return strand_executor_service::do_execute(impl, ex, + ASIO_MOVE_CAST(Function)(function), + std::allocator()); +} + +template +void strand_executor_service::do_execute(const implementation_type& impl, + Executor& ex, ASIO_MOVE_ARG(Function) function, const Allocator& a) +{ + typedef typename decay::type function_type; + + // If the executor is not never-blocking, and we are already in the strand, + // then the function can run immediately. + if (asio::query(ex, execution::blocking) != execution::blocking.never + && call_stack::contains(impl.get())) + { + // Make a local, non-const copy of the function. + function_type tmp(ASIO_MOVE_CAST(Function)(function)); + + fenced_block b(fenced_block::full); + asio_handler_invoke_helpers::invoke(tmp, tmp); + return; + } + + // Allocate and construct an operation to wrap the function. + typedef executor_op op; + typename op::ptr p = { detail::addressof(a), op::ptr::allocate(a), 0 }; + p.p = new (p.v) op(ASIO_MOVE_CAST(Function)(function), a); + + ASIO_HANDLER_CREATION((impl->service_->context(), *p.p, + "strand_executor", impl.get(), 0, "execute")); + + // Add the function to the strand and schedule the strand if required. + bool first = enqueue(impl, p.p); + p.v = p.p = 0; + if (first) + { + execution::execute(ex, invoker(impl, ex)); + } +} + +template +void strand_executor_service::dispatch(const implementation_type& impl, + Executor& ex, ASIO_MOVE_ARG(Function) function, const Allocator& a) +{ + typedef typename decay::type function_type; + + // If we are already in the strand then the function can run immediately. + if (call_stack::contains(impl.get())) + { + // Make a local, non-const copy of the function. + function_type tmp(ASIO_MOVE_CAST(Function)(function)); + + fenced_block b(fenced_block::full); + asio_handler_invoke_helpers::invoke(tmp, tmp); + return; + } + + // Allocate and construct an operation to wrap the function. + typedef executor_op op; + typename op::ptr p = { detail::addressof(a), op::ptr::allocate(a), 0 }; + p.p = new (p.v) op(ASIO_MOVE_CAST(Function)(function), a); + + ASIO_HANDLER_CREATION((impl->service_->context(), *p.p, + "strand_executor", impl.get(), 0, "dispatch")); + + // Add the function to the strand and schedule the strand if required. + bool first = enqueue(impl, p.p); + p.v = p.p = 0; + if (first) + { + asio::dispatch(ex, + allocator_binder, Allocator>( + invoker(impl, ex), a)); + } +} + +// Request invocation of the given function and return immediately. +template +void strand_executor_service::post(const implementation_type& impl, + Executor& ex, ASIO_MOVE_ARG(Function) function, const Allocator& a) +{ + typedef typename decay::type function_type; + + // Allocate and construct an operation to wrap the function. + typedef executor_op op; + typename op::ptr p = { detail::addressof(a), op::ptr::allocate(a), 0 }; + p.p = new (p.v) op(ASIO_MOVE_CAST(Function)(function), a); + + ASIO_HANDLER_CREATION((impl->service_->context(), *p.p, + "strand_executor", impl.get(), 0, "post")); + + // Add the function to the strand and schedule the strand if required. + bool first = enqueue(impl, p.p); + p.v = p.p = 0; + if (first) + { + asio::post(ex, + allocator_binder, Allocator>( + invoker(impl, ex), a)); + } +} + +// Request invocation of the given function and return immediately. +template +void strand_executor_service::defer(const implementation_type& impl, + Executor& ex, ASIO_MOVE_ARG(Function) function, const Allocator& a) +{ + typedef typename decay::type function_type; + + // Allocate and construct an operation to wrap the function. + typedef executor_op op; + typename op::ptr p = { detail::addressof(a), op::ptr::allocate(a), 0 }; + p.p = new (p.v) op(ASIO_MOVE_CAST(Function)(function), a); + + ASIO_HANDLER_CREATION((impl->service_->context(), *p.p, + "strand_executor", impl.get(), 0, "defer")); + + // Add the function to the strand and schedule the strand if required. + bool first = enqueue(impl, p.p); + p.v = p.p = 0; + if (first) + { + asio::defer(ex, + allocator_binder, Allocator>( + invoker(impl, ex), a)); + } +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_IMPL_STRAND_EXECUTOR_SERVICE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/strand_executor_service.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/strand_executor_service.ipp new file mode 100644 index 000000000..dfe64df45 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/strand_executor_service.ipp @@ -0,0 +1,134 @@ +// +// detail/impl/strand_executor_service.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_STRAND_EXECUTOR_SERVICE_IPP +#define ASIO_DETAIL_IMPL_STRAND_EXECUTOR_SERVICE_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/strand_executor_service.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +strand_executor_service::strand_executor_service(execution_context& ctx) + : execution_context_service_base(ctx), + mutex_(), + salt_(0), + impl_list_(0) +{ +} + +void strand_executor_service::shutdown() +{ + op_queue ops; + + asio::detail::mutex::scoped_lock lock(mutex_); + + strand_impl* impl = impl_list_; + while (impl) + { + impl->mutex_->lock(); + impl->shutdown_ = true; + ops.push(impl->waiting_queue_); + ops.push(impl->ready_queue_); + impl->mutex_->unlock(); + impl = impl->next_; + } +} + +strand_executor_service::implementation_type +strand_executor_service::create_implementation() +{ + implementation_type new_impl(new strand_impl); + new_impl->locked_ = false; + new_impl->shutdown_ = false; + + asio::detail::mutex::scoped_lock lock(mutex_); + + // Select a mutex from the pool of shared mutexes. + std::size_t salt = salt_++; + std::size_t mutex_index = reinterpret_cast(new_impl.get()); + mutex_index += (reinterpret_cast(new_impl.get()) >> 3); + mutex_index ^= salt + 0x9e3779b9 + (mutex_index << 6) + (mutex_index >> 2); + mutex_index = mutex_index % num_mutexes; + if (!mutexes_[mutex_index].get()) + mutexes_[mutex_index].reset(new mutex); + new_impl->mutex_ = mutexes_[mutex_index].get(); + + // Insert implementation into linked list of all implementations. + new_impl->next_ = impl_list_; + new_impl->prev_ = 0; + if (impl_list_) + impl_list_->prev_ = new_impl.get(); + impl_list_ = new_impl.get(); + new_impl->service_ = this; + + return new_impl; +} + +strand_executor_service::strand_impl::~strand_impl() +{ + asio::detail::mutex::scoped_lock lock(service_->mutex_); + + // Remove implementation from linked list of all implementations. + if (service_->impl_list_ == this) + service_->impl_list_ = next_; + if (prev_) + prev_->next_ = next_; + if (next_) + next_->prev_= prev_; +} + +bool strand_executor_service::enqueue(const implementation_type& impl, + scheduler_operation* op) +{ + impl->mutex_->lock(); + if (impl->shutdown_) + { + impl->mutex_->unlock(); + op->destroy(); + return false; + } + else if (impl->locked_) + { + // Some other function already holds the strand lock. Enqueue for later. + impl->waiting_queue_.push(op); + impl->mutex_->unlock(); + return false; + } + else + { + // The function is acquiring the strand lock and so is responsible for + // scheduling the strand. + impl->locked_ = true; + impl->mutex_->unlock(); + impl->ready_queue_.push(op); + return true; + } +} + +bool strand_executor_service::running_in_this_thread( + const implementation_type& impl) +{ + return !!call_stack::contains(impl.get()); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_IMPL_STRAND_EXECUTOR_SERVICE_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/strand_service.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/strand_service.hpp new file mode 100644 index 000000000..a9696deb9 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/strand_service.hpp @@ -0,0 +1,117 @@ +// +// detail/impl/strand_service.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_STRAND_SERVICE_HPP +#define ASIO_DETAIL_IMPL_STRAND_SERVICE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/call_stack.hpp" +#include "asio/detail/completion_handler.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/memory.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +inline strand_service::strand_impl::strand_impl() + : operation(&strand_service::do_complete), + locked_(false) +{ +} + +struct strand_service::on_dispatch_exit +{ + io_context_impl* io_context_impl_; + strand_impl* impl_; + + ~on_dispatch_exit() + { + impl_->mutex_.lock(); + impl_->ready_queue_.push(impl_->waiting_queue_); + bool more_handlers = impl_->locked_ = !impl_->ready_queue_.empty(); + impl_->mutex_.unlock(); + + if (more_handlers) + io_context_impl_->post_immediate_completion(impl_, false); + } +}; + +template +void strand_service::dispatch(strand_service::implementation_type& impl, + Handler& handler) +{ + // If we are already in the strand then the handler can run immediately. + if (call_stack::contains(impl)) + { + fenced_block b(fenced_block::full); + asio_handler_invoke_helpers::invoke(handler, handler); + return; + } + + // Allocate and construct an operation to wrap the handler. + typedef completion_handler op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(handler, io_context_.get_executor()); + + ASIO_HANDLER_CREATION((this->context(), + *p.p, "strand", impl, 0, "dispatch")); + + bool dispatch_immediately = do_dispatch(impl, p.p); + operation* o = p.p; + p.v = p.p = 0; + + if (dispatch_immediately) + { + // Indicate that this strand is executing on the current thread. + call_stack::context ctx(impl); + + // Ensure the next handler, if any, is scheduled on block exit. + on_dispatch_exit on_exit = { &io_context_impl_, impl }; + (void)on_exit; + + op::do_complete(&io_context_impl_, o, asio::error_code(), 0); + } +} + +// Request the io_context to invoke the given handler and return immediately. +template +void strand_service::post(strand_service::implementation_type& impl, + Handler& handler) +{ + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef completion_handler op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(handler, io_context_.get_executor()); + + ASIO_HANDLER_CREATION((this->context(), + *p.p, "strand", impl, 0, "post")); + + do_post(impl, p.p, is_continuation); + p.v = p.p = 0; +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_IMPL_STRAND_SERVICE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/strand_service.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/strand_service.ipp new file mode 100644 index 000000000..6bd87fad2 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/strand_service.ipp @@ -0,0 +1,178 @@ +// +// detail/impl/strand_service.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_STRAND_SERVICE_IPP +#define ASIO_DETAIL_IMPL_STRAND_SERVICE_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/call_stack.hpp" +#include "asio/detail/strand_service.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +struct strand_service::on_do_complete_exit +{ + io_context_impl* owner_; + strand_impl* impl_; + + ~on_do_complete_exit() + { + impl_->mutex_.lock(); + impl_->ready_queue_.push(impl_->waiting_queue_); + bool more_handlers = impl_->locked_ = !impl_->ready_queue_.empty(); + impl_->mutex_.unlock(); + + if (more_handlers) + owner_->post_immediate_completion(impl_, true); + } +}; + +strand_service::strand_service(asio::io_context& io_context) + : asio::detail::service_base(io_context), + io_context_(io_context), + io_context_impl_(asio::use_service(io_context)), + mutex_(), + salt_(0) +{ +} + +void strand_service::shutdown() +{ + op_queue ops; + + asio::detail::mutex::scoped_lock lock(mutex_); + + for (std::size_t i = 0; i < num_implementations; ++i) + { + if (strand_impl* impl = implementations_[i].get()) + { + ops.push(impl->waiting_queue_); + ops.push(impl->ready_queue_); + } + } +} + +void strand_service::construct(strand_service::implementation_type& impl) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + + std::size_t salt = salt_++; +#if defined(ASIO_ENABLE_SEQUENTIAL_STRAND_ALLOCATION) + std::size_t index = salt; +#else // defined(ASIO_ENABLE_SEQUENTIAL_STRAND_ALLOCATION) + std::size_t index = reinterpret_cast(&impl); + index += (reinterpret_cast(&impl) >> 3); + index ^= salt + 0x9e3779b9 + (index << 6) + (index >> 2); +#endif // defined(ASIO_ENABLE_SEQUENTIAL_STRAND_ALLOCATION) + index = index % num_implementations; + + if (!implementations_[index].get()) + implementations_[index].reset(new strand_impl); + impl = implementations_[index].get(); +} + +bool strand_service::running_in_this_thread( + const implementation_type& impl) const +{ + return call_stack::contains(impl) != 0; +} + +bool strand_service::do_dispatch(implementation_type& impl, operation* op) +{ + // If we are running inside the io_context, and no other handler already + // holds the strand lock, then the handler can run immediately. + bool can_dispatch = io_context_impl_.can_dispatch(); + impl->mutex_.lock(); + if (can_dispatch && !impl->locked_) + { + // Immediate invocation is allowed. + impl->locked_ = true; + impl->mutex_.unlock(); + return true; + } + + if (impl->locked_) + { + // Some other handler already holds the strand lock. Enqueue for later. + impl->waiting_queue_.push(op); + impl->mutex_.unlock(); + } + else + { + // The handler is acquiring the strand lock and so is responsible for + // scheduling the strand. + impl->locked_ = true; + impl->mutex_.unlock(); + impl->ready_queue_.push(op); + io_context_impl_.post_immediate_completion(impl, false); + } + + return false; +} + +void strand_service::do_post(implementation_type& impl, + operation* op, bool is_continuation) +{ + impl->mutex_.lock(); + if (impl->locked_) + { + // Some other handler already holds the strand lock. Enqueue for later. + impl->waiting_queue_.push(op); + impl->mutex_.unlock(); + } + else + { + // The handler is acquiring the strand lock and so is responsible for + // scheduling the strand. + impl->locked_ = true; + impl->mutex_.unlock(); + impl->ready_queue_.push(op); + io_context_impl_.post_immediate_completion(impl, is_continuation); + } +} + +void strand_service::do_complete(void* owner, operation* base, + const asio::error_code& ec, std::size_t /*bytes_transferred*/) +{ + if (owner) + { + strand_impl* impl = static_cast(base); + + // Indicate that this strand is executing on the current thread. + call_stack::context ctx(impl); + + // Ensure the next handler, if any, is scheduled on block exit. + on_do_complete_exit on_exit; + on_exit.owner_ = static_cast(owner); + on_exit.impl_ = impl; + + // Run all ready handlers. No lock is required since the ready queue is + // accessed only within the strand. + while (operation* o = impl->ready_queue_.front()) + { + impl->ready_queue_.pop(); + o->complete(owner, ec, 0); + } + } +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_IMPL_STRAND_SERVICE_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/throw_error.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/throw_error.ipp new file mode 100644 index 000000000..57d301ac4 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/throw_error.ipp @@ -0,0 +1,60 @@ +// +// detail/impl/throw_error.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_THROW_ERROR_IPP +#define ASIO_DETAIL_IMPL_THROW_ERROR_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/detail/throw_exception.hpp" +#include "asio/system_error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +void do_throw_error(const asio::error_code& err) +{ + asio::system_error e(err); + asio::detail::throw_exception(e); +} + +void do_throw_error(const asio::error_code& err, const char* location) +{ + // boostify: non-boost code starts here +#if defined(ASIO_MSVC) && defined(ASIO_HAS_STD_SYSTEM_ERROR) + // Microsoft's implementation of std::system_error is non-conformant in that + // it ignores the error code's message when a "what" string is supplied. We'll + // work around this by explicitly formatting the "what" string. + std::string what_msg = location; + what_msg += ": "; + what_msg += err.message(); + asio::system_error e(err, what_msg); + asio::detail::throw_exception(e); +#else // defined(ASIO_MSVC) && defined(ASIO_HAS_STD_SYSTEM_ERROR) + // boostify: non-boost code ends here + asio::system_error e(err, location); + asio::detail::throw_exception(e); + // boostify: non-boost code starts here +#endif // defined(ASIO_MSVC) && defined(ASIO_HAS_STD_SYSTEM_ERROR) + // boostify: non-boost code ends here +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_IMPL_THROW_ERROR_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/timer_queue_ptime.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/timer_queue_ptime.ipp new file mode 100644 index 000000000..b246d4811 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/timer_queue_ptime.ipp @@ -0,0 +1,91 @@ +// +// detail/impl/timer_queue_ptime.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_TIMER_QUEUE_PTIME_IPP +#define ASIO_DETAIL_IMPL_TIMER_QUEUE_PTIME_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_BOOST_DATE_TIME) + +#include "asio/detail/timer_queue_ptime.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +timer_queue >::timer_queue() +{ +} + +timer_queue >::~timer_queue() +{ +} + +bool timer_queue >::enqueue_timer( + const time_type& time, per_timer_data& timer, wait_op* op) +{ + return impl_.enqueue_timer(time, timer, op); +} + +bool timer_queue >::empty() const +{ + return impl_.empty(); +} + +long timer_queue >::wait_duration_msec( + long max_duration) const +{ + return impl_.wait_duration_msec(max_duration); +} + +long timer_queue >::wait_duration_usec( + long max_duration) const +{ + return impl_.wait_duration_usec(max_duration); +} + +void timer_queue >::get_ready_timers( + op_queue& ops) +{ + impl_.get_ready_timers(ops); +} + +void timer_queue >::get_all_timers( + op_queue& ops) +{ + impl_.get_all_timers(ops); +} + +std::size_t timer_queue >::cancel_timer( + per_timer_data& timer, op_queue& ops, std::size_t max_cancelled) +{ + return impl_.cancel_timer(timer, ops, max_cancelled); +} + +void timer_queue >::move_timer( + per_timer_data& target, per_timer_data& source) +{ + impl_.move_timer(target, source); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_BOOST_DATE_TIME) + +#endif // ASIO_DETAIL_IMPL_TIMER_QUEUE_PTIME_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/timer_queue_set.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/timer_queue_set.ipp new file mode 100644 index 000000000..38b950be5 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/timer_queue_set.ipp @@ -0,0 +1,101 @@ +// +// detail/impl/timer_queue_set.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_TIMER_QUEUE_SET_IPP +#define ASIO_DETAIL_IMPL_TIMER_QUEUE_SET_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/timer_queue_set.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +timer_queue_set::timer_queue_set() + : first_(0) +{ +} + +void timer_queue_set::insert(timer_queue_base* q) +{ + q->next_ = first_; + first_ = q; +} + +void timer_queue_set::erase(timer_queue_base* q) +{ + if (first_) + { + if (q == first_) + { + first_ = q->next_; + q->next_ = 0; + return; + } + + for (timer_queue_base* p = first_; p->next_; p = p->next_) + { + if (p->next_ == q) + { + p->next_ = q->next_; + q->next_ = 0; + return; + } + } + } +} + +bool timer_queue_set::all_empty() const +{ + for (timer_queue_base* p = first_; p; p = p->next_) + if (!p->empty()) + return false; + return true; +} + +long timer_queue_set::wait_duration_msec(long max_duration) const +{ + long min_duration = max_duration; + for (timer_queue_base* p = first_; p; p = p->next_) + min_duration = p->wait_duration_msec(min_duration); + return min_duration; +} + +long timer_queue_set::wait_duration_usec(long max_duration) const +{ + long min_duration = max_duration; + for (timer_queue_base* p = first_; p; p = p->next_) + min_duration = p->wait_duration_usec(min_duration); + return min_duration; +} + +void timer_queue_set::get_ready_timers(op_queue& ops) +{ + for (timer_queue_base* p = first_; p; p = p->next_) + p->get_ready_timers(ops); +} + +void timer_queue_set::get_all_timers(op_queue& ops) +{ + for (timer_queue_base* p = first_; p; p = p->next_) + p->get_all_timers(ops); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_IMPL_TIMER_QUEUE_SET_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_event.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_event.ipp new file mode 100644 index 000000000..62dec0a1f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_event.ipp @@ -0,0 +1,76 @@ +// +// detail/win_event.ipp +// ~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_WIN_EVENT_IPP +#define ASIO_DETAIL_IMPL_WIN_EVENT_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) + +#include "asio/detail/throw_error.hpp" +#include "asio/detail/win_event.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +win_event::win_event() + : state_(0) +{ +#if defined(ASIO_WINDOWS_APP) + events_[0] = ::CreateEventExW(0, 0, + CREATE_EVENT_MANUAL_RESET, EVENT_ALL_ACCESS); +#else // defined(ASIO_WINDOWS_APP) + events_[0] = ::CreateEventW(0, true, false, 0); +#endif // defined(ASIO_WINDOWS_APP) + if (!events_[0]) + { + DWORD last_error = ::GetLastError(); + asio::error_code ec(last_error, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "event"); + } + +#if defined(ASIO_WINDOWS_APP) + events_[1] = ::CreateEventExW(0, 0, 0, EVENT_ALL_ACCESS); +#else // defined(ASIO_WINDOWS_APP) + events_[1] = ::CreateEventW(0, false, false, 0); +#endif // defined(ASIO_WINDOWS_APP) + if (!events_[1]) + { + DWORD last_error = ::GetLastError(); + ::CloseHandle(events_[0]); + asio::error_code ec(last_error, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "event"); + } +} + +win_event::~win_event() +{ + ::CloseHandle(events_[0]); + ::CloseHandle(events_[1]); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS) + +#endif // ASIO_DETAIL_IMPL_WIN_EVENT_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_iocp_handle_service.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_iocp_handle_service.ipp new file mode 100644 index 000000000..31f2948c5 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_iocp_handle_service.ipp @@ -0,0 +1,525 @@ +// +// detail/impl/win_iocp_handle_service.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// Copyright (c) 2008 Rep Invariant Systems, Inc. (info@repinvariant.com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_WIN_IOCP_HANDLE_SERVICE_IPP +#define ASIO_DETAIL_IMPL_WIN_IOCP_HANDLE_SERVICE_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/detail/win_iocp_handle_service.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class win_iocp_handle_service::overlapped_wrapper + : public OVERLAPPED +{ +public: + explicit overlapped_wrapper(asio::error_code& ec) + { + Internal = 0; + InternalHigh = 0; + Offset = 0; + OffsetHigh = 0; + + // Create a non-signalled manual-reset event, for GetOverlappedResult. + hEvent = ::CreateEventW(0, TRUE, FALSE, 0); + if (hEvent) + { + // As documented in GetQueuedCompletionStatus, setting the low order + // bit of this event prevents our synchronous writes from being treated + // as completion port events. + DWORD_PTR tmp = reinterpret_cast(hEvent); + hEvent = reinterpret_cast(tmp | 1); + } + else + { + DWORD last_error = ::GetLastError(); + ec = asio::error_code(last_error, + asio::error::get_system_category()); + } + } + + ~overlapped_wrapper() + { + if (hEvent) + { + ::CloseHandle(hEvent); + } + } +}; + +win_iocp_handle_service::win_iocp_handle_service(execution_context& context) + : execution_context_service_base(context), + iocp_service_(asio::use_service(context)), + mutex_(), + impl_list_(0) +{ +} + +void win_iocp_handle_service::shutdown() +{ + // Close all implementations, causing all operations to complete. + asio::detail::mutex::scoped_lock lock(mutex_); + implementation_type* impl = impl_list_; + while (impl) + { + close_for_destruction(*impl); + impl = impl->next_; + } +} + +void win_iocp_handle_service::construct( + win_iocp_handle_service::implementation_type& impl) +{ + impl.handle_ = INVALID_HANDLE_VALUE; + impl.safe_cancellation_thread_id_ = 0; + + // Insert implementation into linked list of all implementations. + asio::detail::mutex::scoped_lock lock(mutex_); + impl.next_ = impl_list_; + impl.prev_ = 0; + if (impl_list_) + impl_list_->prev_ = &impl; + impl_list_ = &impl; +} + +void win_iocp_handle_service::move_construct( + win_iocp_handle_service::implementation_type& impl, + win_iocp_handle_service::implementation_type& other_impl) +{ + impl.handle_ = other_impl.handle_; + other_impl.handle_ = INVALID_HANDLE_VALUE; + + impl.safe_cancellation_thread_id_ = other_impl.safe_cancellation_thread_id_; + other_impl.safe_cancellation_thread_id_ = 0; + + // Insert implementation into linked list of all implementations. + asio::detail::mutex::scoped_lock lock(mutex_); + impl.next_ = impl_list_; + impl.prev_ = 0; + if (impl_list_) + impl_list_->prev_ = &impl; + impl_list_ = &impl; +} + +void win_iocp_handle_service::move_assign( + win_iocp_handle_service::implementation_type& impl, + win_iocp_handle_service& other_service, + win_iocp_handle_service::implementation_type& other_impl) +{ + close_for_destruction(impl); + + if (this != &other_service) + { + // Remove implementation from linked list of all implementations. + asio::detail::mutex::scoped_lock lock(mutex_); + if (impl_list_ == &impl) + impl_list_ = impl.next_; + if (impl.prev_) + impl.prev_->next_ = impl.next_; + if (impl.next_) + impl.next_->prev_= impl.prev_; + impl.next_ = 0; + impl.prev_ = 0; + } + + impl.handle_ = other_impl.handle_; + other_impl.handle_ = INVALID_HANDLE_VALUE; + + impl.safe_cancellation_thread_id_ = other_impl.safe_cancellation_thread_id_; + other_impl.safe_cancellation_thread_id_ = 0; + + if (this != &other_service) + { + // Insert implementation into linked list of all implementations. + asio::detail::mutex::scoped_lock lock(other_service.mutex_); + impl.next_ = other_service.impl_list_; + impl.prev_ = 0; + if (other_service.impl_list_) + other_service.impl_list_->prev_ = &impl; + other_service.impl_list_ = &impl; + } +} + +void win_iocp_handle_service::destroy( + win_iocp_handle_service::implementation_type& impl) +{ + close_for_destruction(impl); + + // Remove implementation from linked list of all implementations. + asio::detail::mutex::scoped_lock lock(mutex_); + if (impl_list_ == &impl) + impl_list_ = impl.next_; + if (impl.prev_) + impl.prev_->next_ = impl.next_; + if (impl.next_) + impl.next_->prev_= impl.prev_; + impl.next_ = 0; + impl.prev_ = 0; +} + +asio::error_code win_iocp_handle_service::assign( + win_iocp_handle_service::implementation_type& impl, + const native_handle_type& handle, asio::error_code& ec) +{ + if (is_open(impl)) + { + ec = asio::error::already_open; + return ec; + } + + if (iocp_service_.register_handle(handle, ec)) + return ec; + + impl.handle_ = handle; + ec = asio::error_code(); + return ec; +} + +asio::error_code win_iocp_handle_service::close( + win_iocp_handle_service::implementation_type& impl, + asio::error_code& ec) +{ + if (is_open(impl)) + { + ASIO_HANDLER_OPERATION((iocp_service_.context(), "handle", + &impl, reinterpret_cast(impl.handle_), "close")); + + if (!::CloseHandle(impl.handle_)) + { + DWORD last_error = ::GetLastError(); + ec = asio::error_code(last_error, + asio::error::get_system_category()); + } + else + { + ec = asio::error_code(); + } + + impl.handle_ = INVALID_HANDLE_VALUE; + impl.safe_cancellation_thread_id_ = 0; + } + else + { + ec = asio::error_code(); + } + + return ec; +} + +asio::error_code win_iocp_handle_service::cancel( + win_iocp_handle_service::implementation_type& impl, + asio::error_code& ec) +{ + if (!is_open(impl)) + { + ec = asio::error::bad_descriptor; + return ec; + } + + ASIO_HANDLER_OPERATION((iocp_service_.context(), "handle", + &impl, reinterpret_cast(impl.handle_), "cancel")); + + if (FARPROC cancel_io_ex_ptr = ::GetProcAddress( + ::GetModuleHandleA("KERNEL32"), "CancelIoEx")) + { + // The version of Windows supports cancellation from any thread. + typedef BOOL (WINAPI* cancel_io_ex_t)(HANDLE, LPOVERLAPPED); + cancel_io_ex_t cancel_io_ex = reinterpret_cast( + reinterpret_cast(cancel_io_ex_ptr)); + if (!cancel_io_ex(impl.handle_, 0)) + { + DWORD last_error = ::GetLastError(); + if (last_error == ERROR_NOT_FOUND) + { + // ERROR_NOT_FOUND means that there were no operations to be + // cancelled. We swallow this error to match the behaviour on other + // platforms. + ec = asio::error_code(); + } + else + { + ec = asio::error_code(last_error, + asio::error::get_system_category()); + } + } + else + { + ec = asio::error_code(); + } + } + else if (impl.safe_cancellation_thread_id_ == 0) + { + // No operations have been started, so there's nothing to cancel. + ec = asio::error_code(); + } + else if (impl.safe_cancellation_thread_id_ == ::GetCurrentThreadId()) + { + // Asynchronous operations have been started from the current thread only, + // so it is safe to try to cancel them using CancelIo. + if (!::CancelIo(impl.handle_)) + { + DWORD last_error = ::GetLastError(); + ec = asio::error_code(last_error, + asio::error::get_system_category()); + } + else + { + ec = asio::error_code(); + } + } + else + { + // Asynchronous operations have been started from more than one thread, + // so cancellation is not safe. + ec = asio::error::operation_not_supported; + } + + return ec; +} + +size_t win_iocp_handle_service::do_write( + win_iocp_handle_service::implementation_type& impl, uint64_t offset, + const asio::const_buffer& buffer, asio::error_code& ec) +{ + if (!is_open(impl)) + { + ec = asio::error::bad_descriptor; + return 0; + } + + // A request to write 0 bytes on a handle is a no-op. + if (buffer.size() == 0) + { + ec = asio::error_code(); + return 0; + } + + overlapped_wrapper overlapped(ec); + if (ec) + { + return 0; + } + + // Write the data. + overlapped.Offset = offset & 0xFFFFFFFF; + overlapped.OffsetHigh = (offset >> 32) & 0xFFFFFFFF; + BOOL ok = ::WriteFile(impl.handle_, buffer.data(), + static_cast(buffer.size()), 0, &overlapped); + if (!ok) + { + DWORD last_error = ::GetLastError(); + if (last_error != ERROR_IO_PENDING) + { + ec = asio::error_code(last_error, + asio::error::get_system_category()); + return 0; + } + } + + // Wait for the operation to complete. + DWORD bytes_transferred = 0; + ok = ::GetOverlappedResult(impl.handle_, + &overlapped, &bytes_transferred, TRUE); + if (!ok) + { + DWORD last_error = ::GetLastError(); + ec = asio::error_code(last_error, + asio::error::get_system_category()); + return 0; + } + + ec = asio::error_code(); + return bytes_transferred; +} + +void win_iocp_handle_service::start_write_op( + win_iocp_handle_service::implementation_type& impl, uint64_t offset, + const asio::const_buffer& buffer, operation* op) +{ + update_cancellation_thread_id(impl); + iocp_service_.work_started(); + + if (!is_open(impl)) + { + iocp_service_.on_completion(op, asio::error::bad_descriptor); + } + else if (buffer.size() == 0) + { + // A request to write 0 bytes on a handle is a no-op. + iocp_service_.on_completion(op); + } + else + { + DWORD bytes_transferred = 0; + op->Offset = offset & 0xFFFFFFFF; + op->OffsetHigh = (offset >> 32) & 0xFFFFFFFF; + BOOL ok = ::WriteFile(impl.handle_, buffer.data(), + static_cast(buffer.size()), + &bytes_transferred, op); + DWORD last_error = ::GetLastError(); + if (!ok && last_error != ERROR_IO_PENDING + && last_error != ERROR_MORE_DATA) + { + iocp_service_.on_completion(op, last_error, bytes_transferred); + } + else + { + iocp_service_.on_pending(op); + } + } +} + +size_t win_iocp_handle_service::do_read( + win_iocp_handle_service::implementation_type& impl, uint64_t offset, + const asio::mutable_buffer& buffer, asio::error_code& ec) +{ + if (!is_open(impl)) + { + ec = asio::error::bad_descriptor; + return 0; + } + + // A request to read 0 bytes on a stream handle is a no-op. + if (buffer.size() == 0) + { + ec = asio::error_code(); + return 0; + } + + overlapped_wrapper overlapped(ec); + if (ec) + { + return 0; + } + + // Read some data. + overlapped.Offset = offset & 0xFFFFFFFF; + overlapped.OffsetHigh = (offset >> 32) & 0xFFFFFFFF; + BOOL ok = ::ReadFile(impl.handle_, buffer.data(), + static_cast(buffer.size()), 0, &overlapped); + if (!ok) + { + DWORD last_error = ::GetLastError(); + if (last_error != ERROR_IO_PENDING && last_error != ERROR_MORE_DATA) + { + if (last_error == ERROR_HANDLE_EOF) + { + ec = asio::error::eof; + } + else + { + ec = asio::error_code(last_error, + asio::error::get_system_category()); + } + return 0; + } + } + + // Wait for the operation to complete. + DWORD bytes_transferred = 0; + ok = ::GetOverlappedResult(impl.handle_, + &overlapped, &bytes_transferred, TRUE); + if (!ok) + { + DWORD last_error = ::GetLastError(); + if (last_error == ERROR_HANDLE_EOF) + { + ec = asio::error::eof; + } + else + { + ec = asio::error_code(last_error, + asio::error::get_system_category()); + } + return (last_error == ERROR_MORE_DATA) ? bytes_transferred : 0; + } + + ec = asio::error_code(); + return bytes_transferred; +} + +void win_iocp_handle_service::start_read_op( + win_iocp_handle_service::implementation_type& impl, uint64_t offset, + const asio::mutable_buffer& buffer, operation* op) +{ + update_cancellation_thread_id(impl); + iocp_service_.work_started(); + + if (!is_open(impl)) + { + iocp_service_.on_completion(op, asio::error::bad_descriptor); + } + else if (buffer.size() == 0) + { + // A request to read 0 bytes on a handle is a no-op. + iocp_service_.on_completion(op); + } + else + { + DWORD bytes_transferred = 0; + op->Offset = offset & 0xFFFFFFFF; + op->OffsetHigh = (offset >> 32) & 0xFFFFFFFF; + BOOL ok = ::ReadFile(impl.handle_, buffer.data(), + static_cast(buffer.size()), + &bytes_transferred, op); + DWORD last_error = ::GetLastError(); + if (!ok && last_error != ERROR_IO_PENDING + && last_error != ERROR_MORE_DATA) + { + iocp_service_.on_completion(op, last_error, bytes_transferred); + } + else + { + iocp_service_.on_pending(op); + } + } +} + +void win_iocp_handle_service::update_cancellation_thread_id( + win_iocp_handle_service::implementation_type& impl) +{ + if (impl.safe_cancellation_thread_id_ == 0) + impl.safe_cancellation_thread_id_ = ::GetCurrentThreadId(); + else if (impl.safe_cancellation_thread_id_ != ::GetCurrentThreadId()) + impl.safe_cancellation_thread_id_ = ~DWORD(0); +} + +void win_iocp_handle_service::close_for_destruction(implementation_type& impl) +{ + if (is_open(impl)) + { + ASIO_HANDLER_OPERATION((iocp_service_.context(), "handle", + &impl, reinterpret_cast(impl.handle_), "close")); + + ::CloseHandle(impl.handle_); + impl.handle_ = INVALID_HANDLE_VALUE; + impl.safe_cancellation_thread_id_ = 0; + } +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_IMPL_WIN_IOCP_HANDLE_SERVICE_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_iocp_io_context.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_iocp_io_context.hpp new file mode 100644 index 000000000..07cf0cf06 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_iocp_io_context.hpp @@ -0,0 +1,103 @@ +// +// detail/impl/win_iocp_io_context.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_WIN_IOCP_IO_CONTEXT_HPP +#define ASIO_DETAIL_IMPL_WIN_IOCP_IO_CONTEXT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/detail/completion_handler.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/memory.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +void win_iocp_io_context::add_timer_queue( + timer_queue& queue) +{ + do_add_timer_queue(queue); +} + +template +void win_iocp_io_context::remove_timer_queue( + timer_queue& queue) +{ + do_remove_timer_queue(queue); +} + +template +void win_iocp_io_context::schedule_timer(timer_queue& queue, + const typename Time_Traits::time_type& time, + typename timer_queue::per_timer_data& timer, wait_op* op) +{ + // If the service has been shut down we silently discard the timer. + if (::InterlockedExchangeAdd(&shutdown_, 0) != 0) + { + post_immediate_completion(op, false); + return; + } + + mutex::scoped_lock lock(dispatch_mutex_); + + bool earliest = queue.enqueue_timer(time, timer, op); + work_started(); + if (earliest) + update_timeout(); +} + +template +std::size_t win_iocp_io_context::cancel_timer(timer_queue& queue, + typename timer_queue::per_timer_data& timer, + std::size_t max_cancelled) +{ + // If the service has been shut down we silently ignore the cancellation. + if (::InterlockedExchangeAdd(&shutdown_, 0) != 0) + return 0; + + mutex::scoped_lock lock(dispatch_mutex_); + op_queue ops; + std::size_t n = queue.cancel_timer(timer, ops, max_cancelled); + post_deferred_completions(ops); + return n; +} + +template +void win_iocp_io_context::move_timer(timer_queue& queue, + typename timer_queue::per_timer_data& to, + typename timer_queue::per_timer_data& from) +{ + asio::detail::mutex::scoped_lock lock(dispatch_mutex_); + op_queue ops; + queue.cancel_timer(to, ops); + queue.move_timer(to, from); + lock.unlock(); + post_deferred_completions(ops); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_IMPL_WIN_IOCP_IO_CONTEXT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_iocp_io_context.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_iocp_io_context.ipp new file mode 100644 index 000000000..e7d8d7c38 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_iocp_io_context.ipp @@ -0,0 +1,603 @@ +// +// detail/impl/win_iocp_io_context.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_WIN_IOCP_IO_CONTEXT_IPP +#define ASIO_DETAIL_IMPL_WIN_IOCP_IO_CONTEXT_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/error.hpp" +#include "asio/detail/cstdint.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/limits.hpp" +#include "asio/detail/thread.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/detail/win_iocp_io_context.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +struct win_iocp_io_context::thread_function +{ + explicit thread_function(win_iocp_io_context* s) + : this_(s) + { + } + + void operator()() + { + asio::error_code ec; + this_->run(ec); + } + + win_iocp_io_context* this_; +}; + +struct win_iocp_io_context::work_finished_on_block_exit +{ + ~work_finished_on_block_exit() + { + io_context_->work_finished(); + } + + win_iocp_io_context* io_context_; +}; + +struct win_iocp_io_context::timer_thread_function +{ + void operator()() + { + while (::InterlockedExchangeAdd(&io_context_->shutdown_, 0) == 0) + { + if (::WaitForSingleObject(io_context_->waitable_timer_.handle, + INFINITE) == WAIT_OBJECT_0) + { + ::InterlockedExchange(&io_context_->dispatch_required_, 1); + ::PostQueuedCompletionStatus(io_context_->iocp_.handle, + 0, wake_for_dispatch, 0); + } + } + } + + win_iocp_io_context* io_context_; +}; + +win_iocp_io_context::win_iocp_io_context( + asio::execution_context& ctx, int concurrency_hint, bool own_thread) + : execution_context_service_base(ctx), + iocp_(), + outstanding_work_(0), + stopped_(0), + stop_event_posted_(0), + shutdown_(0), + gqcs_timeout_(get_gqcs_timeout()), + dispatch_required_(0), + concurrency_hint_(concurrency_hint) +{ + ASIO_HANDLER_TRACKING_INIT; + + iocp_.handle = ::CreateIoCompletionPort(INVALID_HANDLE_VALUE, 0, 0, + static_cast(concurrency_hint >= 0 ? concurrency_hint : DWORD(~0))); + if (!iocp_.handle) + { + DWORD last_error = ::GetLastError(); + asio::error_code ec(last_error, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "iocp"); + } + + if (own_thread) + { + ::InterlockedIncrement(&outstanding_work_); + thread_.reset(new asio::detail::thread(thread_function(this))); + } +} + +win_iocp_io_context::~win_iocp_io_context() +{ + if (thread_.get()) + { + stop(); + thread_->join(); + thread_.reset(); + } +} + +void win_iocp_io_context::shutdown() +{ + ::InterlockedExchange(&shutdown_, 1); + + if (timer_thread_.get()) + { + LARGE_INTEGER timeout; + timeout.QuadPart = 1; + ::SetWaitableTimer(waitable_timer_.handle, &timeout, 1, 0, 0, FALSE); + } + + if (thread_.get()) + { + stop(); + thread_->join(); + thread_.reset(); + ::InterlockedDecrement(&outstanding_work_); + } + + while (::InterlockedExchangeAdd(&outstanding_work_, 0) > 0) + { + op_queue ops; + timer_queues_.get_all_timers(ops); + ops.push(completed_ops_); + if (!ops.empty()) + { + while (win_iocp_operation* op = ops.front()) + { + ops.pop(); + ::InterlockedDecrement(&outstanding_work_); + op->destroy(); + } + } + else + { + DWORD bytes_transferred = 0; + dword_ptr_t completion_key = 0; + LPOVERLAPPED overlapped = 0; + ::GetQueuedCompletionStatus(iocp_.handle, &bytes_transferred, + &completion_key, &overlapped, gqcs_timeout_); + if (overlapped) + { + ::InterlockedDecrement(&outstanding_work_); + static_cast(overlapped)->destroy(); + } + } + } + + if (timer_thread_.get()) + timer_thread_->join(); +} + +asio::error_code win_iocp_io_context::register_handle( + HANDLE handle, asio::error_code& ec) +{ + if (::CreateIoCompletionPort(handle, iocp_.handle, 0, 0) == 0) + { + DWORD last_error = ::GetLastError(); + ec = asio::error_code(last_error, + asio::error::get_system_category()); + } + else + { + ec = asio::error_code(); + } + return ec; +} + +size_t win_iocp_io_context::run(asio::error_code& ec) +{ + if (::InterlockedExchangeAdd(&outstanding_work_, 0) == 0) + { + stop(); + ec = asio::error_code(); + return 0; + } + + win_iocp_thread_info this_thread; + thread_call_stack::context ctx(this, this_thread); + + size_t n = 0; + while (do_one(INFINITE, this_thread, ec)) + if (n != (std::numeric_limits::max)()) + ++n; + return n; +} + +size_t win_iocp_io_context::run_one(asio::error_code& ec) +{ + if (::InterlockedExchangeAdd(&outstanding_work_, 0) == 0) + { + stop(); + ec = asio::error_code(); + return 0; + } + + win_iocp_thread_info this_thread; + thread_call_stack::context ctx(this, this_thread); + + return do_one(INFINITE, this_thread, ec); +} + +size_t win_iocp_io_context::wait_one(long usec, asio::error_code& ec) +{ + if (::InterlockedExchangeAdd(&outstanding_work_, 0) == 0) + { + stop(); + ec = asio::error_code(); + return 0; + } + + win_iocp_thread_info this_thread; + thread_call_stack::context ctx(this, this_thread); + + return do_one(usec < 0 ? INFINITE : ((usec - 1) / 1000 + 1), this_thread, ec); +} + +size_t win_iocp_io_context::poll(asio::error_code& ec) +{ + if (::InterlockedExchangeAdd(&outstanding_work_, 0) == 0) + { + stop(); + ec = asio::error_code(); + return 0; + } + + win_iocp_thread_info this_thread; + thread_call_stack::context ctx(this, this_thread); + + size_t n = 0; + while (do_one(0, this_thread, ec)) + if (n != (std::numeric_limits::max)()) + ++n; + return n; +} + +size_t win_iocp_io_context::poll_one(asio::error_code& ec) +{ + if (::InterlockedExchangeAdd(&outstanding_work_, 0) == 0) + { + stop(); + ec = asio::error_code(); + return 0; + } + + win_iocp_thread_info this_thread; + thread_call_stack::context ctx(this, this_thread); + + return do_one(0, this_thread, ec); +} + +void win_iocp_io_context::stop() +{ + if (::InterlockedExchange(&stopped_, 1) == 0) + { + if (::InterlockedExchange(&stop_event_posted_, 1) == 0) + { + if (!::PostQueuedCompletionStatus(iocp_.handle, 0, 0, 0)) + { + DWORD last_error = ::GetLastError(); + asio::error_code ec(last_error, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "pqcs"); + } + } + } +} + +void win_iocp_io_context::capture_current_exception() +{ + if (thread_info_base* this_thread = thread_call_stack::contains(this)) + this_thread->capture_current_exception(); +} + +void win_iocp_io_context::post_deferred_completion(win_iocp_operation* op) +{ + // Flag the operation as ready. + op->ready_ = 1; + + // Enqueue the operation on the I/O completion port. + if (!::PostQueuedCompletionStatus(iocp_.handle, 0, 0, op)) + { + // Out of resources. Put on completed queue instead. + mutex::scoped_lock lock(dispatch_mutex_); + completed_ops_.push(op); + ::InterlockedExchange(&dispatch_required_, 1); + } +} + +void win_iocp_io_context::post_deferred_completions( + op_queue& ops) +{ + while (win_iocp_operation* op = ops.front()) + { + ops.pop(); + + // Flag the operation as ready. + op->ready_ = 1; + + // Enqueue the operation on the I/O completion port. + if (!::PostQueuedCompletionStatus(iocp_.handle, 0, 0, op)) + { + // Out of resources. Put on completed queue instead. + mutex::scoped_lock lock(dispatch_mutex_); + completed_ops_.push(op); + completed_ops_.push(ops); + ::InterlockedExchange(&dispatch_required_, 1); + } + } +} + +void win_iocp_io_context::abandon_operations( + op_queue& ops) +{ + while (win_iocp_operation* op = ops.front()) + { + ops.pop(); + ::InterlockedDecrement(&outstanding_work_); + op->destroy(); + } +} + +void win_iocp_io_context::on_pending(win_iocp_operation* op) +{ + if (::InterlockedCompareExchange(&op->ready_, 1, 0) == 1) + { + // Enqueue the operation on the I/O completion port. + if (!::PostQueuedCompletionStatus(iocp_.handle, + 0, overlapped_contains_result, op)) + { + // Out of resources. Put on completed queue instead. + mutex::scoped_lock lock(dispatch_mutex_); + completed_ops_.push(op); + ::InterlockedExchange(&dispatch_required_, 1); + } + } +} + +void win_iocp_io_context::on_completion(win_iocp_operation* op, + DWORD last_error, DWORD bytes_transferred) +{ + // Flag that the operation is ready for invocation. + op->ready_ = 1; + + // Store results in the OVERLAPPED structure. + op->Internal = reinterpret_cast( + &asio::error::get_system_category()); + op->Offset = last_error; + op->OffsetHigh = bytes_transferred; + + // Enqueue the operation on the I/O completion port. + if (!::PostQueuedCompletionStatus(iocp_.handle, + 0, overlapped_contains_result, op)) + { + // Out of resources. Put on completed queue instead. + mutex::scoped_lock lock(dispatch_mutex_); + completed_ops_.push(op); + ::InterlockedExchange(&dispatch_required_, 1); + } +} + +void win_iocp_io_context::on_completion(win_iocp_operation* op, + const asio::error_code& ec, DWORD bytes_transferred) +{ + // Flag that the operation is ready for invocation. + op->ready_ = 1; + + // Store results in the OVERLAPPED structure. + op->Internal = reinterpret_cast(&ec.category()); + op->Offset = ec.value(); + op->OffsetHigh = bytes_transferred; + + // Enqueue the operation on the I/O completion port. + if (!::PostQueuedCompletionStatus(iocp_.handle, + 0, overlapped_contains_result, op)) + { + // Out of resources. Put on completed queue instead. + mutex::scoped_lock lock(dispatch_mutex_); + completed_ops_.push(op); + ::InterlockedExchange(&dispatch_required_, 1); + } +} + +size_t win_iocp_io_context::do_one(DWORD msec, + win_iocp_thread_info& this_thread, asio::error_code& ec) +{ + for (;;) + { + // Try to acquire responsibility for dispatching timers and completed ops. + if (::InterlockedCompareExchange(&dispatch_required_, 0, 1) == 1) + { + mutex::scoped_lock lock(dispatch_mutex_); + + // Dispatch pending timers and operations. + op_queue ops; + ops.push(completed_ops_); + timer_queues_.get_ready_timers(ops); + post_deferred_completions(ops); + update_timeout(); + } + + // Get the next operation from the queue. + DWORD bytes_transferred = 0; + dword_ptr_t completion_key = 0; + LPOVERLAPPED overlapped = 0; + ::SetLastError(0); + BOOL ok = ::GetQueuedCompletionStatus(iocp_.handle, + &bytes_transferred, &completion_key, &overlapped, + msec < gqcs_timeout_ ? msec : gqcs_timeout_); + DWORD last_error = ::GetLastError(); + + if (overlapped) + { + win_iocp_operation* op = static_cast(overlapped); + asio::error_code result_ec(last_error, + asio::error::get_system_category()); + + // We may have been passed the last_error and bytes_transferred in the + // OVERLAPPED structure itself. + if (completion_key == overlapped_contains_result) + { + result_ec = asio::error_code(static_cast(op->Offset), + *reinterpret_cast(op->Internal)); + bytes_transferred = op->OffsetHigh; + } + + // Otherwise ensure any result has been saved into the OVERLAPPED + // structure. + else + { + op->Internal = reinterpret_cast(&result_ec.category()); + op->Offset = result_ec.value(); + op->OffsetHigh = bytes_transferred; + } + + // Dispatch the operation only if ready. The operation may not be ready + // if the initiating function (e.g. a call to WSARecv) has not yet + // returned. This is because the initiating function still wants access + // to the operation's OVERLAPPED structure. + if (::InterlockedCompareExchange(&op->ready_, 1, 0) == 1) + { + // Ensure the count of outstanding work is decremented on block exit. + work_finished_on_block_exit on_exit = { this }; + (void)on_exit; + + op->complete(this, result_ec, bytes_transferred); + this_thread.rethrow_pending_exception(); + ec = asio::error_code(); + return 1; + } + } + else if (!ok) + { + if (last_error != WAIT_TIMEOUT) + { + ec = asio::error_code(last_error, + asio::error::get_system_category()); + return 0; + } + + // If we're waiting indefinitely we need to keep going until we get a + // real handler. + if (msec == INFINITE) + continue; + + ec = asio::error_code(); + return 0; + } + else if (completion_key == wake_for_dispatch) + { + // We have been woken up to try to acquire responsibility for dispatching + // timers and completed operations. + } + else + { + // Indicate that there is no longer an in-flight stop event. + ::InterlockedExchange(&stop_event_posted_, 0); + + // The stopped_ flag is always checked to ensure that any leftover + // stop events from a previous run invocation are ignored. + if (::InterlockedExchangeAdd(&stopped_, 0) != 0) + { + // Wake up next thread that is blocked on GetQueuedCompletionStatus. + if (::InterlockedExchange(&stop_event_posted_, 1) == 0) + { + if (!::PostQueuedCompletionStatus(iocp_.handle, 0, 0, 0)) + { + last_error = ::GetLastError(); + ec = asio::error_code(last_error, + asio::error::get_system_category()); + return 0; + } + } + + ec = asio::error_code(); + return 0; + } + } + } +} + +DWORD win_iocp_io_context::get_gqcs_timeout() +{ + OSVERSIONINFOEX osvi; + ZeroMemory(&osvi, sizeof(osvi)); + osvi.dwOSVersionInfoSize = sizeof(osvi); + osvi.dwMajorVersion = 6ul; + + const uint64_t condition_mask = ::VerSetConditionMask( + 0, VER_MAJORVERSION, VER_GREATER_EQUAL); + + if (!!::VerifyVersionInfo(&osvi, VER_MAJORVERSION, condition_mask)) + return INFINITE; + + return default_gqcs_timeout; +} + +void win_iocp_io_context::do_add_timer_queue(timer_queue_base& queue) +{ + mutex::scoped_lock lock(dispatch_mutex_); + + timer_queues_.insert(&queue); + + if (!waitable_timer_.handle) + { + waitable_timer_.handle = ::CreateWaitableTimer(0, FALSE, 0); + if (waitable_timer_.handle == 0) + { + DWORD last_error = ::GetLastError(); + asio::error_code ec(last_error, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "timer"); + } + + LARGE_INTEGER timeout; + timeout.QuadPart = -max_timeout_usec; + timeout.QuadPart *= 10; + ::SetWaitableTimer(waitable_timer_.handle, + &timeout, max_timeout_msec, 0, 0, FALSE); + } + + if (!timer_thread_.get()) + { + timer_thread_function thread_function = { this }; + timer_thread_.reset(new thread(thread_function, 65536)); + } +} + +void win_iocp_io_context::do_remove_timer_queue(timer_queue_base& queue) +{ + mutex::scoped_lock lock(dispatch_mutex_); + + timer_queues_.erase(&queue); +} + +void win_iocp_io_context::update_timeout() +{ + if (timer_thread_.get()) + { + // There's no point updating the waitable timer if the new timeout period + // exceeds the maximum timeout. In that case, we might as well wait for the + // existing period of the timer to expire. + long timeout_usec = timer_queues_.wait_duration_usec(max_timeout_usec); + if (timeout_usec < max_timeout_usec) + { + LARGE_INTEGER timeout; + timeout.QuadPart = -timeout_usec; + timeout.QuadPart *= 10; + ::SetWaitableTimer(waitable_timer_.handle, + &timeout, max_timeout_msec, 0, 0, FALSE); + } + } +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_IMPL_WIN_IOCP_IO_CONTEXT_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_iocp_serial_port_service.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_iocp_serial_port_service.ipp new file mode 100644 index 000000000..7a4bc5af4 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_iocp_serial_port_service.ipp @@ -0,0 +1,192 @@ +// +// detail/impl/win_iocp_serial_port_service.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// Copyright (c) 2008 Rep Invariant Systems, Inc. (info@repinvariant.com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_WIN_IOCP_SERIAL_PORT_SERVICE_IPP +#define ASIO_DETAIL_IMPL_WIN_IOCP_SERIAL_PORT_SERVICE_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) && defined(ASIO_HAS_SERIAL_PORT) + +#include +#include "asio/detail/win_iocp_serial_port_service.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +win_iocp_serial_port_service::win_iocp_serial_port_service( + execution_context& context) + : execution_context_service_base(context), + handle_service_(context) +{ +} + +void win_iocp_serial_port_service::shutdown() +{ +} + +asio::error_code win_iocp_serial_port_service::open( + win_iocp_serial_port_service::implementation_type& impl, + const std::string& device, asio::error_code& ec) +{ + if (is_open(impl)) + { + ec = asio::error::already_open; + return ec; + } + + // For convenience, add a leading \\.\ sequence if not already present. + std::string name = (device[0] == '\\') ? device : "\\\\.\\" + device; + + // Open a handle to the serial port. + ::HANDLE handle = ::CreateFileA(name.c_str(), + GENERIC_READ | GENERIC_WRITE, 0, 0, + OPEN_EXISTING, FILE_FLAG_OVERLAPPED, 0); + if (handle == INVALID_HANDLE_VALUE) + { + DWORD last_error = ::GetLastError(); + ec = asio::error_code(last_error, + asio::error::get_system_category()); + return ec; + } + + // Determine the initial serial port parameters. + using namespace std; // For memset. + ::DCB dcb; + memset(&dcb, 0, sizeof(DCB)); + dcb.DCBlength = sizeof(DCB); + if (!::GetCommState(handle, &dcb)) + { + DWORD last_error = ::GetLastError(); + ::CloseHandle(handle); + ec = asio::error_code(last_error, + asio::error::get_system_category()); + return ec; + } + + // Set some default serial port parameters. This implementation does not + // support changing all of these, so they might as well be in a known state. + dcb.fBinary = TRUE; // Win32 only supports binary mode. + dcb.fNull = FALSE; // Do not ignore NULL characters. + dcb.fAbortOnError = FALSE; // Ignore serial framing errors. + dcb.BaudRate = CBR_9600; // 9600 baud by default + dcb.ByteSize = 8; // 8 bit bytes + dcb.fOutxCtsFlow = FALSE; // No flow control + dcb.fOutxDsrFlow = FALSE; + dcb.fDtrControl = DTR_CONTROL_DISABLE; + dcb.fDsrSensitivity = FALSE; + dcb.fOutX = FALSE; + dcb.fInX = FALSE; + dcb.fRtsControl = RTS_CONTROL_DISABLE; + dcb.fParity = FALSE; // No parity + dcb.Parity = NOPARITY; + dcb.StopBits = ONESTOPBIT; // One stop bit + if (!::SetCommState(handle, &dcb)) + { + DWORD last_error = ::GetLastError(); + ::CloseHandle(handle); + ec = asio::error_code(last_error, + asio::error::get_system_category()); + return ec; + } + + // Set up timeouts so that the serial port will behave similarly to a + // network socket. Reads wait for at least one byte, then return with + // whatever they have. Writes return once everything is out the door. + ::COMMTIMEOUTS timeouts; + timeouts.ReadIntervalTimeout = 1; + timeouts.ReadTotalTimeoutMultiplier = 0; + timeouts.ReadTotalTimeoutConstant = 0; + timeouts.WriteTotalTimeoutMultiplier = 0; + timeouts.WriteTotalTimeoutConstant = 0; + if (!::SetCommTimeouts(handle, &timeouts)) + { + DWORD last_error = ::GetLastError(); + ::CloseHandle(handle); + ec = asio::error_code(last_error, + asio::error::get_system_category()); + return ec; + } + + // We're done. Take ownership of the serial port handle. + if (handle_service_.assign(impl, handle, ec)) + ::CloseHandle(handle); + return ec; +} + +asio::error_code win_iocp_serial_port_service::do_set_option( + win_iocp_serial_port_service::implementation_type& impl, + win_iocp_serial_port_service::store_function_type store, + const void* option, asio::error_code& ec) +{ + using namespace std; // For memcpy. + + ::DCB dcb; + memset(&dcb, 0, sizeof(DCB)); + dcb.DCBlength = sizeof(DCB); + if (!::GetCommState(handle_service_.native_handle(impl), &dcb)) + { + DWORD last_error = ::GetLastError(); + ec = asio::error_code(last_error, + asio::error::get_system_category()); + return ec; + } + + if (store(option, dcb, ec)) + return ec; + + if (!::SetCommState(handle_service_.native_handle(impl), &dcb)) + { + DWORD last_error = ::GetLastError(); + ec = asio::error_code(last_error, + asio::error::get_system_category()); + return ec; + } + + ec = asio::error_code(); + return ec; +} + +asio::error_code win_iocp_serial_port_service::do_get_option( + const win_iocp_serial_port_service::implementation_type& impl, + win_iocp_serial_port_service::load_function_type load, + void* option, asio::error_code& ec) const +{ + using namespace std; // For memset. + + ::DCB dcb; + memset(&dcb, 0, sizeof(DCB)); + dcb.DCBlength = sizeof(DCB); + if (!::GetCommState(handle_service_.native_handle(impl), &dcb)) + { + DWORD last_error = ::GetLastError(); + ec = asio::error_code(last_error, + asio::error::get_system_category()); + return ec; + } + + return load(option, dcb, ec); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) && defined(ASIO_HAS_SERIAL_PORT) + +#endif // ASIO_DETAIL_IMPL_WIN_IOCP_SERIAL_PORT_SERVICE_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_iocp_socket_service_base.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_iocp_socket_service_base.ipp new file mode 100644 index 000000000..6235ce476 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_iocp_socket_service_base.ipp @@ -0,0 +1,801 @@ +// +// detail/impl/win_iocp_socket_service_base.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_WIN_IOCP_SOCKET_SERVICE_BASE_IPP +#define ASIO_DETAIL_IMPL_WIN_IOCP_SOCKET_SERVICE_BASE_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/detail/win_iocp_socket_service_base.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +win_iocp_socket_service_base::win_iocp_socket_service_base( + execution_context& context) + : context_(context), + iocp_service_(use_service(context)), + reactor_(0), + connect_ex_(0), + nt_set_info_(0), + mutex_(), + impl_list_(0) +{ +} + +void win_iocp_socket_service_base::base_shutdown() +{ + // Close all implementations, causing all operations to complete. + asio::detail::mutex::scoped_lock lock(mutex_); + base_implementation_type* impl = impl_list_; + while (impl) + { + close_for_destruction(*impl); + impl = impl->next_; + } +} + +void win_iocp_socket_service_base::construct( + win_iocp_socket_service_base::base_implementation_type& impl) +{ + impl.socket_ = invalid_socket; + impl.state_ = 0; + impl.cancel_token_.reset(); +#if defined(ASIO_ENABLE_CANCELIO) + impl.safe_cancellation_thread_id_ = 0; +#endif // defined(ASIO_ENABLE_CANCELIO) + + // Insert implementation into linked list of all implementations. + asio::detail::mutex::scoped_lock lock(mutex_); + impl.next_ = impl_list_; + impl.prev_ = 0; + if (impl_list_) + impl_list_->prev_ = &impl; + impl_list_ = &impl; +} + +void win_iocp_socket_service_base::base_move_construct( + win_iocp_socket_service_base::base_implementation_type& impl, + win_iocp_socket_service_base::base_implementation_type& other_impl) + ASIO_NOEXCEPT +{ + impl.socket_ = other_impl.socket_; + other_impl.socket_ = invalid_socket; + + impl.state_ = other_impl.state_; + other_impl.state_ = 0; + + impl.cancel_token_ = other_impl.cancel_token_; + other_impl.cancel_token_.reset(); + +#if defined(ASIO_ENABLE_CANCELIO) + impl.safe_cancellation_thread_id_ = other_impl.safe_cancellation_thread_id_; + other_impl.safe_cancellation_thread_id_ = 0; +#endif // defined(ASIO_ENABLE_CANCELIO) + + // Insert implementation into linked list of all implementations. + asio::detail::mutex::scoped_lock lock(mutex_); + impl.next_ = impl_list_; + impl.prev_ = 0; + if (impl_list_) + impl_list_->prev_ = &impl; + impl_list_ = &impl; +} + +void win_iocp_socket_service_base::base_move_assign( + win_iocp_socket_service_base::base_implementation_type& impl, + win_iocp_socket_service_base& other_service, + win_iocp_socket_service_base::base_implementation_type& other_impl) +{ + close_for_destruction(impl); + + if (this != &other_service) + { + // Remove implementation from linked list of all implementations. + asio::detail::mutex::scoped_lock lock(mutex_); + if (impl_list_ == &impl) + impl_list_ = impl.next_; + if (impl.prev_) + impl.prev_->next_ = impl.next_; + if (impl.next_) + impl.next_->prev_= impl.prev_; + impl.next_ = 0; + impl.prev_ = 0; + } + + impl.socket_ = other_impl.socket_; + other_impl.socket_ = invalid_socket; + + impl.state_ = other_impl.state_; + other_impl.state_ = 0; + + impl.cancel_token_ = other_impl.cancel_token_; + other_impl.cancel_token_.reset(); + +#if defined(ASIO_ENABLE_CANCELIO) + impl.safe_cancellation_thread_id_ = other_impl.safe_cancellation_thread_id_; + other_impl.safe_cancellation_thread_id_ = 0; +#endif // defined(ASIO_ENABLE_CANCELIO) + + if (this != &other_service) + { + // Insert implementation into linked list of all implementations. + asio::detail::mutex::scoped_lock lock(other_service.mutex_); + impl.next_ = other_service.impl_list_; + impl.prev_ = 0; + if (other_service.impl_list_) + other_service.impl_list_->prev_ = &impl; + other_service.impl_list_ = &impl; + } +} + +void win_iocp_socket_service_base::destroy( + win_iocp_socket_service_base::base_implementation_type& impl) +{ + close_for_destruction(impl); + + // Remove implementation from linked list of all implementations. + asio::detail::mutex::scoped_lock lock(mutex_); + if (impl_list_ == &impl) + impl_list_ = impl.next_; + if (impl.prev_) + impl.prev_->next_ = impl.next_; + if (impl.next_) + impl.next_->prev_= impl.prev_; + impl.next_ = 0; + impl.prev_ = 0; +} + +asio::error_code win_iocp_socket_service_base::close( + win_iocp_socket_service_base::base_implementation_type& impl, + asio::error_code& ec) +{ + if (is_open(impl)) + { + ASIO_HANDLER_OPERATION((iocp_service_.context(), + "socket", &impl, impl.socket_, "close")); + + // Check if the reactor was created, in which case we need to close the + // socket on the reactor as well to cancel any operations that might be + // running there. + select_reactor* r = static_cast( + interlocked_compare_exchange_pointer( + reinterpret_cast(&reactor_), 0, 0)); + if (r) + r->deregister_descriptor(impl.socket_, impl.reactor_data_, true); + + socket_ops::close(impl.socket_, impl.state_, false, ec); + + if (r) + r->cleanup_descriptor_data(impl.reactor_data_); + } + else + { + ec = asio::error_code(); + } + + impl.socket_ = invalid_socket; + impl.state_ = 0; + impl.cancel_token_.reset(); +#if defined(ASIO_ENABLE_CANCELIO) + impl.safe_cancellation_thread_id_ = 0; +#endif // defined(ASIO_ENABLE_CANCELIO) + + return ec; +} + +socket_type win_iocp_socket_service_base::release( + win_iocp_socket_service_base::base_implementation_type& impl, + asio::error_code& ec) +{ + if (!is_open(impl)) + return invalid_socket; + + cancel(impl, ec); + if (ec) + return invalid_socket; + + nt_set_info_fn fn = get_nt_set_info(); + if (fn == 0) + { + ec = asio::error::operation_not_supported; + return invalid_socket; + } + + HANDLE sock_as_handle = reinterpret_cast(impl.socket_); + ULONG_PTR iosb[2] = { 0, 0 }; + void* info[2] = { 0, 0 }; + if (fn(sock_as_handle, iosb, &info, sizeof(info), + 61 /* FileReplaceCompletionInformation */)) + { + ec = asio::error::operation_not_supported; + return invalid_socket; + } + + socket_type tmp = impl.socket_; + impl.socket_ = invalid_socket; + return tmp; +} + +asio::error_code win_iocp_socket_service_base::cancel( + win_iocp_socket_service_base::base_implementation_type& impl, + asio::error_code& ec) +{ + if (!is_open(impl)) + { + ec = asio::error::bad_descriptor; + return ec; + } + + ASIO_HANDLER_OPERATION((iocp_service_.context(), + "socket", &impl, impl.socket_, "cancel")); + + if (FARPROC cancel_io_ex_ptr = ::GetProcAddress( + ::GetModuleHandleA("KERNEL32"), "CancelIoEx")) + { + // The version of Windows supports cancellation from any thread. + typedef BOOL (WINAPI* cancel_io_ex_t)(HANDLE, LPOVERLAPPED); + cancel_io_ex_t cancel_io_ex = reinterpret_cast( + reinterpret_cast(cancel_io_ex_ptr)); + socket_type sock = impl.socket_; + HANDLE sock_as_handle = reinterpret_cast(sock); + if (!cancel_io_ex(sock_as_handle, 0)) + { + DWORD last_error = ::GetLastError(); + if (last_error == ERROR_NOT_FOUND) + { + // ERROR_NOT_FOUND means that there were no operations to be + // cancelled. We swallow this error to match the behaviour on other + // platforms. + ec = asio::error_code(); + } + else + { + ec = asio::error_code(last_error, + asio::error::get_system_category()); + } + } + else + { + ec = asio::error_code(); + } + } +#if defined(ASIO_ENABLE_CANCELIO) + else if (impl.safe_cancellation_thread_id_ == 0) + { + // No operations have been started, so there's nothing to cancel. + ec = asio::error_code(); + } + else if (impl.safe_cancellation_thread_id_ == ::GetCurrentThreadId()) + { + // Asynchronous operations have been started from the current thread only, + // so it is safe to try to cancel them using CancelIo. + socket_type sock = impl.socket_; + HANDLE sock_as_handle = reinterpret_cast(sock); + if (!::CancelIo(sock_as_handle)) + { + DWORD last_error = ::GetLastError(); + ec = asio::error_code(last_error, + asio::error::get_system_category()); + } + else + { + ec = asio::error_code(); + } + } + else + { + // Asynchronous operations have been started from more than one thread, + // so cancellation is not safe. + ec = asio::error::operation_not_supported; + } +#else // defined(ASIO_ENABLE_CANCELIO) + else + { + // Cancellation is not supported as CancelIo may not be used. + ec = asio::error::operation_not_supported; + } +#endif // defined(ASIO_ENABLE_CANCELIO) + + // Cancel any operations started via the reactor. + if (!ec) + { + select_reactor* r = static_cast( + interlocked_compare_exchange_pointer( + reinterpret_cast(&reactor_), 0, 0)); + if (r) + r->cancel_ops(impl.socket_, impl.reactor_data_); + } + + return ec; +} + +asio::error_code win_iocp_socket_service_base::do_open( + win_iocp_socket_service_base::base_implementation_type& impl, + int family, int type, int protocol, asio::error_code& ec) +{ + if (is_open(impl)) + { + ec = asio::error::already_open; + return ec; + } + + socket_holder sock(socket_ops::socket(family, type, protocol, ec)); + if (sock.get() == invalid_socket) + return ec; + + HANDLE sock_as_handle = reinterpret_cast(sock.get()); + if (iocp_service_.register_handle(sock_as_handle, ec)) + return ec; + + impl.socket_ = sock.release(); + switch (type) + { + case SOCK_STREAM: impl.state_ = socket_ops::stream_oriented; break; + case SOCK_DGRAM: impl.state_ = socket_ops::datagram_oriented; break; + default: impl.state_ = 0; break; + } + impl.cancel_token_.reset(static_cast(0), socket_ops::noop_deleter()); + ec = asio::error_code(); + return ec; +} + +asio::error_code win_iocp_socket_service_base::do_assign( + win_iocp_socket_service_base::base_implementation_type& impl, + int type, socket_type native_socket, asio::error_code& ec) +{ + if (is_open(impl)) + { + ec = asio::error::already_open; + return ec; + } + + HANDLE sock_as_handle = reinterpret_cast(native_socket); + if (iocp_service_.register_handle(sock_as_handle, ec)) + return ec; + + impl.socket_ = native_socket; + switch (type) + { + case SOCK_STREAM: impl.state_ = socket_ops::stream_oriented; break; + case SOCK_DGRAM: impl.state_ = socket_ops::datagram_oriented; break; + default: impl.state_ = 0; break; + } + impl.cancel_token_.reset(static_cast(0), socket_ops::noop_deleter()); + ec = asio::error_code(); + return ec; +} + +void win_iocp_socket_service_base::start_send_op( + win_iocp_socket_service_base::base_implementation_type& impl, + WSABUF* buffers, std::size_t buffer_count, + socket_base::message_flags flags, bool noop, operation* op) +{ + update_cancellation_thread_id(impl); + iocp_service_.work_started(); + + if (noop) + iocp_service_.on_completion(op); + else if (!is_open(impl)) + iocp_service_.on_completion(op, asio::error::bad_descriptor); + else + { + DWORD bytes_transferred = 0; + int result = ::WSASend(impl.socket_, buffers, + static_cast(buffer_count), &bytes_transferred, flags, op, 0); + DWORD last_error = ::WSAGetLastError(); + if (last_error == ERROR_PORT_UNREACHABLE) + last_error = WSAECONNREFUSED; + if (result != 0 && last_error != WSA_IO_PENDING) + iocp_service_.on_completion(op, last_error, bytes_transferred); + else + iocp_service_.on_pending(op); + } +} + +void win_iocp_socket_service_base::start_send_to_op( + win_iocp_socket_service_base::base_implementation_type& impl, + WSABUF* buffers, std::size_t buffer_count, + const socket_addr_type* addr, int addrlen, + socket_base::message_flags flags, operation* op) +{ + update_cancellation_thread_id(impl); + iocp_service_.work_started(); + + if (!is_open(impl)) + iocp_service_.on_completion(op, asio::error::bad_descriptor); + else + { + DWORD bytes_transferred = 0; + int result = ::WSASendTo(impl.socket_, buffers, + static_cast(buffer_count), + &bytes_transferred, flags, addr, addrlen, op, 0); + DWORD last_error = ::WSAGetLastError(); + if (last_error == ERROR_PORT_UNREACHABLE) + last_error = WSAECONNREFUSED; + if (result != 0 && last_error != WSA_IO_PENDING) + iocp_service_.on_completion(op, last_error, bytes_transferred); + else + iocp_service_.on_pending(op); + } +} + +void win_iocp_socket_service_base::start_receive_op( + win_iocp_socket_service_base::base_implementation_type& impl, + WSABUF* buffers, std::size_t buffer_count, + socket_base::message_flags flags, bool noop, operation* op) +{ + update_cancellation_thread_id(impl); + iocp_service_.work_started(); + + if (noop) + iocp_service_.on_completion(op); + else if (!is_open(impl)) + iocp_service_.on_completion(op, asio::error::bad_descriptor); + else + { + DWORD bytes_transferred = 0; + DWORD recv_flags = flags; + int result = ::WSARecv(impl.socket_, buffers, + static_cast(buffer_count), + &bytes_transferred, &recv_flags, op, 0); + DWORD last_error = ::WSAGetLastError(); + if (last_error == ERROR_NETNAME_DELETED) + last_error = WSAECONNRESET; + else if (last_error == ERROR_PORT_UNREACHABLE) + last_error = WSAECONNREFUSED; + if (result != 0 && last_error != WSA_IO_PENDING) + iocp_service_.on_completion(op, last_error, bytes_transferred); + else + iocp_service_.on_pending(op); + } +} + +void win_iocp_socket_service_base::start_null_buffers_receive_op( + win_iocp_socket_service_base::base_implementation_type& impl, + socket_base::message_flags flags, reactor_op* op) +{ + if ((impl.state_ & socket_ops::stream_oriented) != 0) + { + // For stream sockets on Windows, we may issue a 0-byte overlapped + // WSARecv to wait until there is data available on the socket. + ::WSABUF buf = { 0, 0 }; + start_receive_op(impl, &buf, 1, flags, false, op); + } + else + { + start_reactor_op(impl, + (flags & socket_base::message_out_of_band) + ? select_reactor::except_op : select_reactor::read_op, + op); + } +} + +void win_iocp_socket_service_base::start_receive_from_op( + win_iocp_socket_service_base::base_implementation_type& impl, + WSABUF* buffers, std::size_t buffer_count, socket_addr_type* addr, + socket_base::message_flags flags, int* addrlen, operation* op) +{ + update_cancellation_thread_id(impl); + iocp_service_.work_started(); + + if (!is_open(impl)) + iocp_service_.on_completion(op, asio::error::bad_descriptor); + else + { + DWORD bytes_transferred = 0; + DWORD recv_flags = flags; + int result = ::WSARecvFrom(impl.socket_, buffers, + static_cast(buffer_count), + &bytes_transferred, &recv_flags, addr, addrlen, op, 0); + DWORD last_error = ::WSAGetLastError(); + if (last_error == ERROR_PORT_UNREACHABLE) + last_error = WSAECONNREFUSED; + if (result != 0 && last_error != WSA_IO_PENDING) + iocp_service_.on_completion(op, last_error, bytes_transferred); + else + iocp_service_.on_pending(op); + } +} + +void win_iocp_socket_service_base::start_accept_op( + win_iocp_socket_service_base::base_implementation_type& impl, + bool peer_is_open, socket_holder& new_socket, int family, int type, + int protocol, void* output_buffer, DWORD address_length, operation* op) +{ + update_cancellation_thread_id(impl); + iocp_service_.work_started(); + + if (!is_open(impl)) + iocp_service_.on_completion(op, asio::error::bad_descriptor); + else if (peer_is_open) + iocp_service_.on_completion(op, asio::error::already_open); + else + { + asio::error_code ec; + new_socket.reset(socket_ops::socket(family, type, protocol, ec)); + if (new_socket.get() == invalid_socket) + iocp_service_.on_completion(op, ec); + else + { + DWORD bytes_read = 0; + BOOL result = ::AcceptEx(impl.socket_, new_socket.get(), output_buffer, + 0, address_length, address_length, &bytes_read, op); + DWORD last_error = ::WSAGetLastError(); + if (!result && last_error != WSA_IO_PENDING) + iocp_service_.on_completion(op, last_error); + else + iocp_service_.on_pending(op); + } + } +} + +void win_iocp_socket_service_base::restart_accept_op( + socket_type s, socket_holder& new_socket, int family, int type, + int protocol, void* output_buffer, DWORD address_length, operation* op) +{ + new_socket.reset(); + iocp_service_.work_started(); + + asio::error_code ec; + new_socket.reset(socket_ops::socket(family, type, protocol, ec)); + if (new_socket.get() == invalid_socket) + iocp_service_.on_completion(op, ec); + else + { + DWORD bytes_read = 0; + BOOL result = ::AcceptEx(s, new_socket.get(), output_buffer, + 0, address_length, address_length, &bytes_read, op); + DWORD last_error = ::WSAGetLastError(); + if (!result && last_error != WSA_IO_PENDING) + iocp_service_.on_completion(op, last_error); + else + iocp_service_.on_pending(op); + } +} + +void win_iocp_socket_service_base::start_reactor_op( + win_iocp_socket_service_base::base_implementation_type& impl, + int op_type, reactor_op* op) +{ + select_reactor& r = get_reactor(); + update_cancellation_thread_id(impl); + + if (is_open(impl)) + { + r.start_op(op_type, impl.socket_, impl.reactor_data_, op, false, false); + return; + } + else + op->ec_ = asio::error::bad_descriptor; + + iocp_service_.post_immediate_completion(op, false); +} + +void win_iocp_socket_service_base::start_connect_op( + win_iocp_socket_service_base::base_implementation_type& impl, + int family, int type, const socket_addr_type* addr, + std::size_t addrlen, win_iocp_socket_connect_op_base* op) +{ + // If ConnectEx is available, use that. + if (family == ASIO_OS_DEF(AF_INET) + || family == ASIO_OS_DEF(AF_INET6)) + { + if (connect_ex_fn connect_ex = get_connect_ex(impl, type)) + { + union address_union + { + socket_addr_type base; + sockaddr_in4_type v4; + sockaddr_in6_type v6; + } a; + + using namespace std; // For memset. + memset(&a, 0, sizeof(a)); + a.base.sa_family = family; + + socket_ops::bind(impl.socket_, &a.base, + family == ASIO_OS_DEF(AF_INET) + ? sizeof(a.v4) : sizeof(a.v6), op->ec_); + if (op->ec_ && op->ec_ != asio::error::invalid_argument) + { + iocp_service_.post_immediate_completion(op, false); + return; + } + + op->connect_ex_ = true; + update_cancellation_thread_id(impl); + iocp_service_.work_started(); + + BOOL result = connect_ex(impl.socket_, + addr, static_cast(addrlen), 0, 0, 0, op); + DWORD last_error = ::WSAGetLastError(); + if (!result && last_error != WSA_IO_PENDING) + iocp_service_.on_completion(op, last_error); + else + iocp_service_.on_pending(op); + return; + } + } + + // Otherwise, fall back to a reactor-based implementation. + select_reactor& r = get_reactor(); + update_cancellation_thread_id(impl); + + if ((impl.state_ & socket_ops::non_blocking) != 0 + || socket_ops::set_internal_non_blocking( + impl.socket_, impl.state_, true, op->ec_)) + { + if (socket_ops::connect(impl.socket_, addr, addrlen, op->ec_) != 0) + { + if (op->ec_ == asio::error::in_progress + || op->ec_ == asio::error::would_block) + { + op->ec_ = asio::error_code(); + r.start_op(select_reactor::connect_op, impl.socket_, + impl.reactor_data_, op, false, false); + return; + } + } + } + + r.post_immediate_completion(op, false); +} + +void win_iocp_socket_service_base::close_for_destruction( + win_iocp_socket_service_base::base_implementation_type& impl) +{ + if (is_open(impl)) + { + ASIO_HANDLER_OPERATION((iocp_service_.context(), + "socket", &impl, impl.socket_, "close")); + + // Check if the reactor was created, in which case we need to close the + // socket on the reactor as well to cancel any operations that might be + // running there. + select_reactor* r = static_cast( + interlocked_compare_exchange_pointer( + reinterpret_cast(&reactor_), 0, 0)); + if (r) + r->deregister_descriptor(impl.socket_, impl.reactor_data_, true); + + asio::error_code ignored_ec; + socket_ops::close(impl.socket_, impl.state_, true, ignored_ec); + + if (r) + r->cleanup_descriptor_data(impl.reactor_data_); + } + + impl.socket_ = invalid_socket; + impl.state_ = 0; + impl.cancel_token_.reset(); +#if defined(ASIO_ENABLE_CANCELIO) + impl.safe_cancellation_thread_id_ = 0; +#endif // defined(ASIO_ENABLE_CANCELIO) +} + +void win_iocp_socket_service_base::update_cancellation_thread_id( + win_iocp_socket_service_base::base_implementation_type& impl) +{ +#if defined(ASIO_ENABLE_CANCELIO) + if (impl.safe_cancellation_thread_id_ == 0) + impl.safe_cancellation_thread_id_ = ::GetCurrentThreadId(); + else if (impl.safe_cancellation_thread_id_ != ::GetCurrentThreadId()) + impl.safe_cancellation_thread_id_ = ~DWORD(0); +#else // defined(ASIO_ENABLE_CANCELIO) + (void)impl; +#endif // defined(ASIO_ENABLE_CANCELIO) +} + +select_reactor& win_iocp_socket_service_base::get_reactor() +{ + select_reactor* r = static_cast( + interlocked_compare_exchange_pointer( + reinterpret_cast(&reactor_), 0, 0)); + if (!r) + { + r = &(use_service(context_)); + interlocked_exchange_pointer(reinterpret_cast(&reactor_), r); + } + return *r; +} + +win_iocp_socket_service_base::connect_ex_fn +win_iocp_socket_service_base::get_connect_ex( + win_iocp_socket_service_base::base_implementation_type& impl, int type) +{ +#if defined(ASIO_DISABLE_CONNECTEX) + (void)impl; + (void)type; + return 0; +#else // defined(ASIO_DISABLE_CONNECTEX) + if (type != ASIO_OS_DEF(SOCK_STREAM) + && type != ASIO_OS_DEF(SOCK_SEQPACKET)) + return 0; + + void* ptr = interlocked_compare_exchange_pointer(&connect_ex_, 0, 0); + if (!ptr) + { + GUID guid = { 0x25a207b9, 0xddf3, 0x4660, + { 0x8e, 0xe9, 0x76, 0xe5, 0x8c, 0x74, 0x06, 0x3e } }; + + DWORD bytes = 0; + if (::WSAIoctl(impl.socket_, SIO_GET_EXTENSION_FUNCTION_POINTER, + &guid, sizeof(guid), &ptr, sizeof(ptr), &bytes, 0, 0) != 0) + { + // Set connect_ex_ to a special value to indicate that ConnectEx is + // unavailable. That way we won't bother trying to look it up again. + ptr = this; + } + + interlocked_exchange_pointer(&connect_ex_, ptr); + } + + return reinterpret_cast(ptr == this ? 0 : ptr); +#endif // defined(ASIO_DISABLE_CONNECTEX) +} + +win_iocp_socket_service_base::nt_set_info_fn +win_iocp_socket_service_base::get_nt_set_info() +{ + void* ptr = interlocked_compare_exchange_pointer(&nt_set_info_, 0, 0); + if (!ptr) + { + if (HMODULE h = ::GetModuleHandleA("NTDLL.DLL")) + ptr = reinterpret_cast(GetProcAddress(h, "NtSetInformationFile")); + + // On failure, set nt_set_info_ to a special value to indicate that the + // NtSetInformationFile function is unavailable. That way we won't bother + // trying to look it up again. + interlocked_exchange_pointer(&nt_set_info_, ptr ? ptr : this); + } + + return reinterpret_cast(ptr == this ? 0 : ptr); +} + +void* win_iocp_socket_service_base::interlocked_compare_exchange_pointer( + void** dest, void* exch, void* cmp) +{ +#if defined(_M_IX86) + return reinterpret_cast(InterlockedCompareExchange( + reinterpret_cast(dest), reinterpret_cast(exch), + reinterpret_cast(cmp))); +#else + return InterlockedCompareExchangePointer(dest, exch, cmp); +#endif +} + +void* win_iocp_socket_service_base::interlocked_exchange_pointer( + void** dest, void* val) +{ +#if defined(_M_IX86) + return reinterpret_cast(InterlockedExchange( + reinterpret_cast(dest), reinterpret_cast(val))); +#else + return InterlockedExchangePointer(dest, val); +#endif +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_IMPL_WIN_IOCP_SOCKET_SERVICE_BASE_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_mutex.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_mutex.ipp new file mode 100644 index 000000000..e5088c601 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_mutex.ipp @@ -0,0 +1,84 @@ +// +// detail/impl/win_mutex.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_WIN_MUTEX_IPP +#define ASIO_DETAIL_IMPL_WIN_MUTEX_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) + +#include "asio/detail/throw_error.hpp" +#include "asio/detail/win_mutex.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +win_mutex::win_mutex() +{ + int error = do_init(); + asio::error_code ec(error, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "mutex"); +} + +int win_mutex::do_init() +{ +#if defined(__MINGW32__) + // Not sure if MinGW supports structured exception handling, so for now + // we'll just call the Windows API and hope. +# if defined(UNDER_CE) + ::InitializeCriticalSection(&crit_section_); +# elif defined(ASIO_WINDOWS_APP) + if (!::InitializeCriticalSectionEx(&crit_section_, 0, 0)) + return ::GetLastError(); +# else + if (!::InitializeCriticalSectionAndSpinCount(&crit_section_, 0x80000000)) + return ::GetLastError(); +# endif + return 0; +#else + __try + { +# if defined(UNDER_CE) + ::InitializeCriticalSection(&crit_section_); +# elif defined(ASIO_WINDOWS_APP) + if (!::InitializeCriticalSectionEx(&crit_section_, 0, 0)) + return ::GetLastError(); +# else + if (!::InitializeCriticalSectionAndSpinCount(&crit_section_, 0x80000000)) + return ::GetLastError(); +# endif + } + __except(GetExceptionCode() == STATUS_NO_MEMORY + ? EXCEPTION_EXECUTE_HANDLER : EXCEPTION_CONTINUE_SEARCH) + { + return ERROR_OUTOFMEMORY; + } + + return 0; +#endif +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS) + +#endif // ASIO_DETAIL_IMPL_WIN_MUTEX_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_object_handle_service.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_object_handle_service.ipp new file mode 100644 index 000000000..0e80edc07 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_object_handle_service.ipp @@ -0,0 +1,448 @@ +// +// detail/impl/win_object_handle_service.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// Copyright (c) 2011 Boris Schaeling (boris@highscore.de) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_WIN_OBJECT_HANDLE_SERVICE_IPP +#define ASIO_DETAIL_IMPL_WIN_OBJECT_HANDLE_SERVICE_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_WINDOWS_OBJECT_HANDLE) + +#include "asio/detail/win_object_handle_service.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +win_object_handle_service::win_object_handle_service(execution_context& context) + : execution_context_service_base(context), + scheduler_(asio::use_service(context)), + mutex_(), + impl_list_(0), + shutdown_(false) +{ +} + +void win_object_handle_service::shutdown() +{ + mutex::scoped_lock lock(mutex_); + + // Setting this flag to true prevents new objects from being registered, and + // new asynchronous wait operations from being started. We only need to worry + // about cleaning up the operations that are currently in progress. + shutdown_ = true; + + op_queue ops; + for (implementation_type* impl = impl_list_; impl; impl = impl->next_) + ops.push(impl->op_queue_); + + lock.unlock(); + + scheduler_.abandon_operations(ops); +} + +void win_object_handle_service::construct( + win_object_handle_service::implementation_type& impl) +{ + impl.handle_ = INVALID_HANDLE_VALUE; + impl.wait_handle_ = INVALID_HANDLE_VALUE; + impl.owner_ = this; + + // Insert implementation into linked list of all implementations. + mutex::scoped_lock lock(mutex_); + if (!shutdown_) + { + impl.next_ = impl_list_; + impl.prev_ = 0; + if (impl_list_) + impl_list_->prev_ = &impl; + impl_list_ = &impl; + } +} + +void win_object_handle_service::move_construct( + win_object_handle_service::implementation_type& impl, + win_object_handle_service::implementation_type& other_impl) +{ + mutex::scoped_lock lock(mutex_); + + // Insert implementation into linked list of all implementations. + if (!shutdown_) + { + impl.next_ = impl_list_; + impl.prev_ = 0; + if (impl_list_) + impl_list_->prev_ = &impl; + impl_list_ = &impl; + } + + impl.handle_ = other_impl.handle_; + other_impl.handle_ = INVALID_HANDLE_VALUE; + impl.wait_handle_ = other_impl.wait_handle_; + other_impl.wait_handle_ = INVALID_HANDLE_VALUE; + impl.op_queue_.push(other_impl.op_queue_); + impl.owner_ = this; + + // We must not hold the lock while calling UnregisterWaitEx. This is because + // the registered callback function might be invoked while we are waiting for + // UnregisterWaitEx to complete. + lock.unlock(); + + if (impl.wait_handle_ != INVALID_HANDLE_VALUE) + ::UnregisterWaitEx(impl.wait_handle_, INVALID_HANDLE_VALUE); + + if (!impl.op_queue_.empty()) + register_wait_callback(impl, lock); +} + +void win_object_handle_service::move_assign( + win_object_handle_service::implementation_type& impl, + win_object_handle_service& other_service, + win_object_handle_service::implementation_type& other_impl) +{ + asio::error_code ignored_ec; + close(impl, ignored_ec); + + mutex::scoped_lock lock(mutex_); + + if (this != &other_service) + { + // Remove implementation from linked list of all implementations. + if (impl_list_ == &impl) + impl_list_ = impl.next_; + if (impl.prev_) + impl.prev_->next_ = impl.next_; + if (impl.next_) + impl.next_->prev_= impl.prev_; + impl.next_ = 0; + impl.prev_ = 0; + } + + impl.handle_ = other_impl.handle_; + other_impl.handle_ = INVALID_HANDLE_VALUE; + impl.wait_handle_ = other_impl.wait_handle_; + other_impl.wait_handle_ = INVALID_HANDLE_VALUE; + impl.op_queue_.push(other_impl.op_queue_); + impl.owner_ = this; + + if (this != &other_service) + { + // Insert implementation into linked list of all implementations. + impl.next_ = other_service.impl_list_; + impl.prev_ = 0; + if (other_service.impl_list_) + other_service.impl_list_->prev_ = &impl; + other_service.impl_list_ = &impl; + } + + // We must not hold the lock while calling UnregisterWaitEx. This is because + // the registered callback function might be invoked while we are waiting for + // UnregisterWaitEx to complete. + lock.unlock(); + + if (impl.wait_handle_ != INVALID_HANDLE_VALUE) + ::UnregisterWaitEx(impl.wait_handle_, INVALID_HANDLE_VALUE); + + if (!impl.op_queue_.empty()) + register_wait_callback(impl, lock); +} + +void win_object_handle_service::destroy( + win_object_handle_service::implementation_type& impl) +{ + mutex::scoped_lock lock(mutex_); + + // Remove implementation from linked list of all implementations. + if (impl_list_ == &impl) + impl_list_ = impl.next_; + if (impl.prev_) + impl.prev_->next_ = impl.next_; + if (impl.next_) + impl.next_->prev_= impl.prev_; + impl.next_ = 0; + impl.prev_ = 0; + + if (is_open(impl)) + { + ASIO_HANDLER_OPERATION((scheduler_.context(), "object_handle", + &impl, reinterpret_cast(impl.wait_handle_), "close")); + + HANDLE wait_handle = impl.wait_handle_; + impl.wait_handle_ = INVALID_HANDLE_VALUE; + + op_queue ops; + while (wait_op* op = impl.op_queue_.front()) + { + op->ec_ = asio::error::operation_aborted; + impl.op_queue_.pop(); + ops.push(op); + } + + // We must not hold the lock while calling UnregisterWaitEx. This is + // because the registered callback function might be invoked while we are + // waiting for UnregisterWaitEx to complete. + lock.unlock(); + + if (wait_handle != INVALID_HANDLE_VALUE) + ::UnregisterWaitEx(wait_handle, INVALID_HANDLE_VALUE); + + ::CloseHandle(impl.handle_); + impl.handle_ = INVALID_HANDLE_VALUE; + + scheduler_.post_deferred_completions(ops); + } +} + +asio::error_code win_object_handle_service::assign( + win_object_handle_service::implementation_type& impl, + const native_handle_type& handle, asio::error_code& ec) +{ + if (is_open(impl)) + { + ec = asio::error::already_open; + return ec; + } + + impl.handle_ = handle; + ec = asio::error_code(); + return ec; +} + +asio::error_code win_object_handle_service::close( + win_object_handle_service::implementation_type& impl, + asio::error_code& ec) +{ + if (is_open(impl)) + { + ASIO_HANDLER_OPERATION((scheduler_.context(), "object_handle", + &impl, reinterpret_cast(impl.wait_handle_), "close")); + + mutex::scoped_lock lock(mutex_); + + HANDLE wait_handle = impl.wait_handle_; + impl.wait_handle_ = INVALID_HANDLE_VALUE; + + op_queue completed_ops; + while (wait_op* op = impl.op_queue_.front()) + { + impl.op_queue_.pop(); + op->ec_ = asio::error::operation_aborted; + completed_ops.push(op); + } + + // We must not hold the lock while calling UnregisterWaitEx. This is + // because the registered callback function might be invoked while we are + // waiting for UnregisterWaitEx to complete. + lock.unlock(); + + if (wait_handle != INVALID_HANDLE_VALUE) + ::UnregisterWaitEx(wait_handle, INVALID_HANDLE_VALUE); + + if (::CloseHandle(impl.handle_)) + { + impl.handle_ = INVALID_HANDLE_VALUE; + ec = asio::error_code(); + } + else + { + DWORD last_error = ::GetLastError(); + ec = asio::error_code(last_error, + asio::error::get_system_category()); + } + + scheduler_.post_deferred_completions(completed_ops); + } + else + { + ec = asio::error_code(); + } + + return ec; +} + +asio::error_code win_object_handle_service::cancel( + win_object_handle_service::implementation_type& impl, + asio::error_code& ec) +{ + if (is_open(impl)) + { + ASIO_HANDLER_OPERATION((scheduler_.context(), "object_handle", + &impl, reinterpret_cast(impl.wait_handle_), "cancel")); + + mutex::scoped_lock lock(mutex_); + + HANDLE wait_handle = impl.wait_handle_; + impl.wait_handle_ = INVALID_HANDLE_VALUE; + + op_queue completed_ops; + while (wait_op* op = impl.op_queue_.front()) + { + op->ec_ = asio::error::operation_aborted; + impl.op_queue_.pop(); + completed_ops.push(op); + } + + // We must not hold the lock while calling UnregisterWaitEx. This is + // because the registered callback function might be invoked while we are + // waiting for UnregisterWaitEx to complete. + lock.unlock(); + + if (wait_handle != INVALID_HANDLE_VALUE) + ::UnregisterWaitEx(wait_handle, INVALID_HANDLE_VALUE); + + ec = asio::error_code(); + + scheduler_.post_deferred_completions(completed_ops); + } + else + { + ec = asio::error::bad_descriptor; + } + + return ec; +} + +void win_object_handle_service::wait( + win_object_handle_service::implementation_type& impl, + asio::error_code& ec) +{ + switch (::WaitForSingleObject(impl.handle_, INFINITE)) + { + case WAIT_FAILED: + { + DWORD last_error = ::GetLastError(); + ec = asio::error_code(last_error, + asio::error::get_system_category()); + break; + } + case WAIT_OBJECT_0: + case WAIT_ABANDONED: + default: + ec = asio::error_code(); + break; + } +} + +void win_object_handle_service::start_wait_op( + win_object_handle_service::implementation_type& impl, wait_op* op) +{ + scheduler_.work_started(); + + if (is_open(impl)) + { + mutex::scoped_lock lock(mutex_); + + if (!shutdown_) + { + impl.op_queue_.push(op); + + // Only the first operation to be queued gets to register a wait callback. + // Subsequent operations have to wait for the first to finish. + if (impl.op_queue_.front() == op) + register_wait_callback(impl, lock); + } + else + { + lock.unlock(); + scheduler_.post_deferred_completion(op); + } + } + else + { + op->ec_ = asio::error::bad_descriptor; + scheduler_.post_deferred_completion(op); + } +} + +void win_object_handle_service::register_wait_callback( + win_object_handle_service::implementation_type& impl, + mutex::scoped_lock& lock) +{ + lock.lock(); + + if (!RegisterWaitForSingleObject(&impl.wait_handle_, + impl.handle_, &win_object_handle_service::wait_callback, + &impl, INFINITE, WT_EXECUTEONLYONCE)) + { + DWORD last_error = ::GetLastError(); + asio::error_code ec(last_error, + asio::error::get_system_category()); + + op_queue completed_ops; + while (wait_op* op = impl.op_queue_.front()) + { + op->ec_ = ec; + impl.op_queue_.pop(); + completed_ops.push(op); + } + + lock.unlock(); + scheduler_.post_deferred_completions(completed_ops); + } +} + +void win_object_handle_service::wait_callback(PVOID param, BOOLEAN) +{ + implementation_type* impl = static_cast(param); + mutex::scoped_lock lock(impl->owner_->mutex_); + + if (impl->wait_handle_ != INVALID_HANDLE_VALUE) + { + ::UnregisterWaitEx(impl->wait_handle_, NULL); + impl->wait_handle_ = INVALID_HANDLE_VALUE; + } + + if (wait_op* op = impl->op_queue_.front()) + { + op_queue completed_ops; + + op->ec_ = asio::error_code(); + impl->op_queue_.pop(); + completed_ops.push(op); + + if (!impl->op_queue_.empty()) + { + if (!RegisterWaitForSingleObject(&impl->wait_handle_, + impl->handle_, &win_object_handle_service::wait_callback, + param, INFINITE, WT_EXECUTEONLYONCE)) + { + DWORD last_error = ::GetLastError(); + asio::error_code ec(last_error, + asio::error::get_system_category()); + + while ((op = impl->op_queue_.front()) != 0) + { + op->ec_ = ec; + impl->op_queue_.pop(); + completed_ops.push(op); + } + } + } + + scheduler_impl& sched = impl->owner_->scheduler_; + lock.unlock(); + sched.post_deferred_completions(completed_ops); + } +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_WINDOWS_OBJECT_HANDLE) + +#endif // ASIO_DETAIL_IMPL_WIN_OBJECT_HANDLE_SERVICE_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_static_mutex.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_static_mutex.ipp new file mode 100644 index 000000000..0b6a6e2f1 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_static_mutex.ipp @@ -0,0 +1,136 @@ +// +// detail/impl/win_static_mutex.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_WIN_STATIC_MUTEX_IPP +#define ASIO_DETAIL_IMPL_WIN_STATIC_MUTEX_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) + +#include +#include "asio/detail/throw_error.hpp" +#include "asio/detail/win_static_mutex.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +void win_static_mutex::init() +{ + int error = do_init(); + asio::error_code ec(error, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "static_mutex"); +} + +int win_static_mutex::do_init() +{ + using namespace std; // For sprintf. + wchar_t mutex_name[128]; +#if defined(ASIO_HAS_SECURE_RTL) + swprintf_s( +#else // defined(ASIO_HAS_SECURE_RTL) + _snwprintf( +#endif // defined(ASIO_HAS_SECURE_RTL) + mutex_name, 128, L"asio-58CCDC44-6264-4842-90C2-F3C545CB8AA7-%u-%p", + static_cast(::GetCurrentProcessId()), this); + +#if defined(ASIO_WINDOWS_APP) + HANDLE mutex = ::CreateMutexExW(0, mutex_name, CREATE_MUTEX_INITIAL_OWNER, 0); +#else // defined(ASIO_WINDOWS_APP) + HANDLE mutex = ::CreateMutexW(0, TRUE, mutex_name); +#endif // defined(ASIO_WINDOWS_APP) + DWORD last_error = ::GetLastError(); + if (mutex == 0) + return ::GetLastError(); + + if (last_error == ERROR_ALREADY_EXISTS) + { +#if defined(ASIO_WINDOWS_APP) + ::WaitForSingleObjectEx(mutex, INFINITE, false); +#else // defined(ASIO_WINDOWS_APP) + ::WaitForSingleObject(mutex, INFINITE); +#endif // defined(ASIO_WINDOWS_APP) + } + + if (initialised_) + { + ::ReleaseMutex(mutex); + ::CloseHandle(mutex); + return 0; + } + +#if defined(__MINGW32__) + // Not sure if MinGW supports structured exception handling, so for now + // we'll just call the Windows API and hope. +# if defined(UNDER_CE) + ::InitializeCriticalSection(&crit_section_); +# else + if (!::InitializeCriticalSectionAndSpinCount(&crit_section_, 0x80000000)) + { + last_error = ::GetLastError(); + ::ReleaseMutex(mutex); + ::CloseHandle(mutex); + return last_error; + } +# endif +#else + __try + { +# if defined(UNDER_CE) + ::InitializeCriticalSection(&crit_section_); +# elif defined(ASIO_WINDOWS_APP) + if (!::InitializeCriticalSectionEx(&crit_section_, 0, 0)) + { + last_error = ::GetLastError(); + ::ReleaseMutex(mutex); + ::CloseHandle(mutex); + return last_error; + } +# else + if (!::InitializeCriticalSectionAndSpinCount(&crit_section_, 0x80000000)) + { + last_error = ::GetLastError(); + ::ReleaseMutex(mutex); + ::CloseHandle(mutex); + return last_error; + } +# endif + } + __except(GetExceptionCode() == STATUS_NO_MEMORY + ? EXCEPTION_EXECUTE_HANDLER : EXCEPTION_CONTINUE_SEARCH) + { + ::ReleaseMutex(mutex); + ::CloseHandle(mutex); + return ERROR_OUTOFMEMORY; + } +#endif + + initialised_ = true; + ::ReleaseMutex(mutex); + ::CloseHandle(mutex); + return 0; +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS) + +#endif // ASIO_DETAIL_IMPL_WIN_STATIC_MUTEX_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_thread.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_thread.ipp new file mode 100644 index 000000000..d2ef02f66 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_thread.ipp @@ -0,0 +1,150 @@ +// +// detail/impl/win_thread.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_WIN_THREAD_IPP +#define ASIO_DETAIL_IMPL_WIN_THREAD_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_APP) \ + && !defined(UNDER_CE) + +#include +#include "asio/detail/throw_error.hpp" +#include "asio/detail/win_thread.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +win_thread::~win_thread() +{ + ::CloseHandle(thread_); + + // The exit_event_ handle is deliberately allowed to leak here since it + // is an error for the owner of an internal thread not to join() it. +} + +void win_thread::join() +{ + HANDLE handles[2] = { exit_event_, thread_ }; + ::WaitForMultipleObjects(2, handles, FALSE, INFINITE); + ::CloseHandle(exit_event_); + if (terminate_threads()) + { + ::TerminateThread(thread_, 0); + } + else + { + ::QueueUserAPC(apc_function, thread_, 0); + ::WaitForSingleObject(thread_, INFINITE); + } +} + +std::size_t win_thread::hardware_concurrency() +{ + SYSTEM_INFO system_info; + ::GetSystemInfo(&system_info); + return system_info.dwNumberOfProcessors; +} + +void win_thread::start_thread(func_base* arg, unsigned int stack_size) +{ + ::HANDLE entry_event = 0; + arg->entry_event_ = entry_event = ::CreateEventW(0, true, false, 0); + if (!entry_event) + { + DWORD last_error = ::GetLastError(); + delete arg; + asio::error_code ec(last_error, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "thread.entry_event"); + } + + arg->exit_event_ = exit_event_ = ::CreateEventW(0, true, false, 0); + if (!exit_event_) + { + DWORD last_error = ::GetLastError(); + delete arg; + asio::error_code ec(last_error, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "thread.exit_event"); + } + + unsigned int thread_id = 0; + thread_ = reinterpret_cast(::_beginthreadex(0, + stack_size, win_thread_function, arg, 0, &thread_id)); + if (!thread_) + { + DWORD last_error = ::GetLastError(); + delete arg; + if (entry_event) + ::CloseHandle(entry_event); + if (exit_event_) + ::CloseHandle(exit_event_); + asio::error_code ec(last_error, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "thread"); + } + + if (entry_event) + { + ::WaitForSingleObject(entry_event, INFINITE); + ::CloseHandle(entry_event); + } +} + +unsigned int __stdcall win_thread_function(void* arg) +{ + win_thread::auto_func_base_ptr func = { + static_cast(arg) }; + + ::SetEvent(func.ptr->entry_event_); + + func.ptr->run(); + + // Signal that the thread has finished its work, but rather than returning go + // to sleep to put the thread into a well known state. If the thread is being + // joined during global object destruction then it may be killed using + // TerminateThread (to avoid a deadlock in DllMain). Otherwise, the SleepEx + // call will be interrupted using QueueUserAPC and the thread will shut down + // cleanly. + HANDLE exit_event = func.ptr->exit_event_; + delete func.ptr; + func.ptr = 0; + ::SetEvent(exit_event); + ::SleepEx(INFINITE, TRUE); + + return 0; +} + +#if defined(WINVER) && (WINVER < 0x0500) +void __stdcall apc_function(ULONG) {} +#else +void __stdcall apc_function(ULONG_PTR) {} +#endif + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_APP) + // && !defined(UNDER_CE) + +#endif // ASIO_DETAIL_IMPL_WIN_THREAD_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_tss_ptr.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_tss_ptr.ipp new file mode 100644 index 000000000..e90c628ce --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/win_tss_ptr.ipp @@ -0,0 +1,57 @@ +// +// detail/impl/win_tss_ptr.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_WIN_TSS_PTR_IPP +#define ASIO_DETAIL_IMPL_WIN_TSS_PTR_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) + +#include "asio/detail/throw_error.hpp" +#include "asio/detail/win_tss_ptr.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +DWORD win_tss_ptr_create() +{ +#if defined(UNDER_CE) + const DWORD out_of_indexes = 0xFFFFFFFF; +#else + const DWORD out_of_indexes = TLS_OUT_OF_INDEXES; +#endif + + DWORD tss_key = ::TlsAlloc(); + if (tss_key == out_of_indexes) + { + DWORD last_error = ::GetLastError(); + asio::error_code ec(last_error, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "tss"); + } + return tss_key; +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS) + +#endif // ASIO_DETAIL_IMPL_WIN_TSS_PTR_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/winrt_ssocket_service_base.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/winrt_ssocket_service_base.ipp new file mode 100644 index 000000000..66d3f7762 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/winrt_ssocket_service_base.ipp @@ -0,0 +1,626 @@ +// +// detail/impl/winrt_ssocket_service_base.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_WINRT_SSOCKET_SERVICE_BASE_IPP +#define ASIO_DETAIL_IMPL_WINRT_SSOCKET_SERVICE_BASE_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) + +#include +#include "asio/detail/winrt_ssocket_service_base.hpp" +#include "asio/detail/winrt_async_op.hpp" +#include "asio/detail/winrt_utils.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +winrt_ssocket_service_base::winrt_ssocket_service_base( + execution_context& context) + : scheduler_(use_service(context)), + async_manager_(use_service(context)), + mutex_(), + impl_list_(0) +{ +} + +void winrt_ssocket_service_base::base_shutdown() +{ + // Close all implementations, causing all operations to complete. + asio::detail::mutex::scoped_lock lock(mutex_); + base_implementation_type* impl = impl_list_; + while (impl) + { + asio::error_code ignored_ec; + close(*impl, ignored_ec); + impl = impl->next_; + } +} + +void winrt_ssocket_service_base::construct( + winrt_ssocket_service_base::base_implementation_type& impl) +{ + // Insert implementation into linked list of all implementations. + asio::detail::mutex::scoped_lock lock(mutex_); + impl.next_ = impl_list_; + impl.prev_ = 0; + if (impl_list_) + impl_list_->prev_ = &impl; + impl_list_ = &impl; +} + +void winrt_ssocket_service_base::base_move_construct( + winrt_ssocket_service_base::base_implementation_type& impl, + winrt_ssocket_service_base::base_implementation_type& other_impl) + ASIO_NOEXCEPT +{ + impl.socket_ = other_impl.socket_; + other_impl.socket_ = nullptr; + + // Insert implementation into linked list of all implementations. + asio::detail::mutex::scoped_lock lock(mutex_); + impl.next_ = impl_list_; + impl.prev_ = 0; + if (impl_list_) + impl_list_->prev_ = &impl; + impl_list_ = &impl; +} + +void winrt_ssocket_service_base::base_move_assign( + winrt_ssocket_service_base::base_implementation_type& impl, + winrt_ssocket_service_base& other_service, + winrt_ssocket_service_base::base_implementation_type& other_impl) +{ + asio::error_code ignored_ec; + close(impl, ignored_ec); + + if (this != &other_service) + { + // Remove implementation from linked list of all implementations. + asio::detail::mutex::scoped_lock lock(mutex_); + if (impl_list_ == &impl) + impl_list_ = impl.next_; + if (impl.prev_) + impl.prev_->next_ = impl.next_; + if (impl.next_) + impl.next_->prev_= impl.prev_; + impl.next_ = 0; + impl.prev_ = 0; + } + + impl.socket_ = other_impl.socket_; + other_impl.socket_ = nullptr; + + if (this != &other_service) + { + // Insert implementation into linked list of all implementations. + asio::detail::mutex::scoped_lock lock(other_service.mutex_); + impl.next_ = other_service.impl_list_; + impl.prev_ = 0; + if (other_service.impl_list_) + other_service.impl_list_->prev_ = &impl; + other_service.impl_list_ = &impl; + } +} + +void winrt_ssocket_service_base::destroy( + winrt_ssocket_service_base::base_implementation_type& impl) +{ + asio::error_code ignored_ec; + close(impl, ignored_ec); + + // Remove implementation from linked list of all implementations. + asio::detail::mutex::scoped_lock lock(mutex_); + if (impl_list_ == &impl) + impl_list_ = impl.next_; + if (impl.prev_) + impl.prev_->next_ = impl.next_; + if (impl.next_) + impl.next_->prev_= impl.prev_; + impl.next_ = 0; + impl.prev_ = 0; +} + +asio::error_code winrt_ssocket_service_base::close( + winrt_ssocket_service_base::base_implementation_type& impl, + asio::error_code& ec) +{ + delete impl.socket_; + impl.socket_ = nullptr; + ec = asio::error_code(); + return ec; +} + +winrt_ssocket_service_base::native_handle_type +winrt_ssocket_service_base::release( + winrt_ssocket_service_base::base_implementation_type& impl, + asio::error_code& ec) +{ + if (!is_open(impl)) + return nullptr; + + cancel(impl, ec); + if (ec) + return nullptr; + + native_handle_type tmp = impl.socket_; + impl.socket_ = nullptr; + return tmp; +} + +std::size_t winrt_ssocket_service_base::do_get_endpoint( + const base_implementation_type& impl, bool local, + void* addr, std::size_t addr_len, asio::error_code& ec) const +{ + if (!is_open(impl)) + { + ec = asio::error::bad_descriptor; + return addr_len; + } + + try + { + std::string addr_string = winrt_utils::string(local + ? impl.socket_->Information->LocalAddress->CanonicalName + : impl.socket_->Information->RemoteAddress->CanonicalName); + unsigned short port = winrt_utils::integer(local + ? impl.socket_->Information->LocalPort + : impl.socket_->Information->RemotePort); + unsigned long scope = 0; + + switch (reinterpret_cast(addr)->sa_family) + { + case ASIO_OS_DEF(AF_INET): + if (addr_len < sizeof(sockaddr_in4_type)) + { + ec = asio::error::invalid_argument; + return addr_len; + } + else + { + socket_ops::inet_pton(ASIO_OS_DEF(AF_INET), addr_string.c_str(), + &reinterpret_cast(addr)->sin_addr, &scope, ec); + reinterpret_cast(addr)->sin_port + = socket_ops::host_to_network_short(port); + ec = asio::error_code(); + return sizeof(sockaddr_in4_type); + } + case ASIO_OS_DEF(AF_INET6): + if (addr_len < sizeof(sockaddr_in6_type)) + { + ec = asio::error::invalid_argument; + return addr_len; + } + else + { + socket_ops::inet_pton(ASIO_OS_DEF(AF_INET6), addr_string.c_str(), + &reinterpret_cast(addr)->sin6_addr, &scope, ec); + reinterpret_cast(addr)->sin6_port + = socket_ops::host_to_network_short(port); + ec = asio::error_code(); + return sizeof(sockaddr_in6_type); + } + default: + ec = asio::error::address_family_not_supported; + return addr_len; + } + } + catch (Platform::Exception^ e) + { + ec = asio::error_code(e->HResult, + asio::system_category()); + return addr_len; + } +} + +asio::error_code winrt_ssocket_service_base::do_set_option( + winrt_ssocket_service_base::base_implementation_type& impl, + int level, int optname, const void* optval, + std::size_t optlen, asio::error_code& ec) +{ + if (!is_open(impl)) + { + ec = asio::error::bad_descriptor; + return ec; + } + + try + { + if (level == ASIO_OS_DEF(SOL_SOCKET) + && optname == ASIO_OS_DEF(SO_KEEPALIVE)) + { + if (optlen == sizeof(int)) + { + int value = 0; + std::memcpy(&value, optval, optlen); + impl.socket_->Control->KeepAlive = !!value; + ec = asio::error_code(); + } + else + { + ec = asio::error::invalid_argument; + } + } + else if (level == ASIO_OS_DEF(IPPROTO_TCP) + && optname == ASIO_OS_DEF(TCP_NODELAY)) + { + if (optlen == sizeof(int)) + { + int value = 0; + std::memcpy(&value, optval, optlen); + impl.socket_->Control->NoDelay = !!value; + ec = asio::error_code(); + } + else + { + ec = asio::error::invalid_argument; + } + } + else + { + ec = asio::error::invalid_argument; + } + } + catch (Platform::Exception^ e) + { + ec = asio::error_code(e->HResult, + asio::system_category()); + } + + return ec; +} + +void winrt_ssocket_service_base::do_get_option( + const winrt_ssocket_service_base::base_implementation_type& impl, + int level, int optname, void* optval, + std::size_t* optlen, asio::error_code& ec) const +{ + if (!is_open(impl)) + { + ec = asio::error::bad_descriptor; + return; + } + + try + { + if (level == ASIO_OS_DEF(SOL_SOCKET) + && optname == ASIO_OS_DEF(SO_KEEPALIVE)) + { + if (*optlen >= sizeof(int)) + { + int value = impl.socket_->Control->KeepAlive ? 1 : 0; + std::memcpy(optval, &value, sizeof(int)); + *optlen = sizeof(int); + ec = asio::error_code(); + } + else + { + ec = asio::error::invalid_argument; + } + } + else if (level == ASIO_OS_DEF(IPPROTO_TCP) + && optname == ASIO_OS_DEF(TCP_NODELAY)) + { + if (*optlen >= sizeof(int)) + { + int value = impl.socket_->Control->NoDelay ? 1 : 0; + std::memcpy(optval, &value, sizeof(int)); + *optlen = sizeof(int); + ec = asio::error_code(); + } + else + { + ec = asio::error::invalid_argument; + } + } + else + { + ec = asio::error::invalid_argument; + } + } + catch (Platform::Exception^ e) + { + ec = asio::error_code(e->HResult, + asio::system_category()); + } +} + +asio::error_code winrt_ssocket_service_base::do_connect( + winrt_ssocket_service_base::base_implementation_type& impl, + const void* addr, asio::error_code& ec) +{ + if (!is_open(impl)) + { + ec = asio::error::bad_descriptor; + return ec; + } + + char addr_string[max_addr_v6_str_len]; + unsigned short port; + switch (reinterpret_cast(addr)->sa_family) + { + case ASIO_OS_DEF(AF_INET): + socket_ops::inet_ntop(ASIO_OS_DEF(AF_INET), + &reinterpret_cast(addr)->sin_addr, + addr_string, sizeof(addr_string), 0, ec); + port = socket_ops::network_to_host_short( + reinterpret_cast(addr)->sin_port); + break; + case ASIO_OS_DEF(AF_INET6): + socket_ops::inet_ntop(ASIO_OS_DEF(AF_INET6), + &reinterpret_cast(addr)->sin6_addr, + addr_string, sizeof(addr_string), 0, ec); + port = socket_ops::network_to_host_short( + reinterpret_cast(addr)->sin6_port); + break; + default: + ec = asio::error::address_family_not_supported; + return ec; + } + + if (!ec) try + { + async_manager_.sync(impl.socket_->ConnectAsync( + ref new Windows::Networking::HostName( + winrt_utils::string(addr_string)), + winrt_utils::string(port)), ec); + } + catch (Platform::Exception^ e) + { + ec = asio::error_code(e->HResult, + asio::system_category()); + } + + return ec; +} + +void winrt_ssocket_service_base::start_connect_op( + winrt_ssocket_service_base::base_implementation_type& impl, + const void* addr, winrt_async_op* op, bool is_continuation) +{ + if (!is_open(impl)) + { + op->ec_ = asio::error::bad_descriptor; + scheduler_.post_immediate_completion(op, is_continuation); + return; + } + + char addr_string[max_addr_v6_str_len]; + unsigned short port = 0; + switch (reinterpret_cast(addr)->sa_family) + { + case ASIO_OS_DEF(AF_INET): + socket_ops::inet_ntop(ASIO_OS_DEF(AF_INET), + &reinterpret_cast(addr)->sin_addr, + addr_string, sizeof(addr_string), 0, op->ec_); + port = socket_ops::network_to_host_short( + reinterpret_cast(addr)->sin_port); + break; + case ASIO_OS_DEF(AF_INET6): + socket_ops::inet_ntop(ASIO_OS_DEF(AF_INET6), + &reinterpret_cast(addr)->sin6_addr, + addr_string, sizeof(addr_string), 0, op->ec_); + port = socket_ops::network_to_host_short( + reinterpret_cast(addr)->sin6_port); + break; + default: + op->ec_ = asio::error::address_family_not_supported; + break; + } + + if (op->ec_) + { + scheduler_.post_immediate_completion(op, is_continuation); + return; + } + + try + { + async_manager_.async(impl.socket_->ConnectAsync( + ref new Windows::Networking::HostName( + winrt_utils::string(addr_string)), + winrt_utils::string(port)), op); + } + catch (Platform::Exception^ e) + { + op->ec_ = asio::error_code( + e->HResult, asio::system_category()); + scheduler_.post_immediate_completion(op, is_continuation); + } +} + +std::size_t winrt_ssocket_service_base::do_send( + winrt_ssocket_service_base::base_implementation_type& impl, + const asio::const_buffer& data, + socket_base::message_flags flags, asio::error_code& ec) +{ + if (flags) + { + ec = asio::error::operation_not_supported; + return 0; + } + + if (!is_open(impl)) + { + ec = asio::error::bad_descriptor; + return 0; + } + + try + { + buffer_sequence_adapter bufs(asio::buffer(data)); + + if (bufs.all_empty()) + { + ec = asio::error_code(); + return 0; + } + + return async_manager_.sync( + impl.socket_->OutputStream->WriteAsync(bufs.buffers()[0]), ec); + } + catch (Platform::Exception^ e) + { + ec = asio::error_code(e->HResult, + asio::system_category()); + return 0; + } +} + +void winrt_ssocket_service_base::start_send_op( + winrt_ssocket_service_base::base_implementation_type& impl, + const asio::const_buffer& data, socket_base::message_flags flags, + winrt_async_op* op, bool is_continuation) +{ + if (flags) + { + op->ec_ = asio::error::operation_not_supported; + scheduler_.post_immediate_completion(op, is_continuation); + return; + } + + if (!is_open(impl)) + { + op->ec_ = asio::error::bad_descriptor; + scheduler_.post_immediate_completion(op, is_continuation); + return; + } + + try + { + buffer_sequence_adapter bufs(asio::buffer(data)); + + if (bufs.all_empty()) + { + scheduler_.post_immediate_completion(op, is_continuation); + return; + } + + async_manager_.async( + impl.socket_->OutputStream->WriteAsync(bufs.buffers()[0]), op); + } + catch (Platform::Exception^ e) + { + op->ec_ = asio::error_code(e->HResult, + asio::system_category()); + scheduler_.post_immediate_completion(op, is_continuation); + } +} + +std::size_t winrt_ssocket_service_base::do_receive( + winrt_ssocket_service_base::base_implementation_type& impl, + const asio::mutable_buffer& data, + socket_base::message_flags flags, asio::error_code& ec) +{ + if (flags) + { + ec = asio::error::operation_not_supported; + return 0; + } + + if (!is_open(impl)) + { + ec = asio::error::bad_descriptor; + return 0; + } + + try + { + buffer_sequence_adapter bufs(asio::buffer(data)); + + if (bufs.all_empty()) + { + ec = asio::error_code(); + return 0; + } + + async_manager_.sync( + impl.socket_->InputStream->ReadAsync( + bufs.buffers()[0], bufs.buffers()[0]->Capacity, + Windows::Storage::Streams::InputStreamOptions::Partial), ec); + + std::size_t bytes_transferred = bufs.buffers()[0]->Length; + if (bytes_transferred == 0 && !ec) + { + ec = asio::error::eof; + } + + return bytes_transferred; + } + catch (Platform::Exception^ e) + { + ec = asio::error_code(e->HResult, + asio::system_category()); + return 0; + } +} + +void winrt_ssocket_service_base::start_receive_op( + winrt_ssocket_service_base::base_implementation_type& impl, + const asio::mutable_buffer& data, socket_base::message_flags flags, + winrt_async_op* op, + bool is_continuation) +{ + if (flags) + { + op->ec_ = asio::error::operation_not_supported; + scheduler_.post_immediate_completion(op, is_continuation); + return; + } + + if (!is_open(impl)) + { + op->ec_ = asio::error::bad_descriptor; + scheduler_.post_immediate_completion(op, is_continuation); + return; + } + + try + { + buffer_sequence_adapter bufs(asio::buffer(data)); + + if (bufs.all_empty()) + { + scheduler_.post_immediate_completion(op, is_continuation); + return; + } + + async_manager_.async( + impl.socket_->InputStream->ReadAsync( + bufs.buffers()[0], bufs.buffers()[0]->Capacity, + Windows::Storage::Streams::InputStreamOptions::Partial), op); + } + catch (Platform::Exception^ e) + { + op->ec_ = asio::error_code(e->HResult, + asio::system_category()); + scheduler_.post_immediate_completion(op, is_continuation); + } +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_IMPL_WINRT_SSOCKET_SERVICE_BASE_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/winrt_timer_scheduler.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/winrt_timer_scheduler.hpp new file mode 100644 index 000000000..17bcc821b --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/winrt_timer_scheduler.hpp @@ -0,0 +1,92 @@ +// +// detail/impl/winrt_timer_scheduler.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_WINRT_TIMER_SCHEDULER_HPP +#define ASIO_DETAIL_IMPL_WINRT_TIMER_SCHEDULER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +void winrt_timer_scheduler::add_timer_queue(timer_queue& queue) +{ + do_add_timer_queue(queue); +} + +// Remove a timer queue from the reactor. +template +void winrt_timer_scheduler::remove_timer_queue(timer_queue& queue) +{ + do_remove_timer_queue(queue); +} + +template +void winrt_timer_scheduler::schedule_timer(timer_queue& queue, + const typename Time_Traits::time_type& time, + typename timer_queue::per_timer_data& timer, wait_op* op) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + + if (shutdown_) + { + scheduler_.post_immediate_completion(op, false); + return; + } + + bool earliest = queue.enqueue_timer(time, timer, op); + scheduler_.work_started(); + if (earliest) + event_.signal(lock); +} + +template +std::size_t winrt_timer_scheduler::cancel_timer(timer_queue& queue, + typename timer_queue::per_timer_data& timer, + std::size_t max_cancelled) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + op_queue ops; + std::size_t n = queue.cancel_timer(timer, ops, max_cancelled); + lock.unlock(); + scheduler_.post_deferred_completions(ops); + return n; +} + +template +void winrt_timer_scheduler::move_timer(timer_queue& queue, + typename timer_queue::per_timer_data& to, + typename timer_queue::per_timer_data& from) +{ + asio::detail::mutex::scoped_lock lock(mutex_); + op_queue ops; + queue.cancel_timer(to, ops); + queue.move_timer(to, from); + lock.unlock(); + scheduler_.post_deferred_completions(ops); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_IMPL_WINRT_TIMER_SCHEDULER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/winrt_timer_scheduler.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/winrt_timer_scheduler.ipp new file mode 100644 index 000000000..91042661b --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/winrt_timer_scheduler.ipp @@ -0,0 +1,121 @@ +// +// detail/impl/winrt_timer_scheduler.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_WINRT_TIMER_SCHEDULER_IPP +#define ASIO_DETAIL_IMPL_WINRT_TIMER_SCHEDULER_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/winrt_timer_scheduler.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +winrt_timer_scheduler::winrt_timer_scheduler(execution_context& context) + : execution_context_service_base(context), + scheduler_(use_service(context)), + mutex_(), + event_(), + timer_queues_(), + thread_(0), + stop_thread_(false), + shutdown_(false) +{ + thread_ = new asio::detail::thread( + bind_handler(&winrt_timer_scheduler::call_run_thread, this)); +} + +winrt_timer_scheduler::~winrt_timer_scheduler() +{ + shutdown(); +} + +void winrt_timer_scheduler::shutdown() +{ + asio::detail::mutex::scoped_lock lock(mutex_); + shutdown_ = true; + stop_thread_ = true; + event_.signal(lock); + lock.unlock(); + + if (thread_) + { + thread_->join(); + delete thread_; + thread_ = 0; + } + + op_queue ops; + timer_queues_.get_all_timers(ops); + scheduler_.abandon_operations(ops); +} + +void winrt_timer_scheduler::notify_fork(execution_context::fork_event) +{ +} + +void winrt_timer_scheduler::init_task() +{ +} + +void winrt_timer_scheduler::run_thread() +{ + asio::detail::mutex::scoped_lock lock(mutex_); + while (!stop_thread_) + { + const long max_wait_duration = 5 * 60 * 1000000; + long wait_duration = timer_queues_.wait_duration_usec(max_wait_duration); + event_.wait_for_usec(lock, wait_duration); + event_.clear(lock); + op_queue ops; + timer_queues_.get_ready_timers(ops); + if (!ops.empty()) + { + lock.unlock(); + scheduler_.post_deferred_completions(ops); + lock.lock(); + } + } +} + +void winrt_timer_scheduler::call_run_thread(winrt_timer_scheduler* scheduler) +{ + scheduler->run_thread(); +} + +void winrt_timer_scheduler::do_add_timer_queue(timer_queue_base& queue) +{ + mutex::scoped_lock lock(mutex_); + timer_queues_.insert(&queue); +} + +void winrt_timer_scheduler::do_remove_timer_queue(timer_queue_base& queue) +{ + mutex::scoped_lock lock(mutex_); + timer_queues_.erase(&queue); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_IMPL_WINRT_TIMER_SCHEDULER_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/winsock_init.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/winsock_init.ipp new file mode 100644 index 000000000..f5943401b --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/impl/winsock_init.ipp @@ -0,0 +1,82 @@ +// +// detail/impl/winsock_init.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IMPL_WINSOCK_INIT_IPP +#define ASIO_DETAIL_IMPL_WINSOCK_INIT_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +#include "asio/detail/socket_types.hpp" +#include "asio/detail/winsock_init.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +void winsock_init_base::startup(data& d, + unsigned char major, unsigned char minor) +{ + if (::InterlockedIncrement(&d.init_count_) == 1) + { + WSADATA wsa_data; + long result = ::WSAStartup(MAKEWORD(major, minor), &wsa_data); + ::InterlockedExchange(&d.result_, result); + } +} + +void winsock_init_base::manual_startup(data& d) +{ + if (::InterlockedIncrement(&d.init_count_) == 1) + { + ::InterlockedExchange(&d.result_, 0); + } +} + +void winsock_init_base::cleanup(data& d) +{ + if (::InterlockedDecrement(&d.init_count_) == 0) + { + ::WSACleanup(); + } +} + +void winsock_init_base::manual_cleanup(data& d) +{ + ::InterlockedDecrement(&d.init_count_); +} + +void winsock_init_base::throw_on_error(data& d) +{ + long result = ::InterlockedExchangeAdd(&d.result_, 0); + if (result != 0) + { + asio::error_code ec(result, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "winsock"); + } +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +#endif // ASIO_DETAIL_IMPL_WINSOCK_INIT_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/io_control.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/io_control.hpp new file mode 100644 index 000000000..0e5de4a92 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/io_control.hpp @@ -0,0 +1,84 @@ +// +// detail/io_control.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IO_CONTROL_HPP +#define ASIO_DETAIL_IO_CONTROL_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include "asio/detail/socket_types.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { +namespace io_control { + +// I/O control command for getting number of bytes available. +class bytes_readable +{ +public: + // Default constructor. + bytes_readable() + : value_(0) + { + } + + // Construct with a specific command value. + bytes_readable(std::size_t value) + : value_(static_cast(value)) + { + } + + // Get the name of the IO control command. + int name() const + { + return static_cast(ASIO_OS_DEF(FIONREAD)); + } + + // Set the value of the I/O control command. + void set(std::size_t value) + { + value_ = static_cast(value); + } + + // Get the current value of the I/O control command. + std::size_t get() const + { + return static_cast(value_); + } + + // Get the address of the command data. + detail::ioctl_arg_type* data() + { + return &value_; + } + + // Get the address of the command data. + const detail::ioctl_arg_type* data() const + { + return &value_; + } + +private: + detail::ioctl_arg_type value_; +}; + +} // namespace io_control +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_IO_CONTROL_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/io_object_impl.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/io_object_impl.hpp new file mode 100644 index 000000000..9819bed03 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/io_object_impl.hpp @@ -0,0 +1,175 @@ +// +// io_object_impl.hpp +// ~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IO_OBJECT_IMPL_HPP +#define ASIO_DETAIL_IO_OBJECT_IMPL_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/context.hpp" +#include "asio/io_context.hpp" +#include "asio/query.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class io_object_impl +{ +public: + // The type of the service that will be used to provide I/O operations. + typedef IoObjectService service_type; + + // The underlying implementation type of I/O object. + typedef typename service_type::implementation_type implementation_type; + + // The type of the executor associated with the object. + typedef Executor executor_type; + + // Construct an I/O object using an executor. + explicit io_object_impl(const executor_type& ex) + : service_(&asio::use_service( + io_object_impl::get_context(ex))), + executor_(ex) + { + service_->construct(implementation_); + } + + // Construct an I/O object using an execution context. + template + explicit io_object_impl(ExecutionContext& context, + typename enable_if::value>::type* = 0) + : service_(&asio::use_service(context)), + executor_(context.get_executor()) + { + service_->construct(implementation_); + } + +#if defined(ASIO_HAS_MOVE) + // Move-construct an I/O object. + io_object_impl(io_object_impl&& other) + : service_(&other.get_service()), + executor_(other.get_executor()) + { + service_->move_construct(implementation_, other.implementation_); + } + + // Perform a converting move-construction of an I/O object. + template + io_object_impl(io_object_impl&& other) + : service_(&asio::use_service( + io_object_impl::get_context(other.get_executor()))), + executor_(other.get_executor()) + { + service_->converting_move_construct(implementation_, + other.get_service(), other.get_implementation()); + } +#endif // defined(ASIO_HAS_MOVE) + + // Destructor. + ~io_object_impl() + { + service_->destroy(implementation_); + } + +#if defined(ASIO_HAS_MOVE) + // Move-assign an I/O object. + io_object_impl& operator=(io_object_impl&& other) + { + if (this != &other) + { + service_->move_assign(implementation_, + *other.service_, other.implementation_); + executor_.~executor_type(); + new (&executor_) executor_type( + std::move(other.executor_)); + service_ = other.service_; + } + return *this; + } +#endif // defined(ASIO_HAS_MOVE) + + // Get the executor associated with the object. + const executor_type& get_executor() ASIO_NOEXCEPT + { + return executor_; + } + + // Get the service associated with the I/O object. + service_type& get_service() + { + return *service_; + } + + // Get the service associated with the I/O object. + const service_type& get_service() const + { + return *service_; + } + + // Get the underlying implementation of the I/O object. + implementation_type& get_implementation() + { + return implementation_; + } + + // Get the underlying implementation of the I/O object. + const implementation_type& get_implementation() const + { + return implementation_; + } + +private: + // Helper function to get an executor's context. + template + static execution_context& get_context(const T& t, + typename enable_if::value>::type* = 0) + { + return asio::query(t, execution::context); + } + + // Helper function to get an executor's context. + template + static execution_context& get_context(const T& t, + typename enable_if::value>::type* = 0) + { + return t.context(); + } + + // Disallow copying and copy assignment. + io_object_impl(const io_object_impl&); + io_object_impl& operator=(const io_object_impl&); + + // The service associated with the I/O object. + service_type* service_; + + // The underlying implementation of the I/O object. + implementation_type implementation_; + + // The associated executor. + executor_type executor_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_IO_OBJECT_IMPL_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/is_buffer_sequence.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/is_buffer_sequence.hpp new file mode 100644 index 000000000..06e303c33 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/is_buffer_sequence.hpp @@ -0,0 +1,312 @@ +// +// detail/is_buffer_sequence.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IS_BUFFER_SEQUENCE_HPP +#define ASIO_DETAIL_IS_BUFFER_SEQUENCE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +class mutable_buffer; +class const_buffer; + +namespace detail { + +struct buffer_sequence_memfns_base +{ + void begin(); + void end(); + void size(); + void max_size(); + void capacity(); + void data(); + void prepare(); + void commit(); + void consume(); + void grow(); + void shrink(); +}; + +template +struct buffer_sequence_memfns_derived + : T, buffer_sequence_memfns_base +{ +}; + +template +struct buffer_sequence_memfns_check +{ +}; + +#if defined(ASIO_HAS_DECLTYPE) + +template +char buffer_sequence_begin_helper(...); + +template +char (&buffer_sequence_begin_helper(T* t, + typename enable_if::value>::type*))[2]; + +#else // defined(ASIO_HAS_DECLTYPE) + +template +char (&buffer_sequence_begin_helper(...))[2]; + +template +char buffer_sequence_begin_helper(T* t, + buffer_sequence_memfns_check< + void (buffer_sequence_memfns_base::*)(), + &buffer_sequence_memfns_derived::begin>*); + +#endif // defined(ASIO_HAS_DECLTYPE) + +#if defined(ASIO_HAS_DECLTYPE) + +template +char buffer_sequence_end_helper(...); + +template +char (&buffer_sequence_end_helper(T* t, + typename enable_if::value>::type*))[2]; + +#else // defined(ASIO_HAS_DECLTYPE) + +template +char (&buffer_sequence_end_helper(...))[2]; + +template +char buffer_sequence_end_helper(T* t, + buffer_sequence_memfns_check< + void (buffer_sequence_memfns_base::*)(), + &buffer_sequence_memfns_derived::end>*); + +#endif // defined(ASIO_HAS_DECLTYPE) + +template +char (&size_memfn_helper(...))[2]; + +template +char size_memfn_helper( + buffer_sequence_memfns_check< + void (buffer_sequence_memfns_base::*)(), + &buffer_sequence_memfns_derived::size>*); + +template +char (&max_size_memfn_helper(...))[2]; + +template +char max_size_memfn_helper( + buffer_sequence_memfns_check< + void (buffer_sequence_memfns_base::*)(), + &buffer_sequence_memfns_derived::max_size>*); + +template +char (&capacity_memfn_helper(...))[2]; + +template +char capacity_memfn_helper( + buffer_sequence_memfns_check< + void (buffer_sequence_memfns_base::*)(), + &buffer_sequence_memfns_derived::capacity>*); + +template +char (&data_memfn_helper(...))[2]; + +template +char data_memfn_helper( + buffer_sequence_memfns_check< + void (buffer_sequence_memfns_base::*)(), + &buffer_sequence_memfns_derived::data>*); + +template +char (&prepare_memfn_helper(...))[2]; + +template +char prepare_memfn_helper( + buffer_sequence_memfns_check< + void (buffer_sequence_memfns_base::*)(), + &buffer_sequence_memfns_derived::prepare>*); + +template +char (&commit_memfn_helper(...))[2]; + +template +char commit_memfn_helper( + buffer_sequence_memfns_check< + void (buffer_sequence_memfns_base::*)(), + &buffer_sequence_memfns_derived::commit>*); + +template +char (&consume_memfn_helper(...))[2]; + +template +char consume_memfn_helper( + buffer_sequence_memfns_check< + void (buffer_sequence_memfns_base::*)(), + &buffer_sequence_memfns_derived::consume>*); + +template +char (&grow_memfn_helper(...))[2]; + +template +char grow_memfn_helper( + buffer_sequence_memfns_check< + void (buffer_sequence_memfns_base::*)(), + &buffer_sequence_memfns_derived::grow>*); + +template +char (&shrink_memfn_helper(...))[2]; + +template +char shrink_memfn_helper( + buffer_sequence_memfns_check< + void (buffer_sequence_memfns_base::*)(), + &buffer_sequence_memfns_derived::shrink>*); + +template +char (&buffer_sequence_element_type_helper(...))[2]; + +#if defined(ASIO_HAS_DECLTYPE) + +template +char buffer_sequence_element_type_helper(T* t, + typename enable_if::value>::type*); + +#else // defined(ASIO_HAS_DECLTYPE) + +template +char buffer_sequence_element_type_helper( + typename T::const_iterator*, + typename enable_if::value>::type*); + +#endif // defined(ASIO_HAS_DECLTYPE) + +template +char (&const_buffers_type_typedef_helper(...))[2]; + +template +char const_buffers_type_typedef_helper( + typename T::const_buffers_type*); + +template +char (&mutable_buffers_type_typedef_helper(...))[2]; + +template +char mutable_buffers_type_typedef_helper( + typename T::mutable_buffers_type*); + +template +struct is_buffer_sequence_class + : integral_constant(0, 0)) != 1 && + sizeof(buffer_sequence_end_helper(0, 0)) != 1 && + sizeof(buffer_sequence_element_type_helper(0, 0)) == 1> +{ +}; + +template +struct is_buffer_sequence + : conditional::value, + is_buffer_sequence_class, + false_type>::type +{ +}; + +template <> +struct is_buffer_sequence + : true_type +{ +}; + +template <> +struct is_buffer_sequence + : true_type +{ +}; + +template <> +struct is_buffer_sequence + : true_type +{ +}; + +template <> +struct is_buffer_sequence + : false_type +{ +}; + +template +struct is_dynamic_buffer_class_v1 + : integral_constant(0)) != 1 && + sizeof(max_size_memfn_helper(0)) != 1 && + sizeof(capacity_memfn_helper(0)) != 1 && + sizeof(data_memfn_helper(0)) != 1 && + sizeof(consume_memfn_helper(0)) != 1 && + sizeof(prepare_memfn_helper(0)) != 1 && + sizeof(commit_memfn_helper(0)) != 1 && + sizeof(const_buffers_type_typedef_helper(0)) == 1 && + sizeof(mutable_buffers_type_typedef_helper(0)) == 1> +{ +}; + +template +struct is_dynamic_buffer_v1 + : conditional::value, + is_dynamic_buffer_class_v1, + false_type>::type +{ +}; + +template +struct is_dynamic_buffer_class_v2 + : integral_constant(0)) != 1 && + sizeof(max_size_memfn_helper(0)) != 1 && + sizeof(capacity_memfn_helper(0)) != 1 && + sizeof(data_memfn_helper(0)) != 1 && + sizeof(consume_memfn_helper(0)) != 1 && + sizeof(grow_memfn_helper(0)) != 1 && + sizeof(shrink_memfn_helper(0)) != 1 && + sizeof(const_buffers_type_typedef_helper(0)) == 1 && + sizeof(mutable_buffers_type_typedef_helper(0)) == 1> +{ +}; + +template +struct is_dynamic_buffer_v2 + : conditional::value, + is_dynamic_buffer_class_v2, + false_type>::type +{ +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_IS_BUFFER_SEQUENCE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/is_executor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/is_executor.hpp new file mode 100644 index 000000000..9dbaf958c --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/is_executor.hpp @@ -0,0 +1,126 @@ +// +// detail/is_executor.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_IS_EXECUTOR_HPP +#define ASIO_DETAIL_IS_EXECUTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +struct executor_memfns_base +{ + void context(); + void on_work_started(); + void on_work_finished(); + void dispatch(); + void post(); + void defer(); +}; + +template +struct executor_memfns_derived + : T, executor_memfns_base +{ +}; + +template +struct executor_memfns_check +{ +}; + +template +char (&context_memfn_helper(...))[2]; + +template +char context_memfn_helper( + executor_memfns_check< + void (executor_memfns_base::*)(), + &executor_memfns_derived::context>*); + +template +char (&on_work_started_memfn_helper(...))[2]; + +template +char on_work_started_memfn_helper( + executor_memfns_check< + void (executor_memfns_base::*)(), + &executor_memfns_derived::on_work_started>*); + +template +char (&on_work_finished_memfn_helper(...))[2]; + +template +char on_work_finished_memfn_helper( + executor_memfns_check< + void (executor_memfns_base::*)(), + &executor_memfns_derived::on_work_finished>*); + +template +char (&dispatch_memfn_helper(...))[2]; + +template +char dispatch_memfn_helper( + executor_memfns_check< + void (executor_memfns_base::*)(), + &executor_memfns_derived::dispatch>*); + +template +char (&post_memfn_helper(...))[2]; + +template +char post_memfn_helper( + executor_memfns_check< + void (executor_memfns_base::*)(), + &executor_memfns_derived::post>*); + +template +char (&defer_memfn_helper(...))[2]; + +template +char defer_memfn_helper( + executor_memfns_check< + void (executor_memfns_base::*)(), + &executor_memfns_derived::defer>*); + +template +struct is_executor_class + : integral_constant(0)) != 1 && + sizeof(on_work_started_memfn_helper(0)) != 1 && + sizeof(on_work_finished_memfn_helper(0)) != 1 && + sizeof(dispatch_memfn_helper(0)) != 1 && + sizeof(post_memfn_helper(0)) != 1 && + sizeof(defer_memfn_helper(0)) != 1> +{ +}; + +template +struct is_executor + : conditional::value, + is_executor_class, + false_type>::type +{ +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_IS_EXECUTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/keyword_tss_ptr.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/keyword_tss_ptr.hpp new file mode 100644 index 000000000..043dde1ce --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/keyword_tss_ptr.hpp @@ -0,0 +1,70 @@ +// +// detail/keyword_tss_ptr.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_KEYWORD_TSS_PTR_HPP +#define ASIO_DETAIL_KEYWORD_TSS_PTR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_THREAD_KEYWORD_EXTENSION) + +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class keyword_tss_ptr + : private noncopyable +{ +public: + // Constructor. + keyword_tss_ptr() + { + } + + // Destructor. + ~keyword_tss_ptr() + { + } + + // Get the value. + operator T*() const + { + return value_; + } + + // Set the value. + void operator=(T* value) + { + value_ = value; + } + +private: + static ASIO_THREAD_KEYWORD T* value_; +}; + +template +ASIO_THREAD_KEYWORD T* keyword_tss_ptr::value_; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_THREAD_KEYWORD_EXTENSION) + +#endif // ASIO_DETAIL_KEYWORD_TSS_PTR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/kqueue_reactor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/kqueue_reactor.hpp new file mode 100644 index 000000000..38ae06711 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/kqueue_reactor.hpp @@ -0,0 +1,242 @@ +// +// detail/kqueue_reactor.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// Copyright (c) 2005 Stefan Arentz (stefan at soze dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_KQUEUE_REACTOR_HPP +#define ASIO_DETAIL_KQUEUE_REACTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_KQUEUE) + +#include +#include +#include +#include +#include "asio/detail/limits.hpp" +#include "asio/detail/mutex.hpp" +#include "asio/detail/object_pool.hpp" +#include "asio/detail/op_queue.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/select_interrupter.hpp" +#include "asio/detail/socket_types.hpp" +#include "asio/detail/timer_queue_base.hpp" +#include "asio/detail/timer_queue_set.hpp" +#include "asio/detail/wait_op.hpp" +#include "asio/error.hpp" +#include "asio/execution_context.hpp" + +// Older versions of Mac OS X may not define EV_OOBAND. +#if !defined(EV_OOBAND) +# define EV_OOBAND EV_FLAG1 +#endif // !defined(EV_OOBAND) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class scheduler; + +class kqueue_reactor + : public execution_context_service_base +{ +private: + // The mutex type used by this reactor. + typedef conditionally_enabled_mutex mutex; + +public: + enum op_types { read_op = 0, write_op = 1, + connect_op = 1, except_op = 2, max_ops = 3 }; + + // Per-descriptor queues. + struct descriptor_state + { + descriptor_state(bool locking) : mutex_(locking) {} + + friend class kqueue_reactor; + friend class object_pool_access; + + descriptor_state* next_; + descriptor_state* prev_; + + mutex mutex_; + int descriptor_; + int num_kevents_; // 1 == read only, 2 == read and write + op_queue op_queue_[max_ops]; + bool shutdown_; + }; + + // Per-descriptor data. + typedef descriptor_state* per_descriptor_data; + + // Constructor. + ASIO_DECL kqueue_reactor(asio::execution_context& ctx); + + // Destructor. + ASIO_DECL ~kqueue_reactor(); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void shutdown(); + + // Recreate internal descriptors following a fork. + ASIO_DECL void notify_fork( + asio::execution_context::fork_event fork_ev); + + // Initialise the task. + ASIO_DECL void init_task(); + + // Register a socket with the reactor. Returns 0 on success, system error + // code on failure. + ASIO_DECL int register_descriptor(socket_type descriptor, + per_descriptor_data& descriptor_data); + + // Register a descriptor with an associated single operation. Returns 0 on + // success, system error code on failure. + ASIO_DECL int register_internal_descriptor( + int op_type, socket_type descriptor, + per_descriptor_data& descriptor_data, reactor_op* op); + + // Move descriptor registration from one descriptor_data object to another. + ASIO_DECL void move_descriptor(socket_type descriptor, + per_descriptor_data& target_descriptor_data, + per_descriptor_data& source_descriptor_data); + + // Post a reactor operation for immediate completion. + void post_immediate_completion(reactor_op* op, bool is_continuation) + { + scheduler_.post_immediate_completion(op, is_continuation); + } + + // Start a new operation. The reactor operation will be performed when the + // given descriptor is flagged as ready, or an error has occurred. + ASIO_DECL void start_op(int op_type, socket_type descriptor, + per_descriptor_data& descriptor_data, reactor_op* op, + bool is_continuation, bool allow_speculative); + + // Cancel all operations associated with the given descriptor. The + // handlers associated with the descriptor will be invoked with the + // operation_aborted error. + ASIO_DECL void cancel_ops(socket_type descriptor, + per_descriptor_data& descriptor_data); + + // Cancel any operations that are running against the descriptor and remove + // its registration from the reactor. The reactor resources associated with + // the descriptor must be released by calling cleanup_descriptor_data. + ASIO_DECL void deregister_descriptor(socket_type descriptor, + per_descriptor_data& descriptor_data, bool closing); + + // Remove the descriptor's registration from the reactor. The reactor + // resources associated with the descriptor must be released by calling + // cleanup_descriptor_data. + ASIO_DECL void deregister_internal_descriptor( + socket_type descriptor, per_descriptor_data& descriptor_data); + + // Perform any post-deregistration cleanup tasks associated with the + // descriptor data. + ASIO_DECL void cleanup_descriptor_data( + per_descriptor_data& descriptor_data); + + // Add a new timer queue to the reactor. + template + void add_timer_queue(timer_queue& queue); + + // Remove a timer queue from the reactor. + template + void remove_timer_queue(timer_queue& queue); + + // Schedule a new operation in the given timer queue to expire at the + // specified absolute time. + template + void schedule_timer(timer_queue& queue, + const typename Time_Traits::time_type& time, + typename timer_queue::per_timer_data& timer, wait_op* op); + + // Cancel the timer operations associated with the given token. Returns the + // number of operations that have been posted or dispatched. + template + std::size_t cancel_timer(timer_queue& queue, + typename timer_queue::per_timer_data& timer, + std::size_t max_cancelled = (std::numeric_limits::max)()); + + // Move the timer operations associated with the given timer. + template + void move_timer(timer_queue& queue, + typename timer_queue::per_timer_data& target, + typename timer_queue::per_timer_data& source); + + // Run the kqueue loop. + ASIO_DECL void run(long usec, op_queue& ops); + + // Interrupt the kqueue loop. + ASIO_DECL void interrupt(); + +private: + // Create the kqueue file descriptor. Throws an exception if the descriptor + // cannot be created. + ASIO_DECL static int do_kqueue_create(); + + // Allocate a new descriptor state object. + ASIO_DECL descriptor_state* allocate_descriptor_state(); + + // Free an existing descriptor state object. + ASIO_DECL void free_descriptor_state(descriptor_state* s); + + // Helper function to add a new timer queue. + ASIO_DECL void do_add_timer_queue(timer_queue_base& queue); + + // Helper function to remove a timer queue. + ASIO_DECL void do_remove_timer_queue(timer_queue_base& queue); + + // Get the timeout value for the kevent call. + ASIO_DECL timespec* get_timeout(long usec, timespec& ts); + + // The scheduler used to post completions. + scheduler& scheduler_; + + // Mutex to protect access to internal data. + mutex mutex_; + + // The kqueue file descriptor. + int kqueue_fd_; + + // The interrupter is used to break a blocking kevent call. + select_interrupter interrupter_; + + // The timer queues. + timer_queue_set timer_queues_; + + // Whether the service has been shut down. + bool shutdown_; + + // Mutex to protect access to the registered descriptors. + mutex registered_descriptors_mutex_; + + // Keep track of all registered descriptors. + object_pool registered_descriptors_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/detail/impl/kqueue_reactor.hpp" +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/kqueue_reactor.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_HAS_KQUEUE) + +#endif // ASIO_DETAIL_KQUEUE_REACTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/limits.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/limits.hpp new file mode 100644 index 000000000..d32470d2d --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/limits.hpp @@ -0,0 +1,26 @@ +// +// detail/limits.hpp +// ~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2011 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_LIMITS_HPP +#define ASIO_DETAIL_LIMITS_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_BOOST_LIMITS) +# include +#else // defined(ASIO_HAS_BOOST_LIMITS) +# include +#endif // defined(ASIO_HAS_BOOST_LIMITS) + +#endif // ASIO_DETAIL_LIMITS_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/local_free_on_block_exit.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/local_free_on_block_exit.hpp new file mode 100644 index 000000000..e6153f021 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/local_free_on_block_exit.hpp @@ -0,0 +1,59 @@ +// +// detail/local_free_on_block_exit.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_LOCAL_FREE_ON_BLOCK_EXIT_HPP +#define ASIO_DETAIL_LOCAL_FREE_ON_BLOCK_EXIT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) +#if !defined(ASIO_WINDOWS_APP) + +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/socket_types.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class local_free_on_block_exit + : private noncopyable +{ +public: + // Constructor blocks all signals for the calling thread. + explicit local_free_on_block_exit(void* p) + : p_(p) + { + } + + // Destructor restores the previous signal mask. + ~local_free_on_block_exit() + { + ::LocalFree(p_); + } + +private: + void* p_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_WINDOWS_APP) +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +#endif // ASIO_DETAIL_LOCAL_FREE_ON_BLOCK_EXIT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/macos_fenced_block.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/macos_fenced_block.hpp new file mode 100644 index 000000000..ee15752c5 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/macos_fenced_block.hpp @@ -0,0 +1,62 @@ +// +// detail/macos_fenced_block.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_MACOS_FENCED_BLOCK_HPP +#define ASIO_DETAIL_MACOS_FENCED_BLOCK_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(__MACH__) && defined(__APPLE__) + +#include +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class macos_fenced_block + : private noncopyable +{ +public: + enum half_t { half }; + enum full_t { full }; + + // Constructor for a half fenced block. + explicit macos_fenced_block(half_t) + { + } + + // Constructor for a full fenced block. + explicit macos_fenced_block(full_t) + { + OSMemoryBarrier(); + } + + // Destructor. + ~macos_fenced_block() + { + OSMemoryBarrier(); + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(__MACH__) && defined(__APPLE__) + +#endif // ASIO_DETAIL_MACOS_FENCED_BLOCK_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/memory.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/memory.hpp new file mode 100644 index 000000000..7c59a5fcb --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/memory.hpp @@ -0,0 +1,73 @@ +// +// detail/memory.hpp +// ~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_MEMORY_HPP +#define ASIO_DETAIL_MEMORY_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include + +#if !defined(ASIO_HAS_STD_SHARED_PTR) +# include +# include +# include +#endif // !defined(ASIO_HAS_STD_SHARED_PTR) + +#if !defined(ASIO_HAS_STD_ADDRESSOF) +# include +#endif // !defined(ASIO_HAS_STD_ADDRESSOF) + +namespace asio { +namespace detail { + +#if defined(ASIO_HAS_STD_SHARED_PTR) +using std::make_shared; +using std::shared_ptr; +using std::weak_ptr; +#else // defined(ASIO_HAS_STD_SHARED_PTR) +using boost::make_shared; +using boost::shared_ptr; +using boost::weak_ptr; +#endif // defined(ASIO_HAS_STD_SHARED_PTR) + +#if defined(ASIO_HAS_STD_ADDRESSOF) +using std::addressof; +#else // defined(ASIO_HAS_STD_ADDRESSOF) +using boost::addressof; +#endif // defined(ASIO_HAS_STD_ADDRESSOF) + +} // namespace detail + +#if defined(ASIO_HAS_CXX11_ALLOCATORS) +using std::allocator_arg_t; +# define ASIO_USES_ALLOCATOR(t) \ + namespace std { \ + template \ + struct uses_allocator : true_type {}; \ + } \ + /**/ +# define ASIO_REBIND_ALLOC(alloc, t) \ + typename std::allocator_traits::template rebind_alloc + /**/ +#else // defined(ASIO_HAS_CXX11_ALLOCATORS) +struct allocator_arg_t {}; +# define ASIO_USES_ALLOCATOR(t) +# define ASIO_REBIND_ALLOC(alloc, t) \ + typename alloc::template rebind::other + /**/ +#endif // defined(ASIO_HAS_CXX11_ALLOCATORS) + +} // namespace asio + +#endif // ASIO_DETAIL_MEMORY_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/mutex.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/mutex.hpp new file mode 100644 index 000000000..8eb4764a5 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/mutex.hpp @@ -0,0 +1,48 @@ +// +// detail/mutex.hpp +// ~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_MUTEX_HPP +#define ASIO_DETAIL_MUTEX_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_THREADS) +# include "asio/detail/null_mutex.hpp" +#elif defined(ASIO_WINDOWS) +# include "asio/detail/win_mutex.hpp" +#elif defined(ASIO_HAS_PTHREADS) +# include "asio/detail/posix_mutex.hpp" +#elif defined(ASIO_HAS_STD_MUTEX_AND_CONDVAR) +# include "asio/detail/std_mutex.hpp" +#else +# error Only Windows, POSIX and std::mutex are supported! +#endif + +namespace asio { +namespace detail { + +#if !defined(ASIO_HAS_THREADS) +typedef null_mutex mutex; +#elif defined(ASIO_WINDOWS) +typedef win_mutex mutex; +#elif defined(ASIO_HAS_PTHREADS) +typedef posix_mutex mutex; +#elif defined(ASIO_HAS_STD_MUTEX_AND_CONDVAR) +typedef std_mutex mutex; +#endif + +} // namespace detail +} // namespace asio + +#endif // ASIO_DETAIL_MUTEX_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/non_const_lvalue.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/non_const_lvalue.hpp new file mode 100644 index 000000000..9a3979c0c --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/non_const_lvalue.hpp @@ -0,0 +1,54 @@ +// +// detail/non_const_lvalue.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_NON_CONST_LVALUE_HPP +#define ASIO_DETAIL_NON_CONST_LVALUE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +struct non_const_lvalue +{ +#if defined(ASIO_HAS_MOVE) + explicit non_const_lvalue(T& t) + : value(static_cast::type>::value, + typename decay::type&, T&&>::type>(t)) + { + } + + typename conditional::type>::value, + typename decay::type&, typename decay::type>::type value; +#else // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + explicit non_const_lvalue(const typename decay::type& t) + : value(t) + { + } + + typename decay::type value; +#endif // defined(ASIO_HAS_MOVE) +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_NON_CONST_LVALUE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/noncopyable.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/noncopyable.hpp new file mode 100644 index 000000000..c730cd1aa --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/noncopyable.hpp @@ -0,0 +1,43 @@ +// +// detail/noncopyable.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_NONCOPYABLE_HPP +#define ASIO_DETAIL_NONCOPYABLE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class noncopyable +{ +protected: + noncopyable() {} + ~noncopyable() {} +private: + noncopyable(const noncopyable&); + const noncopyable& operator=(const noncopyable&); +}; + +} // namespace detail + +using asio::detail::noncopyable; + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_NONCOPYABLE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_event.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_event.hpp new file mode 100644 index 000000000..6083f1e35 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_event.hpp @@ -0,0 +1,106 @@ +// +// detail/null_event.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_NULL_EVENT_HPP +#define ASIO_DETAIL_NULL_EVENT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class null_event + : private noncopyable +{ +public: + // Constructor. + null_event() + { + } + + // Destructor. + ~null_event() + { + } + + // Signal the event. (Retained for backward compatibility.) + template + void signal(Lock&) + { + } + + // Signal all waiters. + template + void signal_all(Lock&) + { + } + + // Unlock the mutex and signal one waiter. + template + void unlock_and_signal_one(Lock&) + { + } + + // Unlock the mutex and signal one waiter who may destroy us. + template + void unlock_and_signal_one_for_destruction(Lock&) + { + } + + // If there's a waiter, unlock the mutex and signal it. + template + bool maybe_unlock_and_signal_one(Lock&) + { + return false; + } + + // Reset the event. + template + void clear(Lock&) + { + } + + // Wait for the event to become signalled. + template + void wait(Lock&) + { + do_wait(); + } + + // Timed wait for the event to become signalled. + template + bool wait_for_usec(Lock&, long usec) + { + do_wait_for_usec(usec); + return true; + } + +private: + ASIO_DECL static void do_wait(); + ASIO_DECL static void do_wait_for_usec(long usec); +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/null_event.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // ASIO_DETAIL_NULL_EVENT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_fenced_block.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_fenced_block.hpp new file mode 100644 index 000000000..a3e58d3cb --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_fenced_block.hpp @@ -0,0 +1,47 @@ +// +// detail/null_fenced_block.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_NULL_FENCED_BLOCK_HPP +#define ASIO_DETAIL_NULL_FENCED_BLOCK_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class null_fenced_block + : private noncopyable +{ +public: + enum half_or_full_t { half, full }; + + // Constructor. + explicit null_fenced_block(half_or_full_t) + { + } + + // Destructor. + ~null_fenced_block() + { + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_NULL_FENCED_BLOCK_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_global.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_global.hpp new file mode 100644 index 000000000..e67f20697 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_global.hpp @@ -0,0 +1,59 @@ +// +// detail/null_global.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_NULL_GLOBAL_HPP +#define ASIO_DETAIL_NULL_GLOBAL_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +struct null_global_impl +{ + null_global_impl() + : ptr_(0) + { + } + + // Destructor automatically cleans up the global. + ~null_global_impl() + { + delete ptr_; + } + + static null_global_impl instance_; + T* ptr_; +}; + +template +null_global_impl null_global_impl::instance_; + +template +T& null_global() +{ + if (null_global_impl::instance_.ptr_ == 0) + null_global_impl::instance_.ptr_ = new T; + return *null_global_impl::instance_.ptr_; +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_NULL_GLOBAL_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_mutex.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_mutex.hpp new file mode 100644 index 000000000..25a8ed1f8 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_mutex.hpp @@ -0,0 +1,64 @@ +// +// detail/null_mutex.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_NULL_MUTEX_HPP +#define ASIO_DETAIL_NULL_MUTEX_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_THREADS) + +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/scoped_lock.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class null_mutex + : private noncopyable +{ +public: + typedef asio::detail::scoped_lock scoped_lock; + + // Constructor. + null_mutex() + { + } + + // Destructor. + ~null_mutex() + { + } + + // Lock the mutex. + void lock() + { + } + + // Unlock the mutex. + void unlock() + { + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_HAS_THREADS) + +#endif // ASIO_DETAIL_NULL_MUTEX_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_reactor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_reactor.hpp new file mode 100644 index 000000000..7c1da5856 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_reactor.hpp @@ -0,0 +1,68 @@ +// +// detail/null_reactor.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_NULL_REACTOR_HPP +#define ASIO_DETAIL_NULL_REACTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) || defined(ASIO_WINDOWS_RUNTIME) + +#include "asio/detail/scheduler_operation.hpp" +#include "asio/execution_context.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class null_reactor + : public execution_context_service_base +{ +public: + // Constructor. + null_reactor(asio::execution_context& ctx) + : execution_context_service_base(ctx) + { + } + + // Destructor. + ~null_reactor() + { + } + + // Destroy all user-defined handler objects owned by the service. + void shutdown() + { + } + + // No-op because should never be called. + void run(long /*usec*/, op_queue& /*ops*/) + { + } + + // No-op. + void interrupt() + { + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) || defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_NULL_REACTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_signal_blocker.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_signal_blocker.hpp new file mode 100644 index 000000000..e9e7b3cee --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_signal_blocker.hpp @@ -0,0 +1,69 @@ +// +// detail/null_signal_blocker.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_NULL_SIGNAL_BLOCKER_HPP +#define ASIO_DETAIL_NULL_SIGNAL_BLOCKER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_THREADS) \ + || defined(ASIO_WINDOWS) \ + || defined(ASIO_WINDOWS_RUNTIME) \ + || defined(__CYGWIN__) \ + || defined(__SYMBIAN32__) + +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class null_signal_blocker + : private noncopyable +{ +public: + // Constructor blocks all signals for the calling thread. + null_signal_blocker() + { + } + + // Destructor restores the previous signal mask. + ~null_signal_blocker() + { + } + + // Block all signals for the calling thread. + void block() + { + } + + // Restore the previous signal mask. + void unblock() + { + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_HAS_THREADS) + // || defined(ASIO_WINDOWS) + // || defined(ASIO_WINDOWS_RUNTIME) + // || defined(__CYGWIN__) + // || defined(__SYMBIAN32__) + +#endif // ASIO_DETAIL_NULL_SIGNAL_BLOCKER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_socket_service.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_socket_service.hpp new file mode 100644 index 000000000..4f6f93368 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_socket_service.hpp @@ -0,0 +1,519 @@ +// +// detail/null_socket_service.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_NULL_SOCKET_SERVICE_HPP +#define ASIO_DETAIL_NULL_SOCKET_SERVICE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) + +#include "asio/buffer.hpp" +#include "asio/error.hpp" +#include "asio/execution_context.hpp" +#include "asio/post.hpp" +#include "asio/socket_base.hpp" +#include "asio/detail/bind_handler.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class null_socket_service : + public execution_context_service_base > +{ +public: + // The protocol type. + typedef Protocol protocol_type; + + // The endpoint type. + typedef typename Protocol::endpoint endpoint_type; + + // The native type of a socket. + typedef int native_handle_type; + + // The implementation type of the socket. + struct implementation_type + { + }; + + // Constructor. + null_socket_service(execution_context& context) + : execution_context_service_base >(context) + { + } + + // Destroy all user-defined handler objects owned by the service. + void shutdown() + { + } + + // Construct a new socket implementation. + void construct(implementation_type&) + { + } + + // Move-construct a new socket implementation. + void move_construct(implementation_type&, implementation_type&) + { + } + + // Move-assign from another socket implementation. + void move_assign(implementation_type&, + null_socket_service&, implementation_type&) + { + } + + // Move-construct a new socket implementation from another protocol type. + template + void converting_move_construct(implementation_type&, + null_socket_service&, + typename null_socket_service::implementation_type&) + { + } + + // Destroy a socket implementation. + void destroy(implementation_type&) + { + } + + // Open a new socket implementation. + asio::error_code open(implementation_type&, + const protocol_type&, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Assign a native socket to a socket implementation. + asio::error_code assign(implementation_type&, const protocol_type&, + const native_handle_type&, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Determine whether the socket is open. + bool is_open(const implementation_type&) const + { + return false; + } + + // Destroy a socket implementation. + asio::error_code close(implementation_type&, + asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Release ownership of the socket. + native_handle_type release(implementation_type&, + asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return 0; + } + + // Get the native socket representation. + native_handle_type native_handle(implementation_type&) + { + return 0; + } + + // Cancel all operations associated with the socket. + asio::error_code cancel(implementation_type&, + asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Determine whether the socket is at the out-of-band data mark. + bool at_mark(const implementation_type&, + asio::error_code& ec) const + { + ec = asio::error::operation_not_supported; + return false; + } + + // Determine the number of bytes available for reading. + std::size_t available(const implementation_type&, + asio::error_code& ec) const + { + ec = asio::error::operation_not_supported; + return 0; + } + + // Place the socket into the state where it will listen for new connections. + asio::error_code listen(implementation_type&, + int, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Perform an IO control command on the socket. + template + asio::error_code io_control(implementation_type&, + IO_Control_Command&, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Gets the non-blocking mode of the socket. + bool non_blocking(const implementation_type&) const + { + return false; + } + + // Sets the non-blocking mode of the socket. + asio::error_code non_blocking(implementation_type&, + bool, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Gets the non-blocking mode of the native socket implementation. + bool native_non_blocking(const implementation_type&) const + { + return false; + } + + // Sets the non-blocking mode of the native socket implementation. + asio::error_code native_non_blocking(implementation_type&, + bool, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Disable sends or receives on the socket. + asio::error_code shutdown(implementation_type&, + socket_base::shutdown_type, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Bind the socket to the specified local endpoint. + asio::error_code bind(implementation_type&, + const endpoint_type&, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Set a socket option. + template + asio::error_code set_option(implementation_type&, + const Option&, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Set a socket option. + template + asio::error_code get_option(const implementation_type&, + Option&, asio::error_code& ec) const + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Get the local endpoint. + endpoint_type local_endpoint(const implementation_type&, + asio::error_code& ec) const + { + ec = asio::error::operation_not_supported; + return endpoint_type(); + } + + // Get the remote endpoint. + endpoint_type remote_endpoint(const implementation_type&, + asio::error_code& ec) const + { + ec = asio::error::operation_not_supported; + return endpoint_type(); + } + + // Send the given data to the peer. + template + std::size_t send(implementation_type&, const ConstBufferSequence&, + socket_base::message_flags, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return 0; + } + + // Wait until data can be sent without blocking. + std::size_t send(implementation_type&, const null_buffers&, + socket_base::message_flags, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return 0; + } + + // Start an asynchronous send. The data being sent must be valid for the + // lifetime of the asynchronous operation. + template + void async_send(implementation_type&, const ConstBufferSequence&, + socket_base::message_flags, Handler& handler, const IoExecutor& io_ex) + { + asio::error_code ec = asio::error::operation_not_supported; + const std::size_t bytes_transferred = 0; + asio::post(io_ex, detail::bind_handler( + handler, ec, bytes_transferred)); + } + + // Start an asynchronous wait until data can be sent without blocking. + template + void async_send(implementation_type&, const null_buffers&, + socket_base::message_flags, Handler& handler, const IoExecutor& io_ex) + { + asio::error_code ec = asio::error::operation_not_supported; + const std::size_t bytes_transferred = 0; + asio::post(io_ex, detail::bind_handler( + handler, ec, bytes_transferred)); + } + + // Receive some data from the peer. Returns the number of bytes received. + template + std::size_t receive(implementation_type&, const MutableBufferSequence&, + socket_base::message_flags, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return 0; + } + + // Wait until data can be received without blocking. + std::size_t receive(implementation_type&, const null_buffers&, + socket_base::message_flags, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return 0; + } + + // Start an asynchronous receive. The buffer for the data being received + // must be valid for the lifetime of the asynchronous operation. + template + void async_receive(implementation_type&, const MutableBufferSequence&, + socket_base::message_flags, Handler& handler, const IoExecutor& io_ex) + { + asio::error_code ec = asio::error::operation_not_supported; + const std::size_t bytes_transferred = 0; + asio::post(io_ex, detail::bind_handler( + handler, ec, bytes_transferred)); + } + + // Wait until data can be received without blocking. + template + void async_receive(implementation_type&, const null_buffers&, + socket_base::message_flags, Handler& handler, const IoExecutor& io_ex) + { + asio::error_code ec = asio::error::operation_not_supported; + const std::size_t bytes_transferred = 0; + asio::post(io_ex, detail::bind_handler( + handler, ec, bytes_transferred)); + } + + // Receive some data with associated flags. Returns the number of bytes + // received. + template + std::size_t receive_with_flags(implementation_type&, + const MutableBufferSequence&, socket_base::message_flags, + socket_base::message_flags&, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return 0; + } + + // Wait until data can be received without blocking. + std::size_t receive_with_flags(implementation_type&, + const null_buffers&, socket_base::message_flags, + socket_base::message_flags&, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return 0; + } + + // Start an asynchronous receive. The buffer for the data being received + // must be valid for the lifetime of the asynchronous operation. + template + void async_receive_with_flags(implementation_type&, + const MutableBufferSequence&, socket_base::message_flags, + socket_base::message_flags&, Handler& handler, const IoExecutor& io_ex) + { + asio::error_code ec = asio::error::operation_not_supported; + const std::size_t bytes_transferred = 0; + asio::post(io_ex, detail::bind_handler( + handler, ec, bytes_transferred)); + } + + // Wait until data can be received without blocking. + template + void async_receive_with_flags(implementation_type&, const null_buffers&, + socket_base::message_flags, socket_base::message_flags&, + Handler& handler, const IoExecutor& io_ex) + { + asio::error_code ec = asio::error::operation_not_supported; + const std::size_t bytes_transferred = 0; + asio::post(io_ex, detail::bind_handler( + handler, ec, bytes_transferred)); + } + + // Send a datagram to the specified endpoint. Returns the number of bytes + // sent. + template + std::size_t send_to(implementation_type&, const ConstBufferSequence&, + const endpoint_type&, socket_base::message_flags, + asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return 0; + } + + // Wait until data can be sent without blocking. + std::size_t send_to(implementation_type&, const null_buffers&, + const endpoint_type&, socket_base::message_flags, + asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return 0; + } + + // Start an asynchronous send. The data being sent must be valid for the + // lifetime of the asynchronous operation. + template + void async_send_to(implementation_type&, const ConstBufferSequence&, + const endpoint_type&, socket_base::message_flags, + Handler& handler) + { + asio::error_code ec = asio::error::operation_not_supported; + const std::size_t bytes_transferred = 0; + asio::post(io_ex, detail::bind_handler( + handler, ec, bytes_transferred)); + } + + // Start an asynchronous wait until data can be sent without blocking. + template + void async_send_to(implementation_type&, const null_buffers&, + const endpoint_type&, socket_base::message_flags, + Handler& handler, const IoExecutor& io_ex) + { + asio::error_code ec = asio::error::operation_not_supported; + const std::size_t bytes_transferred = 0; + asio::post(io_ex, detail::bind_handler( + handler, ec, bytes_transferred)); + } + + // Receive a datagram with the endpoint of the sender. Returns the number of + // bytes received. + template + std::size_t receive_from(implementation_type&, const MutableBufferSequence&, + endpoint_type&, socket_base::message_flags, + asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return 0; + } + + // Wait until data can be received without blocking. + std::size_t receive_from(implementation_type&, const null_buffers&, + endpoint_type&, socket_base::message_flags, + asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return 0; + } + + // Start an asynchronous receive. The buffer for the data being received and + // the sender_endpoint object must both be valid for the lifetime of the + // asynchronous operation. + template + void async_receive_from(implementation_type&, const MutableBufferSequence&, + endpoint_type&, socket_base::message_flags, Handler& handler, + const IoExecutor& io_ex) + { + asio::error_code ec = asio::error::operation_not_supported; + const std::size_t bytes_transferred = 0; + asio::post(io_ex, detail::bind_handler( + handler, ec, bytes_transferred)); + } + + // Wait until data can be received without blocking. + template + void async_receive_from(implementation_type&, const null_buffers&, + endpoint_type&, socket_base::message_flags, Handler& handler, + const IoExecutor& io_ex) + { + asio::error_code ec = asio::error::operation_not_supported; + const std::size_t bytes_transferred = 0; + asio::post(io_ex, detail::bind_handler( + handler, ec, bytes_transferred)); + } + + // Accept a new connection. + template + asio::error_code accept(implementation_type&, + Socket&, endpoint_type*, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Start an asynchronous accept. The peer and peer_endpoint objects + // must be valid until the accept's handler is invoked. + template + void async_accept(implementation_type&, Socket&, endpoint_type*, + Handler& handler, const IoExecutor& io_ex) + { + asio::error_code ec = asio::error::operation_not_supported; + asio::post(io_ex, detail::bind_handler(handler, ec)); + } + + // Connect the socket to the specified endpoint. + asio::error_code connect(implementation_type&, + const endpoint_type&, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Start an asynchronous connect. + template + void async_connect(implementation_type&, const endpoint_type&, + Handler& handler, const IoExecutor& io_ex) + { + asio::error_code ec = asio::error::operation_not_supported; + asio::post(io_ex, detail::bind_handler(handler, ec)); + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_NULL_SOCKET_SERVICE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_static_mutex.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_static_mutex.hpp new file mode 100644 index 000000000..495739eee --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_static_mutex.hpp @@ -0,0 +1,60 @@ +// +// detail/null_static_mutex.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_NULL_STATIC_MUTEX_HPP +#define ASIO_DETAIL_NULL_STATIC_MUTEX_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_THREADS) + +#include "asio/detail/scoped_lock.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +struct null_static_mutex +{ + typedef asio::detail::scoped_lock scoped_lock; + + // Initialise the mutex. + void init() + { + } + + // Lock the mutex. + void lock() + { + } + + // Unlock the mutex. + void unlock() + { + } + + int unused_; +}; + +#define ASIO_NULL_STATIC_MUTEX_INIT { 0 } + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_HAS_THREADS) + +#endif // ASIO_DETAIL_NULL_STATIC_MUTEX_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_thread.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_thread.hpp new file mode 100644 index 000000000..3b3c5b266 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_thread.hpp @@ -0,0 +1,67 @@ +// +// detail/null_thread.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_NULL_THREAD_HPP +#define ASIO_DETAIL_NULL_THREAD_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_THREADS) + +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class null_thread + : private noncopyable +{ +public: + // Constructor. + template + null_thread(Function, unsigned int = 0) + { + asio::detail::throw_error( + asio::error::operation_not_supported, "thread"); + } + + // Destructor. + ~null_thread() + { + } + + // Wait for the thread to exit. + void join() + { + } + + // Get number of CPUs. + static std::size_t hardware_concurrency() + { + return 1; + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_HAS_THREADS) + +#endif // ASIO_DETAIL_NULL_THREAD_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_tss_ptr.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_tss_ptr.hpp new file mode 100644 index 000000000..5ac594b32 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/null_tss_ptr.hpp @@ -0,0 +1,68 @@ +// +// detail/null_tss_ptr.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_NULL_TSS_PTR_HPP +#define ASIO_DETAIL_NULL_TSS_PTR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_THREADS) + +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class null_tss_ptr + : private noncopyable +{ +public: + // Constructor. + null_tss_ptr() + : value_(0) + { + } + + // Destructor. + ~null_tss_ptr() + { + } + + // Get the value. + operator T*() const + { + return value_; + } + + // Set the value. + void operator=(T* value) + { + value_ = value; + } + +private: + T* value_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_HAS_THREADS) + +#endif // ASIO_DETAIL_NULL_TSS_PTR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/object_pool.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/object_pool.hpp new file mode 100644 index 000000000..7b7dc29ea --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/object_pool.hpp @@ -0,0 +1,171 @@ +// +// detail/object_pool.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_OBJECT_POOL_HPP +#define ASIO_DETAIL_OBJECT_POOL_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class object_pool; + +class object_pool_access +{ +public: + template + static Object* create() + { + return new Object; + } + + template + static Object* create(Arg arg) + { + return new Object(arg); + } + + template + static void destroy(Object* o) + { + delete o; + } + + template + static Object*& next(Object* o) + { + return o->next_; + } + + template + static Object*& prev(Object* o) + { + return o->prev_; + } +}; + +template +class object_pool + : private noncopyable +{ +public: + // Constructor. + object_pool() + : live_list_(0), + free_list_(0) + { + } + + // Destructor destroys all objects. + ~object_pool() + { + destroy_list(live_list_); + destroy_list(free_list_); + } + + // Get the object at the start of the live list. + Object* first() + { + return live_list_; + } + + // Allocate a new object. + Object* alloc() + { + Object* o = free_list_; + if (o) + free_list_ = object_pool_access::next(free_list_); + else + o = object_pool_access::create(); + + object_pool_access::next(o) = live_list_; + object_pool_access::prev(o) = 0; + if (live_list_) + object_pool_access::prev(live_list_) = o; + live_list_ = o; + + return o; + } + + // Allocate a new object with an argument. + template + Object* alloc(Arg arg) + { + Object* o = free_list_; + if (o) + free_list_ = object_pool_access::next(free_list_); + else + o = object_pool_access::create(arg); + + object_pool_access::next(o) = live_list_; + object_pool_access::prev(o) = 0; + if (live_list_) + object_pool_access::prev(live_list_) = o; + live_list_ = o; + + return o; + } + + // Free an object. Moves it to the free list. No destructors are run. + void free(Object* o) + { + if (live_list_ == o) + live_list_ = object_pool_access::next(o); + + if (object_pool_access::prev(o)) + { + object_pool_access::next(object_pool_access::prev(o)) + = object_pool_access::next(o); + } + + if (object_pool_access::next(o)) + { + object_pool_access::prev(object_pool_access::next(o)) + = object_pool_access::prev(o); + } + + object_pool_access::next(o) = free_list_; + object_pool_access::prev(o) = 0; + free_list_ = o; + } + +private: + // Helper function to destroy all elements in a list. + void destroy_list(Object* list) + { + while (list) + { + Object* o = list; + list = object_pool_access::next(o); + object_pool_access::destroy(o); + } + } + + // The list of live objects. + Object* live_list_; + + // The free list. + Object* free_list_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_OBJECT_POOL_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/old_win_sdk_compat.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/old_win_sdk_compat.hpp new file mode 100644 index 000000000..b0328715c --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/old_win_sdk_compat.hpp @@ -0,0 +1,214 @@ +// +// detail/old_win_sdk_compat.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_OLD_WIN_SDK_COMPAT_HPP +#define ASIO_DETAIL_OLD_WIN_SDK_COMPAT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +// Guess whether we are building against on old Platform SDK. +#if !defined(IN6ADDR_ANY_INIT) +#define ASIO_HAS_OLD_WIN_SDK 1 +#endif // !defined(IN6ADDR_ANY_INIT) + +#if defined(ASIO_HAS_OLD_WIN_SDK) + +// Emulation of types that are missing from old Platform SDKs. +// +// N.B. this emulation is also used if building for a Windows 2000 target with +// a recent (i.e. Vista or later) SDK, as the SDK does not provide IPv6 support +// in that case. + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +enum +{ + sockaddr_storage_maxsize = 128, // Maximum size. + sockaddr_storage_alignsize = (sizeof(__int64)), // Desired alignment. + sockaddr_storage_pad1size = (sockaddr_storage_alignsize - sizeof(short)), + sockaddr_storage_pad2size = (sockaddr_storage_maxsize - + (sizeof(short) + sockaddr_storage_pad1size + sockaddr_storage_alignsize)) +}; + +struct sockaddr_storage_emulation +{ + short ss_family; + char __ss_pad1[sockaddr_storage_pad1size]; + __int64 __ss_align; + char __ss_pad2[sockaddr_storage_pad2size]; +}; + +struct in6_addr_emulation +{ + union + { + u_char Byte[16]; + u_short Word[8]; + } u; +}; + +#if !defined(s6_addr) +# define _S6_un u +# define _S6_u8 Byte +# define s6_addr _S6_un._S6_u8 +#endif // !defined(s6_addr) + +struct sockaddr_in6_emulation +{ + short sin6_family; + u_short sin6_port; + u_long sin6_flowinfo; + in6_addr_emulation sin6_addr; + u_long sin6_scope_id; +}; + +struct ipv6_mreq_emulation +{ + in6_addr_emulation ipv6mr_multiaddr; + unsigned int ipv6mr_interface; +}; + +struct addrinfo_emulation +{ + int ai_flags; + int ai_family; + int ai_socktype; + int ai_protocol; + size_t ai_addrlen; + char* ai_canonname; + sockaddr* ai_addr; + addrinfo_emulation* ai_next; +}; + +#if !defined(AI_PASSIVE) +# define AI_PASSIVE 0x1 +#endif + +#if !defined(AI_CANONNAME) +# define AI_CANONNAME 0x2 +#endif + +#if !defined(AI_NUMERICHOST) +# define AI_NUMERICHOST 0x4 +#endif + +#if !defined(EAI_AGAIN) +# define EAI_AGAIN WSATRY_AGAIN +#endif + +#if !defined(EAI_BADFLAGS) +# define EAI_BADFLAGS WSAEINVAL +#endif + +#if !defined(EAI_FAIL) +# define EAI_FAIL WSANO_RECOVERY +#endif + +#if !defined(EAI_FAMILY) +# define EAI_FAMILY WSAEAFNOSUPPORT +#endif + +#if !defined(EAI_MEMORY) +# define EAI_MEMORY WSA_NOT_ENOUGH_MEMORY +#endif + +#if !defined(EAI_NODATA) +# define EAI_NODATA WSANO_DATA +#endif + +#if !defined(EAI_NONAME) +# define EAI_NONAME WSAHOST_NOT_FOUND +#endif + +#if !defined(EAI_SERVICE) +# define EAI_SERVICE WSATYPE_NOT_FOUND +#endif + +#if !defined(EAI_SOCKTYPE) +# define EAI_SOCKTYPE WSAESOCKTNOSUPPORT +#endif + +#if !defined(NI_NOFQDN) +# define NI_NOFQDN 0x01 +#endif + +#if !defined(NI_NUMERICHOST) +# define NI_NUMERICHOST 0x02 +#endif + +#if !defined(NI_NAMEREQD) +# define NI_NAMEREQD 0x04 +#endif + +#if !defined(NI_NUMERICSERV) +# define NI_NUMERICSERV 0x08 +#endif + +#if !defined(NI_DGRAM) +# define NI_DGRAM 0x10 +#endif + +#if !defined(IPPROTO_IPV6) +# define IPPROTO_IPV6 41 +#endif + +#if !defined(IPV6_UNICAST_HOPS) +# define IPV6_UNICAST_HOPS 4 +#endif + +#if !defined(IPV6_MULTICAST_IF) +# define IPV6_MULTICAST_IF 9 +#endif + +#if !defined(IPV6_MULTICAST_HOPS) +# define IPV6_MULTICAST_HOPS 10 +#endif + +#if !defined(IPV6_MULTICAST_LOOP) +# define IPV6_MULTICAST_LOOP 11 +#endif + +#if !defined(IPV6_JOIN_GROUP) +# define IPV6_JOIN_GROUP 12 +#endif + +#if !defined(IPV6_LEAVE_GROUP) +# define IPV6_LEAVE_GROUP 13 +#endif + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_OLD_WIN_SDK) + +// Even newer Platform SDKs that support IPv6 may not define IPV6_V6ONLY. +#if !defined(IPV6_V6ONLY) +# define IPV6_V6ONLY 27 +#endif + +// Some SDKs (e.g. Windows CE) don't define IPPROTO_ICMPV6. +#if !defined(IPPROTO_ICMPV6) +# define IPPROTO_ICMPV6 58 +#endif + +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +#endif // ASIO_DETAIL_OLD_WIN_SDK_COMPAT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/op_queue.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/op_queue.hpp new file mode 100644 index 000000000..47a55d67c --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/op_queue.hpp @@ -0,0 +1,162 @@ +// +// detail/op_queue.hpp +// ~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_OP_QUEUE_HPP +#define ASIO_DETAIL_OP_QUEUE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class op_queue; + +class op_queue_access +{ +public: + template + static Operation* next(Operation* o) + { + return static_cast(o->next_); + } + + template + static void next(Operation1*& o1, Operation2* o2) + { + o1->next_ = o2; + } + + template + static void destroy(Operation* o) + { + o->destroy(); + } + + template + static Operation*& front(op_queue& q) + { + return q.front_; + } + + template + static Operation*& back(op_queue& q) + { + return q.back_; + } +}; + +template +class op_queue + : private noncopyable +{ +public: + // Constructor. + op_queue() + : front_(0), + back_(0) + { + } + + // Destructor destroys all operations. + ~op_queue() + { + while (Operation* op = front_) + { + pop(); + op_queue_access::destroy(op); + } + } + + // Get the operation at the front of the queue. + Operation* front() + { + return front_; + } + + // Pop an operation from the front of the queue. + void pop() + { + if (front_) + { + Operation* tmp = front_; + front_ = op_queue_access::next(front_); + if (front_ == 0) + back_ = 0; + op_queue_access::next(tmp, static_cast(0)); + } + } + + // Push an operation on to the back of the queue. + void push(Operation* h) + { + op_queue_access::next(h, static_cast(0)); + if (back_) + { + op_queue_access::next(back_, h); + back_ = h; + } + else + { + front_ = back_ = h; + } + } + + // Push all operations from another queue on to the back of the queue. The + // source queue may contain operations of a derived type. + template + void push(op_queue& q) + { + if (Operation* other_front = op_queue_access::front(q)) + { + if (back_) + op_queue_access::next(back_, other_front); + else + front_ = other_front; + back_ = op_queue_access::back(q); + op_queue_access::front(q) = 0; + op_queue_access::back(q) = 0; + } + } + + // Whether the queue is empty. + bool empty() const + { + return front_ == 0; + } + + // Test whether an operation is already enqueued. + bool is_enqueued(Operation* o) const + { + return op_queue_access::next(o) != 0 || back_ == o; + } + +private: + friend class op_queue_access; + + // The front of the queue. + Operation* front_; + + // The back of the queue. + Operation* back_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_OP_QUEUE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/operation.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/operation.hpp new file mode 100644 index 000000000..51d877eeb --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/operation.hpp @@ -0,0 +1,38 @@ +// +// detail/operation.hpp +// ~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_OPERATION_HPP +#define ASIO_DETAIL_OPERATION_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) +# include "asio/detail/win_iocp_operation.hpp" +#else +# include "asio/detail/scheduler_operation.hpp" +#endif + +namespace asio { +namespace detail { + +#if defined(ASIO_HAS_IOCP) +typedef win_iocp_operation operation; +#else +typedef scheduler_operation operation; +#endif + +} // namespace detail +} // namespace asio + +#endif // ASIO_DETAIL_OPERATION_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/pipe_select_interrupter.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/pipe_select_interrupter.hpp new file mode 100644 index 000000000..74077eff1 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/pipe_select_interrupter.hpp @@ -0,0 +1,89 @@ +// +// detail/pipe_select_interrupter.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_PIPE_SELECT_INTERRUPTER_HPP +#define ASIO_DETAIL_PIPE_SELECT_INTERRUPTER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_WINDOWS) +#if !defined(ASIO_WINDOWS_RUNTIME) +#if !defined(__CYGWIN__) +#if !defined(__SYMBIAN32__) +#if !defined(ASIO_HAS_EVENTFD) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class pipe_select_interrupter +{ +public: + // Constructor. + ASIO_DECL pipe_select_interrupter(); + + // Destructor. + ASIO_DECL ~pipe_select_interrupter(); + + // Recreate the interrupter's descriptors. Used after a fork. + ASIO_DECL void recreate(); + + // Interrupt the select call. + ASIO_DECL void interrupt(); + + // Reset the select interrupter. Returns true if the reset was successful. + ASIO_DECL bool reset(); + + // Get the read descriptor to be passed to select. + int read_descriptor() const + { + return read_descriptor_; + } + +private: + // Open the descriptors. Throws on error. + ASIO_DECL void open_descriptors(); + + // Close the descriptors. + ASIO_DECL void close_descriptors(); + + // The read end of a connection used to interrupt the select call. This file + // descriptor is passed to select such that when it is time to stop, a single + // byte will be written on the other end of the connection and this + // descriptor will become readable. + int read_descriptor_; + + // The write end of a connection used to interrupt the select call. A single + // byte may be written to this to wake up the select which is waiting for the + // other end to become readable. + int write_descriptor_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/pipe_select_interrupter.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // !defined(ASIO_HAS_EVENTFD) +#endif // !defined(__SYMBIAN32__) +#endif // !defined(__CYGWIN__) +#endif // !defined(ASIO_WINDOWS_RUNTIME) +#endif // !defined(ASIO_WINDOWS) + +#endif // ASIO_DETAIL_PIPE_SELECT_INTERRUPTER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/pop_options.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/pop_options.hpp new file mode 100644 index 000000000..f64300a81 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/pop_options.hpp @@ -0,0 +1,141 @@ +// +// detail/pop_options.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +// No header guard + +#if defined(__COMO__) + +// Comeau C++ + +#elif defined(__DMC__) + +// Digital Mars C++ + +#elif defined(__INTEL_COMPILER) || defined(__ICL) \ + || defined(__ICC) || defined(__ECC) + +// Intel C++ + +# if (__GNUC__ == 4 && __GNUC_MINOR__ >= 1) || (__GNUC__ > 4) +# if !defined(ASIO_DISABLE_VISIBILITY) +# pragma GCC visibility pop +# endif // !defined(ASIO_DISABLE_VISIBILITY) +# endif // (__GNUC__ == 4 && __GNUC_MINOR__ >= 1) || (__GNUC__ > 4) + +#elif defined(__clang__) + +// Clang + +# if defined(__OBJC__) +# if !defined(__APPLE_CC__) || (__APPLE_CC__ <= 1) +# if defined(ASIO_OBJC_WORKAROUND) +# undef Protocol +# undef id +# undef ASIO_OBJC_WORKAROUND +# endif +# endif +# endif + +# if !defined(_WIN32) && !defined(__WIN32__) && !defined(WIN32) +# if !defined(ASIO_DISABLE_VISIBILITY) +# pragma GCC visibility pop +# endif // !defined(ASIO_DISABLE_VISIBILITY) +# endif // !defined(_WIN32) && !defined(__WIN32__) && !defined(WIN32) + +# pragma GCC diagnostic pop + +#elif defined(__GNUC__) + +// GNU C++ + +# if defined(__MINGW32__) || defined(__CYGWIN__) +# pragma pack (pop) +# endif + +# if defined(__OBJC__) +# if !defined(__APPLE_CC__) || (__APPLE_CC__ <= 1) +# if defined(ASIO_OBJC_WORKAROUND) +# undef Protocol +# undef id +# undef ASIO_OBJC_WORKAROUND +# endif +# endif +# endif + +# if (__GNUC__ == 4 && __GNUC_MINOR__ >= 1) || (__GNUC__ > 4) +# if !defined(ASIO_DISABLE_VISIBILITY) +# pragma GCC visibility pop +# endif // !defined(ASIO_DISABLE_VISIBILITY) +# endif // (__GNUC__ == 4 && __GNUC_MINOR__ >= 1) || (__GNUC__ > 4) + +# pragma GCC diagnostic pop + +#elif defined(__KCC) + +// Kai C++ + +#elif defined(__sgi) + +// SGI MIPSpro C++ + +#elif defined(__DECCXX) + +// Compaq Tru64 Unix cxx + +#elif defined(__ghs) + +// Greenhills C++ + +#elif defined(__BORLANDC__) && !defined(__clang__) + +// Borland C++ + +# pragma option pop +# pragma nopushoptwarn +# pragma nopackwarning + +#elif defined(__MWERKS__) + +// Metrowerks CodeWarrior + +#elif defined(__SUNPRO_CC) + +// Sun Workshop Compiler C++ + +#elif defined(__HP_aCC) + +// HP aCC + +#elif defined(__MRC__) || defined(__SC__) + +// MPW MrCpp or SCpp + +#elif defined(__IBMCPP__) + +// IBM Visual Age + +#elif defined(_MSC_VER) + +// Microsoft Visual C++ +// +// Must remain the last #elif since some other vendors (Metrowerks, for example) +// also #define _MSC_VER + +# pragma warning (pop) +# pragma pack (pop) + +# if defined(__cplusplus_cli) || defined(__cplusplus_winrt) +# if defined(ASIO_CLR_WORKAROUND) +# undef generic +# undef ASIO_CLR_WORKAROUND +# endif +# endif + +#endif diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_event.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_event.hpp new file mode 100644 index 000000000..b194977c1 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_event.hpp @@ -0,0 +1,175 @@ +// +// detail/posix_event.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_POSIX_EVENT_HPP +#define ASIO_DETAIL_POSIX_EVENT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_PTHREADS) + +#include +#include +#include "asio/detail/assert.hpp" +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class posix_event + : private noncopyable +{ +public: + // Constructor. + ASIO_DECL posix_event(); + + // Destructor. + ~posix_event() + { + ::pthread_cond_destroy(&cond_); + } + + // Signal the event. (Retained for backward compatibility.) + template + void signal(Lock& lock) + { + this->signal_all(lock); + } + + // Signal all waiters. + template + void signal_all(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + (void)lock; + state_ |= 1; + ::pthread_cond_broadcast(&cond_); // Ignore EINVAL. + } + + // Unlock the mutex and signal one waiter. + template + void unlock_and_signal_one(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + state_ |= 1; + bool have_waiters = (state_ > 1); + lock.unlock(); + if (have_waiters) + ::pthread_cond_signal(&cond_); // Ignore EINVAL. + } + + // Unlock the mutex and signal one waiter who may destroy us. + template + void unlock_and_signal_one_for_destruction(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + state_ |= 1; + bool have_waiters = (state_ > 1); + if (have_waiters) + ::pthread_cond_signal(&cond_); // Ignore EINVAL. + lock.unlock(); + } + + // If there's a waiter, unlock the mutex and signal it. + template + bool maybe_unlock_and_signal_one(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + state_ |= 1; + if (state_ > 1) + { + lock.unlock(); + ::pthread_cond_signal(&cond_); // Ignore EINVAL. + return true; + } + return false; + } + + // Reset the event. + template + void clear(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + (void)lock; + state_ &= ~std::size_t(1); + } + + // Wait for the event to become signalled. + template + void wait(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + while ((state_ & 1) == 0) + { + state_ += 2; + ::pthread_cond_wait(&cond_, &lock.mutex().mutex_); // Ignore EINVAL. + state_ -= 2; + } + } + + // Timed wait for the event to become signalled. + template + bool wait_for_usec(Lock& lock, long usec) + { + ASIO_ASSERT(lock.locked()); + if ((state_ & 1) == 0) + { + state_ += 2; + timespec ts; +#if (defined(__MACH__) && defined(__APPLE__)) \ + || (defined(__ANDROID__) && (__ANDROID_API__ < 21) \ + && defined(HAVE_PTHREAD_COND_TIMEDWAIT_RELATIVE)) + ts.tv_sec = usec / 1000000; + ts.tv_nsec = (usec % 1000000) * 1000; + ::pthread_cond_timedwait_relative_np( + &cond_, &lock.mutex().mutex_, &ts); // Ignore EINVAL. +#else // (defined(__MACH__) && defined(__APPLE__)) + // || (defined(__ANDROID__) && (__ANDROID_API__ < 21) + // && defined(HAVE_PTHREAD_COND_TIMEDWAIT_RELATIVE)) + if (::clock_gettime(CLOCK_MONOTONIC, &ts) == 0) + { + ts.tv_sec += usec / 1000000; + ts.tv_nsec += (usec % 1000000) * 1000; + ts.tv_sec += ts.tv_nsec / 1000000000; + ts.tv_nsec = ts.tv_nsec % 1000000000; + ::pthread_cond_timedwait(&cond_, + &lock.mutex().mutex_, &ts); // Ignore EINVAL. + } +#endif // (defined(__MACH__) && defined(__APPLE__)) + // || (defined(__ANDROID__) && (__ANDROID_API__ < 21) + // && defined(HAVE_PTHREAD_COND_TIMEDWAIT_RELATIVE)) + state_ -= 2; + } + return (state_ & 1) != 0; + } + +private: + ::pthread_cond_t cond_; + std::size_t state_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/posix_event.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_HAS_PTHREADS) + +#endif // ASIO_DETAIL_POSIX_EVENT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_fd_set_adapter.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_fd_set_adapter.hpp new file mode 100644 index 000000000..4e57de942 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_fd_set_adapter.hpp @@ -0,0 +1,118 @@ +// +// detail/posix_fd_set_adapter.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_POSIX_FD_SET_ADAPTER_HPP +#define ASIO_DETAIL_POSIX_FD_SET_ADAPTER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_WINDOWS) \ + && !defined(__CYGWIN__) \ + && !defined(ASIO_WINDOWS_RUNTIME) + +#include +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/reactor_op_queue.hpp" +#include "asio/detail/socket_types.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Adapts the FD_SET type to meet the Descriptor_Set concept's requirements. +class posix_fd_set_adapter : noncopyable +{ +public: + posix_fd_set_adapter() + : max_descriptor_(invalid_socket) + { + using namespace std; // Needed for memset on Solaris. + FD_ZERO(&fd_set_); + } + + void reset() + { + using namespace std; // Needed for memset on Solaris. + FD_ZERO(&fd_set_); + } + + bool set(socket_type descriptor) + { + if (descriptor < (socket_type)FD_SETSIZE) + { + if (max_descriptor_ == invalid_socket || descriptor > max_descriptor_) + max_descriptor_ = descriptor; + FD_SET(descriptor, &fd_set_); + return true; + } + return false; + } + + void set(reactor_op_queue& operations, op_queue& ops) + { + reactor_op_queue::iterator i = operations.begin(); + while (i != operations.end()) + { + reactor_op_queue::iterator op_iter = i++; + if (!set(op_iter->first)) + { + asio::error_code ec(error::fd_set_failure); + operations.cancel_operations(op_iter, ops, ec); + } + } + } + + bool is_set(socket_type descriptor) const + { + return FD_ISSET(descriptor, &fd_set_) != 0; + } + + operator fd_set*() + { + return &fd_set_; + } + + socket_type max_descriptor() const + { + return max_descriptor_; + } + + void perform(reactor_op_queue& operations, + op_queue& ops) const + { + reactor_op_queue::iterator i = operations.begin(); + while (i != operations.end()) + { + reactor_op_queue::iterator op_iter = i++; + if (is_set(op_iter->first)) + operations.perform_operations(op_iter, ops); + } + } + +private: + mutable fd_set fd_set_; + socket_type max_descriptor_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_WINDOWS) + // && !defined(__CYGWIN__) + // && !defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_POSIX_FD_SET_ADAPTER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_global.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_global.hpp new file mode 100644 index 000000000..9f3a8d12e --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_global.hpp @@ -0,0 +1,80 @@ +// +// detail/posix_global.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_POSIX_GLOBAL_HPP +#define ASIO_DETAIL_POSIX_GLOBAL_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_PTHREADS) + +#include +#include + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +struct posix_global_impl +{ + // Helper function to perform initialisation. + static void do_init() + { + instance_.static_ptr_ = instance_.ptr_ = new T; + } + + // Destructor automatically cleans up the global. + ~posix_global_impl() + { + delete static_ptr_; + } + + static ::pthread_once_t init_once_; + static T* static_ptr_; + static posix_global_impl instance_; + T* ptr_; +}; + +template +::pthread_once_t posix_global_impl::init_once_ = PTHREAD_ONCE_INIT; + +template +T* posix_global_impl::static_ptr_ = 0; + +template +posix_global_impl posix_global_impl::instance_; + +template +T& posix_global() +{ + int result = ::pthread_once( + &posix_global_impl::init_once_, + &posix_global_impl::do_init); + + if (result != 0) + std::terminate(); + + return *posix_global_impl::instance_.ptr_; +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_PTHREADS) + +#endif // ASIO_DETAIL_POSIX_GLOBAL_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_mutex.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_mutex.hpp new file mode 100644 index 000000000..293d46729 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_mutex.hpp @@ -0,0 +1,76 @@ +// +// detail/posix_mutex.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_POSIX_MUTEX_HPP +#define ASIO_DETAIL_POSIX_MUTEX_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_PTHREADS) + +#include +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/scoped_lock.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class posix_event; + +class posix_mutex + : private noncopyable +{ +public: + typedef asio::detail::scoped_lock scoped_lock; + + // Constructor. + ASIO_DECL posix_mutex(); + + // Destructor. + ~posix_mutex() + { + ::pthread_mutex_destroy(&mutex_); // Ignore EBUSY. + } + + // Lock the mutex. + void lock() + { + (void)::pthread_mutex_lock(&mutex_); // Ignore EINVAL. + } + + // Unlock the mutex. + void unlock() + { + (void)::pthread_mutex_unlock(&mutex_); // Ignore EINVAL. + } + +private: + friend class posix_event; + ::pthread_mutex_t mutex_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/posix_mutex.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_HAS_PTHREADS) + +#endif // ASIO_DETAIL_POSIX_MUTEX_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_signal_blocker.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_signal_blocker.hpp new file mode 100644 index 000000000..08b89cb0a --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_signal_blocker.hpp @@ -0,0 +1,85 @@ +// +// detail/posix_signal_blocker.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_POSIX_SIGNAL_BLOCKER_HPP +#define ASIO_DETAIL_POSIX_SIGNAL_BLOCKER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_PTHREADS) + +#include +#include +#include +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class posix_signal_blocker + : private noncopyable +{ +public: + // Constructor blocks all signals for the calling thread. + posix_signal_blocker() + : blocked_(false) + { + sigset_t new_mask; + sigfillset(&new_mask); + blocked_ = (pthread_sigmask(SIG_BLOCK, &new_mask, &old_mask_) == 0); + } + + // Destructor restores the previous signal mask. + ~posix_signal_blocker() + { + if (blocked_) + pthread_sigmask(SIG_SETMASK, &old_mask_, 0); + } + + // Block all signals for the calling thread. + void block() + { + if (!blocked_) + { + sigset_t new_mask; + sigfillset(&new_mask); + blocked_ = (pthread_sigmask(SIG_BLOCK, &new_mask, &old_mask_) == 0); + } + } + + // Restore the previous signal mask. + void unblock() + { + if (blocked_) + blocked_ = (pthread_sigmask(SIG_SETMASK, &old_mask_, 0) != 0); + } + +private: + // Have signals been blocked. + bool blocked_; + + // The previous signal mask. + sigset_t old_mask_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_PTHREADS) + +#endif // ASIO_DETAIL_POSIX_SIGNAL_BLOCKER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_static_mutex.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_static_mutex.hpp new file mode 100644 index 000000000..7784434aa --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_static_mutex.hpp @@ -0,0 +1,64 @@ +// +// detail/posix_static_mutex.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_POSIX_STATIC_MUTEX_HPP +#define ASIO_DETAIL_POSIX_STATIC_MUTEX_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_PTHREADS) + +#include +#include "asio/detail/scoped_lock.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +struct posix_static_mutex +{ + typedef asio::detail::scoped_lock scoped_lock; + + // Initialise the mutex. + void init() + { + // Nothing to do. + } + + // Lock the mutex. + void lock() + { + (void)::pthread_mutex_lock(&mutex_); // Ignore EINVAL. + } + + // Unlock the mutex. + void unlock() + { + (void)::pthread_mutex_unlock(&mutex_); // Ignore EINVAL. + } + + ::pthread_mutex_t mutex_; +}; + +#define ASIO_POSIX_STATIC_MUTEX_INIT { PTHREAD_MUTEX_INITIALIZER } + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_PTHREADS) + +#endif // ASIO_DETAIL_POSIX_STATIC_MUTEX_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_thread.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_thread.hpp new file mode 100644 index 000000000..7cd63df88 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_thread.hpp @@ -0,0 +1,109 @@ +// +// detail/posix_thread.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_POSIX_THREAD_HPP +#define ASIO_DETAIL_POSIX_THREAD_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_PTHREADS) + +#include +#include +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +extern "C" +{ + ASIO_DECL void* asio_detail_posix_thread_function(void* arg); +} + +class posix_thread + : private noncopyable +{ +public: + // Constructor. + template + posix_thread(Function f, unsigned int = 0) + : joined_(false) + { + start_thread(new func(f)); + } + + // Destructor. + ASIO_DECL ~posix_thread(); + + // Wait for the thread to exit. + ASIO_DECL void join(); + + // Get number of CPUs. + ASIO_DECL static std::size_t hardware_concurrency(); + +private: + friend void* asio_detail_posix_thread_function(void* arg); + + class func_base + { + public: + virtual ~func_base() {} + virtual void run() = 0; + }; + + struct auto_func_base_ptr + { + func_base* ptr; + ~auto_func_base_ptr() { delete ptr; } + }; + + template + class func + : public func_base + { + public: + func(Function f) + : f_(f) + { + } + + virtual void run() + { + f_(); + } + + private: + Function f_; + }; + + ASIO_DECL void start_thread(func_base* arg); + + ::pthread_t thread_; + bool joined_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/posix_thread.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_HAS_PTHREADS) + +#endif // ASIO_DETAIL_POSIX_THREAD_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_tss_ptr.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_tss_ptr.hpp new file mode 100644 index 000000000..b4fa0d558 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/posix_tss_ptr.hpp @@ -0,0 +1,79 @@ +// +// detail/posix_tss_ptr.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_POSIX_TSS_PTR_HPP +#define ASIO_DETAIL_POSIX_TSS_PTR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_PTHREADS) + +#include +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Helper function to create thread-specific storage. +ASIO_DECL void posix_tss_ptr_create(pthread_key_t& key); + +template +class posix_tss_ptr + : private noncopyable +{ +public: + // Constructor. + posix_tss_ptr() + { + posix_tss_ptr_create(tss_key_); + } + + // Destructor. + ~posix_tss_ptr() + { + ::pthread_key_delete(tss_key_); + } + + // Get the value. + operator T*() const + { + return static_cast(::pthread_getspecific(tss_key_)); + } + + // Set the value. + void operator=(T* value) + { + ::pthread_setspecific(tss_key_, value); + } + +private: + // Thread-specific storage to allow unlocked access to determine whether a + // thread is a member of the pool. + pthread_key_t tss_key_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/posix_tss_ptr.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_HAS_PTHREADS) + +#endif // ASIO_DETAIL_POSIX_TSS_PTR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/push_options.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/push_options.hpp new file mode 100644 index 000000000..66e21dc99 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/push_options.hpp @@ -0,0 +1,185 @@ +// +// detail/push_options.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +// No header guard + +#if defined(__COMO__) + +// Comeau C++ + +#elif defined(__DMC__) + +// Digital Mars C++ + +#elif defined(__INTEL_COMPILER) || defined(__ICL) \ + || defined(__ICC) || defined(__ECC) + +// Intel C++ + +# if (__GNUC__ == 4 && __GNUC_MINOR__ >= 1) || (__GNUC__ > 4) +# if !defined(ASIO_DISABLE_VISIBILITY) +# pragma GCC visibility push (default) +# endif // !defined(ASIO_DISABLE_VISIBILITY) +# endif // (__GNUC__ == 4 && __GNUC_MINOR__ >= 1) || (__GNUC__ > 4) + +#elif defined(__clang__) + +// Clang + +# if defined(__OBJC__) +# if !defined(__APPLE_CC__) || (__APPLE_CC__ <= 1) +# if !defined(ASIO_DISABLE_OBJC_WORKAROUND) +# if !defined(Protocol) && !defined(id) +# define Protocol cpp_Protocol +# define id cpp_id +# define ASIO_OBJC_WORKAROUND +# endif +# endif +# endif +# endif + +# if !defined(_WIN32) && !defined(__WIN32__) && !defined(WIN32) +# if !defined(ASIO_DISABLE_VISIBILITY) +# pragma GCC visibility push (default) +# endif // !defined(ASIO_DISABLE_VISIBILITY) +# endif // !defined(_WIN32) && !defined(__WIN32__) && !defined(WIN32) + +# pragma GCC diagnostic push +# pragma GCC diagnostic ignored "-Wnon-virtual-dtor" + +#elif defined(__GNUC__) + +// GNU C++ + +# if defined(__MINGW32__) || defined(__CYGWIN__) +# pragma pack (push, 8) +# endif + +# if defined(__OBJC__) +# if !defined(__APPLE_CC__) || (__APPLE_CC__ <= 1) +# if !defined(ASIO_DISABLE_OBJC_WORKAROUND) +# if !defined(Protocol) && !defined(id) +# define Protocol cpp_Protocol +# define id cpp_id +# define ASIO_OBJC_WORKAROUND +# endif +# endif +# endif +# endif + +# if (__GNUC__ == 4 && __GNUC_MINOR__ >= 1) || (__GNUC__ > 4) +# if !defined(ASIO_DISABLE_VISIBILITY) +# pragma GCC visibility push (default) +# endif // !defined(ASIO_DISABLE_VISIBILITY) +# endif // (__GNUC__ == 4 && __GNUC_MINOR__ >= 1) || (__GNUC__ > 4) + +# pragma GCC diagnostic push +# pragma GCC diagnostic ignored "-Wnon-virtual-dtor" +# if (__GNUC__ >= 7) +# pragma GCC diagnostic ignored "-Wimplicit-fallthrough" +# endif // (__GNUC__ >= 7) + +#elif defined(__KCC) + +// Kai C++ + +#elif defined(__sgi) + +// SGI MIPSpro C++ + +#elif defined(__DECCXX) + +// Compaq Tru64 Unix cxx + +#elif defined(__ghs) + +// Greenhills C++ + +#elif defined(__BORLANDC__) && !defined(__clang__) + +// Borland C++ + +# pragma option push -a8 -b -Ve- -Vx- -w-inl -vi- +# pragma nopushoptwarn +# pragma nopackwarning +# if !defined(__MT__) +# error Multithreaded RTL must be selected. +# endif // !defined(__MT__) + +#elif defined(__MWERKS__) + +// Metrowerks CodeWarrior + +#elif defined(__SUNPRO_CC) + +// Sun Workshop Compiler C++ + +#elif defined(__HP_aCC) + +// HP aCC + +#elif defined(__MRC__) || defined(__SC__) + +// MPW MrCpp or SCpp + +#elif defined(__IBMCPP__) + +// IBM Visual Age + +#elif defined(_MSC_VER) + +// Microsoft Visual C++ +// +// Must remain the last #elif since some other vendors (Metrowerks, for example) +// also #define _MSC_VER + +# pragma warning (disable:4103) +# pragma warning (push) +# pragma warning (disable:4127) +# pragma warning (disable:4180) +# pragma warning (disable:4244) +# pragma warning (disable:4355) +# pragma warning (disable:4510) +# pragma warning (disable:4512) +# pragma warning (disable:4610) +# pragma warning (disable:4675) +# if (_MSC_VER < 1600) +// Visual Studio 2008 generates spurious warnings about unused parameters. +# pragma warning (disable:4100) +# endif // (_MSC_VER < 1600) +# if defined(_M_IX86) && defined(_Wp64) +// The /Wp64 option is broken. If you want to check 64 bit portability, use a +// 64 bit compiler! +# pragma warning (disable:4311) +# pragma warning (disable:4312) +# endif // defined(_M_IX86) && defined(_Wp64) +# pragma pack (push, 8) +// Note that if the /Og optimisation flag is enabled with MSVC6, the compiler +// has a tendency to incorrectly optimise away some calls to member template +// functions, even though those functions contain code that should not be +// optimised away! Therefore we will always disable this optimisation option +// for the MSVC6 compiler. +# if (_MSC_VER < 1300) +# pragma optimize ("g", off) +# endif +# if !defined(_MT) +# error Multithreaded RTL must be selected. +# endif // !defined(_MT) + +# if defined(__cplusplus_cli) || defined(__cplusplus_winrt) +# if !defined(ASIO_DISABLE_CLR_WORKAROUND) +# if !defined(generic) +# define generic cpp_generic +# define ASIO_CLR_WORKAROUND +# endif +# endif +# endif + +#endif diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_descriptor_service.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_descriptor_service.hpp new file mode 100644 index 000000000..11f0328ff --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_descriptor_service.hpp @@ -0,0 +1,416 @@ +// +// detail/reactive_descriptor_service.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REACTIVE_DESCRIPTOR_SERVICE_HPP +#define ASIO_DETAIL_REACTIVE_DESCRIPTOR_SERVICE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_RUNTIME) \ + && !defined(__CYGWIN__) + +#include "asio/buffer.hpp" +#include "asio/execution_context.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/descriptor_ops.hpp" +#include "asio/detail/descriptor_read_op.hpp" +#include "asio/detail/descriptor_write_op.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/reactive_null_buffers_op.hpp" +#include "asio/detail/reactive_wait_op.hpp" +#include "asio/detail/reactor.hpp" +#include "asio/posix/descriptor_base.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class reactive_descriptor_service : + public execution_context_service_base +{ +public: + // The native type of a descriptor. + typedef int native_handle_type; + + // The implementation type of the descriptor. + class implementation_type + : private asio::detail::noncopyable + { + public: + // Default constructor. + implementation_type() + : descriptor_(-1), + state_(0) + { + } + + private: + // Only this service will have access to the internal values. + friend class reactive_descriptor_service; + + // The native descriptor representation. + int descriptor_; + + // The current state of the descriptor. + descriptor_ops::state_type state_; + + // Per-descriptor data used by the reactor. + reactor::per_descriptor_data reactor_data_; + }; + + // Constructor. + ASIO_DECL reactive_descriptor_service(execution_context& context); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void shutdown(); + + // Construct a new descriptor implementation. + ASIO_DECL void construct(implementation_type& impl); + + // Move-construct a new descriptor implementation. + ASIO_DECL void move_construct(implementation_type& impl, + implementation_type& other_impl) ASIO_NOEXCEPT; + + // Move-assign from another descriptor implementation. + ASIO_DECL void move_assign(implementation_type& impl, + reactive_descriptor_service& other_service, + implementation_type& other_impl); + + // Destroy a descriptor implementation. + ASIO_DECL void destroy(implementation_type& impl); + + // Assign a native descriptor to a descriptor implementation. + ASIO_DECL asio::error_code assign(implementation_type& impl, + const native_handle_type& native_descriptor, + asio::error_code& ec); + + // Determine whether the descriptor is open. + bool is_open(const implementation_type& impl) const + { + return impl.descriptor_ != -1; + } + + // Destroy a descriptor implementation. + ASIO_DECL asio::error_code close(implementation_type& impl, + asio::error_code& ec); + + // Get the native descriptor representation. + native_handle_type native_handle(const implementation_type& impl) const + { + return impl.descriptor_; + } + + // Release ownership of the native descriptor representation. + ASIO_DECL native_handle_type release(implementation_type& impl); + + // Cancel all operations associated with the descriptor. + ASIO_DECL asio::error_code cancel(implementation_type& impl, + asio::error_code& ec); + + // Perform an IO control command on the descriptor. + template + asio::error_code io_control(implementation_type& impl, + IO_Control_Command& command, asio::error_code& ec) + { + descriptor_ops::ioctl(impl.descriptor_, impl.state_, + command.name(), static_cast(command.data()), ec); + return ec; + } + + // Gets the non-blocking mode of the descriptor. + bool non_blocking(const implementation_type& impl) const + { + return (impl.state_ & descriptor_ops::user_set_non_blocking) != 0; + } + + // Sets the non-blocking mode of the descriptor. + asio::error_code non_blocking(implementation_type& impl, + bool mode, asio::error_code& ec) + { + descriptor_ops::set_user_non_blocking( + impl.descriptor_, impl.state_, mode, ec); + return ec; + } + + // Gets the non-blocking mode of the native descriptor implementation. + bool native_non_blocking(const implementation_type& impl) const + { + return (impl.state_ & descriptor_ops::internal_non_blocking) != 0; + } + + // Sets the non-blocking mode of the native descriptor implementation. + asio::error_code native_non_blocking(implementation_type& impl, + bool mode, asio::error_code& ec) + { + descriptor_ops::set_internal_non_blocking( + impl.descriptor_, impl.state_, mode, ec); + return ec; + } + + // Wait for the descriptor to become ready to read, ready to write, or to have + // pending error conditions. + asio::error_code wait(implementation_type& impl, + posix::descriptor_base::wait_type w, asio::error_code& ec) + { + switch (w) + { + case posix::descriptor_base::wait_read: + descriptor_ops::poll_read(impl.descriptor_, impl.state_, ec); + break; + case posix::descriptor_base::wait_write: + descriptor_ops::poll_write(impl.descriptor_, impl.state_, ec); + break; + case posix::descriptor_base::wait_error: + descriptor_ops::poll_error(impl.descriptor_, impl.state_, ec); + break; + default: + ec = asio::error::invalid_argument; + break; + } + + return ec; + } + + // Asynchronously wait for the descriptor to become ready to read, ready to + // write, or to have pending error conditions. + template + void async_wait(implementation_type& impl, + posix::descriptor_base::wait_type w, + Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef reactive_wait_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "descriptor", + &impl, impl.descriptor_, "async_wait")); + + int op_type; + switch (w) + { + case posix::descriptor_base::wait_read: + op_type = reactor::read_op; + break; + case posix::descriptor_base::wait_write: + op_type = reactor::write_op; + break; + case posix::descriptor_base::wait_error: + op_type = reactor::except_op; + break; + default: + p.p->ec_ = asio::error::invalid_argument; + reactor_.post_immediate_completion(p.p, is_continuation); + p.v = p.p = 0; + return; + } + + start_op(impl, op_type, p.p, is_continuation, false, false); + p.v = p.p = 0; + } + + // Write some data to the descriptor. + template + size_t write_some(implementation_type& impl, + const ConstBufferSequence& buffers, asio::error_code& ec) + { + typedef buffer_sequence_adapter bufs_type; + + if (bufs_type::is_single_buffer) + { + return descriptor_ops::sync_write1(impl.descriptor_, + impl.state_, bufs_type::first(buffers).data(), + bufs_type::first(buffers).size(), ec); + } + else + { + bufs_type bufs(buffers); + + return descriptor_ops::sync_write(impl.descriptor_, impl.state_, + bufs.buffers(), bufs.count(), bufs.all_empty(), ec); + } + } + + // Wait until data can be written without blocking. + size_t write_some(implementation_type& impl, + const null_buffers&, asio::error_code& ec) + { + // Wait for descriptor to become ready. + descriptor_ops::poll_write(impl.descriptor_, impl.state_, ec); + + return 0; + } + + // Start an asynchronous write. The data being sent must be valid for the + // lifetime of the asynchronous operation. + template + void async_write_some(implementation_type& impl, + const ConstBufferSequence& buffers, Handler& handler, + const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef descriptor_write_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, impl.descriptor_, buffers, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "descriptor", + &impl, impl.descriptor_, "async_write_some")); + + start_op(impl, reactor::write_op, p.p, is_continuation, true, + buffer_sequence_adapter::all_empty(buffers)); + p.v = p.p = 0; + } + + // Start an asynchronous wait until data can be written without blocking. + template + void async_write_some(implementation_type& impl, + const null_buffers&, Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef reactive_null_buffers_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "descriptor", + &impl, impl.descriptor_, "async_write_some(null_buffers)")); + + start_op(impl, reactor::write_op, p.p, is_continuation, false, false); + p.v = p.p = 0; + } + + // Read some data from the stream. Returns the number of bytes read. + template + size_t read_some(implementation_type& impl, + const MutableBufferSequence& buffers, asio::error_code& ec) + { + typedef buffer_sequence_adapter bufs_type; + + if (bufs_type::is_single_buffer) + { + return descriptor_ops::sync_read1(impl.descriptor_, + impl.state_, bufs_type::first(buffers).data(), + bufs_type::first(buffers).size(), ec); + } + else + { + bufs_type bufs(buffers); + + return descriptor_ops::sync_read(impl.descriptor_, impl.state_, + bufs.buffers(), bufs.count(), bufs.all_empty(), ec); + } + } + + // Wait until data can be read without blocking. + size_t read_some(implementation_type& impl, + const null_buffers&, asio::error_code& ec) + { + // Wait for descriptor to become ready. + descriptor_ops::poll_read(impl.descriptor_, impl.state_, ec); + + return 0; + } + + // Start an asynchronous read. The buffer for the data being read must be + // valid for the lifetime of the asynchronous operation. + template + void async_read_some(implementation_type& impl, + const MutableBufferSequence& buffers, + Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef descriptor_read_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, impl.descriptor_, buffers, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "descriptor", + &impl, impl.descriptor_, "async_read_some")); + + start_op(impl, reactor::read_op, p.p, is_continuation, true, + buffer_sequence_adapter::all_empty(buffers)); + p.v = p.p = 0; + } + + // Wait until data can be read without blocking. + template + void async_read_some(implementation_type& impl, + const null_buffers&, Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef reactive_null_buffers_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "descriptor", + &impl, impl.descriptor_, "async_read_some(null_buffers)")); + + start_op(impl, reactor::read_op, p.p, is_continuation, false, false); + p.v = p.p = 0; + } + +private: + // Start the asynchronous operation. + ASIO_DECL void start_op(implementation_type& impl, int op_type, + reactor_op* op, bool is_continuation, bool is_non_blocking, bool noop); + + // The selector that performs event demultiplexing for the service. + reactor& reactor_; + + // Cached success value to avoid accessing category singleton. + const asio::error_code success_ec_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/reactive_descriptor_service.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) + +#endif // ASIO_DETAIL_REACTIVE_DESCRIPTOR_SERVICE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_null_buffers_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_null_buffers_op.hpp new file mode 100644 index 000000000..190fafa8e --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_null_buffers_op.hpp @@ -0,0 +1,98 @@ +// +// detail/reactive_null_buffers_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REACTIVE_NULL_BUFFERS_OP_HPP +#define ASIO_DETAIL_REACTIVE_NULL_BUFFERS_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/reactor_op.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class reactive_null_buffers_op : public reactor_op +{ +public: + ASIO_DEFINE_HANDLER_PTR(reactive_null_buffers_op); + + reactive_null_buffers_op(const asio::error_code& success_ec, + Handler& handler, const IoExecutor& io_ex) + : reactor_op(success_ec, &reactive_null_buffers_op::do_perform, + &reactive_null_buffers_op::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static status do_perform(reactor_op*) + { + return done; + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the handler object. + reactive_null_buffers_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, o->ec_, o->bytes_transferred_); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_REACTIVE_NULL_BUFFERS_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_serial_port_service.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_serial_port_service.hpp new file mode 100644 index 000000000..f8af41135 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_serial_port_service.hpp @@ -0,0 +1,237 @@ +// +// detail/reactive_serial_port_service.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// Copyright (c) 2008 Rep Invariant Systems, Inc. (info@repinvariant.com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REACTIVE_SERIAL_PORT_SERVICE_HPP +#define ASIO_DETAIL_REACTIVE_SERIAL_PORT_SERVICE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_SERIAL_PORT) +#if !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) + +#include +#include "asio/error.hpp" +#include "asio/execution_context.hpp" +#include "asio/serial_port_base.hpp" +#include "asio/detail/descriptor_ops.hpp" +#include "asio/detail/reactive_descriptor_service.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Extend reactive_descriptor_service to provide serial port support. +class reactive_serial_port_service : + public execution_context_service_base +{ +public: + // The native type of a serial port. + typedef reactive_descriptor_service::native_handle_type native_handle_type; + + // The implementation type of the serial port. + typedef reactive_descriptor_service::implementation_type implementation_type; + + ASIO_DECL reactive_serial_port_service(execution_context& context); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void shutdown(); + + // Construct a new serial port implementation. + void construct(implementation_type& impl) + { + descriptor_service_.construct(impl); + } + + // Move-construct a new serial port implementation. + void move_construct(implementation_type& impl, + implementation_type& other_impl) + { + descriptor_service_.move_construct(impl, other_impl); + } + + // Move-assign from another serial port implementation. + void move_assign(implementation_type& impl, + reactive_serial_port_service& other_service, + implementation_type& other_impl) + { + descriptor_service_.move_assign(impl, + other_service.descriptor_service_, other_impl); + } + + // Destroy a serial port implementation. + void destroy(implementation_type& impl) + { + descriptor_service_.destroy(impl); + } + + // Open the serial port using the specified device name. + ASIO_DECL asio::error_code open(implementation_type& impl, + const std::string& device, asio::error_code& ec); + + // Assign a native descriptor to a serial port implementation. + asio::error_code assign(implementation_type& impl, + const native_handle_type& native_descriptor, + asio::error_code& ec) + { + return descriptor_service_.assign(impl, native_descriptor, ec); + } + + // Determine whether the serial port is open. + bool is_open(const implementation_type& impl) const + { + return descriptor_service_.is_open(impl); + } + + // Destroy a serial port implementation. + asio::error_code close(implementation_type& impl, + asio::error_code& ec) + { + return descriptor_service_.close(impl, ec); + } + + // Get the native serial port representation. + native_handle_type native_handle(implementation_type& impl) + { + return descriptor_service_.native_handle(impl); + } + + // Cancel all operations associated with the serial port. + asio::error_code cancel(implementation_type& impl, + asio::error_code& ec) + { + return descriptor_service_.cancel(impl, ec); + } + + // Set an option on the serial port. + template + asio::error_code set_option(implementation_type& impl, + const SettableSerialPortOption& option, asio::error_code& ec) + { + return do_set_option(impl, + &reactive_serial_port_service::store_option, + &option, ec); + } + + // Get an option from the serial port. + template + asio::error_code get_option(const implementation_type& impl, + GettableSerialPortOption& option, asio::error_code& ec) const + { + return do_get_option(impl, + &reactive_serial_port_service::load_option, + &option, ec); + } + + // Send a break sequence to the serial port. + asio::error_code send_break(implementation_type& impl, + asio::error_code& ec) + { + int result = ::tcsendbreak(descriptor_service_.native_handle(impl), 0); + descriptor_ops::get_last_error(ec, result < 0); + return ec; + } + + // Write the given data. Returns the number of bytes sent. + template + size_t write_some(implementation_type& impl, + const ConstBufferSequence& buffers, asio::error_code& ec) + { + return descriptor_service_.write_some(impl, buffers, ec); + } + + // Start an asynchronous write. The data being written must be valid for the + // lifetime of the asynchronous operation. + template + void async_write_some(implementation_type& impl, + const ConstBufferSequence& buffers, + Handler& handler, const IoExecutor& io_ex) + { + descriptor_service_.async_write_some(impl, buffers, handler, io_ex); + } + + // Read some data. Returns the number of bytes received. + template + size_t read_some(implementation_type& impl, + const MutableBufferSequence& buffers, asio::error_code& ec) + { + return descriptor_service_.read_some(impl, buffers, ec); + } + + // Start an asynchronous read. The buffer for the data being received must be + // valid for the lifetime of the asynchronous operation. + template + void async_read_some(implementation_type& impl, + const MutableBufferSequence& buffers, + Handler& handler, const IoExecutor& io_ex) + { + descriptor_service_.async_read_some(impl, buffers, handler, io_ex); + } + +private: + // Function pointer type for storing a serial port option. + typedef asio::error_code (*store_function_type)( + const void*, termios&, asio::error_code&); + + // Helper function template to store a serial port option. + template + static asio::error_code store_option(const void* option, + termios& storage, asio::error_code& ec) + { + static_cast(option)->store(storage, ec); + return ec; + } + + // Helper function to set a serial port option. + ASIO_DECL asio::error_code do_set_option( + implementation_type& impl, store_function_type store, + const void* option, asio::error_code& ec); + + // Function pointer type for loading a serial port option. + typedef asio::error_code (*load_function_type)( + void*, const termios&, asio::error_code&); + + // Helper function template to load a serial port option. + template + static asio::error_code load_option(void* option, + const termios& storage, asio::error_code& ec) + { + static_cast(option)->load(storage, ec); + return ec; + } + + // Helper function to get a serial port option. + ASIO_DECL asio::error_code do_get_option( + const implementation_type& impl, load_function_type load, + void* option, asio::error_code& ec) const; + + // The implementation used for initiating asynchronous operations. + reactive_descriptor_service descriptor_service_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/reactive_serial_port_service.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) +#endif // defined(ASIO_HAS_SERIAL_PORT) + +#endif // ASIO_DETAIL_REACTIVE_SERIAL_PORT_SERVICE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_accept_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_accept_op.hpp new file mode 100644 index 000000000..0bd927984 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_accept_op.hpp @@ -0,0 +1,242 @@ +// +// detail/reactive_socket_accept_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REACTIVE_SOCKET_ACCEPT_OP_HPP +#define ASIO_DETAIL_REACTIVE_SOCKET_ACCEPT_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/socket_holder.hpp" +#include "asio/detail/socket_ops.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class reactive_socket_accept_op_base : public reactor_op +{ +public: + reactive_socket_accept_op_base(const asio::error_code& success_ec, + socket_type socket, socket_ops::state_type state, Socket& peer, + const Protocol& protocol, typename Protocol::endpoint* peer_endpoint, + func_type complete_func) + : reactor_op(success_ec, + &reactive_socket_accept_op_base::do_perform, complete_func), + socket_(socket), + state_(state), + peer_(peer), + protocol_(protocol), + peer_endpoint_(peer_endpoint), + addrlen_(peer_endpoint ? peer_endpoint->capacity() : 0) + { + } + + static status do_perform(reactor_op* base) + { + reactive_socket_accept_op_base* o( + static_cast(base)); + + socket_type new_socket = invalid_socket; + status result = socket_ops::non_blocking_accept(o->socket_, + o->state_, o->peer_endpoint_ ? o->peer_endpoint_->data() : 0, + o->peer_endpoint_ ? &o->addrlen_ : 0, o->ec_, new_socket) + ? done : not_done; + o->new_socket_.reset(new_socket); + + ASIO_HANDLER_REACTOR_OPERATION((*o, "non_blocking_accept", o->ec_)); + + return result; + } + + void do_assign() + { + if (new_socket_.get() != invalid_socket) + { + if (peer_endpoint_) + peer_endpoint_->resize(addrlen_); + peer_.assign(protocol_, new_socket_.get(), ec_); + if (!ec_) + new_socket_.release(); + } + } + +private: + socket_type socket_; + socket_ops::state_type state_; + socket_holder new_socket_; + Socket& peer_; + Protocol protocol_; + typename Protocol::endpoint* peer_endpoint_; + std::size_t addrlen_; +}; + +template +class reactive_socket_accept_op : + public reactive_socket_accept_op_base +{ +public: + ASIO_DEFINE_HANDLER_PTR(reactive_socket_accept_op); + + reactive_socket_accept_op(const asio::error_code& success_ec, + socket_type socket, socket_ops::state_type state, Socket& peer, + const Protocol& protocol, typename Protocol::endpoint* peer_endpoint, + Handler& handler, const IoExecutor& io_ex) + : reactive_socket_accept_op_base( + success_ec, socket, state, peer, protocol, peer_endpoint, + &reactive_socket_accept_op::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the handler object. + reactive_socket_accept_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + // On success, assign new connection to peer socket object. + if (owner) + o->do_assign(); + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder1 + handler(o->handler_, o->ec_); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + handler_work work_; +}; + +#if defined(ASIO_HAS_MOVE) + +template +class reactive_socket_move_accept_op : + private Protocol::socket::template rebind_executor::other, + public reactive_socket_accept_op_base< + typename Protocol::socket::template rebind_executor::other, + Protocol> +{ +public: + ASIO_DEFINE_HANDLER_PTR(reactive_socket_move_accept_op); + + reactive_socket_move_accept_op(const asio::error_code& success_ec, + const PeerIoExecutor& peer_io_ex, socket_type socket, + socket_ops::state_type state, const Protocol& protocol, + typename Protocol::endpoint* peer_endpoint, Handler& handler, + const IoExecutor& io_ex) + : peer_socket_type(peer_io_ex), + reactive_socket_accept_op_base( + success_ec, socket, state, *this, protocol, peer_endpoint, + &reactive_socket_move_accept_op::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the handler object. + reactive_socket_move_accept_op* o( + static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + // On success, assign new connection to peer socket object. + if (owner) + o->do_assign(); + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::move_binder2 + handler(0, ASIO_MOVE_CAST(Handler)(o->handler_), o->ec_, + ASIO_MOVE_CAST(peer_socket_type)(*o)); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, "...")); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + typedef typename Protocol::socket::template + rebind_executor::other peer_socket_type; + + Handler handler_; + handler_work work_; +}; + +#endif // defined(ASIO_HAS_MOVE) + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_REACTIVE_SOCKET_ACCEPT_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_connect_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_connect_op.hpp new file mode 100644 index 000000000..14f01100d --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_connect_op.hpp @@ -0,0 +1,123 @@ +// +// detail/reactive_socket_connect_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REACTIVE_SOCKET_CONNECT_OP_HPP +#define ASIO_DETAIL_REACTIVE_SOCKET_CONNECT_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/socket_ops.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class reactive_socket_connect_op_base : public reactor_op +{ +public: + reactive_socket_connect_op_base(const asio::error_code& success_ec, + socket_type socket, func_type complete_func) + : reactor_op(success_ec, + &reactive_socket_connect_op_base::do_perform, complete_func), + socket_(socket) + { + } + + static status do_perform(reactor_op* base) + { + reactive_socket_connect_op_base* o( + static_cast(base)); + + status result = socket_ops::non_blocking_connect( + o->socket_, o->ec_) ? done : not_done; + + ASIO_HANDLER_REACTOR_OPERATION((*o, "non_blocking_connect", o->ec_)); + + return result; + } + +private: + socket_type socket_; +}; + +template +class reactive_socket_connect_op : public reactive_socket_connect_op_base +{ +public: + ASIO_DEFINE_HANDLER_PTR(reactive_socket_connect_op); + + reactive_socket_connect_op(const asio::error_code& success_ec, + socket_type socket, Handler& handler, const IoExecutor& io_ex) + : reactive_socket_connect_op_base(success_ec, socket, + &reactive_socket_connect_op::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the handler object. + reactive_socket_connect_op* o + (static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder1 + handler(o->handler_, o->ec_); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_REACTIVE_SOCKET_CONNECT_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_recv_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_recv_op.hpp new file mode 100644 index 000000000..b3af2c418 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_recv_op.hpp @@ -0,0 +1,159 @@ +// +// detail/reactive_socket_recv_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REACTIVE_SOCKET_RECV_OP_HPP +#define ASIO_DETAIL_REACTIVE_SOCKET_RECV_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/socket_ops.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class reactive_socket_recv_op_base : public reactor_op +{ +public: + reactive_socket_recv_op_base(const asio::error_code& success_ec, + socket_type socket, socket_ops::state_type state, + const MutableBufferSequence& buffers, + socket_base::message_flags flags, func_type complete_func) + : reactor_op(success_ec, + &reactive_socket_recv_op_base::do_perform, complete_func), + socket_(socket), + state_(state), + buffers_(buffers), + flags_(flags) + { + } + + static status do_perform(reactor_op* base) + { + reactive_socket_recv_op_base* o( + static_cast(base)); + + typedef buffer_sequence_adapter bufs_type; + + status result; + if (bufs_type::is_single_buffer) + { + result = socket_ops::non_blocking_recv1(o->socket_, + bufs_type::first(o->buffers_).data(), + bufs_type::first(o->buffers_).size(), o->flags_, + (o->state_ & socket_ops::stream_oriented) != 0, + o->ec_, o->bytes_transferred_) ? done : not_done; + } + else + { + bufs_type bufs(o->buffers_); + result = socket_ops::non_blocking_recv(o->socket_, + bufs.buffers(), bufs.count(), o->flags_, + (o->state_ & socket_ops::stream_oriented) != 0, + o->ec_, o->bytes_transferred_) ? done : not_done; + } + + if (result == done) + if ((o->state_ & socket_ops::stream_oriented) != 0) + if (o->bytes_transferred_ == 0) + result = done_and_exhausted; + + ASIO_HANDLER_REACTOR_OPERATION((*o, "non_blocking_recv", + o->ec_, o->bytes_transferred_)); + + return result; + } + +private: + socket_type socket_; + socket_ops::state_type state_; + MutableBufferSequence buffers_; + socket_base::message_flags flags_; +}; + +template +class reactive_socket_recv_op : + public reactive_socket_recv_op_base +{ +public: + ASIO_DEFINE_HANDLER_PTR(reactive_socket_recv_op); + + reactive_socket_recv_op(const asio::error_code& success_ec, + socket_type socket, socket_ops::state_type state, + const MutableBufferSequence& buffers, socket_base::message_flags flags, + Handler& handler, const IoExecutor& io_ex) + : reactive_socket_recv_op_base(success_ec, socket, + state, buffers, flags, &reactive_socket_recv_op::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the handler object. + reactive_socket_recv_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, o->ec_, o->bytes_transferred_); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_REACTIVE_SOCKET_RECV_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_recvfrom_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_recvfrom_op.hpp new file mode 100644 index 000000000..f45bb2cb8 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_recvfrom_op.hpp @@ -0,0 +1,164 @@ +// +// detail/reactive_socket_recvfrom_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REACTIVE_SOCKET_RECVFROM_OP_HPP +#define ASIO_DETAIL_REACTIVE_SOCKET_RECVFROM_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/socket_ops.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class reactive_socket_recvfrom_op_base : public reactor_op +{ +public: + reactive_socket_recvfrom_op_base(const asio::error_code& success_ec, + socket_type socket, int protocol_type, + const MutableBufferSequence& buffers, Endpoint& endpoint, + socket_base::message_flags flags, func_type complete_func) + : reactor_op(success_ec, + &reactive_socket_recvfrom_op_base::do_perform, complete_func), + socket_(socket), + protocol_type_(protocol_type), + buffers_(buffers), + sender_endpoint_(endpoint), + flags_(flags) + { + } + + static status do_perform(reactor_op* base) + { + reactive_socket_recvfrom_op_base* o( + static_cast(base)); + + typedef buffer_sequence_adapter bufs_type; + + std::size_t addr_len = o->sender_endpoint_.capacity(); + status result; + if (bufs_type::is_single_buffer) + { + result = socket_ops::non_blocking_recvfrom1( + o->socket_, bufs_type::first(o->buffers_).data(), + bufs_type::first(o->buffers_).size(), o->flags_, + o->sender_endpoint_.data(), &addr_len, + o->ec_, o->bytes_transferred_) ? done : not_done; + } + else + { + bufs_type bufs(o->buffers_); + result = socket_ops::non_blocking_recvfrom(o->socket_, + bufs.buffers(), bufs.count(), o->flags_, + o->sender_endpoint_.data(), &addr_len, + o->ec_, o->bytes_transferred_) ? done : not_done; + } + + if (result && !o->ec_) + o->sender_endpoint_.resize(addr_len); + + ASIO_HANDLER_REACTOR_OPERATION((*o, "non_blocking_recvfrom", + o->ec_, o->bytes_transferred_)); + + return result; + } + +private: + socket_type socket_; + int protocol_type_; + MutableBufferSequence buffers_; + Endpoint& sender_endpoint_; + socket_base::message_flags flags_; +}; + +template +class reactive_socket_recvfrom_op : + public reactive_socket_recvfrom_op_base +{ +public: + ASIO_DEFINE_HANDLER_PTR(reactive_socket_recvfrom_op); + + reactive_socket_recvfrom_op(const asio::error_code& success_ec, + socket_type socket, int protocol_type, + const MutableBufferSequence& buffers, Endpoint& endpoint, + socket_base::message_flags flags, Handler& handler, + const IoExecutor& io_ex) + : reactive_socket_recvfrom_op_base( + success_ec, socket, protocol_type, buffers, endpoint, flags, + &reactive_socket_recvfrom_op::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the handler object. + reactive_socket_recvfrom_op* o( + static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, o->ec_, o->bytes_transferred_); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_REACTIVE_SOCKET_RECVFROM_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_recvmsg_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_recvmsg_op.hpp new file mode 100644 index 000000000..ca49b6b18 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_recvmsg_op.hpp @@ -0,0 +1,145 @@ +// +// detail/reactive_socket_recvmsg_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REACTIVE_SOCKET_RECVMSG_OP_HPP +#define ASIO_DETAIL_REACTIVE_SOCKET_RECVMSG_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/socket_base.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class reactive_socket_recvmsg_op_base : public reactor_op +{ +public: + reactive_socket_recvmsg_op_base(const asio::error_code& success_ec, + socket_type socket, const MutableBufferSequence& buffers, + socket_base::message_flags in_flags, + socket_base::message_flags& out_flags, func_type complete_func) + : reactor_op(success_ec, + &reactive_socket_recvmsg_op_base::do_perform, complete_func), + socket_(socket), + buffers_(buffers), + in_flags_(in_flags), + out_flags_(out_flags) + { + } + + static status do_perform(reactor_op* base) + { + reactive_socket_recvmsg_op_base* o( + static_cast(base)); + + buffer_sequence_adapter bufs(o->buffers_); + + status result = socket_ops::non_blocking_recvmsg(o->socket_, + bufs.buffers(), bufs.count(), + o->in_flags_, o->out_flags_, + o->ec_, o->bytes_transferred_) ? done : not_done; + + ASIO_HANDLER_REACTOR_OPERATION((*o, "non_blocking_recvmsg", + o->ec_, o->bytes_transferred_)); + + return result; + } + +private: + socket_type socket_; + MutableBufferSequence buffers_; + socket_base::message_flags in_flags_; + socket_base::message_flags& out_flags_; +}; + +template +class reactive_socket_recvmsg_op : + public reactive_socket_recvmsg_op_base +{ +public: + ASIO_DEFINE_HANDLER_PTR(reactive_socket_recvmsg_op); + + reactive_socket_recvmsg_op(const asio::error_code& success_ec, + socket_type socket, const MutableBufferSequence& buffers, + socket_base::message_flags in_flags, + socket_base::message_flags& out_flags, Handler& handler, + const IoExecutor& io_ex) + : reactive_socket_recvmsg_op_base( + success_ec, socket, buffers, in_flags, out_flags, + &reactive_socket_recvmsg_op::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the handler object. + reactive_socket_recvmsg_op* o( + static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, o->ec_, o->bytes_transferred_); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_REACTIVE_SOCKET_RECVMSG_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_send_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_send_op.hpp new file mode 100644 index 000000000..4a611c4e0 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_send_op.hpp @@ -0,0 +1,162 @@ +// +// detail/reactive_socket_send_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REACTIVE_SOCKET_SEND_OP_HPP +#define ASIO_DETAIL_REACTIVE_SOCKET_SEND_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/socket_ops.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class reactive_socket_send_op_base : public reactor_op +{ +public: + reactive_socket_send_op_base(const asio::error_code& success_ec, + socket_type socket, socket_ops::state_type state, + const ConstBufferSequence& buffers, + socket_base::message_flags flags, func_type complete_func) + : reactor_op(success_ec, + &reactive_socket_send_op_base::do_perform, complete_func), + socket_(socket), + state_(state), + buffers_(buffers), + flags_(flags) + { + } + + static status do_perform(reactor_op* base) + { + reactive_socket_send_op_base* o( + static_cast(base)); + + typedef buffer_sequence_adapter bufs_type; + + status result; + if (bufs_type::is_single_buffer) + { + result = socket_ops::non_blocking_send1(o->socket_, + bufs_type::first(o->buffers_).data(), + bufs_type::first(o->buffers_).size(), o->flags_, + o->ec_, o->bytes_transferred_) ? done : not_done; + + if (result == done) + if ((o->state_ & socket_ops::stream_oriented) != 0) + if (o->bytes_transferred_ < bufs_type::first(o->buffers_).size()) + result = done_and_exhausted; + } + else + { + bufs_type bufs(o->buffers_); + result = socket_ops::non_blocking_send(o->socket_, + bufs.buffers(), bufs.count(), o->flags_, + o->ec_, o->bytes_transferred_) ? done : not_done; + + if (result == done) + if ((o->state_ & socket_ops::stream_oriented) != 0) + if (o->bytes_transferred_ < bufs.total_size()) + result = done_and_exhausted; + } + + ASIO_HANDLER_REACTOR_OPERATION((*o, "non_blocking_send", + o->ec_, o->bytes_transferred_)); + + return result; + } + +private: + socket_type socket_; + socket_ops::state_type state_; + ConstBufferSequence buffers_; + socket_base::message_flags flags_; +}; + +template +class reactive_socket_send_op : + public reactive_socket_send_op_base +{ +public: + ASIO_DEFINE_HANDLER_PTR(reactive_socket_send_op); + + reactive_socket_send_op(const asio::error_code& success_ec, + socket_type socket, socket_ops::state_type state, + const ConstBufferSequence& buffers, socket_base::message_flags flags, + Handler& handler, const IoExecutor& io_ex) + : reactive_socket_send_op_base(success_ec, socket, + state, buffers, flags, &reactive_socket_send_op::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the handler object. + reactive_socket_send_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, o->ec_, o->bytes_transferred_); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_REACTIVE_SOCKET_SEND_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_sendto_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_sendto_op.hpp new file mode 100644 index 000000000..622b92d26 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_sendto_op.hpp @@ -0,0 +1,156 @@ +// +// detail/reactive_socket_sendto_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REACTIVE_SOCKET_SENDTO_OP_HPP +#define ASIO_DETAIL_REACTIVE_SOCKET_SENDTO_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/socket_ops.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class reactive_socket_sendto_op_base : public reactor_op +{ +public: + reactive_socket_sendto_op_base(const asio::error_code& success_ec, + socket_type socket, const ConstBufferSequence& buffers, + const Endpoint& endpoint, socket_base::message_flags flags, + func_type complete_func) + : reactor_op(success_ec, + &reactive_socket_sendto_op_base::do_perform, complete_func), + socket_(socket), + buffers_(buffers), + destination_(endpoint), + flags_(flags) + { + } + + static status do_perform(reactor_op* base) + { + reactive_socket_sendto_op_base* o( + static_cast(base)); + + typedef buffer_sequence_adapter bufs_type; + + status result; + if (bufs_type::is_single_buffer) + { + result = socket_ops::non_blocking_sendto1(o->socket_, + bufs_type::first(o->buffers_).data(), + bufs_type::first(o->buffers_).size(), o->flags_, + o->destination_.data(), o->destination_.size(), + o->ec_, o->bytes_transferred_) ? done : not_done; + } + else + { + bufs_type bufs(o->buffers_); + result = socket_ops::non_blocking_sendto(o->socket_, + bufs.buffers(), bufs.count(), o->flags_, + o->destination_.data(), o->destination_.size(), + o->ec_, o->bytes_transferred_) ? done : not_done; + } + + ASIO_HANDLER_REACTOR_OPERATION((*o, "non_blocking_sendto", + o->ec_, o->bytes_transferred_)); + + return result; + } + +private: + socket_type socket_; + ConstBufferSequence buffers_; + Endpoint destination_; + socket_base::message_flags flags_; +}; + +template +class reactive_socket_sendto_op : + public reactive_socket_sendto_op_base +{ +public: + ASIO_DEFINE_HANDLER_PTR(reactive_socket_sendto_op); + + reactive_socket_sendto_op(const asio::error_code& success_ec, + socket_type socket, const ConstBufferSequence& buffers, + const Endpoint& endpoint, socket_base::message_flags flags, + Handler& handler, const IoExecutor& io_ex) + : reactive_socket_sendto_op_base( + success_ec, socket, buffers, endpoint, flags, + &reactive_socket_sendto_op::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the handler object. + reactive_socket_sendto_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, o->ec_, o->bytes_transferred_); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_REACTIVE_SOCKET_SENDTO_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_service.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_service.hpp new file mode 100644 index 000000000..bbb2b8437 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_service.hpp @@ -0,0 +1,528 @@ +// +// detail/reactive_socket_service.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REACTIVE_SOCKET_SERVICE_HPP +#define ASIO_DETAIL_REACTIVE_SOCKET_SERVICE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_IOCP) + +#include "asio/buffer.hpp" +#include "asio/error.hpp" +#include "asio/execution_context.hpp" +#include "asio/socket_base.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/reactive_null_buffers_op.hpp" +#include "asio/detail/reactive_socket_accept_op.hpp" +#include "asio/detail/reactive_socket_connect_op.hpp" +#include "asio/detail/reactive_socket_recvfrom_op.hpp" +#include "asio/detail/reactive_socket_sendto_op.hpp" +#include "asio/detail/reactive_socket_service_base.hpp" +#include "asio/detail/reactor.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/socket_holder.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/detail/socket_types.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class reactive_socket_service : + public execution_context_service_base >, + public reactive_socket_service_base +{ +public: + // The protocol type. + typedef Protocol protocol_type; + + // The endpoint type. + typedef typename Protocol::endpoint endpoint_type; + + // The native type of a socket. + typedef socket_type native_handle_type; + + // The implementation type of the socket. + struct implementation_type : + reactive_socket_service_base::base_implementation_type + { + // Default constructor. + implementation_type() + : protocol_(endpoint_type().protocol()) + { + } + + // The protocol associated with the socket. + protocol_type protocol_; + }; + + // Constructor. + reactive_socket_service(execution_context& context) + : execution_context_service_base< + reactive_socket_service >(context), + reactive_socket_service_base(context) + { + } + + // Destroy all user-defined handler objects owned by the service. + void shutdown() + { + this->base_shutdown(); + } + + // Move-construct a new socket implementation. + void move_construct(implementation_type& impl, + implementation_type& other_impl) ASIO_NOEXCEPT + { + this->base_move_construct(impl, other_impl); + + impl.protocol_ = other_impl.protocol_; + other_impl.protocol_ = endpoint_type().protocol(); + } + + // Move-assign from another socket implementation. + void move_assign(implementation_type& impl, + reactive_socket_service_base& other_service, + implementation_type& other_impl) + { + this->base_move_assign(impl, other_service, other_impl); + + impl.protocol_ = other_impl.protocol_; + other_impl.protocol_ = endpoint_type().protocol(); + } + + // Move-construct a new socket implementation from another protocol type. + template + void converting_move_construct(implementation_type& impl, + reactive_socket_service&, + typename reactive_socket_service< + Protocol1>::implementation_type& other_impl) + { + this->base_move_construct(impl, other_impl); + + impl.protocol_ = protocol_type(other_impl.protocol_); + other_impl.protocol_ = typename Protocol1::endpoint().protocol(); + } + + // Open a new socket implementation. + asio::error_code open(implementation_type& impl, + const protocol_type& protocol, asio::error_code& ec) + { + if (!do_open(impl, protocol.family(), + protocol.type(), protocol.protocol(), ec)) + impl.protocol_ = protocol; + return ec; + } + + // Assign a native socket to a socket implementation. + asio::error_code assign(implementation_type& impl, + const protocol_type& protocol, const native_handle_type& native_socket, + asio::error_code& ec) + { + if (!do_assign(impl, protocol.type(), native_socket, ec)) + impl.protocol_ = protocol; + return ec; + } + + // Get the native socket representation. + native_handle_type native_handle(implementation_type& impl) + { + return impl.socket_; + } + + // Bind the socket to the specified local endpoint. + asio::error_code bind(implementation_type& impl, + const endpoint_type& endpoint, asio::error_code& ec) + { + socket_ops::bind(impl.socket_, endpoint.data(), endpoint.size(), ec); + return ec; + } + + // Set a socket option. + template + asio::error_code set_option(implementation_type& impl, + const Option& option, asio::error_code& ec) + { + socket_ops::setsockopt(impl.socket_, impl.state_, + option.level(impl.protocol_), option.name(impl.protocol_), + option.data(impl.protocol_), option.size(impl.protocol_), ec); + return ec; + } + + // Set a socket option. + template + asio::error_code get_option(const implementation_type& impl, + Option& option, asio::error_code& ec) const + { + std::size_t size = option.size(impl.protocol_); + socket_ops::getsockopt(impl.socket_, impl.state_, + option.level(impl.protocol_), option.name(impl.protocol_), + option.data(impl.protocol_), &size, ec); + if (!ec) + option.resize(impl.protocol_, size); + return ec; + } + + // Get the local endpoint. + endpoint_type local_endpoint(const implementation_type& impl, + asio::error_code& ec) const + { + endpoint_type endpoint; + std::size_t addr_len = endpoint.capacity(); + if (socket_ops::getsockname(impl.socket_, endpoint.data(), &addr_len, ec)) + return endpoint_type(); + endpoint.resize(addr_len); + return endpoint; + } + + // Get the remote endpoint. + endpoint_type remote_endpoint(const implementation_type& impl, + asio::error_code& ec) const + { + endpoint_type endpoint; + std::size_t addr_len = endpoint.capacity(); + if (socket_ops::getpeername(impl.socket_, + endpoint.data(), &addr_len, false, ec)) + return endpoint_type(); + endpoint.resize(addr_len); + return endpoint; + } + + // Disable sends or receives on the socket. + asio::error_code shutdown(base_implementation_type& impl, + socket_base::shutdown_type what, asio::error_code& ec) + { + socket_ops::shutdown(impl.socket_, what, ec); + return ec; + } + + // Send a datagram to the specified endpoint. Returns the number of bytes + // sent. + template + size_t send_to(implementation_type& impl, const ConstBufferSequence& buffers, + const endpoint_type& destination, socket_base::message_flags flags, + asio::error_code& ec) + { + typedef buffer_sequence_adapter bufs_type; + + if (bufs_type::is_single_buffer) + { + return socket_ops::sync_sendto1(impl.socket_, impl.state_, + bufs_type::first(buffers).data(), + bufs_type::first(buffers).size(), flags, + destination.data(), destination.size(), ec); + } + else + { + bufs_type bufs(buffers); + return socket_ops::sync_sendto(impl.socket_, impl.state_, + bufs.buffers(), bufs.count(), flags, + destination.data(), destination.size(), ec); + } + } + + // Wait until data can be sent without blocking. + size_t send_to(implementation_type& impl, const null_buffers&, + const endpoint_type&, socket_base::message_flags, + asio::error_code& ec) + { + // Wait for socket to become ready. + socket_ops::poll_write(impl.socket_, impl.state_, -1, ec); + + return 0; + } + + // Start an asynchronous send. The data being sent must be valid for the + // lifetime of the asynchronous operation. + template + void async_send_to(implementation_type& impl, + const ConstBufferSequence& buffers, + const endpoint_type& destination, socket_base::message_flags flags, + Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef reactive_socket_sendto_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, impl.socket_, + buffers, destination, flags, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "socket", + &impl, impl.socket_, "async_send_to")); + + start_op(impl, reactor::write_op, p.p, is_continuation, true, false); + p.v = p.p = 0; + } + + // Start an asynchronous wait until data can be sent without blocking. + template + void async_send_to(implementation_type& impl, const null_buffers&, + const endpoint_type&, socket_base::message_flags, + Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef reactive_null_buffers_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "socket", + &impl, impl.socket_, "async_send_to(null_buffers)")); + + start_op(impl, reactor::write_op, p.p, is_continuation, false, false); + p.v = p.p = 0; + } + + // Receive a datagram with the endpoint of the sender. Returns the number of + // bytes received. + template + size_t receive_from(implementation_type& impl, + const MutableBufferSequence& buffers, + endpoint_type& sender_endpoint, socket_base::message_flags flags, + asio::error_code& ec) + { + typedef buffer_sequence_adapter bufs_type; + + std::size_t addr_len = sender_endpoint.capacity(); + std::size_t bytes_recvd; + if (bufs_type::is_single_buffer) + { + bytes_recvd = socket_ops::sync_recvfrom1(impl.socket_, + impl.state_, bufs_type::first(buffers).data(), + bufs_type::first(buffers).size(), flags, + sender_endpoint.data(), &addr_len, ec); + } + else + { + bufs_type bufs(buffers); + bytes_recvd = socket_ops::sync_recvfrom( + impl.socket_, impl.state_, bufs.buffers(), bufs.count(), + flags, sender_endpoint.data(), &addr_len, ec); + } + + if (!ec) + sender_endpoint.resize(addr_len); + + return bytes_recvd; + } + + // Wait until data can be received without blocking. + size_t receive_from(implementation_type& impl, const null_buffers&, + endpoint_type& sender_endpoint, socket_base::message_flags, + asio::error_code& ec) + { + // Wait for socket to become ready. + socket_ops::poll_read(impl.socket_, impl.state_, -1, ec); + + // Reset endpoint since it can be given no sensible value at this time. + sender_endpoint = endpoint_type(); + + return 0; + } + + // Start an asynchronous receive. The buffer for the data being received and + // the sender_endpoint object must both be valid for the lifetime of the + // asynchronous operation. + template + void async_receive_from(implementation_type& impl, + const MutableBufferSequence& buffers, endpoint_type& sender_endpoint, + socket_base::message_flags flags, Handler& handler, + const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef reactive_socket_recvfrom_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + int protocol = impl.protocol_.type(); + p.p = new (p.v) op(success_ec_, impl.socket_, protocol, + buffers, sender_endpoint, flags, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "socket", + &impl, impl.socket_, "async_receive_from")); + + start_op(impl, + (flags & socket_base::message_out_of_band) + ? reactor::except_op : reactor::read_op, + p.p, is_continuation, true, false); + p.v = p.p = 0; + } + + // Wait until data can be received without blocking. + template + void async_receive_from(implementation_type& impl, const null_buffers&, + endpoint_type& sender_endpoint, socket_base::message_flags flags, + Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef reactive_null_buffers_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "socket", + &impl, impl.socket_, "async_receive_from(null_buffers)")); + + // Reset endpoint since it can be given no sensible value at this time. + sender_endpoint = endpoint_type(); + + start_op(impl, + (flags & socket_base::message_out_of_band) + ? reactor::except_op : reactor::read_op, + p.p, is_continuation, false, false); + p.v = p.p = 0; + } + + // Accept a new connection. + template + asio::error_code accept(implementation_type& impl, + Socket& peer, endpoint_type* peer_endpoint, asio::error_code& ec) + { + // We cannot accept a socket that is already open. + if (peer.is_open()) + { + ec = asio::error::already_open; + return ec; + } + + std::size_t addr_len = peer_endpoint ? peer_endpoint->capacity() : 0; + socket_holder new_socket(socket_ops::sync_accept(impl.socket_, + impl.state_, peer_endpoint ? peer_endpoint->data() : 0, + peer_endpoint ? &addr_len : 0, ec)); + + // On success, assign new connection to peer socket object. + if (new_socket.get() != invalid_socket) + { + if (peer_endpoint) + peer_endpoint->resize(addr_len); + peer.assign(impl.protocol_, new_socket.get(), ec); + if (!ec) + new_socket.release(); + } + + return ec; + } + + // Start an asynchronous accept. The peer and peer_endpoint objects must be + // valid until the accept's handler is invoked. + template + void async_accept(implementation_type& impl, Socket& peer, + endpoint_type* peer_endpoint, Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef reactive_socket_accept_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, impl.socket_, impl.state_, + peer, impl.protocol_, peer_endpoint, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "socket", + &impl, impl.socket_, "async_accept")); + + start_accept_op(impl, p.p, is_continuation, peer.is_open()); + p.v = p.p = 0; + } + +#if defined(ASIO_HAS_MOVE) + // Start an asynchronous accept. The peer_endpoint object must be valid until + // the accept's handler is invoked. + template + void async_move_accept(implementation_type& impl, + const PeerIoExecutor& peer_io_ex, endpoint_type* peer_endpoint, + Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef reactive_socket_move_accept_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, peer_io_ex, impl.socket_, + impl.state_, impl.protocol_, peer_endpoint, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "socket", + &impl, impl.socket_, "async_accept")); + + start_accept_op(impl, p.p, is_continuation, false); + p.v = p.p = 0; + } +#endif // defined(ASIO_HAS_MOVE) + + // Connect the socket to the specified endpoint. + asio::error_code connect(implementation_type& impl, + const endpoint_type& peer_endpoint, asio::error_code& ec) + { + socket_ops::sync_connect(impl.socket_, + peer_endpoint.data(), peer_endpoint.size(), ec); + return ec; + } + + // Start an asynchronous connect. + template + void async_connect(implementation_type& impl, + const endpoint_type& peer_endpoint, + Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef reactive_socket_connect_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, impl.socket_, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "socket", + &impl, impl.socket_, "async_connect")); + + start_connect_op(impl, p.p, is_continuation, + peer_endpoint.data(), peer_endpoint.size()); + p.v = p.p = 0; + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_REACTIVE_SOCKET_SERVICE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_service_base.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_service_base.hpp new file mode 100644 index 000000000..d94b2cc43 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_socket_service_base.hpp @@ -0,0 +1,541 @@ +// +// detail/reactive_socket_service_base.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REACTIVE_SOCKET_SERVICE_BASE_HPP +#define ASIO_DETAIL_REACTIVE_SOCKET_SERVICE_BASE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_IOCP) \ + && !defined(ASIO_WINDOWS_RUNTIME) + +#include "asio/buffer.hpp" +#include "asio/error.hpp" +#include "asio/execution_context.hpp" +#include "asio/socket_base.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/reactive_null_buffers_op.hpp" +#include "asio/detail/reactive_socket_recv_op.hpp" +#include "asio/detail/reactive_socket_recvmsg_op.hpp" +#include "asio/detail/reactive_socket_send_op.hpp" +#include "asio/detail/reactive_wait_op.hpp" +#include "asio/detail/reactor.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/socket_holder.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/detail/socket_types.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class reactive_socket_service_base +{ +public: + // The native type of a socket. + typedef socket_type native_handle_type; + + // The implementation type of the socket. + struct base_implementation_type + { + // The native socket representation. + socket_type socket_; + + // The current state of the socket. + socket_ops::state_type state_; + + // Per-descriptor data used by the reactor. + reactor::per_descriptor_data reactor_data_; + }; + + // Constructor. + ASIO_DECL reactive_socket_service_base(execution_context& context); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void base_shutdown(); + + // Construct a new socket implementation. + ASIO_DECL void construct(base_implementation_type& impl); + + // Move-construct a new socket implementation. + ASIO_DECL void base_move_construct(base_implementation_type& impl, + base_implementation_type& other_impl) ASIO_NOEXCEPT; + + // Move-assign from another socket implementation. + ASIO_DECL void base_move_assign(base_implementation_type& impl, + reactive_socket_service_base& other_service, + base_implementation_type& other_impl); + + // Destroy a socket implementation. + ASIO_DECL void destroy(base_implementation_type& impl); + + // Determine whether the socket is open. + bool is_open(const base_implementation_type& impl) const + { + return impl.socket_ != invalid_socket; + } + + // Destroy a socket implementation. + ASIO_DECL asio::error_code close( + base_implementation_type& impl, asio::error_code& ec); + + // Release ownership of the socket. + ASIO_DECL socket_type release( + base_implementation_type& impl, asio::error_code& ec); + + // Get the native socket representation. + native_handle_type native_handle(base_implementation_type& impl) + { + return impl.socket_; + } + + // Cancel all operations associated with the socket. + ASIO_DECL asio::error_code cancel( + base_implementation_type& impl, asio::error_code& ec); + + // Determine whether the socket is at the out-of-band data mark. + bool at_mark(const base_implementation_type& impl, + asio::error_code& ec) const + { + return socket_ops::sockatmark(impl.socket_, ec); + } + + // Determine the number of bytes available for reading. + std::size_t available(const base_implementation_type& impl, + asio::error_code& ec) const + { + return socket_ops::available(impl.socket_, ec); + } + + // Place the socket into the state where it will listen for new connections. + asio::error_code listen(base_implementation_type& impl, + int backlog, asio::error_code& ec) + { + socket_ops::listen(impl.socket_, backlog, ec); + return ec; + } + + // Perform an IO control command on the socket. + template + asio::error_code io_control(base_implementation_type& impl, + IO_Control_Command& command, asio::error_code& ec) + { + socket_ops::ioctl(impl.socket_, impl.state_, command.name(), + static_cast(command.data()), ec); + return ec; + } + + // Gets the non-blocking mode of the socket. + bool non_blocking(const base_implementation_type& impl) const + { + return (impl.state_ & socket_ops::user_set_non_blocking) != 0; + } + + // Sets the non-blocking mode of the socket. + asio::error_code non_blocking(base_implementation_type& impl, + bool mode, asio::error_code& ec) + { + socket_ops::set_user_non_blocking(impl.socket_, impl.state_, mode, ec); + return ec; + } + + // Gets the non-blocking mode of the native socket implementation. + bool native_non_blocking(const base_implementation_type& impl) const + { + return (impl.state_ & socket_ops::internal_non_blocking) != 0; + } + + // Sets the non-blocking mode of the native socket implementation. + asio::error_code native_non_blocking(base_implementation_type& impl, + bool mode, asio::error_code& ec) + { + socket_ops::set_internal_non_blocking(impl.socket_, impl.state_, mode, ec); + return ec; + } + + // Wait for the socket to become ready to read, ready to write, or to have + // pending error conditions. + asio::error_code wait(base_implementation_type& impl, + socket_base::wait_type w, asio::error_code& ec) + { + switch (w) + { + case socket_base::wait_read: + socket_ops::poll_read(impl.socket_, impl.state_, -1, ec); + break; + case socket_base::wait_write: + socket_ops::poll_write(impl.socket_, impl.state_, -1, ec); + break; + case socket_base::wait_error: + socket_ops::poll_error(impl.socket_, impl.state_, -1, ec); + break; + default: + ec = asio::error::invalid_argument; + break; + } + + return ec; + } + + // Asynchronously wait for the socket to become ready to read, ready to + // write, or to have pending error conditions. + template + void async_wait(base_implementation_type& impl, + socket_base::wait_type w, Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef reactive_wait_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "socket", + &impl, impl.socket_, "async_wait")); + + int op_type; + switch (w) + { + case socket_base::wait_read: + op_type = reactor::read_op; + break; + case socket_base::wait_write: + op_type = reactor::write_op; + break; + case socket_base::wait_error: + op_type = reactor::except_op; + break; + default: + p.p->ec_ = asio::error::invalid_argument; + reactor_.post_immediate_completion(p.p, is_continuation); + p.v = p.p = 0; + return; + } + + start_op(impl, op_type, p.p, is_continuation, false, false); + p.v = p.p = 0; + } + + // Send the given data to the peer. + template + size_t send(base_implementation_type& impl, + const ConstBufferSequence& buffers, + socket_base::message_flags flags, asio::error_code& ec) + { + typedef buffer_sequence_adapter bufs_type; + + if (bufs_type::is_single_buffer) + { + return socket_ops::sync_send1(impl.socket_, + impl.state_, bufs_type::first(buffers).data(), + bufs_type::first(buffers).size(), flags, ec); + } + else + { + bufs_type bufs(buffers); + return socket_ops::sync_send(impl.socket_, impl.state_, + bufs.buffers(), bufs.count(), flags, bufs.all_empty(), ec); + } + } + + // Wait until data can be sent without blocking. + size_t send(base_implementation_type& impl, const null_buffers&, + socket_base::message_flags, asio::error_code& ec) + { + // Wait for socket to become ready. + socket_ops::poll_write(impl.socket_, impl.state_, -1, ec); + + return 0; + } + + // Start an asynchronous send. The data being sent must be valid for the + // lifetime of the asynchronous operation. + template + void async_send(base_implementation_type& impl, + const ConstBufferSequence& buffers, socket_base::message_flags flags, + Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef reactive_socket_send_op< + ConstBufferSequence, Handler, IoExecutor> op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, impl.socket_, + impl.state_, buffers, flags, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "socket", + &impl, impl.socket_, "async_send")); + + start_op(impl, reactor::write_op, p.p, is_continuation, true, + ((impl.state_ & socket_ops::stream_oriented) + && buffer_sequence_adapter::all_empty(buffers))); + p.v = p.p = 0; + } + + // Start an asynchronous wait until data can be sent without blocking. + template + void async_send(base_implementation_type& impl, const null_buffers&, + socket_base::message_flags, Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef reactive_null_buffers_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "socket", + &impl, impl.socket_, "async_send(null_buffers)")); + + start_op(impl, reactor::write_op, p.p, is_continuation, false, false); + p.v = p.p = 0; + } + + // Receive some data from the peer. Returns the number of bytes received. + template + size_t receive(base_implementation_type& impl, + const MutableBufferSequence& buffers, + socket_base::message_flags flags, asio::error_code& ec) + { + typedef buffer_sequence_adapter bufs_type; + + if (bufs_type::is_single_buffer) + { + return socket_ops::sync_recv1(impl.socket_, + impl.state_, bufs_type::first(buffers).data(), + bufs_type::first(buffers).size(), flags, ec); + } + else + { + bufs_type bufs(buffers); + return socket_ops::sync_recv(impl.socket_, impl.state_, + bufs.buffers(), bufs.count(), flags, bufs.all_empty(), ec); + } + } + + // Wait until data can be received without blocking. + size_t receive(base_implementation_type& impl, const null_buffers&, + socket_base::message_flags, asio::error_code& ec) + { + // Wait for socket to become ready. + socket_ops::poll_read(impl.socket_, impl.state_, -1, ec); + + return 0; + } + + // Start an asynchronous receive. The buffer for the data being received + // must be valid for the lifetime of the asynchronous operation. + template + void async_receive(base_implementation_type& impl, + const MutableBufferSequence& buffers, socket_base::message_flags flags, + Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef reactive_socket_recv_op< + MutableBufferSequence, Handler, IoExecutor> op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, impl.socket_, + impl.state_, buffers, flags, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "socket", + &impl, impl.socket_, "async_receive")); + + start_op(impl, + (flags & socket_base::message_out_of_band) + ? reactor::except_op : reactor::read_op, + p.p, is_continuation, + (flags & socket_base::message_out_of_band) == 0, + ((impl.state_ & socket_ops::stream_oriented) + && buffer_sequence_adapter::all_empty(buffers))); + p.v = p.p = 0; + } + + // Wait until data can be received without blocking. + template + void async_receive(base_implementation_type& impl, + const null_buffers&, socket_base::message_flags flags, + Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef reactive_null_buffers_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "socket", + &impl, impl.socket_, "async_receive(null_buffers)")); + + start_op(impl, + (flags & socket_base::message_out_of_band) + ? reactor::except_op : reactor::read_op, + p.p, is_continuation, false, false); + p.v = p.p = 0; + } + + // Receive some data with associated flags. Returns the number of bytes + // received. + template + size_t receive_with_flags(base_implementation_type& impl, + const MutableBufferSequence& buffers, + socket_base::message_flags in_flags, + socket_base::message_flags& out_flags, asio::error_code& ec) + { + buffer_sequence_adapter bufs(buffers); + + return socket_ops::sync_recvmsg(impl.socket_, impl.state_, + bufs.buffers(), bufs.count(), in_flags, out_flags, ec); + } + + // Wait until data can be received without blocking. + size_t receive_with_flags(base_implementation_type& impl, + const null_buffers&, socket_base::message_flags, + socket_base::message_flags& out_flags, asio::error_code& ec) + { + // Wait for socket to become ready. + socket_ops::poll_read(impl.socket_, impl.state_, -1, ec); + + // Clear out_flags, since we cannot give it any other sensible value when + // performing a null_buffers operation. + out_flags = 0; + + return 0; + } + + // Start an asynchronous receive. The buffer for the data being received + // must be valid for the lifetime of the asynchronous operation. + template + void async_receive_with_flags(base_implementation_type& impl, + const MutableBufferSequence& buffers, socket_base::message_flags in_flags, + socket_base::message_flags& out_flags, Handler& handler, + const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef reactive_socket_recvmsg_op< + MutableBufferSequence, Handler, IoExecutor> op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, impl.socket_, + buffers, in_flags, out_flags, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "socket", + &impl, impl.socket_, "async_receive_with_flags")); + + start_op(impl, + (in_flags & socket_base::message_out_of_band) + ? reactor::except_op : reactor::read_op, + p.p, is_continuation, + (in_flags & socket_base::message_out_of_band) == 0, false); + p.v = p.p = 0; + } + + // Wait until data can be received without blocking. + template + void async_receive_with_flags(base_implementation_type& impl, + const null_buffers&, socket_base::message_flags in_flags, + socket_base::message_flags& out_flags, Handler& handler, + const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef reactive_null_buffers_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(success_ec_, handler, io_ex); + + ASIO_HANDLER_CREATION((reactor_.context(), *p.p, "socket", + &impl, impl.socket_, "async_receive_with_flags(null_buffers)")); + + // Clear out_flags, since we cannot give it any other sensible value when + // performing a null_buffers operation. + out_flags = 0; + + start_op(impl, + (in_flags & socket_base::message_out_of_band) + ? reactor::except_op : reactor::read_op, + p.p, is_continuation, false, false); + p.v = p.p = 0; + } + +protected: + // Open a new socket implementation. + ASIO_DECL asio::error_code do_open( + base_implementation_type& impl, int af, + int type, int protocol, asio::error_code& ec); + + // Assign a native socket to a socket implementation. + ASIO_DECL asio::error_code do_assign( + base_implementation_type& impl, int type, + const native_handle_type& native_socket, asio::error_code& ec); + + // Start the asynchronous read or write operation. + ASIO_DECL void start_op(base_implementation_type& impl, int op_type, + reactor_op* op, bool is_continuation, bool is_non_blocking, bool noop); + + // Start the asynchronous accept operation. + ASIO_DECL void start_accept_op(base_implementation_type& impl, + reactor_op* op, bool is_continuation, bool peer_is_open); + + // Start the asynchronous connect operation. + ASIO_DECL void start_connect_op(base_implementation_type& impl, + reactor_op* op, bool is_continuation, + const socket_addr_type* addr, size_t addrlen); + + // The selector that performs event demultiplexing for the service. + reactor& reactor_; + + // Cached success value to avoid accessing category singleton. + const asio::error_code success_ec_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/reactive_socket_service_base.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // !defined(ASIO_HAS_IOCP) + // && !defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_REACTIVE_SOCKET_SERVICE_BASE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_wait_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_wait_op.hpp new file mode 100644 index 000000000..19f1659ea --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactive_wait_op.hpp @@ -0,0 +1,98 @@ +// +// detail/reactive_wait_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REACTIVE_WAIT_OP_HPP +#define ASIO_DETAIL_REACTIVE_WAIT_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/reactor_op.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class reactive_wait_op : public reactor_op +{ +public: + ASIO_DEFINE_HANDLER_PTR(reactive_wait_op); + + reactive_wait_op(const asio::error_code& success_ec, + Handler& handler, const IoExecutor& io_ex) + : reactor_op(success_ec, &reactive_wait_op::do_perform, + &reactive_wait_op::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static status do_perform(reactor_op*) + { + return done; + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the handler object. + reactive_wait_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder1 + handler(o->handler_, o->ec_); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_REACTIVE_WAIT_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactor.hpp new file mode 100644 index 000000000..79891341f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactor.hpp @@ -0,0 +1,32 @@ +// +// detail/reactor.hpp +// ~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REACTOR_HPP +#define ASIO_DETAIL_REACTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/reactor_fwd.hpp" + +#if defined(ASIO_HAS_EPOLL) +# include "asio/detail/epoll_reactor.hpp" +#elif defined(ASIO_HAS_KQUEUE) +# include "asio/detail/kqueue_reactor.hpp" +#elif defined(ASIO_HAS_DEV_POLL) +# include "asio/detail/dev_poll_reactor.hpp" +#elif defined(ASIO_HAS_IOCP) || defined(ASIO_WINDOWS_RUNTIME) +# include "asio/detail/null_reactor.hpp" +#else +# include "asio/detail/select_reactor.hpp" +#endif + +#endif // ASIO_DETAIL_REACTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactor_fwd.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactor_fwd.hpp new file mode 100644 index 000000000..a5c94368d --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactor_fwd.hpp @@ -0,0 +1,40 @@ +// +// detail/reactor_fwd.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REACTOR_FWD_HPP +#define ASIO_DETAIL_REACTOR_FWD_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +namespace asio { +namespace detail { + +#if defined(ASIO_HAS_IOCP) || defined(ASIO_WINDOWS_RUNTIME) +typedef class null_reactor reactor; +#elif defined(ASIO_HAS_IOCP) +typedef class select_reactor reactor; +#elif defined(ASIO_HAS_EPOLL) +typedef class epoll_reactor reactor; +#elif defined(ASIO_HAS_KQUEUE) +typedef class kqueue_reactor reactor; +#elif defined(ASIO_HAS_DEV_POLL) +typedef class dev_poll_reactor reactor; +#else +typedef class select_reactor reactor; +#endif + +} // namespace detail +} // namespace asio + +#endif // ASIO_DETAIL_REACTOR_FWD_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactor_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactor_op.hpp new file mode 100644 index 000000000..b7f88a4b4 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactor_op.hpp @@ -0,0 +1,67 @@ +// +// detail/reactor_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REACTOR_OP_HPP +#define ASIO_DETAIL_REACTOR_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/operation.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class reactor_op + : public operation +{ +public: + // The error code to be passed to the completion handler. + asio::error_code ec_; + + // The number of bytes transferred, to be passed to the completion handler. + std::size_t bytes_transferred_; + + // Status returned by perform function. May be used to decide whether it is + // worth performing more operations on the descriptor immediately. + enum status { not_done, done, done_and_exhausted }; + + // Perform the operation. Returns true if it is finished. + status perform() + { + return perform_func_(this); + } + +protected: + typedef status (*perform_func_type)(reactor_op*); + + reactor_op(const asio::error_code& success_ec, + perform_func_type perform_func, func_type complete_func) + : operation(complete_func), + ec_(success_ec), + bytes_transferred_(0), + perform_func_(perform_func) + { + } + +private: + perform_func_type perform_func_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_REACTOR_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactor_op_queue.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactor_op_queue.hpp new file mode 100644 index 000000000..96eca520c --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/reactor_op_queue.hpp @@ -0,0 +1,168 @@ +// +// detail/reactor_op_queue.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REACTOR_OP_QUEUE_HPP +#define ASIO_DETAIL_REACTOR_OP_QUEUE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/hash_map.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/op_queue.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class reactor_op_queue + : private noncopyable +{ +public: + typedef Descriptor key_type; + + struct mapped_type : op_queue + { + mapped_type() {} + mapped_type(const mapped_type&) {} + void operator=(const mapped_type&) {} + }; + + typedef typename hash_map::value_type value_type; + typedef typename hash_map::iterator iterator; + + // Constructor. + reactor_op_queue() + : operations_() + { + } + + // Obtain iterators to all registered descriptors. + iterator begin() { return operations_.begin(); } + iterator end() { return operations_.end(); } + + // Add a new operation to the queue. Returns true if this is the only + // operation for the given descriptor, in which case the reactor's event + // demultiplexing function call may need to be interrupted and restarted. + bool enqueue_operation(Descriptor descriptor, reactor_op* op) + { + std::pair entry = + operations_.insert(value_type(descriptor, mapped_type())); + entry.first->second.push(op); + return entry.second; + } + + // Cancel all operations associated with the descriptor identified by the + // supplied iterator. Any operations pending for the descriptor will be + // cancelled. Returns true if any operations were cancelled, in which case + // the reactor's event demultiplexing function may need to be interrupted and + // restarted. + bool cancel_operations(iterator i, op_queue& ops, + const asio::error_code& ec = + asio::error::operation_aborted) + { + if (i != operations_.end()) + { + while (reactor_op* op = i->second.front()) + { + op->ec_ = ec; + i->second.pop(); + ops.push(op); + } + operations_.erase(i); + return true; + } + + return false; + } + + // Cancel all operations associated with the descriptor. Any operations + // pending for the descriptor will be cancelled. Returns true if any + // operations were cancelled, in which case the reactor's event + // demultiplexing function may need to be interrupted and restarted. + bool cancel_operations(Descriptor descriptor, op_queue& ops, + const asio::error_code& ec = + asio::error::operation_aborted) + { + return this->cancel_operations(operations_.find(descriptor), ops, ec); + } + + // Whether there are no operations in the queue. + bool empty() const + { + return operations_.empty(); + } + + // Determine whether there are any operations associated with the descriptor. + bool has_operation(Descriptor descriptor) const + { + return operations_.find(descriptor) != operations_.end(); + } + + // Perform the operations corresponding to the descriptor identified by the + // supplied iterator. Returns true if there are still unfinished operations + // queued for the descriptor. + bool perform_operations(iterator i, op_queue& ops) + { + if (i != operations_.end()) + { + while (reactor_op* op = i->second.front()) + { + if (op->perform()) + { + i->second.pop(); + ops.push(op); + } + else + { + return true; + } + } + operations_.erase(i); + } + return false; + } + + // Perform the operations corresponding to the descriptor. Returns true if + // there are still unfinished operations queued for the descriptor. + bool perform_operations(Descriptor descriptor, op_queue& ops) + { + return this->perform_operations(operations_.find(descriptor), ops); + } + + // Get all operations owned by the queue. + void get_all_operations(op_queue& ops) + { + iterator i = operations_.begin(); + while (i != operations_.end()) + { + iterator op_iter = i++; + ops.push(op_iter->second); + operations_.erase(op_iter); + } + } + +private: + // The operations that are currently executing asynchronously. + hash_map operations_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_REACTOR_OP_QUEUE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/recycling_allocator.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/recycling_allocator.hpp new file mode 100644 index 000000000..6c905cdff --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/recycling_allocator.hpp @@ -0,0 +1,106 @@ +// +// detail/recycling_allocator.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_RECYCLING_ALLOCATOR_HPP +#define ASIO_DETAIL_RECYCLING_ALLOCATOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/thread_context.hpp" +#include "asio/detail/thread_info_base.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class recycling_allocator +{ +public: + typedef T value_type; + + template + struct rebind + { + typedef recycling_allocator other; + }; + + recycling_allocator() + { + } + + template + recycling_allocator(const recycling_allocator&) + { + } + + T* allocate(std::size_t n) + { + typedef thread_context::thread_call_stack call_stack; + void* p = thread_info_base::allocate(Purpose(), + call_stack::top(), sizeof(T) * n); + return static_cast(p); + } + + void deallocate(T* p, std::size_t n) + { + typedef thread_context::thread_call_stack call_stack; + thread_info_base::deallocate(Purpose(), + call_stack::top(), p, sizeof(T) * n); + } +}; + +template +class recycling_allocator +{ +public: + typedef void value_type; + + template + struct rebind + { + typedef recycling_allocator other; + }; + + recycling_allocator() + { + } + + template + recycling_allocator(const recycling_allocator&) + { + } +}; + +template +struct get_recycling_allocator +{ + typedef Allocator type; + static type get(const Allocator& a) { return a; } +}; + +template +struct get_recycling_allocator, Purpose> +{ + typedef recycling_allocator type; + static type get(const std::allocator&) { return type(); } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_RECYCLING_ALLOCATOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/regex_fwd.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/regex_fwd.hpp new file mode 100644 index 000000000..6d7b40495 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/regex_fwd.hpp @@ -0,0 +1,35 @@ +// +// detail/regex_fwd.hpp +// ~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_REGEX_FWD_HPP +#define ASIO_DETAIL_REGEX_FWD_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#if defined(ASIO_HAS_BOOST_REGEX) + +#include +#include + +namespace boost { + +template +struct sub_match; + +template +class match_results; + +} // namespace boost + +#endif // defined(ASIO_HAS_BOOST_REGEX) + +#endif // ASIO_DETAIL_REGEX_FWD_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/resolve_endpoint_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/resolve_endpoint_op.hpp new file mode 100644 index 000000000..a9fe05350 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/resolve_endpoint_op.hpp @@ -0,0 +1,140 @@ +// +// detail/resolve_endpoint_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_RESOLVER_ENDPOINT_OP_HPP +#define ASIO_DETAIL_RESOLVER_ENDPOINT_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/resolve_op.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/error.hpp" +#include "asio/ip/basic_resolver_results.hpp" + +#if defined(ASIO_HAS_IOCP) +# include "asio/detail/win_iocp_io_context.hpp" +#else // defined(ASIO_HAS_IOCP) +# include "asio/detail/scheduler.hpp" +#endif // defined(ASIO_HAS_IOCP) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class resolve_endpoint_op : public resolve_op +{ +public: + ASIO_DEFINE_HANDLER_PTR(resolve_endpoint_op); + + typedef typename Protocol::endpoint endpoint_type; + typedef asio::ip::basic_resolver_results results_type; + +#if defined(ASIO_HAS_IOCP) + typedef class win_iocp_io_context scheduler_impl; +#else + typedef class scheduler scheduler_impl; +#endif + + resolve_endpoint_op(socket_ops::weak_cancel_token_type cancel_token, + const endpoint_type& endpoint, scheduler_impl& sched, + Handler& handler, const IoExecutor& io_ex) + : resolve_op(&resolve_endpoint_op::do_complete), + cancel_token_(cancel_token), + endpoint_(endpoint), + scheduler_(sched), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the operation object. + resolve_endpoint_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + if (owner && owner != &o->scheduler_) + { + // The operation is being run on the worker io_context. Time to perform + // the resolver operation. + + // Perform the blocking endpoint resolution operation. + char host_name[NI_MAXHOST]; + char service_name[NI_MAXSERV]; + socket_ops::background_getnameinfo(o->cancel_token_, o->endpoint_.data(), + o->endpoint_.size(), host_name, NI_MAXHOST, service_name, NI_MAXSERV, + o->endpoint_.protocol().type(), o->ec_); + o->results_ = results_type::create(o->endpoint_, host_name, service_name); + + // Pass operation back to main io_context for completion. + o->scheduler_.post_deferred_completion(o); + p.v = p.p = 0; + } + else + { + // The operation has been returned to the main io_context. The completion + // handler is ready to be delivered. + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated + // before the upcall is made. Even if we're not about to make an upcall, + // a sub-object of the handler may be the true owner of the memory + // associated with the handler. Consequently, a local copy of the handler + // is required to ensure that any owning sub-object remains valid until + // after we have deallocated the memory here. + detail::binder2 + handler(o->handler_, o->ec_, o->results_); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, "...")); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + } + +private: + socket_ops::weak_cancel_token_type cancel_token_; + endpoint_type endpoint_; + scheduler_impl& scheduler_; + Handler handler_; + handler_work work_; + results_type results_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_RESOLVER_ENDPOINT_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/resolve_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/resolve_op.hpp new file mode 100644 index 000000000..a4c6409ec --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/resolve_op.hpp @@ -0,0 +1,45 @@ +// +// detail/resolve_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_RESOLVE_OP_HPP +#define ASIO_DETAIL_RESOLVE_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/error.hpp" +#include "asio/detail/operation.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class resolve_op : public operation +{ +public: + // The error code to be passed to the completion handler. + asio::error_code ec_; + +protected: + resolve_op(func_type complete_func) + : operation(complete_func) + { + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_RESOLVE_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/resolve_query_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/resolve_query_op.hpp new file mode 100644 index 000000000..e402a9e53 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/resolve_query_op.hpp @@ -0,0 +1,150 @@ +// +// detail/resolve_query_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_RESOLVE_QUERY_OP_HPP +#define ASIO_DETAIL_RESOLVE_QUERY_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/resolve_op.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/error.hpp" +#include "asio/ip/basic_resolver_query.hpp" +#include "asio/ip/basic_resolver_results.hpp" + +#if defined(ASIO_HAS_IOCP) +# include "asio/detail/win_iocp_io_context.hpp" +#else // defined(ASIO_HAS_IOCP) +# include "asio/detail/scheduler.hpp" +#endif // defined(ASIO_HAS_IOCP) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class resolve_query_op : public resolve_op +{ +public: + ASIO_DEFINE_HANDLER_PTR(resolve_query_op); + + typedef asio::ip::basic_resolver_query query_type; + typedef asio::ip::basic_resolver_results results_type; + +#if defined(ASIO_HAS_IOCP) + typedef class win_iocp_io_context scheduler_impl; +#else + typedef class scheduler scheduler_impl; +#endif + + resolve_query_op(socket_ops::weak_cancel_token_type cancel_token, + const query_type& query, scheduler_impl& sched, + Handler& handler, const IoExecutor& io_ex) + : resolve_op(&resolve_query_op::do_complete), + cancel_token_(cancel_token), + query_(query), + scheduler_(sched), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex), + addrinfo_(0) + { + } + + ~resolve_query_op() + { + if (addrinfo_) + socket_ops::freeaddrinfo(addrinfo_); + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the operation object. + resolve_query_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + if (owner && owner != &o->scheduler_) + { + // The operation is being run on the worker io_context. Time to perform + // the resolver operation. + + // Perform the blocking host resolution operation. + socket_ops::background_getaddrinfo(o->cancel_token_, + o->query_.host_name().c_str(), o->query_.service_name().c_str(), + o->query_.hints(), &o->addrinfo_, o->ec_); + + // Pass operation back to main io_context for completion. + o->scheduler_.post_deferred_completion(o); + p.v = p.p = 0; + } + else + { + // The operation has been returned to the main io_context. The completion + // handler is ready to be delivered. + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated + // before the upcall is made. Even if we're not about to make an upcall, + // a sub-object of the handler may be the true owner of the memory + // associated with the handler. Consequently, a local copy of the handler + // is required to ensure that any owning sub-object remains valid until + // after we have deallocated the memory here. + detail::binder2 + handler(o->handler_, o->ec_, results_type()); + p.h = asio::detail::addressof(handler.handler_); + if (o->addrinfo_) + { + handler.arg2_ = results_type::create(o->addrinfo_, + o->query_.host_name(), o->query_.service_name()); + } + p.reset(); + + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, "...")); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + } + +private: + socket_ops::weak_cancel_token_type cancel_token_; + query_type query_; + scheduler_impl& scheduler_; + Handler handler_; + handler_work work_; + asio::detail::addrinfo_type* addrinfo_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_RESOLVE_QUERY_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/resolver_service.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/resolver_service.hpp new file mode 100644 index 000000000..b09c568c5 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/resolver_service.hpp @@ -0,0 +1,145 @@ +// +// detail/resolver_service.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_RESOLVER_SERVICE_HPP +#define ASIO_DETAIL_RESOLVER_SERVICE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_WINDOWS_RUNTIME) + +#include "asio/ip/basic_resolver_query.hpp" +#include "asio/ip/basic_resolver_results.hpp" +#include "asio/detail/concurrency_hint.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/resolve_endpoint_op.hpp" +#include "asio/detail/resolve_query_op.hpp" +#include "asio/detail/resolver_service_base.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class resolver_service : + public execution_context_service_base >, + public resolver_service_base +{ +public: + // The implementation type of the resolver. A cancellation token is used to + // indicate to the background thread that the operation has been cancelled. + typedef socket_ops::shared_cancel_token_type implementation_type; + + // The endpoint type. + typedef typename Protocol::endpoint endpoint_type; + + // The query type. + typedef asio::ip::basic_resolver_query query_type; + + // The results type. + typedef asio::ip::basic_resolver_results results_type; + + // Constructor. + resolver_service(execution_context& context) + : execution_context_service_base >(context), + resolver_service_base(context) + { + } + + // Destroy all user-defined handler objects owned by the service. + void shutdown() + { + this->base_shutdown(); + } + + // Perform any fork-related housekeeping. + void notify_fork(execution_context::fork_event fork_ev) + { + this->base_notify_fork(fork_ev); + } + + // Resolve a query to a list of entries. + results_type resolve(implementation_type&, const query_type& query, + asio::error_code& ec) + { + asio::detail::addrinfo_type* address_info = 0; + + socket_ops::getaddrinfo(query.host_name().c_str(), + query.service_name().c_str(), query.hints(), &address_info, ec); + auto_addrinfo auto_address_info(address_info); + + return ec ? results_type() : results_type::create( + address_info, query.host_name(), query.service_name()); + } + + // Asynchronously resolve a query to a list of entries. + template + void async_resolve(implementation_type& impl, const query_type& query, + Handler& handler, const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef resolve_query_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(impl, query, scheduler_, handler, io_ex); + + ASIO_HANDLER_CREATION((scheduler_.context(), + *p.p, "resolver", &impl, 0, "async_resolve")); + + start_resolve_op(p.p); + p.v = p.p = 0; + } + + // Resolve an endpoint to a list of entries. + results_type resolve(implementation_type&, + const endpoint_type& endpoint, asio::error_code& ec) + { + char host_name[NI_MAXHOST]; + char service_name[NI_MAXSERV]; + socket_ops::sync_getnameinfo(endpoint.data(), endpoint.size(), + host_name, NI_MAXHOST, service_name, NI_MAXSERV, + endpoint.protocol().type(), ec); + + return ec ? results_type() : results_type::create( + endpoint, host_name, service_name); + } + + // Asynchronously resolve an endpoint to a list of entries. + template + void async_resolve(implementation_type& impl, const endpoint_type& endpoint, + Handler& handler, const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef resolve_endpoint_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(impl, endpoint, scheduler_, handler, io_ex); + + ASIO_HANDLER_CREATION((scheduler_.context(), + *p.p, "resolver", &impl, 0, "async_resolve")); + + start_resolve_op(p.p); + p.v = p.p = 0; + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_RESOLVER_SERVICE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/resolver_service_base.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/resolver_service_base.hpp new file mode 100644 index 000000000..51bdf13dc --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/resolver_service_base.hpp @@ -0,0 +1,143 @@ +// +// detail/resolver_service_base.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_RESOLVER_SERVICE_BASE_HPP +#define ASIO_DETAIL_RESOLVER_SERVICE_BASE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/error.hpp" +#include "asio/execution_context.hpp" +#include "asio/detail/mutex.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/resolve_op.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/detail/socket_types.hpp" +#include "asio/detail/scoped_ptr.hpp" +#include "asio/detail/thread.hpp" + +#if defined(ASIO_HAS_IOCP) +# include "asio/detail/win_iocp_io_context.hpp" +#else // defined(ASIO_HAS_IOCP) +# include "asio/detail/scheduler.hpp" +#endif // defined(ASIO_HAS_IOCP) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class resolver_service_base +{ +public: + // The implementation type of the resolver. A cancellation token is used to + // indicate to the background thread that the operation has been cancelled. + typedef socket_ops::shared_cancel_token_type implementation_type; + + // Constructor. + ASIO_DECL resolver_service_base(execution_context& context); + + // Destructor. + ASIO_DECL ~resolver_service_base(); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void base_shutdown(); + + // Perform any fork-related housekeeping. + ASIO_DECL void base_notify_fork( + execution_context::fork_event fork_ev); + + // Construct a new resolver implementation. + ASIO_DECL void construct(implementation_type& impl); + + // Destroy a resolver implementation. + ASIO_DECL void destroy(implementation_type&); + + // Move-construct a new resolver implementation. + ASIO_DECL void move_construct(implementation_type& impl, + implementation_type& other_impl); + + // Move-assign from another resolver implementation. + ASIO_DECL void move_assign(implementation_type& impl, + resolver_service_base& other_service, + implementation_type& other_impl); + + // Cancel pending asynchronous operations. + ASIO_DECL void cancel(implementation_type& impl); + +protected: + // Helper function to start an asynchronous resolve operation. + ASIO_DECL void start_resolve_op(resolve_op* op); + +#if !defined(ASIO_WINDOWS_RUNTIME) + // Helper class to perform exception-safe cleanup of addrinfo objects. + class auto_addrinfo + : private asio::detail::noncopyable + { + public: + explicit auto_addrinfo(asio::detail::addrinfo_type* ai) + : ai_(ai) + { + } + + ~auto_addrinfo() + { + if (ai_) + socket_ops::freeaddrinfo(ai_); + } + + operator asio::detail::addrinfo_type*() + { + return ai_; + } + + private: + asio::detail::addrinfo_type* ai_; + }; +#endif // !defined(ASIO_WINDOWS_RUNTIME) + + // Helper class to run the work scheduler in a thread. + class work_scheduler_runner; + + // Start the work scheduler if it's not already running. + ASIO_DECL void start_work_thread(); + + // The scheduler implementation used to post completions. +#if defined(ASIO_HAS_IOCP) + typedef class win_iocp_io_context scheduler_impl; +#else + typedef class scheduler scheduler_impl; +#endif + scheduler_impl& scheduler_; + +private: + // Mutex to protect access to internal data. + asio::detail::mutex mutex_; + + // Private scheduler used for performing asynchronous host resolution. + asio::detail::scoped_ptr work_scheduler_; + + // Thread used for running the work io_context's run loop. + asio::detail::scoped_ptr work_thread_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/resolver_service_base.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // ASIO_DETAIL_RESOLVER_SERVICE_BASE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/scheduler.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/scheduler.hpp new file mode 100644 index 000000000..f367c8f63 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/scheduler.hpp @@ -0,0 +1,232 @@ +// +// detail/scheduler.hpp +// ~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SCHEDULER_HPP +#define ASIO_DETAIL_SCHEDULER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#include "asio/error_code.hpp" +#include "asio/execution_context.hpp" +#include "asio/detail/atomic_count.hpp" +#include "asio/detail/conditionally_enabled_event.hpp" +#include "asio/detail/conditionally_enabled_mutex.hpp" +#include "asio/detail/op_queue.hpp" +#include "asio/detail/reactor_fwd.hpp" +#include "asio/detail/scheduler_operation.hpp" +#include "asio/detail/thread.hpp" +#include "asio/detail/thread_context.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +struct scheduler_thread_info; + +class scheduler + : public execution_context_service_base, + public thread_context +{ +public: + typedef scheduler_operation operation; + + // Constructor. Specifies the number of concurrent threads that are likely to + // run the scheduler. If set to 1 certain optimisation are performed. + ASIO_DECL scheduler(asio::execution_context& ctx, + int concurrency_hint = 0, bool own_thread = true); + + // Destructor. + ASIO_DECL ~scheduler(); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void shutdown(); + + // Initialise the task, if required. + ASIO_DECL void init_task(); + + // Run the event loop until interrupted or no more work. + ASIO_DECL std::size_t run(asio::error_code& ec); + + // Run until interrupted or one operation is performed. + ASIO_DECL std::size_t run_one(asio::error_code& ec); + + // Run until timeout, interrupted, or one operation is performed. + ASIO_DECL std::size_t wait_one( + long usec, asio::error_code& ec); + + // Poll for operations without blocking. + ASIO_DECL std::size_t poll(asio::error_code& ec); + + // Poll for one operation without blocking. + ASIO_DECL std::size_t poll_one(asio::error_code& ec); + + // Interrupt the event processing loop. + ASIO_DECL void stop(); + + // Determine whether the scheduler is stopped. + ASIO_DECL bool stopped() const; + + // Restart in preparation for a subsequent run invocation. + ASIO_DECL void restart(); + + // Notify that some work has started. + void work_started() + { + ++outstanding_work_; + } + + // Used to compensate for a forthcoming work_finished call. Must be called + // from within a scheduler-owned thread. + ASIO_DECL void compensating_work_started(); + + // Notify that some work has finished. + void work_finished() + { + if (--outstanding_work_ == 0) + stop(); + } + + // Return whether a handler can be dispatched immediately. + bool can_dispatch() + { + return thread_call_stack::contains(this) != 0; + } + + /// Capture the current exception so it can be rethrown from a run function. + ASIO_DECL void capture_current_exception(); + + // Request invocation of the given operation and return immediately. Assumes + // that work_started() has not yet been called for the operation. + ASIO_DECL void post_immediate_completion( + operation* op, bool is_continuation); + + // Request invocation of the given operations and return immediately. Assumes + // that work_started() has not yet been called for the operations. + ASIO_DECL void post_immediate_completions(std::size_t n, + op_queue& ops, bool is_continuation); + + // Request invocation of the given operation and return immediately. Assumes + // that work_started() was previously called for the operation. + ASIO_DECL void post_deferred_completion(operation* op); + + // Request invocation of the given operations and return immediately. Assumes + // that work_started() was previously called for each operation. + ASIO_DECL void post_deferred_completions(op_queue& ops); + + // Enqueue the given operation following a failed attempt to dispatch the + // operation for immediate invocation. + ASIO_DECL void do_dispatch(operation* op); + + // Process unfinished operations as part of a shutdownoperation. Assumes that + // work_started() was previously called for the operations. + ASIO_DECL void abandon_operations(op_queue& ops); + + // Get the concurrency hint that was used to initialise the scheduler. + int concurrency_hint() const + { + return concurrency_hint_; + } + +private: + // The mutex type used by this scheduler. + typedef conditionally_enabled_mutex mutex; + + // The event type used by this scheduler. + typedef conditionally_enabled_event event; + + // Structure containing thread-specific data. + typedef scheduler_thread_info thread_info; + + // Run at most one operation. May block. + ASIO_DECL std::size_t do_run_one(mutex::scoped_lock& lock, + thread_info& this_thread, const asio::error_code& ec); + + // Run at most one operation with a timeout. May block. + ASIO_DECL std::size_t do_wait_one(mutex::scoped_lock& lock, + thread_info& this_thread, long usec, const asio::error_code& ec); + + // Poll for at most one operation. + ASIO_DECL std::size_t do_poll_one(mutex::scoped_lock& lock, + thread_info& this_thread, const asio::error_code& ec); + + // Stop the task and all idle threads. + ASIO_DECL void stop_all_threads(mutex::scoped_lock& lock); + + // Wake a single idle thread, or the task, and always unlock the mutex. + ASIO_DECL void wake_one_thread_and_unlock( + mutex::scoped_lock& lock); + + // Helper class to run the scheduler in its own thread. + class thread_function; + friend class thread_function; + + // Helper class to perform task-related operations on block exit. + struct task_cleanup; + friend struct task_cleanup; + + // Helper class to call work-related operations on block exit. + struct work_cleanup; + friend struct work_cleanup; + + // Whether to optimise for single-threaded use cases. + const bool one_thread_; + + // Mutex to protect access to internal data. + mutable mutex mutex_; + + // Event to wake up blocked threads. + event wakeup_event_; + + // The task to be run by this service. + reactor* task_; + + // Operation object to represent the position of the task in the queue. + struct task_operation : operation + { + task_operation() : operation(0) {} + } task_operation_; + + // Whether the task has been interrupted. + bool task_interrupted_; + + // The count of unfinished work. + atomic_count outstanding_work_; + + // The queue of handlers that are ready to be delivered. + op_queue op_queue_; + + // Flag to indicate that the dispatcher has been stopped. + bool stopped_; + + // Flag to indicate that the dispatcher has been shut down. + bool shutdown_; + + // The concurrency hint used to initialise the scheduler. + const int concurrency_hint_; + + // The thread that is running the scheduler. + asio::detail::thread* thread_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/scheduler.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // ASIO_DETAIL_SCHEDULER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/scheduler_operation.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/scheduler_operation.hpp new file mode 100644 index 000000000..c87329888 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/scheduler_operation.hpp @@ -0,0 +1,78 @@ +// +// detail/scheduler_operation.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SCHEDULER_OPERATION_HPP +#define ASIO_DETAIL_SCHEDULER_OPERATION_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/error_code.hpp" +#include "asio/detail/handler_tracking.hpp" +#include "asio/detail/op_queue.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class scheduler; + +// Base class for all operations. A function pointer is used instead of virtual +// functions to avoid the associated overhead. +class scheduler_operation ASIO_INHERIT_TRACKED_HANDLER +{ +public: + typedef scheduler_operation operation_type; + + void complete(void* owner, const asio::error_code& ec, + std::size_t bytes_transferred) + { + func_(owner, this, ec, bytes_transferred); + } + + void destroy() + { + func_(0, this, asio::error_code(), 0); + } + +protected: + typedef void (*func_type)(void*, + scheduler_operation*, + const asio::error_code&, std::size_t); + + scheduler_operation(func_type func) + : next_(0), + func_(func), + task_result_(0) + { + } + + // Prevents deletion through this type. + ~scheduler_operation() + { + } + +private: + friend class op_queue_access; + scheduler_operation* next_; + func_type func_; +protected: + friend class scheduler; + unsigned int task_result_; // Passed into bytes transferred. +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_SCHEDULER_OPERATION_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/scheduler_thread_info.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/scheduler_thread_info.hpp new file mode 100644 index 000000000..d69ab9ed1 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/scheduler_thread_info.hpp @@ -0,0 +1,40 @@ +// +// detail/scheduler_thread_info.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SCHEDULER_THREAD_INFO_HPP +#define ASIO_DETAIL_SCHEDULER_THREAD_INFO_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/op_queue.hpp" +#include "asio/detail/thread_info_base.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class scheduler; +class scheduler_operation; + +struct scheduler_thread_info : public thread_info_base +{ + op_queue private_op_queue; + long private_outstanding_work; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_SCHEDULER_THREAD_INFO_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/scoped_lock.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/scoped_lock.hpp new file mode 100644 index 000000000..c0d4f9f88 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/scoped_lock.hpp @@ -0,0 +1,101 @@ +// +// detail/scoped_lock.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SCOPED_LOCK_HPP +#define ASIO_DETAIL_SCOPED_LOCK_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Helper class to lock and unlock a mutex automatically. +template +class scoped_lock + : private noncopyable +{ +public: + // Tag type used to distinguish constructors. + enum adopt_lock_t { adopt_lock }; + + // Constructor adopts a lock that is already held. + scoped_lock(Mutex& m, adopt_lock_t) + : mutex_(m), + locked_(true) + { + } + + // Constructor acquires the lock. + explicit scoped_lock(Mutex& m) + : mutex_(m) + { + mutex_.lock(); + locked_ = true; + } + + // Destructor releases the lock. + ~scoped_lock() + { + if (locked_) + mutex_.unlock(); + } + + // Explicitly acquire the lock. + void lock() + { + if (!locked_) + { + mutex_.lock(); + locked_ = true; + } + } + + // Explicitly release the lock. + void unlock() + { + if (locked_) + { + mutex_.unlock(); + locked_ = false; + } + } + + // Test whether the lock is held. + bool locked() const + { + return locked_; + } + + // Get the underlying mutex. + Mutex& mutex() + { + return mutex_; + } + +private: + // The underlying mutex. + Mutex& mutex_; + + // Whether the mutex is currently locked or unlocked. + bool locked_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_SCOPED_LOCK_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/scoped_ptr.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/scoped_ptr.hpp new file mode 100644 index 000000000..f1e81b662 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/scoped_ptr.hpp @@ -0,0 +1,87 @@ +// +// detail/scoped_ptr.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SCOPED_PTR_HPP +#define ASIO_DETAIL_SCOPED_PTR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class scoped_ptr +{ +public: + // Constructor. + explicit scoped_ptr(T* p = 0) + : p_(p) + { + } + + // Destructor. + ~scoped_ptr() + { + delete p_; + } + + // Access. + T* get() + { + return p_; + } + + // Access. + T* operator->() + { + return p_; + } + + // Dereference. + T& operator*() + { + return *p_; + } + + // Reset pointer. + void reset(T* p = 0) + { + delete p_; + p_ = p; + } + + // Release ownership of the pointer. + T* release() + { + T* tmp = p_; + p_ = 0; + return tmp; + } + +private: + // Disallow copying and assignment. + scoped_ptr(const scoped_ptr&); + scoped_ptr& operator=(const scoped_ptr&); + + T* p_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_SCOPED_PTR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/select_interrupter.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/select_interrupter.hpp new file mode 100644 index 000000000..5976cc6f1 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/select_interrupter.hpp @@ -0,0 +1,46 @@ +// +// detail/select_interrupter.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SELECT_INTERRUPTER_HPP +#define ASIO_DETAIL_SELECT_INTERRUPTER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_WINDOWS_RUNTIME) + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) || defined(__SYMBIAN32__) +# include "asio/detail/socket_select_interrupter.hpp" +#elif defined(ASIO_HAS_EVENTFD) +# include "asio/detail/eventfd_select_interrupter.hpp" +#else +# include "asio/detail/pipe_select_interrupter.hpp" +#endif + +namespace asio { +namespace detail { + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) || defined(__SYMBIAN32__) +typedef socket_select_interrupter select_interrupter; +#elif defined(ASIO_HAS_EVENTFD) +typedef eventfd_select_interrupter select_interrupter; +#else +typedef pipe_select_interrupter select_interrupter; +#endif + +} // namespace detail +} // namespace asio + +#endif // !defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_SELECT_INTERRUPTER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/select_reactor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/select_reactor.hpp new file mode 100644 index 000000000..01eb716bb --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/select_reactor.hpp @@ -0,0 +1,238 @@ +// +// detail/select_reactor.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SELECT_REACTOR_HPP +#define ASIO_DETAIL_SELECT_REACTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) \ + || (!defined(ASIO_HAS_DEV_POLL) \ + && !defined(ASIO_HAS_EPOLL) \ + && !defined(ASIO_HAS_KQUEUE) \ + && !defined(ASIO_WINDOWS_RUNTIME)) + +#include +#include "asio/detail/fd_set_adapter.hpp" +#include "asio/detail/limits.hpp" +#include "asio/detail/mutex.hpp" +#include "asio/detail/op_queue.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/reactor_op_queue.hpp" +#include "asio/detail/select_interrupter.hpp" +#include "asio/detail/socket_types.hpp" +#include "asio/detail/timer_queue_base.hpp" +#include "asio/detail/timer_queue_set.hpp" +#include "asio/detail/wait_op.hpp" +#include "asio/execution_context.hpp" + +#if defined(ASIO_HAS_IOCP) +# include "asio/detail/thread.hpp" +#endif // defined(ASIO_HAS_IOCP) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class select_reactor + : public execution_context_service_base +{ +public: +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + enum op_types { read_op = 0, write_op = 1, except_op = 2, + max_select_ops = 3, connect_op = 3, max_ops = 4 }; +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + enum op_types { read_op = 0, write_op = 1, except_op = 2, + max_select_ops = 3, connect_op = 1, max_ops = 3 }; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + + // Per-descriptor data. + struct per_descriptor_data + { + }; + + // Constructor. + ASIO_DECL select_reactor(asio::execution_context& ctx); + + // Destructor. + ASIO_DECL ~select_reactor(); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void shutdown(); + + // Recreate internal descriptors following a fork. + ASIO_DECL void notify_fork( + asio::execution_context::fork_event fork_ev); + + // Initialise the task, but only if the reactor is not in its own thread. + ASIO_DECL void init_task(); + + // Register a socket with the reactor. Returns 0 on success, system error + // code on failure. + ASIO_DECL int register_descriptor(socket_type, per_descriptor_data&); + + // Register a descriptor with an associated single operation. Returns 0 on + // success, system error code on failure. + ASIO_DECL int register_internal_descriptor( + int op_type, socket_type descriptor, + per_descriptor_data& descriptor_data, reactor_op* op); + + // Post a reactor operation for immediate completion. + void post_immediate_completion(reactor_op* op, bool is_continuation) + { + scheduler_.post_immediate_completion(op, is_continuation); + } + + // Start a new operation. The reactor operation will be performed when the + // given descriptor is flagged as ready, or an error has occurred. + ASIO_DECL void start_op(int op_type, socket_type descriptor, + per_descriptor_data&, reactor_op* op, bool is_continuation, bool); + + // Cancel all operations associated with the given descriptor. The + // handlers associated with the descriptor will be invoked with the + // operation_aborted error. + ASIO_DECL void cancel_ops(socket_type descriptor, per_descriptor_data&); + + // Cancel any operations that are running against the descriptor and remove + // its registration from the reactor. The reactor resources associated with + // the descriptor must be released by calling cleanup_descriptor_data. + ASIO_DECL void deregister_descriptor(socket_type descriptor, + per_descriptor_data&, bool closing); + + // Remove the descriptor's registration from the reactor. The reactor + // resources associated with the descriptor must be released by calling + // cleanup_descriptor_data. + ASIO_DECL void deregister_internal_descriptor( + socket_type descriptor, per_descriptor_data&); + + // Perform any post-deregistration cleanup tasks associated with the + // descriptor data. + ASIO_DECL void cleanup_descriptor_data(per_descriptor_data&); + + // Move descriptor registration from one descriptor_data object to another. + ASIO_DECL void move_descriptor(socket_type descriptor, + per_descriptor_data& target_descriptor_data, + per_descriptor_data& source_descriptor_data); + + // Add a new timer queue to the reactor. + template + void add_timer_queue(timer_queue& queue); + + // Remove a timer queue from the reactor. + template + void remove_timer_queue(timer_queue& queue); + + // Schedule a new operation in the given timer queue to expire at the + // specified absolute time. + template + void schedule_timer(timer_queue& queue, + const typename Time_Traits::time_type& time, + typename timer_queue::per_timer_data& timer, wait_op* op); + + // Cancel the timer operations associated with the given token. Returns the + // number of operations that have been posted or dispatched. + template + std::size_t cancel_timer(timer_queue& queue, + typename timer_queue::per_timer_data& timer, + std::size_t max_cancelled = (std::numeric_limits::max)()); + + // Move the timer operations associated with the given timer. + template + void move_timer(timer_queue& queue, + typename timer_queue::per_timer_data& target, + typename timer_queue::per_timer_data& source); + + // Run select once until interrupted or events are ready to be dispatched. + ASIO_DECL void run(long usec, op_queue& ops); + + // Interrupt the select loop. + ASIO_DECL void interrupt(); + +private: +#if defined(ASIO_HAS_IOCP) + // Run the select loop in the thread. + ASIO_DECL void run_thread(); +#endif // defined(ASIO_HAS_IOCP) + + // Helper function to add a new timer queue. + ASIO_DECL void do_add_timer_queue(timer_queue_base& queue); + + // Helper function to remove a timer queue. + ASIO_DECL void do_remove_timer_queue(timer_queue_base& queue); + + // Get the timeout value for the select call. + ASIO_DECL timeval* get_timeout(long usec, timeval& tv); + + // Cancel all operations associated with the given descriptor. This function + // does not acquire the select_reactor's mutex. + ASIO_DECL void cancel_ops_unlocked(socket_type descriptor, + const asio::error_code& ec); + + // The scheduler implementation used to post completions. +# if defined(ASIO_HAS_IOCP) + typedef class win_iocp_io_context scheduler_type; +# else // defined(ASIO_HAS_IOCP) + typedef class scheduler scheduler_type; +# endif // defined(ASIO_HAS_IOCP) + scheduler_type& scheduler_; + + // Mutex to protect access to internal data. + asio::detail::mutex mutex_; + + // The interrupter is used to break a blocking select call. + select_interrupter interrupter_; + + // The queues of read, write and except operations. + reactor_op_queue op_queue_[max_ops]; + + // The file descriptor sets to be passed to the select system call. + fd_set_adapter fd_sets_[max_select_ops]; + + // The timer queues. + timer_queue_set timer_queues_; + +#if defined(ASIO_HAS_IOCP) + // Helper class to run the reactor loop in a thread. + class thread_function; + friend class thread_function; + + // Does the reactor loop thread need to stop. + bool stop_thread_; + + // The thread that is running the reactor loop. + asio::detail::thread* thread_; +#endif // defined(ASIO_HAS_IOCP) + + // Whether the service has been shut down. + bool shutdown_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/detail/impl/select_reactor.hpp" +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/select_reactor.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_HAS_IOCP) + // || (!defined(ASIO_HAS_DEV_POLL) + // && !defined(ASIO_HAS_EPOLL) + // && !defined(ASIO_HAS_KQUEUE) + // && !defined(ASIO_WINDOWS_RUNTIME)) + +#endif // ASIO_DETAIL_SELECT_REACTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/service_registry.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/service_registry.hpp new file mode 100644 index 000000000..ba2d3efb2 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/service_registry.hpp @@ -0,0 +1,164 @@ +// +// detail/service_registry.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SERVICE_REGISTRY_HPP +#define ASIO_DETAIL_SERVICE_REGISTRY_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include "asio/detail/mutex.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution_context.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +class io_context; + +namespace detail { + +template +class typeid_wrapper {}; + +class service_registry + : private noncopyable +{ +public: + // Constructor. + ASIO_DECL service_registry(execution_context& owner); + + // Destructor. + ASIO_DECL ~service_registry(); + + // Shutdown all services. + ASIO_DECL void shutdown_services(); + + // Destroy all services. + ASIO_DECL void destroy_services(); + + // Notify all services of a fork event. + ASIO_DECL void notify_fork(execution_context::fork_event fork_ev); + + // Get the service object corresponding to the specified service type. Will + // create a new service object automatically if no such object already + // exists. Ownership of the service object is not transferred to the caller. + template + Service& use_service(); + + // Get the service object corresponding to the specified service type. Will + // create a new service object automatically if no such object already + // exists. Ownership of the service object is not transferred to the caller. + // This overload is used for backwards compatibility with services that + // inherit from io_context::service. + template + Service& use_service(io_context& owner); + + // Add a service object. Throws on error, in which case ownership of the + // object is retained by the caller. + template + void add_service(Service* new_service); + + // Check whether a service object of the specified type already exists. + template + bool has_service() const; + +private: + // Initalise a service's key when the key_type typedef is not available. + template + static void init_key(execution_context::service::key& key, ...); + +#if !defined(ASIO_NO_TYPEID) + // Initalise a service's key when the key_type typedef is available. + template + static void init_key(execution_context::service::key& key, + typename enable_if< + is_base_of::value>::type*); +#endif // !defined(ASIO_NO_TYPEID) + + // Initialise a service's key based on its id. + ASIO_DECL static void init_key_from_id( + execution_context::service::key& key, + const execution_context::id& id); + +#if !defined(ASIO_NO_TYPEID) + // Initialise a service's key based on its id. + template + static void init_key_from_id(execution_context::service::key& key, + const service_id& /*id*/); +#endif // !defined(ASIO_NO_TYPEID) + + // Check if a service matches the given id. + ASIO_DECL static bool keys_match( + const execution_context::service::key& key1, + const execution_context::service::key& key2); + + // The type of a factory function used for creating a service instance. + typedef execution_context::service*(*factory_type)(void*); + + // Factory function for creating a service instance. + template + static execution_context::service* create(void* owner); + + // Destroy a service instance. + ASIO_DECL static void destroy(execution_context::service* service); + + // Helper class to manage service pointers. + struct auto_service_ptr; + friend struct auto_service_ptr; + struct auto_service_ptr + { + execution_context::service* ptr_; + ~auto_service_ptr() { destroy(ptr_); } + }; + + // Get the service object corresponding to the specified service key. Will + // create a new service object automatically if no such object already + // exists. Ownership of the service object is not transferred to the caller. + ASIO_DECL execution_context::service* do_use_service( + const execution_context::service::key& key, + factory_type factory, void* owner); + + // Add a service object. Throws on error, in which case ownership of the + // object is retained by the caller. + ASIO_DECL void do_add_service( + const execution_context::service::key& key, + execution_context::service* new_service); + + // Check whether a service object with the specified key already exists. + ASIO_DECL bool do_has_service( + const execution_context::service::key& key) const; + + // Mutex to protect access to internal data. + mutable asio::detail::mutex mutex_; + + // The owner of this service registry and the services it contains. + execution_context& owner_; + + // The first service in the list of contained services. + execution_context::service* first_service_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/detail/impl/service_registry.hpp" +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/service_registry.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // ASIO_DETAIL_SERVICE_REGISTRY_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/signal_blocker.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/signal_blocker.hpp new file mode 100644 index 000000000..aefba1181 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/signal_blocker.hpp @@ -0,0 +1,44 @@ +// +// detail/signal_blocker.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SIGNAL_BLOCKER_HPP +#define ASIO_DETAIL_SIGNAL_BLOCKER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_THREADS) || defined(ASIO_WINDOWS) \ + || defined(ASIO_WINDOWS_RUNTIME) \ + || defined(__CYGWIN__) || defined(__SYMBIAN32__) +# include "asio/detail/null_signal_blocker.hpp" +#elif defined(ASIO_HAS_PTHREADS) +# include "asio/detail/posix_signal_blocker.hpp" +#else +# error Only Windows and POSIX are supported! +#endif + +namespace asio { +namespace detail { + +#if !defined(ASIO_HAS_THREADS) || defined(ASIO_WINDOWS) \ + || defined(ASIO_WINDOWS_RUNTIME) \ + || defined(__CYGWIN__) || defined(__SYMBIAN32__) +typedef null_signal_blocker signal_blocker; +#elif defined(ASIO_HAS_PTHREADS) +typedef posix_signal_blocker signal_blocker; +#endif + +} // namespace detail +} // namespace asio + +#endif // ASIO_DETAIL_SIGNAL_BLOCKER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/signal_handler.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/signal_handler.hpp new file mode 100644 index 000000000..23ac7b34e --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/signal_handler.hpp @@ -0,0 +1,90 @@ +// +// detail/signal_handler.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SIGNAL_HANDLER_HPP +#define ASIO_DETAIL_SIGNAL_HANDLER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/signal_op.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class signal_handler : public signal_op +{ +public: + ASIO_DEFINE_HANDLER_PTR(signal_handler); + + signal_handler(Handler& h, const IoExecutor& io_ex) + : signal_op(&signal_handler::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(h)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the handler object. + signal_handler* h(static_cast(base)); + ptr p = { asio::detail::addressof(h->handler_), h, h }; + + ASIO_HANDLER_COMPLETION((*h)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + h->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(h->handler_, h->ec_, h->signal_number_); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_SIGNAL_HANDLER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/signal_init.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/signal_init.hpp new file mode 100644 index 000000000..dbffde24c --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/signal_init.hpp @@ -0,0 +1,47 @@ +// +// detail/signal_init.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SIGNAL_INIT_HPP +#define ASIO_DETAIL_SIGNAL_INIT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) + +#include + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class signal_init +{ +public: + // Constructor. + signal_init() + { + std::signal(Signal, SIG_IGN); + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) + +#endif // ASIO_DETAIL_SIGNAL_INIT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/signal_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/signal_op.hpp new file mode 100644 index 000000000..863fc5d2f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/signal_op.hpp @@ -0,0 +1,49 @@ +// +// detail/signal_op.hpp +// ~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SIGNAL_OP_HPP +#define ASIO_DETAIL_SIGNAL_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/operation.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class signal_op + : public operation +{ +public: + // The error code to be passed to the completion handler. + asio::error_code ec_; + + // The signal number to be passed to the completion handler. + int signal_number_; + +protected: + signal_op(func_type func) + : operation(func), + signal_number_(0) + { + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_SIGNAL_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/signal_set_service.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/signal_set_service.hpp new file mode 100644 index 000000000..a9a89603f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/signal_set_service.hpp @@ -0,0 +1,229 @@ +// +// detail/signal_set_service.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SIGNAL_SET_SERVICE_HPP +#define ASIO_DETAIL_SIGNAL_SET_SERVICE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#include +#include +#include "asio/error.hpp" +#include "asio/execution_context.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/op_queue.hpp" +#include "asio/detail/signal_handler.hpp" +#include "asio/detail/signal_op.hpp" +#include "asio/detail/socket_types.hpp" + +#if defined(ASIO_HAS_IOCP) +# include "asio/detail/win_iocp_io_context.hpp" +#else // defined(ASIO_HAS_IOCP) +# include "asio/detail/scheduler.hpp" +#endif // defined(ASIO_HAS_IOCP) + +#if !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) +# include "asio/detail/reactor.hpp" +#endif // !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +#if defined(NSIG) && (NSIG > 0) +enum { max_signal_number = NSIG }; +#else +enum { max_signal_number = 128 }; +#endif + +extern ASIO_DECL struct signal_state* get_signal_state(); + +extern "C" ASIO_DECL void asio_signal_handler(int signal_number); + +class signal_set_service : + public execution_context_service_base +{ +public: + // Type used for tracking an individual signal registration. + class registration + { + public: + // Default constructor. + registration() + : signal_number_(0), + queue_(0), + undelivered_(0), + next_in_table_(0), + prev_in_table_(0), + next_in_set_(0) + { + } + + private: + // Only this service will have access to the internal values. + friend class signal_set_service; + + // The signal number that is registered. + int signal_number_; + + // The waiting signal handlers. + op_queue* queue_; + + // The number of undelivered signals. + std::size_t undelivered_; + + // Pointers to adjacent registrations in the registrations_ table. + registration* next_in_table_; + registration* prev_in_table_; + + // Link to next registration in the signal set. + registration* next_in_set_; + }; + + // The implementation type of the signal_set. + class implementation_type + { + public: + // Default constructor. + implementation_type() + : signals_(0) + { + } + + private: + // Only this service will have access to the internal values. + friend class signal_set_service; + + // The pending signal handlers. + op_queue queue_; + + // Linked list of registered signals. + registration* signals_; + }; + + // Constructor. + ASIO_DECL signal_set_service(execution_context& context); + + // Destructor. + ASIO_DECL ~signal_set_service(); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void shutdown(); + + // Perform fork-related housekeeping. + ASIO_DECL void notify_fork( + asio::execution_context::fork_event fork_ev); + + // Construct a new signal_set implementation. + ASIO_DECL void construct(implementation_type& impl); + + // Destroy a signal_set implementation. + ASIO_DECL void destroy(implementation_type& impl); + + // Add a signal to a signal_set. + ASIO_DECL asio::error_code add(implementation_type& impl, + int signal_number, asio::error_code& ec); + + // Remove a signal to a signal_set. + ASIO_DECL asio::error_code remove(implementation_type& impl, + int signal_number, asio::error_code& ec); + + // Remove all signals from a signal_set. + ASIO_DECL asio::error_code clear(implementation_type& impl, + asio::error_code& ec); + + // Cancel all operations associated with the signal set. + ASIO_DECL asio::error_code cancel(implementation_type& impl, + asio::error_code& ec); + + // Start an asynchronous operation to wait for a signal to be delivered. + template + void async_wait(implementation_type& impl, + Handler& handler, const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef signal_handler op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(handler, io_ex); + + ASIO_HANDLER_CREATION((scheduler_.context(), + *p.p, "signal_set", &impl, 0, "async_wait")); + + start_wait_op(impl, p.p); + p.v = p.p = 0; + } + + // Deliver notification that a particular signal occurred. + ASIO_DECL static void deliver_signal(int signal_number); + +private: + // Helper function to add a service to the global signal state. + ASIO_DECL static void add_service(signal_set_service* service); + + // Helper function to remove a service from the global signal state. + ASIO_DECL static void remove_service(signal_set_service* service); + + // Helper function to create the pipe descriptors. + ASIO_DECL static void open_descriptors(); + + // Helper function to close the pipe descriptors. + ASIO_DECL static void close_descriptors(); + + // Helper function to start a wait operation. + ASIO_DECL void start_wait_op(implementation_type& impl, signal_op* op); + + // The scheduler used for dispatching handlers. +#if defined(ASIO_HAS_IOCP) + typedef class win_iocp_io_context scheduler_impl; +#else + typedef class scheduler scheduler_impl; +#endif + scheduler_impl& scheduler_; + +#if !defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_RUNTIME) \ + && !defined(__CYGWIN__) + // The type used for registering for pipe reactor notifications. + class pipe_read_op; + + // The reactor used for waiting for pipe readiness. + reactor& reactor_; + + // The per-descriptor reactor data used for the pipe. + reactor::per_descriptor_data reactor_data_; +#endif // !defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_RUNTIME) + // && !defined(__CYGWIN__) + + // A mapping from signal number to the registered signal sets. + registration* registrations_[max_signal_number]; + + // Pointers to adjacent services in linked list. + signal_set_service* next_; + signal_set_service* prev_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/signal_set_service.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // ASIO_DETAIL_SIGNAL_SET_SERVICE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/socket_holder.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/socket_holder.hpp new file mode 100644 index 000000000..bf631a64b --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/socket_holder.hpp @@ -0,0 +1,98 @@ +// +// detail/socket_holder.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SOCKET_HOLDER_HPP +#define ASIO_DETAIL_SOCKET_HOLDER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/socket_ops.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Implement the resource acquisition is initialisation idiom for sockets. +class socket_holder + : private noncopyable +{ +public: + // Construct as an uninitialised socket. + socket_holder() + : socket_(invalid_socket) + { + } + + // Construct to take ownership of the specified socket. + explicit socket_holder(socket_type s) + : socket_(s) + { + } + + // Destructor. + ~socket_holder() + { + if (socket_ != invalid_socket) + { + asio::error_code ec; + socket_ops::state_type state = 0; + socket_ops::close(socket_, state, true, ec); + } + } + + // Get the underlying socket. + socket_type get() const + { + return socket_; + } + + // Reset to an uninitialised socket. + void reset() + { + if (socket_ != invalid_socket) + { + asio::error_code ec; + socket_ops::state_type state = 0; + socket_ops::close(socket_, state, true, ec); + socket_ = invalid_socket; + } + } + + // Reset to take ownership of the specified socket. + void reset(socket_type s) + { + reset(); + socket_ = s; + } + + // Release ownership of the socket. + socket_type release() + { + socket_type tmp = socket_; + socket_ = invalid_socket; + return tmp; + } + +private: + // The underlying socket. + socket_type socket_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_SOCKET_HOLDER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/socket_ops.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/socket_ops.hpp new file mode 100644 index 000000000..5098c4124 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/socket_ops.hpp @@ -0,0 +1,383 @@ +// +// detail/socket_ops.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SOCKET_OPS_HPP +#define ASIO_DETAIL_SOCKET_OPS_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#include "asio/error_code.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/socket_types.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { +namespace socket_ops { + +// Socket state bits. +enum +{ + // The user wants a non-blocking socket. + user_set_non_blocking = 1, + + // The socket has been set non-blocking. + internal_non_blocking = 2, + + // Helper "state" used to determine whether the socket is non-blocking. + non_blocking = user_set_non_blocking | internal_non_blocking, + + // User wants connection_aborted errors, which are disabled by default. + enable_connection_aborted = 4, + + // The user set the linger option. Needs to be checked when closing. + user_set_linger = 8, + + // The socket is stream-oriented. + stream_oriented = 16, + + // The socket is datagram-oriented. + datagram_oriented = 32, + + // The socket may have been dup()-ed. + possible_dup = 64 +}; + +typedef unsigned char state_type; + +struct noop_deleter { void operator()(void*) {} }; +typedef shared_ptr shared_cancel_token_type; +typedef weak_ptr weak_cancel_token_type; + +#if !defined(ASIO_WINDOWS_RUNTIME) + +ASIO_DECL socket_type accept(socket_type s, socket_addr_type* addr, + std::size_t* addrlen, asio::error_code& ec); + +ASIO_DECL socket_type sync_accept(socket_type s, + state_type state, socket_addr_type* addr, + std::size_t* addrlen, asio::error_code& ec); + +#if defined(ASIO_HAS_IOCP) + +ASIO_DECL void complete_iocp_accept(socket_type s, + void* output_buffer, DWORD address_length, + socket_addr_type* addr, std::size_t* addrlen, + socket_type new_socket, asio::error_code& ec); + +#else // defined(ASIO_HAS_IOCP) + +ASIO_DECL bool non_blocking_accept(socket_type s, + state_type state, socket_addr_type* addr, std::size_t* addrlen, + asio::error_code& ec, socket_type& new_socket); + +#endif // defined(ASIO_HAS_IOCP) + +ASIO_DECL int bind(socket_type s, const socket_addr_type* addr, + std::size_t addrlen, asio::error_code& ec); + +ASIO_DECL int close(socket_type s, state_type& state, + bool destruction, asio::error_code& ec); + +ASIO_DECL bool set_user_non_blocking(socket_type s, + state_type& state, bool value, asio::error_code& ec); + +ASIO_DECL bool set_internal_non_blocking(socket_type s, + state_type& state, bool value, asio::error_code& ec); + +ASIO_DECL int shutdown(socket_type s, + int what, asio::error_code& ec); + +ASIO_DECL int connect(socket_type s, const socket_addr_type* addr, + std::size_t addrlen, asio::error_code& ec); + +ASIO_DECL void sync_connect(socket_type s, const socket_addr_type* addr, + std::size_t addrlen, asio::error_code& ec); + +#if defined(ASIO_HAS_IOCP) + +ASIO_DECL void complete_iocp_connect(socket_type s, + asio::error_code& ec); + +#endif // defined(ASIO_HAS_IOCP) + +ASIO_DECL bool non_blocking_connect(socket_type s, + asio::error_code& ec); + +ASIO_DECL int socketpair(int af, int type, int protocol, + socket_type sv[2], asio::error_code& ec); + +ASIO_DECL bool sockatmark(socket_type s, asio::error_code& ec); + +ASIO_DECL size_t available(socket_type s, asio::error_code& ec); + +ASIO_DECL int listen(socket_type s, + int backlog, asio::error_code& ec); + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) +typedef WSABUF buf; +#else // defined(ASIO_WINDOWS) || defined(__CYGWIN__) +typedef iovec buf; +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +ASIO_DECL void init_buf(buf& b, void* data, size_t size); + +ASIO_DECL void init_buf(buf& b, const void* data, size_t size); + +ASIO_DECL signed_size_type recv(socket_type s, buf* bufs, + size_t count, int flags, asio::error_code& ec); + +ASIO_DECL signed_size_type recv1(socket_type s, + void* data, size_t size, int flags, asio::error_code& ec); + +ASIO_DECL size_t sync_recv(socket_type s, state_type state, buf* bufs, + size_t count, int flags, bool all_empty, asio::error_code& ec); + +ASIO_DECL size_t sync_recv1(socket_type s, state_type state, + void* data, size_t size, int flags, asio::error_code& ec); + +#if defined(ASIO_HAS_IOCP) + +ASIO_DECL void complete_iocp_recv(state_type state, + const weak_cancel_token_type& cancel_token, bool all_empty, + asio::error_code& ec, size_t bytes_transferred); + +#else // defined(ASIO_HAS_IOCP) + +ASIO_DECL bool non_blocking_recv(socket_type s, + buf* bufs, size_t count, int flags, bool is_stream, + asio::error_code& ec, size_t& bytes_transferred); + +ASIO_DECL bool non_blocking_recv1(socket_type s, + void* data, size_t size, int flags, bool is_stream, + asio::error_code& ec, size_t& bytes_transferred); + +#endif // defined(ASIO_HAS_IOCP) + +ASIO_DECL signed_size_type recvfrom(socket_type s, buf* bufs, + size_t count, int flags, socket_addr_type* addr, + std::size_t* addrlen, asio::error_code& ec); + +ASIO_DECL signed_size_type recvfrom1(socket_type s, void* data, + size_t size, int flags, socket_addr_type* addr, + std::size_t* addrlen, asio::error_code& ec); + +ASIO_DECL size_t sync_recvfrom(socket_type s, state_type state, + buf* bufs, size_t count, int flags, socket_addr_type* addr, + std::size_t* addrlen, asio::error_code& ec); + +ASIO_DECL size_t sync_recvfrom1(socket_type s, state_type state, + void* data, size_t size, int flags, socket_addr_type* addr, + std::size_t* addrlen, asio::error_code& ec); + +#if defined(ASIO_HAS_IOCP) + +ASIO_DECL void complete_iocp_recvfrom( + const weak_cancel_token_type& cancel_token, + asio::error_code& ec); + +#else // defined(ASIO_HAS_IOCP) + +ASIO_DECL bool non_blocking_recvfrom(socket_type s, + buf* bufs, size_t count, int flags, + socket_addr_type* addr, std::size_t* addrlen, + asio::error_code& ec, size_t& bytes_transferred); + +ASIO_DECL bool non_blocking_recvfrom1(socket_type s, + void* data, size_t size, int flags, + socket_addr_type* addr, std::size_t* addrlen, + asio::error_code& ec, size_t& bytes_transferred); + +#endif // defined(ASIO_HAS_IOCP) + +ASIO_DECL signed_size_type recvmsg(socket_type s, buf* bufs, + size_t count, int in_flags, int& out_flags, + asio::error_code& ec); + +ASIO_DECL size_t sync_recvmsg(socket_type s, state_type state, + buf* bufs, size_t count, int in_flags, int& out_flags, + asio::error_code& ec); + +#if defined(ASIO_HAS_IOCP) + +ASIO_DECL void complete_iocp_recvmsg( + const weak_cancel_token_type& cancel_token, + asio::error_code& ec); + +#else // defined(ASIO_HAS_IOCP) + +ASIO_DECL bool non_blocking_recvmsg(socket_type s, + buf* bufs, size_t count, int in_flags, int& out_flags, + asio::error_code& ec, size_t& bytes_transferred); + +#endif // defined(ASIO_HAS_IOCP) + +ASIO_DECL signed_size_type send(socket_type s, const buf* bufs, + size_t count, int flags, asio::error_code& ec); + +ASIO_DECL signed_size_type send1(socket_type s, + const void* data, size_t size, int flags, asio::error_code& ec); + +ASIO_DECL size_t sync_send(socket_type s, state_type state, + const buf* bufs, size_t count, int flags, + bool all_empty, asio::error_code& ec); + +ASIO_DECL size_t sync_send1(socket_type s, state_type state, + const void* data, size_t size, int flags, asio::error_code& ec); + +#if defined(ASIO_HAS_IOCP) + +ASIO_DECL void complete_iocp_send( + const weak_cancel_token_type& cancel_token, + asio::error_code& ec); + +#else // defined(ASIO_HAS_IOCP) + +ASIO_DECL bool non_blocking_send(socket_type s, + const buf* bufs, size_t count, int flags, + asio::error_code& ec, size_t& bytes_transferred); + +ASIO_DECL bool non_blocking_send1(socket_type s, + const void* data, size_t size, int flags, + asio::error_code& ec, size_t& bytes_transferred); + +#endif // defined(ASIO_HAS_IOCP) + +ASIO_DECL signed_size_type sendto(socket_type s, const buf* bufs, + size_t count, int flags, const socket_addr_type* addr, + std::size_t addrlen, asio::error_code& ec); + +ASIO_DECL signed_size_type sendto1(socket_type s, const void* data, + size_t size, int flags, const socket_addr_type* addr, + std::size_t addrlen, asio::error_code& ec); + +ASIO_DECL size_t sync_sendto(socket_type s, state_type state, + const buf* bufs, size_t count, int flags, const socket_addr_type* addr, + std::size_t addrlen, asio::error_code& ec); + +ASIO_DECL size_t sync_sendto1(socket_type s, state_type state, + const void* data, size_t size, int flags, const socket_addr_type* addr, + std::size_t addrlen, asio::error_code& ec); + +#if !defined(ASIO_HAS_IOCP) + +ASIO_DECL bool non_blocking_sendto(socket_type s, + const buf* bufs, size_t count, int flags, + const socket_addr_type* addr, std::size_t addrlen, + asio::error_code& ec, size_t& bytes_transferred); + +ASIO_DECL bool non_blocking_sendto1(socket_type s, + const void* data, size_t size, int flags, + const socket_addr_type* addr, std::size_t addrlen, + asio::error_code& ec, size_t& bytes_transferred); + +#endif // !defined(ASIO_HAS_IOCP) + +ASIO_DECL socket_type socket(int af, int type, int protocol, + asio::error_code& ec); + +ASIO_DECL int setsockopt(socket_type s, state_type& state, + int level, int optname, const void* optval, + std::size_t optlen, asio::error_code& ec); + +ASIO_DECL int getsockopt(socket_type s, state_type state, + int level, int optname, void* optval, + size_t* optlen, asio::error_code& ec); + +ASIO_DECL int getpeername(socket_type s, socket_addr_type* addr, + std::size_t* addrlen, bool cached, asio::error_code& ec); + +ASIO_DECL int getsockname(socket_type s, socket_addr_type* addr, + std::size_t* addrlen, asio::error_code& ec); + +ASIO_DECL int ioctl(socket_type s, state_type& state, + int cmd, ioctl_arg_type* arg, asio::error_code& ec); + +ASIO_DECL int select(int nfds, fd_set* readfds, fd_set* writefds, + fd_set* exceptfds, timeval* timeout, asio::error_code& ec); + +ASIO_DECL int poll_read(socket_type s, + state_type state, int msec, asio::error_code& ec); + +ASIO_DECL int poll_write(socket_type s, + state_type state, int msec, asio::error_code& ec); + +ASIO_DECL int poll_error(socket_type s, + state_type state, int msec, asio::error_code& ec); + +ASIO_DECL int poll_connect(socket_type s, + int msec, asio::error_code& ec); + +#endif // !defined(ASIO_WINDOWS_RUNTIME) + +ASIO_DECL const char* inet_ntop(int af, const void* src, char* dest, + size_t length, unsigned long scope_id, asio::error_code& ec); + +ASIO_DECL int inet_pton(int af, const char* src, void* dest, + unsigned long* scope_id, asio::error_code& ec); + +ASIO_DECL int gethostname(char* name, + int namelen, asio::error_code& ec); + +#if !defined(ASIO_WINDOWS_RUNTIME) + +ASIO_DECL asio::error_code getaddrinfo(const char* host, + const char* service, const addrinfo_type& hints, + addrinfo_type** result, asio::error_code& ec); + +ASIO_DECL asio::error_code background_getaddrinfo( + const weak_cancel_token_type& cancel_token, const char* host, + const char* service, const addrinfo_type& hints, + addrinfo_type** result, asio::error_code& ec); + +ASIO_DECL void freeaddrinfo(addrinfo_type* ai); + +ASIO_DECL asio::error_code getnameinfo( + const socket_addr_type* addr, std::size_t addrlen, + char* host, std::size_t hostlen, char* serv, + std::size_t servlen, int flags, asio::error_code& ec); + +ASIO_DECL asio::error_code sync_getnameinfo( + const socket_addr_type* addr, std::size_t addrlen, + char* host, std::size_t hostlen, char* serv, + std::size_t servlen, int sock_type, asio::error_code& ec); + +ASIO_DECL asio::error_code background_getnameinfo( + const weak_cancel_token_type& cancel_token, + const socket_addr_type* addr, std::size_t addrlen, + char* host, std::size_t hostlen, char* serv, + std::size_t servlen, int sock_type, asio::error_code& ec); + +#endif // !defined(ASIO_WINDOWS_RUNTIME) + +ASIO_DECL u_long_type network_to_host_long(u_long_type value); + +ASIO_DECL u_long_type host_to_network_long(u_long_type value); + +ASIO_DECL u_short_type network_to_host_short(u_short_type value); + +ASIO_DECL u_short_type host_to_network_short(u_short_type value); + +} // namespace socket_ops +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/socket_ops.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // ASIO_DETAIL_SOCKET_OPS_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/socket_option.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/socket_option.hpp new file mode 100644 index 000000000..4fe93ace7 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/socket_option.hpp @@ -0,0 +1,316 @@ +// +// detail/socket_option.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SOCKET_OPTION_HPP +#define ASIO_DETAIL_SOCKET_OPTION_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include +#include "asio/detail/socket_types.hpp" +#include "asio/detail/throw_exception.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { +namespace socket_option { + +// Helper template for implementing boolean-based options. +template +class boolean +{ +public: + // Default constructor. + boolean() + : value_(0) + { + } + + // Construct with a specific option value. + explicit boolean(bool v) + : value_(v ? 1 : 0) + { + } + + // Set the current value of the boolean. + boolean& operator=(bool v) + { + value_ = v ? 1 : 0; + return *this; + } + + // Get the current value of the boolean. + bool value() const + { + return !!value_; + } + + // Convert to bool. + operator bool() const + { + return !!value_; + } + + // Test for false. + bool operator!() const + { + return !value_; + } + + // Get the level of the socket option. + template + int level(const Protocol&) const + { + return Level; + } + + // Get the name of the socket option. + template + int name(const Protocol&) const + { + return Name; + } + + // Get the address of the boolean data. + template + int* data(const Protocol&) + { + return &value_; + } + + // Get the address of the boolean data. + template + const int* data(const Protocol&) const + { + return &value_; + } + + // Get the size of the boolean data. + template + std::size_t size(const Protocol&) const + { + return sizeof(value_); + } + + // Set the size of the boolean data. + template + void resize(const Protocol&, std::size_t s) + { + // On some platforms (e.g. Windows Vista), the getsockopt function will + // return the size of a boolean socket option as one byte, even though a + // four byte integer was passed in. + switch (s) + { + case sizeof(char): + value_ = *reinterpret_cast(&value_) ? 1 : 0; + break; + case sizeof(value_): + break; + default: + { + std::length_error ex("boolean socket option resize"); + asio::detail::throw_exception(ex); + } + } + } + +private: + int value_; +}; + +// Helper template for implementing integer options. +template +class integer +{ +public: + // Default constructor. + integer() + : value_(0) + { + } + + // Construct with a specific option value. + explicit integer(int v) + : value_(v) + { + } + + // Set the value of the int option. + integer& operator=(int v) + { + value_ = v; + return *this; + } + + // Get the current value of the int option. + int value() const + { + return value_; + } + + // Get the level of the socket option. + template + int level(const Protocol&) const + { + return Level; + } + + // Get the name of the socket option. + template + int name(const Protocol&) const + { + return Name; + } + + // Get the address of the int data. + template + int* data(const Protocol&) + { + return &value_; + } + + // Get the address of the int data. + template + const int* data(const Protocol&) const + { + return &value_; + } + + // Get the size of the int data. + template + std::size_t size(const Protocol&) const + { + return sizeof(value_); + } + + // Set the size of the int data. + template + void resize(const Protocol&, std::size_t s) + { + if (s != sizeof(value_)) + { + std::length_error ex("integer socket option resize"); + asio::detail::throw_exception(ex); + } + } + +private: + int value_; +}; + +// Helper template for implementing linger options. +template +class linger +{ +public: + // Default constructor. + linger() + { + value_.l_onoff = 0; + value_.l_linger = 0; + } + + // Construct with specific option values. + linger(bool e, int t) + { + enabled(e); + timeout ASIO_PREVENT_MACRO_SUBSTITUTION(t); + } + + // Set the value for whether linger is enabled. + void enabled(bool value) + { + value_.l_onoff = value ? 1 : 0; + } + + // Get the value for whether linger is enabled. + bool enabled() const + { + return value_.l_onoff != 0; + } + + // Set the value for the linger timeout. + void timeout ASIO_PREVENT_MACRO_SUBSTITUTION(int value) + { +#if defined(WIN32) + value_.l_linger = static_cast(value); +#else + value_.l_linger = value; +#endif + } + + // Get the value for the linger timeout. + int timeout ASIO_PREVENT_MACRO_SUBSTITUTION() const + { + return static_cast(value_.l_linger); + } + + // Get the level of the socket option. + template + int level(const Protocol&) const + { + return Level; + } + + // Get the name of the socket option. + template + int name(const Protocol&) const + { + return Name; + } + + // Get the address of the linger data. + template + detail::linger_type* data(const Protocol&) + { + return &value_; + } + + // Get the address of the linger data. + template + const detail::linger_type* data(const Protocol&) const + { + return &value_; + } + + // Get the size of the linger data. + template + std::size_t size(const Protocol&) const + { + return sizeof(value_); + } + + // Set the size of the int data. + template + void resize(const Protocol&, std::size_t s) + { + if (s != sizeof(value_)) + { + std::length_error ex("linger socket option resize"); + asio::detail::throw_exception(ex); + } + } + +private: + detail::linger_type value_; +}; + +} // namespace socket_option +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_SOCKET_OPTION_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/socket_select_interrupter.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/socket_select_interrupter.hpp new file mode 100644 index 000000000..561ad0526 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/socket_select_interrupter.hpp @@ -0,0 +1,91 @@ +// +// detail/socket_select_interrupter.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SOCKET_SELECT_INTERRUPTER_HPP +#define ASIO_DETAIL_SOCKET_SELECT_INTERRUPTER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_WINDOWS_RUNTIME) + +#if defined(ASIO_WINDOWS) \ + || defined(__CYGWIN__) \ + || defined(__SYMBIAN32__) + +#include "asio/detail/socket_types.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class socket_select_interrupter +{ +public: + // Constructor. + ASIO_DECL socket_select_interrupter(); + + // Destructor. + ASIO_DECL ~socket_select_interrupter(); + + // Recreate the interrupter's descriptors. Used after a fork. + ASIO_DECL void recreate(); + + // Interrupt the select call. + ASIO_DECL void interrupt(); + + // Reset the select interrupter. Returns true if the reset was successful. + ASIO_DECL bool reset(); + + // Get the read descriptor to be passed to select. + socket_type read_descriptor() const + { + return read_descriptor_; + } + +private: + // Open the descriptors. Throws on error. + ASIO_DECL void open_descriptors(); + + // Close the descriptors. + ASIO_DECL void close_descriptors(); + + // The read end of a connection used to interrupt the select call. This file + // descriptor is passed to select such that when it is time to stop, a single + // byte will be written on the other end of the connection and this + // descriptor will become readable. + socket_type read_descriptor_; + + // The write end of a connection used to interrupt the select call. A single + // byte may be written to this to wake up the select which is waiting for the + // other end to become readable. + socket_type write_descriptor_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/socket_select_interrupter.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_WINDOWS) + // || defined(__CYGWIN__) + // || defined(__SYMBIAN32__) + +#endif // !defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_SOCKET_SELECT_INTERRUPTER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/socket_types.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/socket_types.hpp new file mode 100644 index 000000000..a118d9de4 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/socket_types.hpp @@ -0,0 +1,416 @@ +// +// detail/socket_types.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SOCKET_TYPES_HPP +#define ASIO_DETAIL_SOCKET_TYPES_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) +// Empty. +#elif defined(ASIO_WINDOWS) || defined(__CYGWIN__) +# if defined(_WINSOCKAPI_) && !defined(_WINSOCK2API_) +# error WinSock.h has already been included +# endif // defined(_WINSOCKAPI_) && !defined(_WINSOCK2API_) +# if defined(__BORLANDC__) +# include // Needed for __errno +# if !defined(_WSPIAPI_H_) +# define _WSPIAPI_H_ +# define ASIO_WSPIAPI_H_DEFINED +# endif // !defined(_WSPIAPI_H_) +# endif // defined(__BORLANDC__) +# include +# include +# if defined(WINAPI_FAMILY) +# if ((WINAPI_FAMILY & WINAPI_PARTITION_DESKTOP) != 0) +# include +# endif // ((WINAPI_FAMILY & WINAPI_PARTITION_DESKTOP) != 0) +# endif // defined(WINAPI_FAMILY) +# if !defined(ASIO_WINDOWS_APP) +# include +# endif // !defined(ASIO_WINDOWS_APP) +# if defined(ASIO_WSPIAPI_H_DEFINED) +# undef _WSPIAPI_H_ +# undef ASIO_WSPIAPI_H_DEFINED +# endif // defined(ASIO_WSPIAPI_H_DEFINED) +# if !defined(ASIO_NO_DEFAULT_LINKED_LIBS) +# if defined(UNDER_CE) +# pragma comment(lib, "ws2.lib") +# elif defined(_MSC_VER) || defined(__BORLANDC__) +# pragma comment(lib, "ws2_32.lib") +# if !defined(ASIO_WINDOWS_APP) +# pragma comment(lib, "mswsock.lib") +# endif // !defined(ASIO_WINDOWS_APP) +# endif // defined(_MSC_VER) || defined(__BORLANDC__) +# endif // !defined(ASIO_NO_DEFAULT_LINKED_LIBS) +# include "asio/detail/old_win_sdk_compat.hpp" +#else +# include +# if (defined(__MACH__) && defined(__APPLE__)) \ + || defined(__FreeBSD__) || defined(__NetBSD__) \ + || defined(__OpenBSD__) || defined(__linux__) \ + || defined(__EMSCRIPTEN__) +# include +# elif !defined(__SYMBIAN32__) +# include +# endif +# include +# include +# include +# if defined(__hpux) +# include +# endif +# if !defined(__hpux) || defined(__SELECT) +# include +# endif +# include +# include +# include +# include +# if !defined(__SYMBIAN32__) +# include +# endif +# include +# include +# include +# include +# if defined(__sun) +# include +# include +# endif +#endif + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +#if defined(ASIO_WINDOWS_RUNTIME) +const int max_addr_v4_str_len = 256; +const int max_addr_v6_str_len = 256; +typedef unsigned __int32 u_long_type; +typedef unsigned __int16 u_short_type; +struct in4_addr_type { u_long_type s_addr; }; +struct in4_mreq_type { in4_addr_type imr_multiaddr, imr_interface; }; +struct in6_addr_type { unsigned char s6_addr[16]; }; +struct in6_mreq_type { in6_addr_type ipv6mr_multiaddr; + unsigned long ipv6mr_interface; }; +struct socket_addr_type { int sa_family; }; +struct sockaddr_in4_type { int sin_family; + in4_addr_type sin_addr; u_short_type sin_port; }; +struct sockaddr_in6_type { int sin6_family; + in6_addr_type sin6_addr; u_short_type sin6_port; + u_long_type sin6_flowinfo; u_long_type sin6_scope_id; }; +struct sockaddr_storage_type { int ss_family; + unsigned char ss_bytes[128 - sizeof(int)]; }; +struct addrinfo_type { int ai_flags; + int ai_family, ai_socktype, ai_protocol; + int ai_addrlen; const void* ai_addr; + const char* ai_canonname; addrinfo_type* ai_next; }; +struct linger_type { u_short_type l_onoff, l_linger; }; +typedef u_long_type ioctl_arg_type; +typedef int signed_size_type; +# define ASIO_OS_DEF(c) ASIO_OS_DEF_##c +# define ASIO_OS_DEF_AF_UNSPEC 0 +# define ASIO_OS_DEF_AF_INET 2 +# define ASIO_OS_DEF_AF_INET6 23 +# define ASIO_OS_DEF_SOCK_STREAM 1 +# define ASIO_OS_DEF_SOCK_DGRAM 2 +# define ASIO_OS_DEF_SOCK_RAW 3 +# define ASIO_OS_DEF_SOCK_SEQPACKET 5 +# define ASIO_OS_DEF_IPPROTO_IP 0 +# define ASIO_OS_DEF_IPPROTO_IPV6 41 +# define ASIO_OS_DEF_IPPROTO_TCP 6 +# define ASIO_OS_DEF_IPPROTO_UDP 17 +# define ASIO_OS_DEF_IPPROTO_ICMP 1 +# define ASIO_OS_DEF_IPPROTO_ICMPV6 58 +# define ASIO_OS_DEF_FIONBIO 1 +# define ASIO_OS_DEF_FIONREAD 2 +# define ASIO_OS_DEF_INADDR_ANY 0 +# define ASIO_OS_DEF_MSG_OOB 0x1 +# define ASIO_OS_DEF_MSG_PEEK 0x2 +# define ASIO_OS_DEF_MSG_DONTROUTE 0x4 +# define ASIO_OS_DEF_MSG_EOR 0 // Not supported. +# define ASIO_OS_DEF_SHUT_RD 0x0 +# define ASIO_OS_DEF_SHUT_WR 0x1 +# define ASIO_OS_DEF_SHUT_RDWR 0x2 +# define ASIO_OS_DEF_SOMAXCONN 0x7fffffff +# define ASIO_OS_DEF_SOL_SOCKET 0xffff +# define ASIO_OS_DEF_SO_BROADCAST 0x20 +# define ASIO_OS_DEF_SO_DEBUG 0x1 +# define ASIO_OS_DEF_SO_DONTROUTE 0x10 +# define ASIO_OS_DEF_SO_KEEPALIVE 0x8 +# define ASIO_OS_DEF_SO_LINGER 0x80 +# define ASIO_OS_DEF_SO_OOBINLINE 0x100 +# define ASIO_OS_DEF_SO_SNDBUF 0x1001 +# define ASIO_OS_DEF_SO_RCVBUF 0x1002 +# define ASIO_OS_DEF_SO_SNDLOWAT 0x1003 +# define ASIO_OS_DEF_SO_RCVLOWAT 0x1004 +# define ASIO_OS_DEF_SO_REUSEADDR 0x4 +# define ASIO_OS_DEF_TCP_NODELAY 0x1 +# define ASIO_OS_DEF_IP_MULTICAST_IF 2 +# define ASIO_OS_DEF_IP_MULTICAST_TTL 3 +# define ASIO_OS_DEF_IP_MULTICAST_LOOP 4 +# define ASIO_OS_DEF_IP_ADD_MEMBERSHIP 5 +# define ASIO_OS_DEF_IP_DROP_MEMBERSHIP 6 +# define ASIO_OS_DEF_IP_TTL 7 +# define ASIO_OS_DEF_IPV6_UNICAST_HOPS 4 +# define ASIO_OS_DEF_IPV6_MULTICAST_IF 9 +# define ASIO_OS_DEF_IPV6_MULTICAST_HOPS 10 +# define ASIO_OS_DEF_IPV6_MULTICAST_LOOP 11 +# define ASIO_OS_DEF_IPV6_JOIN_GROUP 12 +# define ASIO_OS_DEF_IPV6_LEAVE_GROUP 13 +# define ASIO_OS_DEF_AI_CANONNAME 0x2 +# define ASIO_OS_DEF_AI_PASSIVE 0x1 +# define ASIO_OS_DEF_AI_NUMERICHOST 0x4 +# define ASIO_OS_DEF_AI_NUMERICSERV 0x8 +# define ASIO_OS_DEF_AI_V4MAPPED 0x800 +# define ASIO_OS_DEF_AI_ALL 0x100 +# define ASIO_OS_DEF_AI_ADDRCONFIG 0x400 +#elif defined(ASIO_WINDOWS) || defined(__CYGWIN__) +typedef SOCKET socket_type; +const SOCKET invalid_socket = INVALID_SOCKET; +const int socket_error_retval = SOCKET_ERROR; +const int max_addr_v4_str_len = 256; +const int max_addr_v6_str_len = 256; +typedef sockaddr socket_addr_type; +typedef in_addr in4_addr_type; +typedef ip_mreq in4_mreq_type; +typedef sockaddr_in sockaddr_in4_type; +# if defined(ASIO_HAS_OLD_WIN_SDK) +typedef in6_addr_emulation in6_addr_type; +typedef ipv6_mreq_emulation in6_mreq_type; +typedef sockaddr_in6_emulation sockaddr_in6_type; +typedef sockaddr_storage_emulation sockaddr_storage_type; +typedef addrinfo_emulation addrinfo_type; +# else +typedef in6_addr in6_addr_type; +typedef ipv6_mreq in6_mreq_type; +typedef sockaddr_in6 sockaddr_in6_type; +typedef sockaddr_storage sockaddr_storage_type; +typedef addrinfo addrinfo_type; +# endif +typedef ::linger linger_type; +typedef unsigned long ioctl_arg_type; +typedef u_long u_long_type; +typedef u_short u_short_type; +typedef int signed_size_type; +# define ASIO_OS_DEF(c) ASIO_OS_DEF_##c +# define ASIO_OS_DEF_AF_UNSPEC AF_UNSPEC +# define ASIO_OS_DEF_AF_INET AF_INET +# define ASIO_OS_DEF_AF_INET6 AF_INET6 +# define ASIO_OS_DEF_SOCK_STREAM SOCK_STREAM +# define ASIO_OS_DEF_SOCK_DGRAM SOCK_DGRAM +# define ASIO_OS_DEF_SOCK_RAW SOCK_RAW +# define ASIO_OS_DEF_SOCK_SEQPACKET SOCK_SEQPACKET +# define ASIO_OS_DEF_IPPROTO_IP IPPROTO_IP +# define ASIO_OS_DEF_IPPROTO_IPV6 IPPROTO_IPV6 +# define ASIO_OS_DEF_IPPROTO_TCP IPPROTO_TCP +# define ASIO_OS_DEF_IPPROTO_UDP IPPROTO_UDP +# define ASIO_OS_DEF_IPPROTO_ICMP IPPROTO_ICMP +# define ASIO_OS_DEF_IPPROTO_ICMPV6 IPPROTO_ICMPV6 +# define ASIO_OS_DEF_FIONBIO FIONBIO +# define ASIO_OS_DEF_FIONREAD FIONREAD +# define ASIO_OS_DEF_INADDR_ANY INADDR_ANY +# define ASIO_OS_DEF_MSG_OOB MSG_OOB +# define ASIO_OS_DEF_MSG_PEEK MSG_PEEK +# define ASIO_OS_DEF_MSG_DONTROUTE MSG_DONTROUTE +# define ASIO_OS_DEF_MSG_EOR 0 // Not supported on Windows. +# define ASIO_OS_DEF_SHUT_RD SD_RECEIVE +# define ASIO_OS_DEF_SHUT_WR SD_SEND +# define ASIO_OS_DEF_SHUT_RDWR SD_BOTH +# define ASIO_OS_DEF_SOMAXCONN SOMAXCONN +# define ASIO_OS_DEF_SOL_SOCKET SOL_SOCKET +# define ASIO_OS_DEF_SO_BROADCAST SO_BROADCAST +# define ASIO_OS_DEF_SO_DEBUG SO_DEBUG +# define ASIO_OS_DEF_SO_DONTROUTE SO_DONTROUTE +# define ASIO_OS_DEF_SO_KEEPALIVE SO_KEEPALIVE +# define ASIO_OS_DEF_SO_LINGER SO_LINGER +# define ASIO_OS_DEF_SO_OOBINLINE SO_OOBINLINE +# define ASIO_OS_DEF_SO_SNDBUF SO_SNDBUF +# define ASIO_OS_DEF_SO_RCVBUF SO_RCVBUF +# define ASIO_OS_DEF_SO_SNDLOWAT SO_SNDLOWAT +# define ASIO_OS_DEF_SO_RCVLOWAT SO_RCVLOWAT +# define ASIO_OS_DEF_SO_REUSEADDR SO_REUSEADDR +# define ASIO_OS_DEF_TCP_NODELAY TCP_NODELAY +# define ASIO_OS_DEF_IP_MULTICAST_IF IP_MULTICAST_IF +# define ASIO_OS_DEF_IP_MULTICAST_TTL IP_MULTICAST_TTL +# define ASIO_OS_DEF_IP_MULTICAST_LOOP IP_MULTICAST_LOOP +# define ASIO_OS_DEF_IP_ADD_MEMBERSHIP IP_ADD_MEMBERSHIP +# define ASIO_OS_DEF_IP_DROP_MEMBERSHIP IP_DROP_MEMBERSHIP +# define ASIO_OS_DEF_IP_TTL IP_TTL +# define ASIO_OS_DEF_IPV6_UNICAST_HOPS IPV6_UNICAST_HOPS +# define ASIO_OS_DEF_IPV6_MULTICAST_IF IPV6_MULTICAST_IF +# define ASIO_OS_DEF_IPV6_MULTICAST_HOPS IPV6_MULTICAST_HOPS +# define ASIO_OS_DEF_IPV6_MULTICAST_LOOP IPV6_MULTICAST_LOOP +# define ASIO_OS_DEF_IPV6_JOIN_GROUP IPV6_JOIN_GROUP +# define ASIO_OS_DEF_IPV6_LEAVE_GROUP IPV6_LEAVE_GROUP +# define ASIO_OS_DEF_AI_CANONNAME AI_CANONNAME +# define ASIO_OS_DEF_AI_PASSIVE AI_PASSIVE +# define ASIO_OS_DEF_AI_NUMERICHOST AI_NUMERICHOST +# if defined(AI_NUMERICSERV) +# define ASIO_OS_DEF_AI_NUMERICSERV AI_NUMERICSERV +# else +# define ASIO_OS_DEF_AI_NUMERICSERV 0 +# endif +# if defined(AI_V4MAPPED) +# define ASIO_OS_DEF_AI_V4MAPPED AI_V4MAPPED +# else +# define ASIO_OS_DEF_AI_V4MAPPED 0 +# endif +# if defined(AI_ALL) +# define ASIO_OS_DEF_AI_ALL AI_ALL +# else +# define ASIO_OS_DEF_AI_ALL 0 +# endif +# if defined(AI_ADDRCONFIG) +# define ASIO_OS_DEF_AI_ADDRCONFIG AI_ADDRCONFIG +# else +# define ASIO_OS_DEF_AI_ADDRCONFIG 0 +# endif +# if defined (_WIN32_WINNT) +const int max_iov_len = 64; +# else +const int max_iov_len = 16; +# endif +#else +typedef int socket_type; +const int invalid_socket = -1; +const int socket_error_retval = -1; +const int max_addr_v4_str_len = INET_ADDRSTRLEN; +#if defined(INET6_ADDRSTRLEN) +const int max_addr_v6_str_len = INET6_ADDRSTRLEN + 1 + IF_NAMESIZE; +#else // defined(INET6_ADDRSTRLEN) +const int max_addr_v6_str_len = 256; +#endif // defined(INET6_ADDRSTRLEN) +typedef sockaddr socket_addr_type; +typedef in_addr in4_addr_type; +# if defined(__hpux) +// HP-UX doesn't provide ip_mreq when _XOPEN_SOURCE_EXTENDED is defined. +struct in4_mreq_type +{ + struct in_addr imr_multiaddr; + struct in_addr imr_interface; +}; +# else +typedef ip_mreq in4_mreq_type; +# endif +typedef sockaddr_in sockaddr_in4_type; +typedef in6_addr in6_addr_type; +typedef ipv6_mreq in6_mreq_type; +typedef sockaddr_in6 sockaddr_in6_type; +typedef sockaddr_storage sockaddr_storage_type; +typedef sockaddr_un sockaddr_un_type; +typedef addrinfo addrinfo_type; +typedef ::linger linger_type; +typedef int ioctl_arg_type; +typedef uint32_t u_long_type; +typedef uint16_t u_short_type; +#if defined(ASIO_HAS_SSIZE_T) +typedef ssize_t signed_size_type; +#else // defined(ASIO_HAS_SSIZE_T) +typedef int signed_size_type; +#endif // defined(ASIO_HAS_SSIZE_T) +# define ASIO_OS_DEF(c) ASIO_OS_DEF_##c +# define ASIO_OS_DEF_AF_UNSPEC AF_UNSPEC +# define ASIO_OS_DEF_AF_INET AF_INET +# define ASIO_OS_DEF_AF_INET6 AF_INET6 +# define ASIO_OS_DEF_SOCK_STREAM SOCK_STREAM +# define ASIO_OS_DEF_SOCK_DGRAM SOCK_DGRAM +# define ASIO_OS_DEF_SOCK_RAW SOCK_RAW +# define ASIO_OS_DEF_SOCK_SEQPACKET SOCK_SEQPACKET +# define ASIO_OS_DEF_IPPROTO_IP IPPROTO_IP +# define ASIO_OS_DEF_IPPROTO_IPV6 IPPROTO_IPV6 +# define ASIO_OS_DEF_IPPROTO_TCP IPPROTO_TCP +# define ASIO_OS_DEF_IPPROTO_UDP IPPROTO_UDP +# define ASIO_OS_DEF_IPPROTO_ICMP IPPROTO_ICMP +# define ASIO_OS_DEF_IPPROTO_ICMPV6 IPPROTO_ICMPV6 +# define ASIO_OS_DEF_FIONBIO FIONBIO +# define ASIO_OS_DEF_FIONREAD FIONREAD +# define ASIO_OS_DEF_INADDR_ANY INADDR_ANY +# define ASIO_OS_DEF_MSG_OOB MSG_OOB +# define ASIO_OS_DEF_MSG_PEEK MSG_PEEK +# define ASIO_OS_DEF_MSG_DONTROUTE MSG_DONTROUTE +# define ASIO_OS_DEF_MSG_EOR MSG_EOR +# define ASIO_OS_DEF_SHUT_RD SHUT_RD +# define ASIO_OS_DEF_SHUT_WR SHUT_WR +# define ASIO_OS_DEF_SHUT_RDWR SHUT_RDWR +# define ASIO_OS_DEF_SOMAXCONN SOMAXCONN +# define ASIO_OS_DEF_SOL_SOCKET SOL_SOCKET +# define ASIO_OS_DEF_SO_BROADCAST SO_BROADCAST +# define ASIO_OS_DEF_SO_DEBUG SO_DEBUG +# define ASIO_OS_DEF_SO_DONTROUTE SO_DONTROUTE +# define ASIO_OS_DEF_SO_KEEPALIVE SO_KEEPALIVE +# define ASIO_OS_DEF_SO_LINGER SO_LINGER +# define ASIO_OS_DEF_SO_OOBINLINE SO_OOBINLINE +# define ASIO_OS_DEF_SO_SNDBUF SO_SNDBUF +# define ASIO_OS_DEF_SO_RCVBUF SO_RCVBUF +# define ASIO_OS_DEF_SO_SNDLOWAT SO_SNDLOWAT +# define ASIO_OS_DEF_SO_RCVLOWAT SO_RCVLOWAT +# define ASIO_OS_DEF_SO_REUSEADDR SO_REUSEADDR +# define ASIO_OS_DEF_TCP_NODELAY TCP_NODELAY +# define ASIO_OS_DEF_IP_MULTICAST_IF IP_MULTICAST_IF +# define ASIO_OS_DEF_IP_MULTICAST_TTL IP_MULTICAST_TTL +# define ASIO_OS_DEF_IP_MULTICAST_LOOP IP_MULTICAST_LOOP +# define ASIO_OS_DEF_IP_ADD_MEMBERSHIP IP_ADD_MEMBERSHIP +# define ASIO_OS_DEF_IP_DROP_MEMBERSHIP IP_DROP_MEMBERSHIP +# define ASIO_OS_DEF_IP_TTL IP_TTL +# define ASIO_OS_DEF_IPV6_UNICAST_HOPS IPV6_UNICAST_HOPS +# define ASIO_OS_DEF_IPV6_MULTICAST_IF IPV6_MULTICAST_IF +# define ASIO_OS_DEF_IPV6_MULTICAST_HOPS IPV6_MULTICAST_HOPS +# define ASIO_OS_DEF_IPV6_MULTICAST_LOOP IPV6_MULTICAST_LOOP +# define ASIO_OS_DEF_IPV6_JOIN_GROUP IPV6_JOIN_GROUP +# define ASIO_OS_DEF_IPV6_LEAVE_GROUP IPV6_LEAVE_GROUP +# define ASIO_OS_DEF_AI_CANONNAME AI_CANONNAME +# define ASIO_OS_DEF_AI_PASSIVE AI_PASSIVE +# define ASIO_OS_DEF_AI_NUMERICHOST AI_NUMERICHOST +# if defined(AI_NUMERICSERV) +# define ASIO_OS_DEF_AI_NUMERICSERV AI_NUMERICSERV +# else +# define ASIO_OS_DEF_AI_NUMERICSERV 0 +# endif +// Note: QNX Neutrino 6.3 defines AI_V4MAPPED, AI_ALL and AI_ADDRCONFIG but +// does not implement them. Therefore they are specifically excluded here. +# if defined(AI_V4MAPPED) && !defined(__QNXNTO__) +# define ASIO_OS_DEF_AI_V4MAPPED AI_V4MAPPED +# else +# define ASIO_OS_DEF_AI_V4MAPPED 0 +# endif +# if defined(AI_ALL) && !defined(__QNXNTO__) +# define ASIO_OS_DEF_AI_ALL AI_ALL +# else +# define ASIO_OS_DEF_AI_ALL 0 +# endif +# if defined(AI_ADDRCONFIG) && !defined(__QNXNTO__) +# define ASIO_OS_DEF_AI_ADDRCONFIG AI_ADDRCONFIG +# else +# define ASIO_OS_DEF_AI_ADDRCONFIG 0 +# endif +# if defined(IOV_MAX) +const int max_iov_len = IOV_MAX; +# else +// POSIX platforms are not required to define IOV_MAX. +const int max_iov_len = 16; +# endif +#endif +const int custom_socket_option_level = 0xA5100000; +const int enable_connection_aborted_option = 1; +const int always_fail_option = 2; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_SOCKET_TYPES_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/solaris_fenced_block.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/solaris_fenced_block.hpp new file mode 100644 index 000000000..20f833305 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/solaris_fenced_block.hpp @@ -0,0 +1,62 @@ +// +// detail/solaris_fenced_block.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SOLARIS_FENCED_BLOCK_HPP +#define ASIO_DETAIL_SOLARIS_FENCED_BLOCK_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(__sun) + +#include +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class solaris_fenced_block + : private noncopyable +{ +public: + enum half_t { half }; + enum full_t { full }; + + // Constructor for a half fenced block. + explicit solaris_fenced_block(half_t) + { + } + + // Constructor for a full fenced block. + explicit solaris_fenced_block(full_t) + { + membar_consumer(); + } + + // Destructor. + ~solaris_fenced_block() + { + membar_producer(); + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(__sun) + +#endif // ASIO_DETAIL_SOLARIS_FENCED_BLOCK_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/source_location.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/source_location.hpp new file mode 100644 index 000000000..7f831757b --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/source_location.hpp @@ -0,0 +1,45 @@ +// +// detail/source_location.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_SOURCE_LOCATION_HPP +#define ASIO_DETAIL_SOURCE_LOCATION_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_SOURCE_LOCATION) + +#if defined(ASIO_HAS_STD_SOURCE_LOCATION) +# include +#elif defined(ASIO_HAS_STD_EXPERIMENTAL_SOURCE_LOCATION) +# include +#else // defined(ASIO_HAS_STD_EXPERIMENTAL_SOURCE_LOCATION) +# error ASIO_HAS_SOURCE_LOCATION is set \ + but no source_location is available +#endif // defined(ASIO_HAS_STD_EXPERIMENTAL_SOURCE_LOCATION) + +namespace asio { +namespace detail { + +#if defined(ASIO_HAS_STD_SOURCE_LOCATION) +using std::source_location; +#elif defined(ASIO_HAS_STD_EXPERIMENTAL_SOURCE_LOCATION) +using std::experimental::source_location; +#endif // defined(ASIO_HAS_STD_EXPERIMENTAL_SOURCE_LOCATION) + +} // namespace detail +} // namespace asio + +#endif // defined(ASIO_HAS_SOURCE_LOCATION) + +#endif // ASIO_DETAIL_SOURCE_LOCATION_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/static_mutex.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/static_mutex.hpp new file mode 100644 index 000000000..2efd16702 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/static_mutex.hpp @@ -0,0 +1,52 @@ +// +// detail/static_mutex.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_STATIC_MUTEX_HPP +#define ASIO_DETAIL_STATIC_MUTEX_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_THREADS) +# include "asio/detail/null_static_mutex.hpp" +#elif defined(ASIO_WINDOWS) +# include "asio/detail/win_static_mutex.hpp" +#elif defined(ASIO_HAS_PTHREADS) +# include "asio/detail/posix_static_mutex.hpp" +#elif defined(ASIO_HAS_STD_MUTEX_AND_CONDVAR) +# include "asio/detail/std_static_mutex.hpp" +#else +# error Only Windows and POSIX are supported! +#endif + +namespace asio { +namespace detail { + +#if !defined(ASIO_HAS_THREADS) +typedef null_static_mutex static_mutex; +# define ASIO_STATIC_MUTEX_INIT ASIO_NULL_STATIC_MUTEX_INIT +#elif defined(ASIO_WINDOWS) +typedef win_static_mutex static_mutex; +# define ASIO_STATIC_MUTEX_INIT ASIO_WIN_STATIC_MUTEX_INIT +#elif defined(ASIO_HAS_PTHREADS) +typedef posix_static_mutex static_mutex; +# define ASIO_STATIC_MUTEX_INIT ASIO_POSIX_STATIC_MUTEX_INIT +#elif defined(ASIO_HAS_STD_MUTEX_AND_CONDVAR) +typedef std_static_mutex static_mutex; +# define ASIO_STATIC_MUTEX_INIT ASIO_STD_STATIC_MUTEX_INIT +#endif + +} // namespace detail +} // namespace asio + +#endif // ASIO_DETAIL_STATIC_MUTEX_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_event.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_event.hpp new file mode 100644 index 000000000..441d9b476 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_event.hpp @@ -0,0 +1,188 @@ +// +// detail/std_event.hpp +// ~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_STD_EVENT_HPP +#define ASIO_DETAIL_STD_EVENT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_STD_MUTEX_AND_CONDVAR) + +#include +#include +#include "asio/detail/assert.hpp" +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class std_event + : private noncopyable +{ +public: + // Constructor. + std_event() + : state_(0) + { + } + + // Destructor. + ~std_event() + { + } + + // Signal the event. (Retained for backward compatibility.) + template + void signal(Lock& lock) + { + this->signal_all(lock); + } + + // Signal all waiters. + template + void signal_all(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + (void)lock; + state_ |= 1; + cond_.notify_all(); + } + + // Unlock the mutex and signal one waiter. + template + void unlock_and_signal_one(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + state_ |= 1; + bool have_waiters = (state_ > 1); + lock.unlock(); + if (have_waiters) + cond_.notify_one(); + } + + // Unlock the mutex and signal one waiter who may destroy us. + template + void unlock_and_signal_one(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + state_ |= 1; + bool have_waiters = (state_ > 1); + if (have_waiters) + cond_.notify_one(); + lock.unlock(); + } + + // If there's a waiter, unlock the mutex and signal it. + template + bool maybe_unlock_and_signal_one(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + state_ |= 1; + if (state_ > 1) + { + lock.unlock(); + cond_.notify_one(); + return true; + } + return false; + } + + // Reset the event. + template + void clear(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + (void)lock; + state_ &= ~std::size_t(1); + } + + // Wait for the event to become signalled. + template + void wait(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + unique_lock_adapter u_lock(lock); + while ((state_ & 1) == 0) + { + waiter w(state_); + cond_.wait(u_lock.unique_lock_); + } + } + + // Timed wait for the event to become signalled. + template + bool wait_for_usec(Lock& lock, long usec) + { + ASIO_ASSERT(lock.locked()); + unique_lock_adapter u_lock(lock); + if ((state_ & 1) == 0) + { + waiter w(state_); + cond_.wait_for(u_lock.unique_lock_, std::chrono::microseconds(usec)); + } + return (state_ & 1) != 0; + } + +private: + // Helper class to temporarily adapt a scoped_lock into a unique_lock so that + // it can be passed to std::condition_variable::wait(). + struct unique_lock_adapter + { + template + explicit unique_lock_adapter(Lock& lock) + : unique_lock_(lock.mutex().mutex_, std::adopt_lock) + { + } + + ~unique_lock_adapter() + { + unique_lock_.release(); + } + + std::unique_lock unique_lock_; + }; + + // Helper to increment and decrement the state to track outstanding waiters. + class waiter + { + public: + explicit waiter(std::size_t& state) + : state_(state) + { + state_ += 2; + } + + ~waiter() + { + state_ -= 2; + } + + private: + std::size_t& state_; + }; + + std::condition_variable cond_; + std::size_t state_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_STD_MUTEX_AND_CONDVAR) + +#endif // ASIO_DETAIL_STD_EVENT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_fenced_block.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_fenced_block.hpp new file mode 100644 index 000000000..0d0b05461 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_fenced_block.hpp @@ -0,0 +1,62 @@ +// +// detail/std_fenced_block.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_STD_FENCED_BLOCK_HPP +#define ASIO_DETAIL_STD_FENCED_BLOCK_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_STD_ATOMIC) + +#include +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class std_fenced_block + : private noncopyable +{ +public: + enum half_t { half }; + enum full_t { full }; + + // Constructor for a half fenced block. + explicit std_fenced_block(half_t) + { + } + + // Constructor for a full fenced block. + explicit std_fenced_block(full_t) + { + std::atomic_thread_fence(std::memory_order_acquire); + } + + // Destructor. + ~std_fenced_block() + { + std::atomic_thread_fence(std::memory_order_release); + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_STD_ATOMIC) + +#endif // ASIO_DETAIL_STD_FENCED_BLOCK_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_global.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_global.hpp new file mode 100644 index 000000000..ac1d3ca79 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_global.hpp @@ -0,0 +1,70 @@ +// +// detail/std_global.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_STD_GLOBAL_HPP +#define ASIO_DETAIL_STD_GLOBAL_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_STD_CALL_ONCE) + +#include +#include + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +struct std_global_impl +{ + // Helper function to perform initialisation. + static void do_init() + { + instance_.ptr_ = new T; + } + + // Destructor automatically cleans up the global. + ~std_global_impl() + { + delete ptr_; + } + + static std::once_flag init_once_; + static std_global_impl instance_; + T* ptr_; +}; + +template +std::once_flag std_global_impl::init_once_; + +template +std_global_impl std_global_impl::instance_; + +template +T& std_global() +{ + std::call_once(std_global_impl::init_once_, &std_global_impl::do_init); + return *std_global_impl::instance_.ptr_; +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_STD_CALL_ONCE) + +#endif // ASIO_DETAIL_STD_GLOBAL_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_mutex.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_mutex.hpp new file mode 100644 index 000000000..0fdff3ddf --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_mutex.hpp @@ -0,0 +1,73 @@ +// +// detail/std_mutex.hpp +// ~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_STD_MUTEX_HPP +#define ASIO_DETAIL_STD_MUTEX_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_STD_MUTEX_AND_CONDVAR) + +#include +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/scoped_lock.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class std_event; + +class std_mutex + : private noncopyable +{ +public: + typedef asio::detail::scoped_lock scoped_lock; + + // Constructor. + std_mutex() + { + } + + // Destructor. + ~std_mutex() + { + } + + // Lock the mutex. + void lock() + { + mutex_.lock(); + } + + // Unlock the mutex. + void unlock() + { + mutex_.unlock(); + } + +private: + friend class std_event; + std::mutex mutex_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_STD_MUTEX_AND_CONDVAR) + +#endif // ASIO_DETAIL_STD_MUTEX_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_static_mutex.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_static_mutex.hpp new file mode 100644 index 000000000..abcb6e863 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_static_mutex.hpp @@ -0,0 +1,81 @@ +// +// detail/std_static_mutex.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_STD_STATIC_MUTEX_HPP +#define ASIO_DETAIL_STD_STATIC_MUTEX_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_STD_MUTEX_AND_CONDVAR) + +#include +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/scoped_lock.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class std_event; + +class std_static_mutex + : private noncopyable +{ +public: + typedef asio::detail::scoped_lock scoped_lock; + + // Constructor. + std_static_mutex(int) + { + } + + // Destructor. + ~std_static_mutex() + { + } + + // Initialise the mutex. + void init() + { + // Nothing to do. + } + + // Lock the mutex. + void lock() + { + mutex_.lock(); + } + + // Unlock the mutex. + void unlock() + { + mutex_.unlock(); + } + +private: + friend class std_event; + std::mutex mutex_; +}; + +#define ASIO_STD_STATIC_MUTEX_INIT 0 + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_STD_MUTEX_AND_CONDVAR) + +#endif // ASIO_DETAIL_STD_STATIC_MUTEX_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_thread.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_thread.hpp new file mode 100644 index 000000000..7d6386d7d --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/std_thread.hpp @@ -0,0 +1,71 @@ +// +// detail/std_thread.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_STD_THREAD_HPP +#define ASIO_DETAIL_STD_THREAD_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_STD_THREAD) + +#include +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class std_thread + : private noncopyable +{ +public: + // Constructor. + template + std_thread(Function f, unsigned int = 0) + : thread_(f) + { + } + + // Destructor. + ~std_thread() + { + join(); + } + + // Wait for the thread to exit. + void join() + { + if (thread_.joinable()) + thread_.join(); + } + + // Get number of CPUs. + static std::size_t hardware_concurrency() + { + return std::thread::hardware_concurrency(); + } + +private: + std::thread thread_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_STD_THREAD) + +#endif // ASIO_DETAIL_STD_THREAD_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/strand_executor_service.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/strand_executor_service.hpp new file mode 100644 index 000000000..1a984d84f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/strand_executor_service.hpp @@ -0,0 +1,166 @@ +// +// detail/strand_executor_service.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_STRAND_EXECUTOR_SERVICE_HPP +#define ASIO_DETAIL_STRAND_EXECUTOR_SERVICE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/atomic_count.hpp" +#include "asio/detail/executor_op.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/mutex.hpp" +#include "asio/detail/op_queue.hpp" +#include "asio/detail/scheduler_operation.hpp" +#include "asio/detail/scoped_ptr.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution.hpp" +#include "asio/execution_context.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Default service implementation for a strand. +class strand_executor_service + : public execution_context_service_base +{ +public: + // The underlying implementation of a strand. + class strand_impl + { + public: + ASIO_DECL ~strand_impl(); + + private: + friend class strand_executor_service; + + // Mutex to protect access to internal data. + mutex* mutex_; + + // Indicates whether the strand is currently "locked" by a handler. This + // means that there is a handler upcall in progress, or that the strand + // itself has been scheduled in order to invoke some pending handlers. + bool locked_; + + // Indicates that the strand has been shut down and will accept no further + // handlers. + bool shutdown_; + + // The handlers that are waiting on the strand but should not be run until + // after the next time the strand is scheduled. This queue must only be + // modified while the mutex is locked. + op_queue waiting_queue_; + + // The handlers that are ready to be run. Logically speaking, these are the + // handlers that hold the strand's lock. The ready queue is only modified + // from within the strand and so may be accessed without locking the mutex. + op_queue ready_queue_; + + // Pointers to adjacent handle implementations in linked list. + strand_impl* next_; + strand_impl* prev_; + + // The strand service in where the implementation is held. + strand_executor_service* service_; + }; + + typedef shared_ptr implementation_type; + + // Construct a new strand service for the specified context. + ASIO_DECL explicit strand_executor_service(execution_context& context); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void shutdown(); + + // Create a new strand_executor implementation. + ASIO_DECL implementation_type create_implementation(); + + // Request invocation of the given function. + template + static void execute(const implementation_type& impl, Executor& ex, + ASIO_MOVE_ARG(Function) function, + typename enable_if< + can_query >::value + >::type* = 0); + + // Request invocation of the given function. + template + static void execute(const implementation_type& impl, Executor& ex, + ASIO_MOVE_ARG(Function) function, + typename enable_if< + !can_query >::value + >::type* = 0); + + // Request invocation of the given function. + template + static void dispatch(const implementation_type& impl, Executor& ex, + ASIO_MOVE_ARG(Function) function, const Allocator& a); + + // Request invocation of the given function and return immediately. + template + static void post(const implementation_type& impl, Executor& ex, + ASIO_MOVE_ARG(Function) function, const Allocator& a); + + // Request invocation of the given function and return immediately. + template + static void defer(const implementation_type& impl, Executor& ex, + ASIO_MOVE_ARG(Function) function, const Allocator& a); + + // Determine whether the strand is running in the current thread. + ASIO_DECL static bool running_in_this_thread( + const implementation_type& impl); + +private: + friend class strand_impl; + template class allocator_binder; + template class invoker; + + // Adds a function to the strand. Returns true if it acquires the lock. + ASIO_DECL static bool enqueue(const implementation_type& impl, + scheduler_operation* op); + + // Helper function to request invocation of the given function. + template + static void do_execute(const implementation_type& impl, Executor& ex, + ASIO_MOVE_ARG(Function) function, const Allocator& a); + + // Mutex to protect access to the service-wide state. + mutex mutex_; + + // Number of mutexes shared between all strand objects. + enum { num_mutexes = 193 }; + + // Pool of mutexes. + scoped_ptr mutexes_[num_mutexes]; + + // Extra value used when hashing to prevent recycled memory locations from + // getting the same mutex. + std::size_t salt_; + + // The head of a linked list of all implementations. + strand_impl* impl_list_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/detail/impl/strand_executor_service.hpp" +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/strand_executor_service.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // ASIO_DETAIL_STRAND_EXECUTOR_SERVICE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/strand_service.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/strand_service.hpp new file mode 100644 index 000000000..5289ac80a --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/strand_service.hpp @@ -0,0 +1,145 @@ +// +// detail/strand_service.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_STRAND_SERVICE_HPP +#define ASIO_DETAIL_STRAND_SERVICE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/io_context.hpp" +#include "asio/detail/mutex.hpp" +#include "asio/detail/op_queue.hpp" +#include "asio/detail/operation.hpp" +#include "asio/detail/scoped_ptr.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Default service implementation for a strand. +class strand_service + : public asio::detail::service_base +{ +private: + // Helper class to re-post the strand on exit. + struct on_do_complete_exit; + + // Helper class to re-post the strand on exit. + struct on_dispatch_exit; + +public: + + // The underlying implementation of a strand. + class strand_impl + : public operation + { + public: + strand_impl(); + + private: + // Only this service will have access to the internal values. + friend class strand_service; + friend struct on_do_complete_exit; + friend struct on_dispatch_exit; + + // Mutex to protect access to internal data. + asio::detail::mutex mutex_; + + // Indicates whether the strand is currently "locked" by a handler. This + // means that there is a handler upcall in progress, or that the strand + // itself has been scheduled in order to invoke some pending handlers. + bool locked_; + + // The handlers that are waiting on the strand but should not be run until + // after the next time the strand is scheduled. This queue must only be + // modified while the mutex is locked. + op_queue waiting_queue_; + + // The handlers that are ready to be run. Logically speaking, these are the + // handlers that hold the strand's lock. The ready queue is only modified + // from within the strand and so may be accessed without locking the mutex. + op_queue ready_queue_; + }; + + typedef strand_impl* implementation_type; + + // Construct a new strand service for the specified io_context. + ASIO_DECL explicit strand_service(asio::io_context& io_context); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void shutdown(); + + // Construct a new strand implementation. + ASIO_DECL void construct(implementation_type& impl); + + // Request the io_context to invoke the given handler. + template + void dispatch(implementation_type& impl, Handler& handler); + + // Request the io_context to invoke the given handler and return immediately. + template + void post(implementation_type& impl, Handler& handler); + + // Determine whether the strand is running in the current thread. + ASIO_DECL bool running_in_this_thread( + const implementation_type& impl) const; + +private: + // Helper function to dispatch a handler. Returns true if the handler should + // be dispatched immediately. + ASIO_DECL bool do_dispatch(implementation_type& impl, operation* op); + + // Helper fiunction to post a handler. + ASIO_DECL void do_post(implementation_type& impl, + operation* op, bool is_continuation); + + ASIO_DECL static void do_complete(void* owner, + operation* base, const asio::error_code& ec, + std::size_t bytes_transferred); + + // The io_context used to obtain an I/O executor. + io_context& io_context_; + + // The io_context implementation used to post completions. + io_context_impl& io_context_impl_; + + // Mutex to protect access to the array of implementations. + asio::detail::mutex mutex_; + + // Number of implementations shared between all strand objects. +#if defined(ASIO_STRAND_IMPLEMENTATIONS) + enum { num_implementations = ASIO_STRAND_IMPLEMENTATIONS }; +#else // defined(ASIO_STRAND_IMPLEMENTATIONS) + enum { num_implementations = 193 }; +#endif // defined(ASIO_STRAND_IMPLEMENTATIONS) + + // Pool of implementations. + scoped_ptr implementations_[num_implementations]; + + // Extra value used when hashing to prevent recycled memory locations from + // getting the same strand implementation. + std::size_t salt_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/detail/impl/strand_service.hpp" +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/strand_service.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // ASIO_DETAIL_STRAND_SERVICE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/string_view.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/string_view.hpp new file mode 100644 index 000000000..29b894cef --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/string_view.hpp @@ -0,0 +1,47 @@ +// +// detail/string_view.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_STRING_VIEW_HPP +#define ASIO_DETAIL_STRING_VIEW_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_STRING_VIEW) + +#if defined(ASIO_HAS_STD_STRING_VIEW) +# include +#elif defined(ASIO_HAS_STD_EXPERIMENTAL_STRING_VIEW) +# include +#else // defined(ASIO_HAS_STD_EXPERIMENTAL_STRING_VIEW) +# error ASIO_HAS_STRING_VIEW is set but no string_view is available +#endif // defined(ASIO_HAS_STD_EXPERIMENTAL_STRING_VIEW) + +namespace asio { + +#if defined(ASIO_HAS_STD_STRING_VIEW) +using std::basic_string_view; +using std::string_view; +#elif defined(ASIO_HAS_STD_EXPERIMENTAL_STRING_VIEW) +using std::experimental::basic_string_view; +using std::experimental::string_view; +#endif // defined(ASIO_HAS_STD_EXPERIMENTAL_STRING_VIEW) + +} // namespace asio + +# define ASIO_STRING_VIEW_PARAM asio::string_view +#else // defined(ASIO_HAS_STRING_VIEW) +# define ASIO_STRING_VIEW_PARAM const std::string& +#endif // defined(ASIO_HAS_STRING_VIEW) + +#endif // ASIO_DETAIL_STRING_VIEW_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/thread.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/thread.hpp new file mode 100644 index 000000000..c8af81ce5 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/thread.hpp @@ -0,0 +1,60 @@ +// +// detail/thread.hpp +// ~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_THREAD_HPP +#define ASIO_DETAIL_THREAD_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_THREADS) +# include "asio/detail/null_thread.hpp" +#elif defined(ASIO_WINDOWS) +# if defined(UNDER_CE) +# include "asio/detail/wince_thread.hpp" +# elif defined(ASIO_WINDOWS_APP) +# include "asio/detail/winapp_thread.hpp" +# else +# include "asio/detail/win_thread.hpp" +# endif +#elif defined(ASIO_HAS_PTHREADS) +# include "asio/detail/posix_thread.hpp" +#elif defined(ASIO_HAS_STD_THREAD) +# include "asio/detail/std_thread.hpp" +#else +# error Only Windows, POSIX and std::thread are supported! +#endif + +namespace asio { +namespace detail { + +#if !defined(ASIO_HAS_THREADS) +typedef null_thread thread; +#elif defined(ASIO_WINDOWS) +# if defined(UNDER_CE) +typedef wince_thread thread; +# elif defined(ASIO_WINDOWS_APP) +typedef winapp_thread thread; +# else +typedef win_thread thread; +# endif +#elif defined(ASIO_HAS_PTHREADS) +typedef posix_thread thread; +#elif defined(ASIO_HAS_STD_THREAD) +typedef std_thread thread; +#endif + +} // namespace detail +} // namespace asio + +#endif // ASIO_DETAIL_THREAD_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/thread_context.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/thread_context.hpp new file mode 100644 index 000000000..289f31047 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/thread_context.hpp @@ -0,0 +1,42 @@ +// +// detail/thread_context.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_THREAD_CONTEXT_HPP +#define ASIO_DETAIL_THREAD_CONTEXT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include +#include +#include "asio/detail/call_stack.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class thread_info_base; + +// Base class for things that manage threads (scheduler, win_iocp_io_context). +class thread_context +{ +public: + // Per-thread call stack to track the state of each thread in the context. + typedef call_stack thread_call_stack; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_THREAD_CONTEXT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/thread_group.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/thread_group.hpp new file mode 100644 index 000000000..cd1a0d39d --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/thread_group.hpp @@ -0,0 +1,95 @@ +// +// detail/thread_group.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_THREAD_GROUP_HPP +#define ASIO_DETAIL_THREAD_GROUP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/scoped_ptr.hpp" +#include "asio/detail/thread.hpp" + +namespace asio { +namespace detail { + +class thread_group +{ +public: + // Constructor initialises an empty thread group. + thread_group() + : first_(0) + { + } + + // Destructor joins any remaining threads in the group. + ~thread_group() + { + join(); + } + + // Create a new thread in the group. + template + void create_thread(Function f) + { + first_ = new item(f, first_); + } + + // Create new threads in the group. + template + void create_threads(Function f, std::size_t num_threads) + { + for (std::size_t i = 0; i < num_threads; ++i) + create_thread(f); + } + + // Wait for all threads in the group to exit. + void join() + { + while (first_) + { + first_->thread_.join(); + item* tmp = first_; + first_ = first_->next_; + delete tmp; + } + } + + // Test whether the group is empty. + bool empty() const + { + return first_ == 0; + } + +private: + // Structure used to track a single thread in the group. + struct item + { + template + explicit item(Function f, item* next) + : thread_(f), + next_(next) + { + } + + asio::detail::thread thread_; + item* next_; + }; + + // The first thread in the group. + item* first_; +}; + +} // namespace detail +} // namespace asio + +#endif // ASIO_DETAIL_THREAD_GROUP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/thread_info_base.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/thread_info_base.hpp new file mode 100644 index 000000000..1799e542e --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/thread_info_base.hpp @@ -0,0 +1,189 @@ +// +// detail/thread_info_base.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_THREAD_INFO_BASE_HPP +#define ASIO_DETAIL_THREAD_INFO_BASE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include +#include "asio/detail/noncopyable.hpp" + +#if defined(ASIO_HAS_STD_EXCEPTION_PTR) \ + && !defined(ASIO_NO_EXCEPTIONS) +# include +# include "asio/multiple_exceptions.hpp" +#endif // defined(ASIO_HAS_STD_EXCEPTION_PTR) + // && !defined(ASIO_NO_EXCEPTIONS) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class thread_info_base + : private noncopyable +{ +public: + struct default_tag + { + enum { mem_index = 0 }; + }; + + struct awaitable_frame_tag + { + enum { mem_index = 1 }; + }; + + struct executor_function_tag + { + enum { mem_index = 2 }; + }; + + thread_info_base() +#if defined(ASIO_HAS_STD_EXCEPTION_PTR) \ + && !defined(ASIO_NO_EXCEPTIONS) + : has_pending_exception_(0) +#endif // defined(ASIO_HAS_STD_EXCEPTION_PTR) + // && !defined(ASIO_NO_EXCEPTIONS) + { + for (int i = 0; i < max_mem_index; ++i) + { + // The following test for non-null pointers is technically redundant, but + // it is significantly faster when using a tight io_context::poll() loop + // in latency sensitive applications. + if (reusable_memory_[i]) + reusable_memory_[i] = 0; + } + } + + ~thread_info_base() + { + for (int i = 0; i < max_mem_index; ++i) + ::operator delete(reusable_memory_[i]); + } + + static void* allocate(thread_info_base* this_thread, std::size_t size) + { + return allocate(default_tag(), this_thread, size); + } + + static void deallocate(thread_info_base* this_thread, + void* pointer, std::size_t size) + { + deallocate(default_tag(), this_thread, pointer, size); + } + + template + static void* allocate(Purpose, thread_info_base* this_thread, + std::size_t size) + { + std::size_t chunks = (size + chunk_size - 1) / chunk_size; + + if (this_thread && this_thread->reusable_memory_[Purpose::mem_index]) + { + void* const pointer = this_thread->reusable_memory_[Purpose::mem_index]; + this_thread->reusable_memory_[Purpose::mem_index] = 0; + + unsigned char* const mem = static_cast(pointer); + if (static_cast(mem[0]) >= chunks) + { + mem[size] = mem[0]; + return pointer; + } + + ::operator delete(pointer); + } + + void* const pointer = ::operator new(chunks * chunk_size + 1); + unsigned char* const mem = static_cast(pointer); + mem[size] = (chunks <= UCHAR_MAX) ? static_cast(chunks) : 0; + return pointer; + } + + template + static void deallocate(Purpose, thread_info_base* this_thread, + void* pointer, std::size_t size) + { + if (size <= chunk_size * UCHAR_MAX) + { + if (this_thread && this_thread->reusable_memory_[Purpose::mem_index] == 0) + { + unsigned char* const mem = static_cast(pointer); + mem[0] = mem[size]; + this_thread->reusable_memory_[Purpose::mem_index] = pointer; + return; + } + } + + ::operator delete(pointer); + } + + void capture_current_exception() + { +#if defined(ASIO_HAS_STD_EXCEPTION_PTR) \ + && !defined(ASIO_NO_EXCEPTIONS) + switch (has_pending_exception_) + { + case 0: + has_pending_exception_ = 1; + pending_exception_ = std::current_exception(); + break; + case 1: + has_pending_exception_ = 2; + pending_exception_ = + std::make_exception_ptr( + multiple_exceptions(pending_exception_)); + default: + break; + } +#endif // defined(ASIO_HAS_STD_EXCEPTION_PTR) + // && !defined(ASIO_NO_EXCEPTIONS) + } + + void rethrow_pending_exception() + { +#if defined(ASIO_HAS_STD_EXCEPTION_PTR) \ + && !defined(ASIO_NO_EXCEPTIONS) + if (has_pending_exception_ > 0) + { + has_pending_exception_ = 0; + std::exception_ptr ex( + ASIO_MOVE_CAST(std::exception_ptr)( + pending_exception_)); + std::rethrow_exception(ex); + } +#endif // defined(ASIO_HAS_STD_EXCEPTION_PTR) + // && !defined(ASIO_NO_EXCEPTIONS) + } + +private: + enum { chunk_size = 4 }; + enum { max_mem_index = 3 }; + void* reusable_memory_[max_mem_index]; + +#if defined(ASIO_HAS_STD_EXCEPTION_PTR) \ + && !defined(ASIO_NO_EXCEPTIONS) + int has_pending_exception_; + std::exception_ptr pending_exception_; +#endif // defined(ASIO_HAS_STD_EXCEPTION_PTR) + // && !defined(ASIO_NO_EXCEPTIONS) +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_THREAD_INFO_BASE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/throw_error.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/throw_error.hpp new file mode 100644 index 000000000..6ed311279 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/throw_error.hpp @@ -0,0 +1,53 @@ +// +// detail/throw_error.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_THROW_ERROR_HPP +#define ASIO_DETAIL_THROW_ERROR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/error_code.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +ASIO_DECL void do_throw_error(const asio::error_code& err); + +ASIO_DECL void do_throw_error(const asio::error_code& err, + const char* location); + +inline void throw_error(const asio::error_code& err) +{ + if (err) + do_throw_error(err); +} + +inline void throw_error(const asio::error_code& err, + const char* location) +{ + if (err) + do_throw_error(err, location); +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/throw_error.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // ASIO_DETAIL_THROW_ERROR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/throw_exception.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/throw_exception.hpp new file mode 100644 index 000000000..d6dcaab5a --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/throw_exception.hpp @@ -0,0 +1,51 @@ +// +// detail/throw_exception.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_THROW_EXCEPTION_HPP +#define ASIO_DETAIL_THROW_EXCEPTION_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_BOOST_THROW_EXCEPTION) +# include +#endif // defined(ASIO_BOOST_THROW_EXCEPTION) + +namespace asio { +namespace detail { + +#if defined(ASIO_HAS_BOOST_THROW_EXCEPTION) +using boost::throw_exception; +#else // defined(ASIO_HAS_BOOST_THROW_EXCEPTION) + +// Declare the throw_exception function for all targets. +template +void throw_exception(const Exception& e); + +// Only define the throw_exception function when exceptions are enabled. +// Otherwise, it is up to the application to provide a definition of this +// function. +# if !defined(ASIO_NO_EXCEPTIONS) +template +void throw_exception(const Exception& e) +{ + throw e; +} +# endif // !defined(ASIO_NO_EXCEPTIONS) + +#endif // defined(ASIO_HAS_BOOST_THROW_EXCEPTION) + +} // namespace detail +} // namespace asio + +#endif // ASIO_DETAIL_THROW_EXCEPTION_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_queue.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_queue.hpp new file mode 100644 index 000000000..32ebdc7cf --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_queue.hpp @@ -0,0 +1,360 @@ +// +// detail/timer_queue.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_TIMER_QUEUE_HPP +#define ASIO_DETAIL_TIMER_QUEUE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include +#include "asio/detail/cstdint.hpp" +#include "asio/detail/date_time_fwd.hpp" +#include "asio/detail/limits.hpp" +#include "asio/detail/op_queue.hpp" +#include "asio/detail/timer_queue_base.hpp" +#include "asio/detail/wait_op.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class timer_queue + : public timer_queue_base +{ +public: + // The time type. + typedef typename Time_Traits::time_type time_type; + + // The duration type. + typedef typename Time_Traits::duration_type duration_type; + + // Per-timer data. + class per_timer_data + { + public: + per_timer_data() : + heap_index_((std::numeric_limits::max)()), + next_(0), prev_(0) + { + } + + private: + friend class timer_queue; + + // The operations waiting on the timer. + op_queue op_queue_; + + // The index of the timer in the heap. + std::size_t heap_index_; + + // Pointers to adjacent timers in a linked list. + per_timer_data* next_; + per_timer_data* prev_; + }; + + // Constructor. + timer_queue() + : timers_(), + heap_() + { + } + + // Add a new timer to the queue. Returns true if this is the timer that is + // earliest in the queue, in which case the reactor's event demultiplexing + // function call may need to be interrupted and restarted. + bool enqueue_timer(const time_type& time, per_timer_data& timer, wait_op* op) + { + // Enqueue the timer object. + if (timer.prev_ == 0 && &timer != timers_) + { + if (this->is_positive_infinity(time)) + { + // No heap entry is required for timers that never expire. + timer.heap_index_ = (std::numeric_limits::max)(); + } + else + { + // Put the new timer at the correct position in the heap. This is done + // first since push_back() can throw due to allocation failure. + timer.heap_index_ = heap_.size(); + heap_entry entry = { time, &timer }; + heap_.push_back(entry); + up_heap(heap_.size() - 1); + } + + // Insert the new timer into the linked list of active timers. + timer.next_ = timers_; + timer.prev_ = 0; + if (timers_) + timers_->prev_ = &timer; + timers_ = &timer; + } + + // Enqueue the individual timer operation. + timer.op_queue_.push(op); + + // Interrupt reactor only if newly added timer is first to expire. + return timer.heap_index_ == 0 && timer.op_queue_.front() == op; + } + + // Whether there are no timers in the queue. + virtual bool empty() const + { + return timers_ == 0; + } + + // Get the time for the timer that is earliest in the queue. + virtual long wait_duration_msec(long max_duration) const + { + if (heap_.empty()) + return max_duration; + + return this->to_msec( + Time_Traits::to_posix_duration( + Time_Traits::subtract(heap_[0].time_, Time_Traits::now())), + max_duration); + } + + // Get the time for the timer that is earliest in the queue. + virtual long wait_duration_usec(long max_duration) const + { + if (heap_.empty()) + return max_duration; + + return this->to_usec( + Time_Traits::to_posix_duration( + Time_Traits::subtract(heap_[0].time_, Time_Traits::now())), + max_duration); + } + + // Dequeue all timers not later than the current time. + virtual void get_ready_timers(op_queue& ops) + { + if (!heap_.empty()) + { + const time_type now = Time_Traits::now(); + while (!heap_.empty() && !Time_Traits::less_than(now, heap_[0].time_)) + { + per_timer_data* timer = heap_[0].timer_; + ops.push(timer->op_queue_); + remove_timer(*timer); + } + } + } + + // Dequeue all timers. + virtual void get_all_timers(op_queue& ops) + { + while (timers_) + { + per_timer_data* timer = timers_; + timers_ = timers_->next_; + ops.push(timer->op_queue_); + timer->next_ = 0; + timer->prev_ = 0; + } + + heap_.clear(); + } + + // Cancel and dequeue operations for the given timer. + std::size_t cancel_timer(per_timer_data& timer, op_queue& ops, + std::size_t max_cancelled = (std::numeric_limits::max)()) + { + std::size_t num_cancelled = 0; + if (timer.prev_ != 0 || &timer == timers_) + { + while (wait_op* op = (num_cancelled != max_cancelled) + ? timer.op_queue_.front() : 0) + { + op->ec_ = asio::error::operation_aborted; + timer.op_queue_.pop(); + ops.push(op); + ++num_cancelled; + } + if (timer.op_queue_.empty()) + remove_timer(timer); + } + return num_cancelled; + } + + // Move operations from one timer to another, empty timer. + void move_timer(per_timer_data& target, per_timer_data& source) + { + target.op_queue_.push(source.op_queue_); + + target.heap_index_ = source.heap_index_; + source.heap_index_ = (std::numeric_limits::max)(); + + if (target.heap_index_ < heap_.size()) + heap_[target.heap_index_].timer_ = ⌖ + + if (timers_ == &source) + timers_ = ⌖ + if (source.prev_) + source.prev_->next_ = ⌖ + if (source.next_) + source.next_->prev_= ⌖ + target.next_ = source.next_; + target.prev_ = source.prev_; + source.next_ = 0; + source.prev_ = 0; + } + +private: + // Move the item at the given index up the heap to its correct position. + void up_heap(std::size_t index) + { + while (index > 0) + { + std::size_t parent = (index - 1) / 2; + if (!Time_Traits::less_than(heap_[index].time_, heap_[parent].time_)) + break; + swap_heap(index, parent); + index = parent; + } + } + + // Move the item at the given index down the heap to its correct position. + void down_heap(std::size_t index) + { + std::size_t child = index * 2 + 1; + while (child < heap_.size()) + { + std::size_t min_child = (child + 1 == heap_.size() + || Time_Traits::less_than( + heap_[child].time_, heap_[child + 1].time_)) + ? child : child + 1; + if (Time_Traits::less_than(heap_[index].time_, heap_[min_child].time_)) + break; + swap_heap(index, min_child); + index = min_child; + child = index * 2 + 1; + } + } + + // Swap two entries in the heap. + void swap_heap(std::size_t index1, std::size_t index2) + { + heap_entry tmp = heap_[index1]; + heap_[index1] = heap_[index2]; + heap_[index2] = tmp; + heap_[index1].timer_->heap_index_ = index1; + heap_[index2].timer_->heap_index_ = index2; + } + + // Remove a timer from the heap and list of timers. + void remove_timer(per_timer_data& timer) + { + // Remove the timer from the heap. + std::size_t index = timer.heap_index_; + if (!heap_.empty() && index < heap_.size()) + { + if (index == heap_.size() - 1) + { + timer.heap_index_ = (std::numeric_limits::max)(); + heap_.pop_back(); + } + else + { + swap_heap(index, heap_.size() - 1); + timer.heap_index_ = (std::numeric_limits::max)(); + heap_.pop_back(); + if (index > 0 && Time_Traits::less_than( + heap_[index].time_, heap_[(index - 1) / 2].time_)) + up_heap(index); + else + down_heap(index); + } + } + + // Remove the timer from the linked list of active timers. + if (timers_ == &timer) + timers_ = timer.next_; + if (timer.prev_) + timer.prev_->next_ = timer.next_; + if (timer.next_) + timer.next_->prev_= timer.prev_; + timer.next_ = 0; + timer.prev_ = 0; + } + + // Determine if the specified absolute time is positive infinity. + template + static bool is_positive_infinity(const Time_Type&) + { + return false; + } + + // Determine if the specified absolute time is positive infinity. + template + static bool is_positive_infinity( + const boost::date_time::base_time& time) + { + return time.is_pos_infinity(); + } + + // Helper function to convert a duration into milliseconds. + template + long to_msec(const Duration& d, long max_duration) const + { + if (d.ticks() <= 0) + return 0; + int64_t msec = d.total_milliseconds(); + if (msec == 0) + return 1; + if (msec > max_duration) + return max_duration; + return static_cast(msec); + } + + // Helper function to convert a duration into microseconds. + template + long to_usec(const Duration& d, long max_duration) const + { + if (d.ticks() <= 0) + return 0; + int64_t usec = d.total_microseconds(); + if (usec == 0) + return 1; + if (usec > max_duration) + return max_duration; + return static_cast(usec); + } + + // The head of a linked list of all active timers. + per_timer_data* timers_; + + struct heap_entry + { + // The time when the timer should fire. + time_type time_; + + // The associated timer with enqueued operations. + per_timer_data* timer_; + }; + + // The heap of timers, with the earliest timer at the front. + std::vector heap_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_TIMER_QUEUE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_queue_base.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_queue_base.hpp new file mode 100644 index 000000000..28e5b2769 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_queue_base.hpp @@ -0,0 +1,68 @@ +// +// detail/timer_queue_base.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_TIMER_QUEUE_BASE_HPP +#define ASIO_DETAIL_TIMER_QUEUE_BASE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/op_queue.hpp" +#include "asio/detail/operation.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class timer_queue_base + : private noncopyable +{ +public: + // Constructor. + timer_queue_base() : next_(0) {} + + // Destructor. + virtual ~timer_queue_base() {} + + // Whether there are no timers in the queue. + virtual bool empty() const = 0; + + // Get the time to wait until the next timer. + virtual long wait_duration_msec(long max_duration) const = 0; + + // Get the time to wait until the next timer. + virtual long wait_duration_usec(long max_duration) const = 0; + + // Dequeue all ready timers. + virtual void get_ready_timers(op_queue& ops) = 0; + + // Dequeue all timers. + virtual void get_all_timers(op_queue& ops) = 0; + +private: + friend class timer_queue_set; + + // Next timer queue in the set. + timer_queue_base* next_; +}; + +template +class timer_queue; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_TIMER_QUEUE_BASE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_queue_ptime.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_queue_ptime.hpp new file mode 100644 index 000000000..ec25861a2 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_queue_ptime.hpp @@ -0,0 +1,99 @@ +// +// detail/timer_queue_ptime.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_TIMER_QUEUE_PTIME_HPP +#define ASIO_DETAIL_TIMER_QUEUE_PTIME_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_BOOST_DATE_TIME) + +#include "asio/time_traits.hpp" +#include "asio/detail/timer_queue.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +struct forwarding_posix_time_traits : time_traits {}; + +// Template specialisation for the commonly used instantation. +template <> +class timer_queue > + : public timer_queue_base +{ +public: + // The time type. + typedef boost::posix_time::ptime time_type; + + // The duration type. + typedef boost::posix_time::time_duration duration_type; + + // Per-timer data. + typedef timer_queue::per_timer_data + per_timer_data; + + // Constructor. + ASIO_DECL timer_queue(); + + // Destructor. + ASIO_DECL virtual ~timer_queue(); + + // Add a new timer to the queue. Returns true if this is the timer that is + // earliest in the queue, in which case the reactor's event demultiplexing + // function call may need to be interrupted and restarted. + ASIO_DECL bool enqueue_timer(const time_type& time, + per_timer_data& timer, wait_op* op); + + // Whether there are no timers in the queue. + ASIO_DECL virtual bool empty() const; + + // Get the time for the timer that is earliest in the queue. + ASIO_DECL virtual long wait_duration_msec(long max_duration) const; + + // Get the time for the timer that is earliest in the queue. + ASIO_DECL virtual long wait_duration_usec(long max_duration) const; + + // Dequeue all timers not later than the current time. + ASIO_DECL virtual void get_ready_timers(op_queue& ops); + + // Dequeue all timers. + ASIO_DECL virtual void get_all_timers(op_queue& ops); + + // Cancel and dequeue operations for the given timer. + ASIO_DECL std::size_t cancel_timer( + per_timer_data& timer, op_queue& ops, + std::size_t max_cancelled = (std::numeric_limits::max)()); + + // Move operations from one timer to another, empty timer. + ASIO_DECL void move_timer(per_timer_data& target, + per_timer_data& source); + +private: + timer_queue impl_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/timer_queue_ptime.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_HAS_BOOST_DATE_TIME) + +#endif // ASIO_DETAIL_TIMER_QUEUE_PTIME_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_queue_set.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_queue_set.hpp new file mode 100644 index 000000000..9a3389f2a --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_queue_set.hpp @@ -0,0 +1,66 @@ +// +// detail/timer_queue_set.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_TIMER_QUEUE_SET_HPP +#define ASIO_DETAIL_TIMER_QUEUE_SET_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/timer_queue_base.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class timer_queue_set +{ +public: + // Constructor. + ASIO_DECL timer_queue_set(); + + // Add a timer queue to the set. + ASIO_DECL void insert(timer_queue_base* q); + + // Remove a timer queue from the set. + ASIO_DECL void erase(timer_queue_base* q); + + // Determine whether all queues are empty. + ASIO_DECL bool all_empty() const; + + // Get the wait duration in milliseconds. + ASIO_DECL long wait_duration_msec(long max_duration) const; + + // Get the wait duration in microseconds. + ASIO_DECL long wait_duration_usec(long max_duration) const; + + // Dequeue all ready timers. + ASIO_DECL void get_ready_timers(op_queue& ops); + + // Dequeue all timers. + ASIO_DECL void get_all_timers(op_queue& ops); + +private: + timer_queue_base* first_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/timer_queue_set.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // ASIO_DETAIL_TIMER_QUEUE_SET_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_scheduler.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_scheduler.hpp new file mode 100644 index 000000000..5f4ab9e6d --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_scheduler.hpp @@ -0,0 +1,35 @@ +// +// detail/timer_scheduler.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_TIMER_SCHEDULER_HPP +#define ASIO_DETAIL_TIMER_SCHEDULER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/timer_scheduler_fwd.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) +# include "asio/detail/winrt_timer_scheduler.hpp" +#elif defined(ASIO_HAS_IOCP) +# include "asio/detail/win_iocp_io_context.hpp" +#elif defined(ASIO_HAS_EPOLL) +# include "asio/detail/epoll_reactor.hpp" +#elif defined(ASIO_HAS_KQUEUE) +# include "asio/detail/kqueue_reactor.hpp" +#elif defined(ASIO_HAS_DEV_POLL) +# include "asio/detail/dev_poll_reactor.hpp" +#else +# include "asio/detail/select_reactor.hpp" +#endif + +#endif // ASIO_DETAIL_TIMER_SCHEDULER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_scheduler_fwd.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_scheduler_fwd.hpp new file mode 100644 index 000000000..ab4e0a783 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/timer_scheduler_fwd.hpp @@ -0,0 +1,40 @@ +// +// detail/timer_scheduler_fwd.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_TIMER_SCHEDULER_FWD_HPP +#define ASIO_DETAIL_TIMER_SCHEDULER_FWD_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +namespace asio { +namespace detail { + +#if defined(ASIO_WINDOWS_RUNTIME) +typedef class winrt_timer_scheduler timer_scheduler; +#elif defined(ASIO_HAS_IOCP) +typedef class win_iocp_io_context timer_scheduler; +#elif defined(ASIO_HAS_EPOLL) +typedef class epoll_reactor timer_scheduler; +#elif defined(ASIO_HAS_KQUEUE) +typedef class kqueue_reactor timer_scheduler; +#elif defined(ASIO_HAS_DEV_POLL) +typedef class dev_poll_reactor timer_scheduler; +#else +typedef class select_reactor timer_scheduler; +#endif + +} // namespace detail +} // namespace asio + +#endif // ASIO_DETAIL_TIMER_SCHEDULER_FWD_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/tss_ptr.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/tss_ptr.hpp new file mode 100644 index 000000000..9bc8ab198 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/tss_ptr.hpp @@ -0,0 +1,69 @@ +// +// detail/tss_ptr.hpp +// ~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_TSS_PTR_HPP +#define ASIO_DETAIL_TSS_PTR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_THREADS) +# include "asio/detail/null_tss_ptr.hpp" +#elif defined(ASIO_HAS_THREAD_KEYWORD_EXTENSION) +# include "asio/detail/keyword_tss_ptr.hpp" +#elif defined(ASIO_WINDOWS) +# include "asio/detail/win_tss_ptr.hpp" +#elif defined(ASIO_HAS_PTHREADS) +# include "asio/detail/posix_tss_ptr.hpp" +#else +# error Only Windows and POSIX are supported! +#endif + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class tss_ptr +#if !defined(ASIO_HAS_THREADS) + : public null_tss_ptr +#elif defined(ASIO_HAS_THREAD_KEYWORD_EXTENSION) + : public keyword_tss_ptr +#elif defined(ASIO_WINDOWS) + : public win_tss_ptr +#elif defined(ASIO_HAS_PTHREADS) + : public posix_tss_ptr +#endif +{ +public: + void operator=(T* value) + { +#if !defined(ASIO_HAS_THREADS) + null_tss_ptr::operator=(value); +#elif defined(ASIO_HAS_THREAD_KEYWORD_EXTENSION) + keyword_tss_ptr::operator=(value); +#elif defined(ASIO_WINDOWS) + win_tss_ptr::operator=(value); +#elif defined(ASIO_HAS_PTHREADS) + posix_tss_ptr::operator=(value); +#endif + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_TSS_PTR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/type_traits.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/type_traits.hpp new file mode 100644 index 000000000..92792aa78 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/type_traits.hpp @@ -0,0 +1,148 @@ +// +// detail/type_traits.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_TYPE_TRAITS_HPP +#define ASIO_DETAIL_TYPE_TRAITS_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_STD_TYPE_TRAITS) +# include +#else // defined(ASIO_HAS_STD_TYPE_TRAITS) +# include +# include +# include +# include +# include +# include +# include +# include +# include +# include +# include +# include +# include +# include +# include +# include +# include +# include +# include +# include +# include +# include +# include +# include +# include +#endif // defined(ASIO_HAS_STD_TYPE_TRAITS) + +namespace asio { + +#if defined(ASIO_HAS_STD_TYPE_TRAITS) +using std::add_const; +using std::add_lvalue_reference; +using std::aligned_storage; +using std::alignment_of; +using std::conditional; +using std::decay; +using std::declval; +using std::enable_if; +using std::false_type; +using std::integral_constant; +using std::is_base_of; +using std::is_class; +using std::is_const; +using std::is_constructible; +using std::is_convertible; +using std::is_copy_constructible; +using std::is_destructible; +using std::is_function; +using std::is_move_constructible; +using std::is_nothrow_copy_constructible; +using std::is_nothrow_destructible; +using std::is_object; +using std::is_reference; +using std::is_same; +using std::is_scalar; +using std::remove_cv; +template +struct remove_cvref : remove_cv::type> {}; +using std::remove_pointer; +using std::remove_reference; +#if defined(ASIO_HAS_STD_INVOKE_RESULT) +template struct result_of; +template +struct result_of : std::invoke_result {}; +#else // defined(ASIO_HAS_STD_INVOKE_RESULT) +using std::result_of; +#endif // defined(ASIO_HAS_STD_INVOKE_RESULT) +using std::true_type; +#else // defined(ASIO_HAS_STD_TYPE_TRAITS) +using boost::add_const; +using boost::add_lvalue_reference; +using boost::aligned_storage; +using boost::alignment_of; +template +struct enable_if : boost::enable_if_c {}; +using boost::conditional; +using boost::decay; +using boost::declval; +using boost::false_type; +using boost::integral_constant; +using boost::is_base_of; +using boost::is_class; +using boost::is_const; +using boost::is_constructible; +using boost::is_convertible; +using boost::is_copy_constructible; +using boost::is_destructible; +using boost::is_function; +#if defined(ASIO_HAS_MOVE) +template +struct is_move_constructible : false_type {}; +#else // defined(ASIO_HAS_MOVE) +template +struct is_move_constructible : is_copy_constructible {}; +#endif // defined(ASIO_HAS_MOVE) +template +struct is_nothrow_copy_constructible : boost::has_nothrow_copy {}; +template +struct is_nothrow_destructible : boost::has_nothrow_destructor {}; +using boost::is_object; +using boost::is_reference; +using boost::is_same; +using boost::is_scalar; +using boost::remove_cv; +template +struct remove_cvref : remove_cv::type> {}; +using boost::remove_pointer; +using boost::remove_reference; +using boost::result_of; +using boost::true_type; +#endif // defined(ASIO_HAS_STD_TYPE_TRAITS) + +template struct void_type { typedef void type; }; + +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template struct conjunction : true_type {}; +template struct conjunction : T {}; +template struct conjunction : + conditional, Head>::type {}; + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +} // namespace asio + +#endif // ASIO_DETAIL_TYPE_TRAITS_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/variadic_templates.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/variadic_templates.hpp new file mode 100644 index 000000000..3ef67235d --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/variadic_templates.hpp @@ -0,0 +1,294 @@ +// +// detail/variadic_templates.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_VARIADIC_TEMPLATES_HPP +#define ASIO_DETAIL_VARIADIC_TEMPLATES_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if !defined(ASIO_HAS_VARIADIC_TEMPLATES) + +# define ASIO_VARIADIC_TPARAMS(n) ASIO_VARIADIC_TPARAMS_##n + +# define ASIO_VARIADIC_TPARAMS_1 \ + typename T1 +# define ASIO_VARIADIC_TPARAMS_2 \ + typename T1, typename T2 +# define ASIO_VARIADIC_TPARAMS_3 \ + typename T1, typename T2, typename T3 +# define ASIO_VARIADIC_TPARAMS_4 \ + typename T1, typename T2, typename T3, typename T4 +# define ASIO_VARIADIC_TPARAMS_5 \ + typename T1, typename T2, typename T3, typename T4, typename T5 +# define ASIO_VARIADIC_TPARAMS_6 \ + typename T1, typename T2, typename T3, typename T4, typename T5, \ + typename T6 +# define ASIO_VARIADIC_TPARAMS_7 \ + typename T1, typename T2, typename T3, typename T4, typename T5, \ + typename T6, typename T7 +# define ASIO_VARIADIC_TPARAMS_8 \ + typename T1, typename T2, typename T3, typename T4, typename T5, \ + typename T6, typename T7, typename T8 + +# define ASIO_VARIADIC_TARGS(n) ASIO_VARIADIC_TARGS_##n + +# define ASIO_VARIADIC_TARGS_1 T1 +# define ASIO_VARIADIC_TARGS_2 T1, T2 +# define ASIO_VARIADIC_TARGS_3 T1, T2, T3 +# define ASIO_VARIADIC_TARGS_4 T1, T2, T3, T4 +# define ASIO_VARIADIC_TARGS_5 T1, T2, T3, T4, T5 +# define ASIO_VARIADIC_TARGS_6 T1, T2, T3, T4, T5, T6 +# define ASIO_VARIADIC_TARGS_7 T1, T2, T3, T4, T5, T6, T7 +# define ASIO_VARIADIC_TARGS_8 T1, T2, T3, T4, T5, T6, T7, T8 + +# define ASIO_VARIADIC_BYVAL_PARAMS(n) \ + ASIO_VARIADIC_BYVAL_PARAMS_##n + +# define ASIO_VARIADIC_BYVAL_PARAMS_1 T1 x1 +# define ASIO_VARIADIC_BYVAL_PARAMS_2 T1 x1, T2 x2 +# define ASIO_VARIADIC_BYVAL_PARAMS_3 T1 x1, T2 x2, T3 x3 +# define ASIO_VARIADIC_BYVAL_PARAMS_4 T1 x1, T2 x2, T3 x3, T4 x4 +# define ASIO_VARIADIC_BYVAL_PARAMS_5 T1 x1, T2 x2, T3 x3, T4 x4, T5 x5 +# define ASIO_VARIADIC_BYVAL_PARAMS_6 T1 x1, T2 x2, T3 x3, T4 x4, T5 x5, \ + T6 x6 +# define ASIO_VARIADIC_BYVAL_PARAMS_7 T1 x1, T2 x2, T3 x3, T4 x4, T5 x5, \ + T6 x6, T7 x7 +# define ASIO_VARIADIC_BYVAL_PARAMS_8 T1 x1, T2 x2, T3 x3, T4 x4, T5 x5, \ + T6 x6, T7 x7, T8 x8 + +# define ASIO_VARIADIC_BYVAL_ARGS(n) \ + ASIO_VARIADIC_BYVAL_ARGS_##n + +# define ASIO_VARIADIC_BYVAL_ARGS_1 x1 +# define ASIO_VARIADIC_BYVAL_ARGS_2 x1, x2 +# define ASIO_VARIADIC_BYVAL_ARGS_3 x1, x2, x3 +# define ASIO_VARIADIC_BYVAL_ARGS_4 x1, x2, x3, x4 +# define ASIO_VARIADIC_BYVAL_ARGS_5 x1, x2, x3, x4, x5 +# define ASIO_VARIADIC_BYVAL_ARGS_6 x1, x2, x3, x4, x5, x6 +# define ASIO_VARIADIC_BYVAL_ARGS_7 x1, x2, x3, x4, x5, x6, x7 +# define ASIO_VARIADIC_BYVAL_ARGS_8 x1, x2, x3, x4, x5, x6, x7, x8 + +# define ASIO_VARIADIC_CONSTREF_PARAMS(n) \ + ASIO_VARIADIC_CONSTREF_PARAMS_##n + +# define ASIO_VARIADIC_CONSTREF_PARAMS_1 \ + const T1& x1 +# define ASIO_VARIADIC_CONSTREF_PARAMS_2 \ + const T1& x1, const T2& x2 +# define ASIO_VARIADIC_CONSTREF_PARAMS_3 \ + const T1& x1, const T2& x2, const T3& x3 +# define ASIO_VARIADIC_CONSTREF_PARAMS_4 \ + const T1& x1, const T2& x2, const T3& x3, const T4& x4 +# define ASIO_VARIADIC_CONSTREF_PARAMS_5 \ + const T1& x1, const T2& x2, const T3& x3, const T4& x4, const T5& x5 +# define ASIO_VARIADIC_CONSTREF_PARAMS_6 \ + const T1& x1, const T2& x2, const T3& x3, const T4& x4, const T5& x5, \ + const T6& x6 +# define ASIO_VARIADIC_CONSTREF_PARAMS_7 \ + const T1& x1, const T2& x2, const T3& x3, const T4& x4, const T5& x5, \ + const T6& x6, const T7& x7 +# define ASIO_VARIADIC_CONSTREF_PARAMS_8 \ + const T1& x1, const T2& x2, const T3& x3, const T4& x4, const T5& x5, \ + const T6& x6, const T7& x7, const T8& x8 + +# define ASIO_VARIADIC_MOVE_PARAMS(n) \ + ASIO_VARIADIC_MOVE_PARAMS_##n + +# define ASIO_VARIADIC_MOVE_PARAMS_1 \ + ASIO_MOVE_ARG(T1) x1 +# define ASIO_VARIADIC_MOVE_PARAMS_2 \ + ASIO_MOVE_ARG(T1) x1, ASIO_MOVE_ARG(T2) x2 +# define ASIO_VARIADIC_MOVE_PARAMS_3 \ + ASIO_MOVE_ARG(T1) x1, ASIO_MOVE_ARG(T2) x2, \ + ASIO_MOVE_ARG(T3) x3 +# define ASIO_VARIADIC_MOVE_PARAMS_4 \ + ASIO_MOVE_ARG(T1) x1, ASIO_MOVE_ARG(T2) x2, \ + ASIO_MOVE_ARG(T3) x3, ASIO_MOVE_ARG(T4) x4 +# define ASIO_VARIADIC_MOVE_PARAMS_5 \ + ASIO_MOVE_ARG(T1) x1, ASIO_MOVE_ARG(T2) x2, \ + ASIO_MOVE_ARG(T3) x3, ASIO_MOVE_ARG(T4) x4, \ + ASIO_MOVE_ARG(T5) x5 +# define ASIO_VARIADIC_MOVE_PARAMS_6 \ + ASIO_MOVE_ARG(T1) x1, ASIO_MOVE_ARG(T2) x2, \ + ASIO_MOVE_ARG(T3) x3, ASIO_MOVE_ARG(T4) x4, \ + ASIO_MOVE_ARG(T5) x5, ASIO_MOVE_ARG(T6) x6 +# define ASIO_VARIADIC_MOVE_PARAMS_7 \ + ASIO_MOVE_ARG(T1) x1, ASIO_MOVE_ARG(T2) x2, \ + ASIO_MOVE_ARG(T3) x3, ASIO_MOVE_ARG(T4) x4, \ + ASIO_MOVE_ARG(T5) x5, ASIO_MOVE_ARG(T6) x6, \ + ASIO_MOVE_ARG(T7) x7 +# define ASIO_VARIADIC_MOVE_PARAMS_8 \ + ASIO_MOVE_ARG(T1) x1, ASIO_MOVE_ARG(T2) x2, \ + ASIO_MOVE_ARG(T3) x3, ASIO_MOVE_ARG(T4) x4, \ + ASIO_MOVE_ARG(T5) x5, ASIO_MOVE_ARG(T6) x6, \ + ASIO_MOVE_ARG(T7) x7, ASIO_MOVE_ARG(T8) x8 + +# define ASIO_VARIADIC_UNNAMED_MOVE_PARAMS(n) \ + ASIO_VARIADIC_UNNAMED_MOVE_PARAMS_##n + +# define ASIO_VARIADIC_UNNAMED_MOVE_PARAMS_1 \ + ASIO_MOVE_ARG(T1) +# define ASIO_VARIADIC_UNNAMED_MOVE_PARAMS_2 \ + ASIO_MOVE_ARG(T1), ASIO_MOVE_ARG(T2) +# define ASIO_VARIADIC_UNNAMED_MOVE_PARAMS_3 \ + ASIO_MOVE_ARG(T1), ASIO_MOVE_ARG(T2), \ + ASIO_MOVE_ARG(T3) +# define ASIO_VARIADIC_UNNAMED_MOVE_PARAMS_4 \ + ASIO_MOVE_ARG(T1), ASIO_MOVE_ARG(T2), \ + ASIO_MOVE_ARG(T3), ASIO_MOVE_ARG(T4) +# define ASIO_VARIADIC_UNNAMED_MOVE_PARAMS_5 \ + ASIO_MOVE_ARG(T1), ASIO_MOVE_ARG(T2), \ + ASIO_MOVE_ARG(T3), ASIO_MOVE_ARG(T4), \ + ASIO_MOVE_ARG(T5) +# define ASIO_VARIADIC_UNNAMED_MOVE_PARAMS_6 \ + ASIO_MOVE_ARG(T1), ASIO_MOVE_ARG(T2), \ + ASIO_MOVE_ARG(T3), ASIO_MOVE_ARG(T4), \ + ASIO_MOVE_ARG(T5), ASIO_MOVE_ARG(T6) +# define ASIO_VARIADIC_UNNAMED_MOVE_PARAMS_7 \ + ASIO_MOVE_ARG(T1), ASIO_MOVE_ARG(T2), \ + ASIO_MOVE_ARG(T3), ASIO_MOVE_ARG(T4), \ + ASIO_MOVE_ARG(T5), ASIO_MOVE_ARG(T6), \ + ASIO_MOVE_ARG(T7) +# define ASIO_VARIADIC_UNNAMED_MOVE_PARAMS_8 \ + ASIO_MOVE_ARG(T1), ASIO_MOVE_ARG(T2), \ + ASIO_MOVE_ARG(T3), ASIO_MOVE_ARG(T4), \ + ASIO_MOVE_ARG(T5), ASIO_MOVE_ARG(T6), \ + ASIO_MOVE_ARG(T7), ASIO_MOVE_ARG(T8) + +# define ASIO_VARIADIC_MOVE_ARGS(n) \ + ASIO_VARIADIC_MOVE_ARGS_##n + +# define ASIO_VARIADIC_MOVE_ARGS_1 \ + ASIO_MOVE_CAST(T1)(x1) +# define ASIO_VARIADIC_MOVE_ARGS_2 \ + ASIO_MOVE_CAST(T1)(x1), ASIO_MOVE_CAST(T2)(x2) +# define ASIO_VARIADIC_MOVE_ARGS_3 \ + ASIO_MOVE_CAST(T1)(x1), ASIO_MOVE_CAST(T2)(x2), \ + ASIO_MOVE_CAST(T3)(x3) +# define ASIO_VARIADIC_MOVE_ARGS_4 \ + ASIO_MOVE_CAST(T1)(x1), ASIO_MOVE_CAST(T2)(x2), \ + ASIO_MOVE_CAST(T3)(x3), ASIO_MOVE_CAST(T4)(x4) +# define ASIO_VARIADIC_MOVE_ARGS_5 \ + ASIO_MOVE_CAST(T1)(x1), ASIO_MOVE_CAST(T2)(x2), \ + ASIO_MOVE_CAST(T3)(x3), ASIO_MOVE_CAST(T4)(x4), \ + ASIO_MOVE_CAST(T5)(x5) +# define ASIO_VARIADIC_MOVE_ARGS_6 \ + ASIO_MOVE_CAST(T1)(x1), ASIO_MOVE_CAST(T2)(x2), \ + ASIO_MOVE_CAST(T3)(x3), ASIO_MOVE_CAST(T4)(x4), \ + ASIO_MOVE_CAST(T5)(x5), ASIO_MOVE_CAST(T6)(x6) +# define ASIO_VARIADIC_MOVE_ARGS_7 \ + ASIO_MOVE_CAST(T1)(x1), ASIO_MOVE_CAST(T2)(x2), \ + ASIO_MOVE_CAST(T3)(x3), ASIO_MOVE_CAST(T4)(x4), \ + ASIO_MOVE_CAST(T5)(x5), ASIO_MOVE_CAST(T6)(x6), \ + ASIO_MOVE_CAST(T7)(x7) +# define ASIO_VARIADIC_MOVE_ARGS_8 \ + ASIO_MOVE_CAST(T1)(x1), ASIO_MOVE_CAST(T2)(x2), \ + ASIO_MOVE_CAST(T3)(x3), ASIO_MOVE_CAST(T4)(x4), \ + ASIO_MOVE_CAST(T5)(x5), ASIO_MOVE_CAST(T6)(x6), \ + ASIO_MOVE_CAST(T7)(x7), ASIO_MOVE_CAST(T8)(x8) + +# define ASIO_VARIADIC_DECLVAL(n) \ + ASIO_VARIADIC_DECLVAL_##n + +# define ASIO_VARIADIC_DECLVAL_1 \ + declval() +# define ASIO_VARIADIC_DECLVAL_2 \ + declval(), declval() +# define ASIO_VARIADIC_DECLVAL_3 \ + declval(), declval(), declval() +# define ASIO_VARIADIC_DECLVAL_4 \ + declval(), declval(), declval(), declval() +# define ASIO_VARIADIC_DECLVAL_5 \ + declval(), declval(), declval(), declval(), \ + declval() +# define ASIO_VARIADIC_DECLVAL_6 \ + declval(), declval(), declval(), declval(), \ + declval(), declval() +# define ASIO_VARIADIC_DECLVAL_7 \ + declval(), declval(), declval(), declval(), \ + declval(), declval(), declval() +# define ASIO_VARIADIC_DECLVAL_8 \ + declval(), declval(), declval(), declval(), \ + declval(), declval(), declval(), declval() + +# define ASIO_VARIADIC_MOVE_DECLVAL(n) \ + ASIO_VARIADIC_MOVE_DECLVAL_##n + +# define ASIO_VARIADIC_MOVE_DECLVAL_1 \ + declval() +# define ASIO_VARIADIC_MOVE_DECLVAL_2 \ + declval(), declval() +# define ASIO_VARIADIC_MOVE_DECLVAL_3 \ + declval(), declval(), \ + declval() +# define ASIO_VARIADIC_MOVE_DECLVAL_4 \ + declval(), declval(), \ + declval(), declval() +# define ASIO_VARIADIC_MOVE_DECLVAL_5 \ + declval(), declval(), \ + declval(), declval(), \ + declval() +# define ASIO_VARIADIC_MOVE_DECLVAL_6 \ + declval(), declval(), \ + declval(), declval(), \ + declval(), declval() +# define ASIO_VARIADIC_MOVE_DECLVAL_7 \ + declval(), declval(), \ + declval(), declval(), \ + declval(), declval(), \ + declval() +# define ASIO_VARIADIC_MOVE_DECLVAL_8 \ + declval(), declval(), \ + declval(), declval(), \ + declval(), declval(), \ + declval(), declval() + +# define ASIO_VARIADIC_DECAY(n) \ + ASIO_VARIADIC_DECAY_##n + +# define ASIO_VARIADIC_DECAY_1 \ + typename decay::type +# define ASIO_VARIADIC_DECAY_2 \ + typename decay::type, typename decay::type +# define ASIO_VARIADIC_DECAY_3 \ + typename decay::type, typename decay::type, \ + typename decay::type +# define ASIO_VARIADIC_DECAY_4 \ + typename decay::type, typename decay::type, \ + typename decay::type, typename decay::type +# define ASIO_VARIADIC_DECAY_5 \ + typename decay::type, typename decay::type, \ + typename decay::type, typename decay::type, \ + typename decay::type +# define ASIO_VARIADIC_DECAY_6 \ + typename decay::type, typename decay::type, \ + typename decay::type, typename decay::type, \ + typename decay::type, typename decay::type +# define ASIO_VARIADIC_DECAY_7 \ + typename decay::type, typename decay::type, \ + typename decay::type, typename decay::type, \ + typename decay::type, typename decay::type, \ + typename decay::type +# define ASIO_VARIADIC_DECAY_8 \ + typename decay::type, typename decay::type, \ + typename decay::type, typename decay::type, \ + typename decay::type, typename decay::type, \ + typename decay::type, typename decay::type + +# define ASIO_VARIADIC_GENERATE(m) m(1) m(2) m(3) m(4) m(5) m(6) m(7) m(8) +# define ASIO_VARIADIC_GENERATE_5(m) m(1) m(2) m(3) m(4) m(5) + +#endif // !defined(ASIO_HAS_VARIADIC_TEMPLATES) + +#endif // ASIO_DETAIL_VARIADIC_TEMPLATES_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/wait_handler.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/wait_handler.hpp new file mode 100644 index 000000000..0c0981980 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/wait_handler.hpp @@ -0,0 +1,90 @@ +// +// detail/wait_handler.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WAIT_HANDLER_HPP +#define ASIO_DETAIL_WAIT_HANDLER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/wait_op.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class wait_handler : public wait_op +{ +public: + ASIO_DEFINE_HANDLER_PTR(wait_handler); + + wait_handler(Handler& h, const IoExecutor& io_ex) + : wait_op(&wait_handler::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(h)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& /*ec*/, + std::size_t /*bytes_transferred*/) + { + // Take ownership of the handler object. + wait_handler* h(static_cast(base)); + ptr p = { asio::detail::addressof(h->handler_), h, h }; + + ASIO_HANDLER_COMPLETION((*h)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + h->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder1 + handler(h->handler_, h->ec_); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_WAIT_HANDLER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/wait_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/wait_op.hpp new file mode 100644 index 000000000..9ea7c7b57 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/wait_op.hpp @@ -0,0 +1,45 @@ +// +// detail/wait_op.hpp +// ~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WAIT_OP_HPP +#define ASIO_DETAIL_WAIT_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/operation.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class wait_op + : public operation +{ +public: + // The error code to be passed to the completion handler. + asio::error_code ec_; + +protected: + wait_op(func_type func) + : operation(func) + { + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_WAIT_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_event.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_event.hpp new file mode 100644 index 000000000..721795b02 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_event.hpp @@ -0,0 +1,164 @@ +// +// detail/win_event.hpp +// ~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_EVENT_HPP +#define ASIO_DETAIL_WIN_EVENT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) + +#include +#include "asio/detail/assert.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/socket_types.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class win_event + : private noncopyable +{ +public: + // Constructor. + ASIO_DECL win_event(); + + // Destructor. + ASIO_DECL ~win_event(); + + // Signal the event. (Retained for backward compatibility.) + template + void signal(Lock& lock) + { + this->signal_all(lock); + } + + // Signal all waiters. + template + void signal_all(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + (void)lock; + state_ |= 1; + ::SetEvent(events_[0]); + } + + // Unlock the mutex and signal one waiter. + template + void unlock_and_signal_one(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + state_ |= 1; + bool have_waiters = (state_ > 1); + lock.unlock(); + if (have_waiters) + ::SetEvent(events_[1]); + } + + // Unlock the mutex and signal one waiter who may destroy us. + template + void unlock_and_signal_one_for_destruction(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + state_ |= 1; + bool have_waiters = (state_ > 1); + if (have_waiters) + ::SetEvent(events_[1]); + lock.unlock(); + } + + // If there's a waiter, unlock the mutex and signal it. + template + bool maybe_unlock_and_signal_one(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + state_ |= 1; + if (state_ > 1) + { + lock.unlock(); + ::SetEvent(events_[1]); + return true; + } + return false; + } + + // Reset the event. + template + void clear(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + (void)lock; + ::ResetEvent(events_[0]); + state_ &= ~std::size_t(1); + } + + // Wait for the event to become signalled. + template + void wait(Lock& lock) + { + ASIO_ASSERT(lock.locked()); + while ((state_ & 1) == 0) + { + state_ += 2; + lock.unlock(); +#if defined(ASIO_WINDOWS_APP) + ::WaitForMultipleObjectsEx(2, events_, false, INFINITE, false); +#else // defined(ASIO_WINDOWS_APP) + ::WaitForMultipleObjects(2, events_, false, INFINITE); +#endif // defined(ASIO_WINDOWS_APP) + lock.lock(); + state_ -= 2; + } + } + + // Timed wait for the event to become signalled. + template + bool wait_for_usec(Lock& lock, long usec) + { + ASIO_ASSERT(lock.locked()); + if ((state_ & 1) == 0) + { + state_ += 2; + lock.unlock(); + DWORD msec = usec > 0 ? (usec < 1000 ? 1 : usec / 1000) : 0; +#if defined(ASIO_WINDOWS_APP) + ::WaitForMultipleObjectsEx(2, events_, false, msec, false); +#else // defined(ASIO_WINDOWS_APP) + ::WaitForMultipleObjects(2, events_, false, msec); +#endif // defined(ASIO_WINDOWS_APP) + lock.lock(); + state_ -= 2; + } + return (state_ & 1) != 0; + } + +private: + HANDLE events_[2]; + std::size_t state_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/win_event.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_WINDOWS) + +#endif // ASIO_DETAIL_WIN_EVENT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_fd_set_adapter.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_fd_set_adapter.hpp new file mode 100644 index 000000000..f81018045 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_fd_set_adapter.hpp @@ -0,0 +1,149 @@ +// +// detail/win_fd_set_adapter.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_FD_SET_ADAPTER_HPP +#define ASIO_DETAIL_WIN_FD_SET_ADAPTER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/reactor_op_queue.hpp" +#include "asio/detail/socket_types.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Adapts the FD_SET type to meet the Descriptor_Set concept's requirements. +class win_fd_set_adapter : noncopyable +{ +public: + enum { default_fd_set_size = 1024 }; + + win_fd_set_adapter() + : capacity_(default_fd_set_size), + max_descriptor_(invalid_socket) + { + fd_set_ = static_cast(::operator new( + sizeof(win_fd_set) - sizeof(SOCKET) + + sizeof(SOCKET) * (capacity_))); + fd_set_->fd_count = 0; + } + + ~win_fd_set_adapter() + { + ::operator delete(fd_set_); + } + + void reset() + { + fd_set_->fd_count = 0; + max_descriptor_ = invalid_socket; + } + + bool set(socket_type descriptor) + { + for (u_int i = 0; i < fd_set_->fd_count; ++i) + if (fd_set_->fd_array[i] == descriptor) + return true; + + reserve(fd_set_->fd_count + 1); + fd_set_->fd_array[fd_set_->fd_count++] = descriptor; + return true; + } + + void set(reactor_op_queue& operations, op_queue&) + { + reactor_op_queue::iterator i = operations.begin(); + while (i != operations.end()) + { + reactor_op_queue::iterator op_iter = i++; + reserve(fd_set_->fd_count + 1); + fd_set_->fd_array[fd_set_->fd_count++] = op_iter->first; + } + } + + bool is_set(socket_type descriptor) const + { + return !!__WSAFDIsSet(descriptor, + const_cast(reinterpret_cast(fd_set_))); + } + + operator fd_set*() + { + return reinterpret_cast(fd_set_); + } + + socket_type max_descriptor() const + { + return max_descriptor_; + } + + void perform(reactor_op_queue& operations, + op_queue& ops) const + { + for (u_int i = 0; i < fd_set_->fd_count; ++i) + operations.perform_operations(fd_set_->fd_array[i], ops); + } + +private: + // This structure is defined to be compatible with the Windows API fd_set + // structure, but without being dependent on the value of FD_SETSIZE. We use + // the "struct hack" to allow the number of descriptors to be varied at + // runtime. + struct win_fd_set + { + u_int fd_count; + SOCKET fd_array[1]; + }; + + // Increase the fd_set_ capacity to at least the specified number of elements. + void reserve(u_int n) + { + if (n <= capacity_) + return; + + u_int new_capacity = capacity_ + capacity_ / 2; + if (new_capacity < n) + new_capacity = n; + + win_fd_set* new_fd_set = static_cast(::operator new( + sizeof(win_fd_set) - sizeof(SOCKET) + + sizeof(SOCKET) * (new_capacity))); + + new_fd_set->fd_count = fd_set_->fd_count; + for (u_int i = 0; i < fd_set_->fd_count; ++i) + new_fd_set->fd_array[i] = fd_set_->fd_array[i]; + + ::operator delete(fd_set_); + fd_set_ = new_fd_set; + capacity_ = new_capacity; + } + + win_fd_set* fd_set_; + u_int capacity_; + socket_type max_descriptor_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +#endif // ASIO_DETAIL_WIN_FD_SET_ADAPTER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_fenced_block.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_fenced_block.hpp new file mode 100644 index 000000000..17a078532 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_fenced_block.hpp @@ -0,0 +1,90 @@ +// +// detail/win_fenced_block.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_FENCED_BLOCK_HPP +#define ASIO_DETAIL_WIN_FENCED_BLOCK_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) && !defined(UNDER_CE) + +#include "asio/detail/socket_types.hpp" +#include "asio/detail/noncopyable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class win_fenced_block + : private noncopyable +{ +public: + enum half_t { half }; + enum full_t { full }; + + // Constructor for a half fenced block. + explicit win_fenced_block(half_t) + { + } + + // Constructor for a full fenced block. + explicit win_fenced_block(full_t) + { +#if defined(__BORLANDC__) + LONG barrier = 0; + ::InterlockedExchange(&barrier, 1); +#elif defined(ASIO_MSVC) \ + && ((ASIO_MSVC < 1400) || !defined(MemoryBarrier)) +# if defined(_M_IX86) +# pragma warning(push) +# pragma warning(disable:4793) + LONG barrier; + __asm { xchg barrier, eax } +# pragma warning(pop) +# endif // defined(_M_IX86) +#else + MemoryBarrier(); +#endif + } + + // Destructor. + ~win_fenced_block() + { +#if defined(__BORLANDC__) + LONG barrier = 0; + ::InterlockedExchange(&barrier, 1); +#elif defined(ASIO_MSVC) \ + && ((ASIO_MSVC < 1400) || !defined(MemoryBarrier)) +# if defined(_M_IX86) +# pragma warning(push) +# pragma warning(disable:4793) + LONG barrier; + __asm { xchg barrier, eax } +# pragma warning(pop) +# endif // defined(_M_IX86) +#else + MemoryBarrier(); +#endif + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS) && !defined(UNDER_CE) + +#endif // ASIO_DETAIL_WIN_FENCED_BLOCK_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_global.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_global.hpp new file mode 100644 index 000000000..feaa3a37a --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_global.hpp @@ -0,0 +1,71 @@ +// +// detail/win_global.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_GLOBAL_HPP +#define ASIO_DETAIL_WIN_GLOBAL_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/static_mutex.hpp" +#include "asio/detail/tss_ptr.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +struct win_global_impl +{ + // Destructor automatically cleans up the global. + ~win_global_impl() + { + delete ptr_; + } + + static win_global_impl instance_; + static static_mutex mutex_; + T* ptr_; + static tss_ptr tss_ptr_; +}; + +template +win_global_impl win_global_impl::instance_ = { 0 }; + +template +static_mutex win_global_impl::mutex_ = ASIO_STATIC_MUTEX_INIT; + +template +tss_ptr win_global_impl::tss_ptr_; + +template +T& win_global() +{ + if (static_cast(win_global_impl::tss_ptr_) == 0) + { + win_global_impl::mutex_.init(); + static_mutex::scoped_lock lock(win_global_impl::mutex_); + if (win_global_impl::instance_.ptr_ == 0) + win_global_impl::instance_.ptr_ = new T; + win_global_impl::tss_ptr_ = win_global_impl::instance_.ptr_; + } + + return *win_global_impl::tss_ptr_; +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_WIN_GLOBAL_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_handle_read_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_handle_read_op.hpp new file mode 100644 index 000000000..9135cba79 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_handle_read_op.hpp @@ -0,0 +1,117 @@ +// +// detail/win_iocp_handle_read_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// Copyright (c) 2008 Rep Invariant Systems, Inc. (info@repinvariant.com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_HANDLE_READ_OP_HPP +#define ASIO_DETAIL_WIN_IOCP_HANDLE_READ_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/operation.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class win_iocp_handle_read_op : public operation +{ +public: + ASIO_DEFINE_HANDLER_PTR(win_iocp_handle_read_op); + + win_iocp_handle_read_op(const MutableBufferSequence& buffers, + Handler& handler, const IoExecutor& io_ex) + : operation(&win_iocp_handle_read_op::do_complete), + buffers_(buffers), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& result_ec, + std::size_t bytes_transferred) + { + asio::error_code ec(result_ec); + + // Take ownership of the operation object. + win_iocp_handle_read_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + if (owner) + { + // Check whether buffers are still valid. + buffer_sequence_adapter::validate(o->buffers_); + } +#endif // defined(ASIO_ENABLE_BUFFER_DEBUGGING) + + // Map non-portable errors to their portable counterparts. + if (ec.value() == ERROR_HANDLE_EOF) + ec = asio::error::eof; + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, ec, bytes_transferred); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + MutableBufferSequence buffers_; + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_WIN_IOCP_HANDLE_READ_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_handle_service.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_handle_service.hpp new file mode 100644 index 000000000..d3311d102 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_handle_service.hpp @@ -0,0 +1,335 @@ +// +// detail/win_iocp_handle_service.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// Copyright (c) 2008 Rep Invariant Systems, Inc. (info@repinvariant.com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_HANDLE_SERVICE_HPP +#define ASIO_DETAIL_WIN_IOCP_HANDLE_SERVICE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/error.hpp" +#include "asio/execution_context.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/cstdint.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/mutex.hpp" +#include "asio/detail/operation.hpp" +#include "asio/detail/win_iocp_handle_read_op.hpp" +#include "asio/detail/win_iocp_handle_write_op.hpp" +#include "asio/detail/win_iocp_io_context.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class win_iocp_handle_service : + public execution_context_service_base +{ +public: + // The native type of a stream handle. + typedef HANDLE native_handle_type; + + // The implementation type of the stream handle. + class implementation_type + { + public: + // Default constructor. + implementation_type() + : handle_(INVALID_HANDLE_VALUE), + safe_cancellation_thread_id_(0), + next_(0), + prev_(0) + { + } + + private: + // Only this service will have access to the internal values. + friend class win_iocp_handle_service; + + // The native stream handle representation. + native_handle_type handle_; + + // The ID of the thread from which it is safe to cancel asynchronous + // operations. 0 means no asynchronous operations have been started yet. + // ~0 means asynchronous operations have been started from more than one + // thread, and cancellation is not supported for the handle. + DWORD safe_cancellation_thread_id_; + + // Pointers to adjacent handle implementations in linked list. + implementation_type* next_; + implementation_type* prev_; + }; + + ASIO_DECL win_iocp_handle_service(execution_context& context); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void shutdown(); + + // Construct a new handle implementation. + ASIO_DECL void construct(implementation_type& impl); + + // Move-construct a new handle implementation. + ASIO_DECL void move_construct(implementation_type& impl, + implementation_type& other_impl); + + // Move-assign from another handle implementation. + ASIO_DECL void move_assign(implementation_type& impl, + win_iocp_handle_service& other_service, + implementation_type& other_impl); + + // Destroy a handle implementation. + ASIO_DECL void destroy(implementation_type& impl); + + // Assign a native handle to a handle implementation. + ASIO_DECL asio::error_code assign(implementation_type& impl, + const native_handle_type& handle, asio::error_code& ec); + + // Determine whether the handle is open. + bool is_open(const implementation_type& impl) const + { + return impl.handle_ != INVALID_HANDLE_VALUE; + } + + // Destroy a handle implementation. + ASIO_DECL asio::error_code close(implementation_type& impl, + asio::error_code& ec); + + // Get the native handle representation. + native_handle_type native_handle(const implementation_type& impl) const + { + return impl.handle_; + } + + // Cancel all operations associated with the handle. + ASIO_DECL asio::error_code cancel(implementation_type& impl, + asio::error_code& ec); + + // Write the given data. Returns the number of bytes written. + template + size_t write_some(implementation_type& impl, + const ConstBufferSequence& buffers, asio::error_code& ec) + { + return write_some_at(impl, 0, buffers, ec); + } + + // Write the given data at the specified offset. Returns the number of bytes + // written. + template + size_t write_some_at(implementation_type& impl, uint64_t offset, + const ConstBufferSequence& buffers, asio::error_code& ec) + { + asio::const_buffer buffer = + buffer_sequence_adapter::first(buffers); + + return do_write(impl, offset, buffer, ec); + } + + // Start an asynchronous write. The data being written must be valid for the + // lifetime of the asynchronous operation. + template + void async_write_some(implementation_type& impl, + const ConstBufferSequence& buffers, + Handler& handler, const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_handle_write_op< + ConstBufferSequence, Handler, IoExecutor> op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(buffers, handler, io_ex); + + ASIO_HANDLER_CREATION((iocp_service_.context(), *p.p, "handle", &impl, + reinterpret_cast(impl.handle_), "async_write_some")); + + start_write_op(impl, 0, + buffer_sequence_adapter::first(buffers), p.p); + p.v = p.p = 0; + } + + // Start an asynchronous write at a specified offset. The data being written + // must be valid for the lifetime of the asynchronous operation. + template + void async_write_some_at(implementation_type& impl, + uint64_t offset, const ConstBufferSequence& buffers, + Handler& handler, const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_handle_write_op< + ConstBufferSequence, Handler, IoExecutor> op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(buffers, handler, io_ex); + + ASIO_HANDLER_CREATION((iocp_service_.context(), *p.p, "handle", &impl, + reinterpret_cast(impl.handle_), "async_write_some_at")); + + start_write_op(impl, offset, + buffer_sequence_adapter::first(buffers), p.p); + p.v = p.p = 0; + } + + // Read some data. Returns the number of bytes received. + template + size_t read_some(implementation_type& impl, + const MutableBufferSequence& buffers, asio::error_code& ec) + { + return read_some_at(impl, 0, buffers, ec); + } + + // Read some data at a specified offset. Returns the number of bytes received. + template + size_t read_some_at(implementation_type& impl, uint64_t offset, + const MutableBufferSequence& buffers, asio::error_code& ec) + { + asio::mutable_buffer buffer = + buffer_sequence_adapter::first(buffers); + + return do_read(impl, offset, buffer, ec); + } + + // Start an asynchronous read. The buffer for the data being received must be + // valid for the lifetime of the asynchronous operation. + template + void async_read_some(implementation_type& impl, + const MutableBufferSequence& buffers, + Handler& handler, const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_handle_read_op< + MutableBufferSequence, Handler, IoExecutor> op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(buffers, handler, io_ex); + + ASIO_HANDLER_CREATION((iocp_service_.context(), *p.p, "handle", &impl, + reinterpret_cast(impl.handle_), "async_read_some")); + + start_read_op(impl, 0, + buffer_sequence_adapter::first(buffers), p.p); + p.v = p.p = 0; + } + + // Start an asynchronous read at a specified offset. The buffer for the data + // being received must be valid for the lifetime of the asynchronous + // operation. + template + void async_read_some_at(implementation_type& impl, + uint64_t offset, const MutableBufferSequence& buffers, + Handler& handler, const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_handle_read_op< + MutableBufferSequence, Handler, IoExecutor> op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(buffers, handler, io_ex); + + ASIO_HANDLER_CREATION((iocp_service_.context(), *p.p, "handle", &impl, + reinterpret_cast(impl.handle_), "async_read_some_at")); + + start_read_op(impl, offset, + buffer_sequence_adapter::first(buffers), p.p); + p.v = p.p = 0; + } + +private: + // Prevent the use of the null_buffers type with this service. + size_t write_some(implementation_type& impl, + const null_buffers& buffers, asio::error_code& ec); + size_t write_some_at(implementation_type& impl, uint64_t offset, + const null_buffers& buffers, asio::error_code& ec); + template + void async_write_some(implementation_type& impl, + const null_buffers& buffers, Handler& handler, + const IoExecutor& io_ex); + template + void async_write_some_at(implementation_type& impl, uint64_t offset, + const null_buffers& buffers, Handler& handler, const IoExecutor& io_ex); + size_t read_some(implementation_type& impl, + const null_buffers& buffers, asio::error_code& ec); + size_t read_some_at(implementation_type& impl, uint64_t offset, + const null_buffers& buffers, asio::error_code& ec); + template + void async_read_some(implementation_type& impl, + const null_buffers& buffers, Handler& handler, + const IoExecutor& io_ex); + template + void async_read_some_at(implementation_type& impl, uint64_t offset, + const null_buffers& buffers, Handler& handler, const IoExecutor& io_ex); + + // Helper class for waiting for synchronous operations to complete. + class overlapped_wrapper; + + // Helper function to perform a synchronous write operation. + ASIO_DECL size_t do_write(implementation_type& impl, + uint64_t offset, const asio::const_buffer& buffer, + asio::error_code& ec); + + // Helper function to start a write operation. + ASIO_DECL void start_write_op(implementation_type& impl, + uint64_t offset, const asio::const_buffer& buffer, + operation* op); + + // Helper function to perform a synchronous write operation. + ASIO_DECL size_t do_read(implementation_type& impl, + uint64_t offset, const asio::mutable_buffer& buffer, + asio::error_code& ec); + + // Helper function to start a read operation. + ASIO_DECL void start_read_op(implementation_type& impl, + uint64_t offset, const asio::mutable_buffer& buffer, + operation* op); + + // Update the ID of the thread from which cancellation is safe. + ASIO_DECL void update_cancellation_thread_id(implementation_type& impl); + + // Helper function to close a handle when the associated object is being + // destroyed. + ASIO_DECL void close_for_destruction(implementation_type& impl); + + // The IOCP service used for running asynchronous operations and dispatching + // handlers. + win_iocp_io_context& iocp_service_; + + // Mutex to protect access to the linked list of implementations. + mutex mutex_; + + // The head of a linked list of all implementations. + implementation_type* impl_list_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/win_iocp_handle_service.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_WIN_IOCP_HANDLE_SERVICE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_handle_write_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_handle_write_op.hpp new file mode 100644 index 000000000..c03df6542 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_handle_write_op.hpp @@ -0,0 +1,110 @@ +// +// detail/win_iocp_handle_write_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// Copyright (c) 2008 Rep Invariant Systems, Inc. (info@repinvariant.com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_HANDLE_WRITE_OP_HPP +#define ASIO_DETAIL_WIN_IOCP_HANDLE_WRITE_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/operation.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class win_iocp_handle_write_op : public operation +{ +public: + ASIO_DEFINE_HANDLER_PTR(win_iocp_handle_write_op); + + win_iocp_handle_write_op(const ConstBufferSequence& buffers, + Handler& handler, const IoExecutor& io_ex) + : operation(&win_iocp_handle_write_op::do_complete), + buffers_(buffers), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& ec, std::size_t bytes_transferred) + { + // Take ownership of the operation object. + win_iocp_handle_write_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + if (owner) + { + // Check whether buffers are still valid. + buffer_sequence_adapter::validate(o->buffers_); + } +#endif // defined(ASIO_ENABLE_BUFFER_DEBUGGING) + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, ec, bytes_transferred); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + ConstBufferSequence buffers_; + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_WIN_IOCP_HANDLE_WRITE_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_io_context.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_io_context.hpp new file mode 100644 index 000000000..b1a27ee35 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_io_context.hpp @@ -0,0 +1,342 @@ +// +// detail/win_iocp_io_context.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_IO_CONTEXT_HPP +#define ASIO_DETAIL_WIN_IOCP_IO_CONTEXT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/detail/limits.hpp" +#include "asio/detail/mutex.hpp" +#include "asio/detail/op_queue.hpp" +#include "asio/detail/scoped_ptr.hpp" +#include "asio/detail/socket_types.hpp" +#include "asio/detail/thread.hpp" +#include "asio/detail/thread_context.hpp" +#include "asio/detail/timer_queue_base.hpp" +#include "asio/detail/timer_queue_set.hpp" +#include "asio/detail/wait_op.hpp" +#include "asio/detail/win_iocp_operation.hpp" +#include "asio/detail/win_iocp_thread_info.hpp" +#include "asio/execution_context.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class wait_op; + +class win_iocp_io_context + : public execution_context_service_base, + public thread_context +{ +public: + // Constructor. Specifies a concurrency hint that is passed through to the + // underlying I/O completion port. + ASIO_DECL win_iocp_io_context(asio::execution_context& ctx, + int concurrency_hint = -1, bool own_thread = true); + + // Destructor. + ASIO_DECL ~win_iocp_io_context(); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void shutdown(); + + // Initialise the task. Nothing to do here. + void init_task() + { + } + + // Register a handle with the IO completion port. + ASIO_DECL asio::error_code register_handle( + HANDLE handle, asio::error_code& ec); + + // Run the event loop until stopped or no more work. + ASIO_DECL size_t run(asio::error_code& ec); + + // Run until stopped or one operation is performed. + ASIO_DECL size_t run_one(asio::error_code& ec); + + // Run until timeout, interrupted, or one operation is performed. + ASIO_DECL size_t wait_one(long usec, asio::error_code& ec); + + // Poll for operations without blocking. + ASIO_DECL size_t poll(asio::error_code& ec); + + // Poll for one operation without blocking. + ASIO_DECL size_t poll_one(asio::error_code& ec); + + // Stop the event processing loop. + ASIO_DECL void stop(); + + // Determine whether the io_context is stopped. + bool stopped() const + { + return ::InterlockedExchangeAdd(&stopped_, 0) != 0; + } + + // Restart in preparation for a subsequent run invocation. + void restart() + { + ::InterlockedExchange(&stopped_, 0); + } + + // Notify that some work has started. + void work_started() + { + ::InterlockedIncrement(&outstanding_work_); + } + + // Notify that some work has finished. + void work_finished() + { + if (::InterlockedDecrement(&outstanding_work_) == 0) + stop(); + } + + // Return whether a handler can be dispatched immediately. + bool can_dispatch() + { + return thread_call_stack::contains(this) != 0; + } + + /// Capture the current exception so it can be rethrown from a run function. + ASIO_DECL void capture_current_exception(); + + // Request invocation of the given operation and return immediately. Assumes + // that work_started() has not yet been called for the operation. + void post_immediate_completion(win_iocp_operation* op, bool) + { + work_started(); + post_deferred_completion(op); + } + + // Request invocation of the given operation and return immediately. Assumes + // that work_started() was previously called for the operation. + ASIO_DECL void post_deferred_completion(win_iocp_operation* op); + + // Request invocation of the given operation and return immediately. Assumes + // that work_started() was previously called for the operations. + ASIO_DECL void post_deferred_completions( + op_queue& ops); + + // Request invocation of the given operation using the thread-private queue + // and return immediately. Assumes that work_started() has not yet been + // called for the operation. + void post_private_immediate_completion(win_iocp_operation* op) + { + post_immediate_completion(op, false); + } + + // Request invocation of the given operation using the thread-private queue + // and return immediately. Assumes that work_started() was previously called + // for the operation. + void post_private_deferred_completion(win_iocp_operation* op) + { + post_deferred_completion(op); + } + + // Enqueue the given operation following a failed attempt to dispatch the + // operation for immediate invocation. + void do_dispatch(operation* op) + { + post_immediate_completion(op, false); + } + + // Process unfinished operations as part of a shutdown operation. Assumes + // that work_started() was previously called for the operations. + ASIO_DECL void abandon_operations(op_queue& ops); + + // Called after starting an overlapped I/O operation that did not complete + // immediately. The caller must have already called work_started() prior to + // starting the operation. + ASIO_DECL void on_pending(win_iocp_operation* op); + + // Called after starting an overlapped I/O operation that completed + // immediately. The caller must have already called work_started() prior to + // starting the operation. + ASIO_DECL void on_completion(win_iocp_operation* op, + DWORD last_error = 0, DWORD bytes_transferred = 0); + + // Called after starting an overlapped I/O operation that completed + // immediately. The caller must have already called work_started() prior to + // starting the operation. + ASIO_DECL void on_completion(win_iocp_operation* op, + const asio::error_code& ec, DWORD bytes_transferred = 0); + + // Add a new timer queue to the service. + template + void add_timer_queue(timer_queue& timer_queue); + + // Remove a timer queue from the service. + template + void remove_timer_queue(timer_queue& timer_queue); + + // Schedule a new operation in the given timer queue to expire at the + // specified absolute time. + template + void schedule_timer(timer_queue& queue, + const typename Time_Traits::time_type& time, + typename timer_queue::per_timer_data& timer, wait_op* op); + + // Cancel the timer associated with the given token. Returns the number of + // handlers that have been posted or dispatched. + template + std::size_t cancel_timer(timer_queue& queue, + typename timer_queue::per_timer_data& timer, + std::size_t max_cancelled = (std::numeric_limits::max)()); + + // Move the timer operations associated with the given timer. + template + void move_timer(timer_queue& queue, + typename timer_queue::per_timer_data& to, + typename timer_queue::per_timer_data& from); + + // Get the concurrency hint that was used to initialise the io_context. + int concurrency_hint() const + { + return concurrency_hint_; + } + +private: +#if defined(WINVER) && (WINVER < 0x0500) + typedef DWORD dword_ptr_t; + typedef ULONG ulong_ptr_t; +#else // defined(WINVER) && (WINVER < 0x0500) + typedef DWORD_PTR dword_ptr_t; + typedef ULONG_PTR ulong_ptr_t; +#endif // defined(WINVER) && (WINVER < 0x0500) + + // Dequeues at most one operation from the I/O completion port, and then + // executes it. Returns the number of operations that were dequeued (i.e. + // either 0 or 1). + ASIO_DECL size_t do_one(DWORD msec, + win_iocp_thread_info& this_thread, asio::error_code& ec); + + // Helper to calculate the GetQueuedCompletionStatus timeout. + ASIO_DECL static DWORD get_gqcs_timeout(); + + // Helper function to add a new timer queue. + ASIO_DECL void do_add_timer_queue(timer_queue_base& queue); + + // Helper function to remove a timer queue. + ASIO_DECL void do_remove_timer_queue(timer_queue_base& queue); + + // Called to recalculate and update the timeout. + ASIO_DECL void update_timeout(); + + // Helper class to call work_finished() on block exit. + struct work_finished_on_block_exit; + + // Helper class for managing a HANDLE. + struct auto_handle + { + HANDLE handle; + auto_handle() : handle(0) {} + ~auto_handle() { if (handle) ::CloseHandle(handle); } + }; + + // The IO completion port used for queueing operations. + auto_handle iocp_; + + // The count of unfinished work. + long outstanding_work_; + + // Flag to indicate whether the event loop has been stopped. + mutable long stopped_; + + // Flag to indicate whether there is an in-flight stop event. Every event + // posted using PostQueuedCompletionStatus consumes non-paged pool, so to + // avoid exhausting this resouce we limit the number of outstanding events. + long stop_event_posted_; + + // Flag to indicate whether the service has been shut down. + long shutdown_; + + enum + { + // Timeout to use with GetQueuedCompletionStatus on older versions of + // Windows. Some versions of windows have a "bug" where a call to + // GetQueuedCompletionStatus can appear stuck even though there are events + // waiting on the queue. Using a timeout helps to work around the issue. + default_gqcs_timeout = 500, + + // Maximum waitable timer timeout, in milliseconds. + max_timeout_msec = 5 * 60 * 1000, + + // Maximum waitable timer timeout, in microseconds. + max_timeout_usec = max_timeout_msec * 1000, + + // Completion key value used to wake up a thread to dispatch timers or + // completed operations. + wake_for_dispatch = 1, + + // Completion key value to indicate that an operation has posted with the + // original last_error and bytes_transferred values stored in the fields of + // the OVERLAPPED structure. + overlapped_contains_result = 2 + }; + + // Timeout to use with GetQueuedCompletionStatus. + const DWORD gqcs_timeout_; + + // Helper class to run the scheduler in its own thread. + struct thread_function; + friend struct thread_function; + + // Function object for processing timeouts in a background thread. + struct timer_thread_function; + friend struct timer_thread_function; + + // Background thread used for processing timeouts. + scoped_ptr timer_thread_; + + // A waitable timer object used for waiting for timeouts. + auto_handle waitable_timer_; + + // Non-zero if timers or completed operations need to be dispatched. + long dispatch_required_; + + // Mutex for protecting access to the timer queues and completed operations. + mutex dispatch_mutex_; + + // The timer queues. + timer_queue_set timer_queues_; + + // The operations that are ready to dispatch. + op_queue completed_ops_; + + // The concurrency hint used to initialise the io_context. + const int concurrency_hint_; + + // The thread that is running the io_context. + scoped_ptr thread_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/detail/impl/win_iocp_io_context.hpp" +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/win_iocp_io_context.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_WIN_IOCP_IO_CONTEXT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_null_buffers_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_null_buffers_op.hpp new file mode 100644 index 000000000..091832fef --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_null_buffers_op.hpp @@ -0,0 +1,127 @@ +// +// detail/win_iocp_null_buffers_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_NULL_BUFFERS_OP_HPP +#define ASIO_DETAIL_WIN_IOCP_NULL_BUFFERS_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class win_iocp_null_buffers_op : public reactor_op +{ +public: + ASIO_DEFINE_HANDLER_PTR(win_iocp_null_buffers_op); + + win_iocp_null_buffers_op(socket_ops::weak_cancel_token_type cancel_token, + Handler& handler, const IoExecutor& io_ex) + : reactor_op(asio::error_code(), + &win_iocp_null_buffers_op::do_perform, + &win_iocp_null_buffers_op::do_complete), + cancel_token_(cancel_token), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static status do_perform(reactor_op*) + { + return done; + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& result_ec, + std::size_t bytes_transferred) + { + asio::error_code ec(result_ec); + + // Take ownership of the operation object. + win_iocp_null_buffers_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // The reactor may have stored a result in the operation object. + if (o->ec_) + ec = o->ec_; + + // Map non-portable errors to their portable counterparts. + if (ec.value() == ERROR_NETNAME_DELETED) + { + if (o->cancel_token_.expired()) + ec = asio::error::operation_aborted; + else + ec = asio::error::connection_reset; + } + else if (ec.value() == ERROR_PORT_UNREACHABLE) + { + ec = asio::error::connection_refused; + } + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, ec, bytes_transferred); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + socket_ops::weak_cancel_token_type cancel_token_; + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_WIN_IOCP_NULL_BUFFERS_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_operation.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_operation.hpp new file mode 100644 index 000000000..984f4f587 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_operation.hpp @@ -0,0 +1,96 @@ +// +// detail/win_iocp_operation.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_OPERATION_HPP +#define ASIO_DETAIL_WIN_IOCP_OPERATION_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/detail/handler_tracking.hpp" +#include "asio/detail/op_queue.hpp" +#include "asio/detail/socket_types.hpp" +#include "asio/error_code.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class win_iocp_io_context; + +// Base class for all operations. A function pointer is used instead of virtual +// functions to avoid the associated overhead. +class win_iocp_operation + : public OVERLAPPED + ASIO_ALSO_INHERIT_TRACKED_HANDLER +{ +public: + typedef win_iocp_operation operation_type; + + void complete(void* owner, const asio::error_code& ec, + std::size_t bytes_transferred) + { + func_(owner, this, ec, bytes_transferred); + } + + void destroy() + { + func_(0, this, asio::error_code(), 0); + } + +protected: + typedef void (*func_type)( + void*, win_iocp_operation*, + const asio::error_code&, std::size_t); + + win_iocp_operation(func_type func) + : next_(0), + func_(func) + { + reset(); + } + + // Prevents deletion through this type. + ~win_iocp_operation() + { + } + + void reset() + { + Internal = 0; + InternalHigh = 0; + Offset = 0; + OffsetHigh = 0; + hEvent = 0; + ready_ = 0; + } + +private: + friend class op_queue_access; + friend class win_iocp_io_context; + win_iocp_operation* next_; + func_type func_; + long ready_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_WIN_IOCP_OPERATION_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_overlapped_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_overlapped_op.hpp new file mode 100644 index 000000000..71bd73f17 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_overlapped_op.hpp @@ -0,0 +1,96 @@ +// +// detail/win_iocp_overlapped_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_OVERLAPPED_OP_HPP +#define ASIO_DETAIL_WIN_IOCP_OVERLAPPED_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/operation.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class win_iocp_overlapped_op : public operation +{ +public: + ASIO_DEFINE_HANDLER_PTR(win_iocp_overlapped_op); + + win_iocp_overlapped_op(Handler& handler, const IoExecutor& io_ex) + : operation(&win_iocp_overlapped_op::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& ec, std::size_t bytes_transferred) + { + // Take ownership of the operation object. + win_iocp_overlapped_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, ec, bytes_transferred); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_WIN_IOCP_OVERLAPPED_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_overlapped_ptr.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_overlapped_ptr.hpp new file mode 100644 index 000000000..985bbea7c --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_overlapped_ptr.hpp @@ -0,0 +1,171 @@ +// +// detail/win_iocp_overlapped_ptr.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_OVERLAPPED_PTR_HPP +#define ASIO_DETAIL_WIN_IOCP_OVERLAPPED_PTR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/io_context.hpp" +#include "asio/query.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/win_iocp_overlapped_op.hpp" +#include "asio/detail/win_iocp_io_context.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Wraps a handler to create an OVERLAPPED object for use with overlapped I/O. +class win_iocp_overlapped_ptr + : private noncopyable +{ +public: + // Construct an empty win_iocp_overlapped_ptr. + win_iocp_overlapped_ptr() + : ptr_(0), + iocp_service_(0) + { + } + + // Construct an win_iocp_overlapped_ptr to contain the specified handler. + template + explicit win_iocp_overlapped_ptr(const Executor& ex, + ASIO_MOVE_ARG(Handler) handler) + : ptr_(0), + iocp_service_(0) + { + this->reset(ex, ASIO_MOVE_CAST(Handler)(handler)); + } + + // Destructor automatically frees the OVERLAPPED object unless released. + ~win_iocp_overlapped_ptr() + { + reset(); + } + + // Reset to empty. + void reset() + { + if (ptr_) + { + ptr_->destroy(); + ptr_ = 0; + iocp_service_->work_finished(); + iocp_service_ = 0; + } + } + + // Reset to contain the specified handler, freeing any current OVERLAPPED + // object. + template + void reset(const Executor& ex, Handler handler) + { + win_iocp_io_context* iocp_service = this->get_iocp_service(ex); + + typedef win_iocp_overlapped_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(handler, ex); + + ASIO_HANDLER_CREATION((ex.context(), *p.p, + "iocp_service", iocp_service, 0, "overlapped")); + + iocp_service->work_started(); + reset(); + ptr_ = p.p; + p.v = p.p = 0; + iocp_service_ = iocp_service; + } + + // Get the contained OVERLAPPED object. + OVERLAPPED* get() + { + return ptr_; + } + + // Get the contained OVERLAPPED object. + const OVERLAPPED* get() const + { + return ptr_; + } + + // Release ownership of the OVERLAPPED object. + OVERLAPPED* release() + { + if (ptr_) + iocp_service_->on_pending(ptr_); + + OVERLAPPED* tmp = ptr_; + ptr_ = 0; + iocp_service_ = 0; + return tmp; + } + + // Post completion notification for overlapped operation. Releases ownership. + void complete(const asio::error_code& ec, + std::size_t bytes_transferred) + { + if (ptr_) + { + iocp_service_->on_completion(ptr_, ec, + static_cast(bytes_transferred)); + ptr_ = 0; + iocp_service_ = 0; + } + } + +private: + template + static win_iocp_io_context* get_iocp_service(const Executor& ex, + typename enable_if< + can_query::value + >::type* = 0) + { + return &use_service( + asio::query(ex, execution::context)); + } + + template + static win_iocp_io_context* get_iocp_service(const Executor& ex, + typename enable_if< + !can_query::value + >::type* = 0) + { + return &use_service(ex.context()); + } + + static win_iocp_io_context* get_iocp_service( + const io_context::executor_type& ex) + { + return &asio::query(ex, execution::context).impl_; + } + + win_iocp_operation* ptr_; + win_iocp_io_context* iocp_service_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_WIN_IOCP_OVERLAPPED_PTR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_serial_port_service.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_serial_port_service.hpp new file mode 100644 index 000000000..d4c2b4bc2 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_serial_port_service.hpp @@ -0,0 +1,232 @@ +// +// detail/win_iocp_serial_port_service.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// Copyright (c) 2008 Rep Invariant Systems, Inc. (info@repinvariant.com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_SERIAL_PORT_SERVICE_HPP +#define ASIO_DETAIL_WIN_IOCP_SERIAL_PORT_SERVICE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) && defined(ASIO_HAS_SERIAL_PORT) + +#include +#include "asio/error.hpp" +#include "asio/execution_context.hpp" +#include "asio/detail/win_iocp_handle_service.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Extend win_iocp_handle_service to provide serial port support. +class win_iocp_serial_port_service : + public execution_context_service_base +{ +public: + // The native type of a serial port. + typedef win_iocp_handle_service::native_handle_type native_handle_type; + + // The implementation type of the serial port. + typedef win_iocp_handle_service::implementation_type implementation_type; + + // Constructor. + ASIO_DECL win_iocp_serial_port_service(execution_context& context); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void shutdown(); + + // Construct a new serial port implementation. + void construct(implementation_type& impl) + { + handle_service_.construct(impl); + } + + // Move-construct a new serial port implementation. + void move_construct(implementation_type& impl, + implementation_type& other_impl) + { + handle_service_.move_construct(impl, other_impl); + } + + // Move-assign from another serial port implementation. + void move_assign(implementation_type& impl, + win_iocp_serial_port_service& other_service, + implementation_type& other_impl) + { + handle_service_.move_assign(impl, + other_service.handle_service_, other_impl); + } + + // Destroy a serial port implementation. + void destroy(implementation_type& impl) + { + handle_service_.destroy(impl); + } + + // Open the serial port using the specified device name. + ASIO_DECL asio::error_code open(implementation_type& impl, + const std::string& device, asio::error_code& ec); + + // Assign a native handle to a serial port implementation. + asio::error_code assign(implementation_type& impl, + const native_handle_type& handle, asio::error_code& ec) + { + return handle_service_.assign(impl, handle, ec); + } + + // Determine whether the serial port is open. + bool is_open(const implementation_type& impl) const + { + return handle_service_.is_open(impl); + } + + // Destroy a serial port implementation. + asio::error_code close(implementation_type& impl, + asio::error_code& ec) + { + return handle_service_.close(impl, ec); + } + + // Get the native serial port representation. + native_handle_type native_handle(implementation_type& impl) + { + return handle_service_.native_handle(impl); + } + + // Cancel all operations associated with the handle. + asio::error_code cancel(implementation_type& impl, + asio::error_code& ec) + { + return handle_service_.cancel(impl, ec); + } + + // Set an option on the serial port. + template + asio::error_code set_option(implementation_type& impl, + const SettableSerialPortOption& option, asio::error_code& ec) + { + return do_set_option(impl, + &win_iocp_serial_port_service::store_option, + &option, ec); + } + + // Get an option from the serial port. + template + asio::error_code get_option(const implementation_type& impl, + GettableSerialPortOption& option, asio::error_code& ec) const + { + return do_get_option(impl, + &win_iocp_serial_port_service::load_option, + &option, ec); + } + + // Send a break sequence to the serial port. + asio::error_code send_break(implementation_type&, + asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Write the given data. Returns the number of bytes sent. + template + size_t write_some(implementation_type& impl, + const ConstBufferSequence& buffers, asio::error_code& ec) + { + return handle_service_.write_some(impl, buffers, ec); + } + + // Start an asynchronous write. The data being written must be valid for the + // lifetime of the asynchronous operation. + template + void async_write_some(implementation_type& impl, + const ConstBufferSequence& buffers, + Handler& handler, const IoExecutor& io_ex) + { + handle_service_.async_write_some(impl, buffers, handler, io_ex); + } + + // Read some data. Returns the number of bytes received. + template + size_t read_some(implementation_type& impl, + const MutableBufferSequence& buffers, asio::error_code& ec) + { + return handle_service_.read_some(impl, buffers, ec); + } + + // Start an asynchronous read. The buffer for the data being received must be + // valid for the lifetime of the asynchronous operation. + template + void async_read_some(implementation_type& impl, + const MutableBufferSequence& buffers, + Handler& handler, const IoExecutor& io_ex) + { + handle_service_.async_read_some(impl, buffers, handler, io_ex); + } + +private: + // Function pointer type for storing a serial port option. + typedef asio::error_code (*store_function_type)( + const void*, ::DCB&, asio::error_code&); + + // Helper function template to store a serial port option. + template + static asio::error_code store_option(const void* option, + ::DCB& storage, asio::error_code& ec) + { + static_cast(option)->store(storage, ec); + return ec; + } + + // Helper function to set a serial port option. + ASIO_DECL asio::error_code do_set_option( + implementation_type& impl, store_function_type store, + const void* option, asio::error_code& ec); + + // Function pointer type for loading a serial port option. + typedef asio::error_code (*load_function_type)( + void*, const ::DCB&, asio::error_code&); + + // Helper function template to load a serial port option. + template + static asio::error_code load_option(void* option, + const ::DCB& storage, asio::error_code& ec) + { + static_cast(option)->load(storage, ec); + return ec; + } + + // Helper function to get a serial port option. + ASIO_DECL asio::error_code do_get_option( + const implementation_type& impl, load_function_type load, + void* option, asio::error_code& ec) const; + + // The implementation used for initiating asynchronous operations. + win_iocp_handle_service handle_service_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/win_iocp_serial_port_service.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_HAS_IOCP) && defined(ASIO_HAS_SERIAL_PORT) + +#endif // ASIO_DETAIL_WIN_IOCP_SERIAL_PORT_SERVICE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_accept_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_accept_op.hpp new file mode 100644 index 000000000..745125bf1 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_accept_op.hpp @@ -0,0 +1,312 @@ +// +// detail/win_iocp_socket_accept_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_SOCKET_ACCEPT_OP_HPP +#define ASIO_DETAIL_WIN_IOCP_SOCKET_ACCEPT_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/operation.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/detail/win_iocp_socket_service_base.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class win_iocp_socket_accept_op : public operation +{ +public: + ASIO_DEFINE_HANDLER_PTR(win_iocp_socket_accept_op); + + win_iocp_socket_accept_op(win_iocp_socket_service_base& socket_service, + socket_type socket, Socket& peer, const Protocol& protocol, + typename Protocol::endpoint* peer_endpoint, + bool enable_connection_aborted, Handler& handler, const IoExecutor& io_ex) + : operation(&win_iocp_socket_accept_op::do_complete), + socket_service_(socket_service), + socket_(socket), + peer_(peer), + protocol_(protocol), + peer_endpoint_(peer_endpoint), + enable_connection_aborted_(enable_connection_aborted), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + socket_holder& new_socket() + { + return new_socket_; + } + + void* output_buffer() + { + return output_buffer_; + } + + DWORD address_length() + { + return sizeof(sockaddr_storage_type) + 16; + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& result_ec, + std::size_t /*bytes_transferred*/) + { + asio::error_code ec(result_ec); + + // Take ownership of the operation object. + win_iocp_socket_accept_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + if (owner) + { + typename Protocol::endpoint peer_endpoint; + std::size_t addr_len = peer_endpoint.capacity(); + socket_ops::complete_iocp_accept(o->socket_, + o->output_buffer(), o->address_length(), + peer_endpoint.data(), &addr_len, + o->new_socket_.get(), ec); + + // Restart the accept operation if we got the connection_aborted error + // and the enable_connection_aborted socket option is not set. + if (ec == asio::error::connection_aborted + && !o->enable_connection_aborted_) + { + o->reset(); + o->socket_service_.restart_accept_op(o->socket_, + o->new_socket_, o->protocol_.family(), + o->protocol_.type(), o->protocol_.protocol(), + o->output_buffer(), o->address_length(), o); + p.v = p.p = 0; + return; + } + + // If the socket was successfully accepted, transfer ownership of the + // socket to the peer object. + if (!ec) + { + o->peer_.assign(o->protocol_, + typename Socket::native_handle_type( + o->new_socket_.get(), peer_endpoint), ec); + if (!ec) + o->new_socket_.release(); + } + + // Pass endpoint back to caller. + if (o->peer_endpoint_) + *o->peer_endpoint_ = peer_endpoint; + } + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder1 + handler(o->handler_, ec); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + win_iocp_socket_service_base& socket_service_; + socket_type socket_; + socket_holder new_socket_; + Socket& peer_; + Protocol protocol_; + typename Protocol::endpoint* peer_endpoint_; + unsigned char output_buffer_[(sizeof(sockaddr_storage_type) + 16) * 2]; + bool enable_connection_aborted_; + Handler handler_; + handler_work work_; +}; + +#if defined(ASIO_HAS_MOVE) + +template +class win_iocp_socket_move_accept_op : public operation +{ +public: + ASIO_DEFINE_HANDLER_PTR(win_iocp_socket_move_accept_op); + + win_iocp_socket_move_accept_op( + win_iocp_socket_service_base& socket_service, socket_type socket, + const Protocol& protocol, const PeerIoExecutor& peer_io_ex, + typename Protocol::endpoint* peer_endpoint, + bool enable_connection_aborted, Handler& handler, const IoExecutor& io_ex) + : operation(&win_iocp_socket_move_accept_op::do_complete), + socket_service_(socket_service), + socket_(socket), + peer_(peer_io_ex), + protocol_(protocol), + peer_endpoint_(peer_endpoint), + enable_connection_aborted_(enable_connection_aborted), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + socket_holder& new_socket() + { + return new_socket_; + } + + void* output_buffer() + { + return output_buffer_; + } + + DWORD address_length() + { + return sizeof(sockaddr_storage_type) + 16; + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& result_ec, + std::size_t /*bytes_transferred*/) + { + asio::error_code ec(result_ec); + + // Take ownership of the operation object. + win_iocp_socket_move_accept_op* o( + static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + if (owner) + { + typename Protocol::endpoint peer_endpoint; + std::size_t addr_len = peer_endpoint.capacity(); + socket_ops::complete_iocp_accept(o->socket_, + o->output_buffer(), o->address_length(), + peer_endpoint.data(), &addr_len, + o->new_socket_.get(), ec); + + // Restart the accept operation if we got the connection_aborted error + // and the enable_connection_aborted socket option is not set. + if (ec == asio::error::connection_aborted + && !o->enable_connection_aborted_) + { + o->reset(); + o->socket_service_.restart_accept_op(o->socket_, + o->new_socket_, o->protocol_.family(), + o->protocol_.type(), o->protocol_.protocol(), + o->output_buffer(), o->address_length(), o); + p.v = p.p = 0; + return; + } + + // If the socket was successfully accepted, transfer ownership of the + // socket to the peer object. + if (!ec) + { + o->peer_.assign(o->protocol_, + typename Protocol::socket::native_handle_type( + o->new_socket_.get(), peer_endpoint), ec); + if (!ec) + o->new_socket_.release(); + } + + // Pass endpoint back to caller. + if (o->peer_endpoint_) + *o->peer_endpoint_ = peer_endpoint; + } + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::move_binder2 + handler(0, ASIO_MOVE_CAST(Handler)(o->handler_), ec, + ASIO_MOVE_CAST(peer_socket_type)(o->peer_)); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, "...")); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + typedef typename Protocol::socket::template + rebind_executor::other peer_socket_type; + + win_iocp_socket_service_base& socket_service_; + socket_type socket_; + socket_holder new_socket_; + peer_socket_type peer_; + Protocol protocol_; + typename Protocol::endpoint* peer_endpoint_; + unsigned char output_buffer_[(sizeof(sockaddr_storage_type) + 16) * 2]; + bool enable_connection_aborted_; + Handler handler_; + handler_work work_; +}; + +#endif // defined(ASIO_HAS_MOVE) + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_WIN_IOCP_SOCKET_ACCEPT_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_connect_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_connect_op.hpp new file mode 100644 index 000000000..8971499b3 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_connect_op.hpp @@ -0,0 +1,135 @@ +// +// detail/win_iocp_socket_connect_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_SOCKET_CONNECT_OP_HPP +#define ASIO_DETAIL_WIN_IOCP_SOCKET_CONNECT_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class win_iocp_socket_connect_op_base : public reactor_op +{ +public: + win_iocp_socket_connect_op_base(socket_type socket, func_type complete_func) + : reactor_op(asio::error_code(), + &win_iocp_socket_connect_op_base::do_perform, complete_func), + socket_(socket), + connect_ex_(false) + { + } + + static status do_perform(reactor_op* base) + { + win_iocp_socket_connect_op_base* o( + static_cast(base)); + + return socket_ops::non_blocking_connect( + o->socket_, o->ec_) ? done : not_done; + } + + socket_type socket_; + bool connect_ex_; +}; + +template +class win_iocp_socket_connect_op : public win_iocp_socket_connect_op_base +{ +public: + ASIO_DEFINE_HANDLER_PTR(win_iocp_socket_connect_op); + + win_iocp_socket_connect_op(socket_type socket, + Handler& handler, const IoExecutor& io_ex) + : win_iocp_socket_connect_op_base(socket, + &win_iocp_socket_connect_op::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& result_ec, + std::size_t /*bytes_transferred*/) + { + asio::error_code ec(result_ec); + + // Take ownership of the operation object. + win_iocp_socket_connect_op* o( + static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + if (owner) + { + if (o->connect_ex_) + socket_ops::complete_iocp_connect(o->socket_, ec); + else + ec = o->ec_; + } + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder1 + handler(o->handler_, ec); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_WIN_IOCP_SOCKET_CONNECT_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_recv_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_recv_op.hpp new file mode 100644 index 000000000..4b57107d8 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_recv_op.hpp @@ -0,0 +1,124 @@ +// +// detail/win_iocp_socket_recv_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_SOCKET_RECV_OP_HPP +#define ASIO_DETAIL_WIN_IOCP_SOCKET_RECV_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/operation.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class win_iocp_socket_recv_op : public operation +{ +public: + ASIO_DEFINE_HANDLER_PTR(win_iocp_socket_recv_op); + + win_iocp_socket_recv_op(socket_ops::state_type state, + socket_ops::weak_cancel_token_type cancel_token, + const MutableBufferSequence& buffers, Handler& handler, + const IoExecutor& io_ex) + : operation(&win_iocp_socket_recv_op::do_complete), + state_(state), + cancel_token_(cancel_token), + buffers_(buffers), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& result_ec, + std::size_t bytes_transferred) + { + asio::error_code ec(result_ec); + + // Take ownership of the operation object. + win_iocp_socket_recv_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + // Check whether buffers are still valid. + if (owner) + { + buffer_sequence_adapter::validate(o->buffers_); + } +#endif // defined(ASIO_ENABLE_BUFFER_DEBUGGING) + + socket_ops::complete_iocp_recv(o->state_, o->cancel_token_, + buffer_sequence_adapter::all_empty(o->buffers_), + ec, bytes_transferred); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, ec, bytes_transferred); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + socket_ops::state_type state_; + socket_ops::weak_cancel_token_type cancel_token_; + MutableBufferSequence buffers_; + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_WIN_IOCP_SOCKET_RECV_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_recvfrom_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_recvfrom_op.hpp new file mode 100644 index 000000000..b8f6abd0c --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_recvfrom_op.hpp @@ -0,0 +1,133 @@ +// +// detail/win_iocp_socket_recvfrom_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_SOCKET_RECVFROM_OP_HPP +#define ASIO_DETAIL_WIN_IOCP_SOCKET_RECVFROM_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/operation.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class win_iocp_socket_recvfrom_op : public operation +{ +public: + ASIO_DEFINE_HANDLER_PTR(win_iocp_socket_recvfrom_op); + + win_iocp_socket_recvfrom_op(Endpoint& endpoint, + socket_ops::weak_cancel_token_type cancel_token, + const MutableBufferSequence& buffers, Handler& handler, + const IoExecutor& io_ex) + : operation(&win_iocp_socket_recvfrom_op::do_complete), + endpoint_(endpoint), + endpoint_size_(static_cast(endpoint.capacity())), + cancel_token_(cancel_token), + buffers_(buffers), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + int& endpoint_size() + { + return endpoint_size_; + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& result_ec, + std::size_t bytes_transferred) + { + asio::error_code ec(result_ec); + + // Take ownership of the operation object. + win_iocp_socket_recvfrom_op* o( + static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + // Check whether buffers are still valid. + if (owner) + { + buffer_sequence_adapter::validate(o->buffers_); + } +#endif // defined(ASIO_ENABLE_BUFFER_DEBUGGING) + + socket_ops::complete_iocp_recvfrom(o->cancel_token_, ec); + + // Record the size of the endpoint returned by the operation. + o->endpoint_.resize(o->endpoint_size_); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, ec, bytes_transferred); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Endpoint& endpoint_; + int endpoint_size_; + socket_ops::weak_cancel_token_type cancel_token_; + MutableBufferSequence buffers_; + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_WIN_IOCP_SOCKET_RECVFROM_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_recvmsg_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_recvmsg_op.hpp new file mode 100644 index 000000000..79f178962 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_recvmsg_op.hpp @@ -0,0 +1,125 @@ +// +// detail/win_iocp_socket_recvmsg_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_SOCKET_RECVMSG_OP_HPP +#define ASIO_DETAIL_WIN_IOCP_SOCKET_RECVMSG_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/operation.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/error.hpp" +#include "asio/socket_base.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class win_iocp_socket_recvmsg_op : public operation +{ +public: + ASIO_DEFINE_HANDLER_PTR(win_iocp_socket_recvmsg_op); + + win_iocp_socket_recvmsg_op( + socket_ops::weak_cancel_token_type cancel_token, + const MutableBufferSequence& buffers, + socket_base::message_flags& out_flags, + Handler& handler, const IoExecutor& io_ex) + : operation(&win_iocp_socket_recvmsg_op::do_complete), + cancel_token_(cancel_token), + buffers_(buffers), + out_flags_(out_flags), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& result_ec, + std::size_t bytes_transferred) + { + asio::error_code ec(result_ec); + + // Take ownership of the operation object. + win_iocp_socket_recvmsg_op* o( + static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + // Check whether buffers are still valid. + if (owner) + { + buffer_sequence_adapter::validate(o->buffers_); + } +#endif // defined(ASIO_ENABLE_BUFFER_DEBUGGING) + + socket_ops::complete_iocp_recvmsg(o->cancel_token_, ec); + o->out_flags_ = 0; + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, ec, bytes_transferred); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + socket_ops::weak_cancel_token_type cancel_token_; + MutableBufferSequence buffers_; + socket_base::message_flags& out_flags_; + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_WIN_IOCP_SOCKET_RECVMSG_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_send_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_send_op.hpp new file mode 100644 index 000000000..15a463219 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_send_op.hpp @@ -0,0 +1,118 @@ +// +// detail/win_iocp_socket_send_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_SOCKET_SEND_OP_HPP +#define ASIO_DETAIL_WIN_IOCP_SOCKET_SEND_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/operation.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class win_iocp_socket_send_op : public operation +{ +public: + ASIO_DEFINE_HANDLER_PTR(win_iocp_socket_send_op); + + win_iocp_socket_send_op(socket_ops::weak_cancel_token_type cancel_token, + const ConstBufferSequence& buffers, Handler& handler, + const IoExecutor& io_ex) + : operation(&win_iocp_socket_send_op::do_complete), + cancel_token_(cancel_token), + buffers_(buffers), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& result_ec, + std::size_t bytes_transferred) + { + asio::error_code ec(result_ec); + + // Take ownership of the operation object. + win_iocp_socket_send_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + // Check whether buffers are still valid. + if (owner) + { + buffer_sequence_adapter::validate(o->buffers_); + } +#endif // defined(ASIO_ENABLE_BUFFER_DEBUGGING) + + socket_ops::complete_iocp_send(o->cancel_token_, ec); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, ec, bytes_transferred); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + socket_ops::weak_cancel_token_type cancel_token_; + ConstBufferSequence buffers_; + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_WIN_IOCP_SOCKET_SEND_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_service.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_service.hpp new file mode 100644 index 000000000..53dc16322 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_service.hpp @@ -0,0 +1,581 @@ +// +// detail/win_iocp_socket_service.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_SOCKET_SERVICE_HPP +#define ASIO_DETAIL_WIN_IOCP_SOCKET_SERVICE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include +#include "asio/error.hpp" +#include "asio/execution_context.hpp" +#include "asio/socket_base.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/mutex.hpp" +#include "asio/detail/operation.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/select_reactor.hpp" +#include "asio/detail/socket_holder.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/detail/socket_types.hpp" +#include "asio/detail/win_iocp_io_context.hpp" +#include "asio/detail/win_iocp_null_buffers_op.hpp" +#include "asio/detail/win_iocp_socket_accept_op.hpp" +#include "asio/detail/win_iocp_socket_connect_op.hpp" +#include "asio/detail/win_iocp_socket_recvfrom_op.hpp" +#include "asio/detail/win_iocp_socket_send_op.hpp" +#include "asio/detail/win_iocp_socket_service_base.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class win_iocp_socket_service : + public execution_context_service_base >, + public win_iocp_socket_service_base +{ +public: + // The protocol type. + typedef Protocol protocol_type; + + // The endpoint type. + typedef typename Protocol::endpoint endpoint_type; + + // The native type of a socket. + class native_handle_type + { + public: + native_handle_type(socket_type s) + : socket_(s), + have_remote_endpoint_(false) + { + } + + native_handle_type(socket_type s, const endpoint_type& ep) + : socket_(s), + have_remote_endpoint_(true), + remote_endpoint_(ep) + { + } + + void operator=(socket_type s) + { + socket_ = s; + have_remote_endpoint_ = false; + remote_endpoint_ = endpoint_type(); + } + + operator socket_type() const + { + return socket_; + } + + bool have_remote_endpoint() const + { + return have_remote_endpoint_; + } + + endpoint_type remote_endpoint() const + { + return remote_endpoint_; + } + + private: + socket_type socket_; + bool have_remote_endpoint_; + endpoint_type remote_endpoint_; + }; + + // The implementation type of the socket. + struct implementation_type : + win_iocp_socket_service_base::base_implementation_type + { + // Default constructor. + implementation_type() + : protocol_(endpoint_type().protocol()), + have_remote_endpoint_(false), + remote_endpoint_() + { + } + + // The protocol associated with the socket. + protocol_type protocol_; + + // Whether we have a cached remote endpoint. + bool have_remote_endpoint_; + + // A cached remote endpoint. + endpoint_type remote_endpoint_; + }; + + // Constructor. + win_iocp_socket_service(execution_context& context) + : execution_context_service_base< + win_iocp_socket_service >(context), + win_iocp_socket_service_base(context) + { + } + + // Destroy all user-defined handler objects owned by the service. + void shutdown() + { + this->base_shutdown(); + } + + // Move-construct a new socket implementation. + void move_construct(implementation_type& impl, + implementation_type& other_impl) ASIO_NOEXCEPT + { + this->base_move_construct(impl, other_impl); + + impl.protocol_ = other_impl.protocol_; + other_impl.protocol_ = endpoint_type().protocol(); + + impl.have_remote_endpoint_ = other_impl.have_remote_endpoint_; + other_impl.have_remote_endpoint_ = false; + + impl.remote_endpoint_ = other_impl.remote_endpoint_; + other_impl.remote_endpoint_ = endpoint_type(); + } + + // Move-assign from another socket implementation. + void move_assign(implementation_type& impl, + win_iocp_socket_service_base& other_service, + implementation_type& other_impl) + { + this->base_move_assign(impl, other_service, other_impl); + + impl.protocol_ = other_impl.protocol_; + other_impl.protocol_ = endpoint_type().protocol(); + + impl.have_remote_endpoint_ = other_impl.have_remote_endpoint_; + other_impl.have_remote_endpoint_ = false; + + impl.remote_endpoint_ = other_impl.remote_endpoint_; + other_impl.remote_endpoint_ = endpoint_type(); + } + + // Move-construct a new socket implementation from another protocol type. + template + void converting_move_construct(implementation_type& impl, + win_iocp_socket_service&, + typename win_iocp_socket_service< + Protocol1>::implementation_type& other_impl) + { + this->base_move_construct(impl, other_impl); + + impl.protocol_ = protocol_type(other_impl.protocol_); + other_impl.protocol_ = typename Protocol1::endpoint().protocol(); + + impl.have_remote_endpoint_ = other_impl.have_remote_endpoint_; + other_impl.have_remote_endpoint_ = false; + + impl.remote_endpoint_ = other_impl.remote_endpoint_; + other_impl.remote_endpoint_ = typename Protocol1::endpoint(); + } + + // Open a new socket implementation. + asio::error_code open(implementation_type& impl, + const protocol_type& protocol, asio::error_code& ec) + { + if (!do_open(impl, protocol.family(), + protocol.type(), protocol.protocol(), ec)) + { + impl.protocol_ = protocol; + impl.have_remote_endpoint_ = false; + impl.remote_endpoint_ = endpoint_type(); + } + return ec; + } + + // Assign a native socket to a socket implementation. + asio::error_code assign(implementation_type& impl, + const protocol_type& protocol, const native_handle_type& native_socket, + asio::error_code& ec) + { + if (!do_assign(impl, protocol.type(), native_socket, ec)) + { + impl.protocol_ = protocol; + impl.have_remote_endpoint_ = native_socket.have_remote_endpoint(); + impl.remote_endpoint_ = native_socket.remote_endpoint(); + } + return ec; + } + + // Get the native socket representation. + native_handle_type native_handle(implementation_type& impl) + { + if (impl.have_remote_endpoint_) + return native_handle_type(impl.socket_, impl.remote_endpoint_); + return native_handle_type(impl.socket_); + } + + // Bind the socket to the specified local endpoint. + asio::error_code bind(implementation_type& impl, + const endpoint_type& endpoint, asio::error_code& ec) + { + socket_ops::bind(impl.socket_, endpoint.data(), endpoint.size(), ec); + return ec; + } + + // Set a socket option. + template + asio::error_code set_option(implementation_type& impl, + const Option& option, asio::error_code& ec) + { + socket_ops::setsockopt(impl.socket_, impl.state_, + option.level(impl.protocol_), option.name(impl.protocol_), + option.data(impl.protocol_), option.size(impl.protocol_), ec); + return ec; + } + + // Set a socket option. + template + asio::error_code get_option(const implementation_type& impl, + Option& option, asio::error_code& ec) const + { + std::size_t size = option.size(impl.protocol_); + socket_ops::getsockopt(impl.socket_, impl.state_, + option.level(impl.protocol_), option.name(impl.protocol_), + option.data(impl.protocol_), &size, ec); + if (!ec) + option.resize(impl.protocol_, size); + return ec; + } + + // Get the local endpoint. + endpoint_type local_endpoint(const implementation_type& impl, + asio::error_code& ec) const + { + endpoint_type endpoint; + std::size_t addr_len = endpoint.capacity(); + if (socket_ops::getsockname(impl.socket_, endpoint.data(), &addr_len, ec)) + return endpoint_type(); + endpoint.resize(addr_len); + return endpoint; + } + + // Get the remote endpoint. + endpoint_type remote_endpoint(const implementation_type& impl, + asio::error_code& ec) const + { + endpoint_type endpoint = impl.remote_endpoint_; + std::size_t addr_len = endpoint.capacity(); + if (socket_ops::getpeername(impl.socket_, endpoint.data(), + &addr_len, impl.have_remote_endpoint_, ec)) + return endpoint_type(); + endpoint.resize(addr_len); + return endpoint; + } + + // Disable sends or receives on the socket. + asio::error_code shutdown(base_implementation_type& impl, + socket_base::shutdown_type what, asio::error_code& ec) + { + socket_ops::shutdown(impl.socket_, what, ec); + return ec; + } + + // Send a datagram to the specified endpoint. Returns the number of bytes + // sent. + template + size_t send_to(implementation_type& impl, const ConstBufferSequence& buffers, + const endpoint_type& destination, socket_base::message_flags flags, + asio::error_code& ec) + { + buffer_sequence_adapter bufs(buffers); + + return socket_ops::sync_sendto(impl.socket_, impl.state_, + bufs.buffers(), bufs.count(), flags, + destination.data(), destination.size(), ec); + } + + // Wait until data can be sent without blocking. + size_t send_to(implementation_type& impl, const null_buffers&, + const endpoint_type&, socket_base::message_flags, + asio::error_code& ec) + { + // Wait for socket to become ready. + socket_ops::poll_write(impl.socket_, impl.state_, -1, ec); + + return 0; + } + + // Start an asynchronous send. The data being sent must be valid for the + // lifetime of the asynchronous operation. + template + void async_send_to(implementation_type& impl, + const ConstBufferSequence& buffers, const endpoint_type& destination, + socket_base::message_flags flags, Handler& handler, + const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_socket_send_op< + ConstBufferSequence, Handler, IoExecutor> op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(impl.cancel_token_, buffers, handler, io_ex); + + ASIO_HANDLER_CREATION((context_, *p.p, "socket", + &impl, impl.socket_, "async_send_to")); + + buffer_sequence_adapter bufs(buffers); + + start_send_to_op(impl, bufs.buffers(), bufs.count(), + destination.data(), static_cast(destination.size()), + flags, p.p); + p.v = p.p = 0; + } + + // Start an asynchronous wait until data can be sent without blocking. + template + void async_send_to(implementation_type& impl, const null_buffers&, + const endpoint_type&, socket_base::message_flags, Handler& handler, + const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_null_buffers_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(impl.cancel_token_, handler, io_ex); + + ASIO_HANDLER_CREATION((context_, *p.p, "socket", + &impl, impl.socket_, "async_send_to(null_buffers)")); + + start_reactor_op(impl, select_reactor::write_op, p.p); + p.v = p.p = 0; + } + + // Receive a datagram with the endpoint of the sender. Returns the number of + // bytes received. + template + size_t receive_from(implementation_type& impl, + const MutableBufferSequence& buffers, + endpoint_type& sender_endpoint, socket_base::message_flags flags, + asio::error_code& ec) + { + buffer_sequence_adapter bufs(buffers); + + std::size_t addr_len = sender_endpoint.capacity(); + std::size_t bytes_recvd = socket_ops::sync_recvfrom( + impl.socket_, impl.state_, bufs.buffers(), bufs.count(), + flags, sender_endpoint.data(), &addr_len, ec); + + if (!ec) + sender_endpoint.resize(addr_len); + + return bytes_recvd; + } + + // Wait until data can be received without blocking. + size_t receive_from(implementation_type& impl, + const null_buffers&, endpoint_type& sender_endpoint, + socket_base::message_flags, asio::error_code& ec) + { + // Wait for socket to become ready. + socket_ops::poll_read(impl.socket_, impl.state_, -1, ec); + + // Reset endpoint since it can be given no sensible value at this time. + sender_endpoint = endpoint_type(); + + return 0; + } + + // Start an asynchronous receive. The buffer for the data being received and + // the sender_endpoint object must both be valid for the lifetime of the + // asynchronous operation. + template + void async_receive_from(implementation_type& impl, + const MutableBufferSequence& buffers, endpoint_type& sender_endp, + socket_base::message_flags flags, Handler& handler, + const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_socket_recvfrom_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(sender_endp, impl.cancel_token_, + buffers, handler, io_ex); + + ASIO_HANDLER_CREATION((context_, *p.p, "socket", + &impl, impl.socket_, "async_receive_from")); + + buffer_sequence_adapter bufs(buffers); + + start_receive_from_op(impl, bufs.buffers(), bufs.count(), + sender_endp.data(), flags, &p.p->endpoint_size(), p.p); + p.v = p.p = 0; + } + + // Wait until data can be received without blocking. + template + void async_receive_from(implementation_type& impl, const null_buffers&, + endpoint_type& sender_endpoint, socket_base::message_flags flags, + Handler& handler, const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_null_buffers_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(impl.cancel_token_, handler, io_ex); + + ASIO_HANDLER_CREATION((context_, *p.p, "socket", + &impl, impl.socket_, "async_receive_from(null_buffers)")); + + // Reset endpoint since it can be given no sensible value at this time. + sender_endpoint = endpoint_type(); + + start_null_buffers_receive_op(impl, flags, p.p); + p.v = p.p = 0; + } + + // Accept a new connection. + template + asio::error_code accept(implementation_type& impl, Socket& peer, + endpoint_type* peer_endpoint, asio::error_code& ec) + { + // We cannot accept a socket that is already open. + if (peer.is_open()) + { + ec = asio::error::already_open; + return ec; + } + + std::size_t addr_len = peer_endpoint ? peer_endpoint->capacity() : 0; + socket_holder new_socket(socket_ops::sync_accept(impl.socket_, + impl.state_, peer_endpoint ? peer_endpoint->data() : 0, + peer_endpoint ? &addr_len : 0, ec)); + + // On success, assign new connection to peer socket object. + if (new_socket.get() != invalid_socket) + { + if (peer_endpoint) + peer_endpoint->resize(addr_len); + peer.assign(impl.protocol_, new_socket.get(), ec); + if (!ec) + new_socket.release(); + } + + return ec; + } + + // Start an asynchronous accept. The peer and peer_endpoint objects + // must be valid until the accept's handler is invoked. + template + void async_accept(implementation_type& impl, Socket& peer, + endpoint_type* peer_endpoint, Handler& handler, const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_socket_accept_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + bool enable_connection_aborted = + (impl.state_ & socket_ops::enable_connection_aborted) != 0; + p.p = new (p.v) op(*this, impl.socket_, peer, impl.protocol_, + peer_endpoint, enable_connection_aborted, handler, io_ex); + + ASIO_HANDLER_CREATION((context_, *p.p, "socket", + &impl, impl.socket_, "async_accept")); + + start_accept_op(impl, peer.is_open(), p.p->new_socket(), + impl.protocol_.family(), impl.protocol_.type(), + impl.protocol_.protocol(), p.p->output_buffer(), + p.p->address_length(), p.p); + p.v = p.p = 0; + } + +#if defined(ASIO_HAS_MOVE) + // Start an asynchronous accept. The peer and peer_endpoint objects + // must be valid until the accept's handler is invoked. + template + void async_move_accept(implementation_type& impl, + const PeerIoExecutor& peer_io_ex, endpoint_type* peer_endpoint, + Handler& handler, const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_socket_move_accept_op< + protocol_type, PeerIoExecutor, Handler, IoExecutor> op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + bool enable_connection_aborted = + (impl.state_ & socket_ops::enable_connection_aborted) != 0; + p.p = new (p.v) op(*this, impl.socket_, impl.protocol_, + peer_io_ex, peer_endpoint, enable_connection_aborted, + handler, io_ex); + + ASIO_HANDLER_CREATION((context_, *p.p, "socket", + &impl, impl.socket_, "async_accept")); + + start_accept_op(impl, false, p.p->new_socket(), + impl.protocol_.family(), impl.protocol_.type(), + impl.protocol_.protocol(), p.p->output_buffer(), + p.p->address_length(), p.p); + p.v = p.p = 0; + } +#endif // defined(ASIO_HAS_MOVE) + + // Connect the socket to the specified endpoint. + asio::error_code connect(implementation_type& impl, + const endpoint_type& peer_endpoint, asio::error_code& ec) + { + socket_ops::sync_connect(impl.socket_, + peer_endpoint.data(), peer_endpoint.size(), ec); + return ec; + } + + // Start an asynchronous connect. + template + void async_connect(implementation_type& impl, + const endpoint_type& peer_endpoint, Handler& handler, + const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_socket_connect_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(impl.socket_, handler, io_ex); + + ASIO_HANDLER_CREATION((context_, *p.p, "socket", + &impl, impl.socket_, "async_connect")); + + start_connect_op(impl, impl.protocol_.family(), impl.protocol_.type(), + peer_endpoint.data(), static_cast(peer_endpoint.size()), p.p); + p.v = p.p = 0; + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_WIN_IOCP_SOCKET_SERVICE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_service_base.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_service_base.hpp new file mode 100644 index 000000000..6e37745d9 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_socket_service_base.hpp @@ -0,0 +1,600 @@ +// +// detail/win_iocp_socket_service_base.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_SOCKET_SERVICE_BASE_HPP +#define ASIO_DETAIL_WIN_IOCP_SOCKET_SERVICE_BASE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/error.hpp" +#include "asio/execution_context.hpp" +#include "asio/socket_base.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/mutex.hpp" +#include "asio/detail/operation.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/select_reactor.hpp" +#include "asio/detail/socket_holder.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/detail/socket_types.hpp" +#include "asio/detail/win_iocp_io_context.hpp" +#include "asio/detail/win_iocp_null_buffers_op.hpp" +#include "asio/detail/win_iocp_socket_connect_op.hpp" +#include "asio/detail/win_iocp_socket_send_op.hpp" +#include "asio/detail/win_iocp_socket_recv_op.hpp" +#include "asio/detail/win_iocp_socket_recvmsg_op.hpp" +#include "asio/detail/win_iocp_wait_op.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class win_iocp_socket_service_base +{ +public: + // The implementation type of the socket. + struct base_implementation_type + { + // The native socket representation. + socket_type socket_; + + // The current state of the socket. + socket_ops::state_type state_; + + // We use a shared pointer as a cancellation token here to work around the + // broken Windows support for cancellation. MSDN says that when you call + // closesocket any outstanding WSARecv or WSASend operations will complete + // with the error ERROR_OPERATION_ABORTED. In practice they complete with + // ERROR_NETNAME_DELETED, which means you can't tell the difference between + // a local cancellation and the socket being hard-closed by the peer. + socket_ops::shared_cancel_token_type cancel_token_; + + // Per-descriptor data used by the reactor. + select_reactor::per_descriptor_data reactor_data_; + +#if defined(ASIO_ENABLE_CANCELIO) + // The ID of the thread from which it is safe to cancel asynchronous + // operations. 0 means no asynchronous operations have been started yet. + // ~0 means asynchronous operations have been started from more than one + // thread, and cancellation is not supported for the socket. + DWORD safe_cancellation_thread_id_; +#endif // defined(ASIO_ENABLE_CANCELIO) + + // Pointers to adjacent socket implementations in linked list. + base_implementation_type* next_; + base_implementation_type* prev_; + }; + + // Constructor. + ASIO_DECL win_iocp_socket_service_base(execution_context& context); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void base_shutdown(); + + // Construct a new socket implementation. + ASIO_DECL void construct(base_implementation_type& impl); + + // Move-construct a new socket implementation. + ASIO_DECL void base_move_construct(base_implementation_type& impl, + base_implementation_type& other_impl) ASIO_NOEXCEPT; + + // Move-assign from another socket implementation. + ASIO_DECL void base_move_assign(base_implementation_type& impl, + win_iocp_socket_service_base& other_service, + base_implementation_type& other_impl); + + // Destroy a socket implementation. + ASIO_DECL void destroy(base_implementation_type& impl); + + // Determine whether the socket is open. + bool is_open(const base_implementation_type& impl) const + { + return impl.socket_ != invalid_socket; + } + + // Destroy a socket implementation. + ASIO_DECL asio::error_code close( + base_implementation_type& impl, asio::error_code& ec); + + // Release ownership of the socket. + ASIO_DECL socket_type release( + base_implementation_type& impl, asio::error_code& ec); + + // Cancel all operations associated with the socket. + ASIO_DECL asio::error_code cancel( + base_implementation_type& impl, asio::error_code& ec); + + // Determine whether the socket is at the out-of-band data mark. + bool at_mark(const base_implementation_type& impl, + asio::error_code& ec) const + { + return socket_ops::sockatmark(impl.socket_, ec); + } + + // Determine the number of bytes available for reading. + std::size_t available(const base_implementation_type& impl, + asio::error_code& ec) const + { + return socket_ops::available(impl.socket_, ec); + } + + // Place the socket into the state where it will listen for new connections. + asio::error_code listen(base_implementation_type& impl, + int backlog, asio::error_code& ec) + { + socket_ops::listen(impl.socket_, backlog, ec); + return ec; + } + + // Perform an IO control command on the socket. + template + asio::error_code io_control(base_implementation_type& impl, + IO_Control_Command& command, asio::error_code& ec) + { + socket_ops::ioctl(impl.socket_, impl.state_, command.name(), + static_cast(command.data()), ec); + return ec; + } + + // Gets the non-blocking mode of the socket. + bool non_blocking(const base_implementation_type& impl) const + { + return (impl.state_ & socket_ops::user_set_non_blocking) != 0; + } + + // Sets the non-blocking mode of the socket. + asio::error_code non_blocking(base_implementation_type& impl, + bool mode, asio::error_code& ec) + { + socket_ops::set_user_non_blocking(impl.socket_, impl.state_, mode, ec); + return ec; + } + + // Gets the non-blocking mode of the native socket implementation. + bool native_non_blocking(const base_implementation_type& impl) const + { + return (impl.state_ & socket_ops::internal_non_blocking) != 0; + } + + // Sets the non-blocking mode of the native socket implementation. + asio::error_code native_non_blocking(base_implementation_type& impl, + bool mode, asio::error_code& ec) + { + socket_ops::set_internal_non_blocking(impl.socket_, impl.state_, mode, ec); + return ec; + } + + // Wait for the socket to become ready to read, ready to write, or to have + // pending error conditions. + asio::error_code wait(base_implementation_type& impl, + socket_base::wait_type w, asio::error_code& ec) + { + switch (w) + { + case socket_base::wait_read: + socket_ops::poll_read(impl.socket_, impl.state_, -1, ec); + break; + case socket_base::wait_write: + socket_ops::poll_write(impl.socket_, impl.state_, -1, ec); + break; + case socket_base::wait_error: + socket_ops::poll_error(impl.socket_, impl.state_, -1, ec); + break; + default: + ec = asio::error::invalid_argument; + break; + } + + return ec; + } + + // Asynchronously wait for the socket to become ready to read, ready to + // write, or to have pending error conditions. + template + void async_wait(base_implementation_type& impl, + socket_base::wait_type w, Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_wait_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(impl.cancel_token_, handler, io_ex); + + ASIO_HANDLER_CREATION((context_, *p.p, "socket", + &impl, impl.socket_, "async_wait")); + + switch (w) + { + case socket_base::wait_read: + start_null_buffers_receive_op(impl, 0, p.p); + break; + case socket_base::wait_write: + start_reactor_op(impl, select_reactor::write_op, p.p); + break; + case socket_base::wait_error: + start_reactor_op(impl, select_reactor::except_op, p.p); + break; + default: + p.p->ec_ = asio::error::invalid_argument; + iocp_service_.post_immediate_completion(p.p, is_continuation); + break; + } + + p.v = p.p = 0; + } + + // Send the given data to the peer. Returns the number of bytes sent. + template + size_t send(base_implementation_type& impl, + const ConstBufferSequence& buffers, + socket_base::message_flags flags, asio::error_code& ec) + { + buffer_sequence_adapter bufs(buffers); + + return socket_ops::sync_send(impl.socket_, impl.state_, + bufs.buffers(), bufs.count(), flags, bufs.all_empty(), ec); + } + + // Wait until data can be sent without blocking. + size_t send(base_implementation_type& impl, const null_buffers&, + socket_base::message_flags, asio::error_code& ec) + { + // Wait for socket to become ready. + socket_ops::poll_write(impl.socket_, impl.state_, -1, ec); + + return 0; + } + + // Start an asynchronous send. The data being sent must be valid for the + // lifetime of the asynchronous operation. + template + void async_send(base_implementation_type& impl, + const ConstBufferSequence& buffers, socket_base::message_flags flags, + Handler& handler, const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_socket_send_op< + ConstBufferSequence, Handler, IoExecutor> op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(impl.cancel_token_, buffers, handler, io_ex); + + ASIO_HANDLER_CREATION((context_, *p.p, "socket", + &impl, impl.socket_, "async_send")); + + buffer_sequence_adapter bufs(buffers); + + start_send_op(impl, bufs.buffers(), bufs.count(), flags, + (impl.state_ & socket_ops::stream_oriented) != 0 && bufs.all_empty(), + p.p); + p.v = p.p = 0; + } + + // Start an asynchronous wait until data can be sent without blocking. + template + void async_send(base_implementation_type& impl, const null_buffers&, + socket_base::message_flags, Handler& handler, const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_null_buffers_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(impl.cancel_token_, handler, io_ex); + + ASIO_HANDLER_CREATION((context_, *p.p, "socket", + &impl, impl.socket_, "async_send(null_buffers)")); + + start_reactor_op(impl, select_reactor::write_op, p.p); + p.v = p.p = 0; + } + + // Receive some data from the peer. Returns the number of bytes received. + template + size_t receive(base_implementation_type& impl, + const MutableBufferSequence& buffers, + socket_base::message_flags flags, asio::error_code& ec) + { + buffer_sequence_adapter bufs(buffers); + + return socket_ops::sync_recv(impl.socket_, impl.state_, + bufs.buffers(), bufs.count(), flags, bufs.all_empty(), ec); + } + + // Wait until data can be received without blocking. + size_t receive(base_implementation_type& impl, const null_buffers&, + socket_base::message_flags, asio::error_code& ec) + { + // Wait for socket to become ready. + socket_ops::poll_read(impl.socket_, impl.state_, -1, ec); + + return 0; + } + + // Start an asynchronous receive. The buffer for the data being received + // must be valid for the lifetime of the asynchronous operation. + template + void async_receive(base_implementation_type& impl, + const MutableBufferSequence& buffers, socket_base::message_flags flags, + Handler& handler, const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_socket_recv_op< + MutableBufferSequence, Handler, IoExecutor> op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(impl.state_, impl.cancel_token_, + buffers, handler, io_ex); + + ASIO_HANDLER_CREATION((context_, *p.p, "socket", + &impl, impl.socket_, "async_receive")); + + buffer_sequence_adapter bufs(buffers); + + start_receive_op(impl, bufs.buffers(), bufs.count(), flags, + (impl.state_ & socket_ops::stream_oriented) != 0 && bufs.all_empty(), + p.p); + p.v = p.p = 0; + } + + // Wait until data can be received without blocking. + template + void async_receive(base_implementation_type& impl, + const null_buffers&, socket_base::message_flags flags, + Handler& handler, const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_null_buffers_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(impl.cancel_token_, handler, io_ex); + + ASIO_HANDLER_CREATION((context_, *p.p, "socket", + &impl, impl.socket_, "async_receive(null_buffers)")); + + start_null_buffers_receive_op(impl, flags, p.p); + p.v = p.p = 0; + } + + // Receive some data with associated flags. Returns the number of bytes + // received. + template + size_t receive_with_flags(base_implementation_type& impl, + const MutableBufferSequence& buffers, + socket_base::message_flags in_flags, + socket_base::message_flags& out_flags, asio::error_code& ec) + { + buffer_sequence_adapter bufs(buffers); + + return socket_ops::sync_recvmsg(impl.socket_, impl.state_, + bufs.buffers(), bufs.count(), in_flags, out_flags, ec); + } + + // Wait until data can be received without blocking. + size_t receive_with_flags(base_implementation_type& impl, + const null_buffers&, socket_base::message_flags, + socket_base::message_flags& out_flags, asio::error_code& ec) + { + // Wait for socket to become ready. + socket_ops::poll_read(impl.socket_, impl.state_, -1, ec); + + // Clear out_flags, since we cannot give it any other sensible value when + // performing a null_buffers operation. + out_flags = 0; + + return 0; + } + + // Start an asynchronous receive. The buffer for the data being received + // must be valid for the lifetime of the asynchronous operation. + template + void async_receive_with_flags(base_implementation_type& impl, + const MutableBufferSequence& buffers, socket_base::message_flags in_flags, + socket_base::message_flags& out_flags, Handler& handler, + const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_socket_recvmsg_op< + MutableBufferSequence, Handler, IoExecutor> op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(impl.cancel_token_, + buffers, out_flags, handler, io_ex); + + ASIO_HANDLER_CREATION((context_, *p.p, "socket", + &impl, impl.socket_, "async_receive_with_flags")); + + buffer_sequence_adapter bufs(buffers); + + start_receive_op(impl, bufs.buffers(), bufs.count(), in_flags, false, p.p); + p.v = p.p = 0; + } + + // Wait until data can be received without blocking. + template + void async_receive_with_flags(base_implementation_type& impl, + const null_buffers&, socket_base::message_flags in_flags, + socket_base::message_flags& out_flags, Handler& handler, + const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef win_iocp_null_buffers_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(impl.cancel_token_, handler, io_ex); + + ASIO_HANDLER_CREATION((context_, *p.p, "socket", + &impl, impl.socket_, "async_receive_with_flags(null_buffers)")); + + // Reset out_flags since it can be given no sensible value at this time. + out_flags = 0; + + start_null_buffers_receive_op(impl, in_flags, p.p); + p.v = p.p = 0; + } + + // Helper function to restart an asynchronous accept operation. + ASIO_DECL void restart_accept_op(socket_type s, + socket_holder& new_socket, int family, int type, int protocol, + void* output_buffer, DWORD address_length, operation* op); + +protected: + // Open a new socket implementation. + ASIO_DECL asio::error_code do_open( + base_implementation_type& impl, int family, int type, + int protocol, asio::error_code& ec); + + // Assign a native socket to a socket implementation. + ASIO_DECL asio::error_code do_assign( + base_implementation_type& impl, int type, + socket_type native_socket, asio::error_code& ec); + + // Helper function to start an asynchronous send operation. + ASIO_DECL void start_send_op(base_implementation_type& impl, + WSABUF* buffers, std::size_t buffer_count, + socket_base::message_flags flags, bool noop, operation* op); + + // Helper function to start an asynchronous send_to operation. + ASIO_DECL void start_send_to_op(base_implementation_type& impl, + WSABUF* buffers, std::size_t buffer_count, + const socket_addr_type* addr, int addrlen, + socket_base::message_flags flags, operation* op); + + // Helper function to start an asynchronous receive operation. + ASIO_DECL void start_receive_op(base_implementation_type& impl, + WSABUF* buffers, std::size_t buffer_count, + socket_base::message_flags flags, bool noop, operation* op); + + // Helper function to start an asynchronous null_buffers receive operation. + ASIO_DECL void start_null_buffers_receive_op( + base_implementation_type& impl, + socket_base::message_flags flags, reactor_op* op); + + // Helper function to start an asynchronous receive_from operation. + ASIO_DECL void start_receive_from_op(base_implementation_type& impl, + WSABUF* buffers, std::size_t buffer_count, socket_addr_type* addr, + socket_base::message_flags flags, int* addrlen, operation* op); + + // Helper function to start an asynchronous accept operation. + ASIO_DECL void start_accept_op(base_implementation_type& impl, + bool peer_is_open, socket_holder& new_socket, int family, int type, + int protocol, void* output_buffer, DWORD address_length, operation* op); + + // Start an asynchronous read or write operation using the reactor. + ASIO_DECL void start_reactor_op(base_implementation_type& impl, + int op_type, reactor_op* op); + + // Start the asynchronous connect operation using the reactor. + ASIO_DECL void start_connect_op(base_implementation_type& impl, + int family, int type, const socket_addr_type* remote_addr, + std::size_t remote_addrlen, win_iocp_socket_connect_op_base* op); + + // Helper function to close a socket when the associated object is being + // destroyed. + ASIO_DECL void close_for_destruction(base_implementation_type& impl); + + // Update the ID of the thread from which cancellation is safe. + ASIO_DECL void update_cancellation_thread_id( + base_implementation_type& impl); + + // Helper function to get the reactor. If no reactor has been created yet, a + // new one is obtained from the execution context and a pointer to it is + // cached in this service. + ASIO_DECL select_reactor& get_reactor(); + + // The type of a ConnectEx function pointer, as old SDKs may not provide it. + typedef BOOL (PASCAL *connect_ex_fn)(SOCKET, + const socket_addr_type*, int, void*, DWORD, DWORD*, OVERLAPPED*); + + // Helper function to get the ConnectEx pointer. If no ConnectEx pointer has + // been obtained yet, one is obtained using WSAIoctl and the pointer is + // cached. Returns a null pointer if ConnectEx is not available. + ASIO_DECL connect_ex_fn get_connect_ex( + base_implementation_type& impl, int type); + + // The type of a NtSetInformationFile function pointer. + typedef LONG (NTAPI *nt_set_info_fn)(HANDLE, ULONG_PTR*, void*, ULONG, ULONG); + + // Helper function to get the NtSetInformationFile function pointer. If no + // NtSetInformationFile pointer has been obtained yet, one is obtained using + // GetProcAddress and the pointer is cached. Returns a null pointer if + // NtSetInformationFile is not available. + ASIO_DECL nt_set_info_fn get_nt_set_info(); + + // Helper function to emulate InterlockedCompareExchangePointer functionality + // for: + // - very old Platform SDKs; and + // - platform SDKs where MSVC's /Wp64 option causes spurious warnings. + ASIO_DECL void* interlocked_compare_exchange_pointer( + void** dest, void* exch, void* cmp); + + // Helper function to emulate InterlockedExchangePointer functionality for: + // - very old Platform SDKs; and + // - platform SDKs where MSVC's /Wp64 option causes spurious warnings. + ASIO_DECL void* interlocked_exchange_pointer(void** dest, void* val); + + // The execution context used to obtain the reactor, if required. + execution_context& context_; + + // The IOCP service used for running asynchronous operations and dispatching + // handlers. + win_iocp_io_context& iocp_service_; + + // The reactor used for performing connect operations. This object is created + // only if needed. + select_reactor* reactor_; + + // Pointer to ConnectEx implementation. + void* connect_ex_; + + // Pointer to NtSetInformationFile implementation. + void* nt_set_info_; + + // Mutex to protect access to the linked list of implementations. + asio::detail::mutex mutex_; + + // The head of a linked list of all implementations. + base_implementation_type* impl_list_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/win_iocp_socket_service_base.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_WIN_IOCP_SOCKET_SERVICE_BASE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_thread_info.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_thread_info.hpp new file mode 100644 index 000000000..90fa3ba8b --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_thread_info.hpp @@ -0,0 +1,34 @@ +// +// detail/win_iocp_thread_info.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_THREAD_INFO_HPP +#define ASIO_DETAIL_WIN_IOCP_THREAD_INFO_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/thread_info_base.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +struct win_iocp_thread_info : public thread_info_base +{ +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_WIN_IOCP_THREAD_INFO_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_wait_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_wait_op.hpp new file mode 100644 index 000000000..f6c61e1b8 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_iocp_wait_op.hpp @@ -0,0 +1,128 @@ +// +// detail/win_iocp_wait_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_IOCP_WAIT_OP_HPP +#define ASIO_DETAIL_WIN_IOCP_WAIT_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_IOCP) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/reactor_op.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class win_iocp_wait_op : public reactor_op +{ +public: + ASIO_DEFINE_HANDLER_PTR(win_iocp_wait_op); + + win_iocp_wait_op(socket_ops::weak_cancel_token_type cancel_token, + Handler& handler, const IoExecutor& io_ex) + : reactor_op(asio::error_code(), + &win_iocp_wait_op::do_perform, + &win_iocp_wait_op::do_complete), + cancel_token_(cancel_token), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static status do_perform(reactor_op*) + { + return done; + } + + static void do_complete(void* owner, operation* base, + const asio::error_code& result_ec, + std::size_t /*bytes_transferred*/) + { + asio::error_code ec(result_ec); + + // Take ownership of the operation object. + win_iocp_wait_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // The reactor may have stored a result in the operation object. + if (o->ec_) + ec = o->ec_; + + // Map non-portable errors to their portable counterparts. + if (ec.value() == ERROR_NETNAME_DELETED) + { + if (o->cancel_token_.expired()) + ec = asio::error::operation_aborted; + else + ec = asio::error::connection_reset; + } + else if (ec.value() == ERROR_PORT_UNREACHABLE) + { + ec = asio::error::connection_refused; + } + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder1 + handler(o->handler_, ec); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + socket_ops::weak_cancel_token_type cancel_token_; + Handler handler_; + handler_work work_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_HAS_IOCP) + +#endif // ASIO_DETAIL_WIN_IOCP_WAIT_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_mutex.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_mutex.hpp new file mode 100644 index 000000000..e02f34e84 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_mutex.hpp @@ -0,0 +1,78 @@ +// +// detail/win_mutex.hpp +// ~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_MUTEX_HPP +#define ASIO_DETAIL_WIN_MUTEX_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) + +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/scoped_lock.hpp" +#include "asio/detail/socket_types.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class win_mutex + : private noncopyable +{ +public: + typedef asio::detail::scoped_lock scoped_lock; + + // Constructor. + ASIO_DECL win_mutex(); + + // Destructor. + ~win_mutex() + { + ::DeleteCriticalSection(&crit_section_); + } + + // Lock the mutex. + void lock() + { + ::EnterCriticalSection(&crit_section_); + } + + // Unlock the mutex. + void unlock() + { + ::LeaveCriticalSection(&crit_section_); + } + +private: + // Initialisation must be performed in a separate function to the constructor + // since the compiler does not support the use of structured exceptions and + // C++ exceptions in the same function. + ASIO_DECL int do_init(); + + ::CRITICAL_SECTION crit_section_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/win_mutex.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_WINDOWS) + +#endif // ASIO_DETAIL_WIN_MUTEX_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_object_handle_service.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_object_handle_service.hpp new file mode 100644 index 000000000..bba4a921c --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_object_handle_service.hpp @@ -0,0 +1,195 @@ +// +// detail/win_object_handle_service.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// Copyright (c) 2011 Boris Schaeling (boris@highscore.de) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_OBJECT_HANDLE_SERVICE_HPP +#define ASIO_DETAIL_WIN_OBJECT_HANDLE_SERVICE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_WINDOWS_OBJECT_HANDLE) + +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/wait_handler.hpp" +#include "asio/error.hpp" +#include "asio/execution_context.hpp" + +#if defined(ASIO_HAS_IOCP) +# include "asio/detail/win_iocp_io_context.hpp" +#else // defined(ASIO_HAS_IOCP) +# include "asio/detail/scheduler.hpp" +#endif // defined(ASIO_HAS_IOCP) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class win_object_handle_service : + public execution_context_service_base +{ +public: + // The native type of an object handle. + typedef HANDLE native_handle_type; + + // The implementation type of the object handle. + class implementation_type + { + public: + // Default constructor. + implementation_type() + : handle_(INVALID_HANDLE_VALUE), + wait_handle_(INVALID_HANDLE_VALUE), + owner_(0), + next_(0), + prev_(0) + { + } + + private: + // Only this service will have access to the internal values. + friend class win_object_handle_service; + + // The native object handle representation. May be accessed or modified + // without locking the mutex. + native_handle_type handle_; + + // The handle used to unregister the wait operation. The mutex must be + // locked when accessing or modifying this member. + HANDLE wait_handle_; + + // The operations waiting on the object handle. If there is a registered + // wait then the mutex must be locked when accessing or modifying this + // member + op_queue op_queue_; + + // The service instance that owns the object handle implementation. + win_object_handle_service* owner_; + + // Pointers to adjacent handle implementations in linked list. The mutex + // must be locked when accessing or modifying these members. + implementation_type* next_; + implementation_type* prev_; + }; + + // Constructor. + ASIO_DECL win_object_handle_service(execution_context& context); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void shutdown(); + + // Construct a new handle implementation. + ASIO_DECL void construct(implementation_type& impl); + + // Move-construct a new handle implementation. + ASIO_DECL void move_construct(implementation_type& impl, + implementation_type& other_impl); + + // Move-assign from another handle implementation. + ASIO_DECL void move_assign(implementation_type& impl, + win_object_handle_service& other_service, + implementation_type& other_impl); + + // Destroy a handle implementation. + ASIO_DECL void destroy(implementation_type& impl); + + // Assign a native handle to a handle implementation. + ASIO_DECL asio::error_code assign(implementation_type& impl, + const native_handle_type& handle, asio::error_code& ec); + + // Determine whether the handle is open. + bool is_open(const implementation_type& impl) const + { + return impl.handle_ != INVALID_HANDLE_VALUE && impl.handle_ != 0; + } + + // Destroy a handle implementation. + ASIO_DECL asio::error_code close(implementation_type& impl, + asio::error_code& ec); + + // Get the native handle representation. + native_handle_type native_handle(const implementation_type& impl) const + { + return impl.handle_; + } + + // Cancel all operations associated with the handle. + ASIO_DECL asio::error_code cancel(implementation_type& impl, + asio::error_code& ec); + + // Perform a synchronous wait for the object to enter a signalled state. + ASIO_DECL void wait(implementation_type& impl, + asio::error_code& ec); + + /// Start an asynchronous wait. + template + void async_wait(implementation_type& impl, + Handler& handler, const IoExecutor& io_ex) + { + // Allocate and construct an operation to wrap the handler. + typedef wait_handler op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(handler, io_ex); + + ASIO_HANDLER_CREATION((scheduler_.context(), *p.p, "object_handle", + &impl, reinterpret_cast(impl.wait_handle_), "async_wait")); + + start_wait_op(impl, p.p); + p.v = p.p = 0; + } + +private: + // Helper function to start an asynchronous wait operation. + ASIO_DECL void start_wait_op(implementation_type& impl, wait_op* op); + + // Helper function to register a wait operation. + ASIO_DECL void register_wait_callback( + implementation_type& impl, mutex::scoped_lock& lock); + + // Callback function invoked when the registered wait completes. + static ASIO_DECL VOID CALLBACK wait_callback( + PVOID param, BOOLEAN timeout); + + // The scheduler used to post completions. +#if defined(ASIO_HAS_IOCP) + typedef class win_iocp_io_context scheduler_impl; +#else + typedef class scheduler scheduler_impl; +#endif + scheduler_impl& scheduler_; + + // Mutex to protect access to internal state. + mutex mutex_; + + // The head of a linked list of all implementations. + implementation_type* impl_list_; + + // Flag to indicate that the dispatcher has been shut down. + bool shutdown_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/win_object_handle_service.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_HAS_WINDOWS_OBJECT_HANDLE) + +#endif // ASIO_DETAIL_WIN_OBJECT_HANDLE_SERVICE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_static_mutex.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_static_mutex.hpp new file mode 100644 index 000000000..c96e708a4 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_static_mutex.hpp @@ -0,0 +1,74 @@ +// +// detail/win_static_mutex.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_STATIC_MUTEX_HPP +#define ASIO_DETAIL_WIN_STATIC_MUTEX_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) + +#include "asio/detail/scoped_lock.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +struct win_static_mutex +{ + typedef asio::detail::scoped_lock scoped_lock; + + // Initialise the mutex. + ASIO_DECL void init(); + + // Initialisation must be performed in a separate function to the "public" + // init() function since the compiler does not support the use of structured + // exceptions and C++ exceptions in the same function. + ASIO_DECL int do_init(); + + // Lock the mutex. + void lock() + { + ::EnterCriticalSection(&crit_section_); + } + + // Unlock the mutex. + void unlock() + { + ::LeaveCriticalSection(&crit_section_); + } + + bool initialised_; + ::CRITICAL_SECTION crit_section_; +}; + +#if defined(UNDER_CE) +# define ASIO_WIN_STATIC_MUTEX_INIT { false, { 0, 0, 0, 0, 0 } } +#else // defined(UNDER_CE) +# define ASIO_WIN_STATIC_MUTEX_INIT { false, { 0, 0, 0, 0, 0, 0 } } +#endif // defined(UNDER_CE) + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/win_static_mutex.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_WINDOWS) + +#endif // ASIO_DETAIL_WIN_STATIC_MUTEX_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_thread.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_thread.hpp new file mode 100644 index 000000000..6c7168c9e --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_thread.hpp @@ -0,0 +1,147 @@ +// +// detail/win_thread.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_THREAD_HPP +#define ASIO_DETAIL_WIN_THREAD_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) \ + && !defined(ASIO_WINDOWS_APP) \ + && !defined(UNDER_CE) + +#include +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/socket_types.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +ASIO_DECL unsigned int __stdcall win_thread_function(void* arg); + +#if defined(WINVER) && (WINVER < 0x0500) +ASIO_DECL void __stdcall apc_function(ULONG data); +#else +ASIO_DECL void __stdcall apc_function(ULONG_PTR data); +#endif + +template +class win_thread_base +{ +public: + static bool terminate_threads() + { + return ::InterlockedExchangeAdd(&terminate_threads_, 0) != 0; + } + + static void set_terminate_threads(bool b) + { + ::InterlockedExchange(&terminate_threads_, b ? 1 : 0); + } + +private: + static long terminate_threads_; +}; + +template +long win_thread_base::terminate_threads_ = 0; + +class win_thread + : private noncopyable, + public win_thread_base +{ +public: + // Constructor. + template + win_thread(Function f, unsigned int stack_size = 0) + : thread_(0), + exit_event_(0) + { + start_thread(new func(f), stack_size); + } + + // Destructor. + ASIO_DECL ~win_thread(); + + // Wait for the thread to exit. + ASIO_DECL void join(); + + // Get number of CPUs. + ASIO_DECL static std::size_t hardware_concurrency(); + +private: + friend ASIO_DECL unsigned int __stdcall win_thread_function(void* arg); + +#if defined(WINVER) && (WINVER < 0x0500) + friend ASIO_DECL void __stdcall apc_function(ULONG); +#else + friend ASIO_DECL void __stdcall apc_function(ULONG_PTR); +#endif + + class func_base + { + public: + virtual ~func_base() {} + virtual void run() = 0; + ::HANDLE entry_event_; + ::HANDLE exit_event_; + }; + + struct auto_func_base_ptr + { + func_base* ptr; + ~auto_func_base_ptr() { delete ptr; } + }; + + template + class func + : public func_base + { + public: + func(Function f) + : f_(f) + { + } + + virtual void run() + { + f_(); + } + + private: + Function f_; + }; + + ASIO_DECL void start_thread(func_base* arg, unsigned int stack_size); + + ::HANDLE thread_; + ::HANDLE exit_event_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/win_thread.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_WINDOWS) + // && !defined(ASIO_WINDOWS_APP) + // && !defined(UNDER_CE) + +#endif // ASIO_DETAIL_WIN_THREAD_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_tss_ptr.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_tss_ptr.hpp new file mode 100644 index 000000000..7044cd129 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/win_tss_ptr.hpp @@ -0,0 +1,79 @@ +// +// detail/win_tss_ptr.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WIN_TSS_PTR_HPP +#define ASIO_DETAIL_WIN_TSS_PTR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) + +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/socket_types.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +// Helper function to create thread-specific storage. +ASIO_DECL DWORD win_tss_ptr_create(); + +template +class win_tss_ptr + : private noncopyable +{ +public: + // Constructor. + win_tss_ptr() + : tss_key_(win_tss_ptr_create()) + { + } + + // Destructor. + ~win_tss_ptr() + { + ::TlsFree(tss_key_); + } + + // Get the value. + operator T*() const + { + return static_cast(::TlsGetValue(tss_key_)); + } + + // Set the value. + void operator=(T* value) + { + ::TlsSetValue(tss_key_, value); + } + +private: + // Thread-specific storage to allow unlocked access to determine whether a + // thread is a member of the pool. + DWORD tss_key_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/win_tss_ptr.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_WINDOWS) + +#endif // ASIO_DETAIL_WIN_TSS_PTR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winapp_thread.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winapp_thread.hpp new file mode 100644 index 000000000..74e3fddc1 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winapp_thread.hpp @@ -0,0 +1,124 @@ +// +// detail/winapp_thread.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WINAPP_THREAD_HPP +#define ASIO_DETAIL_WINAPP_THREAD_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) && defined(ASIO_WINDOWS_APP) + +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/scoped_ptr.hpp" +#include "asio/detail/socket_types.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +DWORD WINAPI winapp_thread_function(LPVOID arg); + +class winapp_thread + : private noncopyable +{ +public: + // Constructor. + template + winapp_thread(Function f, unsigned int = 0) + { + scoped_ptr arg(new func(f)); + DWORD thread_id = 0; + thread_ = ::CreateThread(0, 0, winapp_thread_function, + arg.get(), 0, &thread_id); + if (!thread_) + { + DWORD last_error = ::GetLastError(); + asio::error_code ec(last_error, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "thread"); + } + arg.release(); + } + + // Destructor. + ~winapp_thread() + { + ::CloseHandle(thread_); + } + + // Wait for the thread to exit. + void join() + { + ::WaitForSingleObjectEx(thread_, INFINITE, false); + } + + // Get number of CPUs. + static std::size_t hardware_concurrency() + { + SYSTEM_INFO system_info; + ::GetNativeSystemInfo(&system_info); + return system_info.dwNumberOfProcessors; + } + +private: + friend DWORD WINAPI winapp_thread_function(LPVOID arg); + + class func_base + { + public: + virtual ~func_base() {} + virtual void run() = 0; + }; + + template + class func + : public func_base + { + public: + func(Function f) + : f_(f) + { + } + + virtual void run() + { + f_(); + } + + private: + Function f_; + }; + + ::HANDLE thread_; +}; + +inline DWORD WINAPI winapp_thread_function(LPVOID arg) +{ + scoped_ptr func( + static_cast(arg)); + func->run(); + return 0; +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS) && defined(ASIO_WINDOWS_APP) + +#endif // ASIO_DETAIL_WINAPP_THREAD_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/wince_thread.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/wince_thread.hpp new file mode 100644 index 000000000..37bf2ad7f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/wince_thread.hpp @@ -0,0 +1,124 @@ +// +// detail/wince_thread.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WINCE_THREAD_HPP +#define ASIO_DETAIL_WINCE_THREAD_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) && defined(UNDER_CE) + +#include "asio/detail/noncopyable.hpp" +#include "asio/detail/scoped_ptr.hpp" +#include "asio/detail/socket_types.hpp" +#include "asio/detail/throw_error.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +DWORD WINAPI wince_thread_function(LPVOID arg); + +class wince_thread + : private noncopyable +{ +public: + // Constructor. + template + wince_thread(Function f, unsigned int = 0) + { + scoped_ptr arg(new func(f)); + DWORD thread_id = 0; + thread_ = ::CreateThread(0, 0, wince_thread_function, + arg.get(), 0, &thread_id); + if (!thread_) + { + DWORD last_error = ::GetLastError(); + asio::error_code ec(last_error, + asio::error::get_system_category()); + asio::detail::throw_error(ec, "thread"); + } + arg.release(); + } + + // Destructor. + ~wince_thread() + { + ::CloseHandle(thread_); + } + + // Wait for the thread to exit. + void join() + { + ::WaitForSingleObject(thread_, INFINITE); + } + + // Get number of CPUs. + static std::size_t hardware_concurrency() + { + SYSTEM_INFO system_info; + ::GetSystemInfo(&system_info); + return system_info.dwNumberOfProcessors; + } + +private: + friend DWORD WINAPI wince_thread_function(LPVOID arg); + + class func_base + { + public: + virtual ~func_base() {} + virtual void run() = 0; + }; + + template + class func + : public func_base + { + public: + func(Function f) + : f_(f) + { + } + + virtual void run() + { + f_(); + } + + private: + Function f_; + }; + + ::HANDLE thread_; +}; + +inline DWORD WINAPI wince_thread_function(LPVOID arg) +{ + scoped_ptr func( + static_cast(arg)); + func->run(); + return 0; +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS) && defined(UNDER_CE) + +#endif // ASIO_DETAIL_WINCE_THREAD_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_async_manager.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_async_manager.hpp new file mode 100644 index 000000000..6058be278 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_async_manager.hpp @@ -0,0 +1,305 @@ +// +// detail/winrt_async_manager.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WINRT_ASYNC_MANAGER_HPP +#define ASIO_DETAIL_WINRT_ASYNC_MANAGER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) + +#include +#include "asio/detail/atomic_count.hpp" +#include "asio/detail/winrt_async_op.hpp" +#include "asio/error.hpp" +#include "asio/execution_context.hpp" + +#if defined(ASIO_HAS_IOCP) +# include "asio/detail/win_iocp_io_context.hpp" +#else // defined(ASIO_HAS_IOCP) +# include "asio/detail/scheduler.hpp" +#endif // defined(ASIO_HAS_IOCP) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class winrt_async_manager + : public execution_context_service_base +{ +public: + // Constructor. + winrt_async_manager(execution_context& context) + : execution_context_service_base(context), + scheduler_(use_service(context)), + outstanding_ops_(1) + { + } + + // Destructor. + ~winrt_async_manager() + { + } + + // Destroy all user-defined handler objects owned by the service. + void shutdown() + { + if (--outstanding_ops_ > 0) + { + // Block until last operation is complete. + std::future f = promise_.get_future(); + f.wait(); + } + } + + void sync(Windows::Foundation::IAsyncAction^ action, + asio::error_code& ec) + { + using namespace Windows::Foundation; + using Windows::Foundation::AsyncStatus; + + auto promise = std::make_shared>(); + auto future = promise->get_future(); + + action->Completed = ref new AsyncActionCompletedHandler( + [promise](IAsyncAction^ action, AsyncStatus status) + { + switch (status) + { + case AsyncStatus::Canceled: + promise->set_value(asio::error::operation_aborted); + break; + case AsyncStatus::Error: + case AsyncStatus::Completed: + default: + asio::error_code ec( + action->ErrorCode.Value, + asio::system_category()); + promise->set_value(ec); + break; + } + }); + + ec = future.get(); + } + + template + TResult sync(Windows::Foundation::IAsyncOperation^ operation, + asio::error_code& ec) + { + using namespace Windows::Foundation; + using Windows::Foundation::AsyncStatus; + + auto promise = std::make_shared>(); + auto future = promise->get_future(); + + operation->Completed = ref new AsyncOperationCompletedHandler( + [promise](IAsyncOperation^ operation, AsyncStatus status) + { + switch (status) + { + case AsyncStatus::Canceled: + promise->set_value(asio::error::operation_aborted); + break; + case AsyncStatus::Error: + case AsyncStatus::Completed: + default: + asio::error_code ec( + operation->ErrorCode.Value, + asio::system_category()); + promise->set_value(ec); + break; + } + }); + + ec = future.get(); + return operation->GetResults(); + } + + template + TResult sync( + Windows::Foundation::IAsyncOperationWithProgress< + TResult, TProgress>^ operation, + asio::error_code& ec) + { + using namespace Windows::Foundation; + using Windows::Foundation::AsyncStatus; + + auto promise = std::make_shared>(); + auto future = promise->get_future(); + + operation->Completed + = ref new AsyncOperationWithProgressCompletedHandler( + [promise](IAsyncOperationWithProgress^ operation, + AsyncStatus status) + { + switch (status) + { + case AsyncStatus::Canceled: + promise->set_value(asio::error::operation_aborted); + break; + case AsyncStatus::Started: + break; + case AsyncStatus::Error: + case AsyncStatus::Completed: + default: + asio::error_code ec( + operation->ErrorCode.Value, + asio::system_category()); + promise->set_value(ec); + break; + } + }); + + ec = future.get(); + return operation->GetResults(); + } + + void async(Windows::Foundation::IAsyncAction^ action, + winrt_async_op* handler) + { + using namespace Windows::Foundation; + using Windows::Foundation::AsyncStatus; + + auto on_completed = ref new AsyncActionCompletedHandler( + [this, handler](IAsyncAction^ action, AsyncStatus status) + { + switch (status) + { + case AsyncStatus::Canceled: + handler->ec_ = asio::error::operation_aborted; + break; + case AsyncStatus::Started: + return; + case AsyncStatus::Completed: + case AsyncStatus::Error: + default: + handler->ec_ = asio::error_code( + action->ErrorCode.Value, + asio::system_category()); + break; + } + scheduler_.post_deferred_completion(handler); + if (--outstanding_ops_ == 0) + promise_.set_value(); + }); + + scheduler_.work_started(); + ++outstanding_ops_; + action->Completed = on_completed; + } + + template + void async(Windows::Foundation::IAsyncOperation^ operation, + winrt_async_op* handler) + { + using namespace Windows::Foundation; + using Windows::Foundation::AsyncStatus; + + auto on_completed = ref new AsyncOperationCompletedHandler( + [this, handler](IAsyncOperation^ operation, AsyncStatus status) + { + switch (status) + { + case AsyncStatus::Canceled: + handler->ec_ = asio::error::operation_aborted; + break; + case AsyncStatus::Started: + return; + case AsyncStatus::Completed: + handler->result_ = operation->GetResults(); + // Fall through. + case AsyncStatus::Error: + default: + handler->ec_ = asio::error_code( + operation->ErrorCode.Value, + asio::system_category()); + break; + } + scheduler_.post_deferred_completion(handler); + if (--outstanding_ops_ == 0) + promise_.set_value(); + }); + + scheduler_.work_started(); + ++outstanding_ops_; + operation->Completed = on_completed; + } + + template + void async( + Windows::Foundation::IAsyncOperationWithProgress< + TResult, TProgress>^ operation, + winrt_async_op* handler) + { + using namespace Windows::Foundation; + using Windows::Foundation::AsyncStatus; + + auto on_completed + = ref new AsyncOperationWithProgressCompletedHandler( + [this, handler](IAsyncOperationWithProgress< + TResult, TProgress>^ operation, AsyncStatus status) + { + switch (status) + { + case AsyncStatus::Canceled: + handler->ec_ = asio::error::operation_aborted; + break; + case AsyncStatus::Started: + return; + case AsyncStatus::Completed: + handler->result_ = operation->GetResults(); + // Fall through. + case AsyncStatus::Error: + default: + handler->ec_ = asio::error_code( + operation->ErrorCode.Value, + asio::system_category()); + break; + } + scheduler_.post_deferred_completion(handler); + if (--outstanding_ops_ == 0) + promise_.set_value(); + }); + + scheduler_.work_started(); + ++outstanding_ops_; + operation->Completed = on_completed; + } + +private: + // The scheduler implementation used to post completed handlers. +#if defined(ASIO_HAS_IOCP) + typedef class win_iocp_io_context scheduler_impl; +#else + typedef class scheduler scheduler_impl; +#endif + scheduler_impl& scheduler_; + + // Count of outstanding operations. + atomic_count outstanding_ops_; + + // Used to keep wait for outstanding operations to complete. + std::promise promise_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_WINRT_ASYNC_MANAGER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_async_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_async_op.hpp new file mode 100644 index 000000000..78c411b4d --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_async_op.hpp @@ -0,0 +1,65 @@ +// +// detail/winrt_async_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WINRT_ASYNC_OP_HPP +#define ASIO_DETAIL_WINRT_ASYNC_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/operation.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class winrt_async_op + : public operation +{ +public: + // The error code to be passed to the completion handler. + asio::error_code ec_; + + // The result of the operation, to be passed to the completion handler. + TResult result_; + +protected: + winrt_async_op(func_type complete_func) + : operation(complete_func), + result_() + { + } +}; + +template <> +class winrt_async_op + : public operation +{ +public: + // The error code to be passed to the completion handler. + asio::error_code ec_; + +protected: + winrt_async_op(func_type complete_func) + : operation(complete_func) + { + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_WINRT_ASYNC_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_resolve_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_resolve_op.hpp new file mode 100644 index 000000000..d2537b924 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_resolve_op.hpp @@ -0,0 +1,125 @@ +// +// detail/winrt_resolve_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WINRT_RESOLVE_OP_HPP +#define ASIO_DETAIL_WINRT_RESOLVE_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/winrt_async_op.hpp" +#include "asio/ip/basic_resolver_results.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class winrt_resolve_op : + public winrt_async_op< + Windows::Foundation::Collections::IVectorView< + Windows::Networking::EndpointPair^>^> +{ +public: + ASIO_DEFINE_HANDLER_PTR(winrt_resolve_op); + + typedef typename Protocol::endpoint endpoint_type; + typedef asio::ip::basic_resolver_query query_type; + typedef asio::ip::basic_resolver_results results_type; + + winrt_resolve_op(const query_type& query, + Handler& handler, const IoExecutor& io_ex) + : winrt_async_op< + Windows::Foundation::Collections::IVectorView< + Windows::Networking::EndpointPair^>^>( + &winrt_resolve_op::do_complete), + query_(query), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code&, std::size_t) + { + // Take ownership of the operation object. + winrt_resolve_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + results_type results = results_type(); + if (!o->ec_) + { + try + { + results = results_type::create(o->result_, o->query_.hints(), + o->query_.host_name(), o->query_.service_name()); + } + catch (Platform::Exception^ e) + { + o->ec_ = asio::error_code(e->HResult, + asio::system_category()); + } + } + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, o->ec_, results); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, "...")); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + query_type query_; + Handler handler_; + handler_work executor_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_WINRT_RESOLVE_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_resolver_service.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_resolver_service.hpp new file mode 100644 index 000000000..e3d2859d7 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_resolver_service.hpp @@ -0,0 +1,212 @@ +// +// detail/winrt_resolver_service.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WINRT_RESOLVER_SERVICE_HPP +#define ASIO_DETAIL_WINRT_RESOLVER_SERVICE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) + +#include "asio/ip/basic_resolver_query.hpp" +#include "asio/ip/basic_resolver_results.hpp" +#include "asio/post.hpp" +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/socket_ops.hpp" +#include "asio/detail/winrt_async_manager.hpp" +#include "asio/detail/winrt_resolve_op.hpp" +#include "asio/detail/winrt_utils.hpp" + +#if defined(ASIO_HAS_IOCP) +# include "asio/detail/win_iocp_io_context.hpp" +#else // defined(ASIO_HAS_IOCP) +# include "asio/detail/scheduler.hpp" +#endif // defined(ASIO_HAS_IOCP) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class winrt_resolver_service : + public execution_context_service_base > +{ +public: + // The implementation type of the resolver. A cancellation token is used to + // indicate to the asynchronous operation that the operation has been + // cancelled. + typedef socket_ops::shared_cancel_token_type implementation_type; + + // The endpoint type. + typedef typename Protocol::endpoint endpoint_type; + + // The query type. + typedef asio::ip::basic_resolver_query query_type; + + // The results type. + typedef asio::ip::basic_resolver_results results_type; + + // Constructor. + winrt_resolver_service(execution_context& context) + : execution_context_service_base< + winrt_resolver_service >(context), + scheduler_(use_service(context)), + async_manager_(use_service(context)) + { + } + + // Destructor. + ~winrt_resolver_service() + { + } + + // Destroy all user-defined handler objects owned by the service. + void shutdown() + { + } + + // Perform any fork-related housekeeping. + void notify_fork(execution_context::fork_event) + { + } + + // Construct a new resolver implementation. + void construct(implementation_type&) + { + } + + // Move-construct a new resolver implementation. + void move_construct(implementation_type&, + implementation_type&) + { + } + + // Move-assign from another resolver implementation. + void move_assign(implementation_type&, + winrt_resolver_service&, implementation_type&) + { + } + + // Destroy a resolver implementation. + void destroy(implementation_type&) + { + } + + // Cancel pending asynchronous operations. + void cancel(implementation_type&) + { + } + + // Resolve a query to a list of entries. + results_type resolve(implementation_type&, + const query_type& query, asio::error_code& ec) + { + try + { + using namespace Windows::Networking::Sockets; + auto endpoint_pairs = async_manager_.sync( + DatagramSocket::GetEndpointPairsAsync( + winrt_utils::host_name(query.host_name()), + winrt_utils::string(query.service_name())), ec); + + if (ec) + return results_type(); + + return results_type::create( + endpoint_pairs, query.hints(), + query.host_name(), query.service_name()); + } + catch (Platform::Exception^ e) + { + ec = asio::error_code(e->HResult, + asio::system_category()); + return results_type(); + } + } + + // Asynchronously resolve a query to a list of entries. + template + void async_resolve(implementation_type& impl, const query_type& query, + Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef winrt_resolve_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(query, handler, io_ex); + + ASIO_HANDLER_CREATION((scheduler_.context(), + *p.p, "resolver", &impl, 0, "async_resolve")); + (void)impl; + + try + { + using namespace Windows::Networking::Sockets; + async_manager_.async(DatagramSocket::GetEndpointPairsAsync( + winrt_utils::host_name(query.host_name()), + winrt_utils::string(query.service_name())), p.p); + p.v = p.p = 0; + } + catch (Platform::Exception^ e) + { + p.p->ec_ = asio::error_code( + e->HResult, asio::system_category()); + scheduler_.post_immediate_completion(p.p, is_continuation); + p.v = p.p = 0; + } + } + + // Resolve an endpoint to a list of entries. + results_type resolve(implementation_type&, + const endpoint_type&, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return results_type(); + } + + // Asynchronously resolve an endpoint to a list of entries. + template + void async_resolve(implementation_type&, const endpoint_type&, + Handler& handler, const IoExecutor& io_ex) + { + asio::error_code ec = asio::error::operation_not_supported; + const results_type results; + asio::post(io_ex, detail::bind_handler(handler, ec, results)); + } + +private: + // The scheduler implementation used for delivering completions. +#if defined(ASIO_HAS_IOCP) + typedef class win_iocp_io_context scheduler_impl; +#else + typedef class scheduler scheduler_impl; +#endif + scheduler_impl& scheduler_; + + winrt_async_manager& async_manager_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_WINRT_RESOLVER_SERVICE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_socket_connect_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_socket_connect_op.hpp new file mode 100644 index 000000000..004fc09fd --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_socket_connect_op.hpp @@ -0,0 +1,98 @@ +// +// detail/winrt_socket_connect_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WINRT_SOCKET_CONNECT_OP_HPP +#define ASIO_DETAIL_WINRT_SOCKET_CONNECT_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/winrt_async_op.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class winrt_socket_connect_op : + public winrt_async_op +{ +public: + ASIO_DEFINE_HANDLER_PTR(winrt_socket_connect_op); + + winrt_socket_connect_op(Handler& handler, const IoExecutor& io_ex) + : winrt_async_op(&winrt_socket_connect_op::do_complete), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code&, std::size_t) + { + // Take ownership of the operation object. + winrt_socket_connect_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder1 + handler(o->handler_, o->ec_); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + Handler handler_; + handler_work executor_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_WINRT_SOCKET_CONNECT_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_socket_recv_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_socket_recv_op.hpp new file mode 100644 index 000000000..74fae7621 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_socket_recv_op.hpp @@ -0,0 +1,119 @@ +// +// detail/winrt_socket_recv_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WINRT_SOCKET_RECV_OP_HPP +#define ASIO_DETAIL_WINRT_SOCKET_RECV_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/winrt_async_op.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class winrt_socket_recv_op : + public winrt_async_op +{ +public: + ASIO_DEFINE_HANDLER_PTR(winrt_socket_recv_op); + + winrt_socket_recv_op(const MutableBufferSequence& buffers, + Handler& handler, const IoExecutor& io_ex) + : winrt_async_op( + &winrt_socket_recv_op::do_complete), + buffers_(buffers), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code&, std::size_t) + { + // Take ownership of the operation object. + winrt_socket_recv_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + // Check whether buffers are still valid. + if (owner) + { + buffer_sequence_adapter::validate(o->buffers_); + } +#endif // defined(ASIO_ENABLE_BUFFER_DEBUGGING) + + std::size_t bytes_transferred = o->result_ ? o->result_->Length : 0; + if (bytes_transferred == 0 && !o->ec_ && + !buffer_sequence_adapter::all_empty(o->buffers_)) + { + o->ec_ = asio::error::eof; + } + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, o->ec_, bytes_transferred); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + MutableBufferSequence buffers_; + Handler handler_; + handler_work executor_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_WINRT_SOCKET_RECV_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_socket_send_op.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_socket_send_op.hpp new file mode 100644 index 000000000..6129c8009 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_socket_send_op.hpp @@ -0,0 +1,110 @@ +// +// detail/winrt_socket_send_op.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WINRT_SOCKET_SEND_OP_HPP +#define ASIO_DETAIL_WINRT_SOCKET_SEND_OP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/fenced_block.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" +#include "asio/detail/handler_work.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/winrt_async_op.hpp" +#include "asio/error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class winrt_socket_send_op : + public winrt_async_op +{ +public: + ASIO_DEFINE_HANDLER_PTR(winrt_socket_send_op); + + winrt_socket_send_op(const ConstBufferSequence& buffers, + Handler& handler, const IoExecutor& io_ex) + : winrt_async_op(&winrt_socket_send_op::do_complete), + buffers_(buffers), + handler_(ASIO_MOVE_CAST(Handler)(handler)), + work_(handler_, io_ex) + { + } + + static void do_complete(void* owner, operation* base, + const asio::error_code&, std::size_t) + { + // Take ownership of the operation object. + winrt_socket_send_op* o(static_cast(base)); + ptr p = { asio::detail::addressof(o->handler_), o, o }; + + ASIO_HANDLER_COMPLETION((*o)); + + // Take ownership of the operation's outstanding work. + handler_work w( + ASIO_MOVE_CAST2(handler_work)( + o->work_)); + +#if defined(ASIO_ENABLE_BUFFER_DEBUGGING) + // Check whether buffers are still valid. + if (owner) + { + buffer_sequence_adapter::validate(o->buffers_); + } +#endif // defined(ASIO_ENABLE_BUFFER_DEBUGGING) + + // Make a copy of the handler so that the memory can be deallocated before + // the upcall is made. Even if we're not about to make an upcall, a + // sub-object of the handler may be the true owner of the memory associated + // with the handler. Consequently, a local copy of the handler is required + // to ensure that any owning sub-object remains valid until after we have + // deallocated the memory here. + detail::binder2 + handler(o->handler_, o->ec_, o->result_); + p.h = asio::detail::addressof(handler.handler_); + p.reset(); + + // Make the upcall if required. + if (owner) + { + fenced_block b(fenced_block::half); + ASIO_HANDLER_INVOCATION_BEGIN((handler.arg1_, handler.arg2_)); + w.complete(handler, handler.handler_); + ASIO_HANDLER_INVOCATION_END; + } + } + +private: + ConstBufferSequence buffers_; + Handler handler_; + handler_work executor_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_WINRT_SOCKET_SEND_OP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_ssocket_service.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_ssocket_service.hpp new file mode 100644 index 000000000..45b614acf --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_ssocket_service.hpp @@ -0,0 +1,250 @@ +// +// detail/winrt_ssocket_service.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WINRT_SSOCKET_SERVICE_HPP +#define ASIO_DETAIL_WINRT_SSOCKET_SERVICE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) + +#include "asio/error.hpp" +#include "asio/execution_context.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/winrt_socket_connect_op.hpp" +#include "asio/detail/winrt_ssocket_service_base.hpp" +#include "asio/detail/winrt_utils.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +class winrt_ssocket_service : + public execution_context_service_base >, + public winrt_ssocket_service_base +{ +public: + // The protocol type. + typedef Protocol protocol_type; + + // The endpoint type. + typedef typename Protocol::endpoint endpoint_type; + + // The native type of a socket. + typedef Windows::Networking::Sockets::StreamSocket^ native_handle_type; + + // The implementation type of the socket. + struct implementation_type : base_implementation_type + { + // Default constructor. + implementation_type() + : base_implementation_type(), + protocol_(endpoint_type().protocol()) + { + } + + // The protocol associated with the socket. + protocol_type protocol_; + }; + + // Constructor. + winrt_ssocket_service(execution_context& context) + : execution_context_service_base >(context), + winrt_ssocket_service_base(context) + { + } + + // Destroy all user-defined handler objects owned by the service. + void shutdown() + { + this->base_shutdown(); + } + + // Move-construct a new socket implementation. + void move_construct(implementation_type& impl, + implementation_type& other_impl) ASIO_NOEXCEPT + { + this->base_move_construct(impl, other_impl); + + impl.protocol_ = other_impl.protocol_; + other_impl.protocol_ = endpoint_type().protocol(); + } + + // Move-assign from another socket implementation. + void move_assign(implementation_type& impl, + winrt_ssocket_service& other_service, + implementation_type& other_impl) + { + this->base_move_assign(impl, other_service, other_impl); + + impl.protocol_ = other_impl.protocol_; + other_impl.protocol_ = endpoint_type().protocol(); + } + + // Move-construct a new socket implementation from another protocol type. + template + void converting_move_construct(implementation_type& impl, + winrt_ssocket_service&, + typename winrt_ssocket_service< + Protocol1>::implementation_type& other_impl) + { + this->base_move_construct(impl, other_impl); + + impl.protocol_ = protocol_type(other_impl.protocol_); + other_impl.protocol_ = typename Protocol1::endpoint().protocol(); + } + + // Open a new socket implementation. + asio::error_code open(implementation_type& impl, + const protocol_type& protocol, asio::error_code& ec) + { + if (is_open(impl)) + { + ec = asio::error::already_open; + return ec; + } + + try + { + impl.socket_ = ref new Windows::Networking::Sockets::StreamSocket; + impl.protocol_ = protocol; + ec = asio::error_code(); + } + catch (Platform::Exception^ e) + { + ec = asio::error_code(e->HResult, + asio::system_category()); + } + + return ec; + } + + // Assign a native socket to a socket implementation. + asio::error_code assign(implementation_type& impl, + const protocol_type& protocol, const native_handle_type& native_socket, + asio::error_code& ec) + { + if (is_open(impl)) + { + ec = asio::error::already_open; + return ec; + } + + impl.socket_ = native_socket; + impl.protocol_ = protocol; + ec = asio::error_code(); + + return ec; + } + + // Bind the socket to the specified local endpoint. + asio::error_code bind(implementation_type&, + const endpoint_type&, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Get the local endpoint. + endpoint_type local_endpoint(const implementation_type& impl, + asio::error_code& ec) const + { + endpoint_type endpoint; + endpoint.resize(do_get_endpoint(impl, true, + endpoint.data(), endpoint.size(), ec)); + return endpoint; + } + + // Get the remote endpoint. + endpoint_type remote_endpoint(const implementation_type& impl, + asio::error_code& ec) const + { + endpoint_type endpoint; + endpoint.resize(do_get_endpoint(impl, false, + endpoint.data(), endpoint.size(), ec)); + return endpoint; + } + + // Disable sends or receives on the socket. + asio::error_code shutdown(implementation_type&, + socket_base::shutdown_type, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Set a socket option. + template + asio::error_code set_option(implementation_type& impl, + const Option& option, asio::error_code& ec) + { + return do_set_option(impl, option.level(impl.protocol_), + option.name(impl.protocol_), option.data(impl.protocol_), + option.size(impl.protocol_), ec); + } + + // Get a socket option. + template + asio::error_code get_option(const implementation_type& impl, + Option& option, asio::error_code& ec) const + { + std::size_t size = option.size(impl.protocol_); + do_get_option(impl, option.level(impl.protocol_), + option.name(impl.protocol_), + option.data(impl.protocol_), &size, ec); + if (!ec) + option.resize(impl.protocol_, size); + return ec; + } + + // Connect the socket to the specified endpoint. + asio::error_code connect(implementation_type& impl, + const endpoint_type& peer_endpoint, asio::error_code& ec) + { + return do_connect(impl, peer_endpoint.data(), ec); + } + + // Start an asynchronous connect. + template + void async_connect(implementation_type& impl, + const endpoint_type& peer_endpoint, + Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef winrt_socket_connect_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(handler, io_ex); + + ASIO_HANDLER_CREATION((scheduler_.context(), + *p.p, "socket", &impl, 0, "async_connect")); + + start_connect_op(impl, peer_endpoint.data(), p.p, is_continuation); + p.v = p.p = 0; + } +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_WINRT_SSOCKET_SERVICE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_ssocket_service_base.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_ssocket_service_base.hpp new file mode 100644 index 000000000..ec2722f50 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_ssocket_service_base.hpp @@ -0,0 +1,362 @@ +// +// detail/winrt_ssocket_service_base.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WINRT_SSOCKET_SERVICE_BASE_HPP +#define ASIO_DETAIL_WINRT_SSOCKET_SERVICE_BASE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) + +#include "asio/buffer.hpp" +#include "asio/error.hpp" +#include "asio/execution_context.hpp" +#include "asio/socket_base.hpp" +#include "asio/detail/buffer_sequence_adapter.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/socket_types.hpp" +#include "asio/detail/winrt_async_manager.hpp" +#include "asio/detail/winrt_socket_recv_op.hpp" +#include "asio/detail/winrt_socket_send_op.hpp" + +#if defined(ASIO_HAS_IOCP) +# include "asio/detail/win_iocp_io_context.hpp" +#else // defined(ASIO_HAS_IOCP) +# include "asio/detail/scheduler.hpp" +#endif // defined(ASIO_HAS_IOCP) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class winrt_ssocket_service_base +{ +public: + // The native type of a socket. + typedef Windows::Networking::Sockets::StreamSocket^ native_handle_type; + + // The implementation type of the socket. + struct base_implementation_type + { + // Default constructor. + base_implementation_type() + : socket_(nullptr), + next_(0), + prev_(0) + { + } + + // The underlying native socket. + native_handle_type socket_; + + // Pointers to adjacent socket implementations in linked list. + base_implementation_type* next_; + base_implementation_type* prev_; + }; + + // Constructor. + ASIO_DECL winrt_ssocket_service_base(execution_context& context); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void base_shutdown(); + + // Construct a new socket implementation. + ASIO_DECL void construct(base_implementation_type&); + + // Move-construct a new socket implementation. + ASIO_DECL void base_move_construct(base_implementation_type& impl, + base_implementation_type& other_impl) ASIO_NOEXCEPT; + + // Move-assign from another socket implementation. + ASIO_DECL void base_move_assign(base_implementation_type& impl, + winrt_ssocket_service_base& other_service, + base_implementation_type& other_impl); + + // Destroy a socket implementation. + ASIO_DECL void destroy(base_implementation_type& impl); + + // Determine whether the socket is open. + bool is_open(const base_implementation_type& impl) const + { + return impl.socket_ != nullptr; + } + + // Destroy a socket implementation. + ASIO_DECL asio::error_code close( + base_implementation_type& impl, asio::error_code& ec); + + // Release ownership of the socket. + ASIO_DECL native_handle_type release( + base_implementation_type& impl, asio::error_code& ec); + + // Get the native socket representation. + native_handle_type native_handle(base_implementation_type& impl) + { + return impl.socket_; + } + + // Cancel all operations associated with the socket. + asio::error_code cancel(base_implementation_type&, + asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Determine whether the socket is at the out-of-band data mark. + bool at_mark(const base_implementation_type&, + asio::error_code& ec) const + { + ec = asio::error::operation_not_supported; + return false; + } + + // Determine the number of bytes available for reading. + std::size_t available(const base_implementation_type&, + asio::error_code& ec) const + { + ec = asio::error::operation_not_supported; + return 0; + } + + // Perform an IO control command on the socket. + template + asio::error_code io_control(base_implementation_type&, + IO_Control_Command&, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Gets the non-blocking mode of the socket. + bool non_blocking(const base_implementation_type&) const + { + return false; + } + + // Sets the non-blocking mode of the socket. + asio::error_code non_blocking(base_implementation_type&, + bool, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Gets the non-blocking mode of the native socket implementation. + bool native_non_blocking(const base_implementation_type&) const + { + return false; + } + + // Sets the non-blocking mode of the native socket implementation. + asio::error_code native_non_blocking(base_implementation_type&, + bool, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return ec; + } + + // Send the given data to the peer. + template + std::size_t send(base_implementation_type& impl, + const ConstBufferSequence& buffers, + socket_base::message_flags flags, asio::error_code& ec) + { + return do_send(impl, + buffer_sequence_adapter::first(buffers), flags, ec); + } + + // Wait until data can be sent without blocking. + std::size_t send(base_implementation_type&, const null_buffers&, + socket_base::message_flags, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return 0; + } + + // Start an asynchronous send. The data being sent must be valid for the + // lifetime of the asynchronous operation. + template + void async_send(base_implementation_type& impl, + const ConstBufferSequence& buffers, socket_base::message_flags flags, + Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef winrt_socket_send_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(buffers, handler, io_ex); + + ASIO_HANDLER_CREATION((scheduler_.context(), + *p.p, "socket", &impl, 0, "async_send")); + + start_send_op(impl, + buffer_sequence_adapter::first(buffers), + flags, p.p, is_continuation); + p.v = p.p = 0; + } + + // Start an asynchronous wait until data can be sent without blocking. + template + void async_send(base_implementation_type&, const null_buffers&, + socket_base::message_flags, Handler& handler, const IoExecutor& io_ex) + { + asio::error_code ec = asio::error::operation_not_supported; + const std::size_t bytes_transferred = 0; + asio::post(io_ex, + detail::bind_handler(handler, ec, bytes_transferred)); + } + + // Receive some data from the peer. Returns the number of bytes received. + template + std::size_t receive(base_implementation_type& impl, + const MutableBufferSequence& buffers, + socket_base::message_flags flags, asio::error_code& ec) + { + return do_receive(impl, + buffer_sequence_adapter::first(buffers), flags, ec); + } + + // Wait until data can be received without blocking. + std::size_t receive(base_implementation_type&, const null_buffers&, + socket_base::message_flags, asio::error_code& ec) + { + ec = asio::error::operation_not_supported; + return 0; + } + + // Start an asynchronous receive. The buffer for the data being received + // must be valid for the lifetime of the asynchronous operation. + template + void async_receive(base_implementation_type& impl, + const MutableBufferSequence& buffers, socket_base::message_flags flags, + Handler& handler, const IoExecutor& io_ex) + { + bool is_continuation = + asio_handler_cont_helpers::is_continuation(handler); + + // Allocate and construct an operation to wrap the handler. + typedef winrt_socket_recv_op op; + typename op::ptr p = { asio::detail::addressof(handler), + op::ptr::allocate(handler), 0 }; + p.p = new (p.v) op(buffers, handler, io_ex); + + ASIO_HANDLER_CREATION((scheduler_.context(), + *p.p, "socket", &impl, 0, "async_receive")); + + start_receive_op(impl, + buffer_sequence_adapter::first(buffers), + flags, p.p, is_continuation); + p.v = p.p = 0; + } + + // Wait until data can be received without blocking. + template + void async_receive(base_implementation_type&, const null_buffers&, + socket_base::message_flags, Handler& handler, const IoExecutor& io_ex) + { + asio::error_code ec = asio::error::operation_not_supported; + const std::size_t bytes_transferred = 0; + asio::post(io_ex, + detail::bind_handler(handler, ec, bytes_transferred)); + } + +protected: + // Helper function to obtain endpoints associated with the connection. + ASIO_DECL std::size_t do_get_endpoint( + const base_implementation_type& impl, bool local, + void* addr, std::size_t addr_len, asio::error_code& ec) const; + + // Helper function to set a socket option. + ASIO_DECL asio::error_code do_set_option( + base_implementation_type& impl, + int level, int optname, const void* optval, + std::size_t optlen, asio::error_code& ec); + + // Helper function to get a socket option. + ASIO_DECL void do_get_option( + const base_implementation_type& impl, + int level, int optname, void* optval, + std::size_t* optlen, asio::error_code& ec) const; + + // Helper function to perform a synchronous connect. + ASIO_DECL asio::error_code do_connect( + base_implementation_type& impl, + const void* addr, asio::error_code& ec); + + // Helper function to start an asynchronous connect. + ASIO_DECL void start_connect_op( + base_implementation_type& impl, const void* addr, + winrt_async_op* op, bool is_continuation); + + // Helper function to perform a synchronous send. + ASIO_DECL std::size_t do_send( + base_implementation_type& impl, const asio::const_buffer& data, + socket_base::message_flags flags, asio::error_code& ec); + + // Helper function to start an asynchronous send. + ASIO_DECL void start_send_op(base_implementation_type& impl, + const asio::const_buffer& data, socket_base::message_flags flags, + winrt_async_op* op, bool is_continuation); + + // Helper function to perform a synchronous receive. + ASIO_DECL std::size_t do_receive( + base_implementation_type& impl, const asio::mutable_buffer& data, + socket_base::message_flags flags, asio::error_code& ec); + + // Helper function to start an asynchronous receive. + ASIO_DECL void start_receive_op(base_implementation_type& impl, + const asio::mutable_buffer& data, socket_base::message_flags flags, + winrt_async_op* op, + bool is_continuation); + + // The scheduler implementation used for delivering completions. +#if defined(ASIO_HAS_IOCP) + typedef class win_iocp_io_context scheduler_impl; +#else + typedef class scheduler scheduler_impl; +#endif + scheduler_impl& scheduler_; + + // The manager that keeps track of outstanding operations. + winrt_async_manager& async_manager_; + + // Mutex to protect access to the linked list of implementations. + asio::detail::mutex mutex_; + + // The head of a linked list of all implementations. + base_implementation_type* impl_list_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/winrt_ssocket_service_base.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_WINRT_SSOCKET_SERVICE_BASE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_timer_scheduler.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_timer_scheduler.hpp new file mode 100644 index 000000000..f27ed3650 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_timer_scheduler.hpp @@ -0,0 +1,147 @@ +// +// detail/winrt_timer_scheduler.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WINRT_TIMER_SCHEDULER_HPP +#define ASIO_DETAIL_WINRT_TIMER_SCHEDULER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) + +#include +#include "asio/detail/event.hpp" +#include "asio/detail/limits.hpp" +#include "asio/detail/mutex.hpp" +#include "asio/detail/op_queue.hpp" +#include "asio/detail/thread.hpp" +#include "asio/detail/timer_queue_base.hpp" +#include "asio/detail/timer_queue_set.hpp" +#include "asio/detail/wait_op.hpp" +#include "asio/execution_context.hpp" + +#if defined(ASIO_HAS_IOCP) +# include "asio/detail/win_iocp_io_context.hpp" +#else // defined(ASIO_HAS_IOCP) +# include "asio/detail/scheduler.hpp" +#endif // defined(ASIO_HAS_IOCP) + +#if defined(ASIO_HAS_IOCP) +# include "asio/detail/thread.hpp" +#endif // defined(ASIO_HAS_IOCP) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class winrt_timer_scheduler + : public execution_context_service_base +{ +public: + // Constructor. + ASIO_DECL winrt_timer_scheduler(execution_context& context); + + // Destructor. + ASIO_DECL ~winrt_timer_scheduler(); + + // Destroy all user-defined handler objects owned by the service. + ASIO_DECL void shutdown(); + + // Recreate internal descriptors following a fork. + ASIO_DECL void notify_fork(execution_context::fork_event fork_ev); + + // Initialise the task. No effect as this class uses its own thread. + ASIO_DECL void init_task(); + + // Add a new timer queue to the reactor. + template + void add_timer_queue(timer_queue& queue); + + // Remove a timer queue from the reactor. + template + void remove_timer_queue(timer_queue& queue); + + // Schedule a new operation in the given timer queue to expire at the + // specified absolute time. + template + void schedule_timer(timer_queue& queue, + const typename Time_Traits::time_type& time, + typename timer_queue::per_timer_data& timer, wait_op* op); + + // Cancel the timer operations associated with the given token. Returns the + // number of operations that have been posted or dispatched. + template + std::size_t cancel_timer(timer_queue& queue, + typename timer_queue::per_timer_data& timer, + std::size_t max_cancelled = (std::numeric_limits::max)()); + + // Move the timer operations associated with the given timer. + template + void move_timer(timer_queue& queue, + typename timer_queue::per_timer_data& to, + typename timer_queue::per_timer_data& from); + +private: + // Run the select loop in the thread. + ASIO_DECL void run_thread(); + + // Entry point for the select loop thread. + ASIO_DECL static void call_run_thread(winrt_timer_scheduler* reactor); + + // Helper function to add a new timer queue. + ASIO_DECL void do_add_timer_queue(timer_queue_base& queue); + + // Helper function to remove a timer queue. + ASIO_DECL void do_remove_timer_queue(timer_queue_base& queue); + + // The scheduler implementation used to post completions. +#if defined(ASIO_HAS_IOCP) + typedef class win_iocp_io_context scheduler_impl; +#else + typedef class scheduler scheduler_impl; +#endif + scheduler_impl& scheduler_; + + // Mutex used to protect internal variables. + asio::detail::mutex mutex_; + + // Event used to wake up background thread. + asio::detail::event event_; + + // The timer queues. + timer_queue_set timer_queues_; + + // The background thread that is waiting for timers to expire. + asio::detail::thread* thread_; + + // Does the background thread need to stop. + bool stop_thread_; + + // Whether the service has been shut down. + bool shutdown_; +}; + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/detail/impl/winrt_timer_scheduler.hpp" +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/winrt_timer_scheduler.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_WINRT_TIMER_SCHEDULER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_utils.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_utils.hpp new file mode 100644 index 000000000..04b3e6fb7 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winrt_utils.hpp @@ -0,0 +1,106 @@ +// +// detail/winrt_utils.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WINRT_UTILS_HPP +#define ASIO_DETAIL_WINRT_UTILS_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS_RUNTIME) + +#include +#include +#include +#include +#include +#include +#include +#include "asio/buffer.hpp" +#include "asio/error_code.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/socket_ops.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { +namespace winrt_utils { + +inline Platform::String^ string(const char* from) +{ + std::wstring tmp(from, from + std::strlen(from)); + return ref new Platform::String(tmp.c_str()); +} + +inline Platform::String^ string(const std::string& from) +{ + std::wstring tmp(from.begin(), from.end()); + return ref new Platform::String(tmp.c_str()); +} + +inline std::string string(Platform::String^ from) +{ + std::wstring_convert> converter; + return converter.to_bytes(from->Data()); +} + +inline Platform::String^ string(unsigned short from) +{ + return string(std::to_string(from)); +} + +template +inline Platform::String^ string(const T& from) +{ + return string(from.to_string()); +} + +inline int integer(Platform::String^ from) +{ + return _wtoi(from->Data()); +} + +template +inline Windows::Networking::HostName^ host_name(const T& from) +{ + return ref new Windows::Networking::HostName((string)(from)); +} + +template +inline Windows::Storage::Streams::IBuffer^ buffer_dup( + const ConstBufferSequence& buffers) +{ + using Microsoft::WRL::ComPtr; + using asio::buffer_size; + std::size_t size = buffer_size(buffers); + auto b = ref new Windows::Storage::Streams::Buffer(size); + ComPtr insp = reinterpret_cast(b); + ComPtr bacc; + insp.As(&bacc); + byte* bytes = nullptr; + bacc->Buffer(&bytes); + asio::buffer_copy(asio::buffer(bytes, size), buffers); + b->Length = size; + return b; +} + +} // namespace winrt_utils +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // defined(ASIO_WINDOWS_RUNTIME) + +#endif // ASIO_DETAIL_WINRT_UTILS_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winsock_init.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winsock_init.hpp new file mode 100644 index 000000000..cde044f4f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/winsock_init.hpp @@ -0,0 +1,128 @@ +// +// detail/winsock_init.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WINSOCK_INIT_HPP +#define ASIO_DETAIL_WINSOCK_INIT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +class winsock_init_base +{ +protected: + // Structure to track result of initialisation and number of uses. POD is used + // to ensure that the values are zero-initialised prior to any code being run. + struct data + { + long init_count_; + long result_; + }; + + ASIO_DECL static void startup(data& d, + unsigned char major, unsigned char minor); + + ASIO_DECL static void manual_startup(data& d); + + ASIO_DECL static void cleanup(data& d); + + ASIO_DECL static void manual_cleanup(data& d); + + ASIO_DECL static void throw_on_error(data& d); +}; + +template +class winsock_init : private winsock_init_base +{ +public: + winsock_init(bool allow_throw = true) + { + startup(data_, Major, Minor); + if (allow_throw) + throw_on_error(data_); + } + + winsock_init(const winsock_init&) + { + startup(data_, Major, Minor); + throw_on_error(data_); + } + + ~winsock_init() + { + cleanup(data_); + } + + // This class may be used to indicate that user code will manage Winsock + // initialisation and cleanup. This may be required in the case of a DLL, for + // example, where it is not safe to initialise Winsock from global object + // constructors. + // + // To prevent asio from initialising Winsock, the object must be constructed + // before any Asio's own global objects. With MSVC, this may be accomplished + // by adding the following code to the DLL: + // + // #pragma warning(push) + // #pragma warning(disable:4073) + // #pragma init_seg(lib) + // asio::detail::winsock_init<>::manual manual_winsock_init; + // #pragma warning(pop) + class manual + { + public: + manual() + { + manual_startup(data_); + } + + manual(const manual&) + { + manual_startup(data_); + } + + ~manual() + { + manual_cleanup(data_); + } + }; + +private: + friend class manual; + static data data_; +}; + +template +winsock_init_base::data winsock_init::data_; + +// Static variable to ensure that winsock is initialised before main, and +// therefore before any other threads can get started. +static const winsock_init<>& winsock_init_instance = winsock_init<>(false); + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/detail/impl/winsock_init.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // defined(ASIO_WINDOWS) || defined(__CYGWIN__) + +#endif // ASIO_DETAIL_WINSOCK_INIT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/work_dispatcher.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/work_dispatcher.hpp new file mode 100644 index 000000000..5b4433d7d --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/work_dispatcher.hpp @@ -0,0 +1,148 @@ +// +// detail/work_dispatcher.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WORK_DISPATCHER_HPP +#define ASIO_DETAIL_WORK_DISPATCHER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/associated_executor.hpp" +#include "asio/associated_allocator.hpp" +#include "asio/executor_work_guard.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/allocator.hpp" +#include "asio/execution/blocking.hpp" +#include "asio/execution/outstanding_work.hpp" +#include "asio/prefer.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +template +struct is_work_dispatcher_required : true_type +{ +}; + +template +struct is_work_dispatcher_required::asio_associated_executor_is_unspecialised, + void + >::value + >::type> : false_type +{ +}; + +template +class work_dispatcher +{ +public: + template + work_dispatcher(ASIO_MOVE_ARG(CompletionHandler) handler, + const Executor& handler_ex) + : handler_(ASIO_MOVE_CAST(CompletionHandler)(handler)), + executor_(asio::prefer(handler_ex, + execution::outstanding_work.tracked)) + { + } + +#if defined(ASIO_HAS_MOVE) + work_dispatcher(const work_dispatcher& other) + : handler_(other.handler_), + executor_(other.executor_) + { + } + + work_dispatcher(work_dispatcher&& other) + : handler_(ASIO_MOVE_CAST(Handler)(other.handler_)), + executor_(ASIO_MOVE_CAST(work_executor_type)(other.executor_)) + { + } +#endif // defined(ASIO_HAS_MOVE) + + void operator()() + { + execution::execute( + asio::prefer(executor_, + execution::blocking.possibly, + execution::allocator((get_associated_allocator)(handler_))), + ASIO_MOVE_CAST(Handler)(handler_)); + } + +private: + typedef typename decay< + typename prefer_result::type + >::type work_executor_type; + + Handler handler_; + work_executor_type executor_; +}; + +#if !defined(ASIO_NO_TS_EXECUTORS) + +template +class work_dispatcher::value>::type> +{ +public: + template + work_dispatcher(ASIO_MOVE_ARG(CompletionHandler) handler, + const Executor& handler_ex) + : work_(handler_ex), + handler_(ASIO_MOVE_CAST(CompletionHandler)(handler)) + { + } + +#if defined(ASIO_HAS_MOVE) + work_dispatcher(const work_dispatcher& other) + : work_(other.work_), + handler_(other.handler_) + { + } + + work_dispatcher(work_dispatcher&& other) + : work_(ASIO_MOVE_CAST(executor_work_guard)(other.work_)), + handler_(ASIO_MOVE_CAST(Handler)(other.handler_)) + { + } +#endif // defined(ASIO_HAS_MOVE) + + void operator()() + { + typename associated_allocator::type alloc( + (get_associated_allocator)(handler_)); + work_.get_executor().dispatch( + ASIO_MOVE_CAST(Handler)(handler_), alloc); + work_.reset(); + } + +private: + executor_work_guard work_; + Handler handler_; +}; + +#endif // !defined(ASIO_NO_TS_EXECUTORS) + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_WORK_DISPATCHER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/wrapped_handler.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/wrapped_handler.hpp new file mode 100644 index 000000000..b1aed8bb4 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/detail/wrapped_handler.hpp @@ -0,0 +1,327 @@ +// +// detail/wrapped_handler.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DETAIL_WRAPPED_HANDLER_HPP +#define ASIO_DETAIL_WRAPPED_HANDLER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/bind_handler.hpp" +#include "asio/detail/handler_alloc_helpers.hpp" +#include "asio/detail/handler_cont_helpers.hpp" +#include "asio/detail/handler_invoke_helpers.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace detail { + +struct is_continuation_delegated +{ + template + bool operator()(Dispatcher&, Handler& handler) const + { + return asio_handler_cont_helpers::is_continuation(handler); + } +}; + +struct is_continuation_if_running +{ + template + bool operator()(Dispatcher& dispatcher, Handler&) const + { + return dispatcher.running_in_this_thread(); + } +}; + +template +class wrapped_handler +{ +public: + typedef void result_type; + + wrapped_handler(Dispatcher dispatcher, Handler& handler) + : dispatcher_(dispatcher), + handler_(ASIO_MOVE_CAST(Handler)(handler)) + { + } + +#if defined(ASIO_HAS_MOVE) + wrapped_handler(const wrapped_handler& other) + : dispatcher_(other.dispatcher_), + handler_(other.handler_) + { + } + + wrapped_handler(wrapped_handler&& other) + : dispatcher_(other.dispatcher_), + handler_(ASIO_MOVE_CAST(Handler)(other.handler_)) + { + } +#endif // defined(ASIO_HAS_MOVE) + + void operator()() + { + dispatcher_.dispatch(ASIO_MOVE_CAST(Handler)(handler_)); + } + + void operator()() const + { + dispatcher_.dispatch(handler_); + } + + template + void operator()(const Arg1& arg1) + { + dispatcher_.dispatch(detail::bind_handler(handler_, arg1)); + } + + template + void operator()(const Arg1& arg1) const + { + dispatcher_.dispatch(detail::bind_handler(handler_, arg1)); + } + + template + void operator()(const Arg1& arg1, const Arg2& arg2) + { + dispatcher_.dispatch(detail::bind_handler(handler_, arg1, arg2)); + } + + template + void operator()(const Arg1& arg1, const Arg2& arg2) const + { + dispatcher_.dispatch(detail::bind_handler(handler_, arg1, arg2)); + } + + template + void operator()(const Arg1& arg1, const Arg2& arg2, const Arg3& arg3) + { + dispatcher_.dispatch(detail::bind_handler(handler_, arg1, arg2, arg3)); + } + + template + void operator()(const Arg1& arg1, const Arg2& arg2, const Arg3& arg3) const + { + dispatcher_.dispatch(detail::bind_handler(handler_, arg1, arg2, arg3)); + } + + template + void operator()(const Arg1& arg1, const Arg2& arg2, const Arg3& arg3, + const Arg4& arg4) + { + dispatcher_.dispatch( + detail::bind_handler(handler_, arg1, arg2, arg3, arg4)); + } + + template + void operator()(const Arg1& arg1, const Arg2& arg2, const Arg3& arg3, + const Arg4& arg4) const + { + dispatcher_.dispatch( + detail::bind_handler(handler_, arg1, arg2, arg3, arg4)); + } + + template + void operator()(const Arg1& arg1, const Arg2& arg2, const Arg3& arg3, + const Arg4& arg4, const Arg5& arg5) + { + dispatcher_.dispatch( + detail::bind_handler(handler_, arg1, arg2, arg3, arg4, arg5)); + } + + template + void operator()(const Arg1& arg1, const Arg2& arg2, const Arg3& arg3, + const Arg4& arg4, const Arg5& arg5) const + { + dispatcher_.dispatch( + detail::bind_handler(handler_, arg1, arg2, arg3, arg4, arg5)); + } + +//private: + Dispatcher dispatcher_; + Handler handler_; +}; + +template +class rewrapped_handler +{ +public: + explicit rewrapped_handler(Handler& handler, const Context& context) + : context_(context), + handler_(ASIO_MOVE_CAST(Handler)(handler)) + { + } + + explicit rewrapped_handler(const Handler& handler, const Context& context) + : context_(context), + handler_(handler) + { + } + +#if defined(ASIO_HAS_MOVE) + rewrapped_handler(const rewrapped_handler& other) + : context_(other.context_), + handler_(other.handler_) + { + } + + rewrapped_handler(rewrapped_handler&& other) + : context_(ASIO_MOVE_CAST(Context)(other.context_)), + handler_(ASIO_MOVE_CAST(Handler)(other.handler_)) + { + } +#endif // defined(ASIO_HAS_MOVE) + + void operator()() + { + handler_(); + } + + void operator()() const + { + handler_(); + } + +//private: + Context context_; + Handler handler_; +}; + +template +inline asio_handler_allocate_is_deprecated +asio_handler_allocate(std::size_t size, + wrapped_handler* this_handler) +{ +#if defined(ASIO_NO_DEPRECATED) + asio_handler_alloc_helpers::allocate(size, this_handler->handler_); + return asio_handler_allocate_is_no_longer_used(); +#else // defined(ASIO_NO_DEPRECATED) + return asio_handler_alloc_helpers::allocate( + size, this_handler->handler_); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline asio_handler_deallocate_is_deprecated +asio_handler_deallocate(void* pointer, std::size_t size, + wrapped_handler* this_handler) +{ + asio_handler_alloc_helpers::deallocate( + pointer, size, this_handler->handler_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_deallocate_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline bool asio_handler_is_continuation( + wrapped_handler* this_handler) +{ + return IsContinuation()(this_handler->dispatcher_, this_handler->handler_); +} + +template +inline asio_handler_invoke_is_deprecated +asio_handler_invoke(Function& function, + wrapped_handler* this_handler) +{ + this_handler->dispatcher_.dispatch( + rewrapped_handler( + function, this_handler->handler_)); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_invoke_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline asio_handler_invoke_is_deprecated +asio_handler_invoke(const Function& function, + wrapped_handler* this_handler) +{ + this_handler->dispatcher_.dispatch( + rewrapped_handler( + function, this_handler->handler_)); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_invoke_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline asio_handler_allocate_is_deprecated +asio_handler_allocate(std::size_t size, + rewrapped_handler* this_handler) +{ +#if defined(ASIO_NO_DEPRECATED) + asio_handler_alloc_helpers::allocate(size, this_handler->handler_); + return asio_handler_allocate_is_no_longer_used(); +#else // defined(ASIO_NO_DEPRECATED) + return asio_handler_alloc_helpers::allocate( + size, this_handler->handler_); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline asio_handler_deallocate_is_deprecated +asio_handler_deallocate(void* pointer, std::size_t size, + rewrapped_handler* this_handler) +{ + asio_handler_alloc_helpers::deallocate( + pointer, size, this_handler->context_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_deallocate_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline bool asio_handler_is_continuation( + rewrapped_handler* this_handler) +{ + return asio_handler_cont_helpers::is_continuation( + this_handler->context_); +} + +template +inline asio_handler_invoke_is_deprecated +asio_handler_invoke(Function& function, + rewrapped_handler* this_handler) +{ + asio_handler_invoke_helpers::invoke( + function, this_handler->context_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_invoke_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +template +inline asio_handler_invoke_is_deprecated +asio_handler_invoke(const Function& function, + rewrapped_handler* this_handler) +{ + asio_handler_invoke_helpers::invoke( + function, this_handler->context_); +#if defined(ASIO_NO_DEPRECATED) + return asio_handler_invoke_is_no_longer_used(); +#endif // defined(ASIO_NO_DEPRECATED) +} + +} // namespace detail +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_DETAIL_WRAPPED_HANDLER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/dispatch.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/dispatch.hpp new file mode 100644 index 000000000..2e5d197fd --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/dispatch.hpp @@ -0,0 +1,121 @@ +// +// dispatch.hpp +// ~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_DISPATCH_HPP +#define ASIO_DISPATCH_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/async_result.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution_context.hpp" +#include "asio/execution/executor.hpp" +#include "asio/is_executor.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +/// Submits a completion token or function object for execution. +/** + * This function submits an object for execution using the object's associated + * executor. The function object may be called from the current thread prior to + * returning from dispatch(). Otherwise, it is queued for execution. + * + * This function has the following effects: + * + * @li Constructs a function object handler of type @c Handler, initialized + * with handler(forward(token)). + * + * @li Constructs an object @c result of type async_result, + * initializing the object as result(handler). + * + * @li Obtains the handler's associated executor object @c ex by performing + * get_associated_executor(handler). + * + * @li Obtains the handler's associated allocator object @c alloc by performing + * get_associated_allocator(handler). + * + * @li Performs ex.dispatch(std::move(handler), alloc). + * + * @li Returns result.get(). + */ +template +ASIO_INITFN_AUTO_RESULT_TYPE(CompletionToken, void()) dispatch( + ASIO_MOVE_ARG(CompletionToken) token); + +/// Submits a completion token or function object for execution. +/** + * This function submits an object for execution using the specified executor. + * The function object may be called from the current thread prior to returning + * from dispatch(). Otherwise, it is queued for execution. + * + * This function has the following effects: + * + * @li Constructs a function object handler of type @c Handler, initialized + * with handler(forward(token)). + * + * @li Constructs an object @c result of type async_result, + * initializing the object as result(handler). + * + * @li Obtains the handler's associated executor object @c ex1 by performing + * get_associated_executor(handler). + * + * @li Creates a work object @c w by performing make_work(ex1). + * + * @li Obtains the handler's associated allocator object @c alloc by performing + * get_associated_allocator(handler). + * + * @li Constructs a function object @c f with a function call operator that + * performs ex1.dispatch(std::move(handler), alloc) followed by + * w.reset(). + * + * @li Performs Executor(ex).dispatch(std::move(f), alloc). + * + * @li Returns result.get(). + */ +template +ASIO_INITFN_AUTO_RESULT_TYPE(CompletionToken, void()) dispatch( + const Executor& ex, + ASIO_MOVE_ARG(CompletionToken) token + ASIO_DEFAULT_COMPLETION_TOKEN(Executor), + typename enable_if< + execution::is_executor::value || is_executor::value + >::type* = 0); + +/// Submits a completion token or function object for execution. +/** + * @returns dispatch(ctx.get_executor(), + * forward(token)). + */ +template +ASIO_INITFN_AUTO_RESULT_TYPE(CompletionToken, void()) dispatch( + ExecutionContext& ctx, + ASIO_MOVE_ARG(CompletionToken) token + ASIO_DEFAULT_COMPLETION_TOKEN( + typename ExecutionContext::executor_type), + typename enable_if::value>::type* = 0); + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#include "asio/impl/dispatch.hpp" + +#endif // ASIO_DISPATCH_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/error.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/error.hpp new file mode 100644 index 000000000..c685d4a20 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/error.hpp @@ -0,0 +1,356 @@ +// +// error.hpp +// ~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_ERROR_HPP +#define ASIO_ERROR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/error_code.hpp" +#include "asio/system_error.hpp" +#if defined(ASIO_WINDOWS) \ + || defined(__CYGWIN__) \ + || defined(ASIO_WINDOWS_RUNTIME) +# include +#else +# include +# include +#endif + +#if defined(GENERATING_DOCUMENTATION) +/// INTERNAL ONLY. +# define ASIO_NATIVE_ERROR(e) implementation_defined +/// INTERNAL ONLY. +# define ASIO_SOCKET_ERROR(e) implementation_defined +/// INTERNAL ONLY. +# define ASIO_NETDB_ERROR(e) implementation_defined +/// INTERNAL ONLY. +# define ASIO_GETADDRINFO_ERROR(e) implementation_defined +/// INTERNAL ONLY. +# define ASIO_WIN_OR_POSIX(e_win, e_posix) implementation_defined +#elif defined(ASIO_WINDOWS_RUNTIME) +# define ASIO_NATIVE_ERROR(e) __HRESULT_FROM_WIN32(e) +# define ASIO_SOCKET_ERROR(e) __HRESULT_FROM_WIN32(WSA ## e) +# define ASIO_NETDB_ERROR(e) __HRESULT_FROM_WIN32(WSA ## e) +# define ASIO_GETADDRINFO_ERROR(e) __HRESULT_FROM_WIN32(WSA ## e) +# define ASIO_WIN_OR_POSIX(e_win, e_posix) e_win +#elif defined(ASIO_WINDOWS) || defined(__CYGWIN__) +# define ASIO_NATIVE_ERROR(e) e +# define ASIO_SOCKET_ERROR(e) WSA ## e +# define ASIO_NETDB_ERROR(e) WSA ## e +# define ASIO_GETADDRINFO_ERROR(e) WSA ## e +# define ASIO_WIN_OR_POSIX(e_win, e_posix) e_win +#else +# define ASIO_NATIVE_ERROR(e) e +# define ASIO_SOCKET_ERROR(e) e +# define ASIO_NETDB_ERROR(e) e +# define ASIO_GETADDRINFO_ERROR(e) e +# define ASIO_WIN_OR_POSIX(e_win, e_posix) e_posix +#endif + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace error { + +enum basic_errors +{ + /// Permission denied. + access_denied = ASIO_SOCKET_ERROR(EACCES), + + /// Address family not supported by protocol. + address_family_not_supported = ASIO_SOCKET_ERROR(EAFNOSUPPORT), + + /// Address already in use. + address_in_use = ASIO_SOCKET_ERROR(EADDRINUSE), + + /// Transport endpoint is already connected. + already_connected = ASIO_SOCKET_ERROR(EISCONN), + + /// Operation already in progress. + already_started = ASIO_SOCKET_ERROR(EALREADY), + + /// Broken pipe. + broken_pipe = ASIO_WIN_OR_POSIX( + ASIO_NATIVE_ERROR(ERROR_BROKEN_PIPE), + ASIO_NATIVE_ERROR(EPIPE)), + + /// A connection has been aborted. + connection_aborted = ASIO_SOCKET_ERROR(ECONNABORTED), + + /// Connection refused. + connection_refused = ASIO_SOCKET_ERROR(ECONNREFUSED), + + /// Connection reset by peer. + connection_reset = ASIO_SOCKET_ERROR(ECONNRESET), + + /// Bad file descriptor. + bad_descriptor = ASIO_SOCKET_ERROR(EBADF), + + /// Bad address. + fault = ASIO_SOCKET_ERROR(EFAULT), + + /// No route to host. + host_unreachable = ASIO_SOCKET_ERROR(EHOSTUNREACH), + + /// Operation now in progress. + in_progress = ASIO_SOCKET_ERROR(EINPROGRESS), + + /// Interrupted system call. + interrupted = ASIO_SOCKET_ERROR(EINTR), + + /// Invalid argument. + invalid_argument = ASIO_SOCKET_ERROR(EINVAL), + + /// Message too long. + message_size = ASIO_SOCKET_ERROR(EMSGSIZE), + + /// The name was too long. + name_too_long = ASIO_SOCKET_ERROR(ENAMETOOLONG), + + /// Network is down. + network_down = ASIO_SOCKET_ERROR(ENETDOWN), + + /// Network dropped connection on reset. + network_reset = ASIO_SOCKET_ERROR(ENETRESET), + + /// Network is unreachable. + network_unreachable = ASIO_SOCKET_ERROR(ENETUNREACH), + + /// Too many open files. + no_descriptors = ASIO_SOCKET_ERROR(EMFILE), + + /// No buffer space available. + no_buffer_space = ASIO_SOCKET_ERROR(ENOBUFS), + + /// Cannot allocate memory. + no_memory = ASIO_WIN_OR_POSIX( + ASIO_NATIVE_ERROR(ERROR_OUTOFMEMORY), + ASIO_NATIVE_ERROR(ENOMEM)), + + /// Operation not permitted. + no_permission = ASIO_WIN_OR_POSIX( + ASIO_NATIVE_ERROR(ERROR_ACCESS_DENIED), + ASIO_NATIVE_ERROR(EPERM)), + + /// Protocol not available. + no_protocol_option = ASIO_SOCKET_ERROR(ENOPROTOOPT), + + /// No such device. + no_such_device = ASIO_WIN_OR_POSIX( + ASIO_NATIVE_ERROR(ERROR_BAD_UNIT), + ASIO_NATIVE_ERROR(ENODEV)), + + /// Transport endpoint is not connected. + not_connected = ASIO_SOCKET_ERROR(ENOTCONN), + + /// Socket operation on non-socket. + not_socket = ASIO_SOCKET_ERROR(ENOTSOCK), + + /// Operation cancelled. + operation_aborted = ASIO_WIN_OR_POSIX( + ASIO_NATIVE_ERROR(ERROR_OPERATION_ABORTED), + ASIO_NATIVE_ERROR(ECANCELED)), + + /// Operation not supported. + operation_not_supported = ASIO_SOCKET_ERROR(EOPNOTSUPP), + + /// Cannot send after transport endpoint shutdown. + shut_down = ASIO_SOCKET_ERROR(ESHUTDOWN), + + /// Connection timed out. + timed_out = ASIO_SOCKET_ERROR(ETIMEDOUT), + + /// Resource temporarily unavailable. + try_again = ASIO_WIN_OR_POSIX( + ASIO_NATIVE_ERROR(ERROR_RETRY), + ASIO_NATIVE_ERROR(EAGAIN)), + + /// The socket is marked non-blocking and the requested operation would block. + would_block = ASIO_SOCKET_ERROR(EWOULDBLOCK) +}; + +enum netdb_errors +{ + /// Host not found (authoritative). + host_not_found = ASIO_NETDB_ERROR(HOST_NOT_FOUND), + + /// Host not found (non-authoritative). + host_not_found_try_again = ASIO_NETDB_ERROR(TRY_AGAIN), + + /// The query is valid but does not have associated address data. + no_data = ASIO_NETDB_ERROR(NO_DATA), + + /// A non-recoverable error occurred. + no_recovery = ASIO_NETDB_ERROR(NO_RECOVERY) +}; + +enum addrinfo_errors +{ + /// The service is not supported for the given socket type. + service_not_found = ASIO_WIN_OR_POSIX( + ASIO_NATIVE_ERROR(WSATYPE_NOT_FOUND), + ASIO_GETADDRINFO_ERROR(EAI_SERVICE)), + + /// The socket type is not supported. + socket_type_not_supported = ASIO_WIN_OR_POSIX( + ASIO_NATIVE_ERROR(WSAESOCKTNOSUPPORT), + ASIO_GETADDRINFO_ERROR(EAI_SOCKTYPE)) +}; + +enum misc_errors +{ + /// Already open. + already_open = 1, + + /// End of file or stream. + eof, + + /// Element not found. + not_found, + + /// The descriptor cannot fit into the select system call's fd_set. + fd_set_failure +}; + +inline const asio::error_category& get_system_category() +{ + return asio::system_category(); +} + +#if !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) + +extern ASIO_DECL +const asio::error_category& get_netdb_category(); + +extern ASIO_DECL +const asio::error_category& get_addrinfo_category(); + +#else // !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) + +inline const asio::error_category& get_netdb_category() +{ + return get_system_category(); +} + +inline const asio::error_category& get_addrinfo_category() +{ + return get_system_category(); +} + +#endif // !defined(ASIO_WINDOWS) && !defined(__CYGWIN__) + +extern ASIO_DECL +const asio::error_category& get_misc_category(); + +static const asio::error_category& + system_category ASIO_UNUSED_VARIABLE + = asio::error::get_system_category(); +static const asio::error_category& + netdb_category ASIO_UNUSED_VARIABLE + = asio::error::get_netdb_category(); +static const asio::error_category& + addrinfo_category ASIO_UNUSED_VARIABLE + = asio::error::get_addrinfo_category(); +static const asio::error_category& + misc_category ASIO_UNUSED_VARIABLE + = asio::error::get_misc_category(); + +} // namespace error +} // namespace asio + +#if defined(ASIO_HAS_STD_SYSTEM_ERROR) +namespace std { + +template<> struct is_error_code_enum +{ + static const bool value = true; +}; + +template<> struct is_error_code_enum +{ + static const bool value = true; +}; + +template<> struct is_error_code_enum +{ + static const bool value = true; +}; + +template<> struct is_error_code_enum +{ + static const bool value = true; +}; + +} // namespace std +#endif // defined(ASIO_HAS_STD_SYSTEM_ERROR) + +namespace asio { +namespace error { + +inline asio::error_code make_error_code(basic_errors e) +{ + return asio::error_code( + static_cast(e), get_system_category()); +} + +inline asio::error_code make_error_code(netdb_errors e) +{ + return asio::error_code( + static_cast(e), get_netdb_category()); +} + +inline asio::error_code make_error_code(addrinfo_errors e) +{ + return asio::error_code( + static_cast(e), get_addrinfo_category()); +} + +inline asio::error_code make_error_code(misc_errors e) +{ + return asio::error_code( + static_cast(e), get_misc_category()); +} + +} // namespace error +namespace stream_errc { + // Simulates the proposed stream_errc scoped enum. + using error::eof; + using error::not_found; +} // namespace stream_errc +namespace socket_errc { + // Simulates the proposed socket_errc scoped enum. + using error::already_open; + using error::not_found; +} // namespace socket_errc +namespace resolver_errc { + // Simulates the proposed resolver_errc scoped enum. + using error::host_not_found; + const error::netdb_errors try_again = error::host_not_found_try_again; + using error::service_not_found; +} // namespace resolver_errc +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#undef ASIO_NATIVE_ERROR +#undef ASIO_SOCKET_ERROR +#undef ASIO_NETDB_ERROR +#undef ASIO_GETADDRINFO_ERROR +#undef ASIO_WIN_OR_POSIX + +#if defined(ASIO_HEADER_ONLY) +# include "asio/impl/error.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // ASIO_ERROR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/error_code.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/error_code.hpp new file mode 100644 index 000000000..2ff681401 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/error_code.hpp @@ -0,0 +1,202 @@ +// +// error_code.hpp +// ~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_ERROR_CODE_HPP +#define ASIO_ERROR_CODE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" + +#if defined(ASIO_HAS_STD_SYSTEM_ERROR) +# include +#else // defined(ASIO_HAS_STD_SYSTEM_ERROR) +# include +# include "asio/detail/noncopyable.hpp" +# if !defined(ASIO_NO_IOSTREAM) +# include +# endif // !defined(ASIO_NO_IOSTREAM) +#endif // defined(ASIO_HAS_STD_SYSTEM_ERROR) + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if defined(ASIO_HAS_STD_SYSTEM_ERROR) + +typedef std::error_category error_category; + +#else // defined(ASIO_HAS_STD_SYSTEM_ERROR) + +/// Base class for all error categories. +class error_category : private noncopyable +{ +public: + /// Destructor. + virtual ~error_category() + { + } + + /// Returns a string naming the error gategory. + virtual const char* name() const = 0; + + /// Returns a string describing the error denoted by @c value. + virtual std::string message(int value) const = 0; + + /// Equality operator to compare two error categories. + bool operator==(const error_category& rhs) const + { + return this == &rhs; + } + + /// Inequality operator to compare two error categories. + bool operator!=(const error_category& rhs) const + { + return !(*this == rhs); + } +}; + +#endif // defined(ASIO_HAS_STD_SYSTEM_ERROR) + +/// Returns the error category used for the system errors produced by asio. +extern ASIO_DECL const error_category& system_category(); + +#if defined(ASIO_HAS_STD_SYSTEM_ERROR) + +typedef std::error_code error_code; + +#else // defined(ASIO_HAS_STD_SYSTEM_ERROR) + +/// Class to represent an error code value. +class error_code +{ +public: + /// Default constructor. + error_code() + : value_(0), + category_(&system_category()) + { + } + + /// Construct with specific error code and category. + error_code(int v, const error_category& c) + : value_(v), + category_(&c) + { + } + + /// Construct from an error code enum. + template + error_code(ErrorEnum e) + { + *this = make_error_code(e); + } + + /// Clear the error value to the default. + void clear() + { + value_ = 0; + category_ = &system_category(); + } + + /// Assign a new error value. + void assign(int v, const error_category& c) + { + value_ = v; + category_ = &c; + } + + /// Get the error value. + int value() const + { + return value_; + } + + /// Get the error category. + const error_category& category() const + { + return *category_; + } + + /// Get the message associated with the error. + std::string message() const + { + return category_->message(value_); + } + + struct unspecified_bool_type_t + { + }; + + typedef void (*unspecified_bool_type)(unspecified_bool_type_t); + + static void unspecified_bool_true(unspecified_bool_type_t) {} + + /// Operator returns non-null if there is a non-success error code. + operator unspecified_bool_type() const + { + if (value_ == 0) + return 0; + else + return &error_code::unspecified_bool_true; + } + + /// Operator to test if the error represents success. + bool operator!() const + { + return value_ == 0; + } + + /// Equality operator to compare two error objects. + friend bool operator==(const error_code& e1, const error_code& e2) + { + return e1.value_ == e2.value_ && e1.category_ == e2.category_; + } + + /// Inequality operator to compare two error objects. + friend bool operator!=(const error_code& e1, const error_code& e2) + { + return e1.value_ != e2.value_ || e1.category_ != e2.category_; + } + +private: + // The value associated with the error code. + int value_; + + // The category associated with the error code. + const error_category* category_; +}; + +# if !defined(ASIO_NO_IOSTREAM) + +/// Output an error code. +template +std::basic_ostream& operator<<( + std::basic_ostream& os, const error_code& ec) +{ + os << ec.category().name() << ':' << ec.value(); + return os; +} + +# endif // !defined(ASIO_NO_IOSTREAM) + +#endif // defined(ASIO_HAS_STD_SYSTEM_ERROR) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/impl/error_code.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // ASIO_ERROR_CODE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution.hpp new file mode 100644 index 000000000..828b46b40 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution.hpp @@ -0,0 +1,48 @@ +// +// execution.hpp +// ~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_HPP +#define ASIO_EXECUTION_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/execution/allocator.hpp" +#include "asio/execution/any_executor.hpp" +#include "asio/execution/bad_executor.hpp" +#include "asio/execution/blocking.hpp" +#include "asio/execution/blocking_adaptation.hpp" +#include "asio/execution/bulk_execute.hpp" +#include "asio/execution/bulk_guarantee.hpp" +#include "asio/execution/connect.hpp" +#include "asio/execution/context.hpp" +#include "asio/execution/context_as.hpp" +#include "asio/execution/execute.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/invocable_archetype.hpp" +#include "asio/execution/mapping.hpp" +#include "asio/execution/occupancy.hpp" +#include "asio/execution/operation_state.hpp" +#include "asio/execution/outstanding_work.hpp" +#include "asio/execution/prefer_only.hpp" +#include "asio/execution/receiver.hpp" +#include "asio/execution/receiver_invocation_error.hpp" +#include "asio/execution/relationship.hpp" +#include "asio/execution/schedule.hpp" +#include "asio/execution/scheduler.hpp" +#include "asio/execution/sender.hpp" +#include "asio/execution/set_done.hpp" +#include "asio/execution/set_error.hpp" +#include "asio/execution/set_value.hpp" +#include "asio/execution/start.hpp" +#include "asio/execution/submit.hpp" + +#endif // ASIO_EXECUTION_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/allocator.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/allocator.hpp new file mode 100644 index 000000000..e9f33444a --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/allocator.hpp @@ -0,0 +1,249 @@ +// +// execution/allocator.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_ALLOCATOR_HPP +#define ASIO_EXECUTION_ALLOCATOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/scheduler.hpp" +#include "asio/execution/sender.hpp" +#include "asio/is_applicable_property.hpp" +#include "asio/traits/query_static_constexpr_member.hpp" +#include "asio/traits/static_query.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if defined(GENERATING_DOCUMENTATION) + +namespace execution { + +/// A property to describe which allocator an executor will use to allocate the +/// memory required to store a submitted function object. +template +struct allocator_t +{ + /// The allocator_t property applies to executors, senders, and schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The allocator_t property can be required. + static constexpr bool is_requirable = true; + + /// The allocator_t property can be preferred. + static constexpr bool is_preferable = true; + + /// Default constructor. + constexpr allocator_t(); + + /// Obtain the allocator stored in the allocator_t property object. + /** + * Present only if @c ProtoAllocator is non-void. + */ + constexpr ProtoAllocator value() const; + + /// Create an allocator_t object with a different allocator. + /** + * Present only if @c ProtoAllocator is void. + */ + template + allocator_t allocator; + +} // namespace execution + +#else // defined(GENERATING_DOCUMENTATION) + +namespace execution { + +template +struct allocator_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = true); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = true); + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = allocator_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + ASIO_CONSTEXPR ProtoAllocator value() const + { + return a_; + } + +private: + friend struct allocator_t; + + explicit ASIO_CONSTEXPR allocator_t(const ProtoAllocator& a) + : a_(a) + { + } + + ProtoAllocator a_; +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T allocator_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template <> +struct allocator_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = true); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = true); + + ASIO_CONSTEXPR allocator_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = allocator_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + template + ASIO_CONSTEXPR allocator_t operator()( + const OtherProtoAllocator& a) const + { + return allocator_t(a); + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template +const T allocator_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +constexpr allocator_t allocator; +#else // defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +template +struct allocator_instance +{ + static allocator_t instance; +}; + +template +allocator_t allocator_instance::instance; + +namespace { +static const allocator_t& allocator = allocator_instance::instance; +} // namespace +#endif + +} // namespace execution + +#if !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +struct is_applicable_property > + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +#endif // !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +namespace traits { + +#if !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct static_query, + typename enable_if< + traits::query_static_constexpr_member >::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member >::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member >::value(); + } +}; + +#endif // !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +} // namespace traits + +#endif // defined(GENERATING_DOCUMENTATION) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_ALLOCATOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/any_executor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/any_executor.hpp new file mode 100644 index 000000000..ce8a4c0a4 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/any_executor.hpp @@ -0,0 +1,2264 @@ +// +// execution/any_executor.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_ANY_EXECUTOR_HPP +#define ASIO_EXECUTION_ANY_EXECUTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include +#include "asio/detail/assert.hpp" +#include "asio/detail/cstddef.hpp" +#include "asio/detail/executor_function.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/non_const_lvalue.hpp" +#include "asio/detail/scoped_ptr.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/detail/throw_exception.hpp" +#include "asio/detail/variadic_templates.hpp" +#include "asio/execution/bad_executor.hpp" +#include "asio/execution/blocking.hpp" +#include "asio/execution/execute.hpp" +#include "asio/execution/executor.hpp" +#include "asio/prefer.hpp" +#include "asio/query.hpp" +#include "asio/require.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if defined(GENERATING_DOCUMENTATION) + +namespace execution { + +/// Polymorphic executor wrapper. +template +class any_executor +{ +public: + /// Default constructor. + any_executor() noexcept; + + /// Construct in an empty state. Equivalent effects to default constructor. + any_executor(nullptr_t) noexcept; + + /// Copy constructor. + any_executor(const any_executor& e) noexcept; + + /// Move constructor. + any_executor(any_executor&& e) noexcept; + + /// Construct to point to the same target as another any_executor. + template + any_executor(any_executor e); + + /// Construct a polymorphic wrapper for the specified executor. + template + any_executor(Executor e); + + /// Assignment operator. + any_executor& operator=(const any_executor& e) noexcept; + + /// Move assignment operator. + any_executor& operator=(any_executor&& e) noexcept; + + /// Assignment operator that sets the polymorphic wrapper to the empty state. + any_executor& operator=(nullptr_t); + + /// Assignment operator to create a polymorphic wrapper for the specified + /// executor. + template + any_executor& operator=(Executor e); + + /// Destructor. + ~any_executor(); + + /// Swap targets with another polymorphic wrapper. + void swap(any_executor& other) noexcept; + + /// Obtain a polymorphic wrapper with the specified property. + /** + * Do not call this function directly. It is intended for use with the + * asio::require and asio::prefer customisation points. + * + * For example: + * @code execution::any_executor ex = ...; + * auto ex2 = asio::requre(ex, execution::blocking.possibly); @endcode + */ + template + any_executor require(Property) const; + + /// Obtain a polymorphic wrapper with the specified property. + /** + * Do not call this function directly. It is intended for use with the + * asio::prefer customisation point. + * + * For example: + * @code execution::any_executor ex = ...; + * auto ex2 = asio::prefer(ex, execution::blocking.possibly); @endcode + */ + template + any_executor prefer(Property) const; + + /// Obtain the value associated with the specified property. + /** + * Do not call this function directly. It is intended for use with the + * asio::query customisation point. + * + * For example: + * @code execution::any_executor ex = ...; + * size_t n = asio::query(ex, execution::occupancy); @endcode + */ + template + typename Property::polymorphic_query_result_type query(Property) const; + + /// Execute the function on the target executor. + /** + * Do not call this function directly. It is intended for use with the + * execution::execute customisation point. + * + * For example: + * @code execution::any_executor<> ex = ...; + * execution::execute(ex, my_function_object); @endcode + * + * Throws asio::bad_executor if the polymorphic wrapper has no target. + */ + template + void execute(Function&& f) const; + + /// Obtain the underlying execution context. + /** + * This function is provided for backward compatibility. It is automatically + * defined when the @c SupportableProperties... list includes a property of + * type execution::context_as, for some type U. + */ + automatically_determined context() const; + + /// Determine whether the wrapper has a target executor. + /** + * @returns @c true if the polymorphic wrapper has a target executor, + * otherwise false. + */ + explicit operator bool() const noexcept; + + /// Get the type of the target executor. + const type_info& target_type() const noexcept; + + /// Get a pointer to the target executor. + template Executor* target() noexcept; + + /// Get a pointer to the target executor. + template const Executor* target() const noexcept; +}; + +/// Equality operator. +/** + * @relates any_executor + */ +template +bool operator==(const any_executor& a, + const any_executor& b) noexcept; + +/// Equality operator. +/** + * @relates any_executor + */ +template +bool operator==(const any_executor& a, + nullptr_t) noexcept; + +/// Equality operator. +/** + * @relates any_executor + */ +template +bool operator==(nullptr_t, + const any_executor& b) noexcept; + +/// Inequality operator. +/** + * @relates any_executor + */ +template +bool operator!=(const any_executor& a, + const any_executor& b) noexcept; + +/// Inequality operator. +/** + * @relates any_executor + */ +template +bool operator!=(const any_executor& a, + nullptr_t) noexcept; + +/// Inequality operator. +/** + * @relates any_executor + */ +template +bool operator!=(nullptr_t, + const any_executor& b) noexcept; + +} // namespace execution + +#else // defined(GENERATING_DOCUMENTATION) + +namespace execution { + +#if !defined(ASIO_EXECUTION_ANY_EXECUTOR_FWD_DECL) +#define ASIO_EXECUTION_ANY_EXECUTOR_FWD_DECL + +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template +class any_executor; + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template +class any_executor; + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +#endif // !defined(ASIO_EXECUTION_ANY_EXECUTOR_FWD_DECL) + +template +struct context_as_t; + +namespace detail { + +// Traits used to detect whether a property is requirable or preferable, taking +// into account that T::is_requirable or T::is_preferable may not not be well +// formed. + +template +struct is_requirable : false_type {}; + +template +struct is_requirable::type> : + true_type {}; + +template +struct is_preferable : false_type {}; + +template +struct is_preferable::type> : + true_type {}; + +// Trait used to detect context_as property, for backward compatibility. + +template +struct is_context_as : false_type {}; + +template +struct is_context_as > : true_type {}; + +// Helper template to: +// - Check if a target can supply the supportable properties. +// - Find the first convertible-from-T property in the list. + +template +struct supportable_properties; + +template +struct supportable_properties +{ + template + struct is_valid_target : integral_constant::value + ? can_require::value + : true + ) + && + ( + is_preferable::value + ? can_prefer::value + : true + ) + && + ( + !is_requirable::value && !is_preferable::value + ? can_query::value + : true + ) + > + { + }; + + struct found + { + ASIO_STATIC_CONSTEXPR(bool, value = true); + typedef Prop type; + typedef typename Prop::polymorphic_query_result_type query_result_type; + ASIO_STATIC_CONSTEXPR(std::size_t, index = I); + }; + + struct not_found + { + ASIO_STATIC_CONSTEXPR(bool, value = false); + }; + + template + struct find_convertible_property : + conditional< + is_same::value || is_convertible::value, + found, + not_found + >::type {}; + + template + struct find_convertible_requirable_property : + conditional< + is_requirable::value + && (is_same::value || is_convertible::value), + found, + not_found + >::type {}; + + template + struct find_convertible_preferable_property : + conditional< + is_preferable::value + && (is_same::value || is_convertible::value), + found, + not_found + >::type {}; + + struct find_context_as_property : + conditional< + is_context_as::value, + found, + not_found + >::type {}; +}; + +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template +struct supportable_properties +{ + template + struct is_valid_target : integral_constant::template is_valid_target::value + && + supportable_properties::template is_valid_target::value + ) + > + { + }; + + template + struct find_convertible_property : + conditional< + is_convertible::value, + typename supportable_properties::found, + typename supportable_properties::template find_convertible_property + >::type {}; + + template + struct find_convertible_requirable_property : + conditional< + is_requirable::value + && is_convertible::value, + typename supportable_properties::found, + typename supportable_properties::template find_convertible_requirable_property + >::type {}; + + template + struct find_convertible_preferable_property : + conditional< + is_preferable::value + && is_convertible::value, + typename supportable_properties::found, + typename supportable_properties::template find_convertible_preferable_property + >::type {}; + + struct find_context_as_property : + conditional< + is_context_as::value, + typename supportable_properties::found, + typename supportable_properties::find_context_as_property + >::type {}; +}; + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +#define ASIO_PRIVATE_ANY_EXECUTOR_PROPS_BASE_DEF(n) \ + template \ + struct supportable_properties \ + { \ + template \ + struct is_valid_target : integral_constant::template is_valid_target::value \ + && \ + supportable_properties::template \ + is_valid_target::value \ + ) \ + > \ + { \ + }; \ + \ + template \ + struct find_convertible_property : \ + conditional< \ + is_convertible::value, \ + typename supportable_properties::found, \ + typename supportable_properties::template \ + find_convertible_property \ + >::type {}; \ + \ + template \ + struct find_convertible_requirable_property : \ + conditional< \ + is_requirable::value \ + && is_convertible::value, \ + typename supportable_properties::found, \ + typename supportable_properties::template \ + find_convertible_requirable_property \ + >::type {}; \ + \ + template \ + struct find_convertible_preferable_property : \ + conditional< \ + is_preferable::value \ + && is_convertible::value, \ + typename supportable_properties::found, \ + typename supportable_properties::template \ + find_convertible_preferable_property \ + >::type {}; \ + \ + struct find_context_as_property : \ + conditional< \ + is_context_as::value, \ + typename supportable_properties::found, \ + typename supportable_properties::find_context_as_property \ + >::type {}; \ + }; \ + /**/ +ASIO_VARIADIC_GENERATE(ASIO_PRIVATE_ANY_EXECUTOR_PROPS_BASE_DEF) +#undef ASIO_PRIVATE_ANY_EXECUTOR_PROPS_BASE_DEF + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template +struct is_valid_target_executor : + conditional< + is_executor::value, + typename supportable_properties<0, Props>::template is_valid_target, + false_type + >::type +{ +}; + +class any_executor_base +{ +public: + any_executor_base() ASIO_NOEXCEPT + : object_fns_(object_fns_table()), + target_(0), + target_fns_(target_fns_table()) + { + } + + template + any_executor_base(Executor ex, false_type) + : target_fns_(target_fns_table( + any_executor_base::query_blocking(ex, + can_query()) + == execution::blocking.always)) + { + any_executor_base::construct_object(ex, + integral_constant::value <= alignment_of::value + >()); + } + + template + any_executor_base(Executor other, true_type) + : object_fns_(object_fns_table >()), + target_fns_(other.target_fns_) + { + asio::detail::shared_ptr p = + asio::detail::make_shared( + ASIO_MOVE_CAST(Executor)(other)); + target_ = p->template target(); + new (&object_) asio::detail::shared_ptr( + ASIO_MOVE_CAST(asio::detail::shared_ptr)(p)); + } + + any_executor_base(const any_executor_base& other) ASIO_NOEXCEPT + : object_fns_(other.object_fns_), + target_fns_(other.target_fns_) + { + object_fns_->copy(*this, other); + } + + ~any_executor_base() ASIO_NOEXCEPT + { + object_fns_->destroy(*this); + } + + any_executor_base& operator=( + const any_executor_base& other) ASIO_NOEXCEPT + { + if (this != &other) + { + object_fns_->destroy(*this); + object_fns_ = other.object_fns_; + target_fns_ = other.target_fns_; + object_fns_->copy(*this, other); + } + return *this; + } + + any_executor_base& operator=(nullptr_t) ASIO_NOEXCEPT + { + object_fns_->destroy(*this); + target_ = 0; + object_fns_ = object_fns_table(); + target_fns_ = target_fns_table(); + return *this; + } + +#if defined(ASIO_HAS_MOVE) + + any_executor_base(any_executor_base&& other) ASIO_NOEXCEPT + : object_fns_(other.object_fns_), + target_fns_(other.target_fns_) + { + other.object_fns_ = object_fns_table(); + other.target_fns_ = target_fns_table(); + object_fns_->move(*this, other); + other.target_ = 0; + } + + any_executor_base& operator=( + any_executor_base&& other) ASIO_NOEXCEPT + { + if (this != &other) + { + object_fns_->destroy(*this); + object_fns_ = other.object_fns_; + other.object_fns_ = object_fns_table(); + target_fns_ = other.target_fns_; + other.target_fns_ = target_fns_table(); + object_fns_->move(*this, other); + other.target_ = 0; + } + return *this; + } + +#endif // defined(ASIO_HAS_MOVE) + + void swap(any_executor_base& other) ASIO_NOEXCEPT + { + if (this != &other) + { + any_executor_base tmp(ASIO_MOVE_CAST(any_executor_base)(other)); + other = ASIO_MOVE_CAST(any_executor_base)(*this); + *this = ASIO_MOVE_CAST(any_executor_base)(tmp); + } + } + + template + void execute(ASIO_MOVE_ARG(F) f) const + { + if (target_fns_->blocking_execute != 0) + { + asio::detail::non_const_lvalue f2(f); + target_fns_->blocking_execute(*this, function_view(f2.value)); + } + else + { + target_fns_->execute(*this, + function(ASIO_MOVE_CAST(F)(f), std::allocator())); + } + } + + template + Executor* target() + { + return static_cast(target_); + } + + template + const Executor* target() const + { + return static_cast(target_); + } + + const std::type_info& target_type() const + { + return target_fns_->target_type(); + } + + struct unspecified_bool_type_t {}; + typedef void (*unspecified_bool_type)(unspecified_bool_type_t); + static void unspecified_bool_true(unspecified_bool_type_t) {} + + operator unspecified_bool_type() const ASIO_NOEXCEPT + { + return target_ ? &any_executor_base::unspecified_bool_true : 0; + } + + bool operator!() const ASIO_NOEXCEPT + { + return target_ == 0; + } + +protected: + bool equality_helper(const any_executor_base& other) const ASIO_NOEXCEPT + { + if (target_ == other.target_) + return true; + if (target_ && !other.target_) + return false; + if (!target_ && other.target_) + return false; + if (target_fns_ != other.target_fns_) + return false; + return target_fns_->equal(*this, other); + } + + template + Ex& object() + { + return *static_cast(static_cast(&object_)); + } + + template + const Ex& object() const + { + return *static_cast(static_cast(&object_)); + } + + struct object_fns + { + void (*destroy)(any_executor_base&); + void (*copy)(any_executor_base&, const any_executor_base&); + void (*move)(any_executor_base&, any_executor_base&); + const void* (*target)(const any_executor_base&); + }; + + static void destroy_void(any_executor_base&) + { + } + + static void copy_void(any_executor_base& ex1, const any_executor_base&) + { + ex1.target_ = 0; + } + + static void move_void(any_executor_base& ex1, any_executor_base&) + { + ex1.target_ = 0; + } + + static const void* target_void(const any_executor_base&) + { + return 0; + } + + template + static const object_fns* object_fns_table( + typename enable_if< + is_same::value + >::type* = 0) + { + static const object_fns fns = + { + &any_executor_base::destroy_void, + &any_executor_base::copy_void, + &any_executor_base::move_void, + &any_executor_base::target_void + }; + return &fns; + } + + static void destroy_shared(any_executor_base& ex) + { + typedef asio::detail::shared_ptr type; + ex.object().~type(); + } + + static void copy_shared(any_executor_base& ex1, const any_executor_base& ex2) + { + typedef asio::detail::shared_ptr type; + new (&ex1.object_) type(ex2.object()); + ex1.target_ = ex2.target_; + } + + static void move_shared(any_executor_base& ex1, any_executor_base& ex2) + { + typedef asio::detail::shared_ptr type; + new (&ex1.object_) type(ASIO_MOVE_CAST(type)(ex2.object())); + ex1.target_ = ex2.target_; + ex2.object().~type(); + } + + static const void* target_shared(const any_executor_base& ex) + { + typedef asio::detail::shared_ptr type; + return ex.object().get(); + } + + template + static const object_fns* object_fns_table( + typename enable_if< + is_same >::value + >::type* = 0) + { + static const object_fns fns = + { + &any_executor_base::destroy_shared, + &any_executor_base::copy_shared, + &any_executor_base::move_shared, + &any_executor_base::target_shared + }; + return &fns; + } + + template + static void destroy_object(any_executor_base& ex) + { + ex.object().~Obj(); + } + + template + static void copy_object(any_executor_base& ex1, const any_executor_base& ex2) + { + new (&ex1.object_) Obj(ex2.object()); + ex1.target_ = &ex1.object(); + } + + template + static void move_object(any_executor_base& ex1, any_executor_base& ex2) + { + new (&ex1.object_) Obj(ASIO_MOVE_CAST(Obj)(ex2.object())); + ex1.target_ = &ex1.object(); + ex2.object().~Obj(); + } + + template + static const void* target_object(const any_executor_base& ex) + { + return &ex.object(); + } + + template + static const object_fns* object_fns_table( + typename enable_if< + !is_same::value + && !is_same >::value + >::type* = 0) + { + static const object_fns fns = + { + &any_executor_base::destroy_object, + &any_executor_base::copy_object, + &any_executor_base::move_object, + &any_executor_base::target_object + }; + return &fns; + } + + typedef asio::detail::executor_function function; + typedef asio::detail::executor_function_view function_view; + + struct target_fns + { + const std::type_info& (*target_type)(); + bool (*equal)(const any_executor_base&, const any_executor_base&); + void (*execute)(const any_executor_base&, ASIO_MOVE_ARG(function)); + void (*blocking_execute)(const any_executor_base&, function_view); + }; + + static const std::type_info& target_type_void() + { + return typeid(void); + } + + static bool equal_void(const any_executor_base&, const any_executor_base&) + { + return true; + } + + static void execute_void(const any_executor_base&, + ASIO_MOVE_ARG(function)) + { + bad_executor ex; + asio::detail::throw_exception(ex); + } + + static void blocking_execute_void(const any_executor_base&, function_view) + { + bad_executor ex; + asio::detail::throw_exception(ex); + } + + template + static const target_fns* target_fns_table( + typename enable_if< + is_same::value + >::type* = 0) + { + static const target_fns fns = + { + &any_executor_base::target_type_void, + &any_executor_base::equal_void, + &any_executor_base::execute_void, + &any_executor_base::blocking_execute_void + }; + return &fns; + } + + template + static const std::type_info& target_type_ex() + { + return typeid(Ex); + } + + template + static bool equal_ex(const any_executor_base& ex1, + const any_executor_base& ex2) + { + return *ex1.target() == *ex2.target(); + } + + template + static void execute_ex(const any_executor_base& ex, + ASIO_MOVE_ARG(function) f) + { + execution::execute(*ex.target(), ASIO_MOVE_CAST(function)(f)); + } + + template + static void blocking_execute_ex(const any_executor_base& ex, function_view f) + { + execution::execute(*ex.target(), f); + } + + template + static const target_fns* target_fns_table(bool is_always_blocking, + typename enable_if< + !is_same::value + >::type* = 0) + { + static const target_fns fns_with_execute = + { + &any_executor_base::target_type_ex, + &any_executor_base::equal_ex, + &any_executor_base::execute_ex, + 0 + }; + + static const target_fns fns_with_blocking_execute = + { + &any_executor_base::target_type_ex, + &any_executor_base::equal_ex, + 0, + &any_executor_base::blocking_execute_ex + }; + + return is_always_blocking ? &fns_with_blocking_execute : &fns_with_execute; + } + +#if defined(ASIO_MSVC) +# pragma warning (push) +# pragma warning (disable:4702) +#endif // defined(ASIO_MSVC) + + static void query_fn_void(void*, const void*, const void*) + { + bad_executor ex; + asio::detail::throw_exception(ex); + } + + template + static void query_fn_non_void(void*, const void* ex, const void* prop, + typename enable_if< + asio::can_query::value + && is_same::value + >::type*) + { + asio::query(*static_cast(ex), + *static_cast(prop)); + } + + template + static void query_fn_non_void(void*, const void*, const void*, + typename enable_if< + !asio::can_query::value + && is_same::value + >::type*) + { + } + + template + static void query_fn_non_void(void* result, const void* ex, const void* prop, + typename enable_if< + asio::can_query::value + && !is_same::value + && is_reference::value + >::type*) + { + *static_cast::type**>(result) + = &static_cast( + asio::query(*static_cast(ex), + *static_cast(prop))); + } + + template + static void query_fn_non_void(void*, const void*, const void*, + typename enable_if< + !asio::can_query::value + && !is_same::value + && is_reference::value + >::type*) + { + std::terminate(); // Combination should not be possible. + } + + template + static void query_fn_non_void(void* result, const void* ex, const void* prop, + typename enable_if< + asio::can_query::value + && !is_same::value + && is_scalar::value + >::type*) + { + *static_cast(result) + = static_cast( + asio::query(*static_cast(ex), + *static_cast(prop))); + } + + template + static void query_fn_non_void(void* result, const void*, const void*, + typename enable_if< + !asio::can_query::value + && !is_same::value + && is_scalar::value + >::type*) + { + *static_cast(result) + = typename Prop::polymorphic_query_result_type(); + } + + template + static void query_fn_non_void(void* result, const void* ex, const void* prop, + typename enable_if< + asio::can_query::value + && !is_same::value + && !is_reference::value + && !is_scalar::value + >::type*) + { + *static_cast(result) + = new typename Prop::polymorphic_query_result_type( + asio::query(*static_cast(ex), + *static_cast(prop))); + } + + template + static void query_fn_non_void(void* result, const void*, const void*, ...) + { + *static_cast(result) + = new typename Prop::polymorphic_query_result_type(); + } + + template + static void query_fn_impl(void* result, const void* ex, const void* prop, + typename enable_if< + is_same::value + >::type*) + { + query_fn_void(result, ex, prop); + } + + template + static void query_fn_impl(void* result, const void* ex, const void* prop, + typename enable_if< + !is_same::value + >::type*) + { + query_fn_non_void(result, ex, prop, 0); + } + + template + static void query_fn(void* result, const void* ex, const void* prop) + { + query_fn_impl(result, ex, prop, 0); + } + + template + static Poly require_fn_impl(const void*, const void*, + typename enable_if< + is_same::value + >::type*) + { + bad_executor ex; + asio::detail::throw_exception(ex); + return Poly(); + } + + template + static Poly require_fn_impl(const void* ex, const void* prop, + typename enable_if< + !is_same::value && Prop::is_requirable + >::type*) + { + return asio::require(*static_cast(ex), + *static_cast(prop)); + } + + template + static Poly require_fn_impl(const void*, const void*, ...) + { + return Poly(); + } + + template + static Poly require_fn(const void* ex, const void* prop) + { + return require_fn_impl(ex, prop, 0); + } + + template + static Poly prefer_fn_impl(const void*, const void*, + typename enable_if< + is_same::value + >::type*) + { + bad_executor ex; + asio::detail::throw_exception(ex); + return Poly(); + } + + template + static Poly prefer_fn_impl(const void* ex, const void* prop, + typename enable_if< + !is_same::value && Prop::is_preferable + >::type*) + { + return asio::prefer(*static_cast(ex), + *static_cast(prop)); + } + + template + static Poly prefer_fn_impl(const void*, const void*, ...) + { + return Poly(); + } + + template + static Poly prefer_fn(const void* ex, const void* prop) + { + return prefer_fn_impl(ex, prop, 0); + } + + template + struct prop_fns + { + void (*query)(void*, const void*, const void*); + Poly (*require)(const void*, const void*); + Poly (*prefer)(const void*, const void*); + }; + +#if defined(ASIO_MSVC) +# pragma warning (pop) +#endif // defined(ASIO_MSVC) + +private: + template + static execution::blocking_t query_blocking(const Executor& ex, true_type) + { + return asio::query(ex, execution::blocking); + } + + template + static execution::blocking_t query_blocking(const Executor&, false_type) + { + return execution::blocking_t(); + } + + template + void construct_object(Executor& ex, true_type) + { + object_fns_ = object_fns_table(); + target_ = new (&object_) Executor(ASIO_MOVE_CAST(Executor)(ex)); + } + + template + void construct_object(Executor& ex, false_type) + { + object_fns_ = object_fns_table >(); + asio::detail::shared_ptr p = + asio::detail::make_shared( + ASIO_MOVE_CAST(Executor)(ex)); + target_ = p.get(); + new (&object_) asio::detail::shared_ptr( + ASIO_MOVE_CAST(asio::detail::shared_ptr)(p)); + } + +/*private:*/public: +// template friend class any_executor; + + typedef aligned_storage< + sizeof(asio::detail::shared_ptr), + alignment_of >::value + >::type object_type; + + object_type object_; + const object_fns* object_fns_; + void* target_; + const target_fns* target_fns_; +}; + +template +struct any_executor_context +{ +}; + +#if !defined(ASIO_NO_TS_EXECUTORS) + +template +struct any_executor_context::type> +{ + typename Property::query_result_type context() const + { + return static_cast(this)->query(typename Property::type()); + } +}; + +#endif // !defined(ASIO_NO_TS_EXECUTORS) + +} // namespace detail + +template <> +class any_executor<> : public detail::any_executor_base +{ +public: + any_executor() ASIO_NOEXCEPT + : detail::any_executor_base() + { + } + + any_executor(nullptr_t) ASIO_NOEXCEPT + : detail::any_executor_base() + { + } + + template + any_executor(Executor ex, + typename enable_if< + conditional< + !is_same::value + && !is_base_of::value, + is_executor, + false_type + >::type::value + >::type* = 0) + : detail::any_executor_base( + ASIO_MOVE_CAST(Executor)(ex), false_type()) + { + } + +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) + + template + any_executor(any_executor other) + : detail::any_executor_base( + static_cast(other)) + { + } + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + + template + any_executor(any_executor other) + : detail::any_executor_base( + static_cast(other)) + { + } + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) + + any_executor(const any_executor& other) ASIO_NOEXCEPT + : detail::any_executor_base( + static_cast(other)) + { + } + + any_executor& operator=(const any_executor& other) ASIO_NOEXCEPT + { + if (this != &other) + { + detail::any_executor_base::operator=( + static_cast(other)); + } + return *this; + } + + any_executor& operator=(nullptr_t p) ASIO_NOEXCEPT + { + detail::any_executor_base::operator=(p); + return *this; + } + +#if defined(ASIO_HAS_MOVE) + + any_executor(any_executor&& other) ASIO_NOEXCEPT + : detail::any_executor_base( + static_cast( + static_cast(other))) + { + } + + any_executor& operator=(any_executor&& other) ASIO_NOEXCEPT + { + if (this != &other) + { + detail::any_executor_base::operator=( + static_cast( + static_cast(other))); + } + return *this; + } + +#endif // defined(ASIO_HAS_MOVE) + + void swap(any_executor& other) ASIO_NOEXCEPT + { + detail::any_executor_base::swap( + static_cast(other)); + } + + using detail::any_executor_base::execute; + using detail::any_executor_base::target; + using detail::any_executor_base::target_type; + using detail::any_executor_base::operator unspecified_bool_type; + using detail::any_executor_base::operator!; + + bool equality_helper(const any_executor& other) const ASIO_NOEXCEPT + { + return any_executor_base::equality_helper(other); + } +}; + +inline bool operator==(const any_executor<>& a, + const any_executor<>& b) ASIO_NOEXCEPT +{ + return a.equality_helper(b); +} + +inline bool operator==(const any_executor<>& a, nullptr_t) ASIO_NOEXCEPT +{ + return !a; +} + +inline bool operator==(nullptr_t, const any_executor<>& b) ASIO_NOEXCEPT +{ + return !b; +} + +inline bool operator!=(const any_executor<>& a, + const any_executor<>& b) ASIO_NOEXCEPT +{ + return !a.equality_helper(b); +} + +inline bool operator!=(const any_executor<>& a, nullptr_t) ASIO_NOEXCEPT +{ + return !!a; +} + +inline bool operator!=(nullptr_t, const any_executor<>& b) ASIO_NOEXCEPT +{ + return !!b; +} + +inline void swap(any_executor<>& a, any_executor<>& b) ASIO_NOEXCEPT +{ + return a.swap(b); +} + +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template +class any_executor : + public detail::any_executor_base, + public detail::any_executor_context< + any_executor, + typename detail::supportable_properties< + 0, void(SupportableProperties...)>::find_context_as_property> +{ +public: + any_executor() ASIO_NOEXCEPT + : detail::any_executor_base(), + prop_fns_(prop_fns_table()) + { + } + + any_executor(nullptr_t) ASIO_NOEXCEPT + : detail::any_executor_base(), + prop_fns_(prop_fns_table()) + { + } + + template + any_executor(Executor ex, + typename enable_if< + conditional< + !is_same::value + && !is_base_of::value, + detail::is_valid_target_executor< + Executor, void(SupportableProperties...)>, + false_type + >::type::value + >::type* = 0) + : detail::any_executor_base( + ASIO_MOVE_CAST(Executor)(ex), false_type()), + prop_fns_(prop_fns_table()) + { + } + + template + any_executor(any_executor other, + typename enable_if< + conditional< + !is_same< + any_executor, + any_executor + >::value, + typename detail::supportable_properties< + 0, void(SupportableProperties...)>::template is_valid_target< + any_executor >, + false_type + >::type::value + >::type* = 0) + : detail::any_executor_base(ASIO_MOVE_CAST( + any_executor)(other), true_type()), + prop_fns_(prop_fns_table >()) + { + } + + any_executor(const any_executor& other) ASIO_NOEXCEPT + : detail::any_executor_base( + static_cast(other)), + prop_fns_(other.prop_fns_) + { + } + + any_executor& operator=(const any_executor& other) ASIO_NOEXCEPT + { + if (this != &other) + { + prop_fns_ = other.prop_fns_; + detail::any_executor_base::operator=( + static_cast(other)); + } + return *this; + } + + any_executor& operator=(nullptr_t p) ASIO_NOEXCEPT + { + prop_fns_ = prop_fns_table(); + detail::any_executor_base::operator=(p); + return *this; + } + +#if defined(ASIO_HAS_MOVE) + + any_executor(any_executor&& other) ASIO_NOEXCEPT + : detail::any_executor_base( + static_cast( + static_cast(other))), + prop_fns_(other.prop_fns_) + { + other.prop_fns_ = prop_fns_table(); + } + + any_executor& operator=(any_executor&& other) ASIO_NOEXCEPT + { + if (this != &other) + { + prop_fns_ = other.prop_fns_; + detail::any_executor_base::operator=( + static_cast( + static_cast(other))); + } + return *this; + } + +#endif // defined(ASIO_HAS_MOVE) + + void swap(any_executor& other) ASIO_NOEXCEPT + { + if (this != &other) + { + detail::any_executor_base::swap( + static_cast(other)); + const prop_fns* tmp_prop_fns = other.prop_fns_; + other.prop_fns_ = prop_fns_; + prop_fns_ = tmp_prop_fns; + } + } + + using detail::any_executor_base::execute; + using detail::any_executor_base::target; + using detail::any_executor_base::target_type; + using detail::any_executor_base::operator unspecified_bool_type; + using detail::any_executor_base::operator!; + + bool equality_helper(const any_executor& other) const ASIO_NOEXCEPT + { + return any_executor_base::equality_helper(other); + } + + template + struct find_convertible_property : + detail::supportable_properties< + 0, void(SupportableProperties...)>::template + find_convertible_property {}; + + template + void query(const Property& p, + typename enable_if< + is_same< + typename find_convertible_property::query_result_type, + void + >::value + >::type* = 0) const + { + typedef find_convertible_property found; + prop_fns_[found::index].query(0, object_fns_->target(*this), + &static_cast(p)); + } + + template + typename find_convertible_property::query_result_type + query(const Property& p, + typename enable_if< + !is_same< + typename find_convertible_property::query_result_type, + void + >::value + && + is_reference< + typename find_convertible_property::query_result_type + >::value + >::type* = 0) const + { + typedef find_convertible_property found; + typename remove_reference< + typename found::query_result_type>::type* result = 0; + prop_fns_[found::index].query(&result, object_fns_->target(*this), + &static_cast(p)); + return *result; + } + + template + typename find_convertible_property::query_result_type + query(const Property& p, + typename enable_if< + !is_same< + typename find_convertible_property::query_result_type, + void + >::value + && + is_scalar< + typename find_convertible_property::query_result_type + >::value + >::type* = 0) const + { + typedef find_convertible_property found; + typename found::query_result_type result; + prop_fns_[found::index].query(&result, object_fns_->target(*this), + &static_cast(p)); + return result; + } + + template + typename find_convertible_property::query_result_type + query(const Property& p, + typename enable_if< + !is_same< + typename find_convertible_property::query_result_type, + void + >::value + && + !is_reference< + typename find_convertible_property::query_result_type + >::value + && + !is_scalar< + typename find_convertible_property::query_result_type + >::value + >::type* = 0) const + { + typedef find_convertible_property found; + typename found::query_result_type* result; + prop_fns_[found::index].query(&result, object_fns_->target(*this), + &static_cast(p)); + return *asio::detail::scoped_ptr< + typename found::query_result_type>(result); + } + + template + struct find_convertible_requirable_property : + detail::supportable_properties< + 0, void(SupportableProperties...)>::template + find_convertible_requirable_property {}; + + template + any_executor require(const Property& p, + typename enable_if< + find_convertible_requirable_property::value + >::type* = 0) const + { + typedef find_convertible_requirable_property found; + return prop_fns_[found::index].require(object_fns_->target(*this), + &static_cast(p)); + } + + template + struct find_convertible_preferable_property : + detail::supportable_properties< + 0, void(SupportableProperties...)>::template + find_convertible_preferable_property {}; + + template + any_executor prefer(const Property& p, + typename enable_if< + find_convertible_preferable_property::value + >::type* = 0) const + { + typedef find_convertible_preferable_property found; + return prop_fns_[found::index].prefer(object_fns_->target(*this), + &static_cast(p)); + } + +//private: + template + static const prop_fns* prop_fns_table() + { + static const prop_fns fns[] = + { + { + &detail::any_executor_base::query_fn< + Ex, SupportableProperties>, + &detail::any_executor_base::require_fn< + any_executor, Ex, SupportableProperties>, + &detail::any_executor_base::prefer_fn< + any_executor, Ex, SupportableProperties> + }... + }; + return fns; + } + + const prop_fns* prop_fns_; +}; + +template +inline bool operator==(const any_executor& a, + const any_executor& b) ASIO_NOEXCEPT +{ + return a.equality_helper(b); +} + +template +inline bool operator==(const any_executor& a, + nullptr_t) ASIO_NOEXCEPT +{ + return !a; +} + +template +inline bool operator==(nullptr_t, + const any_executor& b) ASIO_NOEXCEPT +{ + return !b; +} + +template +inline bool operator!=(const any_executor& a, + const any_executor& b) ASIO_NOEXCEPT +{ + return !a.equality_helper(b); +} + +template +inline bool operator!=(const any_executor& a, + nullptr_t) ASIO_NOEXCEPT +{ + return !!a; +} + +template +inline bool operator!=(nullptr_t, + const any_executor& b) ASIO_NOEXCEPT +{ + return !!b; +} + +template +inline void swap(any_executor& a, + any_executor& b) ASIO_NOEXCEPT +{ + return a.swap(b); +} + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +#define ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS(n) \ + ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_##n + +#define ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_1 \ + { \ + &detail::any_executor_base::query_fn, \ + &detail::any_executor_base::require_fn, \ + &detail::any_executor_base::prefer_fn \ + } +#define ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_2 \ + ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_1, \ + { \ + &detail::any_executor_base::query_fn, \ + &detail::any_executor_base::require_fn, \ + &detail::any_executor_base::prefer_fn \ + } +#define ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_3 \ + ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_2, \ + { \ + &detail::any_executor_base::query_fn, \ + &detail::any_executor_base::require_fn, \ + &detail::any_executor_base::prefer_fn \ + } +#define ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_4 \ + ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_3, \ + { \ + &detail::any_executor_base::query_fn, \ + &detail::any_executor_base::require_fn, \ + &detail::any_executor_base::prefer_fn \ + } +#define ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_5 \ + ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_4, \ + { \ + &detail::any_executor_base::query_fn, \ + &detail::any_executor_base::require_fn, \ + &detail::any_executor_base::prefer_fn \ + } +#define ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_6 \ + ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_5, \ + { \ + &detail::any_executor_base::query_fn, \ + &detail::any_executor_base::require_fn, \ + &detail::any_executor_base::prefer_fn \ + } +#define ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_7 \ + ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_6, \ + { \ + &detail::any_executor_base::query_fn, \ + &detail::any_executor_base::require_fn, \ + &detail::any_executor_base::prefer_fn \ + } +#define ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_8 \ + ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_7, \ + { \ + &detail::any_executor_base::query_fn, \ + &detail::any_executor_base::require_fn, \ + &detail::any_executor_base::prefer_fn \ + } + +#if defined(ASIO_HAS_MOVE) + +# define ASIO_PRIVATE_ANY_EXECUTOR_MOVE_OPS \ + any_executor(any_executor&& other) ASIO_NOEXCEPT \ + : detail::any_executor_base( \ + static_cast( \ + static_cast(other))), \ + prop_fns_(other.prop_fns_) \ + { \ + other.prop_fns_ = prop_fns_table(); \ + } \ + \ + any_executor& operator=(any_executor&& other) ASIO_NOEXCEPT \ + { \ + if (this != &other) \ + { \ + prop_fns_ = other.prop_fns_; \ + detail::any_executor_base::operator=( \ + static_cast( \ + static_cast(other))); \ + } \ + return *this; \ + } \ + /**/ +#else // defined(ASIO_HAS_MOVE) + +# define ASIO_PRIVATE_ANY_EXECUTOR_MOVE_OPS + +#endif // defined(ASIO_HAS_MOVE) + +#define ASIO_PRIVATE_ANY_EXECUTOR_DEF(n) \ + template \ + class any_executor : \ + public detail::any_executor_base, \ + public detail::any_executor_context< \ + any_executor, \ + typename detail::supportable_properties< \ + 0, void(ASIO_VARIADIC_TARGS(n))>::find_context_as_property> \ + { \ + public: \ + any_executor() ASIO_NOEXCEPT \ + : detail::any_executor_base(), \ + prop_fns_(prop_fns_table()) \ + { \ + } \ + \ + any_executor(nullptr_t) ASIO_NOEXCEPT \ + : detail::any_executor_base(), \ + prop_fns_(prop_fns_table()) \ + { \ + } \ + \ + template \ + any_executor(Executor ex, \ + typename enable_if< \ + conditional< \ + !is_same::value \ + && !is_base_of::value, \ + detail::is_valid_target_executor< \ + Executor, void(ASIO_VARIADIC_TARGS(n))>, \ + false_type \ + >::type::value \ + >::type* = 0) \ + : detail::any_executor_base(ASIO_MOVE_CAST( \ + Executor)(ex), false_type()), \ + prop_fns_(prop_fns_table()) \ + { \ + } \ + \ + any_executor(const any_executor& other) ASIO_NOEXCEPT \ + : detail::any_executor_base( \ + static_cast(other)), \ + prop_fns_(other.prop_fns_) \ + { \ + } \ + \ + any_executor(any_executor<> other) \ + : detail::any_executor_base(ASIO_MOVE_CAST( \ + any_executor<>)(other), true_type()), \ + prop_fns_(prop_fns_table >()) \ + { \ + } \ + \ + template \ + any_executor(OtherAnyExecutor other, \ + typename enable_if< \ + conditional< \ + !is_same::value \ + && is_base_of::value, \ + typename detail::supportable_properties< \ + 0, void(ASIO_VARIADIC_TARGS(n))>::template \ + is_valid_target, \ + false_type \ + >::type::value \ + >::type* = 0) \ + : detail::any_executor_base(ASIO_MOVE_CAST( \ + OtherAnyExecutor)(other), true_type()), \ + prop_fns_(prop_fns_table()) \ + { \ + } \ + \ + any_executor& operator=(const any_executor& other) ASIO_NOEXCEPT \ + { \ + if (this != &other) \ + { \ + prop_fns_ = other.prop_fns_; \ + detail::any_executor_base::operator=( \ + static_cast(other)); \ + } \ + return *this; \ + } \ + \ + any_executor& operator=(nullptr_t p) ASIO_NOEXCEPT \ + { \ + prop_fns_ = prop_fns_table(); \ + detail::any_executor_base::operator=(p); \ + return *this; \ + } \ + \ + ASIO_PRIVATE_ANY_EXECUTOR_MOVE_OPS \ + \ + void swap(any_executor& other) ASIO_NOEXCEPT \ + { \ + if (this != &other) \ + { \ + detail::any_executor_base::swap( \ + static_cast(other)); \ + const prop_fns* tmp_prop_fns = other.prop_fns_; \ + other.prop_fns_ = prop_fns_; \ + prop_fns_ = tmp_prop_fns; \ + } \ + } \ + \ + using detail::any_executor_base::execute; \ + using detail::any_executor_base::target; \ + using detail::any_executor_base::target_type; \ + using detail::any_executor_base::operator unspecified_bool_type; \ + using detail::any_executor_base::operator!; \ + \ + bool equality_helper(const any_executor& other) const ASIO_NOEXCEPT \ + { \ + return any_executor_base::equality_helper(other); \ + } \ + \ + template \ + struct find_convertible_property : \ + detail::supportable_properties< \ + 0, void(ASIO_VARIADIC_TARGS(n))>::template \ + find_convertible_property {}; \ + \ + template \ + void query(const Property& p, \ + typename enable_if< \ + is_same< \ + typename find_convertible_property::query_result_type, \ + void \ + >::value \ + >::type* = 0) const \ + { \ + typedef find_convertible_property found; \ + prop_fns_[found::index].query(0, object_fns_->target(*this), \ + &static_cast(p)); \ + } \ + \ + template \ + typename find_convertible_property::query_result_type \ + query(const Property& p, \ + typename enable_if< \ + !is_same< \ + typename find_convertible_property::query_result_type, \ + void \ + >::value \ + && \ + is_reference< \ + typename find_convertible_property::query_result_type \ + >::value \ + >::type* = 0) const \ + { \ + typedef find_convertible_property found; \ + typename remove_reference< \ + typename found::query_result_type>::type* result; \ + prop_fns_[found::index].query(&result, object_fns_->target(*this), \ + &static_cast(p)); \ + return *result; \ + } \ + \ + template \ + typename find_convertible_property::query_result_type \ + query(const Property& p, \ + typename enable_if< \ + !is_same< \ + typename find_convertible_property::query_result_type, \ + void \ + >::value \ + && \ + is_scalar< \ + typename find_convertible_property::query_result_type \ + >::value \ + >::type* = 0) const \ + { \ + typedef find_convertible_property found; \ + typename found::query_result_type result; \ + prop_fns_[found::index].query(&result, object_fns_->target(*this), \ + &static_cast(p)); \ + return result; \ + } \ + \ + template \ + typename find_convertible_property::query_result_type \ + query(const Property& p, \ + typename enable_if< \ + !is_same< \ + typename find_convertible_property::query_result_type, \ + void \ + >::value \ + && \ + !is_reference< \ + typename find_convertible_property::query_result_type \ + >::value \ + && \ + !is_scalar< \ + typename find_convertible_property::query_result_type \ + >::value \ + >::type* = 0) const \ + { \ + typedef find_convertible_property found; \ + typename found::query_result_type* result; \ + prop_fns_[found::index].query(&result, object_fns_->target(*this), \ + &static_cast(p)); \ + return *asio::detail::scoped_ptr< \ + typename found::query_result_type>(result); \ + } \ + \ + template \ + struct find_convertible_requirable_property : \ + detail::supportable_properties< \ + 0, void(ASIO_VARIADIC_TARGS(n))>::template \ + find_convertible_requirable_property {}; \ + \ + template \ + any_executor require(const Property& p, \ + typename enable_if< \ + find_convertible_requirable_property::value \ + >::type* = 0) const \ + { \ + typedef find_convertible_requirable_property found; \ + return prop_fns_[found::index].require(object_fns_->target(*this), \ + &static_cast(p)); \ + } \ + \ + template \ + struct find_convertible_preferable_property : \ + detail::supportable_properties< \ + 0, void(ASIO_VARIADIC_TARGS(n))>::template \ + find_convertible_preferable_property {}; \ + \ + template \ + any_executor prefer(const Property& p, \ + typename enable_if< \ + find_convertible_preferable_property::value \ + >::type* = 0) const \ + { \ + typedef find_convertible_preferable_property found; \ + return prop_fns_[found::index].prefer(object_fns_->target(*this), \ + &static_cast(p)); \ + } \ + \ + template \ + static const prop_fns* prop_fns_table() \ + { \ + static const prop_fns fns[] = \ + { \ + ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS(n) \ + }; \ + return fns; \ + } \ + \ + const prop_fns* prop_fns_; \ + typedef detail::supportable_properties<0, \ + void(ASIO_VARIADIC_TARGS(n))> supportable_properties_type; \ + }; \ + \ + template \ + inline bool operator==(const any_executor& a, \ + const any_executor& b) ASIO_NOEXCEPT \ + { \ + return a.equality_helper(b); \ + } \ + \ + template \ + inline bool operator==(const any_executor& a, \ + nullptr_t) ASIO_NOEXCEPT \ + { \ + return !a; \ + } \ + \ + template \ + inline bool operator==(nullptr_t, \ + const any_executor& b) ASIO_NOEXCEPT \ + { \ + return !b; \ + } \ + \ + template \ + inline bool operator!=(const any_executor& a, \ + const any_executor& b) ASIO_NOEXCEPT \ + { \ + return !a.equality_helper(b); \ + } \ + \ + template \ + inline bool operator!=(const any_executor& a, \ + nullptr_t) ASIO_NOEXCEPT \ + { \ + return !!a; \ + } \ + \ + template \ + inline bool operator!=(nullptr_t, \ + const any_executor& b) ASIO_NOEXCEPT \ + { \ + return !!b; \ + } \ + \ + template \ + inline void swap(any_executor& a, \ + any_executor& b) ASIO_NOEXCEPT \ + { \ + return a.swap(b); \ + } \ + /**/ + ASIO_VARIADIC_GENERATE(ASIO_PRIVATE_ANY_EXECUTOR_DEF) +#undef ASIO_PRIVATE_ANY_EXECUTOR_DEF +#undef ASIO_PRIVATE_ANY_EXECUTOR_MOVE_OPS +#undef ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS +#undef ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_1 +#undef ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_2 +#undef ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_3 +#undef ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_4 +#undef ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_5 +#undef ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_6 +#undef ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_7 +#undef ASIO_PRIVATE_ANY_EXECUTOR_PROP_FNS_8 + +#endif // if defined(ASIO_HAS_VARIADIC_TEMPLATES) + +} // namespace execution +namespace traits { + +#if !defined(ASIO_HAS_DEDUCED_EQUALITY_COMPARABLE_TRAIT) +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template +struct equality_comparable > +{ + static const bool is_valid = true; + static const bool is_noexcept = true; +}; + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template <> +struct equality_comparable > +{ + static const bool is_valid = true; + static const bool is_noexcept = true; +}; + +#define ASIO_PRIVATE_ANY_EXECUTOR_EQUALITY_COMPARABLE_DEF(n) \ + template \ + struct equality_comparable< \ + execution::any_executor > \ + { \ + static const bool is_valid = true; \ + static const bool is_noexcept = true; \ + }; \ + /**/ + ASIO_VARIADIC_GENERATE( + ASIO_PRIVATE_ANY_EXECUTOR_EQUALITY_COMPARABLE_DEF) +#undef ASIO_PRIVATE_ANY_EXECUTOR_EQUALITY_COMPARABLE_DEF + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) +#endif // !defined(ASIO_HAS_DEDUCED_EQUALITY_COMPARABLE_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_EXECUTE_MEMBER_TRAIT) +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template +struct execute_member, F> +{ + static const bool is_valid = true; + static const bool is_noexcept = false; + typedef void result_type; +}; + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template +struct execute_member, F> +{ + static const bool is_valid = true; + static const bool is_noexcept = false; + typedef void result_type; +}; + +#define ASIO_PRIVATE_ANY_EXECUTOR_EXECUTE_MEMBER_DEF(n) \ + template \ + struct execute_member< \ + execution::any_executor, F> \ + { \ + static const bool is_valid = true; \ + static const bool is_noexcept = false; \ + typedef void result_type; \ + }; \ + /**/ + ASIO_VARIADIC_GENERATE( + ASIO_PRIVATE_ANY_EXECUTOR_EXECUTE_MEMBER_DEF) +#undef ASIO_PRIVATE_ANY_EXECUTOR_EXECUTE_MEMBER_DEF + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) +#endif // !defined(ASIO_HAS_DEDUCED_EXECUTE_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_QUERY_MEMBER_TRAIT) +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template +struct query_member< + execution::any_executor, Prop, + typename enable_if< + execution::detail::supportable_properties< + 0, void(SupportableProperties...)>::template + find_convertible_property::value + >::type> +{ + static const bool is_valid = true; + static const bool is_noexcept = false; + typedef typename execution::detail::supportable_properties< + 0, void(SupportableProperties...)>::template + find_convertible_property::query_result_type result_type; +}; + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +#define ASIO_PRIVATE_ANY_EXECUTOR_QUERY_MEMBER_DEF(n) \ + template \ + struct query_member< \ + execution::any_executor, Prop, \ + typename enable_if< \ + execution::detail::supportable_properties< \ + 0, void(ASIO_VARIADIC_TARGS(n))>::template \ + find_convertible_property::value \ + >::type> \ + { \ + static const bool is_valid = true; \ + static const bool is_noexcept = false; \ + typedef typename execution::detail::supportable_properties< \ + 0, void(ASIO_VARIADIC_TARGS(n))>::template \ + find_convertible_property::query_result_type result_type; \ + }; \ + /**/ + ASIO_VARIADIC_GENERATE(ASIO_PRIVATE_ANY_EXECUTOR_QUERY_MEMBER_DEF) +#undef ASIO_PRIVATE_ANY_EXECUTOR_QUERY_MEMBER_DEF + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) +#endif // !defined(ASIO_HAS_DEDUCED_QUERY_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_REQUIRE_MEMBER_TRAIT) +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template +struct require_member< + execution::any_executor, Prop, + typename enable_if< + execution::detail::supportable_properties< + 0, void(SupportableProperties...)>::template + find_convertible_requirable_property::value + >::type> +{ + static const bool is_valid = true; + static const bool is_noexcept = false; + typedef execution::any_executor result_type; +}; + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +#define ASIO_PRIVATE_ANY_EXECUTOR_REQUIRE_MEMBER_DEF(n) \ + template \ + struct require_member< \ + execution::any_executor, Prop, \ + typename enable_if< \ + execution::detail::supportable_properties< \ + 0, void(ASIO_VARIADIC_TARGS(n))>::template \ + find_convertible_requirable_property::value \ + >::type> \ + { \ + static const bool is_valid = true; \ + static const bool is_noexcept = false; \ + typedef execution::any_executor result_type; \ + }; \ + /**/ + ASIO_VARIADIC_GENERATE( + ASIO_PRIVATE_ANY_EXECUTOR_REQUIRE_MEMBER_DEF) +#undef ASIO_PRIVATE_ANY_EXECUTOR_REQUIRE_MEMBER_DEF + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) +#endif // !defined(ASIO_HAS_DEDUCED_REQUIRE_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_PREFER_FREE_TRAIT) +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template +struct prefer_member< + execution::any_executor, Prop, + typename enable_if< + execution::detail::supportable_properties< + 0, void(SupportableProperties...)>::template + find_convertible_preferable_property::value + >::type> +{ + static const bool is_valid = true; + static const bool is_noexcept = false; + typedef execution::any_executor result_type; +}; + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +#define ASIO_PRIVATE_ANY_EXECUTOR_PREFER_FREE_DEF(n) \ + template \ + struct prefer_member< \ + execution::any_executor, Prop, \ + typename enable_if< \ + execution::detail::supportable_properties< \ + 0, void(ASIO_VARIADIC_TARGS(n))>::template \ + find_convertible_preferable_property::value \ + >::type> \ + { \ + static const bool is_valid = true; \ + static const bool is_noexcept = false; \ + typedef execution::any_executor result_type; \ + }; \ + /**/ + ASIO_VARIADIC_GENERATE(ASIO_PRIVATE_ANY_EXECUTOR_PREFER_FREE_DEF) +#undef ASIO_PRIVATE_ANY_EXECUTOR_PREFER_FREE_DEF + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) +#endif // !defined(ASIO_HAS_DEDUCED_PREFER_FREE_TRAIT) + +} // namespace traits + +#endif // defined(GENERATING_DOCUMENTATION) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_ANY_EXECUTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/bad_executor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/bad_executor.hpp new file mode 100644 index 000000000..006952936 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/bad_executor.hpp @@ -0,0 +1,47 @@ +// +// execution/bad_executor.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_BAD_EXECUTOR_HPP +#define ASIO_EXECUTION_BAD_EXECUTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace execution { + +/// Exception thrown when trying to access an empty polymorphic executor. +class bad_executor + : public std::exception +{ +public: + /// Constructor. + ASIO_DECL bad_executor() ASIO_NOEXCEPT; + + /// Obtain message associated with exception. + ASIO_DECL virtual const char* what() const + ASIO_NOEXCEPT_OR_NOTHROW; +}; + +} // namespace execution +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/execution/impl/bad_executor.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // ASIO_EXECUTION_BAD_EXECUTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/blocking.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/blocking.hpp new file mode 100644 index 000000000..4d193496a --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/blocking.hpp @@ -0,0 +1,1351 @@ +// +// execution/blocking.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_BLOCKING_HPP +#define ASIO_EXECUTION_BLOCKING_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/execute.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/scheduler.hpp" +#include "asio/execution/sender.hpp" +#include "asio/is_applicable_property.hpp" +#include "asio/prefer.hpp" +#include "asio/query.hpp" +#include "asio/require.hpp" +#include "asio/traits/query_free.hpp" +#include "asio/traits/query_member.hpp" +#include "asio/traits/query_static_constexpr_member.hpp" +#include "asio/traits/static_query.hpp" +#include "asio/traits/static_require.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if defined(GENERATING_DOCUMENTATION) + +namespace execution { + +/// A property to describe what guarantees an executor makes about the blocking +/// behaviour of their execution functions. +struct blocking_t +{ + /// The blocking_t property applies to executors, senders, and schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The top-level blocking_t property cannot be required. + static constexpr bool is_requirable = false; + + /// The top-level blocking_t property cannot be preferred. + static constexpr bool is_preferable = false; + + /// The type returned by queries against an @c any_executor. + typedef blocking_t polymorphic_query_result_type; + + /// A sub-property that indicates that invocation of an executor's execution + /// function may block pending completion of one or more invocations of the + /// submitted function object. + struct possibly_t + { + /// The blocking_t::possibly_t property applies to executors, senders, and + /// schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The blocking_t::possibly_t property can be required. + static constexpr bool is_requirable = true; + + /// The blocking_t::possibly_t property can be preferred. + static constexpr bool is_preferable = true; + + /// The type returned by queries against an @c any_executor. + typedef blocking_t polymorphic_query_result_type; + + /// Default constructor. + constexpr possibly_t(); + + /// Get the value associated with a property object. + /** + * @returns possibly_t(); + */ + static constexpr blocking_t value(); + }; + + /// A sub-property that indicates that invocation of an executor's execution + /// function shall block until completion of all invocations of the submitted + /// function object. + struct always_t + { + /// The blocking_t::always_t property applies to executors, senders, and + /// schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The blocking_t::always_t property can be required. + static constexpr bool is_requirable = true; + + /// The blocking_t::always_t property can be preferred. + static constexpr bool is_preferable = false; + + /// The type returned by queries against an @c any_executor. + typedef blocking_t polymorphic_query_result_type; + + /// Default constructor. + constexpr always_t(); + + /// Get the value associated with a property object. + /** + * @returns always_t(); + */ + static constexpr blocking_t value(); + }; + + /// A sub-property that indicates that invocation of an executor's execution + /// function shall not block pending completion of the invocations of the + /// submitted function object. + struct never_t + { + /// The blocking_t::never_t property applies to executors, senders, and + /// schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The blocking_t::never_t property can be required. + static constexpr bool is_requirable = true; + + /// The blocking_t::never_t property can be preferred. + static constexpr bool is_preferable = true; + + /// The type returned by queries against an @c any_executor. + typedef blocking_t polymorphic_query_result_type; + + /// Default constructor. + constexpr never_t(); + + /// Get the value associated with a property object. + /** + * @returns never_t(); + */ + static constexpr blocking_t value(); + }; + + /// A special value used for accessing the blocking_t::possibly_t property. + static constexpr possibly_t possibly; + + /// A special value used for accessing the blocking_t::always_t property. + static constexpr always_t always; + + /// A special value used for accessing the blocking_t::never_t property. + static constexpr never_t never; + + /// Default constructor. + constexpr blocking_t(); + + /// Construct from a sub-property value. + constexpr blocking_t(possibly_t); + + /// Construct from a sub-property value. + constexpr blocking_t(always_t); + + /// Construct from a sub-property value. + constexpr blocking_t(never_t); + + /// Compare property values for equality. + friend constexpr bool operator==( + const blocking_t& a, const blocking_t& b) noexcept; + + /// Compare property values for inequality. + friend constexpr bool operator!=( + const blocking_t& a, const blocking_t& b) noexcept; +}; + +/// A special value used for accessing the blocking_t property. +constexpr blocking_t blocking; + +} // namespace execution + +#else // defined(GENERATING_DOCUMENTATION) + +namespace execution { +namespace detail { +namespace blocking { + +template struct possibly_t; +template struct always_t; +template struct never_t; + +} // namespace blocking +namespace blocking_adaptation { + +template struct allowed_t; + +template +void blocking_execute( + ASIO_MOVE_ARG(Executor) ex, + ASIO_MOVE_ARG(Function) func); + +} // namespace blocking_adaptation + +template +struct blocking_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = false); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = false); + typedef blocking_t polymorphic_query_result_type; + + typedef detail::blocking::possibly_t possibly_t; + typedef detail::blocking::always_t always_t; + typedef detail::blocking::never_t never_t; + + ASIO_CONSTEXPR blocking_t() + : value_(-1) + { + } + + ASIO_CONSTEXPR blocking_t(possibly_t) + : value_(0) + { + } + + ASIO_CONSTEXPR blocking_t(always_t) + : value_(1) + { + } + + ASIO_CONSTEXPR blocking_t(never_t) + : value_(2) + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template + static ASIO_CONSTEXPR + typename traits::static_query::result_type + static_query( + typename enable_if< + !traits::query_static_constexpr_member::is_valid + && !traits::query_member::is_valid + && traits::static_query::is_valid + >::type* = 0) ASIO_NOEXCEPT + { + return traits::static_query::value(); + } + + template + static ASIO_CONSTEXPR + typename traits::static_query::result_type + static_query( + typename enable_if< + !traits::query_static_constexpr_member::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type* = 0) ASIO_NOEXCEPT + { + return traits::static_query::value(); + } + + template + static ASIO_CONSTEXPR + typename traits::static_query::result_type + static_query( + typename enable_if< + !traits::query_static_constexpr_member::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type* = 0) ASIO_NOEXCEPT + { + return traits::static_query::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = blocking_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + friend ASIO_CONSTEXPR bool operator==( + const blocking_t& a, const blocking_t& b) + { + return a.value_ == b.value_; + } + + friend ASIO_CONSTEXPR bool operator!=( + const blocking_t& a, const blocking_t& b) + { + return a.value_ != b.value_; + } + + struct convertible_from_blocking_t + { + ASIO_CONSTEXPR convertible_from_blocking_t(blocking_t) {} + }; + + template + friend ASIO_CONSTEXPR blocking_t query( + const Executor& ex, convertible_from_blocking_t, + typename enable_if< + can_query::value + >::type* = 0) +#if !defined(__clang__) // Clang crashes if noexcept is used here. +#if defined(ASIO_MSVC) // Visual C++ wants the type to be qualified. + ASIO_NOEXCEPT_IF(( + is_nothrow_query::possibly_t>::value)) +#else // defined(ASIO_MSVC) + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#endif // defined(ASIO_MSVC) +#endif // !defined(__clang__) + { + return asio::query(ex, possibly_t()); + } + + template + friend ASIO_CONSTEXPR blocking_t query( + const Executor& ex, convertible_from_blocking_t, + typename enable_if< + !can_query::value + && can_query::value + >::type* = 0) +#if !defined(__clang__) // Clang crashes if noexcept is used here. +#if defined(ASIO_MSVC) // Visual C++ wants the type to be qualified. + ASIO_NOEXCEPT_IF(( + is_nothrow_query::always_t>::value)) +#else // defined(ASIO_MSVC) + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#endif // defined(ASIO_MSVC) +#endif // !defined(__clang__) + { + return asio::query(ex, always_t()); + } + + template + friend ASIO_CONSTEXPR blocking_t query( + const Executor& ex, convertible_from_blocking_t, + typename enable_if< + !can_query::value + && !can_query::value + && can_query::value + >::type* = 0) +#if !defined(__clang__) // Clang crashes if noexcept is used here. +#if defined(ASIO_MSVC) // Visual C++ wants the type to be qualified. + ASIO_NOEXCEPT_IF(( + is_nothrow_query::never_t>::value)) +#else // defined(ASIO_MSVC) + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#endif // defined(ASIO_MSVC) +#endif // !defined(__clang__) + { + return asio::query(ex, never_t()); + } + + ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(possibly_t, possibly); + ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(always_t, always); + ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(never_t, never); + +#if !defined(ASIO_HAS_CONSTEXPR) + static const blocking_t instance; +#endif // !defined(ASIO_HAS_CONSTEXPR) + +private: + int value_; +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T blocking_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_CONSTEXPR) +template +const blocking_t blocking_t::instance; +#endif + +template +const typename blocking_t::possibly_t blocking_t::possibly; + +template +const typename blocking_t::always_t blocking_t::always; + +template +const typename blocking_t::never_t blocking_t::never; + +namespace blocking { + +template +struct possibly_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = true); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = true); + typedef blocking_t polymorphic_query_result_type; + + ASIO_CONSTEXPR possibly_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template + static ASIO_CONSTEXPR possibly_t static_query( + typename enable_if< + !traits::query_static_constexpr_member::is_valid + && !traits::query_member::is_valid + && !traits::query_free::is_valid + && !can_query >::value + && !can_query >::value + >::type* = 0) ASIO_NOEXCEPT + { + return possibly_t(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = possibly_t::static_query(); +#endif // defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + static ASIO_CONSTEXPR blocking_t value() + { + return possibly_t(); + } + + friend ASIO_CONSTEXPR bool operator==( + const possibly_t&, const possibly_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator!=( + const possibly_t&, const possibly_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator==( + const possibly_t&, const always_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator!=( + const possibly_t&, const always_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator==( + const possibly_t&, const never_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator!=( + const possibly_t&, const never_t&) + { + return true; + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T possibly_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +class adapter +{ +public: + adapter(int, const Executor& e) ASIO_NOEXCEPT + : executor_(e) + { + } + + adapter(const adapter& other) ASIO_NOEXCEPT + : executor_(other.executor_) + { + } + +#if defined(ASIO_HAS_MOVE) + adapter(adapter&& other) ASIO_NOEXCEPT + : executor_(ASIO_MOVE_CAST(Executor)(other.executor_)) + { + } +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + template + static ASIO_CONSTEXPR always_t query( + blocking_t) ASIO_NOEXCEPT + { + return always_t(); + } + + template + static ASIO_CONSTEXPR always_t query( + possibly_t) ASIO_NOEXCEPT + { + return always_t(); + } + + template + static ASIO_CONSTEXPR always_t query( + always_t) ASIO_NOEXCEPT + { + return always_t(); + } + + template + static ASIO_CONSTEXPR always_t query( + never_t) ASIO_NOEXCEPT + { + return always_t(); + } + + template + typename enable_if< + can_query::value, + typename query_result::type + >::type query(const Property& p) const + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) + { + return asio::query(executor_, p); + } + + template + typename enable_if< + can_require >::value, + typename require_result >::type + >::type require(possibly_t) const ASIO_NOEXCEPT + { + return asio::require(executor_, possibly_t()); + } + + template + typename enable_if< + can_require >::value, + typename require_result >::type + >::type require(never_t) const ASIO_NOEXCEPT + { + return asio::require(executor_, never_t()); + } + + template + typename enable_if< + can_require::value, + adapter::type + >::type> + >::type require(const Property& p) const + ASIO_NOEXCEPT_IF(( + is_nothrow_require::value)) + { + return adapter::type + >::type>(0, asio::require(executor_, p)); + } + + template + typename enable_if< + can_prefer::value, + adapter::type + >::type> + >::type prefer(const Property& p) const + ASIO_NOEXCEPT_IF(( + is_nothrow_prefer::value)) + { + return adapter::type + >::type>(0, asio::prefer(executor_, p)); + } + + template + typename enable_if< + execution::can_execute::value + >::type execute(ASIO_MOVE_ARG(Function) f) const + { + blocking_adaptation::blocking_execute( + executor_, ASIO_MOVE_CAST(Function)(f)); + } + + friend bool operator==(const adapter& a, const adapter& b) ASIO_NOEXCEPT + { + return a.executor_ == b.executor_; + } + + friend bool operator!=(const adapter& a, const adapter& b) ASIO_NOEXCEPT + { + return a.executor_ != b.executor_; + } + +private: + Executor executor_; +}; + +template +struct always_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = true); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = false); + typedef blocking_t polymorphic_query_result_type; + + ASIO_CONSTEXPR always_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = always_t::static_query(); +#endif // defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + static ASIO_CONSTEXPR blocking_t value() + { + return always_t(); + } + + friend ASIO_CONSTEXPR bool operator==( + const always_t&, const always_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator!=( + const always_t&, const always_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator==( + const always_t&, const possibly_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator!=( + const always_t&, const possibly_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator==( + const always_t&, const never_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator!=( + const always_t&, const never_t&) + { + return true; + } + + template + friend adapter require( + const Executor& e, const always_t&, + typename enable_if< + is_executor::value + && traits::static_require< + const Executor&, + blocking_adaptation::allowed_t<0> + >::is_valid + >::type* = 0) + { + return adapter(0, e); + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T always_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct never_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = true); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = true); + typedef blocking_t polymorphic_query_result_type; + + ASIO_CONSTEXPR never_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = never_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + static ASIO_CONSTEXPR blocking_t value() + { + return never_t(); + } + + friend ASIO_CONSTEXPR bool operator==( + const never_t&, const never_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator!=( + const never_t&, const never_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator==( + const never_t&, const possibly_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator!=( + const never_t&, const possibly_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator==( + const never_t&, const always_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator!=( + const never_t&, const always_t&) + { + return true; + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T never_t::static_query_v; +#endif // defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +} // namespace blocking +} // namespace detail + +typedef detail::blocking_t<> blocking_t; + +#if defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +constexpr blocking_t blocking; +#else // defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +namespace { static const blocking_t& blocking = blocking_t::instance; } +#endif + +} // namespace execution + +#if !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +#endif // !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +namespace traits { + +#if !defined(ASIO_HAS_DEDUCED_QUERY_FREE_TRAIT) + +template +struct query_free_default::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + + typedef execution::blocking_t result_type; +}; + +template +struct query_free_default::value + && can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + + typedef execution::blocking_t result_type; +}; + +template +struct query_free_default::value + && !can_query::value + && can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + + typedef execution::blocking_t result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_QUERY_FREE_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && traits::static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::static_query::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::static_query::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::static_query::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::static_query::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::static_query::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::static_query::value(); + } +}; + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && !traits::query_free::is_valid + && !can_query::value + && !can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef execution::blocking_t::possibly_t result_type; + + static ASIO_CONSTEXPR result_type value() + { + return result_type(); + } +}; + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +#endif // !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_DEDUCED_STATIC_REQUIRE_TRAIT) + +template +struct static_require::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = + (is_same::result_type, + execution::blocking_t::possibly_t>::value)); +}; + +template +struct static_require::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = + (is_same::result_type, + execution::blocking_t::always_t>::value)); +}; + +template +struct static_require::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = + (is_same::result_type, + execution::blocking_t::never_t>::value)); +}; + +#endif // !defined(ASIO_HAS_DEDUCED_STATIC_REQUIRE_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_REQUIRE_FREE_TRAIT) + +template +struct require_free_default::type>::value + && execution::is_executor::value + && traits::static_require< + const T&, + execution::detail::blocking_adaptation::allowed_t<0> + >::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = false); + typedef execution::detail::blocking::adapter result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_REQUIRE_FREE_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_EQUALITY_COMPARABLE_TRAIT) + +template +struct equality_comparable< + execution::detail::blocking::adapter > +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); +}; + +#endif // !defined(ASIO_HAS_DEDUCED_EQUALITY_COMPARABLE_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_EXECUTE_MEMBER_TRAIT) + +template +struct execute_member< + execution::detail::blocking::adapter, Function> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = false); + typedef void result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_EXECUTE_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_QUERY_STATIC_CONSTEXPR_MEMBER_TRAIT) + +template +struct query_static_constexpr_member< + execution::detail::blocking::adapter, + execution::detail::blocking_t > +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef execution::blocking_t::always_t result_type; + + static ASIO_CONSTEXPR result_type value() ASIO_NOEXCEPT + { + return result_type(); + } +}; + +template +struct query_static_constexpr_member< + execution::detail::blocking::adapter, + execution::detail::blocking::always_t > +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef execution::blocking_t::always_t result_type; + + static ASIO_CONSTEXPR result_type value() ASIO_NOEXCEPT + { + return result_type(); + } +}; + +template +struct query_static_constexpr_member< + execution::detail::blocking::adapter, + execution::detail::blocking::possibly_t > +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef execution::blocking_t::always_t result_type; + + static ASIO_CONSTEXPR result_type value() ASIO_NOEXCEPT + { + return result_type(); + } +}; + +template +struct query_static_constexpr_member< + execution::detail::blocking::adapter, + execution::detail::blocking::never_t > +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef execution::blocking_t::always_t result_type; + + static ASIO_CONSTEXPR result_type value() ASIO_NOEXCEPT + { + return result_type(); + } +}; + +#endif // !defined(ASIO_HAS_DEDUCED_QUERY_STATIC_CONSTEXPR_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_QUERY_MEMBER_TRAIT) + +template +struct query_member< + execution::detail::blocking::adapter, Property, + typename enable_if< + can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + typedef typename query_result::type result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_QUERY_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_REQUIRE_MEMBER_TRAIT) + +template +struct require_member< + execution::detail::blocking::adapter, + execution::detail::blocking::possibly_t, + typename enable_if< + can_require< + const Executor&, + execution::detail::blocking::possibly_t + >::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_require >::value)); + typedef typename require_result >::type result_type; +}; + +template +struct require_member< + execution::detail::blocking::adapter, + execution::detail::blocking::never_t, + typename enable_if< + can_require< + const Executor&, + execution::detail::blocking::never_t + >::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_require >::value)); + typedef typename require_result >::type result_type; +}; + +template +struct require_member< + execution::detail::blocking::adapter, Property, + typename enable_if< + can_require::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_require::value)); + typedef execution::detail::blocking::adapter::type + >::type> result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_REQUIRE_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_PREFER_MEMBER_TRAIT) + +template +struct prefer_member< + execution::detail::blocking::adapter, Property, + typename enable_if< + can_prefer::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_prefer::value)); + typedef execution::detail::blocking::adapter::type + >::type> result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_PREFER_MEMBER_TRAIT) + +} // namespace traits + +#endif // defined(GENERATING_DOCUMENTATION) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_BLOCKING_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/blocking_adaptation.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/blocking_adaptation.hpp new file mode 100644 index 000000000..8f4bf81d9 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/blocking_adaptation.hpp @@ -0,0 +1,1064 @@ +// +// execution/blocking_adaptation.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_BLOCKING_ADAPTATION_HPP +#define ASIO_EXECUTION_BLOCKING_ADAPTATION_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/event.hpp" +#include "asio/detail/mutex.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/execute.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/scheduler.hpp" +#include "asio/execution/sender.hpp" +#include "asio/is_applicable_property.hpp" +#include "asio/prefer.hpp" +#include "asio/query.hpp" +#include "asio/require.hpp" +#include "asio/traits/prefer_member.hpp" +#include "asio/traits/query_free.hpp" +#include "asio/traits/query_member.hpp" +#include "asio/traits/query_static_constexpr_member.hpp" +#include "asio/traits/require_member.hpp" +#include "asio/traits/static_query.hpp" +#include "asio/traits/static_require.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if defined(GENERATING_DOCUMENTATION) + +namespace execution { + +/// A property to describe whether automatic adaptation of an executor is +/// allowed in order to apply the blocking_adaptation_t::allowed_t property. +struct blocking_adaptation_t +{ + /// The blocking_adaptation_t property applies to executors, senders, and + /// schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The top-level blocking_adaptation_t property cannot be required. + static constexpr bool is_requirable = false; + + /// The top-level blocking_adaptation_t property cannot be preferred. + static constexpr bool is_preferable = false; + + /// The type returned by queries against an @c any_executor. + typedef blocking_adaptation_t polymorphic_query_result_type; + + /// A sub-property that indicates that automatic adaptation is not allowed. + struct disallowed_t + { + /// The blocking_adaptation_t::disallowed_t property applies to executors, + /// senders, and schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The blocking_adaptation_t::disallowed_t property can be required. + static constexpr bool is_requirable = true; + + /// The blocking_adaptation_t::disallowed_t property can be preferred. + static constexpr bool is_preferable = true; + + /// The type returned by queries against an @c any_executor. + typedef blocking_adaptation_t polymorphic_query_result_type; + + /// Default constructor. + constexpr disallowed_t(); + + /// Get the value associated with a property object. + /** + * @returns disallowed_t(); + */ + static constexpr blocking_adaptation_t value(); + }; + + /// A sub-property that indicates that automatic adaptation is allowed. + struct allowed_t + { + /// The blocking_adaptation_t::allowed_t property applies to executors, + /// senders, and schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The blocking_adaptation_t::allowed_t property can be required. + static constexpr bool is_requirable = true; + + /// The blocking_adaptation_t::allowed_t property can be preferred. + static constexpr bool is_preferable = false; + + /// The type returned by queries against an @c any_executor. + typedef blocking_adaptation_t polymorphic_query_result_type; + + /// Default constructor. + constexpr allowed_t(); + + /// Get the value associated with a property object. + /** + * @returns allowed_t(); + */ + static constexpr blocking_adaptation_t value(); + }; + + /// A special value used for accessing the blocking_adaptation_t::disallowed_t + /// property. + static constexpr disallowed_t disallowed; + + /// A special value used for accessing the blocking_adaptation_t::allowed_t + /// property. + static constexpr allowed_t allowed; + + /// Default constructor. + constexpr blocking_adaptation_t(); + + /// Construct from a sub-property value. + constexpr blocking_adaptation_t(disallowed_t); + + /// Construct from a sub-property value. + constexpr blocking_adaptation_t(allowed_t); + + /// Compare property values for equality. + friend constexpr bool operator==( + const blocking_adaptation_t& a, const blocking_adaptation_t& b) noexcept; + + /// Compare property values for inequality. + friend constexpr bool operator!=( + const blocking_adaptation_t& a, const blocking_adaptation_t& b) noexcept; +}; + +/// A special value used for accessing the blocking_adaptation_t property. +constexpr blocking_adaptation_t blocking_adaptation; + +} // namespace execution + +#else // defined(GENERATING_DOCUMENTATION) + +namespace execution { +namespace detail { +namespace blocking_adaptation { + +template struct disallowed_t; +template struct allowed_t; + +} // namespace blocking_adaptation + +template +struct blocking_adaptation_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = false); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = false); + typedef blocking_adaptation_t polymorphic_query_result_type; + + typedef detail::blocking_adaptation::disallowed_t disallowed_t; + typedef detail::blocking_adaptation::allowed_t allowed_t; + + ASIO_CONSTEXPR blocking_adaptation_t() + : value_(-1) + { + } + + ASIO_CONSTEXPR blocking_adaptation_t(disallowed_t) + : value_(0) + { + } + + ASIO_CONSTEXPR blocking_adaptation_t(allowed_t) + : value_(1) + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member< + T, blocking_adaptation_t>::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member< + T, blocking_adaptation_t + >::is_noexcept)) + { + return traits::query_static_constexpr_member< + T, blocking_adaptation_t>::value(); + } + + template + static ASIO_CONSTEXPR + typename traits::static_query::result_type + static_query( + typename enable_if< + !traits::query_static_constexpr_member< + T, blocking_adaptation_t>::is_valid + && !traits::query_member::is_valid + && traits::static_query::is_valid + >::type* = 0) ASIO_NOEXCEPT + { + return traits::static_query::value(); + } + + template + static ASIO_CONSTEXPR + typename traits::static_query::result_type + static_query( + typename enable_if< + !traits::query_static_constexpr_member< + T, blocking_adaptation_t>::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type* = 0) ASIO_NOEXCEPT + { + return traits::static_query::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = blocking_adaptation_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + friend ASIO_CONSTEXPR bool operator==( + const blocking_adaptation_t& a, const blocking_adaptation_t& b) + { + return a.value_ == b.value_; + } + + friend ASIO_CONSTEXPR bool operator!=( + const blocking_adaptation_t& a, const blocking_adaptation_t& b) + { + return a.value_ != b.value_; + } + + struct convertible_from_blocking_adaptation_t + { + ASIO_CONSTEXPR convertible_from_blocking_adaptation_t( + blocking_adaptation_t) + { + } + }; + + template + friend ASIO_CONSTEXPR blocking_adaptation_t query( + const Executor& ex, convertible_from_blocking_adaptation_t, + typename enable_if< + can_query::value + >::type* = 0) +#if !defined(__clang__) // Clang crashes if noexcept is used here. +#if defined(ASIO_MSVC) // Visual C++ wants the type to be qualified. + ASIO_NOEXCEPT_IF(( + is_nothrow_query::disallowed_t>::value)) +#else // defined(ASIO_MSVC) + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#endif // defined(ASIO_MSVC) +#endif // !defined(__clang__) + { + return asio::query(ex, disallowed_t()); + } + + template + friend ASIO_CONSTEXPR blocking_adaptation_t query( + const Executor& ex, convertible_from_blocking_adaptation_t, + typename enable_if< + !can_query::value + && can_query::value + >::type* = 0) +#if !defined(__clang__) // Clang crashes if noexcept is used here. +#if defined(ASIO_MSVC) // Visual C++ wants the type to be qualified. + ASIO_NOEXCEPT_IF(( + is_nothrow_query::allowed_t>::value)) +#else // defined(ASIO_MSVC) + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#endif // defined(ASIO_MSVC) +#endif // !defined(__clang__) + { + return asio::query(ex, allowed_t()); + } + + ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(disallowed_t, disallowed); + ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(allowed_t, allowed); + +#if !defined(ASIO_HAS_CONSTEXPR) + static const blocking_adaptation_t instance; +#endif // !defined(ASIO_HAS_CONSTEXPR) + +private: + int value_; +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T blocking_adaptation_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_CONSTEXPR) +template +const blocking_adaptation_t blocking_adaptation_t::instance; +#endif + +template +const typename blocking_adaptation_t::disallowed_t +blocking_adaptation_t::disallowed; + +template +const typename blocking_adaptation_t::allowed_t +blocking_adaptation_t::allowed; + +namespace blocking_adaptation { + +template +struct disallowed_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = true); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = true); + typedef blocking_adaptation_t polymorphic_query_result_type; + + ASIO_CONSTEXPR disallowed_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template + static ASIO_CONSTEXPR disallowed_t static_query( + typename enable_if< + !traits::query_static_constexpr_member::is_valid + && !traits::query_member::is_valid + && !traits::query_free::is_valid + && !can_query >::value + >::type* = 0) ASIO_NOEXCEPT + { + return disallowed_t(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = disallowed_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + static ASIO_CONSTEXPR blocking_adaptation_t value() + { + return disallowed_t(); + } + + friend ASIO_CONSTEXPR bool operator==( + const disallowed_t&, const disallowed_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator!=( + const disallowed_t&, const disallowed_t&) + { + return false; + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T disallowed_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +class adapter +{ +public: + adapter(int, const Executor& e) ASIO_NOEXCEPT + : executor_(e) + { + } + + adapter(const adapter& other) ASIO_NOEXCEPT + : executor_(other.executor_) + { + } + +#if defined(ASIO_HAS_MOVE) + adapter(adapter&& other) ASIO_NOEXCEPT + : executor_(ASIO_MOVE_CAST(Executor)(other.executor_)) + { + } +#endif // defined(ASIO_HAS_MOVE) || defined(GENERATING_DOCUMENTATION) + + template + static ASIO_CONSTEXPR allowed_t query( + blocking_adaptation_t) ASIO_NOEXCEPT + { + return allowed_t(); + } + + template + static ASIO_CONSTEXPR allowed_t query( + allowed_t) ASIO_NOEXCEPT + { + return allowed_t(); + } + + template + static ASIO_CONSTEXPR allowed_t query( + disallowed_t) ASIO_NOEXCEPT + { + return allowed_t(); + } + + template + typename enable_if< + can_query::value, + typename query_result::type + >::type query(const Property& p) const + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) + { + return asio::query(executor_, p); + } + + template + Executor require(disallowed_t) const ASIO_NOEXCEPT + { + return executor_; + } + + template + typename enable_if< + can_require::value, + adapter::type + >::type> + >::type require(const Property& p) const + ASIO_NOEXCEPT_IF(( + is_nothrow_require::value)) + { + return adapter::type + >::type>(0, asio::require(executor_, p)); + } + + template + typename enable_if< + can_prefer::value, + adapter::type + >::type> + >::type prefer(const Property& p) const + ASIO_NOEXCEPT_IF(( + is_nothrow_prefer::value)) + { + return adapter::type + >::type>(0, asio::prefer(executor_, p)); + } + + template + typename enable_if< + execution::can_execute::value + >::type execute(ASIO_MOVE_ARG(Function) f) const + { + execution::execute(executor_, ASIO_MOVE_CAST(Function)(f)); + } + + friend bool operator==(const adapter& a, const adapter& b) ASIO_NOEXCEPT + { + return a.executor_ == b.executor_; + } + + friend bool operator!=(const adapter& a, const adapter& b) ASIO_NOEXCEPT + { + return a.executor_ != b.executor_; + } + +private: + Executor executor_; +}; + +template +struct allowed_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = true); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = false); + typedef blocking_adaptation_t polymorphic_query_result_type; + + ASIO_CONSTEXPR allowed_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = allowed_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + static ASIO_CONSTEXPR blocking_adaptation_t value() + { + return allowed_t(); + } + + friend ASIO_CONSTEXPR bool operator==( + const allowed_t&, const allowed_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator!=( + const allowed_t&, const allowed_t&) + { + return false; + } + + template + friend adapter require( + const Executor& e, const allowed_t&, + typename enable_if< + is_executor::value + >::type* = 0) + { + return adapter(0, e); + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T allowed_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +class blocking_execute_state +{ +public: + template + blocking_execute_state(ASIO_MOVE_ARG(F) f) + : func_(ASIO_MOVE_CAST(F)(f)), + is_complete_(false) + { + } + + template + void execute_and_wait(ASIO_MOVE_ARG(Executor) ex) + { + handler h = { this }; + execution::execute(ASIO_MOVE_CAST(Executor)(ex), h); + asio::detail::mutex::scoped_lock lock(mutex_); + while (!is_complete_) + event_.wait(lock); + } + + struct cleanup + { + ~cleanup() + { + asio::detail::mutex::scoped_lock lock(state_->mutex_); + state_->is_complete_ = true; + state_->event_.unlock_and_signal_one_for_destruction(lock); + } + + blocking_execute_state* state_; + }; + + struct handler + { + void operator()() + { + cleanup c = { state_ }; + state_->func_(); + } + + blocking_execute_state* state_; + }; + + Function func_; + asio::detail::mutex mutex_; + asio::detail::event event_; + bool is_complete_; +}; + +template +void blocking_execute( + ASIO_MOVE_ARG(Executor) ex, + ASIO_MOVE_ARG(Function) func) +{ + typedef typename decay::type func_t; + blocking_execute_state state(ASIO_MOVE_CAST(Function)(func)); + state.execute_and_wait(ex); +} + +} // namespace blocking_adaptation +} // namespace detail + +typedef detail::blocking_adaptation_t<> blocking_adaptation_t; + +#if defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +constexpr blocking_adaptation_t blocking_adaptation; +#else // defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +namespace { static const blocking_adaptation_t& + blocking_adaptation = blocking_adaptation_t::instance; } +#endif + +} // namespace execution + +#if !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +#endif // !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +namespace traits { + +#if !defined(ASIO_HAS_DEDUCED_QUERY_FREE_TRAIT) + +template +struct query_free_default::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = (is_nothrow_query::value)); + + typedef execution::blocking_adaptation_t result_type; +}; + +template +struct query_free_default::value + && can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + + typedef execution::blocking_adaptation_t result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_QUERY_FREE_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && traits::static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::static_query::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::static_query::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::static_query::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::static_query::value(); + } +}; + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && !traits::query_free::is_valid + && !can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef execution::blocking_adaptation_t::disallowed_t result_type; + + static ASIO_CONSTEXPR result_type value() + { + return result_type(); + } +}; + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +#endif // !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_DEDUCED_STATIC_REQUIRE_TRAIT) + +template +struct static_require::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = + (is_same::result_type, + execution::blocking_adaptation_t::disallowed_t>::value)); +}; + +template +struct static_require::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = + (is_same::result_type, + execution::blocking_adaptation_t::allowed_t>::value)); +}; + +#endif // !defined(ASIO_HAS_DEDUCED_STATIC_REQUIRE_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_REQUIRE_FREE_TRAIT) + +template +struct require_free_default::type>::value + && execution::is_executor::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = false); + typedef execution::detail::blocking_adaptation::adapter result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_REQUIRE_FREE_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_EQUALITY_COMPARABLE_TRAIT) + +template +struct equality_comparable< + execution::detail::blocking_adaptation::adapter > +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); +}; + +#endif // !defined(ASIO_HAS_DEDUCED_EQUALITY_COMPARABLE_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_EXECUTE_MEMBER_TRAIT) + +template +struct execute_member< + execution::detail::blocking_adaptation::adapter, Function> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = false); + typedef void result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_EXECUTE_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_QUERY_STATIC_CONSTEXPR_MEMBER_TRAIT) + +template +struct query_static_constexpr_member< + execution::detail::blocking_adaptation::adapter, + execution::detail::blocking_adaptation_t > +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef execution::blocking_adaptation_t::allowed_t result_type; + + static ASIO_CONSTEXPR result_type value() ASIO_NOEXCEPT + { + return result_type(); + } +}; + +template +struct query_static_constexpr_member< + execution::detail::blocking_adaptation::adapter, + execution::detail::blocking_adaptation::allowed_t > +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef execution::blocking_adaptation_t::allowed_t result_type; + + static ASIO_CONSTEXPR result_type value() ASIO_NOEXCEPT + { + return result_type(); + } +}; + +template +struct query_static_constexpr_member< + execution::detail::blocking_adaptation::adapter, + execution::detail::blocking_adaptation::disallowed_t > +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef execution::blocking_adaptation_t::allowed_t result_type; + + static ASIO_CONSTEXPR result_type value() ASIO_NOEXCEPT + { + return result_type(); + } +}; + +#endif // !defined(ASIO_HAS_DEDUCED_QUERY_STATIC_CONSTEXPR_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_QUERY_MEMBER_TRAIT) + +template +struct query_member< + execution::detail::blocking_adaptation::adapter, Property, + typename enable_if< + can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + typedef typename query_result::type result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_QUERY_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_REQUIRE_MEMBER_TRAIT) + +template +struct require_member< + execution::detail::blocking_adaptation::adapter, + execution::detail::blocking_adaptation::disallowed_t > +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef Executor result_type; +}; + +template +struct require_member< + execution::detail::blocking_adaptation::adapter, Property, + typename enable_if< + can_require::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_require::value)); + typedef execution::detail::blocking_adaptation::adapter::type + >::type> result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_REQUIRE_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_PREFER_MEMBER_TRAIT) + +template +struct prefer_member< + execution::detail::blocking_adaptation::adapter, Property, + typename enable_if< + can_prefer::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_prefer::value)); + typedef execution::detail::blocking_adaptation::adapter::type + >::type> result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_PREFER_MEMBER_TRAIT) + +} // namespace traits + +#endif // defined(GENERATING_DOCUMENTATION) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_BLOCKING_ADAPTATION_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/bulk_execute.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/bulk_execute.hpp new file mode 100644 index 000000000..001b6088f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/bulk_execute.hpp @@ -0,0 +1,390 @@ +// +// execution/bulk_execute.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_BULK_EXECUTE_HPP +#define ASIO_EXECUTION_BULK_EXECUTE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/bulk_guarantee.hpp" +#include "asio/execution/detail/bulk_sender.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/sender.hpp" +#include "asio/traits/bulk_execute_member.hpp" +#include "asio/traits/bulk_execute_free.hpp" + +#include "asio/detail/push_options.hpp" + +#if defined(GENERATING_DOCUMENTATION) + +namespace asio { +namespace execution { + +/// A customisation point that creates a bulk sender. +/** + * The name execution::bulk_execute denotes a customisation point + * object. If is_convertible_v is true, then the expression + * execution::bulk_execute(S, F, N) for some subexpressions + * S, F, and N is expression-equivalent to: + * + * @li S.bulk_execute(F, N), if that expression is valid. If the + * function selected does not execute N invocations of the function + * object F on the executor S in bulk with forward progress + * guarantee asio::query(S, execution::bulk_guarantee), and + * the result of that function does not model sender, the + * program is ill-formed with no diagnostic required. + * + * @li Otherwise, bulk_execute(S, F, N), if that expression is valid, + * with overload resolution performed in a context that includes the + * declaration void bulk_execute(); and that does not include a + * declaration of execution::bulk_execute. If the function selected + * by overload resolution does not execute N invocations of the + * function object F on the executor S in bulk with forward + * progress guarantee asio::query(E, + * execution::bulk_guarantee), and the result of that function does not + * model sender, the program is ill-formed with no diagnostic + * required. + * + * @li Otherwise, if the types F and + * executor_index_t> model invocable and + * if asio::query(S, execution::bulk_guarantee) equals + * execution::bulk_guarantee.unsequenced, then + * + * - Evaluates DECAY_COPY(std::forward(F)) on the + * calling thread to create a function object cf. [Note: + * Additional copies of cf may subsequently be created. --end + * note.] + * + * - For each value of i in N, cf(i) (or copy of + * cf)) will be invoked at most once by an execution agent that is + * unique for each value of i. + * + * - May block pending completion of one or more invocations of cf. + * + * - Synchronizes with (C++Std [intro.multithread]) the invocations of + * cf. + * + * @li Otherwise, execution::bulk_execute(S, F, N) is ill-formed. + */ +inline constexpr unspecified bulk_execute = unspecified; + +/// A type trait that determines whether a @c bulk_execute expression is +/// well-formed. +/** + * Class template @c can_bulk_execute is a trait that is derived from @c + * true_type if the expression execution::bulk_execute(std::declval(), + * std::declval(), std::declval) is well formed; otherwise @c + * false_type. + */ +template +struct can_bulk_execute : + integral_constant +{ +}; + +} // namespace execution +} // namespace asio + +#else // defined(GENERATING_DOCUMENTATION) + +namespace asio_execution_bulk_execute_fn { + +using asio::declval; +using asio::enable_if; +using asio::execution::bulk_guarantee_t; +using asio::execution::detail::bulk_sender; +using asio::execution::executor_index; +using asio::execution::is_sender; +using asio::is_convertible; +using asio::is_same; +using asio::remove_cvref; +using asio::result_of; +using asio::traits::bulk_execute_free; +using asio::traits::bulk_execute_member; +using asio::traits::static_require; + +void bulk_execute(); + +enum overload_type +{ + call_member, + call_free, + adapter, + ill_formed +}; + +template +struct call_traits +{ + ASIO_STATIC_CONSTEXPR(overload_type, overload = ill_formed); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = false); + typedef void result_type; +}; + +template +struct call_traits::value + && + bulk_execute_member::is_valid + && + is_sender< + typename bulk_execute_member::result_type + >::value + ) + >::type> : + bulk_execute_member +{ + ASIO_STATIC_CONSTEXPR(overload_type, overload = call_member); +}; + +template +struct call_traits::value + && + !bulk_execute_member::is_valid + && + bulk_execute_free::is_valid + && + is_sender< + typename bulk_execute_free::result_type + >::value + ) + >::type> : + bulk_execute_free +{ + ASIO_STATIC_CONSTEXPR(overload_type, overload = call_free); +}; + +template +struct call_traits::value + && + !bulk_execute_member::is_valid + && + !bulk_execute_free::is_valid + && + is_sender::value + && + is_same< + typename result_of< + F(typename executor_index::type>::type) + >::type, + typename result_of< + F(typename executor_index::type>::type) + >::type + >::value + && + static_require::is_valid + ) + >::type> +{ + ASIO_STATIC_CONSTEXPR(overload_type, overload = adapter); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = false); + typedef bulk_sender result_type; +}; + +struct impl +{ +#if defined(ASIO_HAS_MOVE) + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_member, + typename call_traits::result_type + >::type + operator()(S&& s, F&& f, N&& n) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return ASIO_MOVE_CAST(S)(s).bulk_execute( + ASIO_MOVE_CAST(F)(f), ASIO_MOVE_CAST(N)(n)); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_free, + typename call_traits::result_type + >::type + operator()(S&& s, F&& f, N&& n) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return bulk_execute(ASIO_MOVE_CAST(S)(s), + ASIO_MOVE_CAST(F)(f), ASIO_MOVE_CAST(N)(n)); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == adapter, + typename call_traits::result_type + >::type + operator()(S&& s, F&& f, N&& n) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return typename call_traits::result_type( + ASIO_MOVE_CAST(S)(s), ASIO_MOVE_CAST(F)(f), + ASIO_MOVE_CAST(N)(n)); + } +#else // defined(ASIO_HAS_MOVE) + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_member, + typename call_traits::result_type + >::type + operator()(S& s, const F& f, const N& n) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return s.bulk_execute(ASIO_MOVE_CAST(F)(f), + ASIO_MOVE_CAST(N)(n)); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_member, + typename call_traits::result_type + >::type + operator()(const S& s, const F& f, const N& n) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return s.bulk_execute(ASIO_MOVE_CAST(F)(f), + ASIO_MOVE_CAST(N)(n)); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_free, + typename call_traits::result_type + >::type + operator()(S& s, const F& f, const N& n) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return bulk_execute(s, ASIO_MOVE_CAST(F)(f), + ASIO_MOVE_CAST(N)(n)); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_free, + typename call_traits::result_type + >::type + operator()(const S& s, const F& f, const N& n) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return bulk_execute(s, ASIO_MOVE_CAST(F)(f), + ASIO_MOVE_CAST(N)(n)); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == adapter, + typename call_traits::result_type + >::type + operator()(S& s, const F& f, const N& n) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return typename call_traits::result_type( + s, ASIO_MOVE_CAST(F)(f), ASIO_MOVE_CAST(N)(n)); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == adapter, + typename call_traits::result_type + >::type + operator()(const S& s, const F& f, const N& n) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return typename call_traits::result_type( + s, ASIO_MOVE_CAST(F)(f), ASIO_MOVE_CAST(N)(n)); + } +#endif // defined(ASIO_HAS_MOVE) +}; + +template +struct static_instance +{ + static const T instance; +}; + +template +const T static_instance::instance = {}; + +} // namespace asio_execution_bulk_execute_fn +namespace asio { +namespace execution { +namespace { + +static ASIO_CONSTEXPR + const asio_execution_bulk_execute_fn::impl& bulk_execute = + asio_execution_bulk_execute_fn::static_instance<>::instance; + +} // namespace + +template +struct can_bulk_execute : + integral_constant::overload != + asio_execution_bulk_execute_fn::ill_formed> +{ +}; + +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +constexpr bool can_bulk_execute_v = can_bulk_execute::value; + +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +struct is_nothrow_bulk_execute : + integral_constant::is_noexcept> +{ +}; + +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +constexpr bool is_nothrow_bulk_execute_v + = is_nothrow_bulk_execute::value; + +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +struct bulk_execute_result +{ + typedef typename asio_execution_bulk_execute_fn::call_traits< + S, void(F, N)>::result_type type; +}; + +} // namespace execution +} // namespace asio + +#endif // defined(GENERATING_DOCUMENTATION) + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_BULK_EXECUTE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/bulk_guarantee.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/bulk_guarantee.hpp new file mode 100644 index 000000000..4a099f582 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/bulk_guarantee.hpp @@ -0,0 +1,1018 @@ +// +// execution/bulk_guarantee.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_BULK_GUARANTEE_HPP +#define ASIO_EXECUTION_BULK_GUARANTEE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/scheduler.hpp" +#include "asio/execution/sender.hpp" +#include "asio/is_applicable_property.hpp" +#include "asio/query.hpp" +#include "asio/traits/query_free.hpp" +#include "asio/traits/query_member.hpp" +#include "asio/traits/query_static_constexpr_member.hpp" +#include "asio/traits/static_query.hpp" +#include "asio/traits/static_require.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if defined(GENERATING_DOCUMENTATION) + +namespace execution { + +/// A property to communicate the forward progress and ordering guarantees of +/// execution agents associated with the bulk execution. +struct bulk_guarantee_t +{ + /// The bulk_guarantee_t property applies to executors, senders, and + /// schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The top-level bulk_guarantee_t property cannot be required. + static constexpr bool is_requirable = false; + + /// The top-level bulk_guarantee_t property cannot be preferred. + static constexpr bool is_preferable = false; + + /// The type returned by queries against an @c any_executor. + typedef bulk_guarantee_t polymorphic_query_result_type; + + /// A sub-property that indicates that execution agents within the same bulk + /// execution may be parallelised and vectorised. + struct unsequenced_t + { + /// The bulk_guarantee_t::unsequenced_t property applies to executors, + /// senders, and schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The bulk_guarantee_t::unsequenced_t property can be required. + static constexpr bool is_requirable = true; + + /// The bulk_guarantee_t::unsequenced_t property can be preferred. + static constexpr bool is_preferable = true; + + /// The type returned by queries against an @c any_executor. + typedef bulk_guarantee_t polymorphic_query_result_type; + + /// Default constructor. + constexpr unsequenced_t(); + + /// Get the value associated with a property object. + /** + * @returns unsequenced_t(); + */ + static constexpr bulk_guarantee_t value(); + }; + + /// A sub-property that indicates that execution agents within the same bulk + /// execution may not be parallelised and vectorised. + struct sequenced_t + { + /// The bulk_guarantee_t::sequenced_t property applies to executors, + /// senders, and schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The bulk_guarantee_t::sequenced_t property can be required. + static constexpr bool is_requirable = true; + + /// The bulk_guarantee_t::sequenced_t property can be preferred. + static constexpr bool is_preferable = true; + + /// The type returned by queries against an @c any_executor. + typedef bulk_guarantee_t polymorphic_query_result_type; + + /// Default constructor. + constexpr sequenced_t(); + + /// Get the value associated with a property object. + /** + * @returns sequenced_t(); + */ + static constexpr bulk_guarantee_t value(); + }; + + /// A sub-property that indicates that execution agents within the same bulk + /// execution may be parallelised. + struct parallel_t + { + /// The bulk_guarantee_t::parallel_t property applies to executors, + /// senders, and schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The bulk_guarantee_t::parallel_t property can be required. + static constexpr bool is_requirable = true; + + /// The bulk_guarantee_t::parallel_t property can be preferred. + static constexpr bool is_preferable = true; + + /// The type returned by queries against an @c any_executor. + typedef bulk_guarantee_t polymorphic_query_result_type; + + /// Default constructor. + constexpr parallel_t(); + + /// Get the value associated with a property object. + /** + * @returns parallel_t(); + */ + static constexpr bulk_guarantee_t value(); + }; + + /// A special value used for accessing the bulk_guarantee_t::unsequenced_t + /// property. + static constexpr unsequenced_t unsequenced; + + /// A special value used for accessing the bulk_guarantee_t::sequenced_t + /// property. + static constexpr sequenced_t sequenced; + + /// A special value used for accessing the bulk_guarantee_t::parallel_t + /// property. + static constexpr parallel_t parallel; + + /// Default constructor. + constexpr bulk_guarantee_t(); + + /// Construct from a sub-property value. + constexpr bulk_guarantee_t(unsequenced_t); + + /// Construct from a sub-property value. + constexpr bulk_guarantee_t(sequenced_t); + + /// Construct from a sub-property value. + constexpr bulk_guarantee_t(parallel_t); + + /// Compare property values for equality. + friend constexpr bool operator==( + const bulk_guarantee_t& a, const bulk_guarantee_t& b) noexcept; + + /// Compare property values for inequality. + friend constexpr bool operator!=( + const bulk_guarantee_t& a, const bulk_guarantee_t& b) noexcept; +}; + +/// A special value used for accessing the bulk_guarantee_t property. +constexpr bulk_guarantee_t bulk_guarantee; + +} // namespace execution + +#else // defined(GENERATING_DOCUMENTATION) + +namespace execution { +namespace detail { +namespace bulk_guarantee { + +template struct unsequenced_t; +template struct sequenced_t; +template struct parallel_t; + +} // namespace bulk_guarantee + +template +struct bulk_guarantee_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = false); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = false); + typedef bulk_guarantee_t polymorphic_query_result_type; + + typedef detail::bulk_guarantee::unsequenced_t unsequenced_t; + typedef detail::bulk_guarantee::sequenced_t sequenced_t; + typedef detail::bulk_guarantee::parallel_t parallel_t; + + ASIO_CONSTEXPR bulk_guarantee_t() + : value_(-1) + { + } + + ASIO_CONSTEXPR bulk_guarantee_t(unsequenced_t) + : value_(0) + { + } + + ASIO_CONSTEXPR bulk_guarantee_t(sequenced_t) + : value_(1) + { + } + + ASIO_CONSTEXPR bulk_guarantee_t(parallel_t) + : value_(2) + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member< + T, bulk_guarantee_t>::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template + static ASIO_CONSTEXPR + typename traits::static_query::result_type + static_query( + typename enable_if< + !traits::query_static_constexpr_member::is_valid + && !traits::query_member::is_valid + && traits::static_query::is_valid + >::type* = 0) ASIO_NOEXCEPT + { + return traits::static_query::value(); + } + + template + static ASIO_CONSTEXPR + typename traits::static_query::result_type + static_query( + typename enable_if< + !traits::query_static_constexpr_member::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type* = 0) ASIO_NOEXCEPT + { + return traits::static_query::value(); + } + + template + static ASIO_CONSTEXPR + typename traits::static_query::result_type + static_query( + typename enable_if< + !traits::query_static_constexpr_member::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type* = 0) ASIO_NOEXCEPT + { + return traits::static_query::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = bulk_guarantee_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + friend ASIO_CONSTEXPR bool operator==( + const bulk_guarantee_t& a, const bulk_guarantee_t& b) + { + return a.value_ == b.value_; + } + + friend ASIO_CONSTEXPR bool operator!=( + const bulk_guarantee_t& a, const bulk_guarantee_t& b) + { + return a.value_ != b.value_; + } + + struct convertible_from_bulk_guarantee_t + { + ASIO_CONSTEXPR convertible_from_bulk_guarantee_t(bulk_guarantee_t) {} + }; + + template + friend ASIO_CONSTEXPR bulk_guarantee_t query( + const Executor& ex, convertible_from_bulk_guarantee_t, + typename enable_if< + can_query::value + >::type* = 0) +#if !defined(__clang__) // Clang crashes if noexcept is used here. +#if defined(ASIO_MSVC) // Visual C++ wants the type to be qualified. + ASIO_NOEXCEPT_IF(( + is_nothrow_query::unsequenced_t>::value)) +#else // defined(ASIO_MSVC) + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#endif // defined(ASIO_MSVC) +#endif // !defined(__clang__) + { + return asio::query(ex, unsequenced_t()); + } + + template + friend ASIO_CONSTEXPR bulk_guarantee_t query( + const Executor& ex, convertible_from_bulk_guarantee_t, + typename enable_if< + !can_query::value + && can_query::value + >::type* = 0) +#if !defined(__clang__) // Clang crashes if noexcept is used here. +#if defined(ASIO_MSVC) // Visual C++ wants the type to be qualified. + ASIO_NOEXCEPT_IF(( + is_nothrow_query::sequenced_t>::value)) +#else // defined(ASIO_MSVC) + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#endif // defined(ASIO_MSVC) +#endif // !defined(__clang__) + { + return asio::query(ex, sequenced_t()); + } + + template + friend ASIO_CONSTEXPR bulk_guarantee_t query( + const Executor& ex, convertible_from_bulk_guarantee_t, + typename enable_if< + !can_query::value + && !can_query::value + && can_query::value + >::type* = 0) +#if !defined(__clang__) // Clang crashes if noexcept is used here. +#if defined(ASIO_MSVC) // Visual C++ wants the type to be qualified. + ASIO_NOEXCEPT_IF(( + is_nothrow_query::parallel_t>::value)) +#else // defined(ASIO_MSVC) + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#endif // defined(ASIO_MSVC) +#endif // !defined(__clang__) + { + return asio::query(ex, parallel_t()); + } + + ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(unsequenced_t, unsequenced); + ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(sequenced_t, sequenced); + ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(parallel_t, parallel); + +#if !defined(ASIO_HAS_CONSTEXPR) + static const bulk_guarantee_t instance; +#endif // !defined(ASIO_HAS_CONSTEXPR) + +private: + int value_; +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T bulk_guarantee_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_CONSTEXPR) +template +const bulk_guarantee_t bulk_guarantee_t::instance; +#endif + +template +const typename bulk_guarantee_t::unsequenced_t +bulk_guarantee_t::unsequenced; + +template +const typename bulk_guarantee_t::sequenced_t +bulk_guarantee_t::sequenced; + +template +const typename bulk_guarantee_t::parallel_t +bulk_guarantee_t::parallel; + +namespace bulk_guarantee { + +template +struct unsequenced_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = true); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = true); + typedef bulk_guarantee_t polymorphic_query_result_type; + + ASIO_CONSTEXPR unsequenced_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template + static ASIO_CONSTEXPR unsequenced_t static_query( + typename enable_if< + !traits::query_static_constexpr_member::is_valid + && !traits::query_member::is_valid + && !traits::query_free::is_valid + && !can_query >::value + && !can_query >::value + >::type* = 0) ASIO_NOEXCEPT + { + return unsequenced_t(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = unsequenced_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + static ASIO_CONSTEXPR bulk_guarantee_t value() + { + return unsequenced_t(); + } + + friend ASIO_CONSTEXPR bool operator==( + const unsequenced_t&, const unsequenced_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator!=( + const unsequenced_t&, const unsequenced_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator==( + const unsequenced_t&, const sequenced_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator!=( + const unsequenced_t&, const sequenced_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator==( + const unsequenced_t&, const parallel_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator!=( + const unsequenced_t&, const parallel_t&) + { + return true; + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T unsequenced_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct sequenced_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = true); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = true); + typedef bulk_guarantee_t polymorphic_query_result_type; + + ASIO_CONSTEXPR sequenced_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = sequenced_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + static ASIO_CONSTEXPR bulk_guarantee_t value() + { + return sequenced_t(); + } + + friend ASIO_CONSTEXPR bool operator==( + const sequenced_t&, const sequenced_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator!=( + const sequenced_t&, const sequenced_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator==( + const sequenced_t&, const unsequenced_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator!=( + const sequenced_t&, const unsequenced_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator==( + const sequenced_t&, const parallel_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator!=( + const sequenced_t&, const parallel_t&) + { + return true; + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T sequenced_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct parallel_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = true); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = true); + typedef bulk_guarantee_t polymorphic_query_result_type; + + ASIO_CONSTEXPR parallel_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = parallel_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + static ASIO_CONSTEXPR bulk_guarantee_t value() + { + return parallel_t(); + } + + friend ASIO_CONSTEXPR bool operator==( + const parallel_t&, const parallel_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator!=( + const parallel_t&, const parallel_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator==( + const parallel_t&, const unsequenced_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator!=( + const parallel_t&, const unsequenced_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator==( + const parallel_t&, const sequenced_t&) + { + return false; + } + + friend ASIO_CONSTEXPR bool operator!=( + const parallel_t&, const sequenced_t&) + { + return true; + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T parallel_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +} // namespace bulk_guarantee +} // namespace detail + +typedef detail::bulk_guarantee_t<> bulk_guarantee_t; + +#if defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +constexpr bulk_guarantee_t bulk_guarantee; +#else // defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +namespace { static const bulk_guarantee_t& + bulk_guarantee = bulk_guarantee_t::instance; } +#endif + +} // namespace execution + +#if !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +#endif // !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +namespace traits { + +#if !defined(ASIO_HAS_DEDUCED_QUERY_FREE_TRAIT) + +template +struct query_free_default::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + + typedef execution::bulk_guarantee_t result_type; +}; + +template +struct query_free_default::value + && can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + + typedef execution::bulk_guarantee_t result_type; +}; + +template +struct query_free_default::value + && !can_query::value + && can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + + typedef execution::bulk_guarantee_t result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_QUERY_FREE_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && traits::static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::static_query::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::static_query::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::static_query::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::static_query::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::static_query::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::static_query::value(); + } +}; + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && !traits::query_free::is_valid + && !can_query::value + && !can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef execution::bulk_guarantee_t::unsequenced_t result_type; + + static ASIO_CONSTEXPR result_type value() + { + return result_type(); + } +}; + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +#endif // !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_DEDUCED_STATIC_REQUIRE_TRAIT) + +template +struct static_require::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = + (is_same::result_type, + execution::bulk_guarantee_t::unsequenced_t>::value)); +}; + +template +struct static_require::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = + (is_same::result_type, + execution::bulk_guarantee_t::sequenced_t>::value)); +}; + +template +struct static_require::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = + (is_same::result_type, + execution::bulk_guarantee_t::parallel_t>::value)); +}; + +#endif // !defined(ASIO_HAS_DEDUCED_STATIC_REQUIRE_TRAIT) + +} // namespace traits + +#endif // defined(GENERATING_DOCUMENTATION) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_BULK_GUARANTEE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/connect.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/connect.hpp new file mode 100644 index 000000000..47dd58b69 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/connect.hpp @@ -0,0 +1,486 @@ +// +// execution/connect.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_CONNECT_HPP +#define ASIO_EXECUTION_CONNECT_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/detail/as_invocable.hpp" +#include "asio/execution/detail/as_operation.hpp" +#include "asio/execution/detail/as_receiver.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/operation_state.hpp" +#include "asio/execution/receiver.hpp" +#include "asio/execution/sender.hpp" +#include "asio/traits/connect_member.hpp" +#include "asio/traits/connect_free.hpp" + +#include "asio/detail/push_options.hpp" + +#if defined(GENERATING_DOCUMENTATION) + +namespace asio { +namespace execution { + +/// A customisation point that connects a sender to a receiver. +/** + * The name execution::connect denotes a customisation point object. + * For some subexpressions s and r, let S be a type + * such that decltype((s)) is S and let R be a type + * such that decltype((r)) is R. The expression + * execution::connect(s, r) is expression-equivalent to: + * + * @li s.connect(r), if that expression is valid, if its type + * satisfies operation_state, and if S satisfies + * sender. + * + * @li Otherwise, connect(s, r), if that expression is valid, if its + * type satisfies operation_state, and if S satisfies + * sender, with overload resolution performed in a context that + * includes the declaration void connect(); and that does not include + * a declaration of execution::connect. + * + * @li Otherwise, as_operation{s, r}, if r is not an instance + * of as_receiver for some type F, and if + * receiver_of && executor_of, + * as_invocable, S>> is true, where + * as_operation is an implementation-defined class equivalent to + * @code template + * struct as_operation + * { + * remove_cvref_t e_; + * remove_cvref_t r_; + * void start() noexcept try { + * execution::execute(std::move(e_), + * as_invocable, S>{r_}); + * } catch(...) { + * execution::set_error(std::move(r_), current_exception()); + * } + * }; @endcode + * and as_invocable is a class template equivalent to the following: + * @code template + * struct as_invocable + * { + * R* r_; + * explicit as_invocable(R& r) noexcept + * : r_(std::addressof(r)) {} + * as_invocable(as_invocable && other) noexcept + * : r_(std::exchange(other.r_, nullptr)) {} + * ~as_invocable() { + * if(r_) + * execution::set_done(std::move(*r_)); + * } + * void operator()() & noexcept try { + * execution::set_value(std::move(*r_)); + * r_ = nullptr; + * } catch(...) { + * execution::set_error(std::move(*r_), current_exception()); + * r_ = nullptr; + * } + * }; + * @endcode + * + * @li Otherwise, execution::connect(s, r) is ill-formed. + */ +inline constexpr unspecified connect = unspecified; + +/// A type trait that determines whether a @c connect expression is +/// well-formed. +/** + * Class template @c can_connect is a trait that is derived from + * @c true_type if the expression execution::connect(std::declval(), + * std::declval()) is well formed; otherwise @c false_type. + */ +template +struct can_connect : + integral_constant +{ +}; + +/// A type trait to determine the result of a @c connect expression. +template +struct connect_result +{ + /// The type of the connect expression. + /** + * The type of the expression execution::connect(std::declval(), + * std::declval()). + */ + typedef automatically_determined type; +}; + +/// A type alis to determine the result of a @c connect expression. +template +using connect_result_t = typename connect_result::type; + +} // namespace execution +} // namespace asio + +#else // defined(GENERATING_DOCUMENTATION) + +namespace asio_execution_connect_fn { + +using asio::conditional; +using asio::declval; +using asio::enable_if; +using asio::execution::detail::as_invocable; +using asio::execution::detail::as_operation; +using asio::execution::detail::is_as_receiver; +using asio::execution::is_executor_of; +using asio::execution::is_operation_state; +using asio::execution::is_receiver; +using asio::execution::is_sender; +using asio::false_type; +using asio::remove_cvref; +using asio::traits::connect_free; +using asio::traits::connect_member; + +void connect(); + +enum overload_type +{ + call_member, + call_free, + adapter, + ill_formed +}; + +template +struct call_traits +{ + ASIO_STATIC_CONSTEXPR(overload_type, overload = ill_formed); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = false); + typedef void result_type; +}; + +template +struct call_traits::is_valid + && + is_operation_state::result_type>::value + && + is_sender::type>::value + ) + >::type> : + connect_member +{ + ASIO_STATIC_CONSTEXPR(overload_type, overload = call_member); +}; + +template +struct call_traits::is_valid + && + connect_free::is_valid + && + is_operation_state::result_type>::value + && + is_sender::type>::value + ) + >::type> : + connect_free +{ + ASIO_STATIC_CONSTEXPR(overload_type, overload = call_free); +}; + +template +struct call_traits::is_valid + && + !connect_free::is_valid + && + is_receiver::value + && + conditional< + !is_as_receiver< + typename remove_cvref::type + >::value, + is_executor_of< + typename remove_cvref::type, + as_invocable::type, S> + >, + false_type + >::type::value + ) + >::type> +{ + ASIO_STATIC_CONSTEXPR(overload_type, overload = adapter); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = false); + typedef as_operation result_type; +}; + +struct impl +{ +#if defined(ASIO_HAS_MOVE) + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_member, + typename call_traits::result_type + >::type + operator()(S&& s, R&& r) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return ASIO_MOVE_CAST(S)(s).connect(ASIO_MOVE_CAST(R)(r)); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_free, + typename call_traits::result_type + >::type + operator()(S&& s, R&& r) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return connect(ASIO_MOVE_CAST(S)(s), ASIO_MOVE_CAST(R)(r)); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == adapter, + typename call_traits::result_type + >::type + operator()(S&& s, R&& r) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return typename call_traits::result_type( + ASIO_MOVE_CAST(S)(s), ASIO_MOVE_CAST(R)(r)); + } +#else // defined(ASIO_HAS_MOVE) + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_member, + typename call_traits::result_type + >::type + operator()(S& s, R& r) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return s.connect(r); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_member, + typename call_traits::result_type + >::type + operator()(const S& s, R& r) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return s.connect(r); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_free, + typename call_traits::result_type + >::type + operator()(S& s, R& r) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return connect(s, r); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_free, + typename call_traits::result_type + >::type + operator()(const S& s, R& r) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return connect(s, r); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == adapter, + typename call_traits::result_type + >::type + operator()(S& s, R& r) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return typename call_traits::result_type(s, r); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == adapter, + typename call_traits::result_type + >::type + operator()(const S& s, R& r) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return typename call_traits::result_type(s, r); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_member, + typename call_traits::result_type + >::type + operator()(S& s, const R& r) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return s.connect(r); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_member, + typename call_traits::result_type + >::type + operator()(const S& s, const R& r) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return s.connect(r); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_free, + typename call_traits::result_type + >::type + operator()(S& s, const R& r) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return connect(s, r); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_free, + typename call_traits::result_type + >::type + operator()(const S& s, const R& r) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return connect(s, r); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == adapter, + typename call_traits::result_type + >::type + operator()(S& s, const R& r) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return typename call_traits::result_type(s, r); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == adapter, + typename call_traits::result_type + >::type + operator()(const S& s, const R& r) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return typename call_traits::result_type(s, r); + } +#endif // defined(ASIO_HAS_MOVE) +}; + +template +struct static_instance +{ + static const T instance; +}; + +template +const T static_instance::instance = {}; + +} // namespace asio_execution_connect_fn +namespace asio { +namespace execution { +namespace { + +static ASIO_CONSTEXPR const asio_execution_connect_fn::impl& + connect = asio_execution_connect_fn::static_instance<>::instance; + +} // namespace + +template +struct can_connect : + integral_constant::overload != + asio_execution_connect_fn::ill_formed> +{ +}; + +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +constexpr bool can_connect_v = can_connect::value; + +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +struct is_nothrow_connect : + integral_constant::is_noexcept> +{ +}; + +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +constexpr bool is_nothrow_connect_v + = is_nothrow_connect::value; + +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +struct connect_result +{ + typedef typename asio_execution_connect_fn::call_traits< + S, void(R)>::result_type type; +}; + +#if defined(ASIO_HAS_ALIAS_TEMPLATES) + +template +using connect_result_t = typename connect_result::type; + +#endif // defined(ASIO_HAS_ALIAS_TEMPLATES) + +} // namespace execution +} // namespace asio + +#endif // defined(GENERATING_DOCUMENTATION) + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_CONNECT_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/context.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/context.hpp new file mode 100644 index 000000000..4a535d6e9 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/context.hpp @@ -0,0 +1,185 @@ +// +// execution/context.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_CONTEXT2_HPP +#define ASIO_EXECUTION_CONTEXT2_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/scheduler.hpp" +#include "asio/execution/sender.hpp" +#include "asio/is_applicable_property.hpp" +#include "asio/traits/query_static_constexpr_member.hpp" +#include "asio/traits/static_query.hpp" + +#if defined(ASIO_HAS_STD_ANY) +# include +#endif // defined(ASIO_HAS_STD_ANY) + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if defined(GENERATING_DOCUMENTATION) + +namespace execution { + +/// A property that is used to obtain the execution context that is associated +/// with an executor. +struct context_t +{ + /// The context_t property applies to executors, senders, and schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The context_t property cannot be required. + static constexpr bool is_requirable = false; + + /// The context_t property cannot be preferred. + static constexpr bool is_preferable = false; + + /// The type returned by queries against an @c any_executor. + typedef std::any polymorphic_query_result_type; +}; + +/// A special value used for accessing the context_t property. +constexpr context_t context; + +} // namespace execution + +#else // defined(GENERATING_DOCUMENTATION) + +namespace execution { +namespace detail { + +template +struct context_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = false); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = false); + +#if defined(ASIO_HAS_STD_ANY) + typedef std::any polymorphic_query_result_type; +#endif // defined(ASIO_HAS_STD_ANY) + + ASIO_CONSTEXPR context_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = context_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_CONSTEXPR) + static const context_t instance; +#endif // !defined(ASIO_HAS_CONSTEXPR) +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T context_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_CONSTEXPR) +template +const context_t context_t::instance; +#endif + +} // namespace detail + +typedef detail::context_t<> context_t; + +#if defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +constexpr context_t context; +#else // defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +namespace { static const context_t& context = context_t::instance; } +#endif + +} // namespace execution + +#if !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +#endif // !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +namespace traits { + +#if !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +#endif // !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +} // namespace traits + +#endif // defined(GENERATING_DOCUMENTATION) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_CONTEXT2_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/context_as.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/context_as.hpp new file mode 100644 index 000000000..8acc945aa --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/context_as.hpp @@ -0,0 +1,201 @@ +// +// execution/context_as.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_CONTEXT_AS_HPP +#define ASIO_EXECUTION_CONTEXT_AS_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/context.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/scheduler.hpp" +#include "asio/execution/sender.hpp" +#include "asio/is_applicable_property.hpp" +#include "asio/query.hpp" +#include "asio/traits/query_static_constexpr_member.hpp" +#include "asio/traits/static_query.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if defined(GENERATING_DOCUMENTATION) + +namespace execution { + +/// A property that is used to obtain the execution context that is associated +/// with an executor. +template +struct context_as_t +{ + /// The context_as_t property applies to executors, senders, and schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The context_t property cannot be required. + static constexpr bool is_requirable = false; + + /// The context_t property cannot be preferred. + static constexpr bool is_preferable = false; + + /// The type returned by queries against an @c any_executor. + typedef T polymorphic_query_result_type; +}; + +/// A special value used for accessing the context_as_t property. +template +constexpr context_as_t context_as; + +} // namespace execution + +#else // defined(GENERATING_DOCUMENTATION) + +namespace execution { + +template +struct context_as_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = false); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = false); + + typedef T polymorphic_query_result_type; + + ASIO_CONSTEXPR context_as_t() + { + } + + ASIO_CONSTEXPR context_as_t(context_t) + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template ())> + static ASIO_CONSTEXPR const U static_query_v + = context_as_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + template + friend ASIO_CONSTEXPR U query( + const Executor& ex, const context_as_t&, + typename enable_if< + is_same::value + && can_query::value + >::type* = 0) +#if !defined(__clang__) // Clang crashes if noexcept is used here. +#if defined(ASIO_MSVC) // Visual C++ wants the type to be qualified. + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#else // defined(ASIO_MSVC) + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#endif // defined(ASIO_MSVC) +#endif // !defined(__clang__) + { + return asio::query(ex, context); + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const U context_as_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if (defined(ASIO_HAS_VARIABLE_TEMPLATES) \ + && defined(ASIO_HAS_CONSTEXPR)) \ + || defined(GENERATING_DOCUMENTATION) +template +constexpr context_as_t context_as{}; +#endif // (defined(ASIO_HAS_VARIABLE_TEMPLATES) + // && defined(ASIO_HAS_CONSTEXPR)) + // || defined(GENERATING_DOCUMENTATION) + +} // namespace execution + +#if !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +struct is_applicable_property > + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +#endif // !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +namespace traits { + +#if !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct static_query, + typename enable_if< + static_query::is_valid + >::type> : static_query +{ +}; + +#endif // !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_DEDUCED_QUERY_FREE_TRAIT) + +template +struct query_free, + typename enable_if< + can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + + typedef U result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_QUERY_FREE_TRAIT) + +} // namespace traits + +#endif // defined(GENERATING_DOCUMENTATION) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_CONTEXT_AS_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/as_invocable.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/as_invocable.hpp new file mode 100644 index 000000000..d91c700bb --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/as_invocable.hpp @@ -0,0 +1,152 @@ +// +// execution/detail/as_invocable.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_DETAIL_AS_INVOCABLE_HPP +#define ASIO_EXECUTION_DETAIL_AS_INVOCABLE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/atomic_count.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/receiver_invocation_error.hpp" +#include "asio/execution/set_done.hpp" +#include "asio/execution/set_error.hpp" +#include "asio/execution/set_value.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace execution { +namespace detail { + +#if defined(ASIO_HAS_MOVE) + +template +struct as_invocable +{ + Receiver* receiver_; + + explicit as_invocable(Receiver& r) ASIO_NOEXCEPT + : receiver_(asio::detail::addressof(r)) + { + } + + as_invocable(as_invocable&& other) ASIO_NOEXCEPT + : receiver_(other.receiver_) + { + other.receiver_ = 0; + } + + ~as_invocable() + { + if (receiver_) + execution::set_done(ASIO_MOVE_OR_LVALUE(Receiver)(*receiver_)); + } + + void operator()() ASIO_LVALUE_REF_QUAL ASIO_NOEXCEPT + { +#if !defined(ASIO_NO_EXCEPTIONS) + try + { +#endif // !defined(ASIO_NO_EXCEPTIONS) + execution::set_value(ASIO_MOVE_CAST(Receiver)(*receiver_)); + receiver_ = 0; +#if !defined(ASIO_NO_EXCEPTIONS) + } + catch (...) + { +#if defined(ASIO_HAS_STD_EXCEPTION_PTR) + execution::set_error(ASIO_MOVE_CAST(Receiver)(*receiver_), + std::make_exception_ptr(receiver_invocation_error())); + receiver_ = 0; +#else // defined(ASIO_HAS_STD_EXCEPTION_PTR) + std::terminate(); +#endif // defined(ASIO_HAS_STD_EXCEPTION_PTR) + } +#endif // !defined(ASIO_NO_EXCEPTIONS) + } +}; + +#else // defined(ASIO_HAS_MOVE) + +template +struct as_invocable +{ + Receiver* receiver_; + asio::detail::shared_ptr ref_count_; + + explicit as_invocable(Receiver& r, + const asio::detail::shared_ptr< + asio::detail::atomic_count>& c) ASIO_NOEXCEPT + : receiver_(asio::detail::addressof(r)), + ref_count_(c) + { + } + + as_invocable(const as_invocable& other) ASIO_NOEXCEPT + : receiver_(other.receiver_), + ref_count_(other.ref_count_) + { + ++(*ref_count_); + } + + ~as_invocable() + { + if (--(*ref_count_) == 0) + execution::set_done(*receiver_); + } + + void operator()() ASIO_LVALUE_REF_QUAL ASIO_NOEXCEPT + { +#if !defined(ASIO_NO_EXCEPTIONS) + try + { +#endif // !defined(ASIO_NO_EXCEPTIONS) + execution::set_value(*receiver_); + ++(*ref_count_); + } +#if !defined(ASIO_NO_EXCEPTIONS) + catch (...) + { +#if defined(ASIO_HAS_STD_EXCEPTION_PTR) + execution::set_error(*receiver_, + std::make_exception_ptr(receiver_invocation_error())); + ++(*ref_count_); +#else // defined(ASIO_HAS_STD_EXCEPTION_PTR) + std::terminate(); +#endif // defined(ASIO_HAS_STD_EXCEPTION_PTR) + } +#endif // !defined(ASIO_NO_EXCEPTIONS) + } +}; + +#endif // defined(ASIO_HAS_MOVE) + +template +struct is_as_invocable : false_type +{ +}; + +template +struct is_as_invocable > : true_type +{ +}; + +} // namespace detail +} // namespace execution +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_DETAIL_AS_INVOCABLE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/as_operation.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/as_operation.hpp new file mode 100644 index 000000000..fcaf5c345 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/as_operation.hpp @@ -0,0 +1,105 @@ +// +// execution/detail/as_operation.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_DETAIL_AS_OPERATION_HPP +#define ASIO_EXECUTION_DETAIL_AS_OPERATION_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/memory.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/detail/as_invocable.hpp" +#include "asio/execution/execute.hpp" +#include "asio/execution/set_error.hpp" +#include "asio/traits/start_member.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace execution { +namespace detail { + +template +struct as_operation +{ + typename remove_cvref::type ex_; + typename remove_cvref::type receiver_; +#if !defined(ASIO_HAS_MOVE) + asio::detail::shared_ptr ref_count_; +#endif // !defined(ASIO_HAS_MOVE) + + template + explicit as_operation(ASIO_MOVE_ARG(E) e, ASIO_MOVE_ARG(R) r) + : ex_(ASIO_MOVE_CAST(E)(e)), + receiver_(ASIO_MOVE_CAST(R)(r)) +#if !defined(ASIO_HAS_MOVE) + , ref_count_(new asio::detail::atomic_count(1)) +#endif // !defined(ASIO_HAS_MOVE) + { + } + + void start() ASIO_NOEXCEPT + { +#if !defined(ASIO_NO_EXCEPTIONS) + try + { +#endif // !defined(ASIO_NO_EXCEPTIONS) + execution::execute( + ASIO_MOVE_CAST(typename remove_cvref::type)(ex_), + as_invocable::type, + Executor>(receiver_ +#if !defined(ASIO_HAS_MOVE) + , ref_count_ +#endif // !defined(ASIO_HAS_MOVE) + )); +#if !defined(ASIO_NO_EXCEPTIONS) + } + catch (...) + { +#if defined(ASIO_HAS_STD_EXCEPTION_PTR) + execution::set_error( + ASIO_MOVE_OR_LVALUE( + typename remove_cvref::type)( + receiver_), + std::current_exception()); +#else // defined(ASIO_HAS_STD_EXCEPTION_PTR) + std::terminate(); +#endif // defined(ASIO_HAS_STD_EXCEPTION_PTR) + } +#endif // !defined(ASIO_NO_EXCEPTIONS) + } +}; + +} // namespace detail +} // namespace execution +namespace traits { + +#if !defined(ASIO_HAS_DEDUCED_START_MEMBER_TRAIT) + +template +struct start_member< + asio::execution::detail::as_operation > +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef void result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_START_MEMBER_TRAIT) + +} // namespace traits +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_DETAIL_AS_OPERATION_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/as_receiver.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/as_receiver.hpp new file mode 100644 index 000000000..e4d74ed98 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/as_receiver.hpp @@ -0,0 +1,128 @@ +// +// execution/detail/as_receiver.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_DETAIL_AS_RECEIVER_HPP +#define ASIO_EXECUTION_DETAIL_AS_RECEIVER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/traits/set_done_member.hpp" +#include "asio/traits/set_error_member.hpp" +#include "asio/traits/set_value_member.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace execution { +namespace detail { + +template +struct as_receiver +{ + Function f_; + + template + explicit as_receiver(ASIO_MOVE_ARG(F) f, int) + : f_(ASIO_MOVE_CAST(F)(f)) + { + } + +#if defined(ASIO_MSVC) && defined(ASIO_HAS_MOVE) + as_receiver(as_receiver&& other) + : f_(ASIO_MOVE_CAST(Function)(other.f_)) + { + } +#endif // defined(ASIO_MSVC) && defined(ASIO_HAS_MOVE) + + void set_value() + ASIO_NOEXCEPT_IF(noexcept(declval()())) + { + f_(); + } + + template + void set_error(E) ASIO_NOEXCEPT + { + std::terminate(); + } + + void set_done() ASIO_NOEXCEPT + { + } +}; + +template +struct is_as_receiver : false_type +{ +}; + +template +struct is_as_receiver > : true_type +{ +}; + +} // namespace detail +} // namespace execution +namespace traits { + +#if !defined(ASIO_HAS_DEDUCED_SET_VALUE_MEMBER_TRAIT) + +template +struct set_value_member< + asio::execution::detail::as_receiver, void()> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); +#if defined(ASIO_HAS_NOEXCEPT) + ASIO_STATIC_CONSTEXPR(bool, + is_noexcept = noexcept(declval()())); +#else // defined(ASIO_HAS_NOEXCEPT) + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); +#endif // defined(ASIO_HAS_NOEXCEPT) + typedef void result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_SET_VALUE_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_SET_ERROR_MEMBER_TRAIT) + +template +struct set_error_member< + asio::execution::detail::as_receiver, E> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef void result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_SET_ERROR_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_SET_DONE_MEMBER_TRAIT) + +template +struct set_done_member< + asio::execution::detail::as_receiver > +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef void result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_SET_DONE_MEMBER_TRAIT) + +} // namespace traits +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_DETAIL_AS_RECEIVER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/bulk_sender.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/bulk_sender.hpp new file mode 100644 index 000000000..c1f6de4d2 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/bulk_sender.hpp @@ -0,0 +1,261 @@ +// +// execution/detail/bulk_sender.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_DETAIL_BULK_SENDER_HPP +#define ASIO_EXECUTION_DETAIL_BULK_SENDER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/connect.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/set_done.hpp" +#include "asio/execution/set_error.hpp" +#include "asio/traits/connect_member.hpp" +#include "asio/traits/set_done_member.hpp" +#include "asio/traits/set_error_member.hpp" +#include "asio/traits/set_value_member.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace execution { +namespace detail { + +template +struct bulk_receiver +{ + typename remove_cvref::type receiver_; + typename decay::type f_; + typename decay::type n_; + + template + explicit bulk_receiver(ASIO_MOVE_ARG(R) r, + ASIO_MOVE_ARG(F) f, ASIO_MOVE_ARG(N) n) + : receiver_(ASIO_MOVE_CAST(R)(r)), + f_(ASIO_MOVE_CAST(F)(f)), + n_(ASIO_MOVE_CAST(N)(n)) + { + } + + void set_value() + { + for (Index i = 0; i < n_; ++i) + f_(i); + + execution::set_value( + ASIO_MOVE_OR_LVALUE( + typename remove_cvref::type)(receiver_)); + } + + template + void set_error(ASIO_MOVE_ARG(Error) e) ASIO_NOEXCEPT + { + execution::set_error( + ASIO_MOVE_OR_LVALUE( + typename remove_cvref::type)(receiver_), + ASIO_MOVE_CAST(Error)(e)); + } + + void set_done() ASIO_NOEXCEPT + { + execution::set_done( + ASIO_MOVE_OR_LVALUE( + typename remove_cvref::type)(receiver_)); + } +}; + +template +struct bulk_receiver_traits +{ + typedef bulk_receiver< + Receiver, Function, Number, + typename execution::executor_index< + typename remove_cvref::type + >::type + > type; + +#if defined(ASIO_HAS_MOVE) + typedef type arg_type; +#else // defined(ASIO_HAS_MOVE) + typedef const type& arg_type; +#endif // defined(ASIO_HAS_MOVE) +}; + +template +struct bulk_sender : sender_base +{ + typename remove_cvref::type sender_; + typename decay::type f_; + typename decay::type n_; + + template + explicit bulk_sender(ASIO_MOVE_ARG(S) s, + ASIO_MOVE_ARG(F) f, ASIO_MOVE_ARG(N) n) + : sender_(ASIO_MOVE_CAST(S)(s)), + f_(ASIO_MOVE_CAST(F)(f)), + n_(ASIO_MOVE_CAST(N)(n)) + { + } + + template + typename connect_result< + ASIO_MOVE_OR_LVALUE_TYPE(typename remove_cvref::type), + typename bulk_receiver_traits< + Sender, Receiver, Function, Number + >::arg_type + >::type connect(ASIO_MOVE_ARG(Receiver) r, + typename enable_if< + can_connect< + typename remove_cvref::type, + typename bulk_receiver_traits< + Sender, Receiver, Function, Number + >::arg_type + >::value + >::type* = 0) ASIO_RVALUE_REF_QUAL ASIO_NOEXCEPT + { + return execution::connect( + ASIO_MOVE_OR_LVALUE(typename remove_cvref::type)(sender_), + typename bulk_receiver_traits::type( + ASIO_MOVE_CAST(Receiver)(r), + ASIO_MOVE_CAST(typename decay::type)(f_), + ASIO_MOVE_CAST(typename decay::type)(n_))); + } + + template + typename connect_result< + const typename remove_cvref::type&, + typename bulk_receiver_traits< + Sender, Receiver, Function, Number + >::arg_type + >::type connect(ASIO_MOVE_ARG(Receiver) r, + typename enable_if< + can_connect< + const typename remove_cvref::type&, + typename bulk_receiver_traits< + Sender, Receiver, Function, Number + >::arg_type + >::value + >::type* = 0) const ASIO_LVALUE_REF_QUAL ASIO_NOEXCEPT + { + return execution::connect(sender_, + typename bulk_receiver_traits::type( + ASIO_MOVE_CAST(Receiver)(r), f_, n_)); + } +}; + +} // namespace detail +} // namespace execution +namespace traits { + +#if !defined(ASIO_HAS_DEDUCED_SET_VALUE_MEMBER_TRAIT) + +template +struct set_value_member< + execution::detail::bulk_receiver, + void()> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = false); + typedef void result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_SET_VALUE_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_SET_ERROR_MEMBER_TRAIT) + +template +struct set_error_member< + execution::detail::bulk_receiver, + Error> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef void result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_SET_ERROR_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_SET_DONE_MEMBER_TRAIT) + +template +struct set_done_member< + execution::detail::bulk_receiver > +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef void result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_SET_DONE_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_CONNECT_MEMBER_TRAIT) + +template +struct connect_member< + execution::detail::bulk_sender, + Receiver, + typename enable_if< + execution::can_connect< + ASIO_MOVE_OR_LVALUE_TYPE(typename remove_cvref::type), + typename execution::detail::bulk_receiver_traits< + Sender, Receiver, Function, Number + >::arg_type + >::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = false); + typedef typename execution::connect_result< + ASIO_MOVE_OR_LVALUE_TYPE(typename remove_cvref::type), + typename execution::detail::bulk_receiver_traits< + Sender, Receiver, Function, Number + >::arg_type + >::type result_type; +}; + +template +struct connect_member< + const execution::detail::bulk_sender, + Receiver, + typename enable_if< + execution::can_connect< + const typename remove_cvref::type&, + typename execution::detail::bulk_receiver_traits< + Sender, Receiver, Function, Number + >::arg_type + >::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = false); + typedef typename execution::connect_result< + const typename remove_cvref::type&, + typename execution::detail::bulk_receiver_traits< + Sender, Receiver, Function, Number + >::arg_type + >::type result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_CONNECT_MEMBER_TRAIT) + +} // namespace traits +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_DETAIL_BULK_SENDER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/submit_receiver.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/submit_receiver.hpp new file mode 100644 index 000000000..5f78356ab --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/submit_receiver.hpp @@ -0,0 +1,233 @@ +// +// execution/detail/submit_receiver.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_DETAIL_SUBMIT_RECEIVER_HPP +#define ASIO_EXECUTION_DETAIL_SUBMIT_RECEIVER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/detail/variadic_templates.hpp" +#include "asio/execution/connect.hpp" +#include "asio/execution/receiver.hpp" +#include "asio/execution/set_done.hpp" +#include "asio/execution/set_error.hpp" +#include "asio/execution/set_value.hpp" +#include "asio/traits/set_done_member.hpp" +#include "asio/traits/set_error_member.hpp" +#include "asio/traits/set_value_member.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace execution { +namespace detail { + +template +struct submit_receiver; + +template +struct submit_receiver_wrapper +{ + submit_receiver* p_; + + explicit submit_receiver_wrapper(submit_receiver* p) + : p_(p) + { + } + +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) + + template + typename enable_if::value>::type + set_value(ASIO_MOVE_ARG(Args)... args) ASIO_RVALUE_REF_QUAL + ASIO_NOEXCEPT_IF((is_nothrow_receiver_of::value)) + { + execution::set_value( + ASIO_MOVE_OR_LVALUE( + typename remove_cvref::type)(p_->r_), + ASIO_MOVE_CAST(Args)(args)...); + delete p_; + } + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + + void set_value() ASIO_RVALUE_REF_QUAL + ASIO_NOEXCEPT_IF((is_nothrow_receiver_of::value)) + { + execution::set_value( + ASIO_MOVE_OR_LVALUE( + typename remove_cvref::type)(p_->r_)); + delete p_; + } + +#define ASIO_PRIVATE_SUBMIT_RECEIVER_SET_VALUE_DEF(n) \ + template \ + typename enable_if::value>::type \ + set_value(ASIO_VARIADIC_MOVE_PARAMS(n)) ASIO_RVALUE_REF_QUAL \ + ASIO_NOEXCEPT_IF((is_nothrow_receiver_of< \ + Receiver, ASIO_VARIADIC_TARGS(n)>::value)) \ + { \ + execution::set_value( \ + ASIO_MOVE_OR_LVALUE( \ + typename remove_cvref::type)(p_->r_), \ + ASIO_VARIADIC_MOVE_ARGS(n)); \ + delete p_; \ + } \ + /**/ +ASIO_VARIADIC_GENERATE(ASIO_PRIVATE_SUBMIT_RECEIVER_SET_VALUE_DEF) +#undef ASIO_PRIVATE_SUBMIT_RECEIVER_SET_VALUE_DEF + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) + + template + void set_error(ASIO_MOVE_ARG(E) e) + ASIO_RVALUE_REF_QUAL ASIO_NOEXCEPT + { + execution::set_error( + ASIO_MOVE_OR_LVALUE( + typename remove_cvref::type)(p_->r_), + ASIO_MOVE_CAST(E)(e)); + delete p_; + } + + void set_done() ASIO_RVALUE_REF_QUAL ASIO_NOEXCEPT + { + execution::set_done( + ASIO_MOVE_OR_LVALUE( + typename remove_cvref::type)(p_->r_)); + delete p_; + } +}; + +template +struct submit_receiver +{ + typename remove_cvref::type r_; +#if defined(ASIO_HAS_MOVE) + typename connect_result >::type state_; +#else // defined(ASIO_HAS_MOVE) + typename connect_result& >::type state_; +#endif // defined(ASIO_HAS_MOVE) + +#if defined(ASIO_HAS_MOVE) + template + explicit submit_receiver(ASIO_MOVE_ARG(S) s, ASIO_MOVE_ARG(R) r) + : r_(ASIO_MOVE_CAST(R)(r)), + state_(execution::connect(ASIO_MOVE_CAST(S)(s), + submit_receiver_wrapper(this))) + { + } +#else // defined(ASIO_HAS_MOVE) + explicit submit_receiver(Sender s, Receiver r) + : r_(r), + state_(execution::connect(s, + submit_receiver_wrapper(this))) + { + } +#endif // defined(ASIO_HAS_MOVE) +}; + +} // namespace detail +} // namespace execution +namespace traits { + +#if !defined(ASIO_HAS_DEDUCED_SET_VALUE_MEMBER_TRAIT) + +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template +struct set_value_member< + asio::execution::detail::submit_receiver_wrapper< + Sender, Receiver>, + void(Args...)> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (asio::execution::is_nothrow_receiver_of::value)); + typedef void result_type; +}; + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +template +struct set_value_member< + asio::execution::detail::submit_receiver_wrapper< + Sender, Receiver>, + void()> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + asio::execution::is_nothrow_receiver_of::value); + typedef void result_type; +}; + +#define ASIO_PRIVATE_SUBMIT_RECEIVER_TRAIT_DEF(n) \ + template \ + struct set_value_member< \ + asio::execution::detail::submit_receiver_wrapper< \ + Sender, Receiver>, \ + void(ASIO_VARIADIC_TARGS(n))> \ + { \ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); \ + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = \ + (asio::execution::is_nothrow_receiver_of::value)); \ + typedef void result_type; \ + }; \ + /**/ +ASIO_VARIADIC_GENERATE(ASIO_PRIVATE_SUBMIT_RECEIVER_TRAIT_DEF) +#undef ASIO_PRIVATE_SUBMIT_RECEIVER_TRAIT_DEF + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) + +#endif // !defined(ASIO_HAS_DEDUCED_SET_VALUE_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_SET_ERROR_MEMBER_TRAIT) + +template +struct set_error_member< + asio::execution::detail::submit_receiver_wrapper< + Sender, Receiver>, E> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef void result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_SET_ERROR_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_SET_DONE_MEMBER_TRAIT) + +template +struct set_done_member< + asio::execution::detail::submit_receiver_wrapper< + Sender, Receiver> > +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef void result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_SET_DONE_MEMBER_TRAIT) + +} // namespace traits +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_DETAIL_SUBMIT_RECEIVER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/void_receiver.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/void_receiver.hpp new file mode 100644 index 000000000..87d45b8b1 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/detail/void_receiver.hpp @@ -0,0 +1,90 @@ +// +// execution/detail/void_receiver.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_DETAIL_VOID_RECEIVER_HPP +#define ASIO_EXECUTION_DETAIL_VOID_RECEIVER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/traits/set_done_member.hpp" +#include "asio/traits/set_error_member.hpp" +#include "asio/traits/set_value_member.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace execution { +namespace detail { + +struct void_receiver +{ + void set_value() ASIO_NOEXCEPT + { + } + + template + void set_error(ASIO_MOVE_ARG(E)) ASIO_NOEXCEPT + { + } + + void set_done() ASIO_NOEXCEPT + { + } +}; + +} // namespace detail +} // namespace execution +namespace traits { + +#if !defined(ASIO_HAS_DEDUCED_SET_VALUE_MEMBER_TRAIT) + +template <> +struct set_value_member +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef void result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_SET_VALUE_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_SET_ERROR_MEMBER_TRAIT) + +template +struct set_error_member +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef void result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_SET_ERROR_MEMBER_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_SET_DONE_MEMBER_TRAIT) + +template <> +struct set_done_member +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + typedef void result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_SET_DONE_MEMBER_TRAIT) + +} // namespace traits +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_DETAIL_VOID_RECEIVER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/execute.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/execute.hpp new file mode 100644 index 000000000..277cd18a0 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/execute.hpp @@ -0,0 +1,264 @@ +// +// execution/execute.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_EXECUTE_HPP +#define ASIO_EXECUTION_EXECUTE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/detail/as_invocable.hpp" +#include "asio/execution/detail/as_receiver.hpp" +#include "asio/traits/execute_member.hpp" +#include "asio/traits/execute_free.hpp" + +#include "asio/detail/push_options.hpp" + +#if defined(GENERATING_DOCUMENTATION) + +namespace asio { +namespace execution { + +/// A customisation point that executes a function on an executor. +/** + * The name execution::execute denotes a customisation point object. + * + * For some subexpressions e and f, let E be a type + * such that decltype((e)) is E and let F be a type + * such that decltype((f)) is F. The expression + * execution::execute(e, f) is ill-formed if F does not model + * invocable, or if E does not model either executor + * or sender. Otherwise, it is expression-equivalent to: + * + * @li e.execute(f), if that expression is valid. If the function + * selected does not execute the function object f on the executor + * e, the program is ill-formed with no diagnostic required. + * + * @li Otherwise, execute(e, f), if that expression is valid, with + * overload resolution performed in a context that includes the declaration + * void execute(); and that does not include a declaration of + * execution::execute. If the function selected by overload + * resolution does not execute the function object f on the executor + * e, the program is ill-formed with no diagnostic required. + */ +inline constexpr unspecified execute = unspecified; + +/// A type trait that determines whether a @c execute expression is well-formed. +/** + * Class template @c can_execute is a trait that is derived from + * @c true_type if the expression execution::execute(std::declval(), + * std::declval()) is well formed; otherwise @c false_type. + */ +template +struct can_execute : + integral_constant +{ +}; + +} // namespace execution +} // namespace asio + +#else // defined(GENERATING_DOCUMENTATION) + +namespace asio { +namespace execution { + +template +struct is_sender_to; + +namespace detail { + +template +void submit_helper(ASIO_MOVE_ARG(S) s, ASIO_MOVE_ARG(R) r); + +} // namespace detail +} // namespace execution +} // namespace asio +namespace asio_execution_execute_fn { + +using asio::conditional; +using asio::decay; +using asio::declval; +using asio::enable_if; +using asio::execution::detail::as_receiver; +using asio::execution::detail::is_as_invocable; +using asio::execution::is_sender_to; +using asio::false_type; +using asio::result_of; +using asio::traits::execute_free; +using asio::traits::execute_member; +using asio::true_type; + +void execute(); + +enum overload_type +{ + call_member, + call_free, + adapter, + ill_formed +}; + +template +struct call_traits +{ + ASIO_STATIC_CONSTEXPR(overload_type, overload = ill_formed); +}; + +template +struct call_traits::is_valid + ) + >::type> : + execute_member +{ + ASIO_STATIC_CONSTEXPR(overload_type, overload = call_member); +}; + +template +struct call_traits::is_valid + && + execute_free::is_valid + ) + >::type> : + execute_free +{ + ASIO_STATIC_CONSTEXPR(overload_type, overload = call_free); +}; + +template +struct call_traits::is_valid + && + !execute_free::is_valid + && + conditional::type&()>::type + >::type::value + && + conditional< + !is_as_invocable< + typename decay::type + >::value, + is_sender_to< + T, + as_receiver::type, T> + >, + false_type + >::type::value + ) + >::type> +{ + ASIO_STATIC_CONSTEXPR(overload_type, overload = adapter); + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = false); + typedef void result_type; +}; + +struct impl +{ + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_member, + typename call_traits::result_type + >::type + operator()( + ASIO_MOVE_ARG(T) t, + ASIO_MOVE_ARG(F) f) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return ASIO_MOVE_CAST(T)(t).execute(ASIO_MOVE_CAST(F)(f)); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_free, + typename call_traits::result_type + >::type + operator()( + ASIO_MOVE_ARG(T) t, + ASIO_MOVE_ARG(F) f) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return execute(ASIO_MOVE_CAST(T)(t), ASIO_MOVE_CAST(F)(f)); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == adapter, + typename call_traits::result_type + >::type + operator()( + ASIO_MOVE_ARG(T) t, + ASIO_MOVE_ARG(F) f) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return asio::execution::detail::submit_helper( + ASIO_MOVE_CAST(T)(t), + as_receiver::type, T>( + ASIO_MOVE_CAST(F)(f), 0)); + } +}; + +template +struct static_instance +{ + static const T instance; +}; + +template +const T static_instance::instance = {}; + +} // namespace asio_execution_execute_fn +namespace asio { +namespace execution { +namespace { + +static ASIO_CONSTEXPR const asio_execution_execute_fn::impl& + execute = asio_execution_execute_fn::static_instance<>::instance; + +} // namespace + +template +struct can_execute : + integral_constant::overload != + asio_execution_execute_fn::ill_formed> +{ +}; + +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +constexpr bool can_execute_v = can_execute::value; + +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + +} // namespace execution +} // namespace asio + +#endif // defined(GENERATING_DOCUMENTATION) + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_EXECUTE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/executor.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/executor.hpp new file mode 100644 index 000000000..558f6c4fd --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/executor.hpp @@ -0,0 +1,238 @@ +// +// execution/executor.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_EXECUTOR_HPP +#define ASIO_EXECUTION_EXECUTOR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/execute.hpp" +#include "asio/execution/invocable_archetype.hpp" +#include "asio/traits/equality_comparable.hpp" + +#if defined(ASIO_HAS_DEDUCED_EXECUTE_FREE_TRAIT) \ + && defined(ASIO_HAS_DEDUCED_EXECUTE_MEMBER_TRAIT) \ + && defined(ASIO_HAS_DEDUCED_EQUALITY_COMPARABLE_TRAIT) +# define ASIO_HAS_DEDUCED_EXECUTION_IS_EXECUTOR_TRAIT 1 +#endif // defined(ASIO_HAS_DEDUCED_EXECUTE_FREE_TRAIT) + // && defined(ASIO_HAS_DEDUCED_EXECUTE_MEMBER_TRAIT) + // && defined(ASIO_HAS_DEDUCED_EQUALITY_COMPARABLE_TRAIT) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace execution { +namespace detail { + +template +struct is_executor_of_impl_base : + integral_constant::type&()>::type + >::type::value + && is_constructible::type, F>::value + && is_move_constructible::type>::value +#if defined(ASIO_HAS_NOEXCEPT) + && is_nothrow_copy_constructible::value + && is_nothrow_destructible::value +#else // defined(ASIO_HAS_NOEXCEPT) + && is_copy_constructible::value + && is_destructible::value +#endif // defined(ASIO_HAS_NOEXCEPT) + && traits::equality_comparable::is_valid + && traits::equality_comparable::is_noexcept + > +{ +}; + +template +struct is_executor_of_impl : + conditional< + can_execute::value, + is_executor_of_impl_base, + false_type + >::type +{ +}; + +template +struct executor_shape +{ + typedef std::size_t type; +}; + +template +struct executor_shape::type> +{ + typedef typename T::shape_type type; +}; + +template +struct executor_index +{ + typedef Default type; +}; + +template +struct executor_index::type> +{ + typedef typename T::index_type type; +}; + +} // namespace detail + +/// The is_executor trait detects whether a type T satisfies the +/// execution::executor concept. +/** + * Class template @c is_executor is a UnaryTypeTrait that is derived from @c + * true_type if the type @c T meets the concept definition for an executor, + * otherwise @c false_type. + */ +template +struct is_executor : +#if defined(GENERATING_DOCUMENTATION) + integral_constant +#else // defined(GENERATING_DOCUMENTATION) + detail::is_executor_of_impl +#endif // defined(GENERATING_DOCUMENTATION) +{ +}; + +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +ASIO_CONSTEXPR const bool is_executor_v = is_executor::value; + +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + +#if defined(ASIO_HAS_CONCEPTS) + +template +ASIO_CONCEPT executor = is_executor::value; + +#define ASIO_EXECUTION_EXECUTOR ::asio::execution::executor + +#else // defined(ASIO_HAS_CONCEPTS) + +#define ASIO_EXECUTION_EXECUTOR typename + +#endif // defined(ASIO_HAS_CONCEPTS) + +/// The is_executor_of trait detects whether a type T satisfies the +/// execution::executor_of concept for some set of value arguments. +/** + * Class template @c is_executor_of is a type trait that is derived from @c + * true_type if the type @c T meets the concept definition for an executor + * that is invocable with a function object of type @c F, otherwise @c + * false_type. + */ +template +struct is_executor_of : +#if defined(GENERATING_DOCUMENTATION) + integral_constant +#else // defined(GENERATING_DOCUMENTATION) + integral_constant::value && detail::is_executor_of_impl::value + > +#endif // defined(GENERATING_DOCUMENTATION) +{ +}; + +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +ASIO_CONSTEXPR const bool is_executor_of_v = + is_executor_of::value; + +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + +#if defined(ASIO_HAS_CONCEPTS) + +template +ASIO_CONCEPT executor_of = is_executor_of::value; + +#define ASIO_EXECUTION_EXECUTOR_OF(f) \ + ::asio::execution::executor_of + +#else // defined(ASIO_HAS_CONCEPTS) + +#define ASIO_EXECUTION_EXECUTOR_OF typename + +#endif // defined(ASIO_HAS_CONCEPTS) + +/// The executor_shape trait detects the type used by an executor to represent +/// the shape of a bulk operation. +/** + * Class template @c executor_shape is a type trait with a nested type alias + * @c type whose type is @c T::shape_type if @c T::shape_type is valid, + * otherwise @c std::size_t. + */ +template +struct executor_shape +#if !defined(GENERATING_DOCUMENTATION) + : detail::executor_shape +#endif // !defined(GENERATING_DOCUMENTATION) +{ +#if defined(GENERATING_DOCUMENTATION) + /// @c T::shape_type if @c T::shape_type is valid, otherwise @c std::size_t. + typedef automatically_determined type; +#endif // defined(GENERATING_DOCUMENTATION) +}; + +#if defined(ASIO_HAS_ALIAS_TEMPLATES) + +template +using executor_shape_t = typename executor_shape::type; + +#endif // defined(ASIO_HAS_ALIAS_TEMPLATES) + +/// The executor_index trait detects the type used by an executor to represent +/// an index within a bulk operation. +/** + * Class template @c executor_index is a type trait with a nested type alias + * @c type whose type is @c T::index_type if @c T::index_type is valid, + * otherwise @c executor_shape_t. + */ +template +struct executor_index +#if !defined(GENERATING_DOCUMENTATION) + : detail::executor_index::type> +#endif // !defined(GENERATING_DOCUMENTATION) +{ +#if defined(GENERATING_DOCUMENTATION) + /// @c T::index_type if @c T::index_type is valid, otherwise + /// @c executor_shape_t. + typedef automatically_determined type; +#endif // defined(GENERATING_DOCUMENTATION) +}; + +#if defined(ASIO_HAS_ALIAS_TEMPLATES) + +template +using executor_index_t = typename executor_index::type; + +#endif // defined(ASIO_HAS_ALIAS_TEMPLATES) + +} // namespace execution +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_EXECUTOR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/impl/bad_executor.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/impl/bad_executor.ipp new file mode 100644 index 000000000..c36012b52 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/impl/bad_executor.ipp @@ -0,0 +1,40 @@ +// +// exection/impl/bad_executor.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_IMPL_BAD_EXECUTOR_IPP +#define ASIO_EXECUTION_IMPL_BAD_EXECUTOR_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/execution/bad_executor.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace execution { + +bad_executor::bad_executor() ASIO_NOEXCEPT +{ +} + +const char* bad_executor::what() const ASIO_NOEXCEPT_OR_NOTHROW +{ + return "bad executor"; +} + +} // namespace execution +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_IMPL_BAD_EXECUTOR_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/impl/receiver_invocation_error.ipp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/impl/receiver_invocation_error.ipp new file mode 100644 index 000000000..1b0200711 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/impl/receiver_invocation_error.ipp @@ -0,0 +1,36 @@ +// +// exection/impl/receiver_invocation_error.ipp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_IMPL_RECEIVER_INVOCATION_ERROR_IPP +#define ASIO_EXECUTION_IMPL_RECEIVER_INVOCATION_ERROR_IPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/execution/receiver_invocation_error.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace execution { + +receiver_invocation_error::receiver_invocation_error() + : std::runtime_error("receiver invocation error") +{ +} + +} // namespace execution +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_IMPL_RECEIVER_INVOCATION_ERROR_IPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/invocable_archetype.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/invocable_archetype.hpp new file mode 100644 index 000000000..9ccbb8cea --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/invocable_archetype.hpp @@ -0,0 +1,71 @@ +// +// execution/invocable_archetype.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_INVOCABLE_ARCHETYPE_HPP +#define ASIO_EXECUTION_INVOCABLE_ARCHETYPE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/detail/variadic_templates.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace execution { + +/// An archetypal function object used for determining adherence to the +/// execution::executor concept. +struct invocable_archetype +{ +#if !defined(GENERATING_DOCUMENTATION) + // Necessary for compatibility with a C++03 implementation of result_of. + typedef void result_type; +#endif // !defined(GENERATING_DOCUMENTATION) + +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) \ + || defined(GENERATING_DOCUMENTATION) + + /// Function call operator. + template + void operator()(ASIO_MOVE_ARG(Args)...) + { + } + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + // || defined(GENERATING_DOCUMENTATION) + + void operator()() + { + } + +#define ASIO_PRIVATE_INVOCABLE_ARCHETYPE_CALL_DEF(n) \ + template \ + void operator()(ASIO_VARIADIC_UNNAMED_MOVE_PARAMS(n)) \ + { \ + } \ + /**/ + ASIO_VARIADIC_GENERATE(ASIO_PRIVATE_INVOCABLE_ARCHETYPE_CALL_DEF) +#undef ASIO_PRIVATE_INVOCABLE_ARCHETYPE_CALL_DEF + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) + // || defined(GENERATING_DOCUMENTATION) +}; + +} // namespace execution +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_INVOCABLE_ARCHETYPE_HPP + diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/mapping.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/mapping.hpp new file mode 100644 index 000000000..acfee66f6 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/mapping.hpp @@ -0,0 +1,917 @@ +// +// execution/mapping.hpp +// ~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_MAPPING_HPP +#define ASIO_EXECUTION_MAPPING_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/scheduler.hpp" +#include "asio/execution/sender.hpp" +#include "asio/is_applicable_property.hpp" +#include "asio/query.hpp" +#include "asio/traits/query_free.hpp" +#include "asio/traits/query_member.hpp" +#include "asio/traits/query_static_constexpr_member.hpp" +#include "asio/traits/static_query.hpp" +#include "asio/traits/static_require.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if defined(GENERATING_DOCUMENTATION) + +namespace execution { + +/// A property to describe what guarantees an executor makes about the mapping +/// of execution agents on to threads of execution. +struct mapping_t +{ + /// The mapping_t property applies to executors, senders, and schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The top-level mapping_t property cannot be required. + static constexpr bool is_requirable = false; + + /// The top-level mapping_t property cannot be preferred. + static constexpr bool is_preferable = false; + + /// The type returned by queries against an @c any_executor. + typedef mapping_t polymorphic_query_result_type; + + /// A sub-property that indicates that execution agents are mapped on to + /// threads of execution. + struct thread_t + { + /// The mapping_t::thread_t property applies to executors, senders, and + /// schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The mapping_t::thread_t property can be required. + static constexpr bool is_requirable = true; + + /// The mapping_t::thread_t property can be preferred. + static constexpr bool is_preferable = true; + + /// The type returned by queries against an @c any_executor. + typedef mapping_t polymorphic_query_result_type; + + /// Default constructor. + constexpr thread_t(); + + /// Get the value associated with a property object. + /** + * @returns thread_t(); + */ + static constexpr mapping_t value(); + }; + + /// A sub-property that indicates that execution agents are mapped on to + /// new threads of execution. + struct new_thread_t + { + /// The mapping_t::new_thread_t property applies to executors, senders, and + /// schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The mapping_t::new_thread_t property can be required. + static constexpr bool is_requirable = true; + + /// The mapping_t::new_thread_t property can be preferred. + static constexpr bool is_preferable = true; + + /// The type returned by queries against an @c any_executor. + typedef mapping_t polymorphic_query_result_type; + + /// Default constructor. + constexpr new_thread_t(); + + /// Get the value associated with a property object. + /** + * @returns new_thread_t(); + */ + static constexpr mapping_t value(); + }; + + /// A sub-property that indicates that the mapping of execution agents is + /// implementation-defined. + struct other_t + { + /// The mapping_t::other_t property applies to executors, senders, and + /// schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The mapping_t::other_t property can be required. + static constexpr bool is_requirable = true; + + /// The mapping_t::other_t property can be preferred. + static constexpr bool is_preferable = true; + + /// The type returned by queries against an @c any_executor. + typedef mapping_t polymorphic_query_result_type; + + /// Default constructor. + constexpr other_t(); + + /// Get the value associated with a property object. + /** + * @returns other_t(); + */ + static constexpr mapping_t value(); + }; + + /// A special value used for accessing the mapping_t::thread_t property. + static constexpr thread_t thread; + + /// A special value used for accessing the mapping_t::new_thread_t property. + static constexpr new_thread_t new_thread; + + /// A special value used for accessing the mapping_t::other_t property. + static constexpr other_t other; + + /// Default constructor. + constexpr mapping_t(); + + /// Construct from a sub-property value. + constexpr mapping_t(thread_t); + + /// Construct from a sub-property value. + constexpr mapping_t(new_thread_t); + + /// Construct from a sub-property value. + constexpr mapping_t(other_t); + + /// Compare property values for equality. + friend constexpr bool operator==( + const mapping_t& a, const mapping_t& b) noexcept; + + /// Compare property values for inequality. + friend constexpr bool operator!=( + const mapping_t& a, const mapping_t& b) noexcept; +}; + +/// A special value used for accessing the mapping_t property. +constexpr mapping_t mapping; + +} // namespace execution + +#else // defined(GENERATING_DOCUMENTATION) + +namespace execution { +namespace detail { +namespace mapping { + +template struct thread_t; +template struct new_thread_t; +template struct other_t; + +} // namespace mapping + +template +struct mapping_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = false); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = false); + typedef mapping_t polymorphic_query_result_type; + + typedef detail::mapping::thread_t thread_t; + typedef detail::mapping::new_thread_t new_thread_t; + typedef detail::mapping::other_t other_t; + + ASIO_CONSTEXPR mapping_t() + : value_(-1) + { + } + + ASIO_CONSTEXPR mapping_t(thread_t) + : value_(0) + { + } + + ASIO_CONSTEXPR mapping_t(new_thread_t) + : value_(1) + { + } + + ASIO_CONSTEXPR mapping_t(other_t) + : value_(2) + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template + static ASIO_CONSTEXPR + typename traits::static_query::result_type + static_query( + typename enable_if< + !traits::query_static_constexpr_member::is_valid + && !traits::query_member::is_valid + && traits::static_query::is_valid + >::type* = 0) ASIO_NOEXCEPT + { + return traits::static_query::value(); + } + + template + static ASIO_CONSTEXPR + typename traits::static_query::result_type + static_query( + typename enable_if< + !traits::query_static_constexpr_member::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type* = 0) ASIO_NOEXCEPT + { + return traits::static_query::value(); + } + + template + static ASIO_CONSTEXPR + typename traits::static_query::result_type + static_query( + typename enable_if< + !traits::query_static_constexpr_member::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type* = 0) ASIO_NOEXCEPT + { + return traits::static_query::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = mapping_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + friend ASIO_CONSTEXPR bool operator==( + const mapping_t& a, const mapping_t& b) + { + return a.value_ == b.value_; + } + + friend ASIO_CONSTEXPR bool operator!=( + const mapping_t& a, const mapping_t& b) + { + return a.value_ != b.value_; + } + + struct convertible_from_mapping_t + { + ASIO_CONSTEXPR convertible_from_mapping_t(mapping_t) {} + }; + + template + friend ASIO_CONSTEXPR mapping_t query( + const Executor& ex, convertible_from_mapping_t, + typename enable_if< + can_query::value + >::type* = 0) +#if !defined(__clang__) // Clang crashes if noexcept is used here. +#if defined(ASIO_MSVC) // Visual C++ wants the type to be qualified. + ASIO_NOEXCEPT_IF(( + is_nothrow_query::thread_t>::value)) +#else // defined(ASIO_MSVC) + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#endif // defined(ASIO_MSVC) +#endif // !defined(__clang__) + { + return asio::query(ex, thread_t()); + } + + template + friend ASIO_CONSTEXPR mapping_t query( + const Executor& ex, convertible_from_mapping_t, + typename enable_if< + !can_query::value + && can_query::value + >::type* = 0) +#if !defined(__clang__) // Clang crashes if noexcept is used here. +#if defined(ASIO_MSVC) // Visual C++ wants the type to be qualified. + ASIO_NOEXCEPT_IF(( + is_nothrow_query::new_thread_t>::value)) +#else // defined(ASIO_MSVC) + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#endif // defined(ASIO_MSVC) +#endif // !defined(__clang__) + { + return asio::query(ex, new_thread_t()); + } + + template + friend ASIO_CONSTEXPR mapping_t query( + const Executor& ex, convertible_from_mapping_t, + typename enable_if< + !can_query::value + && !can_query::value + && can_query::value + >::type* = 0) +#if !defined(__clang__) // Clang crashes if noexcept is used here. +#if defined(ASIO_MSVC) // Visual C++ wants the type to be qualified. + ASIO_NOEXCEPT_IF(( + is_nothrow_query::other_t>::value)) +#else // defined(ASIO_MSVC) + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#endif // defined(ASIO_MSVC) +#endif // !defined(__clang__) + { + return asio::query(ex, other_t()); + } + + ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(thread_t, thread); + ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(new_thread_t, new_thread); + ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(other_t, other); + +#if !defined(ASIO_HAS_CONSTEXPR) + static const mapping_t instance; +#endif // !defined(ASIO_HAS_CONSTEXPR) + +private: + int value_; +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T mapping_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_CONSTEXPR) +template +const mapping_t mapping_t::instance; +#endif + +template +const typename mapping_t::thread_t mapping_t::thread; + +template +const typename mapping_t::new_thread_t mapping_t::new_thread; + +template +const typename mapping_t::other_t mapping_t::other; + +namespace mapping { + +template +struct thread_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = true); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = true); + typedef mapping_t polymorphic_query_result_type; + + ASIO_CONSTEXPR thread_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template + static ASIO_CONSTEXPR thread_t static_query( + typename enable_if< + !traits::query_static_constexpr_member::is_valid + && !traits::query_member::is_valid + && !traits::query_free::is_valid + && !can_query >::value + && !can_query >::value + >::type* = 0) ASIO_NOEXCEPT + { + return thread_t(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = thread_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + static ASIO_CONSTEXPR mapping_t value() + { + return thread_t(); + } + + friend ASIO_CONSTEXPR bool operator==( + const thread_t&, const thread_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator!=( + const thread_t&, const thread_t&) + { + return false; + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T thread_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct new_thread_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = true); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = true); + typedef mapping_t polymorphic_query_result_type; + + ASIO_CONSTEXPR new_thread_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = new_thread_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + static ASIO_CONSTEXPR mapping_t value() + { + return new_thread_t(); + } + + friend ASIO_CONSTEXPR bool operator==( + const new_thread_t&, const new_thread_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator!=( + const new_thread_t&, const new_thread_t&) + { + return false; + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T new_thread_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct other_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = true); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = true); + typedef mapping_t polymorphic_query_result_type; + + ASIO_CONSTEXPR other_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = other_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + static ASIO_CONSTEXPR mapping_t value() + { + return other_t(); + } + + friend ASIO_CONSTEXPR bool operator==( + const other_t&, const other_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator!=( + const other_t&, const other_t&) + { + return false; + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T other_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +} // namespace mapping +} // namespace detail + +typedef detail::mapping_t<> mapping_t; + +#if defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +constexpr mapping_t mapping; +#else // defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +namespace { static const mapping_t& mapping = mapping_t::instance; } +#endif + +} // namespace execution + +#if !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +#endif // !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +namespace traits { + +#if !defined(ASIO_HAS_DEDUCED_QUERY_FREE_TRAIT) + +template +struct query_free_default::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + + typedef execution::mapping_t result_type; +}; + +template +struct query_free_default::value + && can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + + typedef execution::mapping_t result_type; +}; + +template +struct query_free_default::value + && !can_query::value + && can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + + typedef execution::mapping_t result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_QUERY_FREE_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && traits::static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::static_query::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::static_query::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::static_query::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::static_query::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::static_query::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::static_query::value(); + } +}; + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && !traits::query_free::is_valid + && !can_query::value + && !can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef execution::mapping_t::thread_t result_type; + + static ASIO_CONSTEXPR result_type value() + { + return result_type(); + } +}; + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +#endif // !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_DEDUCED_STATIC_REQUIRE_TRAIT) + +template +struct static_require::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = + (is_same::result_type, + execution::mapping_t::thread_t>::value)); +}; + +template +struct static_require::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = + (is_same::result_type, + execution::mapping_t::new_thread_t>::value)); +}; + +template +struct static_require::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = + (is_same::result_type, + execution::mapping_t::other_t>::value)); +}; + +#endif // !defined(ASIO_HAS_DEDUCED_STATIC_REQUIRE_TRAIT) + +} // namespace traits + +#endif // defined(GENERATING_DOCUMENTATION) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_MAPPING_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/occupancy.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/occupancy.hpp new file mode 100644 index 000000000..00bf867bb --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/occupancy.hpp @@ -0,0 +1,178 @@ +// +// execution/occupancy.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_OCCUPANCY_HPP +#define ASIO_EXECUTION_OCCUPANCY_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/scheduler.hpp" +#include "asio/execution/sender.hpp" +#include "asio/is_applicable_property.hpp" +#include "asio/traits/query_static_constexpr_member.hpp" +#include "asio/traits/static_query.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if defined(GENERATING_DOCUMENTATION) + +namespace execution { + +/// A property that gives an estimate of the number of execution agents that +/// should occupy the associated execution context. +struct occupancy_t +{ + /// The occupancy_t property applies to executors, senders, and schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The occupancy_t property cannot be required. + static constexpr bool is_requirable = false; + + /// The occupancy_t property cannot be preferred. + static constexpr bool is_preferable = false; + + /// The type returned by queries against an @c any_executor. + typedef std::size_t polymorphic_query_result_type; +}; + +/// A special value used for accessing the occupancy_t property. +constexpr occupancy_t occupancy; + +} // namespace execution + +#else // defined(GENERATING_DOCUMENTATION) + +namespace execution { +namespace detail { + +template +struct occupancy_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = false); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = false); + typedef std::size_t polymorphic_query_result_type; + + ASIO_CONSTEXPR occupancy_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = occupancy_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_CONSTEXPR) + static const occupancy_t instance; +#endif // !defined(ASIO_HAS_CONSTEXPR) +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T occupancy_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_CONSTEXPR) +template +const occupancy_t occupancy_t::instance; +#endif + +} // namespace detail + +typedef detail::occupancy_t<> occupancy_t; + +#if defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +constexpr occupancy_t occupancy; +#else // defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +namespace { static const occupancy_t& occupancy = occupancy_t::instance; } +#endif + +} // namespace execution + +#if !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +#endif // !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +namespace traits { + +#if !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +#endif // !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +} // namespace traits + +#endif // defined(GENERATING_DOCUMENTATION) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_OCCUPANCY_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/operation_state.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/operation_state.hpp new file mode 100644 index 000000000..7eeb532a4 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/operation_state.hpp @@ -0,0 +1,94 @@ +// +// execution/operation_state.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_OPERATION_STATE_HPP +#define ASIO_EXECUTION_OPERATION_STATE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/start.hpp" + +#if defined(ASIO_HAS_DEDUCED_START_FREE_TRAIT) \ + && defined(ASIO_HAS_DEDUCED_START_MEMBER_TRAIT) +# define ASIO_HAS_DEDUCED_EXECUTION_IS_OPERATION_STATE_TRAIT 1 +#endif // defined(ASIO_HAS_DEDUCED_START_FREE_TRAIT) + // && defined(ASIO_HAS_DEDUCED_START_MEMBER_TRAIT) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace execution { +namespace detail { + +template +struct is_operation_state_base : + integral_constant::value + && is_object::value + > +{ +}; + +} // namespace detail + +/// The is_operation_state trait detects whether a type T satisfies the +/// execution::operation_state concept. +/** + * Class template @c is_operation_state is a type trait that is derived from + * @c true_type if the type @c T meets the concept definition for an + * @c operation_state, otherwise @c false_type. + */ +template +struct is_operation_state : +#if defined(GENERATING_DOCUMENTATION) + integral_constant +#else // defined(GENERATING_DOCUMENTATION) + conditional< + can_start::type>::value + && is_nothrow_start::type>::value, + detail::is_operation_state_base, + false_type + >::type +#endif // defined(GENERATING_DOCUMENTATION) +{ +}; + +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +ASIO_CONSTEXPR const bool is_operation_state_v = + is_operation_state::value; + +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + +#if defined(ASIO_HAS_CONCEPTS) + +template +ASIO_CONCEPT operation_state = is_operation_state::value; + +#define ASIO_EXECUTION_OPERATION_STATE \ + ::asio::execution::operation_state + +#else // defined(ASIO_HAS_CONCEPTS) + +#define ASIO_EXECUTION_OPERATION_STATE typename + +#endif // defined(ASIO_HAS_CONCEPTS) + +} // namespace execution +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_OPERATION_STATE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/outstanding_work.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/outstanding_work.hpp new file mode 100644 index 000000000..4ccc0d28f --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/outstanding_work.hpp @@ -0,0 +1,721 @@ +// +// execution/outstanding_work.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_OUTSTANDING_WORK_HPP +#define ASIO_EXECUTION_OUTSTANDING_WORK_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/scheduler.hpp" +#include "asio/execution/sender.hpp" +#include "asio/is_applicable_property.hpp" +#include "asio/query.hpp" +#include "asio/traits/query_free.hpp" +#include "asio/traits/query_member.hpp" +#include "asio/traits/query_static_constexpr_member.hpp" +#include "asio/traits/static_query.hpp" +#include "asio/traits/static_require.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if defined(GENERATING_DOCUMENTATION) + +namespace execution { + +/// A property to describe whether task submission is likely in the future. +struct outstanding_work_t +{ + /// The outstanding_work_t property applies to executors, senders, and + /// schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The top-level outstanding_work_t property cannot be required. + static constexpr bool is_requirable = false; + + /// The top-level outstanding_work_t property cannot be preferred. + static constexpr bool is_preferable = false; + + /// The type returned by queries against an @c any_executor. + typedef outstanding_work_t polymorphic_query_result_type; + + /// A sub-property that indicates that the executor does not represent likely + /// future submission of a function object. + struct untracked_t + { + /// The outstanding_work_t::untracked_t property applies to executors, + /// senders, and schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The outstanding_work_t::untracked_t property can be required. + static constexpr bool is_requirable = true; + + /// The outstanding_work_t::untracked_t property can be preferred. + static constexpr bool is_preferable = true; + + /// The type returned by queries against an @c any_executor. + typedef outstanding_work_t polymorphic_query_result_type; + + /// Default constructor. + constexpr untracked_t(); + + /// Get the value associated with a property object. + /** + * @returns untracked_t(); + */ + static constexpr outstanding_work_t value(); + }; + + /// A sub-property that indicates that the executor represents likely + /// future submission of a function object. + struct tracked_t + { + /// The outstanding_work_t::untracked_t property applies to executors, + /// senders, and schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The outstanding_work_t::tracked_t property can be required. + static constexpr bool is_requirable = true; + + /// The outstanding_work_t::tracked_t property can be preferred. + static constexpr bool is_preferable = true; + + /// The type returned by queries against an @c any_executor. + typedef outstanding_work_t polymorphic_query_result_type; + + /// Default constructor. + constexpr tracked_t(); + + /// Get the value associated with a property object. + /** + * @returns tracked_t(); + */ + static constexpr outstanding_work_t value(); + }; + + /// A special value used for accessing the outstanding_work_t::untracked_t + /// property. + static constexpr untracked_t untracked; + + /// A special value used for accessing the outstanding_work_t::tracked_t + /// property. + static constexpr tracked_t tracked; + + /// Default constructor. + constexpr outstanding_work_t(); + + /// Construct from a sub-property value. + constexpr outstanding_work_t(untracked_t); + + /// Construct from a sub-property value. + constexpr outstanding_work_t(tracked_t); + + /// Compare property values for equality. + friend constexpr bool operator==( + const outstanding_work_t& a, const outstanding_work_t& b) noexcept; + + /// Compare property values for inequality. + friend constexpr bool operator!=( + const outstanding_work_t& a, const outstanding_work_t& b) noexcept; +}; + +/// A special value used for accessing the outstanding_work_t property. +constexpr outstanding_work_t outstanding_work; + +} // namespace execution + +#else // defined(GENERATING_DOCUMENTATION) + +namespace execution { +namespace detail { +namespace outstanding_work { + +template struct untracked_t; +template struct tracked_t; + +} // namespace outstanding_work + +template +struct outstanding_work_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = false); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = false); + typedef outstanding_work_t polymorphic_query_result_type; + + typedef detail::outstanding_work::untracked_t untracked_t; + typedef detail::outstanding_work::tracked_t tracked_t; + + ASIO_CONSTEXPR outstanding_work_t() + : value_(-1) + { + } + + ASIO_CONSTEXPR outstanding_work_t(untracked_t) + : value_(0) + { + } + + ASIO_CONSTEXPR outstanding_work_t(tracked_t) + : value_(1) + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member< + T, outstanding_work_t>::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member< + T, outstanding_work_t + >::is_noexcept)) + { + return traits::query_static_constexpr_member< + T, outstanding_work_t>::value(); + } + + template + static ASIO_CONSTEXPR + typename traits::static_query::result_type + static_query( + typename enable_if< + !traits::query_static_constexpr_member< + T, outstanding_work_t>::is_valid + && !traits::query_member::is_valid + && traits::static_query::is_valid + >::type* = 0) ASIO_NOEXCEPT + { + return traits::static_query::value(); + } + + template + static ASIO_CONSTEXPR + typename traits::static_query::result_type + static_query( + typename enable_if< + !traits::query_static_constexpr_member< + T, outstanding_work_t>::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type* = 0) ASIO_NOEXCEPT + { + return traits::static_query::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = outstanding_work_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + friend ASIO_CONSTEXPR bool operator==( + const outstanding_work_t& a, const outstanding_work_t& b) + { + return a.value_ == b.value_; + } + + friend ASIO_CONSTEXPR bool operator!=( + const outstanding_work_t& a, const outstanding_work_t& b) + { + return a.value_ != b.value_; + } + + struct convertible_from_outstanding_work_t + { + ASIO_CONSTEXPR convertible_from_outstanding_work_t(outstanding_work_t) + { + } + }; + + template + friend ASIO_CONSTEXPR outstanding_work_t query( + const Executor& ex, convertible_from_outstanding_work_t, + typename enable_if< + can_query::value + >::type* = 0) +#if !defined(__clang__) // Clang crashes if noexcept is used here. +#if defined(ASIO_MSVC) // Visual C++ wants the type to be qualified. + ASIO_NOEXCEPT_IF(( + is_nothrow_query::untracked_t>::value)) +#else // defined(ASIO_MSVC) + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#endif // defined(ASIO_MSVC) +#endif // !defined(__clang__) + { + return asio::query(ex, untracked_t()); + } + + template + friend ASIO_CONSTEXPR outstanding_work_t query( + const Executor& ex, convertible_from_outstanding_work_t, + typename enable_if< + !can_query::value + && can_query::value + >::type* = 0) +#if !defined(__clang__) // Clang crashes if noexcept is used here. +#if defined(ASIO_MSVC) // Visual C++ wants the type to be qualified. + ASIO_NOEXCEPT_IF(( + is_nothrow_query::tracked_t>::value)) +#else // defined(ASIO_MSVC) + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#endif // defined(ASIO_MSVC) +#endif // !defined(__clang__) + { + return asio::query(ex, tracked_t()); + } + + ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(untracked_t, untracked); + ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(tracked_t, tracked); + +#if !defined(ASIO_HAS_CONSTEXPR) + static const outstanding_work_t instance; +#endif // !defined(ASIO_HAS_CONSTEXPR) + +private: + int value_; +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T outstanding_work_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_CONSTEXPR) +template +const outstanding_work_t outstanding_work_t::instance; +#endif + +template +const typename outstanding_work_t::untracked_t +outstanding_work_t::untracked; + +template +const typename outstanding_work_t::tracked_t +outstanding_work_t::tracked; + +namespace outstanding_work { + +template +struct untracked_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = true); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = true); + typedef outstanding_work_t polymorphic_query_result_type; + + ASIO_CONSTEXPR untracked_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template + static ASIO_CONSTEXPR untracked_t static_query( + typename enable_if< + !traits::query_static_constexpr_member::is_valid + && !traits::query_member::is_valid + && !traits::query_free::is_valid + && !can_query >::value + >::type* = 0) ASIO_NOEXCEPT + { + return untracked_t(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = untracked_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + static ASIO_CONSTEXPR outstanding_work_t value() + { + return untracked_t(); + } + + friend ASIO_CONSTEXPR bool operator==( + const untracked_t&, const untracked_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator!=( + const untracked_t&, const untracked_t&) + { + return false; + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T untracked_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct tracked_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = true); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = true); + typedef outstanding_work_t polymorphic_query_result_type; + + ASIO_CONSTEXPR tracked_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = tracked_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + static ASIO_CONSTEXPR outstanding_work_t value() + { + return tracked_t(); + } + + friend ASIO_CONSTEXPR bool operator==( + const tracked_t&, const tracked_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator!=( + const tracked_t&, const tracked_t&) + { + return false; + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T tracked_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +} // namespace outstanding_work +} // namespace detail + +typedef detail::outstanding_work_t<> outstanding_work_t; + +#if defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +constexpr outstanding_work_t outstanding_work; +#else // defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +namespace { static const outstanding_work_t& + outstanding_work = outstanding_work_t::instance; } +#endif + +} // namespace execution + +#if !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +#endif // !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +namespace traits { + +#if !defined(ASIO_HAS_DEDUCED_QUERY_FREE_TRAIT) + +template +struct query_free_default::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + + typedef execution::outstanding_work_t result_type; +}; + +template +struct query_free_default::value + && can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + + typedef execution::outstanding_work_t result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_QUERY_FREE_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && traits::static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::static_query::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::static_query::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::static_query::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::static_query::value(); + } +}; + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && !traits::query_free::is_valid + && !can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef execution::outstanding_work_t::untracked_t result_type; + + static ASIO_CONSTEXPR result_type value() + { + return result_type(); + } +}; + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +#endif // !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_DEDUCED_STATIC_REQUIRE_TRAIT) + +template +struct static_require::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = + (is_same::result_type, + execution::outstanding_work_t::untracked_t>::value)); +}; + +template +struct static_require::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = + (is_same::result_type, + execution::outstanding_work_t::tracked_t>::value)); +}; + +#endif // !defined(ASIO_HAS_DEDUCED_STATIC_REQUIRE_TRAIT) + +} // namespace traits + +#endif // defined(GENERATING_DOCUMENTATION) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_OUTSTANDING_WORK_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/prefer_only.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/prefer_only.hpp new file mode 100644 index 000000000..9823dade3 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/prefer_only.hpp @@ -0,0 +1,327 @@ +// +// execution/prefer_only.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_PREFER_ONLY_HPP +#define ASIO_EXECUTION_PREFER_ONLY_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/is_applicable_property.hpp" +#include "asio/prefer.hpp" +#include "asio/query.hpp" +#include "asio/traits/static_query.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if defined(GENERATING_DOCUMENTATION) + +namespace execution { + +/// A property adapter that is used with the polymorphic executor wrapper +/// to mark properties as preferable, but not requirable. +template +struct prefer_only +{ + /// The prefer_only adapter applies to the same types as the nested property. + template + static constexpr bool is_applicable_property_v = + is_applicable_property::value; + + /// The context_t property cannot be required. + static constexpr bool is_requirable = false; + + /// The context_t property can be preferred, it the underlying property can + /// be preferred. + /** + * @c true if @c Property::is_preferable is @c true, otherwise @c false. + */ + static constexpr bool is_preferable = automatically_determined; + + /// The type returned by queries against an @c any_executor. + typedef typename Property::polymorphic_query_result_type + polymorphic_query_result_type; +}; + +} // namespace execution + +#else // defined(GENERATING_DOCUMENTATION) + +namespace execution { +namespace detail { + +template +struct prefer_only_is_preferable +{ + ASIO_STATIC_CONSTEXPR(bool, is_preferable = false); +}; + +template +struct prefer_only_is_preferable::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_preferable = true); +}; + +template +struct prefer_only_polymorphic_query_result_type +{ +}; + +template +struct prefer_only_polymorphic_query_result_type::type> +{ + typedef typename InnerProperty::polymorphic_query_result_type + polymorphic_query_result_type; +}; + +template +struct prefer_only_property +{ + InnerProperty property; + + prefer_only_property(const InnerProperty& p) + : property(p) + { + } +}; + +#if defined(ASIO_HAS_DECLTYPE) \ + && defined(ASIO_HAS_WORKING_EXPRESSION_SFINAE) + +template +struct prefer_only_property().value()) + >::type> +{ + InnerProperty property; + + prefer_only_property(const InnerProperty& p) + : property(p) + { + } + + ASIO_CONSTEXPR auto value() const + ASIO_NOEXCEPT_IF(( + noexcept(asio::declval().value()))) + -> decltype(asio::declval().value()) + { + return property.value(); + } +}; + +#else // defined(ASIO_HAS_DECLTYPE) + // && defined(ASIO_HAS_WORKING_EXPRESSION_SFINAE) + +struct prefer_only_memfns_base +{ + void value(); +}; + +template +struct prefer_only_memfns_derived + : T, prefer_only_memfns_base +{ +}; + +template +struct prefer_only_memfns_check +{ +}; + +template +char (&prefer_only_value_memfn_helper(...))[2]; + +template +char prefer_only_value_memfn_helper( + prefer_only_memfns_check< + void (prefer_only_memfns_base::*)(), + &prefer_only_memfns_derived::value>*); + +template +struct prefer_only_property(0)) != 1 + && !is_same::value + >::type> +{ + InnerProperty property; + + prefer_only_property(const InnerProperty& p) + : property(p) + { + } + + ASIO_CONSTEXPR typename InnerProperty::polymorphic_query_result_type + value() const + { + return property.value(); + } +}; + +#endif // defined(ASIO_HAS_DECLTYPE) + // && defined(ASIO_HAS_WORKING_EXPRESSION_SFINAE) + +} // namespace detail + +template +struct prefer_only : + detail::prefer_only_is_preferable, + detail::prefer_only_polymorphic_query_result_type, + detail::prefer_only_property +{ + ASIO_STATIC_CONSTEXPR(bool, is_requirable = false); + + ASIO_CONSTEXPR prefer_only(const InnerProperty& p) + : detail::prefer_only_property(p) + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::static_query::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::static_query::is_noexcept)) + { + return traits::static_query::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = prefer_only::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + template + friend ASIO_CONSTEXPR + typename prefer_result::type + prefer(const Executor& ex, const prefer_only& p, + typename enable_if< + is_same::value + && can_prefer::value + >::type* = 0) +#if !defined(ASIO_MSVC) \ + && !defined(__clang__) // Clang crashes if noexcept is used here. + ASIO_NOEXCEPT_IF(( + is_nothrow_prefer::value)) +#endif // !defined(ASIO_MSVC) + // && !defined(__clang__) + { + return asio::prefer(ex, p.property); + } + + template + friend ASIO_CONSTEXPR + typename query_result::type + query(const Executor& ex, const prefer_only& p, + typename enable_if< + is_same::value + && can_query::value + >::type* = 0) +#if !defined(ASIO_MSVC) \ + && !defined(__clang__) // Clang crashes if noexcept is used here. + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#endif // !defined(ASIO_MSVC) + // && !defined(__clang__) + { + return asio::query(ex, p.property); + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T prefer_only::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +} // namespace execution + +template +struct is_applicable_property > + : is_applicable_property +{ +}; + +namespace traits { + +#if !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct static_query > : + static_query +{ +}; + +#endif // !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_DEDUCED_PREFER_FREE_TRAIT) + +template +struct prefer_free_default, + typename enable_if< + can_prefer::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_prefer::value)); + + typedef typename prefer_result::type result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_PREFER_FREE_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_QUERY_FREE_TRAIT) + +template +struct query_free, + typename enable_if< + can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + + typedef typename query_result::type result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_QUERY_FREE_TRAIT) + +} // namespace traits + +#endif // defined(GENERATING_DOCUMENTATION) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_PREFER_ONLY_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/receiver.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/receiver.hpp new file mode 100644 index 000000000..b63f788df --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/receiver.hpp @@ -0,0 +1,280 @@ +// +// execution/receiver.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_RECEIVER_HPP +#define ASIO_EXECUTION_RECEIVER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/detail/variadic_templates.hpp" +#include "asio/execution/set_done.hpp" +#include "asio/execution/set_error.hpp" +#include "asio/execution/set_value.hpp" + +#if defined(ASIO_HAS_STD_EXCEPTION_PTR) +# include +#else // defined(ASIO_HAS_STD_EXCEPTION_PTR) +# include "asio/error_code.hpp" +#endif // defined(ASIO_HAS_STD_EXCEPTION_PTR) + +#if defined(ASIO_HAS_DEDUCED_SET_DONE_FREE_TRAIT) \ + && defined(ASIO_HAS_DEDUCED_SET_DONE_MEMBER_TRAIT) \ + && defined(ASIO_HAS_DEDUCED_SET_ERROR_FREE_TRAIT) \ + && defined(ASIO_HAS_DEDUCED_SET_ERROR_MEMBER_TRAIT) \ + && defined(ASIO_HAS_DEDUCED_SET_VALUE_FREE_TRAIT) \ + && defined(ASIO_HAS_DEDUCED_SET_VALUE_MEMBER_TRAIT) \ + && defined(ASIO_HAS_DEDUCED_RECEIVER_OF_FREE_TRAIT) \ + && defined(ASIO_HAS_DEDUCED_RECEIVER_OF_MEMBER_TRAIT) +# define ASIO_HAS_DEDUCED_EXECUTION_IS_RECEIVER_TRAIT 1 +#endif // defined(ASIO_HAS_DEDUCED_SET_DONE_FREE_TRAIT) + // && defined(ASIO_HAS_DEDUCED_SET_DONE_MEMBER_TRAIT) + // && defined(ASIO_HAS_DEDUCED_SET_ERROR_FREE_TRAIT) + // && defined(ASIO_HAS_DEDUCED_SET_ERROR_MEMBER_TRAIT) + // && defined(ASIO_HAS_DEDUCED_SET_VALUE_FREE_TRAIT) + // && defined(ASIO_HAS_DEDUCED_SET_VALUE_MEMBER_TRAIT) + // && defined(ASIO_HAS_DEDUCED_RECEIVER_OF_FREE_TRAIT) + // && defined(ASIO_HAS_DEDUCED_RECEIVER_OF_MEMBER_TRAIT) + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace execution { +namespace detail { + +template +struct is_receiver_base : + integral_constant::type>::value + && is_constructible::type, T>::value + > +{ +}; + +} // namespace detail + +#if defined(ASIO_HAS_STD_EXCEPTION_PTR) +# define ASIO_EXECUTION_RECEIVER_ERROR_DEFAULT = std::exception_ptr +#else // defined(ASIO_HAS_STD_EXCEPTION_PTR) +# define ASIO_EXECUTION_RECEIVER_ERROR_DEFAULT \ + = ::asio::error_code +#endif // defined(ASIO_HAS_STD_EXCEPTION_PTR) + +/// The is_receiver trait detects whether a type T satisfies the +/// execution::receiver concept. +/** + * Class template @c is_receiver is a type trait that is derived from @c + * true_type if the type @c T meets the concept definition for a receiver for + * error type @c E, otherwise @c false_type. + */ +template +struct is_receiver : +#if defined(GENERATING_DOCUMENTATION) + integral_constant +#else // defined(GENERATING_DOCUMENTATION) + conditional< + can_set_done::type>::value + && is_nothrow_set_done::type>::value + && can_set_error::type, E>::value + && is_nothrow_set_error::type, E>::value, + detail::is_receiver_base, + false_type + >::type +#endif // defined(GENERATING_DOCUMENTATION) +{ +}; + +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +ASIO_CONSTEXPR const bool is_receiver_v = is_receiver::value; + +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + +#if defined(ASIO_HAS_CONCEPTS) + +template +ASIO_CONCEPT receiver = is_receiver::value; + +#define ASIO_EXECUTION_RECEIVER ::asio::execution::receiver + +#else // defined(ASIO_HAS_CONCEPTS) + +#define ASIO_EXECUTION_RECEIVER typename + +#endif // defined(ASIO_HAS_CONCEPTS) + +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) \ + || defined(GENERATING_DOCUMENTATION) + +/// The is_receiver_of trait detects whether a type T satisfies the +/// execution::receiver_of concept for some set of value arguments. +/** + * Class template @c is_receiver_of is a type trait that is derived from @c + * true_type if the type @c T meets the concept definition for a receiver for + * value arguments @c Vs, otherwise @c false_type. + */ +template +struct is_receiver_of : +#if defined(GENERATING_DOCUMENTATION) + integral_constant +#else // defined(GENERATING_DOCUMENTATION) + conditional< + is_receiver::value, + can_set_value::type, Vs...>, + false_type + >::type +#endif // defined(GENERATING_DOCUMENTATION) +{ +}; + +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +ASIO_CONSTEXPR const bool is_receiver_of_v = + is_receiver_of::value; + +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + +#if defined(ASIO_HAS_CONCEPTS) + +template +ASIO_CONCEPT receiver_of = is_receiver_of::value; + +#define ASIO_EXECUTION_RECEIVER_OF_0 \ + ::asio::execution::receiver_of + +#define ASIO_EXECUTION_RECEIVER_OF_1(v) \ + ::asio::execution::receiver_of + +#else // defined(ASIO_HAS_CONCEPTS) + +#define ASIO_EXECUTION_RECEIVER_OF_0 typename +#define ASIO_EXECUTION_RECEIVER_OF_1(v) typename + +#endif // defined(ASIO_HAS_CONCEPTS) + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + // || defined(GENERATING_DOCUMENTATION) + +template +struct is_receiver_of; + +template +struct is_receiver_of : + conditional< + is_receiver::value, + can_set_value::type>, + false_type + >::type +{ +}; + +#define ASIO_PRIVATE_RECEIVER_OF_TRAITS_DEF(n) \ + template \ + struct is_receiver_of : \ + conditional< \ + conditional, void>::type::value, \ + can_set_value< \ + typename remove_cvref::type, \ + ASIO_VARIADIC_TARGS(n)>, \ + false_type \ + >::type \ + { \ + }; \ + /**/ +ASIO_VARIADIC_GENERATE(ASIO_PRIVATE_RECEIVER_OF_TRAITS_DEF) +#undef ASIO_PRIVATE_RECEIVER_OF_TRAITS_DEF + +#define ASIO_EXECUTION_RECEIVER_OF_0 typename +#define ASIO_EXECUTION_RECEIVER_OF_1(v) typename + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) + // || defined(GENERATING_DOCUMENTATION) + +#if defined(ASIO_HAS_VARIADIC_TEMPLATES) \ + || defined(GENERATING_DOCUMENTATION) + +/// The is_nothrow_receiver_of trait detects whether a type T satisfies the +/// execution::receiver_of concept for some set of value arguments, with a +/// noexcept @c set_value operation. +/** + * Class template @c is_nothrow_receiver_of is a type trait that is derived + * from @c true_type if the type @c T meets the concept definition for a + * receiver for value arguments @c Vs, and the expression + * execution::set_value(declval(), declval()...) is noexcept, + * otherwise @c false_type. + */ +template +struct is_nothrow_receiver_of : +#if defined(GENERATING_DOCUMENTATION) + integral_constant +#else // defined(GENERATING_DOCUMENTATION) + integral_constant::value + && is_nothrow_set_value::type, Vs...>::value + > +#endif // defined(GENERATING_DOCUMENTATION) +{ +}; + +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +ASIO_CONSTEXPR const bool is_nothrow_receiver_of_v = + is_nothrow_receiver_of::value; + +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + +#else // defined(ASIO_HAS_VARIADIC_TEMPLATES) + // || defined(GENERATING_DOCUMENTATION) + +template +struct is_nothrow_receiver_of; + +template +struct is_nothrow_receiver_of : + integral_constant::value + && is_nothrow_set_value::type>::value + > +{ +}; + +#define ASIO_PRIVATE_NOTHROW_RECEIVER_OF_TRAITS_DEF(n) \ + template \ + struct is_nothrow_receiver_of : \ + integral_constant::value \ + && is_nothrow_set_value::type, \ + ASIO_VARIADIC_TARGS(n)>::value \ + > \ + { \ + }; \ + /**/ +ASIO_VARIADIC_GENERATE(ASIO_PRIVATE_NOTHROW_RECEIVER_OF_TRAITS_DEF) +#undef ASIO_PRIVATE_NOTHROW_RECEIVER_OF_TRAITS_DEF + +#endif // defined(ASIO_HAS_VARIADIC_TEMPLATES) + // || defined(GENERATING_DOCUMENTATION) + +} // namespace execution +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_RECEIVER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/receiver_invocation_error.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/receiver_invocation_error.hpp new file mode 100644 index 000000000..5c4ee6dfb --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/receiver_invocation_error.hpp @@ -0,0 +1,48 @@ +// +// execution/receiver_invocation_error.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_RECEIVER_INVOCATION_ERROR_HPP +#define ASIO_EXECUTION_RECEIVER_INVOCATION_ERROR_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace execution { + +/// Exception reported via @c set_error when an exception escapes from +/// @c set_value. +class receiver_invocation_error + : public std::runtime_error +#if defined(ASIO_HAS_STD_NESTED_EXCEPTION) + , public std::nested_exception +#endif // defined(ASIO_HAS_STD_NESTED_EXCEPTION) +{ +public: + /// Constructor. + ASIO_DECL receiver_invocation_error(); +}; + +} // namespace execution +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#if defined(ASIO_HEADER_ONLY) +# include "asio/execution/impl/receiver_invocation_error.ipp" +#endif // defined(ASIO_HEADER_ONLY) + +#endif // ASIO_EXECUTION_RECEIVER_INVOCATION_ERROR_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/relationship.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/relationship.hpp new file mode 100644 index 000000000..720a3394e --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/relationship.hpp @@ -0,0 +1,720 @@ +// +// execution/relationship.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_RELATIONSHIP_HPP +#define ASIO_EXECUTION_RELATIONSHIP_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/scheduler.hpp" +#include "asio/execution/sender.hpp" +#include "asio/is_applicable_property.hpp" +#include "asio/query.hpp" +#include "asio/traits/query_free.hpp" +#include "asio/traits/query_member.hpp" +#include "asio/traits/query_static_constexpr_member.hpp" +#include "asio/traits/static_query.hpp" +#include "asio/traits/static_require.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { + +#if defined(GENERATING_DOCUMENTATION) + +namespace execution { + +/// A property to describe whether submitted tasks represent continuations of +/// the calling context. +struct relationship_t +{ + /// The relationship_t property applies to executors, senders, and schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The top-level relationship_t property cannot be required. + static constexpr bool is_requirable = false; + + /// The top-level relationship_t property cannot be preferred. + static constexpr bool is_preferable = false; + + /// The type returned by queries against an @c any_executor. + typedef relationship_t polymorphic_query_result_type; + + /// A sub-property that indicates that the executor does not represent a + /// continuation of the calling context. + struct fork_t + { + /// The relationship_t::fork_t property applies to executors, senders, and + /// schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The relationship_t::fork_t property can be required. + static constexpr bool is_requirable = true; + + /// The relationship_t::fork_t property can be preferred. + static constexpr bool is_preferable = true; + + /// The type returned by queries against an @c any_executor. + typedef relationship_t polymorphic_query_result_type; + + /// Default constructor. + constexpr fork_t(); + + /// Get the value associated with a property object. + /** + * @returns fork_t(); + */ + static constexpr relationship_t value(); + }; + + /// A sub-property that indicates that the executor represents a continuation + /// of the calling context. + struct continuation_t + { + /// The relationship_t::continuation_t property applies to executors, + /// senders, and schedulers. + template + static constexpr bool is_applicable_property_v = + is_executor_v || is_sender_v || is_scheduler_v; + + /// The relationship_t::continuation_t property can be required. + static constexpr bool is_requirable = true; + + /// The relationship_t::continuation_t property can be preferred. + static constexpr bool is_preferable = true; + + /// The type returned by queries against an @c any_executor. + typedef relationship_t polymorphic_query_result_type; + + /// Default constructor. + constexpr continuation_t(); + + /// Get the value associated with a property object. + /** + * @returns continuation_t(); + */ + static constexpr relationship_t value(); + }; + + /// A special value used for accessing the relationship_t::fork_t property. + static constexpr fork_t fork; + + /// A special value used for accessing the relationship_t::continuation_t + /// property. + static constexpr continuation_t continuation; + + /// Default constructor. + constexpr relationship_t(); + + /// Construct from a sub-property value. + constexpr relationship_t(fork_t); + + /// Construct from a sub-property value. + constexpr relationship_t(continuation_t); + + /// Compare property values for equality. + friend constexpr bool operator==( + const relationship_t& a, const relationship_t& b) noexcept; + + /// Compare property values for inequality. + friend constexpr bool operator!=( + const relationship_t& a, const relationship_t& b) noexcept; +}; + +/// A special value used for accessing the relationship_t property. +constexpr relationship_t relationship; + +} // namespace execution + +#else // defined(GENERATING_DOCUMENTATION) + +namespace execution { +namespace detail { +namespace relationship { + +template struct fork_t; +template struct continuation_t; + +} // namespace relationship + +template +struct relationship_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = false); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = false); + typedef relationship_t polymorphic_query_result_type; + + typedef detail::relationship::fork_t fork_t; + typedef detail::relationship::continuation_t continuation_t; + + ASIO_CONSTEXPR relationship_t() + : value_(-1) + { + } + + ASIO_CONSTEXPR relationship_t(fork_t) + : value_(0) + { + } + + ASIO_CONSTEXPR relationship_t(continuation_t) + : value_(1) + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member< + T, relationship_t>::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member< + T, relationship_t + >::is_noexcept)) + { + return traits::query_static_constexpr_member< + T, relationship_t>::value(); + } + + template + static ASIO_CONSTEXPR + typename traits::static_query::result_type + static_query( + typename enable_if< + !traits::query_static_constexpr_member< + T, relationship_t>::is_valid + && !traits::query_member::is_valid + && traits::static_query::is_valid + >::type* = 0) ASIO_NOEXCEPT + { + return traits::static_query::value(); + } + + template + static ASIO_CONSTEXPR + typename traits::static_query::result_type + static_query( + typename enable_if< + !traits::query_static_constexpr_member< + T, relationship_t>::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type* = 0) ASIO_NOEXCEPT + { + return traits::static_query::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = relationship_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + friend ASIO_CONSTEXPR bool operator==( + const relationship_t& a, const relationship_t& b) + { + return a.value_ == b.value_; + } + + friend ASIO_CONSTEXPR bool operator!=( + const relationship_t& a, const relationship_t& b) + { + return a.value_ != b.value_; + } + + struct convertible_from_relationship_t + { + ASIO_CONSTEXPR convertible_from_relationship_t(relationship_t) + { + } + }; + + template + friend ASIO_CONSTEXPR relationship_t query( + const Executor& ex, convertible_from_relationship_t, + typename enable_if< + can_query::value + >::type* = 0) +#if !defined(__clang__) // Clang crashes if noexcept is used here. +#if defined(ASIO_MSVC) // Visual C++ wants the type to be qualified. + ASIO_NOEXCEPT_IF(( + is_nothrow_query::fork_t>::value)) +#else // defined(ASIO_MSVC) + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#endif // defined(ASIO_MSVC) +#endif // !defined(__clang__) + { + return asio::query(ex, fork_t()); + } + + template + friend ASIO_CONSTEXPR relationship_t query( + const Executor& ex, convertible_from_relationship_t, + typename enable_if< + !can_query::value + && can_query::value + >::type* = 0) +#if !defined(__clang__) // Clang crashes if noexcept is used here. +#if defined(ASIO_MSVC) // Visual C++ wants the type to be qualified. + ASIO_NOEXCEPT_IF(( + is_nothrow_query::continuation_t>::value)) +#else // defined(ASIO_MSVC) + ASIO_NOEXCEPT_IF(( + is_nothrow_query::value)) +#endif // defined(ASIO_MSVC) +#endif // !defined(__clang__) + { + return asio::query(ex, continuation_t()); + } + + ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(fork_t, fork); + ASIO_STATIC_CONSTEXPR_DEFAULT_INIT(continuation_t, continuation); + +#if !defined(ASIO_HAS_CONSTEXPR) + static const relationship_t instance; +#endif // !defined(ASIO_HAS_CONSTEXPR) + +private: + int value_; +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T relationship_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_CONSTEXPR) +template +const relationship_t relationship_t::instance; +#endif + +template +const typename relationship_t::fork_t +relationship_t::fork; + +template +const typename relationship_t::continuation_t +relationship_t::continuation; + +namespace relationship { + +template +struct fork_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = true); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = true); + typedef relationship_t polymorphic_query_result_type; + + ASIO_CONSTEXPR fork_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template + static ASIO_CONSTEXPR fork_t static_query( + typename enable_if< + !traits::query_static_constexpr_member::is_valid + && !traits::query_member::is_valid + && !traits::query_free::is_valid + && !can_query >::value + >::type* = 0) ASIO_NOEXCEPT + { + return fork_t(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = fork_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + static ASIO_CONSTEXPR relationship_t value() + { + return fork_t(); + } + + friend ASIO_CONSTEXPR bool operator==( + const fork_t&, const fork_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator!=( + const fork_t&, const fork_t&) + { + return false; + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T fork_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct continuation_t +{ +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + template + ASIO_STATIC_CONSTEXPR(bool, + is_applicable_property_v = is_executor::value + || is_sender::value || is_scheduler::value); +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + + ASIO_STATIC_CONSTEXPR(bool, is_requirable = true); + ASIO_STATIC_CONSTEXPR(bool, is_preferable = true); + typedef relationship_t polymorphic_query_result_type; + + ASIO_CONSTEXPR continuation_t() + { + } + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + template + static ASIO_CONSTEXPR + typename traits::query_static_constexpr_member::result_type + static_query() + ASIO_NOEXCEPT_IF(( + traits::query_static_constexpr_member::is_noexcept)) + { + return traits::query_static_constexpr_member::value(); + } + + template ())> + static ASIO_CONSTEXPR const T static_query_v + = continuation_t::static_query(); +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + + static ASIO_CONSTEXPR relationship_t value() + { + return continuation_t(); + } + + friend ASIO_CONSTEXPR bool operator==( + const continuation_t&, const continuation_t&) + { + return true; + } + + friend ASIO_CONSTEXPR bool operator!=( + const continuation_t&, const continuation_t&) + { + return false; + } +}; + +#if defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) +template template +const T continuation_t::static_query_v; +#endif // defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // && defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +} // namespace relationship +} // namespace detail + +typedef detail::relationship_t<> relationship_t; + +#if defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +constexpr relationship_t relationship; +#else // defined(ASIO_HAS_CONSTEXPR) || defined(GENERATING_DOCUMENTATION) +namespace { static const relationship_t& + relationship = relationship_t::instance; } +#endif + +} // namespace execution + +#if !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +template +struct is_applicable_property + : integral_constant::value + || execution::is_sender::value + || execution::is_scheduler::value> +{ +}; + +#endif // !defined(ASIO_HAS_VARIABLE_TEMPLATES) + +namespace traits { + +#if !defined(ASIO_HAS_DEDUCED_QUERY_FREE_TRAIT) + +template +struct query_free_default::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + + typedef execution::relationship_t result_type; +}; + +template +struct query_free_default::value + && can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = + (is_nothrow_query::value)); + + typedef execution::relationship_t result_type; +}; + +#endif // !defined(ASIO_HAS_DEDUCED_QUERY_FREE_TRAIT) + +#if !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) \ + || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && traits::static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::static_query::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::static_query::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && !traits::static_query::is_valid + && traits::static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::static_query::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::static_query::value(); + } +}; + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +template +struct static_query::is_valid + && !traits::query_member::is_valid + && !traits::query_free::is_valid + && !can_query::value + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef execution::relationship_t::fork_t result_type; + + static ASIO_CONSTEXPR result_type value() + { + return result_type(); + } +}; + +template +struct static_query::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = true); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + + typedef typename traits::query_static_constexpr_member::result_type result_type; + + static ASIO_CONSTEXPR result_type value() + { + return traits::query_static_constexpr_member::value(); + } +}; + +#endif // !defined(ASIO_HAS_DEDUCED_STATIC_QUERY_TRAIT) + // || !defined(ASIO_HAS_SFINAE_VARIABLE_TEMPLATES) + +#if !defined(ASIO_HAS_DEDUCED_STATIC_REQUIRE_TRAIT) + +template +struct static_require::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = + (is_same::result_type, + execution::relationship_t::fork_t>::value)); +}; + +template +struct static_require::is_valid + >::type> +{ + ASIO_STATIC_CONSTEXPR(bool, is_valid = + (is_same::result_type, + execution::relationship_t::continuation_t>::value)); +}; + +#endif // !defined(ASIO_HAS_DEDUCED_STATIC_REQUIRE_TRAIT) + +} // namespace traits + +#endif // defined(GENERATING_DOCUMENTATION) + +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_RELATIONSHIP_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/schedule.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/schedule.hpp new file mode 100644 index 000000000..1262735f3 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/schedule.hpp @@ -0,0 +1,290 @@ +// +// execution/schedule.hpp +// ~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_SCHEDULE_HPP +#define ASIO_EXECUTION_SCHEDULE_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/executor.hpp" +#include "asio/traits/schedule_member.hpp" +#include "asio/traits/schedule_free.hpp" + +#include "asio/detail/push_options.hpp" + +#if defined(GENERATING_DOCUMENTATION) + +namespace asio { +namespace execution { + +/// A customisation point that is used to obtain a sender from a scheduler. +/** + * The name execution::schedule denotes a customisation point object. + * For some subexpression s, let S be a type such that + * decltype((s)) is S. The expression + * execution::schedule(s) is expression-equivalent to: + * + * @li s.schedule(), if that expression is valid and its type models + * sender. + * + * @li Otherwise, schedule(s), if that expression is valid and its + * type models sender with overload resolution performed in a context + * that includes the declaration void schedule(); and that does not + * include a declaration of execution::schedule. + * + * @li Otherwise, S if S satisfies executor. + * + * @li Otherwise, execution::schedule(s) is ill-formed. + */ +inline constexpr unspecified schedule = unspecified; + +/// A type trait that determines whether a @c schedule expression is +/// well-formed. +/** + * Class template @c can_schedule is a trait that is derived from @c true_type + * if the expression execution::schedule(std::declval()) is well + * formed; otherwise @c false_type. + */ +template +struct can_schedule : + integral_constant +{ +}; + +} // namespace execution +} // namespace asio + +#else // defined(GENERATING_DOCUMENTATION) + +namespace asio_execution_schedule_fn { + +using asio::decay; +using asio::declval; +using asio::enable_if; +using asio::execution::is_executor; +using asio::traits::schedule_free; +using asio::traits::schedule_member; + +void schedule(); + +enum overload_type +{ + identity, + call_member, + call_free, + ill_formed +}; + +template +struct call_traits +{ + ASIO_STATIC_CONSTEXPR(overload_type, overload = ill_formed); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = false); + typedef void result_type; +}; + +template +struct call_traits::is_valid + ) + >::type> : + schedule_member +{ + ASIO_STATIC_CONSTEXPR(overload_type, overload = call_member); +}; + +template +struct call_traits::is_valid + && + schedule_free::is_valid + ) + >::type> : + schedule_free +{ + ASIO_STATIC_CONSTEXPR(overload_type, overload = call_free); +}; + +template +struct call_traits::is_valid + && + !schedule_free::is_valid + && + is_executor::type>::value + ) + >::type> +{ + ASIO_STATIC_CONSTEXPR(overload_type, overload = identity); + ASIO_STATIC_CONSTEXPR(bool, is_noexcept = true); + +#if defined(ASIO_HAS_MOVE) + typedef ASIO_MOVE_ARG(S) result_type; +#else // defined(ASIO_HAS_MOVE) + typedef ASIO_MOVE_ARG(typename decay::type) result_type; +#endif // defined(ASIO_HAS_MOVE) +}; + +struct impl +{ + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == identity, + typename call_traits::result_type + >::type + operator()(ASIO_MOVE_ARG(S) s) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return ASIO_MOVE_CAST(S)(s); + } + +#if defined(ASIO_HAS_MOVE) + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_member, + typename call_traits::result_type + >::type + operator()(S&& s) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return ASIO_MOVE_CAST(S)(s).schedule(); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_free, + typename call_traits::result_type + >::type + operator()(S&& s) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return schedule(ASIO_MOVE_CAST(S)(s)); + } +#else // defined(ASIO_HAS_MOVE) + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_member, + typename call_traits::result_type + >::type + operator()(S& s) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return s.schedule(); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_member, + typename call_traits::result_type + >::type + operator()(const S& s) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return s.schedule(); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_free, + typename call_traits::result_type + >::type + operator()(S& s) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return schedule(s); + } + + template + ASIO_CONSTEXPR typename enable_if< + call_traits::overload == call_free, + typename call_traits::result_type + >::type + operator()(const S& s) const + ASIO_NOEXCEPT_IF(( + call_traits::is_noexcept)) + { + return schedule(s); + } +#endif // defined(ASIO_HAS_MOVE) +}; + +template +struct static_instance +{ + static const T instance; +}; + +template +const T static_instance::instance = {}; + +} // namespace asio_execution_schedule_fn +namespace asio { +namespace execution { +namespace { + +static ASIO_CONSTEXPR const asio_execution_schedule_fn::impl& + schedule = asio_execution_schedule_fn::static_instance<>::instance; + +} // namespace + +template +struct can_schedule : + integral_constant::overload != + asio_execution_schedule_fn::ill_formed> +{ +}; + +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +constexpr bool can_schedule_v = can_schedule::value; + +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +struct is_nothrow_schedule : + integral_constant::is_noexcept> +{ +}; + +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +constexpr bool is_nothrow_schedule_v + = is_nothrow_schedule::value; + +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + +} // namespace execution +} // namespace asio + +#endif // defined(GENERATING_DOCUMENTATION) + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_SCHEDULE_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/scheduler.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/scheduler.hpp new file mode 100644 index 000000000..c6c53ca10 --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/scheduler.hpp @@ -0,0 +1,86 @@ +// +// execution/scheduler.hpp +// ~~~~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_SCHEDULER_HPP +#define ASIO_EXECUTION_SCHEDULER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/schedule.hpp" +#include "asio/traits/equality_comparable.hpp" + +#include "asio/detail/push_options.hpp" + +namespace asio { +namespace execution { +namespace detail { + +template +struct is_scheduler_base : + integral_constant::type>::value + && traits::equality_comparable::type>::is_valid + > +{ +}; + +} // namespace detail + +/// The is_scheduler trait detects whether a type T satisfies the +/// execution::scheduler concept. +/** + * Class template @c is_scheduler is a type trait that is derived from @c + * true_type if the type @c T meets the concept definition for a scheduler for + * error type @c E, otherwise @c false_type. + */ +template +struct is_scheduler : +#if defined(GENERATING_DOCUMENTATION) + integral_constant +#else // defined(GENERATING_DOCUMENTATION) + conditional< + can_schedule::value, + detail::is_scheduler_base, + false_type + >::type +#endif // defined(GENERATING_DOCUMENTATION) +{ +}; + +#if defined(ASIO_HAS_VARIABLE_TEMPLATES) + +template +ASIO_CONSTEXPR const bool is_scheduler_v = is_scheduler::value; + +#endif // defined(ASIO_HAS_VARIABLE_TEMPLATES) + +#if defined(ASIO_HAS_CONCEPTS) + +template +ASIO_CONCEPT scheduler = is_scheduler::value; + +#define ASIO_EXECUTION_SCHEDULER ::asio::execution::scheduler + +#else // defined(ASIO_HAS_CONCEPTS) + +#define ASIO_EXECUTION_SCHEDULER typename + +#endif // defined(ASIO_HAS_CONCEPTS) + +} // namespace execution +} // namespace asio + +#include "asio/detail/pop_options.hpp" + +#endif // ASIO_EXECUTION_SCHEDULER_HPP diff --git a/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/sender.hpp b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/sender.hpp new file mode 100644 index 000000000..747e673ab --- /dev/null +++ b/tidal-link/link/modules/asio-standalone/asio/include/asio/execution/sender.hpp @@ -0,0 +1,311 @@ +// +// execution/sender.hpp +// ~~~~~~~~~~~~~~~~~~~~ +// +// Copyright (c) 2003-2020 Christopher M. Kohlhoff (chris at kohlhoff dot com) +// +// Distributed under the Boost Software License, Version 1.0. (See accompanying +// file LICENSE_1_0.txt or copy at http://www.boost.org/LICENSE_1_0.txt) +// + +#ifndef ASIO_EXECUTION_SENDER_HPP +#define ASIO_EXECUTION_SENDER_HPP + +#if defined(_MSC_VER) && (_MSC_VER >= 1200) +# pragma once +#endif // defined(_MSC_VER) && (_MSC_VER >= 1200) + +#include "asio/detail/config.hpp" +#include "asio/detail/type_traits.hpp" +#include "asio/execution/detail/as_invocable.hpp" +#include "asio/execution/detail/void_receiver.hpp" +#include "asio/execution/executor.hpp" +#include "asio/execution/receiver.hpp" + +#include "asio/detail/push_options.hpp" + +#if defined(ASIO_HAS_ALIAS_TEMPLATES) \ + && defined(ASIO_HAS_VARIADIC_TEMPLATES) \ + && defined(ASIO_HAS_DECLTYPE) \ + && !defined(ASIO_MSVC) || (_MSC_VER >= 1910) +# define ASIO_HAS_DEDUCED_EXECUTION_IS_TYPED_SENDER_TRAIT 1 +#endif // defined(ASIO_HAS_ALIAS_TEMPLATES) + // && defined(ASIO_HAS_VARIADIC_TEMPLATES) + // && defined(ASIO_HAS_DECLTYPE) + // && !defined(ASIO_MSVC) || (_MSC_VER >= 1910) + +namespace asio { +namespace execution { +namespace detail { + +namespace sender_base_ns { struct sender_base {}; } + +template +struct sender_traits_base +{ + typedef void asio_execution_sender_traits_base_is_unspecialised; +}; + +template +struct sender_traits_base::value + >::type> +{ +}; + +template +struct has_sender_types : false_type +{ +}; + +#if defined(ASIO_HAS_DEDUCED_EXECUTION_IS_TYPED_SENDER_TRAIT) + +template < + template < + template class Tuple, + template class Variant + > class> +struct has_value_types +{ + typedef void type; +}; + +template < + template < + template class Variant + > class> +struct has_error_types +{ + typedef void type; +}; + +template +struct has_sender_types::type, + typename has_error_types::type, + typename conditional::type> : true_type +{ +}; + +template +struct sender_traits_base::value + >::type> +{ + template < + template class Tuple, + template class Variant> + using value_types = typename S::template value_types; + + template