Skip to content

Commit

Permalink
Remove dependence on Data.Data.
Browse files Browse the repository at this point in the history
  • Loading branch information
leepike committed May 25, 2012
1 parent 533603f commit 1aedbcb
Show file tree
Hide file tree
Showing 5 changed files with 17 additions and 21 deletions.
3 changes: 1 addition & 2 deletions examples/Div0.hs
Expand Up @@ -8,14 +8,13 @@ module Div0 where
import Test.QuickCheck import Test.QuickCheck
import Test.SmartCheck import Test.SmartCheck
import Control.Monad import Control.Monad
import Data.Data


import GHC.Generics import GHC.Generics


data M = C Int data M = C Int
| A M M | A M M
| D M M | D M M
deriving (Read, Show, Data, Typeable, Generic) deriving (Read, Show, Typeable, Generic)


instance SubTypes M instance SubTypes M


Expand Down
14 changes: 6 additions & 8 deletions examples/Heap_Program.hs
Expand Up @@ -18,7 +18,6 @@ import Data.List
) )


import qualified Data.Tree as T import qualified Data.Tree as T
import Data.Data
import GHC.Generics import GHC.Generics


import qualified Test.SmartCheck as SC import qualified Test.SmartCheck as SC
Expand All @@ -31,19 +30,18 @@ import qualified Test.SmartCheck as SC
instance Read OrdA where instance Read OrdA where
readsPrec _ i = [ (OrdA j, str) | (j, str) <- reads i ] readsPrec _ i = [ (OrdA j, str) | (j, str) <- reads i ]


deriving instance Data OrdA
deriving instance Typeable OrdA deriving instance Typeable OrdA
deriving instance Generic OrdA deriving instance Generic OrdA


heapProgramTest :: IO () heapProgramTest :: IO ()
heapProgramTest = SC.smartCheck SC.scStdArgs (\h -> property (prop_ToSortedList h)) heapProgramTest = SC.smartCheck SC.scStdArgs (\h -> property (prop_ToSortedList h))


instance SC.SubTypes OrdA instance SC.SubTypes OrdA
instance (SC.SubTypes a, Ord a, Arbitrary a, Data a, Generic a) instance (SC.SubTypes a, Ord a, Arbitrary a, Generic a)
=> SC.SubTypes (Heap a) => SC.SubTypes (Heap a)
instance (SC.SubTypes a, Arbitrary a, Data a, Generic a) instance (SC.SubTypes a, Arbitrary a, Generic a)
=> SC.SubTypes (HeapP a) => SC.SubTypes (HeapP a)
instance (SC.SubTypes a, Ord a, Arbitrary a, Data a, Generic a) instance (SC.SubTypes a, Ord a, Arbitrary a, Generic a)
=> SC.SubTypes (HeapPP a) => SC.SubTypes (HeapPP a)


-- instance (Ord a, Arbitrary a, Data a, Show a) => SC.SubTypes (Heap a) where -- instance (Ord a, Arbitrary a, Data a, Show a) => SC.SubTypes (Heap a) where
Expand Down Expand Up @@ -85,7 +83,7 @@ instance (Ord a, Arbitrary a) => Arbitrary (Heap a) where
data Heap a data Heap a
= Node a (Heap a) (Heap a) = Node a (Heap a) (Heap a)
| Nil | Nil
deriving ( Eq, Ord, Show, Read, Data, Typeable, Generic ) deriving ( Eq, Ord, Show, Read, Typeable, Generic )


empty :: Heap a empty :: Heap a
empty = Nil empty = Nil
Expand Down Expand Up @@ -147,7 +145,7 @@ data HeapP a
| SafeRemoveMin (HeapP a) | SafeRemoveMin (HeapP a)
| Merge (HeapP a) (HeapP a) | Merge (HeapP a) (HeapP a)
| FromList [a] | FromList [a]
deriving ( Show, Read, Data, Typeable, Generic ) deriving ( Show, Read, Typeable, Generic )


heap :: Ord a => HeapP a -> Heap a heap :: Ord a => HeapP a -> Heap a
heap Empty = empty heap Empty = empty
Expand Down Expand Up @@ -197,7 +195,7 @@ instance Arbitrary a => Arbitrary (HeapP a) where
-- shrink _ = [] -- shrink _ = []


