Skip to content

Commit

Permalink
bin
Browse files Browse the repository at this point in the history
  • Loading branch information
phadej committed May 22, 2024
1 parent f32fafa commit 68b7c29
Show file tree
Hide file tree
Showing 9 changed files with 10 additions and 78 deletions.
11 changes: 0 additions & 11 deletions bin/src/Data/Bin.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,5 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE Safe #-}

#if __GLASGOW_HASKELL__ < 710
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE StandaloneDeriving #-}
#endif
-- | Binary natural numbers, 'Bin'.
--
-- This module is designed to be imported qualified.
Expand Down Expand Up @@ -81,11 +75,6 @@ data Bin
-- Instances
-------------------------------------------------------------------------------

#if __GLASGOW_HASKELL__ < 710
deriving instance Typeable 'BZ
deriving instance Typeable 'BP
#endif

-- | 'Bin' is printed as 'Natural'.
--
-- To see explicit structure, use 'explicitShow' or 'explicitShowsPrec'
Expand Down
10 changes: 2 additions & 8 deletions bin/src/Data/Bin/Pos.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE EmptyCase #-}
Expand Down Expand Up @@ -36,15 +35,12 @@ import Prelude
import Control.DeepSeq (NFData (..))
import Data.Bin (Bin (..), BinP (..))
import Data.BinP.PosP (PosP (..))
import Data.EqP (EqP (..))
import Data.GADT.Show (GShow (..))
import Data.OrdP (OrdP (..))
import Data.Typeable (Typeable)
import Numeric.Natural (Natural)

#if MIN_VERSION_some(1,0,5)
import Data.EqP (EqP (..))
import Data.OrdP (OrdP (..))
#endif

import qualified Data.BinP.PosP as PP
import qualified Data.Boring as Boring
import qualified Data.Type.Bin as B
Expand Down Expand Up @@ -87,7 +83,6 @@ instance Show (Pos b) where
instance GShow Pos where
gshowsPrec = showsPrec

#if MIN_VERSION_some(1,0,5)
-- |
--
-- >>> eqp (top :: Pos Bin4) (top :: Pos Bin6)
Expand Down Expand Up @@ -115,7 +110,6 @@ instance EqP Pos where
--
instance OrdP Pos where
comparep (Pos x) (Pos y) = comparep x y
#endif

-- |
--
Expand Down
12 changes: 0 additions & 12 deletions bin/src/Data/BinP.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,6 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE Safe #-}

#if __GLASGOW_HASKELL__ < 710
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE StandaloneDeriving #-}
#endif
-- | Positive binary natural numbers, 'BinP'.
--
-- This module is designed to be imported qualified.
Expand Down Expand Up @@ -61,12 +55,6 @@ data BinP
-- Instances
-------------------------------------------------------------------------------

#if __GLASGOW_HASKELL__ < 710
deriving instance Typeable 'BE
deriving instance Typeable 'B0
deriving instance Typeable 'B1
#endif

-- |
--
-- >>> sort [ 1 .. 9 :: BinP ]
Expand Down
14 changes: 4 additions & 10 deletions bin/src/Data/BinP/PosP.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
Expand Down Expand Up @@ -33,23 +32,20 @@ module Data.BinP.PosP (
) where

import Prelude
(Bounded (..), Either (..), Eq (..), Int, Integer, Num, Ord (..), Ordering (..), Show (..), ShowS, String, either,
fmap, fromIntegral, map, showParen, showString, ($), (*), (+), (++), (.))
(Bounded (..), Either (..), Eq (..), Int, Integer, Num, Ord (..), Ordering (..), Show (..), ShowS, String,
either, fmap, fromIntegral, map, showParen, showString, ($), (*), (+), (++), (.))

import Control.DeepSeq (NFData (..))
import Data.Bin (BinP (..))
import Data.EqP (EqP (..))
import Data.GADT.Show (GShow (..))
import Data.Nat (Nat (..))
import Data.OrdP (OrdP (..))
import Data.Proxy (Proxy (..))
import Data.Typeable (Typeable)
import Data.Wrd (Wrd (..))
import Numeric.Natural (Natural)

#if MIN_VERSION_some(1,0,5)
import Data.EqP (EqP (..))
import Data.OrdP (OrdP (..))
#endif

