Skip to content

Commit

Permalink
Merge pull request #219 from noinia/rename->hgeom
Browse files Browse the repository at this point in the history
Rename new modules not on hackage to HGeometry.<name of module>
  • Loading branch information
noinia authored Nov 20, 2022
2 parents 137ef77 + f39e63b commit ddc7d45
Show file tree
Hide file tree
Showing 39 changed files with 186 additions and 168 deletions.
12 changes: 6 additions & 6 deletions hgeometry-combinatorial/changelog.org
Original file line number Diff line number Diff line change
Expand Up @@ -8,18 +8,18 @@
core-only value of type ~c~ and an ~Ext~.
- Added an ~AsExt~ class that to capture types that can be decomposed
(and recomposed) into an ~Ext~.
- Added ~Data.Ratio.Generalized~ that implements Ratio but supports
- Added ~HGeometry.Number.Ratio.Generalized~ that implements Ratio but supports
types that are not ~Integral~.
- A ~Data.RealNumber.Symbolic~ type that represents numbers with a
- A ~HGeometry.Number.Real.Symbolic~ type that represents numbers with a
symbolic pertubation. Useful for Simulation of Simplicity.
- Dropped the ~CanAquire~ module.
- Explicit export list for ~Data.Permutation~.
- Added the ~Data.Sign~ and ~Data.Indexed~ modules.
- Added the ~HGeometry.Sign~ and ~HGeometry.Indexed~ modules.
- Support mtl 2.3
- Added ~Data.Radical~ for types that support computing square roots.
- Added ~Data.Foldable.Sort~ which has a faster sort implementation
- Added ~HGeometry.Number.Radical~ for types that support computing square roots.
- Added ~HGeometry.Foldable.Sort~ which has a faster sort implementation
(that will take any Foldable and return an Vector.)
- Added ~Data.Cyclic~ and ~Data.Vector.NonEmpty~ modules.
- Added ~HGeometry.Cyclic~ and ~HGeometry.Vector.NonEmpty~ modules.
- Added Uniform and UniformRange instances for ~Ext~.
- Removed ~Data.PlanarGraph.Mutable~, ~Data.PlanarGraph.Persistent~,
and ~Data.PlanarGraph.Immutable~, since they were note used anyway.
Expand Down
2 changes: 1 addition & 1 deletion hgeometry-combinatorial/doctests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,5 +71,5 @@ modules =
, "Data.Double.Approximate"
, "Data.Double.Shaman"

, "Data.RealNumber.Symbolic"
, "HGeometry.Number.Real.Symbolic"
]
25 changes: 16 additions & 9 deletions hgeometry-combinatorial/hgeometry-combinatorial.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -130,11 +130,16 @@ library

-- * Numeric Data Types
Data.RealNumber.Rational
Data.RealNumber.Symbolic


HGeometry.Number.Real.Rational
HGeometry.Number.Real.Symbolic

Data.Double.Approximate
Data.Double.Shaman
Data.Ratio.Generalized
Data.Radical

HGeometry.Number.Ratio.Generalized
HGeometry.Number.Radical

-- * Measurements
Data.Measured
Expand All @@ -146,8 +151,10 @@ library
Data.Intersection
Data.Range
Data.Ext
Data.Sign
Data.Indexed


HGeometry.Sign
HGeometry.Indexed

-- Data.Ext.Multi

Expand Down Expand Up @@ -193,12 +200,12 @@ library

Data.Yaml.Util

Data.Foldable.Sort
Data.Foldable.Util
HGeometry.Foldable.Sort
HGeometry.Foldable.Util

Data.Vector.NonEmpty.Util
HGeometry.Vector.NonEmpty.Util

Data.Cyclic
HGeometry.Cyclic