data HeapPP a = HeapPP (HeapP a) (Heap a) data HeapPP a = HeapPP (HeapP a) (Heap a)
deriving ( Show, Read, Data, Typeable, Generic ) deriving ( Show, Read, Typeable, Generic )


instance (Ord a, Arbitrary a) => Arbitrary (HeapPP a) where instance (Ord a, Arbitrary a) => Arbitrary (HeapPP a) where
arbitrary = arbitrary =
Expand Down
7 changes: 4 additions & 3 deletions examples/LambdaCalc.hs
Expand Up @@ -7,7 +7,8 @@ module LambdaCalc where


import Data.List import Data.List
import Data.Tree import Data.Tree
import Data.Data import Data.Typeable

import Control.Monad import Control.Monad
import GHC.Generics import GHC.Generics


Expand All @@ -21,7 +22,7 @@ data Expr
= Var Sym = Var Sym
| App Expr Expr | App Expr Expr
| Lam Sym Expr | Lam Sym Expr
deriving (Eq, Read, Show, Data, Typeable, Generic) deriving (Eq, Read, Show, Typeable, Generic)


freeVars :: Expr -> [Sym] freeVars :: Expr -> [Sym]
freeVars (Var s) = [s] freeVars (Var s) = [s]
Expand Down Expand Up @@ -84,7 +85,7 @@ instance SubTypes Pr
--------------------------------------------------------------------------------- ---------------------------------------------------------------------------------


data Pr = Pr Expr Expr data Pr = Pr Expr Expr
deriving (Read, Show, Data, Typeable, Generic) deriving (Read, Show, Typeable, Generic)


instance Arbitrary Expr where instance Arbitrary Expr where
arbitrary = sized mkE arbitrary = sized mkE
Expand Down
5 changes: 2 additions & 3 deletions examples/MutualRecData.hs
Expand Up @@ -8,7 +8,6 @@ import Test.SmartCheck
import Test.QuickCheck hiding (Result) import Test.QuickCheck hiding (Result)


import Data.Tree import Data.Tree
import Data.Data
import Control.Monad.State import Control.Monad.State


import GHC.Generics import GHC.Generics
Expand All @@ -17,12 +16,12 @@ import GHC.Generics


data M = M N N Int data M = M N N Int
| P | P
deriving (Data, Typeable, Show, Eq, Read, Generic) deriving (Typeable, Show, Eq, Read, Generic)


instance SubTypes M instance SubTypes M


data N = N M Int String data N = N M Int String
deriving (Data, Typeable, Show, Eq, Read, Generic) deriving (Typeable, Show, Eq, Read, Generic)


instance SubTypes N instance SubTypes N


Expand Down
9 changes: 4 additions & 5 deletions examples/Protocol.hs
Expand Up @@ -5,7 +5,6 @@
module Protocol where module Protocol where


import Prelude hiding (last, id) import Prelude hiding (last, id)
import Data.Data
import Data.List hiding (last) import Data.List hiding (last)
import Control.Monad import Control.Monad
import Test.QuickCheck import Test.QuickCheck
Expand All @@ -15,7 +14,7 @@ import Test.SmartCheck


data Input = Input data Input = Input
{ header :: Header } { header :: Header }
deriving (Data, Typeable, Show, Eq, Read) deriving (Typeable, Show, Eq, Read)


data Header = Header data Header = Header
{ name :: String { name :: String
Expand All @@ -37,17 +36,17 @@ data Fields = Fields
, f8 :: Ins , f8 :: Ins
, f9 :: Ins , f9 :: Ins
, fn :: Ins' } , fn :: Ins' }
deriving (Data, Typeable, Show, Eq, Read) deriving (Typeable, Show, Eq, Read)


data Ins = Strs [String] data Ins = Strs [String]
| Ints [Int] | Ints [Int]
| Else [String] | Else [String]
deriving (Data, Typeable, Show, Eq, Read) deriving (Typeable, Show, Eq, Read)


data Ins' = Strs' [String] data Ins' = Strs' [String]
| Ints' [Int] | Ints' [Int]
| Else' [String] | Else' [String]
deriving (Data, Typeable, Show, Eq, Read) deriving (Typeable, Show, Eq, Read)


-- Output format -- Output format
data Output = Output data Output = Output
Expand Down

0 comments on commit 1aedbcb

Please sign in to comment.