Skip to content

Commit

Permalink
removing unnecessary headers
Browse files Browse the repository at this point in the history
  • Loading branch information
kazu-yamamoto committed Feb 8, 2024
1 parent 005ba34 commit 3120e18
Show file tree
Hide file tree
Showing 32 changed files with 27 additions and 230 deletions.
9 changes: 1 addition & 8 deletions core/Network/TLS/Backend.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,4 @@
-- |
-- Module : Network.TLS.Backend
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
--
-- A Backend represents a unified way to do IO on different
-- | A Backend represents a unified way to do IO on different
-- types without burdening our calling API with multiple
-- ways to initialize a new context.
--
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/Cipher.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,6 @@
{-# LANGUAGE ExistentialQuantification #-}
{-# OPTIONS_HADDOCK hide #-}

-- |
-- Module : Network.TLS.Cipher
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.Cipher (
CipherKeyExchangeType (..),
Bulk (..),
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/Compression.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,6 @@
{-# LANGUAGE ExistentialQuantification #-}
{-# OPTIONS_HADDOCK hide #-}

-- |
-- Module : Network.TLS.Compression
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.Compression (
CompressionC (..),
Compression (..),
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/Credentials.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,5 @@
{-# LANGUAGE CPP #-}

-- |
-- Module : Network.TLS.Credentials
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.Credentials (
Credential,
Credentials (..),
Expand Down
9 changes: 1 addition & 8 deletions core/Network/TLS/ErrT.hs
Original file line number Diff line number Diff line change
@@ -1,13 +1,6 @@
{-# LANGUAGE CPP #-}

-- |
-- Module : Network.TLS.ErrT
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
--
-- a simple compat ErrorT and other error stuff
-- | A simple compat ErrorT and other error stuff
module Network.TLS.ErrT (
runErrT,
ErrT,
Expand Down
9 changes: 1 addition & 8 deletions core/Network/TLS/Extension.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}

-- |
-- Module : Network.TLS.Extension
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
--
-- basic extensions are defined in RFC 6066
-- | Basic extensions are defined in RFC 6066
module Network.TLS.Extension (
Extension (..),
supportedExtensions,
Expand Down
9 changes: 1 addition & 8 deletions core/Network/TLS/Extra.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,4 @@
-- |
-- Module : Network.TLS.Extra
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
--
-- default values and ciphers
-- | Default values and ciphers
module Network.TLS.Extra (
module Network.TLS.Extra.Cipher,
module Network.TLS.Extra.FFDHE,
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/Handshake/Certificate.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,3 @@
-- |
-- Module : Network.TLS.Handshake.Certificate
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.Handshake.Certificate (
certificateRejected,
badCertificate,
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/Handshake/Control.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,3 @@
-- |
-- Module : Network.TLS.Handshake.Control
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.Handshake.Control (
ClientState (..),
ServerState (..),
Expand Down
9 changes: 1 addition & 8 deletions core/Network/TLS/Handshake/Key.hs
Original file line number Diff line number Diff line change
@@ -1,13 +1,6 @@
{-# LANGUAGE FlexibleInstances #-}

-- |
-- Module : Network.TLS.Handshake.Key
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
--
-- functions for RSA operations
-- | Functions for RSA operations
module Network.TLS.Handshake.Key (
encryptRSA,
signPrivate,
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/Handshake/Random.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,5 @@
{-# LANGUAGE PatternGuards #-}

-- |
-- Module : Network.TLS.Handshake.Random
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.Handshake.Random (
serverRandom,
clientRandom,
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/Hooks.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,3 @@
-- |
-- Module : Network.TLS.Context
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.Hooks (
Logging (..),
Hooks (..),
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/IO.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,6 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RankNTypes #-}

-- |
-- Module : Network.TLS.IO
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.IO (
sendPacket12,
sendPacket13,
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/Internal.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,5 @@
{-# OPTIONS_HADDOCK hide #-}

-- |
-- Module : Network.TLS.Internal
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.Internal (
module Network.TLS.Struct,
module Network.TLS.Struct13,
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/KeySchedule.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}

-- |
-- Module : Network.TLS.KeySchedule
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.KeySchedule (
hkdfExtract,
hkdfExpandLabel,
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/MAC.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,3 @@
-- |
-- Module : Network.TLS.MAC
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.MAC (
macSSL,
hmac,
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/Measurement.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,3 @@
-- |
-- Module : Network.TLS.Measurement
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.Measurement (
Measurement (..),
newMeasurement,
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/Packet13.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,6 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}

-- |
-- Module : Network.TLS.Packet13
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.Packet13 (
encodeHandshake13,
decodeHandshakeRecord13,
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/Parameters.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,3 @@
-- |
-- Module : Network.TLS.Parameters
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.Parameters (
ClientParams (..),
ServerParams (..),
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/PostHandshake.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,3 @@
-- |
-- Module : Network.TLS.PostHandshake
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.PostHandshake (
requestCertificate,
requestCertificateServer,
Expand Down
17 changes: 5 additions & 12 deletions core/Network/TLS/Record.hs
Original file line number Diff line number Diff line change
@@ -1,15 +1,8 @@
-- |
-- Module : Network.TLS.Record
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
--
-- The Record Protocol takes messages to be transmitted, fragments the
-- data into manageable blocks, optionally compresses the data, applies
-- a MAC, encrypts, and transmits the result. Received data is
-- decrypted, verified, decompressed, reassembled, and then delivered to
-- higher-level clients.
-- | The Record Protocol takes messages to be transmitted, fragments
-- the data into manageable blocks, optionally compresses the data,
-- applies a MAC, encrypts, and transmits the result. Received data
-- is decrypted, verified, decompressed, reassembled, and then
-- delivered to higher-level clients.
module Network.TLS.Record (
Record (..),

Expand Down
9 changes: 1 addition & 8 deletions core/Network/TLS/Record/Reading.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,4 @@
-- |
-- Module : Network.TLS.Record.Reading
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
--
-- TLS record layer in Rx direction
-- | TLS record layer in Rx direction
module Network.TLS.Record.Reading (
recvRecord,
recvRecord13,
Expand Down
17 changes: 5 additions & 12 deletions core/Network/TLS/Record/Types.hs
Original file line number Diff line number Diff line change
@@ -1,17 +1,10 @@
{-# LANGUAGE EmptyDataDecls #-}

-- |
-- Module : Network.TLS.Record.Types
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
--
-- The Record Protocol takes messages to be transmitted, fragments the
-- data into manageable blocks, optionally compresses the data, applies
-- a MAC, encrypts, and transmits the result. Received data is
-- decrypted, verified, decompressed, reassembled, and then delivered to
-- higher-level clients.
-- | The Record Protocol takes messages to be transmitted, fragments
-- the data into manageable blocks, optionally compresses the data,
-- applies a MAC, encrypts, and transmits the result. Received data
-- is decrypted, verified, decompressed, reassembled, and then
-- delivered to higher-level clients.
module Network.TLS.Record.Types (
Header (..),
ProtocolType (..),
Expand Down
9 changes: 1 addition & 8 deletions core/Network/TLS/Record/Writing.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,4 @@
-- |
-- Module : Network.TLS.Record.Writing
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
--
-- TLS record layer in Tx direction
-- | TLS record layer in Tx direction
module Network.TLS.Record.Writing (
encodeRecord,
encodeRecord13,
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/Session.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,3 @@
-- |
-- Module : Network.TLS.Session
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.Session (
SessionManager (..),
noSessionManager,
Expand Down
12 changes: 3 additions & 9 deletions core/Network/TLS/State.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,15 +3,9 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Rank2Types #-}

-- |
-- Module : Network.TLS.State
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
--
-- the State module contains calls related to state initialization/manipulation
-- which is use by the Receiving module and the Sending module.
-- | the State module contains calls related to state
-- initialization/manipulation which is use by the Receiving module
-- and the Sending module.
module Network.TLS.State (
TLSState (..),
TLSSt,
Expand Down
10 changes: 2 additions & 8 deletions core/Network/TLS/Struct.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,14 +2,8 @@
{-# LANGUAGE PatternSynonyms #-}
{-# OPTIONS_HADDOCK hide #-}

-- |
-- Module : Network.TLS.Struct
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
--
-- the Struct module contains all definitions and values of the TLS protocol
-- | The Struct module contains all definitions and values of the TLS
-- protocol.
module Network.TLS.Struct (
Version (..),
CipherData (..),
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/Struct13.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,3 @@
-- |
-- Module : Network.TLS.Struct13
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.Struct13 (
Packet13 (..),
Handshake13 (..),
Expand Down
6 changes: 0 additions & 6 deletions core/Network/TLS/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,12 +2,6 @@
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE PatternSynonyms #-}

-- |
-- Module : Network.TLS.Types
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
module Network.TLS.Types (
Version (Version, SSL2, SSL3, TLS10, TLS11, TLS12, TLS13),
SessionID,
Expand Down
9 changes: 1 addition & 8 deletions core/Network/TLS/Util/ASN1.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,4 @@
-- |
-- Module : Network.TLS.Util.ASN1
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
--
-- ASN1 utils for TLS
-- | ASN1 utils for TLS
module Network.TLS.Util.ASN1 (
decodeASN1Object,
encodeASN1Object,
Expand Down
Loading

0 comments on commit 3120e18

Please sign in to comment.