other-modules: Data.PlanarGraph.Internal
Data.PlanarGraph.Core
Expand Down
94 changes: 2 additions & 92 deletions hgeometry-combinatorial/src/Data/RealNumber/Rational.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,96 +6,6 @@
-- License : see the LICENSE file
-- Maintainer : Frank Staals
--------------------------------------------------------------------------------
module Data.RealNumber.Rational(RealNumber(..)
module Data.RealNumber.Rational(module HGeometry.Number.Real.Rational) where

-- * Converting to and from RealNumber's
, AsFixed(..), asFixed
, toFixed, fromFixed
, Nat
) where

import Data.Aeson
import Data.Data
import Data.Fixed
import Data.Hashable
import Data.List (dropWhileEnd)
import GHC.Generics (Generic (..))
import GHC.TypeLits
import Test.QuickCheck (Arbitrary (..))
import Control.Monad.Random
import Data.Ratio
import Control.DeepSeq

--------------------------------------------------------------------------------

-- | Real Numbers represented using Rational numbers. The number type
-- itself is exact in the sense that we can represent any rational
-- number.
--
-- The parameter, a natural number, represents the precision (in
-- number of decimals behind the period) with which we display the
-- numbers when printing them (using Show).
--
-- If the number cannot be displayed exactly a '~' is printed after
-- the number.
newtype RealNumber (p :: Nat) = RealNumber Rational
deriving (Eq,Ord,Data,Num,Fractional,Real,RealFrac,Generic,Hashable,ToJSON,FromJSON,NFData)

data NatPrec (p :: Nat) = NatPrec

instance KnownNat p => HasResolution (NatPrec p) where
resolution _ = 10 ^ (natVal (NatPrec @p))


instance KnownNat p => Show (RealNumber p) where
showsPrec d r = showParen (d > app_prec && r < 0) $
case asFixed r of
Exact p -> showString (dropWhileEnd (== '.') . dropWhileEnd (== '0') . show $ p)
Lossy p -> shows p . showChar '~'
where
app_prec = 10

