Skip to content

Commit

Permalink
Fixes for cardano-ledger
Browse files Browse the repository at this point in the history
  • Loading branch information
erikd committed May 14, 2024
1 parent 43909a1 commit bfe309b
Showing 1 changed file with 24 additions and 11 deletions.
35 changes: 24 additions & 11 deletions cardano-prelude/src/Cardano/Prelude/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,19 +2,18 @@
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE Safe #-}

module Cardano.Prelude.Base (
module X,
HasLength (..),
identity,
length,
panic,
putTextLn,
scanl',
Cardano.Prelude.Base.length,
#if __GLASGOW_HASKELL__ >= 906
type (~)
#endif
)
where

Expand All @@ -28,33 +27,44 @@ import Control.Category qualified as Category
import Control.Category as X hiding (id)
import Numeric.Natural as X

import Control.Applicative as X (many)
import Control.Applicative as X (Applicative (..), many)
import Control.Concurrent.MVar as X (MVar, newMVar)
import Control.DeepSeq as X (NFData (..), ($!!), force)
import Control.Exception as X (Exception, bracket)
import Control.Monad as X (liftM, unless)
import Control.Monad as X (Monad, (=<<), (>>=), liftM, return, unless)
import Control.Monad.Except as X (MonadError, throwError)
import Control.Monad.IO.Class as X (MonadIO (..))
import Data.ByteString as X (ByteString)
import Data.Bifunctor as X (first)
import Data.Either as X (Either (..))
import Data.Foldable as X (Foldable)
import Data.Functor as X (Functor (..), (<$>))
import Data.Functor.Identity as X (Identity, runIdentity)
import Data.Int as X (Int8, Int16, Int32, Int64)
import Data.Int as X (Int, Int8, Int16, Int32, Int64)
import Data.Kind as X (Type)
import Data.Ord as X (Ord (..), comparing)
import Data.List as X (sortBy)
import Data.List.NonEmpty as X (NonEmpty (..), nonEmpty)
import Data.Maybe as X (catMaybes)
import Data.Maybe as X (Maybe (..), catMaybes)
import Data.Monoid as X (Monoid (..))
import Data.Proxy as X (Proxy (..))
import Data.Ratio as X ((%), denominator, numerator)
import Data.Semigroup as X (Semigroup (..), Any, diff)
import Data.Typeable as X (Typeable, typeRep)
import Data.Word as X (Word8, Word16, Word32, Word64)
import Data.Word as X (Word, Word8, Word16, Word32, Word64)
import Foreign.Ptr as X (Ptr)
import GHC.Generics as X (Generic)
import GHC.Stack as X
import Prelude as X (Eq (..), Integer, Num (..), Read, Show (..), type (~), ($), fromIntegral, fst,
otherwise, rem, snd)
import System.Exit as X
import System.IO as X (Handle, stderr, stdout)
import System.IO as X (Handle, IO, stderr, stdout)
import Text.Read as X (readEither)

-- Need to import this qualifed so we can redefine `length` below.
import qualified Data.Foldable as Foldable
import Prelude qualified as Prelude

-- | Rename `id` to `identity` to allow `id` as a variable name
identity :: Category cat => cat a a
identity = Category.id
Expand All @@ -72,8 +82,11 @@ instance HasLength Text where
length' = Text.length

instance Foldable t => HasLength (t a) where
length' = Prelude.length
length' = Foldable.length

-- | We can pass several things here, as long as they have length.
length :: HasLength a => a -> Int
length = length'

panic :: Text -> a
panic = Prelude.error . Text.unpack

0 comments on commit bfe309b

Please sign in to comment.