Skip to content
Snippets Groups Projects
Commit 8f3af33e authored by Ryan Scott's avatar Ryan Scott
Browse files

Add data-r-tree, obdd, tpdb patches

parent 4bc62a23
No related branches found
No related tags found
No related merge requests found
diff --git a/Data/RTree/Base.hs b/Data/RTree/Base.hs
index 36c041b..9df462f 100644
--- a/Data/RTree/Base.hs
+++ b/Data/RTree/Base.hs
@@ -83,11 +83,11 @@ import Prelude hiding (length, lookup, map, null)
import Data.RTree.MBB hiding (mbb)
data RTree a =
- Node4 {getMBB :: {-# UNPACK #-} ! MBB, getC1 :: ! (RTree a), getC2 :: ! (RTree a), getC3 :: ! (RTree a), getC4 :: ! (RTree a) }
- | Node3 {getMBB :: {-# UNPACK #-} ! MBB, getC1 :: ! (RTree a), getC2 :: ! (RTree a), getC3 :: ! (RTree a) }
- | Node2 {getMBB :: {-# UNPACK #-} ! MBB, getC1 :: ! (RTree a), getC2 :: ! (RTree a) }
+ Node4 {getMBB :: {-# UNPACK #-} !MBB, getC1 :: !(RTree a), getC2 :: !(RTree a), getC3 :: !(RTree a), getC4 :: !(RTree a) }
+ | Node3 {getMBB :: {-# UNPACK #-} !MBB, getC1 :: !(RTree a), getC2 :: !(RTree a), getC3 :: !(RTree a) }
+ | Node2 {getMBB :: {-# UNPACK #-} !MBB, getC1 :: !(RTree a), getC2 :: !(RTree a) }
| Node {getMBB :: MBB, getChildren' :: [RTree a] }
- | Leaf {getMBB :: {-# UNPACK #-} ! MBB, getElem :: a}
+ | Leaf {getMBB :: {-# UNPACK #-} !MBB, getElem :: a}
| Empty
deriving (Show, Eq, Typeable, Generic, Functor)
diff --git a/Data/RTree/MBB.hs b/Data/RTree/MBB.hs
index 03548dd..209cc7d 100644
--- a/Data/RTree/MBB.hs
+++ b/Data/RTree/MBB.hs
@@ -34,7 +34,7 @@ import Data.Binary
import GHC.Generics (Generic)
-- | Minimal bounding box
-data MBB = MBB {getUlx :: {-# UNPACK #-} ! Double, getUly :: {-# UNPACK #-} ! Double, getBrx :: {-# UNPACK #-} ! Double, getBry :: {-# UNPACK #-} ! Double}
+data MBB = MBB {getUlx :: {-# UNPACK #-} !Double, getUly :: {-# UNPACK #-} !Double, getBrx :: {-# UNPACK #-} !Double, getBry :: {-# UNPACK #-} !Double}
deriving (Eq, Generic, Ord)
-- | created a minimal bounding box (or a rectangle)
diff --git a/src/OBDD/Data.hs b/src/OBDD/Data.hs
index 6484d78..da9df16 100644
--- a/src/OBDD/Data.hs
+++ b/src/OBDD/Data.hs
@@ -72,8 +72,8 @@ data OBDD v = OBDD
-- , icore :: !(Map ( Node v Index ) Index)
, icore :: !(VarIntIntMap v Index)
- , ifalse :: ! Index
- , itrue :: ! Index
+ , ifalse :: !Index
+ , itrue :: !Index
, next :: !Index
, top :: !Index
}
diff --git a/src/TPDB/Data.hs b/src/TPDB/Data.hs
index 2d4b88e..4a6dfd5 100644
--- a/src/TPDB/Data.hs
+++ b/src/TPDB/Data.hs
@@ -32,8 +32,8 @@ import qualified Data.Text as T
import qualified Data.Set as S
data Identifier =
- Identifier { _identifier_hash :: ! Int
- , name :: ! T.Text
+ Identifier { _identifier_hash :: !Int
+ , name :: !T.Text
, arity :: Int
}
deriving ( Eq, Ord, Typeable )
diff --git a/src/TPDB/XTC/Read.hs b/src/TPDB/XTC/Read.hs
index ff0c889..482df5f 100644
--- a/src/TPDB/XTC/Read.hs
+++ b/src/TPDB/XTC/Read.hs
@@ -35,11 +35,11 @@ readProblemT t = case ( getProblem . fromDocument ) <$> Text.XML.parseText Text.
getProblem :: Cursor -> [ Problem Identifier Identifier ]
getProblem = element "problem" >=> \ c -> do
- let ! ty = case c $| attribute "type" of
+ let !ty = case c $| attribute "type" of
[ "termination" ] -> Termination
[ "complexity" ] -> Complexity
_ -> error "type"
- let ! st = case c $/ element "strategy" &/ content of
+ let !st = case c $/ element "strategy" &/ content of
[ "FULL" ] -> Just Full
[ "INNERMOST" ] -> Just Innermost
[ "OUTERMOST" ] -> Just Outermost
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment