Skip to content

Commit 061ebf1

Browse files
committed
update: clean-up
1 parent a6c113d commit 061ebf1

File tree

9 files changed

+35
-27
lines changed

9 files changed

+35
-27
lines changed

lambda-buffers-compiler/lambda-buffers-compiler.cabal

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -156,10 +156,9 @@ test-suite tests
156156

157157
other-modules:
158158
Test.KindCheck
159-
Test.Samples
160159
Test.Samples.Proto.CompilerInput
161-
Test.Samples.Proto.Helpers
162160
Test.Samples.Proto.Module
163161
Test.Samples.Proto.SourceInfo
164162
Test.Samples.Proto.TyDef
163+
Test.Samples.Proto.Utils
165164
Test.TypeClassCheck

lambda-buffers-compiler/src/LambdaBuffers/Compiler/KindCheck/Type.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ module LambdaBuffers.Compiler.KindCheck.Type (
88

99
import LambdaBuffers.Compiler.KindCheck.Variable (Variable (LocalRef))
1010
import Prettyprinter (Doc, Pretty (pretty), parens, (<+>))
11-
import Test.QuickCheck (Arbitrary, arbitrary, oneof, sized)
11+
import Test.QuickCheck (Arbitrary, Gen, arbitrary, oneof, sized)
1212

1313
data Type
1414
= Var Variable
@@ -37,6 +37,7 @@ instance Pretty Type where
3737
instance Arbitrary Type where
3838
arbitrary = sized f
3939
where
40+
f :: Integral a => a -> Gen Type
4041
f n
4142
| n <= 0 = Var <$> arbitrary
4243
| otherwise =

lambda-buffers-compiler/src/LambdaBuffers/Compiler/KindCheck/Variable.hs

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,15 +1,19 @@
11
module LambdaBuffers.Compiler.KindCheck.Variable (Variable (LocalRef, ForeignRef), Atom) where
22

33
import Data.Text (Text)
4-
import Orphan.Text
4+
import GHC.Generics (Generic)
5+
import Orphan.Text ()
56
import Prettyprinter (Pretty (pretty), concatWith)
7+
import Test.QuickCheck (Arbitrary)
8+
import Test.QuickCheck.Arbitrary.Generic (GenericArbitrary (GenericArbitrary))
69

710
type Atom = Text
811

912
data Variable
1013
= LocalRef Text
1114
| ForeignRef [Text] Text
12-
deriving stock (Eq, Ord, Show)
15+
deriving stock (Eq, Ord, Show, Generic)
16+
deriving (Arbitrary) via GenericArbitrary Variable
1317

1418
instance Pretty Variable where
1519
pretty = \case

lambda-buffers-compiler/src/LambdaBuffers/Compiler/ProtoCompat/Types.hs

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -46,12 +46,11 @@ module LambdaBuffers.Compiler.ProtoCompat.Types (
4646

4747
import Control.Exception (Exception)
4848
import Data.List.NonEmpty (NonEmpty ((:|)), (<|))
49-
import Data.Map qualified as M
5049
import Data.Text (Text)
5150
import GHC.Generics (Generic)
52-
import LambdaBuffers.Compiler.KindCheck.Variable as VARS (Atom, Var, Variable)
53-
import Test.QuickCheck (Arbitrary (arbitrary), Gen, NonEmptyList (getNonEmpty), oneof, resize, sized)
54-
import Test.QuickCheck.Arbitrary.Generic
51+
import LambdaBuffers.Compiler.KindCheck.Variable as VARS (Atom, Variable)
52+
import Test.QuickCheck (Gen, oneof, resize, sized)
53+
import Test.QuickCheck.Arbitrary.Generic (Arbitrary (arbitrary), GenericArbitrary (GenericArbitrary))
5554

5655
data SourceInfo = SourceInfo {file :: Text, posFrom :: SourcePosition, posTo :: SourcePosition}
5756
deriving stock (Show, Eq, Ord, Generic)
@@ -128,6 +127,7 @@ data Ty = TyVarI TyVar | TyAppI TyApp | TyRefI TyRef
128127
instance Arbitrary Ty where
129128
arbitrary = sized fn
130129
where
130+
fn :: (Num a, Ord a) => a -> Gen Ty
131131
fn n
132132
| n <= 0 = TyRefI <$> arbitrary
133133
| otherwise =
@@ -276,7 +276,6 @@ instance Arbitrary CompilerInput where
276276
where
277277
fn n = CompilerInput <$> resize n arbitrary
278278

279-
newtype CompilerOutput = CompilerOutput {typeDefs :: M.Map Var Kind}
280279
data KindCheckError
281280
= -- | The following term is unbound in the following type definition.
282281
UnboundTermError TyName VarName
@@ -287,22 +286,23 @@ data KindCheckError
287286
| -- | The following type has the wrong.
288287
InconsistentTypeError TyName Kind Kind
289288
deriving stock (Show, Eq, Ord, Generic)
289+
deriving (Arbitrary) via GenericArbitrary KindCheckError
290290
instance Exception KindCheckError
291291

292292
data CompilerError
293293
= CompKindCheckError KindCheckError
294294
| InternalError Text
295295
deriving stock (Show, Eq, Ord, Generic)
296-
deriving (Arbitrary) via GenericArbitrary CompilerOutput
296+
deriving (Arbitrary) via GenericArbitrary CompilerError
297297

298298
data CompilerResult = CompilerResult
299299
deriving stock (Show, Eq, Ord, Generic)
300-
deriving (Arbitrary) via GenericArbitrary CompilerFailure
300+
deriving (Arbitrary) via GenericArbitrary CompilerResult
301301

302302
type CompilerOutput = Either CompilerError CompilerResult
303303

304-
nonEmptyArbList :: forall a. Arbitrary a => Gen [a]
305-
nonEmptyArbList = getNonEmpty <$> arbitrary @(NonEmptyList a)
304+
-- nonEmptyArbList :: forall a. Arbitrary a => Gen [a]
305+
-- nonEmptyArbList = getNonEmpty <$> arbitrary @(NonEmptyList a)
306306

307307
-- Orphan Instances
308308
instance Arbitrary a => Arbitrary (NonEmpty a) where
Lines changed: 14 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,17 @@
1-
module Orphan.Text where
1+
{-# OPTIONS_GHC -Wno-orphans #-}
22

3-
import Data.Text
4-
import Test.QuickCheck (Arbitrary (arbitrary), Gen, oneof, sized)
3+
module Orphan.Text () where
4+
5+
import Data.Text (Text, pack)
6+
import Test.QuickCheck (Arbitrary (arbitrary), Gen, sized)
57

68
instance Arbitrary Text where
7-
arbitrary = pack <$> arbitrary
9+
arbitrary = sized f
10+
where
11+
f :: (Ord a, Num a) => a -> Gen Text
12+
f n
13+
| n <= 0 = pure $ pack []
14+
| otherwise = do
15+
c <- arbitrary
16+
cs <- f (n - 1)
17+
pure $ pack [c] <> cs

lambda-buffers-compiler/test/Test/KindCheck.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -78,6 +78,7 @@ kcTestOrdering =
7878
shuffledMods <- shuffle mods
7979
pure (P.CompilerInput mods, P.CompilerInput shuffledMods)
8080

81+
eitherFailOrPass :: forall {a} {c}. Either a c -> Either () ()
8182
eitherFailOrPass = bimap (const ()) (const ())
8283

8384
--------------------------------------------------------------------------------

lambda-buffers-compiler/test/Test/Samples.hs

Lines changed: 0 additions & 7 deletions
This file was deleted.

lambda-buffers-compiler/test/Test/Samples/Proto/TyDef.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
module Test.Samples.Proto.TyDef (tyDef'maybe, tyDef'incoherent) where
22

33
import LambdaBuffers.Compiler.ProtoCompat qualified as P
4-
import Test.Samples.Proto.Helpers (
4+
import Test.Samples.Proto.Utils (
55
_TupleI,
66
_TyAbs,
77
_TyDef,

lambda-buffers-compiler/test/Test/Samples/Proto/Helpers.hs renamed to lambda-buffers-compiler/test/Test/Samples/Proto/Utils.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
module Test.Samples.Proto.Helpers (
1+
module Test.Samples.Proto.Utils (
22
_tyName,
33
_varName,
44
_tyVar,

0 commit comments

Comments
 (0)