1
Fork 0
mirror of https://github.com/Jaxan/ons-hs.git synced 2025-04-27 22:57:44 +02:00

Moved Support to directory. This way we can choose its representation.

This commit is contained in:
Joshua Moerman 2018-04-09 17:56:52 +02:00
parent 1f0e50898f
commit 72d6310cae
6 changed files with 101 additions and 82 deletions

View file

@ -21,6 +21,9 @@ library
, Orbit.Class , Orbit.Class
, Orbit.Products , Orbit.Products
, Support , Support
, Support.Rat
, Support.OrdList
, Support.Set
build-depends: base >= 4.7 && < 5 build-depends: base >= 4.7 && < 5
, containers , containers
, data-ordlist , data-ordlist

View file

@ -1,85 +1,15 @@
{-# LANGUAGE DeriveGeneric #-} module Support
( module Support
, module Support.OrdList
, module Support.Rat
) where
module Support where import Support.OrdList
import Support.Rat
import qualified Data.List as List -- A support is a set of rational numbers, which can always be ordered. There
import qualified Data.List.Ordered as OrdList -- are several implementations: Ordered Lists, Sets, ...? This module chooses
import GHC.Generics (Generic) -- the implementation. Change the import and export to experiment.
-- We take some model of the dense linear order. The rationals are a natural
-- choice. (Note that every countable model is order-isomorphic, so it doesn't
-- matter so much in the end.) I wrap it in a newtype, so we will only use the
-- Ord instances, and because it's not very nice to work with type synonyms.
-- Show instance included for debugging.
newtype Rat = Rat { unRat :: Rational }
deriving (Eq, Ord, Show, Generic)
-- A support is a set of rational numbers, which can always be ordered. I tried
-- an implementation using Data.Set, it was slower. We could also use Vectors?
-- Note that a sorted list makes sense in many cases, since we do not really
-- need membership queries on this type. Maybe make this into a newtype.
type Support = [Rat] -- always sorted
size :: Support -> Int
size = List.length
null :: Support -> Bool
null = List.null
min :: Support -> Rat
min = List.head
empty :: Support
empty = []
union :: Support -> Support -> Support
union = OrdList.union
singleton :: Rat -> Support
singleton r = [r]
toList :: Support -> Support
toList = id
fromList, fromAscList, fromDistinctAscList :: [Rat] -> Support
fromList = OrdList.nubSort
fromAscList = OrdList.nub
fromDistinctAscList = id
def :: Int -> Support def :: Int -> Support
def n = fromDistinctAscList . fmap (Rat . toRational) $ [1..n] def n = fromDistinctAscList . fmap (Rat . toRational) $ [1..n]
{-
-- The Data.Set implementation
import Data.Set (Set)
import qualified Data.Set as Set
type Support = Set Rat
size :: Support -> Int
size = Set.size
null :: Support -> Bool
null = Set.null
min :: Support -> Rat
min = Set.findMin
empty :: Support
empty = Set.empty
union :: Support -> Support -> Support
union = Set.union
singleton :: Rat -> Support
singleton = Set.singleton
toList :: Support -> [Rat]
toList = Set.toAscList
fromList, fromAscList, fromDistinctAscList :: [Rat] -> Support
fromList = Set.fromList
fromAscList = Set.fromAscList
fromDistinctAscList = Set.fromDistinctAscList
-}

36
src/Support/OrdList.hs Normal file
View file

@ -0,0 +1,36 @@
module Support.OrdList where
import qualified Data.List as List
import qualified Data.List.Ordered as OrdList
import Support.Rat
-- always sorted
newtype Support = Support { unSupport :: [Rat] }
deriving (Show, Eq, Ord)
size :: Support -> Int
size = List.length . unSupport
null :: Support -> Bool
null = List.null . unSupport
min :: Support -> Rat
min = List.head . unSupport
empty :: Support
empty = Support []
union :: Support -> Support -> Support
union (Support x) (Support y) = Support (OrdList.union x y)
singleton :: Rat -> Support
singleton r = Support [r]
toList :: Support -> [Rat]
toList = unSupport
fromList, fromAscList, fromDistinctAscList :: [Rat] -> Support
fromList = Support . OrdList.nubSort
fromAscList = Support . OrdList.nub
fromDistinctAscList = Support

13
src/Support/Rat.hs Normal file
View file

@ -0,0 +1,13 @@
{-# LANGUAGE DeriveGeneric #-}
module Support.Rat where
import GHC.Generics (Generic)
-- We take some model of the dense linear order. The rationals are a natural
-- choice. (Note that every countable model is order-isomorphic, so it doesn't
-- matter so much in the end.) I wrap it in a newtype, so we will only use the
-- Ord instances, and because it's not very nice to work with type synonyms.
-- Show instance included for debugging.
newtype Rat = Rat { unRat :: Rational }
deriving (Eq, Ord, Show, Generic)

37
src/Support/Set.hs Normal file
View file

@ -0,0 +1,37 @@
module Support.Set where
import Data.Set (Set)
import qualified Data.Set as Set
import Support.Rat
-- Tree-based ordered set
newtype Support = Support { unSupport :: Set Rat }
size :: Support -> Int
size = Set.size . unSupport
null :: Support -> Bool
null = Set.null . unSupport
min :: Support -> Rat
min = Set.findMin . unSupport
empty :: Support
empty = Support Set.empty
union :: Support -> Support -> Support
union (Support x) (Support y) = Support (Set.union x y)
singleton :: Rat -> Support
singleton = Support . Set.singleton
toList :: Support -> [Rat]
toList = Set.toAscList . unSupport
fromList, fromAscList, fromDistinctAscList :: [Rat] -> Support
fromList = Support . Set.fromList
fromAscList = Support . Set.fromAscList
fromDistinctAscList = Support . Set.fromDistinctAscList

View file

@ -15,7 +15,7 @@
# resolver: # resolver:
# name: custom-snapshot # name: custom-snapshot
# location: "./custom-snapshot.yaml" # location: "./custom-snapshot.yaml"
resolver: lts-10.5 resolver: lts-11.0
# User packages to be built. # User packages to be built.
# Various formats can be used as shown in the example below. # Various formats can be used as shown in the example below.