instance KnownNat p => Read (RealNumber p) where
readsPrec i = map wrap . readsPrec @(Fixed (NatPrec p)) i
where
wrap (RealNumber . realToFrac -> x,s') = case s' of
'~':s'' -> (x,s'')
_ -> (x,s')

instance KnownNat p => Arbitrary (RealNumber p) where
arbitrary = fromFixed <$> arbitrary


instance Random (RealNumber p) where
-- Generate a random number between a and b with 'maxBound `div` 2 :: Int' discrete increments.
randomR (a,b) = runRand $ do
v <- getRandom
pure $ (b-a)*abs v + a
-- Generate a random number between -1 and +1 with 'maxBound::Int' discrete increments.
random = runRand $ do
v <- getRandom
let fromInt :: Int -> Integer; fromInt = fromIntegral
pure $ RealNumber $ fromInt v % fromInt maxBound

--------------------------------------------------------------------------------



-- | Fixed-precision representation of a 'RealNumber'. If there's insufficient
-- precision to accurately represent the 'RealNumber' then the 'Lossy' constructor
-- will be used.
data AsFixed p = Exact !(Fixed p) | Lossy !(Fixed p) deriving (Show,Eq)

-- | Cast 'RealNumber' to a fixed-precision number. Data is silently lost if there's
-- insufficient precision.
toFixed :: KnownNat p => RealNumber p -> Fixed (NatPrec p)
toFixed = realToFrac

-- | Cast a fixed-precision number to a 'RealNumber'.
fromFixed :: KnownNat p => Fixed (NatPrec p) -> RealNumber p
fromFixed = realToFrac

-- | Cast 'RealNumber' to a fixed-precision number. Data-loss caused by insufficient
-- precision will be marked by the 'Lossy' constructor.
asFixed :: KnownNat p => RealNumber p -> AsFixed (NatPrec p)
asFixed r = let p = toFixed r in if r == fromFixed p then Exact p else Lossy p
import HGeometry.Number.Real.Rational
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE QuantifiedConstraints #-}
module Data.Cyclic
module HGeometry.Cyclic
( Cyclic(..)
, toCircularVector
) where
Expand All @@ -11,11 +11,11 @@ module Data.Cyclic
import Control.DeepSeq (NFData)
import Control.Lens
import qualified Data.Foldable as F
import Data.Foldable.Util
import Data.Semigroup.Foldable
import Data.Vector.Circular (CircularVector(..))
import Data.Vector.NonEmpty (NonEmptyVector)
import GHC.Generics (Generic)
import HGeometry.Foldable.Util
--------------------------------------------------------------------------------

-- | A cyclic sequence type
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Data.Foldable.Sort
module HGeometry.Foldable.Sort
( sortBy
, sort
, sortOnCheap
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Data.Foldable.Util
module HGeometry.Foldable.Util
( HasFromFoldable(..)
, HasFromFoldable1(..)
) where
Expand Down
Original file line number Diff line number Diff line change
@@ -1,15 +1,15 @@
{-# LANGUAGE ScopedTypeVariables #-}
--------------------------------------------------------------------------------
-- |
-- Module : Data.Indexed
-- Module : HGeometry.Indexed
-- Copyright : (C) Frank Staals
-- License : see the LICENSE file
-- Maintainer : Frank Staals
--
-- Things that have an index.
--
--------------------------------------------------------------------------------
module Data.Indexed
module HGeometry.Indexed
( HasIndex(..)
, Index
, WithIndex(..), theValue
Expand Down
Original file line number Diff line number Diff line change
@@ -1,14 +1,14 @@
{-# LANGUAGE DefaultSignatures #-}
--------------------------------------------------------------------------------
-- |
-- Module : Data.Radical
-- Module : HGeometry.Number.Radical
-- Copyright : (C) Frank Staals
-- License : see the LICENSE file
-- Maintainer : Frank Staals
--
-- Types that support computing Square roots
--------------------------------------------------------------------------------
module Data.Radical
module HGeometry.Number.Radical
( Radical(..)
) where

Expand Down
Original file line number Diff line number Diff line change
@@ -1,14 +1,14 @@
--------------------------------------------------------------------------------
-- |
-- Module : Data.Ratio.Generalized
-- Module : HGeometry.Number.Ratio.Generalized
-- Copyright : (C) Frank Staals
-- License : see the LICENSE file
-- Maintainer : Frank Staals
--
-- Generalized Ratio type that accepts arbitrary 'Num a' types rather
-- than just Integral ones as in Data.Ratio
--------------------------------------------------------------------------------
module Data.Ratio.Generalized
module HGeometry.Number.Ratio.Generalized
( GRatio
, (%)
, numerator, denominator
Expand Down
102 changes: 102 additions & 0 deletions hgeometry-combinatorial/src/HGeometry/Number/Real/Rational.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,102 @@
{-# LANGUAGE DeriveDataTypeable #-}
--------------------------------------------------------------------------------
-- |
-- Module : HGeometry.Number.Real.Rational
-- Copyright : (C) Frank Staals
-- License : see the LICENSE file
-- Maintainer : Frank Staals
--------------------------------------------------------------------------------
module HGeometry.Number.Real.Rational(
RealNumber(..)

-- * Converting to and from RealNumber's
, AsFixed(..), asFixed
, toFixed, fromFixed
, Nat
) where

import Control.DeepSeq
import Control.Monad.Random
import Data.Aeson
import Data.Data
import Data.Fixed
import Data.Hashable
import Data.List (dropWhileEnd)
import Data.Ratio
import GHC.Generics (Generic (..))
import GHC.TypeLits
import Test.QuickCheck (Arbitrary (..))

--------------------------------------------------------------------------------

-- | Real Numbers represented using Rational numbers. The number type
-- itself is exact in the sense that we can represent any rational
-- number.
--
-- The parameter, a natural number, represents the precision (in
-- number of decimals behind the period) with which we display the
-- numbers when printing them (using Show).
--
-- If the number cannot be displayed exactly a '~' is printed after
-- the number.
newtype RealNumber (p :: Nat) = RealNumber Rational
deriving (Eq,Ord,Data,Num,Fractional,Real,RealFrac,Generic,Hashable,ToJSON,FromJSON,NFData)

data NatPrec (p :: Nat) = NatPrec

instance KnownNat p => HasResolution (NatPrec p) where
resolution _ = 10 ^ (natVal (NatPrec @p))


instance KnownNat p => Show (RealNumber p) where
showsPrec d r = showParen (d > app_prec && r < 0) $
case asFixed r of
Exact p -> showString (dropWhileEnd (== '.') . dropWhileEnd (== '0') . show $ p)
Lossy p -> shows p . showChar '~'
where
app_prec = 10

instance KnownNat p => Read (RealNumber p) where
readsPrec i = map wrap . readsPrec @(Fixed (NatPrec p)) i
where
wrap (RealNumber . realToFrac -> x,s') = case s' of
'~':s'' -> (x,s'')
_ -> (x,s')

instance KnownNat p => Arbitrary (RealNumber p) where
arbitrary = fromFixed <$> arbitrary


instance Random (RealNumber p) where
-- Generate a random number between a and b with 'maxBound `div` 2 :: Int' discrete increments.
randomR (a,b) = runRand $ do
v <- getRandom
pure $ (b-a)*abs v + a
-- Generate a random number between -1 and +1 with 'maxBound::Int' discrete increments.
random = runRand $ do
v <- getRandom
let fromInt :: Int -> Integer; fromInt = fromIntegral
pure $ RealNumber $ fromInt v % fromInt maxBound

--------------------------------------------------------------------------------



-- | Fixed-precision representation of a 'RealNumber'. If there's insufficient
-- precision to accurately represent the 'RealNumber' then the 'Lossy' constructor
-- will be used.
data AsFixed p = Exact !(Fixed p) | Lossy !(Fixed p) deriving (Show,Eq)

-- | Cast 'RealNumber' to a fixed-precision number. Data is silently lost if there's
-- insufficient precision.
toFixed :: KnownNat p => RealNumber p -> Fixed (NatPrec p)
toFixed = realToFrac

-- | Cast a fixed-precision number to a 'RealNumber'.
fromFixed :: KnownNat p => Fixed (NatPrec p) -> RealNumber p
fromFixed = realToFrac

-- | Cast 'RealNumber' to a fixed-precision number. Data-loss caused by insufficient
-- precision will be marked by the 'Lossy' constructor.
asFixed :: KnownNat p => RealNumber p -> AsFixed (NatPrec p)
asFixed r = let p = toFixed r in if r == fromFixed p then Exact p else Lossy p
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE UndecidableInstances #-}
--------------------------------------------------------------------------------
-- |
-- Module : Data.RealNumber.Symbolic
-- Module : HGeometry.Number.Real.Symbolic
-- Copyright : (C) Frank Staals
-- License : see the LICENSE file
-- Maintainer : Frank Staals
Expand All @@ -19,7 +19,7 @@
--
--
--------------------------------------------------------------------------------
module Data.RealNumber.Symbolic(
module HGeometry.Number.Real.Symbolic(
EpsFold
, eps, mkEpsFold
, evalEps
Expand All @@ -46,8 +46,8 @@ import qualified Data.List as List
import qualified Data.Map.Merge.Strict as Map
import qualified Data.Map.Strict as Map
import Data.Maybe (isNothing)
import Data.Ratio.Generalized (GRatio, (%))
import Data.Sign (Sign(..))
import HGeometry.Number.Ratio.Generalized (GRatio, (%))
import HGeometry.Sign (Sign(..))
import Test.QuickCheck (Arbitrary(..), listOf)
import Test.QuickCheck.Instances ()

Expand Down
Loading

0 comments on commit ddc7d45

Please sign in to comment.