-
Notifications
You must be signed in to change notification settings - Fork 0
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Refactor, and major restructuring of package layout.
- Loading branch information
Showing
24 changed files
with
220 additions
and
187 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
|
@@ -6,3 +6,6 @@ cabal-dev | |
*.chi | ||
*.chs.h | ||
tests/Properties | ||
tests/Test | ||
tests/Test.* | ||
TODO.txt |
This file was deleted.
Oops, something went wrong.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
|
@@ -5,7 +5,7 @@ | |
-- Maintainer : Anders Claesson <[email protected]> | ||
-- | ||
|
||
module Math.Sym | ||
module Sym | ||
( | ||
Permutation(..) | ||
, perms | ||
|
@@ -14,12 +14,12 @@ module Math.Sym | |
) where | ||
|
||
import Data.Ord | ||
import Data.SSYT (SSYTPair (..)) | ||
import qualified Data.SSYT as Y | ||
import Sym.Perm.SSYT (SSYTPair (..)) | ||
import qualified Sym.Perm.SSYT as Y | ||
import Data.List | ||
import Math.Perm (Perm) | ||
import qualified Math.Perm as P | ||
import qualified Math.Perm.D8 as D8 | ||
import Sym.Perm.Meta (Perm) | ||
import qualified Sym.Perm.Meta as P | ||
import qualified Sym.Perm.D8 as D8 | ||
|
||
|
||
-- The permutation typeclass | ||
|
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -1,4 +1,4 @@ | ||
module Data.Size (Size (..)) where | ||
module Sym.Internal.Size (Size (..)) where | ||
|
||
import qualified Data.Set as Set | ||
|
||
|
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
|
@@ -5,65 +5,21 @@ | |
-- Maintainer : Anders Claesson <[email protected]> | ||
-- | ||
|
||
module Data.Perm.Internal | ||
module Sym.Internal.SubSeq | ||
( | ||
Set | ||
, normalize | ||
, subsets | ||
, minima | ||
, maxima | ||
, powerset | ||
, kSubsets | ||
module Sym.Internal.CLongArray | ||
, SubSeq | ||
, choose | ||
) where | ||
|
||
import Data.List | ||
import Data.Ord | ||
import qualified Data.Set as S | ||
import Data.CLongArray | ||
import Sym.Internal.CLongArray | ||
import Foreign | ||
import Foreign.C.Types | ||
import System.IO.Unsafe | ||
|
||
|
||
-- | A set is represented by an increasing array of non-negative | ||
-- | A SubSeq is represented by an increasing array of non-negative | ||
-- integers. | ||
type Set = CLongArray | ||
|
||
|
||
-- Utils | ||
-- ----- | ||
|
||
-- | Sort and remove duplicates. | ||
normalize :: Ord a => [a] -> [a] | ||
normalize = map head . group . sort | ||
|
||
-- | The set of minimal elements with respect to inclusion. | ||
minima :: Ord a => [S.Set a] -> [S.Set a] | ||
minima = minima' . sortBy (comparing S.size) | ||
where | ||
minima' [] = [] | ||
minima' (x:xs) = x : minima' [ y | y<-xs, not (S.isSubsetOf x y) ] | ||
|
||
-- | The set of maximal elements with respect to the given order. | ||
maxima :: Ord a => [S.Set a] -> [S.Set a] | ||
maxima = maxima' . sortBy (comparing $ \x -> -S.size x) | ||
where | ||
maxima' [] = [] | ||
maxima' (x:xs) = x : maxima' [ y | y<-xs, not (S.isSubsetOf y x) ] | ||
|
||
kSubsets :: Ord a => Int -> S.Set a -> [S.Set a] | ||
kSubsets 0 _ = [ S.empty ] | ||
kSubsets k s = if S.null s | ||
then [] | ||
else let (x, t) = S.deleteFindMin s | ||
in kSubsets k t ++ map (S.insert x) (kSubsets (k-1) t) | ||
|
||
powerset :: Ord a => S.Set a -> [S.Set a] | ||
powerset s = if S.null s | ||
then [s] | ||
else let (x, t) = S.deleteFindMin s | ||
ts = powerset t | ||
in ts ++ map (S.insert x) ts | ||
type SubSeq = CLongArray | ||
|
||
-- Bitmasks | ||
-- -------- | ||
|
@@ -73,12 +29,12 @@ class (Bits a, Integral a) => Bitmask a where | |
-- | Lexicographically, the next bitmask with the same Hamming weight. | ||
next :: a -> a | ||
|
||
-- | @ones k m@ is the set of indices whose bits are set in | ||
-- @m@. Default implementation: | ||
-- | @ones k m@ is the set / subsequence of indices whose bits are | ||
-- set in @m@. Default implementation: | ||
-- | ||
-- > ones m = fromListN (popCount m) $ filter (testBit m) [0..] | ||
-- | ||
ones :: a -> CLongArray | ||
ones :: a -> SubSeq | ||
ones m = fromList . take (popCount m) $ filter (testBit m) [0..] | ||
|
||
instance Bitmask CLong where | ||
|
@@ -97,10 +53,10 @@ bitmasks n k = take binomial (iterate next ((1 `shiftL` k) - 1)) | |
k' = toInteger k | ||
binomial = fromIntegral $ product [n', n'-1 .. n'-k'+1] `div` product [1..k'] | ||
|
||
-- | @subsets n k@ is the list of subsets of @[0..n-1]@ with @k@ | ||
-- | @n \`choose\` k@ is the list of subsequences of @[0..n-1]@ with @k@ | ||
-- elements. | ||
subsets :: Int -> Int -> [Set] | ||
subsets n k | ||
choose :: Int -> Int -> [SubSeq] | ||
choose n k | ||
| n <= 32 = map ones (bitmasks n k :: [CLong]) | ||
| otherwise = map ones (bitmasks n k :: [Integer]) | ||
|
||
|
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,53 @@ | ||
-- | | ||
-- Copyright : Anders Claesson 2014 | ||
-- Maintainer : Anders Claesson <[email protected]> | ||
-- | ||
|
||
module Sym.Internal.Util | ||
( | ||
minima | ||
, maxima | ||
, kSubsets | ||
, powerset | ||
, nubSort | ||
) where | ||
|
||
import Data.List | ||
import Data.Ord | ||
import Data.Set (Set) | ||
import qualified Data.Set as S | ||
|
||
-- | The set of minimal elements with respect to inclusion. | ||
minima :: Ord a => [Set a] -> [Set a] | ||
minima = minima' . sortBy (comparing S.size) | ||
where | ||
minima' [] = [] | ||
minima' (x:xs) = x : minima' [ y | y<-xs, not (x `S.isSubsetOf` y) ] | ||
|
||
-- | The set of maximal elements with respect to the given order. | ||
maxima :: Ord a => [Set a] -> [Set a] | ||
maxima = maxima' . sortBy (comparing $ \x -> -S.size x) | ||
where | ||
maxima' [] = [] | ||
maxima' (x:xs) = x : maxima' [ y | y<-xs, not (y `S.isSubsetOf` x) ] | ||
|
||
-- | A list of all k element subsets of the given set. | ||
kSubsets :: Ord a => Int -> Set a -> [Set a] | ||
kSubsets 0 _ = [ S.empty ] | ||
kSubsets k s | ||
| S.null s = [] | ||
| otherwise = kSubsets k t ++ map (S.insert x) (kSubsets (k-1) t) | ||
where | ||
(x,t) = S.deleteFindMin s | ||
|
||
-- | A list of all subsets of the given set. | ||
powerset :: Ord a => Set a -> [Set a] | ||
powerset s | ||
| S.null s = [s] | ||
| otherwise = ts ++ map (S.insert x) ts | ||
where | ||
(x,t) = S.deleteFindMin s; ts = powerset t | ||
|
||
-- | Sort and remove duplicates. | ||
nubSort :: Ord a => [a] -> [a] | ||
nubSort = map head . group . sort |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
|
@@ -5,13 +5,13 @@ | |
-- Maintainer : Anders Claesson <[email protected]> | ||
-- | ||
|
||
module Math.Perm.Bijection | ||
module Sym.Perm.Bijection | ||
( | ||
simionSchmidt | ||
, simionSchmidt' | ||
) where | ||
|
||
import Data.Perm | ||
import Sym.Perm | ||
import Foreign | ||
import Foreign.C.Types | ||
import System.IO.Unsafe | ||
|
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
|
@@ -3,7 +3,7 @@ | |
-- Maintainer : Anders Claesson <[email protected]> | ||
-- | ||
|
||
module Math.Perm.Class | ||
module Sym.Perm.Class | ||
( | ||
inc | ||
, dec | ||
|
@@ -32,12 +32,12 @@ module Math.Perm.Class | |
, fibonacci | ||
) where | ||
|
||
import Data.Perm | ||
import Math.Perm.Bijection | ||
import Math.Perm.Constructions | ||
import Data.Perm.Internal | ||
import Math.Perm.Pattern | ||
import qualified Math.Perm.D8 as D8 | ||
import Sym.Internal.Util | ||
import Sym.Perm | ||
import Sym.Perm.Bijection | ||
import Sym.Perm.Constructions | ||
import Sym.Perm.Pattern | ||
import qualified Sym.Perm.D8 as D8 | ||
|
||
-- | The class of increasing permutations. | ||
inc :: Int -> [Perm] | ||
|
@@ -137,7 +137,7 @@ lt :: Int -> [Perm] | |
lt = map D8.reverse . gt | ||
|
||
union :: [Int -> [Perm]] -> Int -> [Perm] | ||
union cs n = normalize $ concat [ c n | c <- cs ] | ||
union cs n = nubSort $ concat [ c n | c <- cs ] | ||
|
||
-- | The union of 'vee', 'caret', 'gt' and 'lt'. | ||
wedges :: Int -> [Perm] | ||
|
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Oops, something went wrong.