Skip to content

Commit

Permalink
using NonEmpty
Browse files Browse the repository at this point in the history
  • Loading branch information
kazu-yamamoto committed Dec 18, 2024
1 parent 0d7ac07 commit dfc5571
Show file tree
Hide file tree
Showing 2 changed files with 11 additions and 5 deletions.
6 changes: 4 additions & 2 deletions tls/util/Client.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,8 @@ module Client (

import qualified Data.ByteString.Base16 as BS16
import qualified Data.ByteString.Lazy.Char8 as CL8
import Data.List.NonEmpty (NonEmpty)
import qualified Data.List.NonEmpty as NE
import Network.Socket
import Network.TLS

Expand All @@ -23,13 +25,13 @@ data Aux = Aux
, auxReadResumptionData :: IO [(SessionID, SessionData)]
}

type Cli = Aux -> [ByteString] -> Context -> IO ()
type Cli = Aux -> NonEmpty ByteString -> Context -> IO ()

clientHTTP11 :: Cli
clientHTTP11 aux@Aux{..} paths ctx = do
sendData ctx $
"GET "
<> CL8.fromStrict (head paths)
<> CL8.fromStrict (NE.head paths)
<> " HTTP/1.1\r\n"
<> "Host: "
<> CL8.pack auxAuthority
Expand Down
10 changes: 7 additions & 3 deletions tls/util/tls-client.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}

Expand All @@ -9,6 +10,8 @@ import qualified Data.ByteString.Base16 as BS16
import qualified Data.ByteString.Char8 as C8
import Data.Default (def)
import Data.IORef
import Data.List.NonEmpty (NonEmpty)
import qualified Data.List.NonEmpty as NE
import Data.X509.CertificateStore
import Network.Run.TCP
import Network.Socket
Expand Down Expand Up @@ -136,7 +139,7 @@ main = do
[] -> showUsageAndExit usage
_ : [] -> showUsageAndExit usage
h : p : [] -> return (h, p, ["/"])
h : p : ps -> return (h, p, C8.pack <$> ps)
h : p : ps -> return (h, p, C8.pack <$> NE.fromList ps)
when (null optGroups) $ do
putStrLn "Error: unsupported groups"
exitFailure
Expand All @@ -163,7 +166,8 @@ main = do
| otherwise = clientHTTP11
runClient opts client cparams aux paths

runClient :: Options -> Cli -> ClientParams -> Aux -> [ByteString] -> IO ()
runClient
:: Options -> Cli -> ClientParams -> Aux -> NonEmpty ByteString -> IO ()
runClient opts@Options{..} client cparams aux@Aux{..} paths = do
auxDebug "------------------------"
(info1, msd) <- runTLS cparams aux $ \ctx -> do
Expand Down Expand Up @@ -232,7 +236,7 @@ runClient2
-> Cli
-> ClientParams
-> Aux
-> [ByteString]
-> NonEmpty ByteString
-> IO Information
runClient2 Options{..} client cparams aux@Aux{..} paths = do
threadDelay 100000
Expand Down

0 comments on commit dfc5571

Please sign in to comment.