Split tests into individual files
parent
89a9f47b72
commit
21e86adf6e
|
@ -24,7 +24,8 @@ extra-doc-files:
|
||||||
README.md
|
README.md
|
||||||
doc/implementation/*.md
|
doc/implementation/*.md
|
||||||
extra-source-files:
|
extra-source-files:
|
||||||
data/*.blt
|
data/brittany.yaml
|
||||||
|
data/*.hs
|
||||||
|
|
||||||
source-repository head
|
source-repository head
|
||||||
type: git
|
type: git
|
||||||
|
@ -143,7 +144,6 @@ test-suite brittany-test-suite
|
||||||
|
|
||||||
build-depends:
|
build-depends:
|
||||||
, hspec ^>= 2.8.3
|
, hspec ^>= 2.8.3
|
||||||
, parsec ^>= 3.1.14
|
|
||||||
hs-source-dirs: source/test-suite
|
hs-source-dirs: source/test-suite
|
||||||
main-is: Main.hs
|
main-is: Main.hs
|
||||||
type: exitcode-stdio-1.0
|
type: exitcode-stdio-1.0
|
||||||
|
|
1757
data/10-tests.blt
1757
data/10-tests.blt
File diff suppressed because it is too large
Load Diff
|
@ -1,241 +0,0 @@
|
||||||
###############################################################################
|
|
||||||
###############################################################################
|
|
||||||
###############################################################################
|
|
||||||
#group extensions
|
|
||||||
###############################################################################
|
|
||||||
###############################################################################
|
|
||||||
###############################################################################
|
|
||||||
|
|
||||||
###############################################################################
|
|
||||||
## MultiWayIf
|
|
||||||
#test multiwayif 1
|
|
||||||
{-# LANGUAGE MultiWayIf #-}
|
|
||||||
func = if
|
|
||||||
| cond1 -> loooooooooooooooooooooooooooooong expr1
|
|
||||||
| cond2 -> loooooooooooooooooooooooooooooong expr2
|
|
||||||
|
|
||||||
#test multiwayif 2
|
|
||||||
{-# LANGUAGE MultiWayIf #-}
|
|
||||||
func = do
|
|
||||||
foo
|
|
||||||
bar $ if
|
|
||||||
| cond1 -> loooooooooooooooooooooooooooooong expr1
|
|
||||||
| cond2 -> loooooooooooooooooooooooooooooong expr2
|
|
||||||
|
|
||||||
|
|
||||||
###############################################################################
|
|
||||||
## LambdaCase
|
|
||||||
#test lambdacase 1
|
|
||||||
{-# LANGUAGE LambdaCase #-}
|
|
||||||
func = \case
|
|
||||||
FooBar -> x
|
|
||||||
Baz -> y
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
###############################################################################
|
|
||||||
## ImplicitParams
|
|
||||||
#test ImplicitParams 1
|
|
||||||
{-# LANGUAGE ImplicitParams #-}
|
|
||||||
func :: (?asd::Int) -> ()
|
|
||||||
|
|
||||||
#test ImplicitParams 2
|
|
||||||
{-# LANGUAGE ImplicitParams #-}
|
|
||||||
func
|
|
||||||
:: ( ?asd
|
|
||||||
:: lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
|
||||||
-> lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
|
||||||
)
|
|
||||||
-> ()
|
|
||||||
|
|
||||||
|
|
||||||
###############################################################################
|
|
||||||
## RecursiveDo
|
|
||||||
#test recursivedo 1
|
|
||||||
{-# LANGUAGE RecursiveDo #-}
|
|
||||||
foo = do
|
|
||||||
rec a <- f b
|
|
||||||
b <- g a
|
|
||||||
return (a, b)
|
|
||||||
|
|
||||||
#test recursivedo 2
|
|
||||||
{-# LANGUAGE RecursiveDo #-}
|
|
||||||
foo = do
|
|
||||||
rec -- comment
|
|
||||||
a <- f b
|
|
||||||
b <- g a
|
|
||||||
return (a, b)
|
|
||||||
|
|
||||||
###############################################################################
|
|
||||||
## ExplicitNamespaces + PatternSynonyms
|
|
||||||
#test explicitnamespaces_patternsynonyms export
|
|
||||||
{-# LANGUAGE ExplicitNamespaces #-}
|
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
|
||||||
module Test (type (++), (++), pattern Foo) where
|
|
||||||
|
|
||||||
#test explicitnamespaces_patternsynonyms import
|
|
||||||
{-# LANGUAGE ExplicitNamespaces #-}
|
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
|
||||||
import Test ( type (++)
|
|
||||||
, (++)
|
|
||||||
, pattern (:.)
|
|
||||||
, pattern Foo
|
|
||||||
)
|
|
||||||
|
|
||||||
###############################################################################
|
|
||||||
## PatternSynonyms
|
|
||||||
#test bidirectional pattern
|
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
|
||||||
pattern J x = Just x
|
|
||||||
|
|
||||||
#test unidirection pattern
|
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
|
||||||
pattern F x <- (x, _)
|
|
||||||
|
|
||||||
#test explicitly bidirectional pattern
|
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
|
||||||
pattern HeadC x <- x : xs where
|
|
||||||
HeadC x = [x]
|
|
||||||
|
|
||||||
#test Multiple arguments
|
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
|
||||||
pattern Head2 x y <- x : y : xs where
|
|
||||||
Head2 x y = [x, y]
|
|
||||||
|
|
||||||
#test Infix argument
|
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
|
||||||
pattern x :> y = [x, y]
|
|
||||||
|
|
||||||
#test Record argument
|
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
|
||||||
pattern MyData { a, b, c } = [a, b, c]
|
|
||||||
|
|
||||||
#test long pattern match
|
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
|
||||||
pattern myLongLeftVariableName `MyLongInfixPatternMatcher` myLongRightVariableName =
|
|
||||||
[myLongLeftVariableName, myLongRightVariableName]
|
|
||||||
|
|
||||||
#test long explicitly bidirectional match
|
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
|
||||||
pattern myLeftVariableName `MyInfixPatternMatcher` myRightVariableName <-
|
|
||||||
[myLongLeftVariableName, myLongRightVariableName] where
|
|
||||||
MyInfixPatternMatcher x y = [x, x, y]
|
|
||||||
|
|
||||||
#test Pattern synonym types
|
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
|
||||||
pattern J :: a -> Maybe a
|
|
||||||
pattern J x = Just x
|
|
||||||
|
|
||||||
#test pattern synonym bidirectional multiple cases
|
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
|
||||||
{-# LANGUAGE ViewPatterns #-}
|
|
||||||
pattern Signed x <- (asSigned -> x) where
|
|
||||||
Signed (Neg x) = -x
|
|
||||||
Signed Zero = 0
|
|
||||||
Signed (Pos x) = x
|
|
||||||
|
|
||||||
#test pattern synonym bidirectional multiple cases long
|
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
|
||||||
{-# LANGUAGE ViewPatterns #-}
|
|
||||||
pattern Signed xxxxxxxxxxxxxxxxxxxxxxxx <-
|
|
||||||
(asSigned -> xxxxxxxxxxxxxxxxxxxxxxxx) where
|
|
||||||
Signed (Neg x) = -x
|
|
||||||
Signed Zero = 0
|
|
||||||
Signed (Pos x) = x
|
|
||||||
|
|
||||||
#test pattern synonym bidirectional multiple cases with comments
|
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
|
||||||
{-# LANGUAGE ViewPatterns #-}
|
|
||||||
pattern Signed x <- (asSigned -> x) where
|
|
||||||
Signed (Neg x) = -x -- negative comment
|
|
||||||
Signed Zero = 0 -- zero comment
|
|
||||||
Signed (Pos x) = x -- positive comment
|
|
||||||
|
|
||||||
#test Pattern synonym types multiple names
|
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
|
||||||
pattern J, K :: a -> Maybe a
|
|
||||||
|
|
||||||
#test Pattern synonym type sig wrapped
|
|
||||||
{-# LANGUAGE PatternSynonyms #-}
|
|
||||||
pattern LongMatcher
|
|
||||||
:: longlongtypevar
|
|
||||||
-> longlongtypevar
|
|
||||||
-> longlongtypevar
|
|
||||||
-> Maybe [longlongtypevar]
|
|
||||||
pattern LongMatcher x y z = Just [x, y, z]
|
|
||||||
|
|
||||||
|
|
||||||
###############################################################################
|
|
||||||
## UnboxedTuples + MagicHash
|
|
||||||
#test unboxed-tuple and vanilla names
|
|
||||||
{-# LANGUAGE UnboxedTuples #-}
|
|
||||||
spanKey :: (# Int, Int #) -> (# Int, Int #)
|
|
||||||
spanKey = case foo of
|
|
||||||
(# bar, baz #) -> (# baz, bar #)
|
|
||||||
|
|
||||||
#test unboxed-tuple and hashed name
|
|
||||||
{-# LANGUAGE MagicHash, UnboxedTuples #-}
|
|
||||||
spanKey :: (# Int#, Int# #) -> (# Int#, Int# #)
|
|
||||||
spanKey = case foo of
|
|
||||||
(# bar#, baz# #) -> (# baz# +# bar#, bar# #)
|
|
||||||
|
|
||||||
|
|
||||||
###############################################################################
|
|
||||||
## QuasiQuotes
|
|
||||||
#test quasi-quotes simple 1
|
|
||||||
{-# LANGUAGE QuasiQuotes #-}
|
|
||||||
func = [blub|
|
|
||||||
asd
|
|
||||||
qwe
|
|
||||||
|]
|
|
||||||
|
|
||||||
#test quasi-quotes simple 2
|
|
||||||
{-# LANGUAGE QuasiQuotes #-}
|
|
||||||
func = [blub|
|
|
||||||
asd
|
|
||||||
qwe|]
|
|
||||||
|
|
||||||
#test quasi-quotes ignoring layouting
|
|
||||||
{-# LANGUAGE QuasiQuotes #-}
|
|
||||||
func = do
|
|
||||||
let body = [json|
|
|
||||||
hello
|
|
||||||
|]
|
|
||||||
pure True
|
|
||||||
|
|
||||||
#test quasi-quotes ignoring layouting, strict mode
|
|
||||||
-- brittany { lconfig_allowHangingQuasiQuotes: False }
|
|
||||||
{-# LANGUAGE QuasiQuotes #-}
|
|
||||||
func = do
|
|
||||||
let
|
|
||||||
body =
|
|
||||||
[json|
|
|
||||||
hello
|
|
||||||
|]
|
|
||||||
pure True
|
|
||||||
|
|
||||||
###############################################################################
|
|
||||||
## OverloadedLabels
|
|
||||||
#test bare label
|
|
||||||
{-# LANGUAGE OverloadedLabels #-}
|
|
||||||
foo = #bar
|
|
||||||
|
|
||||||
#test applied and composed label
|
|
||||||
{-# LANGUAGE OverloadedLabels #-}
|
|
||||||
foo = #bar . #baz $ fmap #foo xs
|
|
||||||
|
|
||||||
###############################################################################
|
|
||||||
## ImplicitParams
|
|
||||||
|
|
||||||
#test IP usage
|
|
||||||
{-# LANGUAGE ImplicitParams #-}
|
|
||||||
foo = ?bar
|
|
||||||
|
|
||||||
#test IP binding
|
|
||||||
{-# LANGUAGE ImplicitParams #-}
|
|
||||||
foo = let ?bar = Foo in value
|
|
||||||
|
|
||||||
#test IP type signature
|
|
||||||
{-# LANGUAGE ImplicitParams #-}
|
|
||||||
foo :: (?bar::Bool) => ()
|
|
||||||
foo = ()
|
|
|
@ -1,874 +0,0 @@
|
||||||
###############################################################################
|
|
||||||
###############################################################################
|
|
||||||
###############################################################################
|
|
||||||
#group regression
|
|
||||||
###############################################################################
|
|
||||||
###############################################################################
|
|
||||||
###############################################################################
|
|
||||||
|
|
||||||
#test newlines-comment
|
|
||||||
func = do
|
|
||||||
abc <- foo
|
|
||||||
|
|
||||||
--abc
|
|
||||||
return ()
|
|
||||||
|
|
||||||
#test parenthesis-around-unit
|
|
||||||
func = (())
|
|
||||||
|
|
||||||
#test let-defs indentation
|
|
||||||
func = do
|
|
||||||
let foo True = True
|
|
||||||
foo _ = False
|
|
||||||
return ()
|
|
||||||
|
|
||||||
#test record update indentation 1
|
|
||||||
func = do
|
|
||||||
s <- mGet
|
|
||||||
mSet $ s { _lstate_indent = _lstate_indent state }
|
|
||||||
|
|
||||||
#test record update indentation 2
|
|
||||||
func = do
|
|
||||||
s <- mGet
|
|
||||||
mSet $ s { _lstate_indent = _lstate_indent state
|
|
||||||
, _lstate_foo = _lstate_foo state
|
|
||||||
}
|
|
||||||
|
|
||||||
#test record update indentation 3
|
|
||||||
func = do
|
|
||||||
s <- mGet
|
|
||||||
mSet $ s
|
|
||||||
{ _lstate_indent = _lstate_indent lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
|
||||||
, _lstate_foo = _lstate_foo lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
|
||||||
}
|
|
||||||
|
|
||||||
#test record construction 1
|
|
||||||
func = Foo { _lstate_indent = _lstate_indent state }
|
|
||||||
|
|
||||||
#test record construction 2
|
|
||||||
func = Foo
|
|
||||||
{ _lstate_indent = _lstate_indent lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
|
||||||
, _lstate_fooo = _lstate_foo lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
|
||||||
}
|
|
||||||
|
|
||||||
#test record construction 3
|
|
||||||
func = do
|
|
||||||
Foo { _lstate_indent = _lstate_indent lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
|
||||||
, _lstate_foo = _lstate_foo lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
|
||||||
}
|
|
||||||
|
|
||||||
#test post-indent comment
|
|
||||||
func = do
|
|
||||||
-- abc
|
|
||||||
-- def
|
|
||||||
return ()
|
|
||||||
|
|
||||||
#test post-unindent comment
|
|
||||||
func = do
|
|
||||||
do
|
|
||||||
return ()
|
|
||||||
-- abc
|
|
||||||
-- def
|
|
||||||
return ()
|
|
||||||
|
|
||||||
#test CPP empty comment case
|
|
||||||
#pending CPP parsing needs fixing for roundTripEqual
|
|
||||||
{-# LANGUAGE CPP #-}
|
|
||||||
module Test where
|
|
||||||
func = do
|
|
||||||
#if FOO
|
|
||||||
let x = 13
|
|
||||||
#endif
|
|
||||||
stmt x
|
|
||||||
|
|
||||||
## really, the following should be handled by forcing the Alt to multiline
|
|
||||||
## because there are comments. as long as this is not implemented though,
|
|
||||||
## we should ensure the trivial solution works.
|
|
||||||
#test comment inline placement (temporary)
|
|
||||||
func
|
|
||||||
:: Int -- basic indentation amount
|
|
||||||
-> Int -- currently used width in current line (after indent)
|
|
||||||
-- used to accurately calc placing of the current-line
|
|
||||||
-> LayoutDesc
|
|
||||||
-> Int
|
|
||||||
|
|
||||||
#test some indentation thingy
|
|
||||||
func =
|
|
||||||
( lkjadljasldjalskdjaldjalsdjkalsdjlaksdjlasjdlajsaldskj
|
|
||||||
$ abc
|
|
||||||
$ def
|
|
||||||
$ ghi
|
|
||||||
$ jkl
|
|
||||||
)
|
|
||||||
|
|
||||||
#test parenthesized operator
|
|
||||||
buildG bounds0 edges0 = accumArray (flip (:)) [] bounds0 (map reassoc edges0)
|
|
||||||
where reassoc (v, e, w) = (v, (e, w))
|
|
||||||
|
|
||||||
#test record pattern matching stuff
|
|
||||||
downloadRepoPackage = case repo of
|
|
||||||
RepoLocal {..} -> return ()
|
|
||||||
RepoLocal { abc } -> return ()
|
|
||||||
RepoLocal{} -> return ()
|
|
||||||
|
|
||||||
#test do let comment indentation level problem
|
|
||||||
func = do
|
|
||||||
let (primaryPkg, otherPkgs) = selectPrimaryLocalPackage pwd pkgs'
|
|
||||||
(bproblems, x) = resolveBuildTargets primaryPkg otherPkgs utargets''
|
|
||||||
-- default local dir target if there's no given target
|
|
||||||
utargets'' = "foo"
|
|
||||||
return ()
|
|
||||||
|
|
||||||
#test list comprehension comment placement
|
|
||||||
func =
|
|
||||||
[ (thing, take 10 alts) --TODO: select best ones
|
|
||||||
| (thing, _got, alts@(_ : _)) <- nosuchFooThing
|
|
||||||
, gast <- award
|
|
||||||
]
|
|
||||||
|
|
||||||
#test if-then-else comment placement
|
|
||||||
func = if x
|
|
||||||
then if y -- y is important
|
|
||||||
then foo
|
|
||||||
else bar
|
|
||||||
else Nothing
|
|
||||||
|
|
||||||
#test qualified infix pattern
|
|
||||||
wrapPatPrepend pat prepElem = do
|
|
||||||
patDocs <- layoutPat pat
|
|
||||||
case Seq.viewl patDocs of
|
|
||||||
Seq.EmptyL -> return $ Seq.empty
|
|
||||||
x1 Seq.:< xR -> do
|
|
||||||
x1' <- docSeq [prepElem, return x1]
|
|
||||||
return $ x1' Seq.<| xR
|
|
||||||
|
|
||||||
#test type signature multiline forcing issue
|
|
||||||
layoutWriteNewlineBlock
|
|
||||||
:: ( MonadMultiWriter Text.Builder.Builder m
|
|
||||||
, MonadMultiState LayoutState m
|
|
||||||
, MonadMultiWriter (Seq String) m
|
|
||||||
)
|
|
||||||
=> m ()
|
|
||||||
|
|
||||||
#test multiwayif proper indentation
|
|
||||||
{-# LANGUAGE MultiWayIf #-}
|
|
||||||
readMergePersConfig path shouldCreate conf = do
|
|
||||||
exists <- liftIO $ System.Directory.doesFileExist path
|
|
||||||
if
|
|
||||||
| exists -> do
|
|
||||||
contents <- liftIO $ ByteString.readFile path -- no lazy IO, tyvm.
|
|
||||||
fileConf <- case Data.Yaml.decodeEither contents of
|
|
||||||
Left e -> do
|
|
||||||
liftIO
|
|
||||||
$ putStrErrLn
|
|
||||||
$ "error reading in brittany config from "
|
|
||||||
++ path
|
|
||||||
++ ":"
|
|
||||||
liftIO $ putStrErrLn e
|
|
||||||
mzero
|
|
||||||
Right x -> return x
|
|
||||||
return $ fileConf Semigroup.<> conf
|
|
||||||
| shouldCreate -> do
|
|
||||||
liftIO $ ByteString.writeFile path $ Data.Yaml.encode $ cMap
|
|
||||||
(Option . Just . runIdentity)
|
|
||||||
staticDefaultConfig
|
|
||||||
return $ conf
|
|
||||||
| otherwise -> do
|
|
||||||
return conf
|
|
||||||
|
|
||||||
#test nested pattern alignment issue"
|
|
||||||
func = BuildReport
|
|
||||||
where
|
|
||||||
convertInstallOutcome = case result of
|
|
||||||
Left BR.PlanningFailed -> PlanningFailed
|
|
||||||
Left (BR.DependentFailed p) -> DependencyFailed p
|
|
||||||
Left (BR.DownloadFailed _) -> DownloadFailed
|
|
||||||
Left (BR.UnpackFailed _) -> UnpackFailed
|
|
||||||
Left (BR.ConfigureFailed _) -> ConfigureFailed
|
|
||||||
Left (BR.BuildFailed _) -> BuildFailed
|
|
||||||
Left (BR.TestsFailed _) -> TestsFailed
|
|
||||||
Left (BR.InstallFailed _) -> InstallFailed
|
|
||||||
Right (BR.BuildOk _ _ _ ) -> InstallOk
|
|
||||||
|
|
||||||
#test nested pattern alignment issue"
|
|
||||||
func = BuildReport
|
|
||||||
where
|
|
||||||
convertInstallOutcome = case result of
|
|
||||||
Left BR.PlanningFailed -> PlanningFailed
|
|
||||||
Left (BR.DependentFailed p) -> DependencyFailed p
|
|
||||||
Left (BR.DownloadFailed _) -> DownloadFailed
|
|
||||||
Left (BR.UnpackFailed _) -> UnpackFailed
|
|
||||||
Left (BR.ConfigureFailed _) -> ConfigureFailed
|
|
||||||
Left (BR.BuildFailed _) -> BuildFailed
|
|
||||||
Left (BR.TestsFailed _) -> TestsFailed
|
|
||||||
Left (BR.InstallFailed _) -> InstallFailed
|
|
||||||
Right (BR.BuildOk _ _ _ ) -> InstallOk
|
|
||||||
|
|
||||||
#test partially overflowing alignment issue"
|
|
||||||
showPackageDetailedInfo pkginfo =
|
|
||||||
renderStyle (style { lineLength = 80, ribbonsPerLine = 1 })
|
|
||||||
$ char '*'
|
|
||||||
$+$ something
|
|
||||||
[ entry "Synopsis" synopsis hideIfNull reflowParagraphs
|
|
||||||
, entry "Versions available"
|
|
||||||
sourceVersions
|
|
||||||
(altText null "[ Not available from server ]")
|
|
||||||
(dispTopVersions 9 (preferredVersions pkginfo))
|
|
||||||
, entry
|
|
||||||
"Versions installed"
|
|
||||||
installedVersions
|
|
||||||
(altText
|
|
||||||
null
|
|
||||||
(if hasLib pkginfo then "[ Not installed ]" else "[ Unknown ]")
|
|
||||||
)
|
|
||||||
(dispTopVersions 4 (preferredVersions pkginfo))
|
|
||||||
, entry "Homepage" homepage orNotSpecified text
|
|
||||||
, entry "Bug reports" bugReports orNotSpecified text
|
|
||||||
, entry "Description" description hideIfNull reflowParagraphs
|
|
||||||
, entry "Category" category hideIfNull text
|
|
||||||
, entry "License" license alwaysShow disp
|
|
||||||
, entry "Author" author hideIfNull reflowLines
|
|
||||||
, entry "Maintainer" maintainer hideIfNull reflowLines
|
|
||||||
, entry "Source repo" sourceRepo orNotSpecified text
|
|
||||||
, entry "Executables" executables hideIfNull (commaSep text)
|
|
||||||
, entry "Flags" flags hideIfNull (commaSep dispFlag)
|
|
||||||
, entry "Dependencies" dependencies hideIfNull (commaSep dispExtDep)
|
|
||||||
, entry "Documentation" haddockHtml showIfInstalled text
|
|
||||||
, entry "Cached" haveTarball alwaysShow dispYesNo
|
|
||||||
, if not (hasLib pkginfo)
|
|
||||||
then empty
|
|
||||||
else text "Modules:"
|
|
||||||
$+$ nest 4 (vcat (map disp . sort . modules $ pkginfo))
|
|
||||||
]
|
|
||||||
|
|
||||||
#test issue 7a
|
|
||||||
isValidPosition position | validX && validY = Just position
|
|
||||||
| otherwise = Nothing
|
|
||||||
|
|
||||||
#test issue-6-pattern-linebreak-validity
|
|
||||||
## this is ugly, but at least syntactically valid.
|
|
||||||
foo = Reflex.runSpiderHost $ ReflexHost.hostApp $ do
|
|
||||||
(inputEvent :: Reflex.Event Reflex.Spider String, inputFire :: String
|
|
||||||
-> IO Bool ) <-
|
|
||||||
ReflexHost.newExternalEvent
|
|
||||||
liftIO . forkIO . forever $ getLine >>= inputFire
|
|
||||||
ReflexHost.performEvent_ $ fmap (liftIO . putStrLn) inputEvent
|
|
||||||
|
|
||||||
#test issue 16
|
|
||||||
foldrDesc f z = unSwitchQueue $ \q ->
|
|
||||||
switch (Min.foldrDesc (f unTaggedF) z q) (Min.foldrAsc (f unTaggedF) z q)
|
|
||||||
|
|
||||||
#test issue 18
|
|
||||||
autocheckCases =
|
|
||||||
[ ("Never Deadlocks" , representative deadlocksNever)
|
|
||||||
, ("No Exceptions" , representative exceptionsNever)
|
|
||||||
, ("Consistent Result", alwaysSame) -- already representative
|
|
||||||
]
|
|
||||||
|
|
||||||
#test issue 18b
|
|
||||||
autocheckCases =
|
|
||||||
[ ("Never Deadlocks", representative deadlocksNever)
|
|
||||||
, ("No Exceptions" , representative exceptionsNever)
|
|
||||||
, ( "Consistent Result"
|
|
||||||
, alwaysSame -- already representative
|
|
||||||
)
|
|
||||||
]
|
|
||||||
|
|
||||||
#test issue 18c
|
|
||||||
func =
|
|
||||||
[ (abc, (1111, 1111))
|
|
||||||
, (def, (2, 2))
|
|
||||||
, foo -- comment
|
|
||||||
]
|
|
||||||
|
|
||||||
#test issue 26
|
|
||||||
foo a b = g a b -- fooooooooooooooooooooooooooooooooooooooooooooooooooooooooooo
|
|
||||||
where g a b = b + b * a
|
|
||||||
|
|
||||||
#test issue 26b
|
|
||||||
foo a b = g a b where g a b = b + b * a -- fooooooooooooooooooooooooooooooooooo
|
|
||||||
|
|
||||||
#test aggressive alignment 1
|
|
||||||
func = do
|
|
||||||
abc <- expr
|
|
||||||
abcccccccccccccccccc <- expr
|
|
||||||
abcccccccccccccccccccccccccccccccccccccccccc <- expr
|
|
||||||
abccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc <- expr
|
|
||||||
|
|
||||||
#test example alignment 1
|
|
||||||
func (MyLongFoo abc def) = 1
|
|
||||||
func (Bar a d ) = 2
|
|
||||||
func _ = 3
|
|
||||||
|
|
||||||
#test listcomprehension-case-of
|
|
||||||
parserCompactLocation =
|
|
||||||
[ try
|
|
||||||
$ [ ParseRelAbs (Text.Read.read digits) _ _
|
|
||||||
| digits <- many1 digit
|
|
||||||
, rel1 :: Maybe (Either Int (Ratio Int)) <- optionMaybe
|
|
||||||
[ case divPart of
|
|
||||||
Nothing -> Left $ Text.Read.read digits
|
|
||||||
Just ddigits ->
|
|
||||||
Right $ Text.Read.read digits % Text.Read.read ddigits
|
|
||||||
| digits <- many1 digit
|
|
||||||
, divPart <- optionMaybe (string "/" *> many1 digit)
|
|
||||||
]
|
|
||||||
]
|
|
||||||
]
|
|
||||||
|
|
||||||
#test opapp-specialcasing-1
|
|
||||||
func = fooooooooooooooooooooooooooooooooo $ foooooooooooooooooooooooooooooooo
|
|
||||||
foooooooooooooooooooooooooooooooo
|
|
||||||
foooooooooooooooooooooooooooooooo
|
|
||||||
|
|
||||||
#test opapp-specialcasing-2
|
|
||||||
func =
|
|
||||||
fooooooooooooooooooooooooooooooooo
|
|
||||||
+ foooooooooooooooooooooooooooooooo foooooooooooooooooooooooooooooooo
|
|
||||||
foooooooooooooooooooooooooooooooo
|
|
||||||
|
|
||||||
#test opapp-specialcasing-3
|
|
||||||
func = fooooooooooooooooooooooooooooooooo + foooooooooooooooooooooooooooooooo
|
|
||||||
[ foooooooooooooooooooooooooooooooo
|
|
||||||
, foooooooooooooooooooooooooooooooo
|
|
||||||
, foooooooooooooooooooooooooooooooo
|
|
||||||
]
|
|
||||||
|
|
||||||
#test opapp-indenting
|
|
||||||
parserPrim =
|
|
||||||
[ r
|
|
||||||
| r <-
|
|
||||||
[ SGPPrimFloat $ bool id (0 -) minus $ readGnok "parserPrim"
|
|
||||||
(d1 ++ d2 ++ d3 ++ d4)
|
|
||||||
| d2 <- string "."
|
|
||||||
, d3 <- many1 (oneOf "0123456789")
|
|
||||||
, _ <- string "f"
|
|
||||||
]
|
|
||||||
<|> [ SGPPrimFloat $ bool id (0 -) minus $ fromIntegral
|
|
||||||
(readGnok "parserPrim" d1 :: Integer)
|
|
||||||
| _ <- string "f"
|
|
||||||
]
|
|
||||||
<|> [ SGPPrimInt $ bool id (0 -) minus $ fromIntegral
|
|
||||||
(readGnok "parserPrim" d1 :: Integer)
|
|
||||||
| _ <- string "i"
|
|
||||||
]
|
|
||||||
]
|
|
||||||
|
|
||||||
#test another-parspacing-testcase
|
|
||||||
|
|
||||||
samples = (SV.unpackaaaaadat) <&> \f ->
|
|
||||||
aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
|
|
||||||
|
|
||||||
#test recordupd-singleline-bug
|
|
||||||
|
|
||||||
runBrittany tabSize text = do
|
|
||||||
let config' = staticDefaultConfig
|
|
||||||
config = config'
|
|
||||||
{ _conf_layout = (_conf_layout config')
|
|
||||||
{ _lconfig_indentAmount = coerce tabSize
|
|
||||||
}
|
|
||||||
, _conf_forward = forwardOptionsSyntaxExtsEnabled
|
|
||||||
}
|
|
||||||
parsePrintModule config text
|
|
||||||
|
|
||||||
#test recordupd-singleline-bug-left
|
|
||||||
|
|
||||||
-- brittany { lconfig_indentPolicy: IndentPolicyLeft }
|
|
||||||
runBrittany tabSize text = do
|
|
||||||
let
|
|
||||||
config' = staticDefaultConfig
|
|
||||||
config = config'
|
|
||||||
{ _conf_layout = (_conf_layout config')
|
|
||||||
{ _lconfig_indentAmount = coerce tabSize
|
|
||||||
}
|
|
||||||
, _conf_forward = forwardOptionsSyntaxExtsEnabled
|
|
||||||
}
|
|
||||||
parsePrintModule config text
|
|
||||||
|
|
||||||
#test issue 37
|
|
||||||
|
|
||||||
foo =
|
|
||||||
( a
|
|
||||||
, -- comment1
|
|
||||||
b
|
|
||||||
-- comment2
|
|
||||||
, c
|
|
||||||
)
|
|
||||||
|
|
||||||
#test issue 38
|
|
||||||
|
|
||||||
{-# LANGUAGE TypeApplications #-}
|
|
||||||
foo = bar @Baz
|
|
||||||
|
|
||||||
#test comment-before-BDCols
|
|
||||||
{-# LANGUAGE TypeApplications #-}
|
|
||||||
layoutPatternBindFinal alignmentToken binderDoc mPatDoc clauseDocs = do
|
|
||||||
docAlt
|
|
||||||
$ -- one-line solution
|
|
||||||
[ docCols
|
|
||||||
(ColBindingLine alignmentToken)
|
|
||||||
[ docSeq (patPartInline ++ [guardPart])
|
|
||||||
, docSeq
|
|
||||||
[ appSep $ return binderDoc
|
|
||||||
, docForceSingleline $ return body
|
|
||||||
, wherePart
|
|
||||||
]
|
|
||||||
]
|
|
||||||
| not hasComments
|
|
||||||
, [(guards, body, _bodyRaw)] <- [clauseDocs]
|
|
||||||
, let guardPart = singleLineGuardsDoc guards
|
|
||||||
, wherePart <- case mWhereDocs of
|
|
||||||
Nothing -> return @[] $ docEmpty
|
|
||||||
Just [w] -> return @[] $ docSeq
|
|
||||||
[ docSeparator
|
|
||||||
, appSep $ docLit $ Text.pack "where"
|
|
||||||
, docSetIndentLevel $ docForceSingleline $ return w
|
|
||||||
]
|
|
||||||
_ -> []
|
|
||||||
]
|
|
||||||
++ -- one-line solution + where in next line(s)
|
|
||||||
[ docLines
|
|
||||||
$ [ docCols
|
|
||||||
(ColBindingLine alignmentToken)
|
|
||||||
[ docSeq (patPartInline ++ [guardPart])
|
|
||||||
, docSeq
|
|
||||||
[appSep $ return binderDoc, docForceParSpacing $ return body]
|
|
||||||
]
|
|
||||||
]
|
|
||||||
++ wherePartMultiLine
|
|
||||||
| [(guards, body, _bodyRaw)] <- [clauseDocs]
|
|
||||||
, let guardPart = singleLineGuardsDoc guards
|
|
||||||
, Data.Maybe.isJust mWhereDocs
|
|
||||||
]
|
|
||||||
++ -- two-line solution + where in next line(s)
|
|
||||||
[ docLines
|
|
||||||
$ [ docForceSingleline
|
|
||||||
$ docSeq (patPartInline ++ [guardPart, return binderDoc])
|
|
||||||
, docEnsureIndent BrIndentRegular $ docForceSingleline $ return
|
|
||||||
body
|
|
||||||
]
|
|
||||||
++ wherePartMultiLine
|
|
||||||
| [(guards, body, _bodyRaw)] <- [clauseDocs]
|
|
||||||
, let guardPart = singleLineGuardsDoc guards
|
|
||||||
]
|
|
||||||
|
|
||||||
#test comment-testcase-17
|
|
||||||
{-# LANGUAGE MultiWayIf #-}
|
|
||||||
func = do
|
|
||||||
let foo = if
|
|
||||||
| Constuctoooooooooooooooooooooooooooooooooooor `elem` artics -- TODO
|
|
||||||
-> max
|
|
||||||
(defLen - 0.2) -- TODO
|
|
||||||
(defLen * 0.8)
|
|
||||||
| otherwise -> max (defLen - 0.05) (defLen * 0.95) -- TODO
|
|
||||||
return True
|
|
||||||
|
|
||||||
#test issue 49
|
|
||||||
|
|
||||||
foo n = case n of
|
|
||||||
1 -> True
|
|
||||||
-1 -> False
|
|
||||||
|
|
||||||
bar n = case n of
|
|
||||||
(-2, -2) -> (-2, -2)
|
|
||||||
|
|
||||||
#test issue 48 b
|
|
||||||
|
|
||||||
{-# LANGUAGE TypeApplications #-}
|
|
||||||
foo =
|
|
||||||
let a = b @1
|
|
||||||
cccc = ()
|
|
||||||
in foo
|
|
||||||
|
|
||||||
#test issue 52 a
|
|
||||||
|
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
|
||||||
v = A { a = 1, .. } where b = 2
|
|
||||||
|
|
||||||
#test issue 52 b
|
|
||||||
|
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
|
||||||
v = A { .. } where b = 2
|
|
||||||
|
|
||||||
#test issue 52 c
|
|
||||||
|
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
|
||||||
v = A { a = 1, b = 2, c = 3 }
|
|
||||||
|
|
||||||
#test issue 63 a
|
|
||||||
test :: Proxy 'Int
|
|
||||||
|
|
||||||
#test issue 63 b
|
|
||||||
test :: Proxy '[ 'True]
|
|
||||||
|
|
||||||
#test issue 63 c
|
|
||||||
test :: Proxy '[Bool]
|
|
||||||
|
|
||||||
#test issue 64
|
|
||||||
{-# LANGUAGE RankNTypes, KindSignatures #-}
|
|
||||||
func
|
|
||||||
:: forall m str
|
|
||||||
. (Str str, Monad m)
|
|
||||||
=> Int
|
|
||||||
-> Proxy (str :: [*])
|
|
||||||
-> m (Tagged str String)
|
|
||||||
|
|
||||||
#test issue 65
|
|
||||||
widgetsDyn =
|
|
||||||
[ [ vBox
|
|
||||||
[ padTop Max outputLinesWidget
|
|
||||||
, padRight Max wid1 <+> flowWidget -- alignment here is strange/buggy
|
|
||||||
, padBottom (Pad 5) help
|
|
||||||
]
|
|
||||||
]
|
|
||||||
| wid1 <- promptDyn
|
|
||||||
, (flowWidget, _) <- flowResultD
|
|
||||||
, outputLinesWidget <- outputLinesWidgetD
|
|
||||||
, help <- suggestionHelpBox
|
|
||||||
, parser <- cmdParserD
|
|
||||||
]
|
|
||||||
|
|
||||||
#test issue 67
|
|
||||||
fmapuv :: U.Unbox a => (a -> b) -> U.Vector a -> V.Vector b
|
|
||||||
fmapuv f xs = G.generate (G.length xs) (f . (xs G.!))
|
|
||||||
|
|
||||||
|
|
||||||
#test parallellistcomp-workaround
|
|
||||||
cs0 = 0 : [ c / Interval n | c <- cs | n <- [1..] ]
|
|
||||||
|
|
||||||
#test issue 70
|
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
|
||||||
deriveFromJSON (unPrefix "assignPost") ''AssignmentPost
|
|
||||||
|
|
||||||
#test issue 110
|
|
||||||
main = -- a
|
|
||||||
let --b
|
|
||||||
x = 1 -- x
|
|
||||||
y = 2 -- y
|
|
||||||
in do
|
|
||||||
print x
|
|
||||||
print y
|
|
||||||
|
|
||||||
#test issue 111
|
|
||||||
alternatives :: Parser (Maybe Text)
|
|
||||||
alternatives =
|
|
||||||
alternativeOne -- first try this one
|
|
||||||
<|> alterantiveTwo -- then this one
|
|
||||||
<|> alternativeThree -- then this one
|
|
||||||
where
|
|
||||||
alternativeOne = purer "one"
|
|
||||||
alternativeTwo = purer "two"
|
|
||||||
alterantiveThree = purer "three"
|
|
||||||
|
|
||||||
#test issue 116
|
|
||||||
{-# LANGUAGE BangPatterns #-}
|
|
||||||
func = do
|
|
||||||
let !forced = some
|
|
||||||
pure ()
|
|
||||||
|
|
||||||
#test let-in-hanging
|
|
||||||
spanKey p q = case minViewWithKey q of
|
|
||||||
Just ((k, _), q') | p k ->
|
|
||||||
let (kas, q'') = spanKey p q' in ((k, a) : kas, q'')
|
|
||||||
_ -> ([], q)
|
|
||||||
|
|
||||||
#test issue 125
|
|
||||||
a :: () ':- ()
|
|
||||||
|
|
||||||
#test issue 128
|
|
||||||
func = do
|
|
||||||
createDirectoryIfMissing True path
|
|
||||||
openFile fileName AppendMode
|
|
||||||
|
|
||||||
#test hspar-comments
|
|
||||||
|
|
||||||
alternatives :: Parser (Maybe Text)
|
|
||||||
alternatives = -- a
|
|
||||||
( -- b
|
|
||||||
alternativeOne -- c
|
|
||||||
<|> alterantiveTwo -- d
|
|
||||||
<|> alternativeThree -- e
|
|
||||||
) -- f
|
|
||||||
|
|
||||||
#test issue 133
|
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
|
||||||
func
|
|
||||||
:: forall a
|
|
||||||
. ()
|
|
||||||
=> aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
|
|
||||||
-> aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
|
|
||||||
func
|
|
||||||
:: ()
|
|
||||||
=> aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
|
|
||||||
-> aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
|
|
||||||
|
|
||||||
#test alignment-potential-overflow
|
|
||||||
go l [] = Right l
|
|
||||||
go l ((IRType, _a) : eqr) = go l eqr
|
|
||||||
go l ((_, IRType) : eqr) = go l eqr
|
|
||||||
go _ ((IRTypeError ps t1 t2, _) : _) = Left $ makeError ps t1 t2
|
|
||||||
go _ ((_, IRTypeError ps t1 t2) : _) = Left $ makeError ps t1 t2
|
|
||||||
|
|
||||||
#test issue 89 - type-family-instance
|
|
||||||
type instance XPure StageParse = ()
|
|
||||||
type Pair a = (a, a)
|
|
||||||
|
|
||||||
#test issue 144
|
|
||||||
-- brittany { lconfig_indentAmount: 4, lconfig_indentPolicy: IndentPolicyMultiple }
|
|
||||||
dsfnjKeekbwwbosbOfakxqRsiyix cnehokzozwbVaguvu migbnaRwutbz =
|
|
||||||
let
|
|
||||||
eyuAfrarIso'
|
|
||||||
:: (RveoexdxunuAafalm -> Axlau (Axlau (a, OinejrdCplle)))
|
|
||||||
-> Gbodoy
|
|
||||||
-> Axlau (Axlau OinejrdCplle, Gbodoy)
|
|
||||||
eyuAfrarIso' = ulcPaaekBst cnehokzozwbVaguvu
|
|
||||||
amkgoxEhalazJjxunecCuIfaw
|
|
||||||
:: Axlau (Axlau OinejrdCplle, Gbodoy) -> Axlau RqlnrluYqednbCiggxi
|
|
||||||
amkgoxEhalazJjxunecCuIfaw uKqviuBisjtn = do
|
|
||||||
(sEmo, quc) <- uKqviuBisjtn
|
|
||||||
pure (xoheccewfWoeyiagOkfodiq sEmo quc)
|
|
||||||
xoheccewfWoeyiagOkfodiq
|
|
||||||
:: Axlau OinejrdCplle -> Gbodoy -> RqlnrluYqednbCiggxi
|
|
||||||
xoheccewfWoeyiagOkfodiq sEmo quc = case migbnaRwutbz of
|
|
||||||
Afogmf -> xgeqe (OfBkkuih quc) (Ciitog quc) sEmo
|
|
||||||
in QabqyilexuiNizzhsQuxxac migbnaRwutbz (hwaTihhjt lhowvscIiozgqe)
|
|
||||||
|
|
||||||
#test issue 159
|
|
||||||
spec = do
|
|
||||||
it "creates a snapshot at the given level" . withGraph runDB $ do
|
|
||||||
lift $ do
|
|
||||||
studentDiagnosticReadingLevel updatedStudent `shouldBe` Just 10 -- x
|
|
||||||
elaSnapshotReadingLevel snapshot `shouldBe` 12
|
|
||||||
|
|
||||||
#test non-bottom-specialcase-altsearch
|
|
||||||
jaicyhHumzo btrKpeyiFej mava = do
|
|
||||||
m :: VtohxeRgpmgsu <- qloxIfiq mava
|
|
||||||
case m of
|
|
||||||
ZumnaoFujayerIswadabo kkecm chlixxag -> do
|
|
||||||
imomue <- ozisduRaqiseSBAob btrKpeyiFej $ \s ->
|
|
||||||
case MizA.pigevo kkecm (_tc_gulawulu s) of
|
|
||||||
Ebocaba ->
|
|
||||||
( s { _tc_gulawulu = MizA.jxariu kkecm rwuRqxzhjo (_tc_gulawulu s) }
|
|
||||||
, Gtzvonm
|
|
||||||
)
|
|
||||||
Xcde{} -> (s, Pioemav)
|
|
||||||
pure imomue
|
|
||||||
|
|
||||||
#test issue 214
|
|
||||||
-- brittany { lconfig_indentPolicy: IndentPolicyMultiple }
|
|
||||||
foo = bar
|
|
||||||
arg1 -- this is the first argument
|
|
||||||
arg2 -- this is the second argument
|
|
||||||
arg3 -- this is the third argument, now I'll skip one comment
|
|
||||||
arg4
|
|
||||||
arg5 -- this is the fifth argument
|
|
||||||
arg6 -- this is the sixth argument
|
|
||||||
|
|
||||||
#test issue 234
|
|
||||||
|
|
||||||
True `nand` True = False
|
|
||||||
nand _ _ = True
|
|
||||||
|
|
||||||
nor False False = True
|
|
||||||
_ `nor` _ = False
|
|
||||||
|
|
||||||
#test issue 256 prefix operator match
|
|
||||||
|
|
||||||
f ((:) a as) = undefined
|
|
||||||
|
|
||||||
#test issue 228 lambda plus lazy or bang pattern
|
|
||||||
|
|
||||||
{-# LANGUAGE BangPatterns #-}
|
|
||||||
a = \x -> x
|
|
||||||
b = \ ~x -> x
|
|
||||||
c = \ !x -> x
|
|
||||||
d = \(~x) -> x
|
|
||||||
|
|
||||||
#test type signature with forall and constraint
|
|
||||||
{-# LANGUAGE RankNTypes #-}
|
|
||||||
func :: forall b . Show b => b -> String
|
|
||||||
|
|
||||||
#test issue 267
|
|
||||||
|
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
|
||||||
f :: ((~) a b) => a -> b
|
|
||||||
f = id
|
|
||||||
|
|
||||||
#test large record update
|
|
||||||
-- brittany { lconfig_indentPolicy: IndentPolicyLeft }
|
|
||||||
vakjkeSulxudbFokvir = Duotpo
|
|
||||||
{ _ekku_gcrpbze = xgonae (1 :: Int)
|
|
||||||
, _oola_louwu = FoqsiYcuidx
|
|
||||||
{ _xxagu_umea_iaztoj = xgonae False
|
|
||||||
, _tuktg_tizo_kfikacygsqf = xgonae False
|
|
||||||
, _ahzbo_xpow_otq_nzeyufq = xgonae False
|
|
||||||
, _uagpi_lzps_luy_xcjn = xgonae False
|
|
||||||
, _dxono_qjef_aqtafq_bes = xgonae False
|
|
||||||
, _yzuaf_nviy_vuhwxe_ihnbo_uhw = xgonae False
|
|
||||||
, _iwcit_fzjs_yerakt_dicox_mtryitko = xgonae False
|
|
||||||
, _ehjim_ucfe_dewarp_newrt_gso = xgonae False
|
|
||||||
, _ogtxb_ivoj_amqgai_rttui_xuwhetb = xgonae False
|
|
||||||
, _bhycb_iexz_megaug_qunoa_ohaked = xgonae False
|
|
||||||
, _nnmbe_uqgt_ewsuga_vaiis = xgonae False
|
|
||||||
, _otzil_ucvugaiyj_aosoiatunx_asir = xgonae False
|
|
||||||
}
|
|
||||||
, _iwsc_lalojz = XqspaiDainqw
|
|
||||||
{ _uajznac_ugah = xgonae (80 :: Int)
|
|
||||||
, _qayziku_gazibzDejipj = xgonae DewizeCxwgyiKjig
|
|
||||||
, _auhebll_fiqjxyArfxia = xgonae (2 :: Int)
|
|
||||||
, _zubfuhq_dupiwnIoophXameeet = xgonae True
|
|
||||||
, _oavnuqg_opkreyOufuIkifiin = xgonae True
|
|
||||||
, _ufojfwy_fhuzcePeqwfu = xgonae (50 :: Int)
|
|
||||||
, _mlosikq_zajdxxSeRoelpf = xgonae (50 :: Int)
|
|
||||||
, _heemavf_fjgOfoaikh = xgonae (FyoVfvdygaZuzuvbeWarwuq 3)
|
|
||||||
, _ohxmeoq_ogtbfoPtqezVseu = xgonae (EdjotoLcbapUdiuMmytwoig 0.7)
|
|
||||||
, _omupuiu_ituamexjuLccwu = xgonae (30 :: Int)
|
|
||||||
, _xoseksf_atvwwdwaoHanofMyUvujjopoz = xgonae True
|
|
||||||
, _umuuuat_nuamezwWeqfUqzrnaxwp = xgonae False
|
|
||||||
, _uuriguz_wixhutbuKecigaFiwosret = xgonae True
|
|
||||||
, _betohxp_scixaLsvcesErtwItxrnaJmuz = xgonae False
|
|
||||||
, _lchxgee_olaetGcqzuqxVujenCzexub = xgonae True
|
|
||||||
, _egeibao_imamkuigqikhZdcbpidokVcixiqew = xgonae False
|
|
||||||
}
|
|
||||||
, _nloo_cfmrgZcisiugk = YuwodSavxwnicBekuel
|
|
||||||
{ _oebew_rrtpvthUzlizjAqIwesly = xgonae False
|
|
||||||
, _blkff_Acxoid = xgonae False
|
|
||||||
, _datei_YewolAowoqOpunvpgu = xgonae BeekgUzojaPnixxaruJehyPmnnfu
|
|
||||||
, _ejfrj_eheb_justvh_pumcp_ismya = xgonae False
|
|
||||||
}
|
|
||||||
, _kena_uzeddovosoki = NyoRvshullezUpauud
|
|
||||||
{ _mtfuwi_TUVEmoi = xgonae RZXKoytUtogx
|
|
||||||
, _larqam_adaxPehaylZafeqgpc = xgonae False
|
|
||||||
}
|
|
||||||
, _spob_qipaarx = KaxavsmOtoyeaq { _rusrirw_okx = Tajemkix [] }
|
|
||||||
, _vmah_uivucnfka_ikaquebxay_gzcm = xgonae False
|
|
||||||
, _qaqb_eykzuyuwi = xgonae False
|
|
||||||
-- test comment
|
|
||||||
}
|
|
||||||
|
|
||||||
#test large record wildcard comment
|
|
||||||
|
|
||||||
-- brittany { lconfig_indentPolicy: IndentPolicyLeft }
|
|
||||||
vakjkeSulxudbFokvir = Duotpo
|
|
||||||
{ _ekku_gcrpbze = xgonae (1 :: Int)
|
|
||||||
, _spob_qipaarx = KaxavsmOtoyeaq { _rusrirw_okx = Tajemkix [] }
|
|
||||||
, _vmah_uivucnfka_ikaquebxay_gzcm = xgonae False
|
|
||||||
, _qaqb_eykzuyuwi = xgonae False
|
|
||||||
-- test comment
|
|
||||||
, -- N.B.
|
|
||||||
.. -- x
|
|
||||||
}
|
|
||||||
|
|
||||||
#test issue 263
|
|
||||||
|
|
||||||
func = abc + def
|
|
||||||
-- a
|
|
||||||
-- b
|
|
||||||
|
|
||||||
-- comment
|
|
||||||
|
|
||||||
where
|
|
||||||
abc = 13
|
|
||||||
def = 1
|
|
||||||
|
|
||||||
#test AddBaseY/EnsureIndent float in effect
|
|
||||||
|
|
||||||
zItazySunefp twgq nlyo lwojjoBiecao =
|
|
||||||
let mhIarjyai =
|
|
||||||
ukwAausnfcn
|
|
||||||
$ XojlsTOSR.vuwOvuvdAZUOJaa
|
|
||||||
$ XojlsTOSR.vkesForanLiufjeDI
|
|
||||||
$ XojlsTOSR.vkesForanLiufjeDI
|
|
||||||
$ XojlsTOSR.popjAyijoWarueeP
|
|
||||||
$ XojlsTOSR.jpwuPmafuDqlbkt nlyo
|
|
||||||
$ XojlsTOSR.jpwuPmafuDqlbkt xxneswWhxwng
|
|
||||||
$ XojlsTOSR.jpwuPmafuDqlbkt oloCuxeDdow
|
|
||||||
$ XojlsTOSR.jpwuPmafuDqlbkt (uwurrvoNnukzefuDjeh lwojjoBiecao nlyo)
|
|
||||||
$ etOslnoz lwojjoBiecao
|
|
||||||
in kucotg $ (bbbr, Yoxe.Dwzbuzi.zrLokoTnuy piv)
|
|
||||||
|
|
||||||
#test module initial comment
|
|
||||||
-- test
|
|
||||||
module MyModule where
|
|
||||||
|
|
||||||
#test issue 231
|
|
||||||
|
|
||||||
foo =
|
|
||||||
[ ("xxx", "xx")
|
|
||||||
, --
|
|
||||||
("xx" , "xx")
|
|
||||||
--
|
|
||||||
, ("xx" , "xxxxx")
|
|
||||||
, ("xx" , "xx")
|
|
||||||
]
|
|
||||||
|
|
||||||
#test issue 231 not
|
|
||||||
|
|
||||||
foo =
|
|
||||||
[ ("xx", "xx")
|
|
||||||
, ( "xx" --
|
|
||||||
, "xx"
|
|
||||||
)
|
|
||||||
, ("xx", "xxxxx")
|
|
||||||
, ("xx", "xx")
|
|
||||||
]
|
|
||||||
|
|
||||||
#test issue 281
|
|
||||||
|
|
||||||
module Main
|
|
||||||
( DataTypeI
|
|
||||||
, DataTypeII(DataConstructor)
|
|
||||||
-- * Haddock heading
|
|
||||||
, name
|
|
||||||
) where
|
|
||||||
|
|
||||||
#test type level list
|
|
||||||
|
|
||||||
xeoeqibIaib
|
|
||||||
:: ( KqujhIsaus m
|
|
||||||
, XivuvIpoboi Droqifim m
|
|
||||||
, IgorvOtowtf m
|
|
||||||
, RyagaYaqac m
|
|
||||||
, QouruDU m
|
|
||||||
)
|
|
||||||
=> MaptAdfuxgu
|
|
||||||
-> Zcnxg NsxayqmvIjsezea -- ^ if Lvqucoo, opsip jl reyoyhk lfil qaculxgd
|
|
||||||
-> QNOZqwuzg
|
|
||||||
-> Eoattuq
|
|
||||||
'[ XkatytdWdquraosu -- test comment
|
|
||||||
, KyezKijim -- another test comment
|
|
||||||
, DjmioeePuoeg
|
|
||||||
, NinrxoiOwezc
|
|
||||||
, QATAlrijacpk
|
|
||||||
, TrutvotwIwifiqOjdtu
|
|
||||||
, CoMmuatjwr
|
|
||||||
, BoZckzqyodseZole
|
|
||||||
, VagfwoXaeChfqe
|
|
||||||
]
|
|
||||||
m
|
|
||||||
()
|
|
||||||
|
|
||||||
#test recordupd-overflow-bad-multiline-spacing
|
|
||||||
|
|
||||||
createRedirectedProcess processConfig = do
|
|
||||||
let redirectedProc = (_processConfig_inner processConfig)
|
|
||||||
{ std_in = CreatePipe
|
|
||||||
, std_out = CreatePipe
|
|
||||||
, std_err = CreatePipe
|
|
||||||
}
|
|
||||||
foo
|
|
||||||
|
|
||||||
#test issue 282
|
|
||||||
|
|
||||||
instance HasDependencies SomeDataModel where
|
|
||||||
-- N.B. Here is a bunch of explanatory context about the relationship
|
|
||||||
-- between these data models or whatever.
|
|
||||||
type Dependencies SomeDataModel
|
|
||||||
= (SomeOtherDataModelId, SomeOtherOtherDataModelId)
|
|
||||||
|
|
||||||
#test stupid-do-operator-combination
|
|
||||||
|
|
||||||
func =
|
|
||||||
do
|
|
||||||
y
|
|
||||||
>>= x
|
|
|
@ -1,35 +0,0 @@
|
||||||
###############################################################################
|
|
||||||
###############################################################################
|
|
||||||
###############################################################################
|
|
||||||
#group pending
|
|
||||||
###############################################################################
|
|
||||||
###############################################################################
|
|
||||||
###############################################################################
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
## this testcase is not about idempotency, but about _how_ the output differs
|
|
||||||
## from the input; i cannot really express this yet with the current
|
|
||||||
## test-suite.
|
|
||||||
## #test ayaz
|
|
||||||
##
|
|
||||||
## myManageHook =
|
|
||||||
## composeOne [isFullscreen -?> doFullFloat, isDialog -?> doFloat, transience]
|
|
||||||
## <+> composeAll
|
|
||||||
## [ className =? "Pidgin" --> doFloat
|
|
||||||
## , className =? "XCalc" --> doFloat
|
|
||||||
## -- plan9port's acme
|
|
||||||
## , className =? "acme" --> doFloat
|
|
||||||
## -- Acme with Vi bindings editor
|
|
||||||
## , title =? "ED" --> doFloat
|
|
||||||
## , title =? "wlc-x11" --> doFloat
|
|
||||||
## , className =? "Skype" --> doFloat
|
|
||||||
## , className =? "ffplay" --> doFloat
|
|
||||||
## , className =? "mpv" --> doFloat
|
|
||||||
## , className =? "Plugin-container" --> doFloat -- Firefox flash, etc.
|
|
||||||
## -- Firefox works well tiled, but it has dialog windows we want to float.
|
|
||||||
## , appName =? "Browser" --> doFloat
|
|
||||||
## ]
|
|
||||||
## where
|
|
||||||
## role = stringProperty "WM_WINDOW_ROLE"
|
|
||||||
|
|
File diff suppressed because it is too large
Load Diff
|
@ -1,42 +0,0 @@
|
||||||
###############################################################################
|
|
||||||
###############################################################################
|
|
||||||
###############################################################################
|
|
||||||
#group indent-policy-multiple
|
|
||||||
###############################################################################
|
|
||||||
###############################################################################
|
|
||||||
###############################################################################
|
|
||||||
|
|
||||||
#test long
|
|
||||||
-- brittany { lconfig_indentAmount: 4, lconfig_indentPolicy: IndentPolicyMultiple }
|
|
||||||
func =
|
|
||||||
mweroiuxlskdfjlksjdflkjsdfljksldkjflkjsdflkj
|
|
||||||
+ mweroiuxlskdfjlksjdflkjsdfljksldkjflkjsdflkj
|
|
||||||
|
|
||||||
#test let indAmount=4
|
|
||||||
-- brittany { lconfig_indentAmount: 4, lconfig_indentPolicy: IndentPolicyMultiple }
|
|
||||||
foo = do
|
|
||||||
let aaaaaaaaaaaaaaaaaaaaaaaaaaaaaa =
|
|
||||||
aaaaaaaaaaaaaaaaaaaaaaaaaaaaaa + aaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
|
|
||||||
foo
|
|
||||||
|
|
||||||
#test let indAmount=8
|
|
||||||
-- brittany { lconfig_indentAmount: 8, lconfig_indentPolicy: IndentPolicyMultiple }
|
|
||||||
foo = do
|
|
||||||
let aaaaaaaaaaaaaaaaaaaaaaaaaaaaaa =
|
|
||||||
aaaaaaaaaaaaaaaaaaaaaaaaaaaaaa + aaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
|
|
||||||
foo
|
|
||||||
foo = do
|
|
||||||
let aaaaaaaaaaaaaaaaaaaaaaaaaaaaaa =
|
|
||||||
aaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
|
|
||||||
+ aaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
|
|
||||||
+ aaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
|
|
||||||
foo
|
|
||||||
|
|
||||||
#test nested do-block
|
|
||||||
-- brittany { lconfig_indentAmount: 4, lconfig_indentPolicy: IndentPolicyMultiple }
|
|
||||||
foo = asdyf8asdf
|
|
||||||
"ajsdfas"
|
|
||||||
[ asjdf asyhf $ do
|
|
||||||
aaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
|
|
||||||
aaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
|
|
||||||
]
|
|
|
@ -0,0 +1 @@
|
||||||
|
func :: a -> a
|
|
@ -0,0 +1,3 @@
|
||||||
|
func
|
||||||
|
:: lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
||||||
|
-> (lakjsdlkjasldkj -> lakjsdlkjasldkj)
|
|
@ -0,0 +1 @@
|
||||||
|
func = klajsdas klajsdas klajsdas
|
|
@ -0,0 +1,3 @@
|
||||||
|
func = lakjsdlajsdljasdlkjasldjasldjasldjalsdjlaskjd
|
||||||
|
lakjsdlajsdljasdlkjasldjasldjasldjalsdjlaskjd
|
||||||
|
lakjsdlajsdljasdlkjasldjasldjasldjalsdjlaskjd
|
|
@ -0,0 +1,3 @@
|
||||||
|
func = lakjsdlajsdljasdlkjasldjasldjasldjalsdjlaskjd lakjsdlajsdljas
|
||||||
|
lakjsdlajsdljas
|
||||||
|
lakjsdlajsdljas
|
|
@ -0,0 +1 @@
|
||||||
|
func = (1 +)
|
|
@ -0,0 +1 @@
|
||||||
|
func = (+ 1)
|
|
@ -0,0 +1 @@
|
||||||
|
func = (1 `abc`)
|
|
@ -0,0 +1 @@
|
||||||
|
func = (`abc` 1)
|
|
@ -0,0 +1 @@
|
||||||
|
func = (abc, def)
|
|
@ -0,0 +1 @@
|
||||||
|
func = (abc, )
|
|
@ -0,0 +1 @@
|
||||||
|
func = (, abc)
|
|
@ -0,0 +1,3 @@
|
||||||
|
func
|
||||||
|
:: (lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd -> lakjsdlkjasldkj)
|
||||||
|
-> lakjsdlkjasldkj
|
|
@ -0,0 +1,6 @@
|
||||||
|
myTupleSection =
|
||||||
|
( verylaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaargefirstelement
|
||||||
|
,
|
||||||
|
, verylaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaargethirdelement
|
||||||
|
,
|
||||||
|
)
|
|
@ -0,0 +1,4 @@
|
||||||
|
func =
|
||||||
|
( lakjsdlajsdljasdlkjasldjasldjasldjalsdjlaskjd
|
||||||
|
, lakjsdlajsdljasdlkjasldjasldjasldjalsdjlaskjd
|
||||||
|
)
|
|
@ -0,0 +1,6 @@
|
||||||
|
foo = if True
|
||||||
|
then
|
||||||
|
-- iiiiii
|
||||||
|
"a "
|
||||||
|
else
|
||||||
|
"b "
|
|
@ -0,0 +1,5 @@
|
||||||
|
func = if cond
|
||||||
|
then pure 42
|
||||||
|
else do
|
||||||
|
-- test
|
||||||
|
abc
|
|
@ -0,0 +1,3 @@
|
||||||
|
func = case x of
|
||||||
|
False -> False
|
||||||
|
True -> True
|
|
@ -0,0 +1,7 @@
|
||||||
|
func =
|
||||||
|
case
|
||||||
|
lakjsdlajsdljasdlkjasldjasldjasldjalsdjlaskjd
|
||||||
|
lakjsdlajsdljasdlkjasldjasldjasldjalsdjlaskjd
|
||||||
|
of
|
||||||
|
False -> False
|
||||||
|
True -> True
|
|
@ -0,0 +1,7 @@
|
||||||
|
func = do
|
||||||
|
case
|
||||||
|
lakjsdlajsdljasdlkjasldjasldjasldjalsdjlaskjd
|
||||||
|
lakjsdlajsdljasdlkjasldjasldjasldjalsdjlaskjd
|
||||||
|
of
|
||||||
|
False -> False
|
||||||
|
True -> True
|
|
@ -0,0 +1 @@
|
||||||
|
func = case x of {}
|
|
@ -0,0 +1,5 @@
|
||||||
|
func =
|
||||||
|
case
|
||||||
|
lakjsdlajsdljasdlkjasldjasldjasldjalsdjlaskjd
|
||||||
|
lakjsdlajsdljasdlkjasldjasldjasldjalsdjlaskjd
|
||||||
|
of {}
|
|
@ -0,0 +1,5 @@
|
||||||
|
func = do
|
||||||
|
case
|
||||||
|
lakjsdlajsdljasdlkjasldjasldjasldjalsdjlaskjd
|
||||||
|
lakjsdlajsdljasdlkjasldjasldjasldjalsdjlaskjd
|
||||||
|
of {}
|
|
@ -0,0 +1,5 @@
|
||||||
|
func
|
||||||
|
:: ( lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
||||||
|
-> lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
||||||
|
)
|
||||||
|
-> lakjsdlkjasldkj
|
|
@ -0,0 +1,3 @@
|
||||||
|
func = do
|
||||||
|
stmt
|
||||||
|
stmt
|
|
@ -0,0 +1,3 @@
|
||||||
|
func = do
|
||||||
|
x <- stmt
|
||||||
|
stmt x
|
|
@ -0,0 +1,3 @@
|
||||||
|
func = do
|
||||||
|
let x = 13
|
||||||
|
stmt x
|
|
@ -0,0 +1,7 @@
|
||||||
|
func =
|
||||||
|
foooooo
|
||||||
|
$ [ case
|
||||||
|
foooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooo
|
||||||
|
of
|
||||||
|
_ -> True
|
||||||
|
]
|
|
@ -0,0 +1,4 @@
|
||||||
|
testMethod foo bar baz qux =
|
||||||
|
let x = undefined foo bar baz qux qux baz bar :: String
|
||||||
|
-- some comment explaining the in expression
|
||||||
|
in undefined foo x :: String
|
|
@ -0,0 +1,4 @@
|
||||||
|
testMethod foo bar baz qux =
|
||||||
|
let x = undefined :: String
|
||||||
|
-- some comment explaining the in expression
|
||||||
|
in undefined :: String
|
|
@ -0,0 +1,3 @@
|
||||||
|
testMethod foo bar baz qux =
|
||||||
|
-- some comment explaining the in expression
|
||||||
|
let x = undefined :: String in undefined :: String
|
|
@ -0,0 +1,6 @@
|
||||||
|
foo foo bar baz qux =
|
||||||
|
let a = 1
|
||||||
|
b = 2
|
||||||
|
c = 3
|
||||||
|
-- some comment explaining the in expression
|
||||||
|
in undefined :: String
|
|
@ -0,0 +1,6 @@
|
||||||
|
func =
|
||||||
|
foo
|
||||||
|
$ [ aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
|
||||||
|
, bbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbb
|
||||||
|
]
|
||||||
|
++ [ccccccccccccccccccccccccccccccccccccccccccccccccccccccccc]
|
|
@ -0,0 +1 @@
|
||||||
|
module Main where
|
|
@ -0,0 +1,5 @@
|
||||||
|
func
|
||||||
|
:: ( ( lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
||||||
|
-> lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
||||||
|
)
|
||||||
|
)
|
|
@ -0,0 +1 @@
|
||||||
|
module Main () where
|
|
@ -0,0 +1 @@
|
||||||
|
module Main (main) where
|
|
@ -0,0 +1 @@
|
||||||
|
module Main (main, test1, test2) where
|
|
@ -0,0 +1,12 @@
|
||||||
|
module Main
|
||||||
|
( main
|
||||||
|
, test1
|
||||||
|
, test2
|
||||||
|
, test3
|
||||||
|
, test4
|
||||||
|
, test5
|
||||||
|
, test6
|
||||||
|
, test7
|
||||||
|
, test8
|
||||||
|
, test9
|
||||||
|
) where
|
|
@ -0,0 +1,12 @@
|
||||||
|
module Main
|
||||||
|
( main
|
||||||
|
-- main
|
||||||
|
, test1
|
||||||
|
, test2
|
||||||
|
-- Test 3
|
||||||
|
, test3
|
||||||
|
, test4
|
||||||
|
-- Test 5
|
||||||
|
, test5
|
||||||
|
-- Test 6
|
||||||
|
) where
|
|
@ -0,0 +1 @@
|
||||||
|
module Main (Test(..)) where
|
|
@ -0,0 +1 @@
|
||||||
|
module Main (module Main) where
|
|
@ -0,0 +1 @@
|
||||||
|
module Main (Test(Test, a, b)) where
|
|
@ -0,0 +1,6 @@
|
||||||
|
-- comment1
|
||||||
|
module Main
|
||||||
|
( Test(Test, a, b)
|
||||||
|
, foo -- comment2
|
||||||
|
) -- comment3
|
||||||
|
where
|
|
@ -0,0 +1 @@
|
||||||
|
module Main (Test()) where
|
|
@ -0,0 +1 @@
|
||||||
|
func :: asd -> Either a b
|
|
@ -0,0 +1 @@
|
||||||
|
-- Intentionally left empty
|
|
@ -0,0 +1 @@
|
||||||
|
import Data.List
|
|
@ -0,0 +1 @@
|
||||||
|
import Data.List as L
|
|
@ -0,0 +1 @@
|
||||||
|
import qualified Data.List
|
|
@ -0,0 +1 @@
|
||||||
|
import qualified Data.List as L
|
|
@ -0,0 +1 @@
|
||||||
|
import safe Data.List as L
|
|
@ -0,0 +1 @@
|
||||||
|
import {-# SOURCE #-} Data.List ( )
|
|
@ -0,0 +1 @@
|
||||||
|
import safe qualified Data.List
|
|
@ -0,0 +1 @@
|
||||||
|
import {-# SOURCE #-} safe qualified Data.List
|
|
@ -0,0 +1 @@
|
||||||
|
import qualified "base" Data.List
|
|
@ -0,0 +1,5 @@
|
||||||
|
func
|
||||||
|
:: asd
|
||||||
|
-> Either
|
||||||
|
lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
||||||
|
lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
|
@ -0,0 +1,3 @@
|
||||||
|
import {-# SOURCE #-} safe qualified "base" Data.List as L
|
||||||
|
import {-# SOURCE #-} safe qualified "base" Data.List ( )
|
||||||
|
import {-# SOURCE #-} safe qualified Data.List hiding ( )
|
|
@ -0,0 +1 @@
|
||||||
|
import qualified Data.List ( )
|
|
@ -0,0 +1 @@
|
||||||
|
import Data.List ( nub )
|
|
@ -0,0 +1,4 @@
|
||||||
|
import Data.List ( foldl'
|
||||||
|
, indexElem
|
||||||
|
, nub
|
||||||
|
)
|
|
@ -0,0 +1,14 @@
|
||||||
|
import Test ( Long
|
||||||
|
, anymore
|
||||||
|
, fit
|
||||||
|
, items
|
||||||
|
, line
|
||||||
|
, list
|
||||||
|
, not
|
||||||
|
, onA
|
||||||
|
, quite
|
||||||
|
, single
|
||||||
|
, that
|
||||||
|
, will
|
||||||
|
, with
|
||||||
|
)
|
|
@ -0,0 +1,11 @@
|
||||||
|
import Test ( (+)
|
||||||
|
, (:!)(..)
|
||||||
|
, (:*)((:.), T7, t7)
|
||||||
|
, (:.)
|
||||||
|
, T
|
||||||
|
, T2()
|
||||||
|
, T3(..)
|
||||||
|
, T4(T4)
|
||||||
|
, T5(T5, t5)
|
||||||
|
, T6((<|>))
|
||||||
|
)
|
|
@ -0,0 +1,3 @@
|
||||||
|
import Test hiding ( )
|
||||||
|
import Test as T
|
||||||
|
hiding ( )
|
|
@ -0,0 +1,13 @@
|
||||||
|
import Prelude as X
|
||||||
|
hiding ( head
|
||||||
|
, init
|
||||||
|
, last
|
||||||
|
, maximum
|
||||||
|
, minimum
|
||||||
|
, pred
|
||||||
|
, read
|
||||||
|
, readFile
|
||||||
|
, succ
|
||||||
|
, tail
|
||||||
|
, undefined
|
||||||
|
)
|
|
@ -0,0 +1,3 @@
|
||||||
|
import TestJustAbitToLongModuleNameLikeThisOneIs
|
||||||
|
( )
|
||||||
|
import TestJustShortEnoughModuleNameLikeThisOne ( )
|
|
@ -0,0 +1,3 @@
|
||||||
|
import TestJustAbitToLongModuleNameLikeThisOneI
|
||||||
|
as T
|
||||||
|
import TestJustShortEnoughModuleNameLikeThisOn as T
|
|
@ -0,0 +1,6 @@
|
||||||
|
func
|
||||||
|
:: asd
|
||||||
|
-> Trither
|
||||||
|
lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
||||||
|
lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
||||||
|
lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
|
@ -0,0 +1,3 @@
|
||||||
|
import TestJustAbitToLongModuleNameLikeTh
|
||||||
|
hiding ( )
|
||||||
|
import TestJustShortEnoughModuleNameLike hiding ( )
|
|
@ -0,0 +1,10 @@
|
||||||
|
import MoreThanSufficientlyLongModuleNameWithSome
|
||||||
|
( compact
|
||||||
|
, fit
|
||||||
|
, inA
|
||||||
|
, items
|
||||||
|
, layout
|
||||||
|
, not
|
||||||
|
, that
|
||||||
|
, will
|
||||||
|
)
|
|
@ -0,0 +1,11 @@
|
||||||
|
import TestJustAbitToLongModuleNameLikeTh
|
||||||
|
hiding ( abc
|
||||||
|
, def
|
||||||
|
, ghci
|
||||||
|
, jklm
|
||||||
|
)
|
||||||
|
import TestJustShortEnoughModuleNameLike hiding ( abc
|
||||||
|
, def
|
||||||
|
, ghci
|
||||||
|
, jklm
|
||||||
|
)
|
|
@ -0,0 +1,9 @@
|
||||||
|
import {-# SOURCE #-} safe qualified "qualifier" A hiding ( )
|
||||||
|
import {-# SOURCE #-} safe qualified "qualifiers" A
|
||||||
|
hiding ( )
|
||||||
|
import {-# SOURCE #-} safe qualified "qualifiers" AlsoAf as T
|
||||||
|
import {-# SOURCE #-} safe qualified "qualifiers" AlsoAff ( )
|
||||||
|
import {-# SOURCE #-} safe qualified "qualifiers" AlsoAff
|
||||||
|
as T
|
||||||
|
import {-# SOURCE #-} safe qualified "qualifiers" AlsoAffe
|
||||||
|
( )
|
|
@ -0,0 +1,7 @@
|
||||||
|
-- Test
|
||||||
|
import Data.List ( nub ) -- Test
|
||||||
|
{- Test -}
|
||||||
|
import qualified Data.List as L
|
||||||
|
( foldl' ) {- Test -}
|
||||||
|
-- Test
|
||||||
|
import Test ( test )
|
|
@ -0,0 +1,4 @@
|
||||||
|
import Test ( abc
|
||||||
|
, def
|
||||||
|
-- comment
|
||||||
|
)
|
|
@ -0,0 +1,3 @@
|
||||||
|
import Test ( abc
|
||||||
|
-- comment
|
||||||
|
)
|
|
@ -0,0 +1,8 @@
|
||||||
|
import Test ( abc
|
||||||
|
-- comment
|
||||||
|
, def
|
||||||
|
, ghi
|
||||||
|
{- comment -}
|
||||||
|
, jkl
|
||||||
|
-- comment
|
||||||
|
)
|
|
@ -0,0 +1,2 @@
|
||||||
|
import Test ( -- comment
|
||||||
|
)
|
|
@ -0,0 +1,8 @@
|
||||||
|
import Test ( longbindingNameThatoverflowsColum
|
||||||
|
)
|
||||||
|
import Test ( Long
|
||||||
|
( List
|
||||||
|
, Of
|
||||||
|
, Things
|
||||||
|
)
|
||||||
|
)
|
|
@ -0,0 +1,6 @@
|
||||||
|
func
|
||||||
|
:: Trither
|
||||||
|
lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
||||||
|
lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
||||||
|
lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
||||||
|
-> asd
|
|
@ -0,0 +1,18 @@
|
||||||
|
import Test ( Thing
|
||||||
|
( -- Comments
|
||||||
|
)
|
||||||
|
)
|
||||||
|
import Test ( Thing
|
||||||
|
( Item
|
||||||
|
-- and Comment
|
||||||
|
)
|
||||||
|
)
|
||||||
|
import Test ( Thing
|
||||||
|
( With
|
||||||
|
-- Comments
|
||||||
|
, and
|
||||||
|
-- also
|
||||||
|
, items
|
||||||
|
-- !
|
||||||
|
)
|
||||||
|
)
|
|
@ -0,0 +1,2 @@
|
||||||
|
import VeryLongModuleNameThatCouldEvenCauseAnEmptyBindingListToExpandIntoMultipleLine
|
||||||
|
( )
|
|
@ -0,0 +1,26 @@
|
||||||
|
{-# LANGUAGE BangPatterns #-}
|
||||||
|
{-
|
||||||
|
- Test module
|
||||||
|
-}
|
||||||
|
module Test
|
||||||
|
( test1
|
||||||
|
-- ^ test
|
||||||
|
, test2
|
||||||
|
-- | test
|
||||||
|
, test3
|
||||||
|
, test4
|
||||||
|
, test5
|
||||||
|
, test6
|
||||||
|
, test7
|
||||||
|
, test8
|
||||||
|
, test9
|
||||||
|
, test10
|
||||||
|
-- Test 10
|
||||||
|
) where
|
||||||
|
-- Test
|
||||||
|
import Data.List ( nub ) -- Test
|
||||||
|
{- Test -}
|
||||||
|
import qualified Data.List as L
|
||||||
|
( foldl' ) {- Test -}
|
||||||
|
-- Test
|
||||||
|
import Test ( test )
|
|
@ -0,0 +1,2 @@
|
||||||
|
import Aaa
|
||||||
|
import Baa
|
|
@ -0,0 +1,5 @@
|
||||||
|
import Zaa
|
||||||
|
import Zab
|
||||||
|
|
||||||
|
import Aaa
|
||||||
|
import Baa
|
|
@ -0,0 +1,2 @@
|
||||||
|
import Boo
|
||||||
|
import qualified Zoo
|
|
@ -0,0 +1,3 @@
|
||||||
|
import Boo ( a )
|
||||||
|
|
||||||
|
import Boo ( b )
|
|
@ -0,0 +1,2 @@
|
||||||
|
import A.B.C
|
||||||
|
import A.B.D
|
|
@ -0,0 +1 @@
|
||||||
|
type MySynonym = String
|
|
@ -0,0 +1 @@
|
||||||
|
type MySynonym a = [a]
|
|
@ -0,0 +1,5 @@
|
||||||
|
func
|
||||||
|
:: Trither
|
||||||
|
lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
||||||
|
lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd
|
||||||
|
(lkasdlkjalsdjlakjsdlkjasldkjalskdjlkajsd -> asd)
|
|
@ -0,0 +1,3 @@
|
||||||
|
-- | Important comment thrown in
|
||||||
|
type MySynonym b a
|
||||||
|
= MySynonym a b -> MySynonym a b -> MyParamType a b -> MyParamType a b
|
|
@ -0,0 +1,7 @@
|
||||||
|
type MySynonym3 b a
|
||||||
|
= MySynonym a b
|
||||||
|
-> MySynonym a b
|
||||||
|
-- ^ RandomComment
|
||||||
|
-> MyParamType a b
|
||||||
|
-> MyParamType a b
|
||||||
|
-> MySynonym2 b a
|
|
@ -0,0 +1,7 @@
|
||||||
|
{-# LANGUAGE StarIsType #-}
|
||||||
|
type MySynonym (a :: * -> *)
|
||||||
|
= MySynonym a b
|
||||||
|
-> MySynonym a b
|
||||||
|
-> MyParamType a b
|
||||||
|
-> MyParamType a b
|
||||||
|
-> MySynonym2 b a
|
Some files were not shown because too many files have changed in this diff Show More
Loading…
Reference in New Issue