Skip to content

Commit

Permalink
renaming: Arch -> H2
Browse files Browse the repository at this point in the history
  • Loading branch information
kazu-yamamoto committed Nov 14, 2023
1 parent aaf977c commit 8c0e236
Show file tree
Hide file tree
Showing 30 changed files with 130 additions and 130 deletions.
35 changes: 0 additions & 35 deletions Network/HTTP2/Arch.hs

This file was deleted.

2 changes: 1 addition & 1 deletion Network/HTTP2/Client.hs
Original file line number Diff line number Diff line change
Expand Up @@ -128,7 +128,7 @@ import Data.IORef (readIORef)
import Network.HTTP.Types

import Network.HPACK
import Network.HTTP2.Arch
import Network.HTTP2.H2
import Network.HTTP2.Client.Run
import Network.HTTP2.Client.Types
import Network.HTTP2.Frame
Expand Down
2 changes: 1 addition & 1 deletion Network/HTTP2/Client/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,6 @@ module Network.HTTP2.Client.Internal (
runIO,
) where

import Network.HTTP2.Arch
import Network.HTTP2.H2
import Network.HTTP2.Client.Run
import Network.HTTP2.Client.Types
2 changes: 1 addition & 1 deletion Network/HTTP2/Client/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ import UnliftIO.Concurrent
import UnliftIO.STM

import Imports
import Network.HTTP2.Arch
import Network.HTTP2.H2
import Network.HTTP2.Client.Types
import Network.HTTP2.Frame

Expand Down
2 changes: 1 addition & 1 deletion Network/HTTP2/Client/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@

module Network.HTTP2.Client.Types where

import Network.HTTP2.Arch
import Network.HTTP2.H2

----------------------------------------------------------------

Expand Down
35 changes: 35 additions & 0 deletions Network/HTTP2/H2.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
module Network.HTTP2.H2 (
module Network.HTTP2.H2.Config,
module Network.HTTP2.H2.Context,
module Network.HTTP2.H2.EncodeFrame,
module Network.HTTP2.H2.File,
module Network.HTTP2.H2.HPACK,
module Network.HTTP2.H2.Manager,
module Network.HTTP2.H2.Queue,
module Network.HTTP2.H2.ReadN,
module Network.HTTP2.H2.Receiver,
module Network.HTTP2.H2.Sender,
module Network.HTTP2.H2.Settings,
module Network.HTTP2.H2.Status,
module Network.HTTP2.H2.Stream,
module Network.HTTP2.H2.StreamTable,
module Network.HTTP2.H2.Types,
module Network.HTTP2.H2.Window,
) where

import Network.HTTP2.H2.Config
import Network.HTTP2.H2.Context
import Network.HTTP2.H2.EncodeFrame
import Network.HTTP2.H2.File
import Network.HTTP2.H2.HPACK
import Network.HTTP2.H2.Manager
import Network.HTTP2.H2.Queue
import Network.HTTP2.H2.ReadN
import Network.HTTP2.H2.Receiver
import Network.HTTP2.H2.Sender
import Network.HTTP2.H2.Settings
import Network.HTTP2.H2.Status
import Network.HTTP2.H2.Stream
import Network.HTTP2.H2.StreamTable
import Network.HTTP2.H2.Types
import Network.HTTP2.H2.Window
6 changes: 3 additions & 3 deletions Network/HTTP2/Arch/Config.hs → Network/HTTP2/H2/Config.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Network.HTTP2.Arch.Config where
module Network.HTTP2.H2.Config where

import Data.ByteString (ByteString)
import Data.IORef
Expand All @@ -8,8 +8,8 @@ import Network.Socket.ByteString (sendAll)
import qualified System.TimeManager as T

import Network.HPACK
import Network.HTTP2.Arch.File
import Network.HTTP2.Arch.ReadN
import Network.HTTP2.H2.File
import Network.HTTP2.H2.ReadN

-- | HTTP/2 configuration.
data Config = Config
Expand Down
10 changes: 5 additions & 5 deletions Network/HTTP2/Arch/Context.hs → Network/HTTP2/H2/Context.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}

module Network.HTTP2.Arch.Context where
module Network.HTTP2.H2.Context where

import Control.Exception
import Data.IORef
Expand All @@ -13,10 +13,10 @@ import UnliftIO.STM

