From 0165fcdb35eab5a5b8dc750146e332d7f798acff Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Thu, 22 Sep 2022 18:38:43 +0900 Subject: [PATCH 01/24] Add tests that previous ones did not cover This commit is split from https://github.com/mihaimaruseac/hindent/pull/593 to reduce the PR's size. --- TESTS.md | 321 +++++++++++++++++++++++++++++++++++++++++++++++++++++-- 1 file changed, 314 insertions(+), 7 deletions(-) diff --git a/TESTS.md b/TESTS.md index 287e65a5e..af0cb6987 100644 --- a/TESTS.md +++ b/TESTS.md @@ -30,6 +30,16 @@ Extension pragmas fun @Int 12 ``` +A pragma's length is adjusted automatically + +```haskell given +{-# LANGUAGE OverloadedStrings #-} +``` + +```haskell expect +{-# LANGUAGE OverloadedStrings #-} +``` + Module header ``` haskell @@ -132,13 +142,13 @@ Type declaration type EventSource a = (AddHandler a, a -> IO ()) ``` -Type declaration with infix promoted type constructor +Type declaration with promoted lists ```haskell -fun1 :: Def ('[ Ref s (Stored Uint32), IBool] 'T.:-> IBool) +fun1 :: Def ('[ Ref s (Stored Uint32), IBool] T.:-> IBool) fun1 = undefined -fun2 :: Def ('[ Ref s (Stored Uint32), IBool] ':-> IBool) +fun2 :: Def ('[ Ref s (Stored Uint32), IBool] :-> IBool) fun2 = undefined ``` @@ -165,6 +175,15 @@ instance Bool :?: Bool instance (:?:) Int Bool ``` +An instance declaration with a comment between the header and `where`. + +```haskell +instance Pretty MatchForCase + -- TODO: Do not forget to handle comments! + where + pretty' = undefined +``` + GADT declarations ```haskell @@ -178,6 +197,12 @@ data Ty :: (* -> *) where # Expressions +A minus sign + +```haskell +f = -(3 + 5) +``` + Lazy patterns in a lambda ``` haskell @@ -293,6 +318,25 @@ strToMonth month = _ -> error $ "Unknown month " ++ month ``` +Lambda in case + +```haskell +f x = + case filter (\y -> isHappy y x) of + [] -> Nothing + (z:_) -> Just (\a b -> makeSmile z a b) +``` + +A guard in a case + +```haskell +f = + case g of + [] + | even h -> Nothing + _ -> undefined +``` + Operators, bad ``` haskell @@ -311,6 +355,14 @@ x = Just thisissolong <*> Just stilllonger <*> evenlonger ``` +`$` chain + +```haskell +f = + Right $ + S.lazyByteStrings $ addPrefix prefix $ S.toLazyByteString $ prettyPrint m +``` + Operator with `do` ```haskell @@ -319,6 +371,23 @@ for xs $ do right x ``` +`do` with a binding + +```haskell +foo = do + mcp <- findCabalFiles (takeDirectory abssrcpath) (takeFileName abssrcpath) + print mcp +``` + +A `let` with a signature inside a `do` + +```haskell +f = do + let try :: Typeable b => b + try = undefined + undefined +``` + Operator with lambda ```haskell @@ -431,6 +500,28 @@ type family Closed (a :: k) :: Bool where Closed x = 'True ``` +Sections +```haskell +double = (2 *) + +halve = (/ 2) +``` + +A field updater in a `do` inside a `let ... in`. + +```haskell +f = undefined + where + g h = + let x = undefined + in do foo + pure + h + { grhssLocalBinds = + HsValBinds x (ValBinds (newSigs newSigMethods)) + } +``` + # Template Haskell Expression brackets @@ -470,6 +561,38 @@ g = # Type signatures +A long signature inside a where clause + +```haskell +cppSplitBlocks :: ByteString -> [CodeBlock] +cppSplitBlocks inp = undefined + where + spanCPPLines :: + [(Int, ByteString)] -> ([(Int, ByteString)], [(Int, ByteString)]) + spanCPPLines = undefined +``` + +A `forall` type inside a where clause + +```haskell +replaceAllNotUsedAnns :: HsModule -> HsModule +replaceAllNotUsedAnns = everywhere app + where + app :: + forall a. Data a + => (a -> a) + app = undefined + +f :: a +f = undefined + where + ggg :: + forall a. Typeable a + => a + -> a + ggg = undefined +``` + Long argument list should line break ```haskell @@ -569,6 +692,16 @@ c :: '(:->) 'True 'False d :: (:->) 'True 'False ``` +`forall` type + +```haskell +f :: (forall a. Data a => + a -> a) + -> (forall a. Data a => + a -> a) +f = undefined +``` + # Function declarations Prefix notation for operators @@ -578,6 +711,12 @@ Prefix notation for operators (+) a b = a ``` +As pattern + +```haskell +f all@(x:xs) = all +``` + Where clause ``` haskell @@ -588,6 +727,41 @@ sayHello = do greeting name = "Hello, " ++ name ++ "!" ``` +An empty line is inserted after an empty `where` + +```haskell given +f = evalState + -- A comment + where +``` + +```haskell expect +f = evalState + -- A comment + where + +``` + +Multiple function declarations with an empty `where` + +```haskell +f = undefined + where + + +g = undefined +``` + +A `where` clause between instance functions. + +```haskell +instance Pretty HsModule where + pretty' = undefined + where + a = b + commentsBefore = Nothing +``` + Guards and pattern guards ``` haskell @@ -601,6 +775,22 @@ f x x = y ``` +Guard and infix operator +```haskell +s8_stripPrefix bs1@(S.PS _ _ l1) bs2 + | bs1 `S.isPrefixOf` bs2 = Just (S.unsafeDrop l1 bs2) + | otherwise = Nothing +``` + +A `do` inside a guard arm + +```haskell +f + | x == 1 = do + a + b +``` + Multi-way if ``` haskell @@ -628,6 +818,36 @@ g x = y = 2 ``` +A `case` inside a `let`. + +```haskell +f = do + let (x, xs) = + case gs of + [] -> undefined + (x':xs') -> (x', xs') + undefined +``` + +A `do` inside a lambda. + +```haskell +printCommentsAfter = + case commentsAfter p of + xs -> do + forM_ xs $ \(L loc c) -> do + eolCommentsArePrinted +``` + +Case with natural pattern (See NPat of https://hackage.haskell.org/package/ghc-lib-parser-9.2.3.20220527/docs/Language-Haskell-Syntax-Pat.html#t:Pat) + +```haskell +foo = + case x of + 0 -> pure () + _ -> undefined +``` + Let inside a `where` ``` haskell @@ -641,6 +861,15 @@ g x = in y ``` +Let containing a type signature inside a `do` + +```haskell +f = do + let g :: Int + g = 3 + print g +``` + Lists ``` haskell @@ -701,6 +930,27 @@ test ,) ``` +Match against a list + +```haskell +head [] = undefined +head [x] = x +head xs = head $ init xs +``` + +Range + +```haskell +a = [1 ..] +``` + +View pattern + +```haskell +foo (f -> Just x) = print x +foo _ = Nothing +``` + # Record syntax Pattern matching, short @@ -723,6 +973,14 @@ fun Rec { alpha = beta beta + delta + zeta + theta + kappa + mu + beta + delta + zeta + theta + kappa ``` +Another pattern matching, long + +```haskell +resetModuleStartLine m@HsModule { hsmodAnn = epa@EpAnn {..} + , hsmodName = Just (L (SrcSpanAnn _ (RealSrcSpan sp _)) _) + } = undefined +``` + Symbol constructor, short ```haskell @@ -824,6 +1082,16 @@ data Expression a } ``` +Data declaration with underscore + +```haskell +data Stanza = + MkStanza + { _stanzaBuildInfo :: BuildInfo + , stanzaIsSourceFilePath :: FilePath -> Bool + } +``` + Spaces between deriving classes ``` haskell @@ -853,8 +1121,38 @@ foo = cFunction fooo barrr muuu (fooo barrr muuu) (fooo barrr muuu) ``` +Case inside `do` and lambda + +```haskell +foo = + \x -> do + case x of + Just _ -> 1 + Nothing -> 2 +``` + # Comments +A module header with comments + +```haskell +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE PatternGuards #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE ScopedTypeVariables #-} + +-- | Haskell indenter. +module HIndent + -- * Formatting functions. + ( reformat + , prettyPrint + -- * Testing + , defaultExtensions + , getExtensions + , testAst + ) where +``` + Comments within a declaration ``` haskell @@ -1160,6 +1458,16 @@ Escaped newlines x ``` +A blank line is inserted after an `infixl`. + +```haskell +(^-^) = undefined + +infixl 1 ^-^ + +f = undefined +``` + # Regression tests jml Adds trailing whitespace when wrapping #221 @@ -1594,8 +1902,9 @@ class Foo a b c d e f utdemir Hindent breaks TH name captures of operators #412 -```haskell +```haskell pending -- https://github.com/commercialhaskell/hindent/issues/412 +-- This code compile on GHC 8.0.2 but does not from 8.2.2. data T = (-) @@ -1710,7 +2019,7 @@ class (Eq a, Show a) => fromInteger :: Integer -> a ``` -michalrus `let … in …` inside of `do` breaks compilation #467 +michalrus `let ... in ...` inside of `do` breaks compilation #467 ```haskell -- https://github.com/commercialhaskell/hindent/issues/467 @@ -1738,8 +2047,6 @@ schroffl Hindent produces invalid Syntax from FFI exports #479 -- https://github.com/commercialhaskell/hindent/issues/479 foreign export ccall "test" test :: IO () -foreign import ccall "test" test :: IO () - foreign import ccall safe "test" test :: IO () foreign import ccall unsafe "test" test :: IO () From 28bd28eade8a33c5e2d709e9b079ccf426e9b130 Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Thu, 22 Sep 2022 18:52:13 +0900 Subject: [PATCH 02/24] Fix a test --- TESTS.md | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/TESTS.md b/TESTS.md index af0cb6987..10037ccfd 100644 --- a/TESTS.md +++ b/TESTS.md @@ -835,8 +835,7 @@ A `do` inside a lambda. printCommentsAfter = case commentsAfter p of xs -> do - forM_ xs $ \(L loc c) -> do - eolCommentsArePrinted + forM_ xs $ \(L loc c) -> do eolCommentsArePrinted ``` Case with natural pattern (See NPat of https://hackage.haskell.org/package/ghc-lib-parser-9.2.3.20220527/docs/Language-Haskell-Syntax-Pat.html#t:Pat) From 078b340ea73db547af6ab0f1cd7d0874ad2f14a8 Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Thu, 29 Sep 2022 13:03:16 +0900 Subject: [PATCH 03/24] Add tests --- TESTS.md | 12 ++++++++++-- 1 file changed, 10 insertions(+), 2 deletions(-) diff --git a/TESTS.md b/TESTS.md index 10037ccfd..7ea029086 100644 --- a/TESTS.md +++ b/TESTS.md @@ -700,6 +700,9 @@ f :: (forall a. Data a => -> (forall a. Data a => a -> a) f = undefined + +g :: forall a b. a -> b +g = undefined ``` # Function declarations @@ -1753,7 +1756,10 @@ ttuegel Record formatting applied to expressions with RecordWildCards #274 ```haskell -- https://github.com/chrisdone/hindent/issues/274 -foo (Bar {..}) = Bar {..} +foo (bar@Bar {..}) = Bar {..} + +resetModuleNameColumn m@HsModule {hsmodName = Just (L (SrcSpanAnn epa@EpAnn {..} sp) name)} = + m ``` RecursiveDo `rec` and `mdo` keyword #328 @@ -2108,7 +2114,9 @@ topLevelFunc2 = f . g {- multi line comment -} - f = undefined + f = undefined -- single line comment -- single line comment + -- Different size of indents + g :: a g = undefined ``` From 262b608bffaf82e26ef5e9dc584e9f393fd2d910 Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Thu, 29 Sep 2022 14:40:04 +0900 Subject: [PATCH 04/24] Add a test --- TESTS.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/TESTS.md b/TESTS.md index 7ea029086..4088d6ed5 100644 --- a/TESTS.md +++ b/TESTS.md @@ -697,8 +697,8 @@ d :: (:->) 'True 'False ```haskell f :: (forall a. Data a => a -> a) - -> (forall a. Data a => - a -> a) + -> (forall a b. Data a => + a -> b) f = undefined g :: forall a b. a -> b From 5019e9dadf9a1619e6d01c24dfe5f1ab17e3f637 Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Thu, 29 Sep 2022 22:37:58 +0900 Subject: [PATCH 05/24] Add a test --- TESTS.md | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) diff --git a/TESTS.md b/TESTS.md index 4088d6ed5..ef04b3740 100644 --- a/TESTS.md +++ b/TESTS.md @@ -1321,6 +1321,22 @@ main = putStrLn "Hello, World!" {- This is another random comment. -} ``` +Comments in a 'where' clause + +```haskell +everywhereMEpAnnsInOrder cmp f hm = undefined + where + collectEpAnnsInOrderEverywhereMTraverses + -- This function uses 'everywhereM' to collect 'EpAnn's because they + -- should be collected in the same order as 'putModifiedEpAnnsToModule' + -- puts them to the AST. + = reverse <$> execStateT (everywhereM collectEpAnnsST hm) [] + where + collectEpAnns x + -- If 'a' is 'EpAnn b' ('b' can be any type), wrap 'x' with a 'Wrapper'. + | otherwise = id +``` + # MINIMAL pragma Monad example From 58c0c292d392a2d7eca2ecac7745ec7fd91e863a Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Thu, 29 Sep 2022 22:51:32 +0900 Subject: [PATCH 06/24] Update a test --- TESTS.md | 15 ++++++--------- 1 file changed, 6 insertions(+), 9 deletions(-) diff --git a/TESTS.md b/TESTS.md index ef04b3740..f23198978 100644 --- a/TESTS.md +++ b/TESTS.md @@ -1324,17 +1324,14 @@ main = putStrLn "Hello, World!" Comments in a 'where' clause ```haskell -everywhereMEpAnnsInOrder cmp f hm = undefined +foo = undefined where - collectEpAnnsInOrderEverywhereMTraverses - -- This function uses 'everywhereM' to collect 'EpAnn's because they - -- should be collected in the same order as 'putModifiedEpAnnsToModule' - -- puts them to the AST. - = reverse <$> execStateT (everywhereM collectEpAnnsST hm) [] + bar + -- A comment + = undefined where - collectEpAnns x - -- If 'a' is 'EpAnn b' ('b' can be any type), wrap 'x' with a 'Wrapper'. - | otherwise = id + a = b + baz = undefined ``` # MINIMAL pragma From 6cf1be084c4cc29ea89a84611e62bfd4c657a97d Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Fri, 30 Sep 2022 17:09:44 +0900 Subject: [PATCH 07/24] Add a test for using a wildcard and a binding --- TESTS.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/TESTS.md b/TESTS.md index f23198978..2830f189e 100644 --- a/TESTS.md +++ b/TESTS.md @@ -1773,6 +1773,8 @@ foo (bar@Bar {..}) = Bar {..} resetModuleNameColumn m@HsModule {hsmodName = Just (L (SrcSpanAnn epa@EpAnn {..} sp) name)} = m + +bar Bar {baz = before, ..} = Bar {baz = after, ..} ``` RecursiveDo `rec` and `mdo` keyword #328 From 447dabb2e258907d641d745da1b510d1facfc714 Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Fri, 30 Sep 2022 17:39:22 +0900 Subject: [PATCH 08/24] Add a haddock test --- TESTS.md | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/TESTS.md b/TESTS.md index 2830f189e..48e5715cd 100644 --- a/TESTS.md +++ b/TESTS.md @@ -1254,6 +1254,12 @@ data X = -- ^ This is a long comment which starts on the following line -- from from the field, lines continue at the sme column. } + +foo :: + String -- ^ Reason for eating pizza. + -> Int -- ^ How many did you eat pizza? + -> String -- ^ The report. +foo = undefined ``` Comments around regular declarations From 1c40aae3ebaf7d980c2358679de38602870ee395 Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Fri, 30 Sep 2022 23:05:18 +0900 Subject: [PATCH 09/24] Add a test --- TESTS.md | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/TESTS.md b/TESTS.md index 48e5715cd..d109168d6 100644 --- a/TESTS.md +++ b/TESTS.md @@ -561,6 +561,12 @@ g = # Type signatures +Multiple function signatures at once + +```haskell +a, b, c :: Int +``` + A long signature inside a where clause ```haskell From 414d2206d317f8f4142982c3df1413be17c20161 Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Fri, 30 Sep 2022 23:15:59 +0900 Subject: [PATCH 10/24] Add a test --- TESTS.md | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/TESTS.md b/TESTS.md index d109168d6..fa912c6dc 100644 --- a/TESTS.md +++ b/TESTS.md @@ -30,6 +30,17 @@ Extension pragmas fun @Int 12 ``` +Pragmas and GHC pragmas + +```haskell +{-# LANGUAGE CPP #-} +{-# LANGUAGE NoRebindableSyntax #-} +{-# OPTIONS_GHC -fno-warn-missing-import-lists #-} +{-# OPTIONS_GHC -w #-} + +module Paths_hindent where +``` + A pragma's length is adjusted automatically ```haskell given From 275c008985c98ccb0380e5f173727bb2019809cb Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Sat, 1 Oct 2022 08:39:45 +0900 Subject: [PATCH 11/24] Add a test --- TESTS.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/TESTS.md b/TESTS.md index fa912c6dc..5f77305f4 100644 --- a/TESTS.md +++ b/TESTS.md @@ -955,6 +955,8 @@ Match against a list head [] = undefined head [x] = x head xs = head $ init xs + +foo [Coord _ _, Coord _ _] = undefined ``` Range From d69b635444679af7d418874a2aea81a5c88e83fc Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Sat, 1 Oct 2022 09:20:05 +0900 Subject: [PATCH 12/24] Add a test --- TESTS.md | 1 + 1 file changed, 1 insertion(+) diff --git a/TESTS.md b/TESTS.md index 5f77305f4..9ed74b404 100644 --- a/TESTS.md +++ b/TESTS.md @@ -2150,6 +2150,7 @@ topLevelFunc1 = f f = undefined topLevelFunc2 = f . g + -- Another comment where {- multi line From 774908f181b673e2676eacca076ff1f65bc7567e Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Sat, 1 Oct 2022 09:55:23 +0900 Subject: [PATCH 13/24] Add a test --- TESTS.md | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/TESTS.md b/TESTS.md index 9ed74b404..0eb97e651 100644 --- a/TESTS.md +++ b/TESTS.md @@ -1113,6 +1113,15 @@ data Stanza = } ``` +Multiple constructors at once + +```haskell +data Foo = + Foo + { foo, bar, baz, qux, quux :: Int + } +``` + Spaces between deriving classes ``` haskell From dfb02cffe474ec5d2cc6c012dad62820722b9696 Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Sat, 1 Oct 2022 10:27:45 +0900 Subject: [PATCH 14/24] Add a test --- TESTS.md | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/TESTS.md b/TESTS.md index 0eb97e651..48e3fdda4 100644 --- a/TESTS.md +++ b/TESTS.md @@ -1368,6 +1368,18 @@ foo = undefined baz = undefined ``` +Haddocks around data constructors + +```haskell +data Foo + -- | A haddock comment for 'Bar'. + = Bar + -- | A haddock comment for 'Baz'. + | Baz + -- | A haddock comment for 'Baz'. + | Quuz +``` + # MINIMAL pragma Monad example From b170b2ceb9838c46f1fc00425ca0a5030abffd05 Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Sat, 1 Oct 2022 10:56:22 +0900 Subject: [PATCH 15/24] Fix a test --- TESTS.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/TESTS.md b/TESTS.md index 48e3fdda4..76847d284 100644 --- a/TESTS.md +++ b/TESTS.md @@ -1376,7 +1376,7 @@ data Foo = Bar -- | A haddock comment for 'Baz'. | Baz - -- | A haddock comment for 'Baz'. + -- | A haddock comment for 'Quuz'. | Quuz ``` From 29a206ce2d712f9f63a7029837e5715a80cdd5e1 Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Sat, 1 Oct 2022 10:59:52 +0900 Subject: [PATCH 16/24] Add a test --- TESTS.md | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/TESTS.md b/TESTS.md index 76847d284..cc5cf5c61 100644 --- a/TESTS.md +++ b/TESTS.md @@ -782,6 +782,16 @@ instance Pretty HsModule where commentsBefore = Nothing ``` +A `DEPRECATED`. + +```haskell +{-# DEPRECATED +giveUp "Never give up." + #-} + +giveUp = undefined +``` + Guards and pattern guards ``` haskell From 627323d4b54616315d211e3d9ceac6f3875d07a1 Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Sat, 1 Oct 2022 11:55:48 +0900 Subject: [PATCH 17/24] Add a test --- TESTS.md | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/TESTS.md b/TESTS.md index cc5cf5c61..929b3923d 100644 --- a/TESTS.md +++ b/TESTS.md @@ -1265,6 +1265,15 @@ gamma = do alpha = alpha ``` +Comments in a class declaration + +```haskell +class Foo a + -- A comment + where + foo :: a -> Int +``` + Haddock comments ``` haskell From 264f77122599521e7c47e545d018f21fb40728de Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Sat, 1 Oct 2022 16:30:48 +0900 Subject: [PATCH 18/24] Add a test --- TESTS.md | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/TESTS.md b/TESTS.md index 929b3923d..0244583f4 100644 --- a/TESTS.md +++ b/TESTS.md @@ -30,15 +30,16 @@ Extension pragmas fun @Int 12 ``` -Pragmas and GHC pragmas +Pragmas, GHC options, and haddock options. ```haskell {-# LANGUAGE CPP #-} {-# LANGUAGE NoRebindableSyntax #-} {-# OPTIONS_GHC -fno-warn-missing-import-lists #-} {-# OPTIONS_GHC -w #-} +{-# OPTIONS_HADDOCK show-extensions #-} -module Paths_hindent where +module Foo where ``` A pragma's length is adjusted automatically From 53ca1d4a26d26389a5de10f3d329f671e73e3fb9 Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Sat, 1 Oct 2022 16:31:54 +0900 Subject: [PATCH 19/24] Add a test --- TESTS.md | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/TESTS.md b/TESTS.md index 0244583f4..378ee37ee 100644 --- a/TESTS.md +++ b/TESTS.md @@ -666,6 +666,13 @@ class Foo a where bar = mappend ``` +Class methods with constraints + +```haskell +class Foo f where + myEq :: (Eq a) => f a -> f a -> Bool +``` + Implicit parameters ```haskell From f13c3bef43266a0ba7544b727f52e24ef4bdc39f Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Sat, 1 Oct 2022 20:15:05 +0900 Subject: [PATCH 20/24] Add a test --- TESTS.md | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/TESTS.md b/TESTS.md index 378ee37ee..f0bf7efbb 100644 --- a/TESTS.md +++ b/TESTS.md @@ -146,6 +146,16 @@ import Name hiding () import {-# SOURCE #-} safe qualified Module as M hiding (a, b, c, d, e, f) ``` +An import declaration importing lots of data constructors + +```haskell +import Direction + ( Direction(East, North, NorthEast, NorthWest, South, SouthEast, + SouthWest, West) + , allDirections + ) +``` + # Declarations Type declaration From fcf4e57e15ccba8fe52939fe9a203274fdb50a4c Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Sun, 2 Oct 2022 11:28:38 +0900 Subject: [PATCH 21/24] Add a test --- TESTS.md | 1 + 1 file changed, 1 insertion(+) diff --git a/TESTS.md b/TESTS.md index f0bf7efbb..8066d6182 100644 --- a/TESTS.md +++ b/TESTS.md @@ -68,6 +68,7 @@ module X , y , Z , P(x, z) + , module Foo ) where ``` From da4cc54ca00502331b8ce9fb1c30057b1de0539a Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Sun, 2 Oct 2022 11:35:04 +0900 Subject: [PATCH 22/24] Add a test --- TESTS.md | 1 + 1 file changed, 1 insertion(+) diff --git a/TESTS.md b/TESTS.md index 8066d6182..0ef075cd0 100644 --- a/TESTS.md +++ b/TESTS.md @@ -88,6 +88,7 @@ module X Import lists ``` haskell +import Control.Lens (_2, _Just) import Data.Text import Data.Text import qualified Data.Text as T From 56e83f25b956dfb0f385af8f13455b83ae926be9 Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Sun, 2 Oct 2022 12:00:40 +0900 Subject: [PATCH 23/24] Add a test --- TESTS.md | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/TESTS.md b/TESTS.md index 0ef075cd0..aa8db24dd 100644 --- a/TESTS.md +++ b/TESTS.md @@ -531,6 +531,16 @@ double = (2 *) halve = (/ 2) ``` +A section with a large RHS. + +```haskell +foo = + (`elem` concat + [ [20, 68, 92, 112, 28, 124, 116, 80] + , [21, 84, 87, 221, 127, 255, 241, 17] + ]) +``` + A field updater in a `do` inside a `let ... in`. ```haskell From 23e8c4795aaed6b4f9d1aa8af205aafa08116ba8 Mon Sep 17 00:00:00 2001 From: Hiroki Tokunaga Date: Sun, 2 Oct 2022 12:45:22 +0900 Subject: [PATCH 24/24] Add a test --- TESTS.md | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/TESTS.md b/TESTS.md index aa8db24dd..6ec92590f 100644 --- a/TESTS.md +++ b/TESTS.md @@ -851,6 +851,16 @@ f b ``` +`if` having a long condition + +```haskell +foo = + if fooooooo || + baaaaaaaaaaaaaaaaaaaaa || apsdgiuhasdpfgiuahdfpgiuah || bazzzzzzzzzzzzz + then a + else b +``` + Multi-way if ``` haskell