import qualified Data.Bin as B
import qualified Data.Boring as Boring
import qualified Data.Type.Bin as B
Expand Down Expand Up @@ -95,15 +91,13 @@ instance Ord (PosP' n b) where
-- some
-------------------------------------------------------------------------------

#if MIN_VERSION_some(1,0,5)
-- | @since 0.1.3
instance EqP PosP where
eqp x y = toNatural x == toNatural y

-- | @since 0.1.3
instance OrdP PosP where
comparep x y = compare (toNatural x) (toNatural y)
#endif

-------------------------------------------------------------------------------
-- Instances
Expand Down
21 changes: 3 additions & 18 deletions bin/src/Data/Type/Bin.hs
Original file line number Diff line number Diff line change
@@ -1,20 +1,15 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
#if MIN_VERSION_base(4,8,0)
{-# LANGUAGE Safe #-}
#else
{-# LANGUAGE Trustworthy #-}
#endif
-- | Binary natural numbers. @DataKinds@ stuff.
module Data.Type.Bin (
-- * Singleton
Expand Down Expand Up @@ -54,7 +49,8 @@ module Data.Type.Bin (
import Control.DeepSeq (NFData (..))
import Data.Bin (Bin (..), BinP (..))
import Data.Boring (Boring (..))
import Data.GADT.Compare (GEq (..))
import Data.EqP (EqP (..))
import Data.GADT.Compare (GEq (..), defaultEq)
import Data.GADT.DeepSeq (GNFData (..))
import Data.GADT.Show (GShow (..))
import Data.Nat (Nat (..))
Expand All @@ -63,11 +59,6 @@ import Data.Type.BinP (SBinP (..), SBinPI (..))
import Data.Typeable (Typeable)
import Numeric.Natural (Natural)

#if MIN_VERSION_some(1,0,5)
import Data.EqP (EqP (..))
import Data.GADT.Compare (defaultEq)
#endif

import qualified Data.Type.BinP as BP
import qualified Data.Type.Nat as N
import qualified GHC.TypeLits as GHC
Expand Down Expand Up @@ -189,10 +180,6 @@ type family EqBin (n :: Bin) (m :: Bin) where
EqBin ('BP n) ('BP m) = BP.EqBinP n m
EqBin n m = 'False

#if !MIN_VERSION_base(4,11,0)
type instance n == m = EqBin n m
#endif

-------------------------------------------------------------------------------
-- Induction
-------------------------------------------------------------------------------
Expand Down Expand Up @@ -419,10 +406,8 @@ instance Eq (SBin a) where
instance Ord (SBin a) where
compare _ _ = EQ

#if MIN_VERSION_some(1,0,5)
-- | @since 0.1.3
instance EqP SBin where eqp = defaultEq
#endif

-- | @since 0.1.2
instance GShow SBin where
Expand Down
13 changes: 0 additions & 13 deletions bin/src/Data/Type/BinP.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,11 +10,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
#if MIN_VERSION_base(4,8,0)
{-# LANGUAGE Safe #-}
#else
{-# LANGUAGE Trustworthy #-}
#endif
-- | Positive binary natural numbers. @DataKinds@ stuff.
module Data.Type.BinP (
-- * Singleton
Expand Down Expand Up @@ -57,11 +53,8 @@ import Data.Nat (Nat (..))
import Data.Proxy (Proxy (..))
import Data.Typeable (Typeable)
import Numeric.Natural (Natural)

#if MIN_VERSION_some(1,0,5)
import Data.EqP (EqP (..))
import Data.GADT.Compare (defaultEq)
#endif

import qualified Data.Type.Nat as N
import qualified GHC.TypeLits as GHC
Expand Down Expand Up @@ -167,10 +160,6 @@ type family EqBinP (n :: BinP) (m :: BinP) where
EqBinP ('B1 n) ('B1 m) = EqBinP n m
EqBinP n m = 'False

#if !MIN_VERSION_base(4,11,0)
type instance n == m = EqBinP n m
#endif

-------------------------------------------------------------------------------
-- Convert to GHC Nat
-------------------------------------------------------------------------------
Expand Down Expand Up @@ -295,10 +284,8 @@ instance Eq (SBinP a) where
instance Ord (SBinP a) where
compare _ _ = EQ

#if MIN_VERSION_some(1,0,5)
-- | @since 0.1.3
instance EqP SBinP where eqp = defaultEq
#endif

-- | @since 0.1.2
instance GShow SBinP where
Expand Down
4 changes: 0 additions & 4 deletions bin/src/Data/Wrd.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GADTs #-}
Expand Down Expand Up @@ -215,10 +214,7 @@ instance N.SNatI n => I.Bits (Wrd n) where

instance N.SNatI n => I.FiniteBits (Wrd n) where
finiteBitSize _ = N.reflectToNum (Proxy :: Proxy n)

#if MIN_VERSION_base(4,8,0)
countLeadingZeros = countLeadingZeros
#endif

testBit :: Wrd n -> Int -> Bool
testBit w0 i = snd (go 0 w0) where
Expand Down
2 changes: 1 addition & 1 deletion ral-optics/ral-optics.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ library
Data.RAVec.NonEmpty.Optics.Internal

build-depends:
, base >=4.12.0.0 && <4.20
, base >=4.12.0.0 && <4.21
, bin ^>=0.1.4
, fin ^>=0.3.1
, optics-core ^>=0.4.1.1
Expand Down
1 change: 0 additions & 1 deletion vec/vec.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -169,7 +169,6 @@ test-suite inspection
default-language: Haskell2010
build-depends:
, base
, base-compat
, fin
, inspection-testing ^>=0.5.0.3
, tagged
Expand Down

0 comments on commit 68b7c29

Please sign in to comment.