diff --git a/TESTS.md b/TESTS.md index dc44eef1b..6ec92590f 100644 --- a/TESTS.md +++ b/TESTS.md @@ -30,6 +30,28 @@ Extension pragmas fun @Int 12 ``` +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 Foo where +``` + +A pragma's length is adjusted automatically + +```haskell given +{-# LANGUAGE OverloadedStrings #-} +``` + +```haskell expect +{-# LANGUAGE OverloadedStrings #-} +``` + Module header ``` haskell @@ -46,6 +68,7 @@ module X , y , Z , P(x, z) + , module Foo ) where ``` @@ -65,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 @@ -124,6 +148,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 @@ -132,13 +166,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 +199,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 +221,12 @@ data Ty :: (* -> *) where # Expressions +A minus sign + +```haskell +f = -(3 + 5) +``` + Lazy patterns in a lambda ``` haskell @@ -293,6 +342,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 +379,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 +395,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 +524,38 @@ type family Closed (a :: k) :: Bool where Closed x = 'True ``` +Sections +```haskell +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 +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 +595,44 @@ g = # Type signatures +Multiple function signatures at once + +```haskell +a, b, c :: Int +``` + +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 @@ -525,6 +688,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 @@ -569,6 +739,19 @@ c :: '(:->) 'True 'False d :: (:->) 'True 'False ``` +`forall` type + +```haskell +f :: (forall a. Data a => + a -> a) + -> (forall a b. Data a => + a -> b) +f = undefined + +g :: forall a b. a -> b +g = undefined +``` + # Function declarations Prefix notation for operators @@ -578,6 +761,12 @@ Prefix notation for operators (+) a b = a ``` +As pattern + +```haskell +f all@(x:xs) = all +``` + Where clause ``` haskell @@ -588,6 +777,51 @@ 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 +``` + +A `DEPRECATED`. + +```haskell +{-# DEPRECATED +giveUp "Never give up." + #-} + +giveUp = undefined +``` + Guards and pattern guards ``` haskell @@ -601,6 +835,32 @@ 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 +``` + +`if` having a long condition + +```haskell +foo = + if fooooooo || + baaaaaaaaaaaaaaaaaaaaa || apsdgiuhasdpfgiuahdfpgiuah || bazzzzzzzzzzzzz + then a + else b +``` + Multi-way if ``` haskell @@ -628,6 +888,35 @@ 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 +930,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 +999,29 @@ test ,) ``` +Match against a list + +```haskell +head [] = undefined +head [x] = x +head xs = head $ init xs + +foo [Coord _ _, Coord _ _] = undefined +``` + +Range + +```haskell +a = [1 ..] +``` + +View pattern + +```haskell +foo (f -> Just x) = print x +foo _ = Nothing +``` + # Record syntax Pattern matching, short @@ -723,6 +1044,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 +1153,25 @@ data Expression a } ``` +Data declaration with underscore + +```haskell +data Stanza = + MkStanza + { _stanzaBuildInfo :: BuildInfo + , stanzaIsSourceFilePath :: FilePath -> Bool + } +``` + +Multiple constructors at once + +```haskell +data Foo = + Foo + { foo, bar, baz, qux, quux :: Int + } +``` + Spaces between deriving classes ``` haskell @@ -853,8 +1201,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 @@ -927,6 +1305,15 @@ gamma = do alpha = alpha ``` +Comments in a class declaration + +```haskell +class Foo a + -- A comment + where + foo :: a -> Int +``` + Haddock comments ``` haskell @@ -954,6 +1341,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 @@ -1021,6 +1414,31 @@ main = putStrLn "Hello, World!" {- This is another random comment. -} ``` +Comments in a 'where' clause + +```haskell +foo = undefined + where + bar + -- A comment + = undefined + where + a = b + 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 'Quuz'. + | Quuz +``` + # MINIMAL pragma Monad example @@ -1160,6 +1578,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 @@ -1446,7 +1874,12 @@ 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 + +bar Bar {baz = before, ..} = Bar {baz = after, ..} ``` RecursiveDo `rec` and `mdo` keyword #328 @@ -1594,8 +2027,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 = (-) @@ -1738,8 +2172,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 () @@ -1798,11 +2230,14 @@ topLevelFunc1 = f f = undefined topLevelFunc2 = f . g + -- Another comment where {- multi line comment -} - f = undefined + f = undefined -- single line comment -- single line comment + -- Different size of indents + g :: a g = undefined ```