Skip to content
GitLab
Projects
Groups
Snippets
/
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Glasgow Haskell Compiler
Packages
text
Commits
e9c98f42
Commit
e9c98f42
authored
Oct 09, 2021
by
Bodigrim
Committed by
Xia Li-yao
Oct 13, 2021
Browse files
Add inspection tests for Text literal
parent
bb03e6f8
Changes
2
Hide whitespace changes
Inline
Side-by-side
tests/Tests/Properties/LowLevel.hs
View file @
e9c98f42
-- | Test low-level operations
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-missing-signatures -fno-warn-unused-imports #-}
#
ifdef
MIN_VERSION_tasty_inspection_testing
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -O -dsuppress-all -dno-suppress-type-signatures -fplugin=Test.Tasty.Inspection.Plugin #-}
#
endif
module
Tests.Properties.LowLevel
(
testLowLevel
)
where
import
Control.Applicative
((
<$>
),
pure
)
...
...
@@ -24,6 +32,13 @@ import qualified Data.Text.Lazy as TL
import
qualified
Data.Text.Lazy.IO
as
TL
import
qualified
System.IO
as
IO
#
ifdef
MIN_VERSION_tasty_inspection_testing
import
Test.Tasty.Inspection
(
inspectObligations
,
hasNoTypes
,
doesNotUseAnyOf
)
import
qualified
Data.Text.Internal.Fusion
as
S
import
qualified
Data.Text.Internal.Fusion.Common
as
S
import
qualified
GHC.CString
as
GHC
#
endif
mulRef
::
(
Integral
a
,
Bounded
a
)
=>
a
->
a
->
Maybe
a
mulRef
a
b
|
ab
<
bot
||
ab
>
top
=
Nothing
...
...
@@ -67,6 +82,11 @@ t_literal_surrogates = assertEqual xs (T.pack xs) (T.pack ys)
ys
=
"
\xd7ff
\xd800
\xdbff
\xdc00
\xdfff
\xe000
"
xs
=
map
safe
ys
#
ifdef
MIN_VERSION_tasty_inspection_testing
t_literal_foo
::
Text
t_literal_foo
=
T
.
pack
"foo"
#
endif
-- Input and output.
-- t_put_get = write_read T.unlines T.filter put get
...
...
@@ -102,6 +122,15 @@ testLowLevel =
testCase
"t_literal_length1"
t_literal_length1
,
testCase
"t_literal_length2"
t_literal_length2
,
testCase
"t_literal_surrogates"
t_literal_surrogates
#
ifdef
MIN_VERSION_tasty_inspection_testing
,
$
(
inspectObligations
[
(`
hasNoTypes
`
[
''Char
,
''
[]
])
,
(`
doesNotUseAnyOf
`
[
'T
.
pack
,
'S
.
unstream
,
'T
.
map
,
'safe
,
'S
.
streamList
])
,
(`
doesNotUseAnyOf
`
[
'GHC
.
unpackCString
#
,
'GHC
.
unpackCStringUtf8
#
])
,
(`
doesNotUseAnyOf
`
[
'T
.
unpackCString
#
,
'T
.
unpackCStringAscii
#
])
]
't_literal_foo
)
#
endif
],
testGroup
"input-output"
[
...
...
text.cabal
View file @
e9c98f42
...
...
@@ -216,12 +216,18 @@ test-suite tests
bytestring,
deepseq,
directory,
ghc-prim,
tasty,
tasty-hunit,
tasty-quickcheck,
template-haskell,
text
-- Starting from 9.2 ghc library depends on parsec,
-- which causes circular dependency.
if impl(ghc < 9.2)
build-depends: tasty-inspection-testing
default-language: Haskell2010
default-extensions: NondecreasingIndentation
...
...
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment