Skip to content

Commit

Permalink
Common.hs: avoid using Opt.auto to avoid overflows going silent
Browse files Browse the repository at this point in the history
  • Loading branch information
smelc committed Aug 20, 2024
1 parent abe9d0f commit fdeb30d
Showing 1 changed file with 19 additions and 1 deletion.
20 changes: 19 additions & 1 deletion cardano-cli/src/Cardano/CLI/EraBased/Options/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

{- HLINT ignore "Move brackets to avoid $" -}
{- HLINT ignore "Use <$>" -}
Expand All @@ -28,9 +29,11 @@ import qualified Ouroboros.Network.Protocol.LocalStateQuery.Type as Consensus
import Control.Monad (mfilter)
import qualified Data.Aeson as Aeson
import Data.Bifunctor
import Data.Bits (Bits, toIntegralSized)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Base16 as B16
import qualified Data.ByteString.Char8 as BSC
import Data.Data (Proxy (..), Typeable, typeRep)
import Data.Foldable
import Data.Functor (($>))
import qualified Data.IP as IP
Expand Down Expand Up @@ -3180,9 +3183,24 @@ pMaxTransactionSize =
, Opt.help "Maximum transaction size."
]

-- | @integralReader@ is a reader for a word of type @a@. When it fails
-- parsing, it provides a nice error message. This custom reader is needed
-- to avoid the overflow issues of 'Opt.auto' described in https://github.com/IntersectMBO/cardano-cli/issues/860.
integralReader :: forall a. (Typeable a, Integral a, Bits a) => ReadM a
integralReader =
readerFromParsecParser parsecParser
where
parsecParser :: Parsec.Parser a
parsecParser = do
i <- decimal
case toIntegralSized i of
Nothing -> fail $ "Cannot parse " <> show i <> " as a " <> typeName
Just n -> return n
typeName = show $ typeRep (Proxy @a)

pMaxBlockHeaderSize :: Parser Word16
pMaxBlockHeaderSize =
Opt.option Opt.auto $
Opt.option integralReader $
mconcat
[ Opt.long "max-block-header-size"
, Opt.metavar "WORD16"
Expand Down

0 comments on commit fdeb30d

Please sign in to comment.