Skip to content

Commit

Permalink
removing a warning
Browse files Browse the repository at this point in the history
  • Loading branch information
kazu-yamamoto committed Sep 10, 2024
1 parent fd84ce0 commit aa7fd99
Showing 1 changed file with 8 additions and 6 deletions.
14 changes: 8 additions & 6 deletions Network/HPACK/Table/RevIndex.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,8 @@ import qualified Data.Array as A
import Data.Array.Base (unsafeAt)
import Data.Function (on)
import Data.IORef
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.List.NonEmpty as NE
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
import Network.HTTP.Semantics
Expand Down Expand Up @@ -64,15 +66,15 @@ staticRevIndex = A.array (minTokenIx, maxStaticTokenIx) $ map toEnt zs
toEnt (k, xs) = (tokenIx $ toToken $ foldedCase k, m)
where
m = case xs of
[] -> error "staticRevIndex"
[("", i)] -> StaticEntry i Nothing
(_, i) : _ ->
let vs = M.fromList xs
("", i) :| [] -> StaticEntry i Nothing
(_, i) :| _ ->
let vs = M.fromList $ NE.toList xs
in StaticEntry i (Just vs)
zs = map extract $ groupBy ((==) `on` fst) lst
zs = map extract $ NE.groupBy ((==) `on` fst) lst
where
lst = zipWith (\(k, v) i -> (k, (v, i))) staticTableList $ map SIndex [1 ..]
extract xs = (fst (head xs), map snd xs)

extract xs = (fst (NE.head xs), NE.map snd xs)

{-# INLINE lookupStaticRevIndex #-}
lookupStaticRevIndex
Expand Down

0 comments on commit aa7fd99

Please sign in to comment.