import Imports hiding (insert)
import Network.HPACK
import Network.HTTP2.Arch.Rate
import Network.HTTP2.Arch.Stream
import Network.HTTP2.Arch.StreamTable
import Network.HTTP2.Arch.Types
import Network.HTTP2.H2.Rate
import Network.HTTP2.H2.Stream
import Network.HTTP2.H2.StreamTable
import Network.HTTP2.H2.Types
import Network.HTTP2.Frame

data Role = Client | Server deriving (Eq, Show)
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Network.HTTP2.Arch.EncodeFrame where
module Network.HTTP2.H2.EncodeFrame where

import Network.HTTP2.Frame

Expand Down
2 changes: 1 addition & 1 deletion Network/HTTP2/Arch/File.hs → Network/HTTP2/H2/File.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Network.HTTP2.Arch.File where
module Network.HTTP2.H2.File where

import System.IO

Expand Down
6 changes: 3 additions & 3 deletions Network/HTTP2/Arch/HPACK.hs → Network/HTTP2/H2/HPACK.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}

module Network.HTTP2.Arch.HPACK (
module Network.HTTP2.H2.HPACK (
hpackEncodeHeader,
hpackEncodeHeaderLoop,
hpackDecodeHeader,
Expand All @@ -17,8 +17,8 @@ import qualified Network.HTTP.Types as H
import Imports
import Network.HPACK
import Network.HPACK.Token
import Network.HTTP2.Arch.Context
import Network.HTTP2.Arch.Types
import Network.HTTP2.H2.Context
import Network.HTTP2.H2.Types
import Network.HTTP2.Frame

-- $setup
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@
-- | A thread manager.
-- The manager has responsibility to spawn and kill
-- worker threads.
module Network.HTTP2.Arch.Manager (
module Network.HTTP2.H2.Manager (
Manager,
Action,
start,
Expand Down
6 changes: 3 additions & 3 deletions Network/HTTP2/Arch/Queue.hs → Network/HTTP2/H2/Queue.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,11 @@
{-# LANGUAGE RecordWildCards #-}

module Network.HTTP2.Arch.Queue where
module Network.HTTP2.H2.Queue where

import UnliftIO.STM

import Network.HTTP2.Arch.Manager
import Network.HTTP2.Arch.Types
import Network.HTTP2.H2.Manager
import Network.HTTP2.H2.Types

{-# INLINE forkAndEnqueueWhenReady #-}
forkAndEnqueueWhenReady
Expand Down
2 changes: 1 addition & 1 deletion Network/HTTP2/Arch/Rate.hs → Network/HTTP2/H2/Rate.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Network.HTTP2.Arch.Rate (
module Network.HTTP2.H2.Rate (
Rate,
newRate,
getRate,
Expand Down
2 changes: 1 addition & 1 deletion Network/HTTP2/Arch/ReadN.hs → Network/HTTP2/H2/ReadN.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Network.HTTP2.Arch.ReadN where
module Network.HTTP2.H2.ReadN where

import qualified Data.ByteString as B
import Data.IORef
Expand Down
24 changes: 12 additions & 12 deletions Network/HTTP2/Arch/Receiver.hs → Network/HTTP2/H2/Receiver.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}

module Network.HTTP2.Arch.Receiver (
module Network.HTTP2.H2.Receiver (
frameReceiver,
) where

Expand All @@ -18,17 +18,17 @@ import UnliftIO.STM
import Imports hiding (delete, insert)
import Network.HPACK
import Network.HPACK.Token
import Network.HTTP2.Arch.Config
import Network.HTTP2.Arch.Context
import Network.HTTP2.Arch.EncodeFrame
import Network.HTTP2.Arch.HPACK
import Network.HTTP2.Arch.Queue
import Network.HTTP2.Arch.Rate
import Network.HTTP2.Arch.Settings
import Network.HTTP2.Arch.Stream
import Network.HTTP2.Arch.StreamTable
import Network.HTTP2.Arch.Types
import Network.HTTP2.Arch.Window
import Network.HTTP2.H2.Config
import Network.HTTP2.H2.Context
import Network.HTTP2.H2.EncodeFrame
import Network.HTTP2.H2.HPACK
import Network.HTTP2.H2.Queue
import Network.HTTP2.H2.Rate
import Network.HTTP2.H2.Settings
import Network.HTTP2.H2.Stream
import Network.HTTP2.H2.StreamTable
import Network.HTTP2.H2.Types
import Network.HTTP2.H2.Window
import Network.HTTP2.Frame

----------------------------------------------------------------
Expand Down
24 changes: 12 additions & 12 deletions Network/HTTP2/Arch/Sender.hs → Network/HTTP2/H2/Sender.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Network.HTTP2.Arch.Sender (
module Network.HTTP2.H2.Sender (
frameSender,
fillBuilderBodyGetNext,
fillFileBodyGetNext,
Expand All @@ -23,17 +23,17 @@ import UnliftIO.STM

import Imports
import Network.HPACK (TokenHeaderList, setLimitForEncoding, toHeaderTable)
import Network.HTTP2.Arch.Config
import Network.HTTP2.Arch.Context
import Network.HTTP2.Arch.EncodeFrame
import Network.HTTP2.Arch.File
import Network.HTTP2.Arch.HPACK
import Network.HTTP2.Arch.Manager hiding (start)
import Network.HTTP2.Arch.Queue
import Network.HTTP2.Arch.Settings
import Network.HTTP2.Arch.Stream
import Network.HTTP2.Arch.Types
import Network.HTTP2.Arch.Window
import Network.HTTP2.H2.Config
import Network.HTTP2.H2.Context
import Network.HTTP2.H2.EncodeFrame
import Network.HTTP2.H2.File
import Network.HTTP2.H2.HPACK
import Network.HTTP2.H2.Manager hiding (start)
import Network.HTTP2.H2.Queue
import Network.HTTP2.H2.Settings
import Network.HTTP2.H2.Stream
import Network.HTTP2.H2.Types
import Network.HTTP2.H2.Window
import Network.HTTP2.Frame

----------------------------------------------------------------
Expand Down
12 changes: 6 additions & 6 deletions Network/HTTP2/Arch/Settings.hs → Network/HTTP2/H2/Settings.hs
Original file line number Diff line number Diff line change
@@ -1,17 +1,17 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}

module Network.HTTP2.Arch.Settings where
module Network.HTTP2.H2.Settings where

import Data.IORef
import UnliftIO.STM

import Imports
import Network.HTTP2.Arch.Config
import Network.HTTP2.Arch.Context
import Network.HTTP2.Arch.EncodeFrame
import Network.HTTP2.Arch.StreamTable
import Network.HTTP2.Arch.Types
import Network.HTTP2.H2.Config
import Network.HTTP2.H2.Context
import Network.HTTP2.H2.EncodeFrame
import Network.HTTP2.H2.StreamTable
import Network.HTTP2.H2.Types
import Network.HTTP2.Frame

-- max: 2,147,483,647 (2^31-1) is too large.
Expand Down
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}

module Network.HTTP2.Arch.Status (
module Network.HTTP2.H2.Status (
getStatus,
setStatus,
) where
Expand Down
6 changes: 3 additions & 3 deletions Network/HTTP2/Arch/Stream.hs → Network/HTTP2/H2/Stream.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}

module Network.HTTP2.Arch.Stream where
module Network.HTTP2.H2.Stream where

import Control.Exception
import Control.Monad
Expand All @@ -10,8 +10,8 @@ import Data.Maybe (fromMaybe)
import UnliftIO.Concurrent
import UnliftIO.STM

import Network.HTTP2.Arch.StreamTable
import Network.HTTP2.Arch.Types
import Network.HTTP2.H2.StreamTable
import Network.HTTP2.H2.Types
import Network.HTTP2.Frame

----------------------------------------------------------------
Expand Down
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# LANGUAGE RecordWildCards #-}

module Network.HTTP2.Arch.StreamTable (
module Network.HTTP2.H2.StreamTable (
-- * Types
OddStreamTable,
emptyOddStreamTable,
Expand Down Expand Up @@ -40,7 +40,7 @@ import qualified Data.OrdPSQ as PSQ
import Network.HTTP.Types (Method)

import Imports
import Network.HTTP2.Arch.Types (Stream (..))
import Network.HTTP2.H2.Types (Stream (..))

----------------------------------------------------------------

Expand Down
4 changes: 2 additions & 2 deletions Network/HTTP2/Arch/Types.hs → Network/HTTP2/H2/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}

module Network.HTTP2.Arch.Types where
module Network.HTTP2.H2.Types where

import qualified Control.Exception as E
import Data.ByteString.Builder (Builder)
Expand All @@ -16,7 +16,7 @@ import UnliftIO.STM

import Imports
import Network.HPACK
import Network.HTTP2.Arch.File
import Network.HTTP2.H2.File
import Network.HTTP2.Frame

----------------------------------------------------------------
Expand Down
Loading

0 comments on commit 8c0e236

Please sign in to comment.