This file is a test suite. Each section maps to an HSpec test, and each line that is followed by a Haskell code fence is tested to make sure re-formatting that code snippet produces the same result.
You can browse through this document to see what HIndent's style is like, or contribute additional sections to it, or regression tests.
No newlines after a shebang
#!/usr/bin/env stack
-- stack runghc
main =
pure ()
-- https://github.com/mihaimaruseac/hindent/issues/208
#!/usr/bin/env stack
-- stack runghc
main = pure ()
-- https://github.com/mihaimaruseac/hindent/issues/208
Double shebangs
#!/usr/bin/env stack
#!/usr/bin/env stack
main = pure ()
Empty module
Without an export list
module X where
x = 1
With an export list
module X
( x
, y
, Z
, P(x, z)
, Q(..)
, module Foo
) where
With an export list; indentation 4
module X
( x
, y
, Z
, P(x, z)
) where
A pragma's name is converted to the SHOUT_CASE.
{-# lAnGuAgE CPP #-}
{-# LANGUAGE CPP #-}
Pragmas, GHC options, and haddock options.
{-# LANGUAGE CPP #-}
{-# LANGUAGE NoRebindableSyntax #-}
{-# OPTIONS_GHC -fno-warn-missing-import-lists #-}
{-# OPTIONS_GHC -w #-}
{-# OPTIONS_HADDOCK show-extensions #-}
module Foo where
Accept pragmas via OPTIONS -XFOO
{-# OPTIONS -XPatternSynonyms #-}
import Foo (pattern Bar)
Accept pragmas via OPTIONS_GHC -XFOO
{-# OPTIONS_GHC -XPatternSynonyms #-}
import Foo (pattern Bar)
A pragma's length is adjusted automatically
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedStrings #-}
Collect multiple extensions correctly
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE PatternSynonyms #-}
import Language.C.Types (pattern TypeName)
Collect multiple extensions separated by commas correctly
{-# LANGUAGE TypeApplications,
PatternSynonyms #-}
import Foo (pattern Bar)
foo = bar @Int 3
{-# LANGUAGE TypeApplications, PatternSynonyms #-}
import Foo (pattern Bar)
foo = bar @Int 3
Do not collect pragma-like comments
-- {-# LANGUAGE StaticPointers #-}
{-
{-# LANGUAGE StaticPointers #-}
-}
-- @static@ is no longer a valid identifier
-- once `StaticPointers` is enabled.
static = 3
Without messages and an export list.
module Foo {-# WARNING [] #-} where
With a string without an export list.
module Foo {-# WARNING "Debug purpose only." #-} where
With a list of reasons without an export list.
module Foo {-# WARNING ["Debug purpose only.", "Okay?"] #-} where
Without messages and an export list.
module Foo {-# DEPRECATED [] #-} where
With a string without an export list.
module Foo {-# DEPRECATED "Use Bar." #-} where
With a list of reasons and an export list.
module Foo {-# DEPRECATED ["Use Bar.", "Or use Baz."] #-}
( x
, y
, z
) where
Import lists
import Control.Lens (_2, _Just)
import Data.Text
import Data.Text
import qualified Data.Text as T
import qualified Data.Text (a, b, c)
import Data.Text (a, b, c)
import Data.Text hiding (a, b, c)
Shorter identifiers come first
import Foo ((!), (!!))
Import with ExplicitNamespaces
.
{-# LANGUAGE ExplicitNamespaces #-}
import Prlude (type FilePath)
Import a pattern
{-# LANGUAGE PatternSynonyms #-}
import Foo (pattern Bar)
Sorted
import B
import A
import A
import B
Explicit imports - capitals first (typeclasses/types), then operators, then identifiers
import qualified MegaModule as M ((>>>), MonadBaseControl, void, MaybeT(..), join, Maybe(Nothing, Just), liftIO, Either, (<<<), Monad(return, (>>=), (>>)))
import qualified MegaModule as M
( Either
, Maybe(Just, Nothing)
, MaybeT(..)
, Monad((>>), (>>=), return)
, MonadBaseControl
, (<<<)
, (>>>)
, join
, liftIO
, void
)
Pretty import specification
{-# LANGUAGE ForeignFunctionInterface #-}
import A hiding
( foobarbazqux
, foobarbazqux
, foobarbazqux
, foobarbazqux
, foobarbazqux
, foobarbazqux
, foobarbazqux
)
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
import Language
( Language(Ada, Ada, Assembly, C, CPlusPlus, CSharp, Clojure, Cobol, Dart, Elixir,
Elm, Erlang, Fortran, Go, Groovy, Haskell, Java, JavaScript, Julia,
Kotlin, Lisp, Lua, ObjectiveC, PHP, Pascal, Perl, Prolog, Python, Ruby,
Rust, Scala)
, allLanguages
)
Preserve newlines between import groups
-- https://github.com/mihaimaruseac/hindent/issues/200
import GHC.Monad
import CommentAfter -- Comment here shouldn't affect newlines
import HelloWorld
import CommentAfter -- Comment here shouldn't affect newlines
-- Comment here shouldn't affect newlines
import CommentAfter
PackageImports
-- https://github.com/mihaimaruseac/hindent/issues/480
{-# LANGUAGE PackageImports #-}
import qualified "base" Prelude as P
ImportQualifiedPost
{-# LANGUAGE ImportQualifiedPost #-}
import Data.Text qualified as T
Importing a #
-- https://github.com/mihaimaruseac/hindent/issues/547
import Diagrams.Prelude ((#))
A ccall
foreign export
{-# LANGUAGE ForeignFunctionInterface #-}
foreign export ccall "test" test :: IO ()
A ccall
unsafe foreign import
{-# LANGUAGE ForeignFunctionInterface #-}
foreign import ccall unsafe "test" test :: IO ()
A capi
foreign import
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE ForeignFunctionInterface #-}
foreign import capi safe "foo" test :: IO Int
A stdcall
foreign import
{-# LANGUAGE ForeignFunctionInterface #-}
foreign import stdcall safe "test" bar :: IO ()
A prim
foreign import
{-# LANGUAGE ForeignFunctionInterface #-}
foreign import prim safe "test" test :: IO ()
A javascript
foreign import
{-# LANGUAGE ForeignFunctionInterface #-}
foreign import javascript safe "test" test :: IO ()
Data family
data family Foo a
StandaloneKindSignatures
{-# LANGUAGE StandaloneKindSignatures #-}
type Foo :: Type -> Type -> Type
data Foo a b =
Foo a b
Default declaration
default (Integer, Double)
Value annotation.
{-# ANN foo "annotation" #-}
Type annotation.
{-# ANN type Foo "annotation" #-}
Module annotation.
{-# ANN module "annotation" #-}
Default signatures
-- https://github.com/chrisdone/hindent/issues/283
class Foo a where
bar :: a -> a -> a
default bar :: Monoid a => a -> a -> a
bar = mappend
TypeOperators
and MultiParamTypeClasses
-- https://github.com/chrisdone/hindent/issues/277
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE MultiParamTypeClasses #-}
class (a :< b) c
Empty
class () =>
Foo a
Long
class ( Foo a
, Bar a
, Baz a
, Hoge a
, Fuga a
, Piyo a
, Hogera a
, Hogehoge a
, Spam a
, Ham a
) =>
Quux a
With class constraints
class Foo f where
myEq :: (Eq a) => f a -> f a -> Bool
Long signatures
class Foo a where
fooBarBazQuuxHogeFuga ::
a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a
Associated type synonyms
class Foo a where
type Bar b
Associated type synonyms annotated with injectivity information
-- https://github.com/commercialhaskell/hindent/issues/528
class C a where
type F a = b | b -> a
Without methods
instance C a
With methods
instance C a where
foobar = do
x y
k p
With type operators
-- https://github.com/mihaimaruseac/hindent/issues/342
instance Foo (->)
instance Foo (^>)
instance Foo (T.<^)
With a type alias
instance Foo a where
type Bar a = Int
A where
clause between instance functions
instance Pretty HsModule where
pretty' = undefined
where
a = b
commentsBefore = Nothing
With a SPECIALISE
pragma
instance (Show a) => Show (Foo a) where
{-# SPECIALISE instance Show (Foo String) #-}
show = undefined
With associated data types
-- https://github.com/mihaimaruseac/hindent/issues/493
instance GM 'Practice where
data MatchConfig 'Practice = MatchConfig'Practice
{ teamSize :: Int
, ladder :: Ladder
}
With associated newtypes
-- https://github.com/mihaimaruseac/hindent/issues/837
instance Foo a where
newtype Bar a =
FooBar a
OVERLAPPING
-- https://github.com/mihaimaruseac/hindent/issues/386
instance {-# OVERLAPPING #-} Arbitrary (Set Int) where
arbitrary = undefined
OVERLAPPABLE
instance {-# OVERLAPPABLE #-} Arbitrary Int where
arbitrary = undefined
OVERLAPS
instance {-# OVERLAPS #-} Arbitrary String where
arbitrary = undefined
INCOHERENT
instance {-# INCOHERENT #-} Arbitrary String where
arbitrary = undefined
Short name
-- https://github.com/mihaimaruseac/hindent/issues/244
instance Num a => C a
Long name
-- https://github.com/mihaimaruseac/hindent/issues/244
instance Nuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuum a =>
C a where
f = undefined
Without class constraints
-- https://github.com/mihaimaruseac/hindent/issues/218
instance forall x. C
With class constraints
-- https://github.com/mihaimaruseac/hindent/issues/218
instance forall x. Show x => C x
Infix
instance Bool :?: Bool
Prefix
instance (:?:) Int Bool
Data declaration with underscore
data Stanza = MkStanza
{ _stanzaBuildInfo :: BuildInfo
, stanzaIsSourceFilePath :: FilePath -> Bool
}
A data declaration with typeclass constraints
data Ord a =>
Foo =
Foo a
Multiple constructors at once
data Foo = Foo
{ foo, bar, baz, qux, quux :: Int
}
No fields
data Foo
Single field
data Foo =
Foo
Multiple unnamed fields
data HttpException
= InvalidStatusCode Int
| MissingContentHeader
A lot of unnamed fields in a constructor
data Foo =
Foo
String
String
String
String
String
String
String
String
String
String
String
A banged field
data Foo =
Foo !Int
A record constructor with a field
data Foo = Foo
{ foo :: Int
}
Multiple constructors with fields
data Expression a
= VariableExpression
{ id :: Id Expression
, label :: a
}
| FunctionExpression
{ var :: Id Expression
, body :: Expression a
, label :: a
}
| ApplyExpression
{ func :: Expression a
, arg :: Expression a
, label :: a
}
| ConstructorExpression
{ id :: Id Constructor
, label :: a
}
A mixture of constructors with unnamed fields and record constructors
-- https://github.com/mihaimaruseac/hindent/issues/393
data X
= X
{ x :: Int
, x' :: Int
}
| X'
An infix data constructor
data Foo =
Int :--> Int
An UNPACK
ed field.
data Foo = Foo
{ x :: {-# UNPACK #-} Int
}
An NOUNPACK
ed field.
data Foo = Foo
{ x :: {-# NOUNPACK #-} !Int
}
A lazy field.
data Foo = Foo
{ x :: ~Int
}
Single
data D =
forall a. D a
Multiple
-- https://github.com/mihaimaruseac/hindent/issues/443
{-# LANGUAGE ExistentialQuantification #-}
data D =
forall a b c. D a b c
With an infix constructor
data D =
forall a. a :== a
Without a forall
data Foo =
Eq a => Foo a
With a forall
-- https://github.com/mihaimaruseac/hindent/issues/278
data Link c1 c2 a c =
forall b. (c1 a b, c2 b c) =>
Link (Proxy b)
With an infix constructor without a forall
data Foo =
Eq a => a :== a
With an infix constructor with a forall
data Foo =
forall a. Eq a =>
a :== a
With a single constructor
data Simple =
Simple
deriving (Show)
With multiple constructors
data Stuffs
= Things
| This
| That
deriving (Show)
With a record constructor
-- From https://github.com/mihaimaruseac/hindent/issues/167
data Person = Person
{ firstName :: !String -- ^ First name
, lastName :: !String -- ^ Last name
, age :: !Int -- ^ Age
} deriving (Eq, Show)
Multiple derivings
-- https://github.com/mihaimaruseac/hindent/issues/289
newtype Foo =
Foo Proxy
deriving ( Functor
, Applicative
, Monad
, Semigroup
, Monoid
, Alternative
, MonadPlus
, Foldable
, Traversable
)
Various deriving strategies
-- https://github.com/mihaimaruseac/hindent/issues/503
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveVia #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Foo where
import Data.Typeable
import GHC.Generics
newtype Number a =
Number a
deriving (Generic)
deriving stock (Ord)
deriving newtype (Eq)
deriving anyclass (Typeable)
deriving (Show) via a
StandaloneDeriving
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE StandaloneDeriving #-}
data Foo =
Foo
deriving instance Eq Foo
deriving stock instance Ord Foo
deriving via (Foo a) instance Show (Bar a)
With a kind signature
data Ty :: (* -> *) where
TCon
:: { field1 :: Int
, field2 :: Bool}
-> Ty Bool
TCon' :: (a :: *) -> a -> Ty a
Without a kind signature
data Foo where
Foo
:: forall v. Ord v
=> v
-> v
-> Foo
With a forall
but no contexts
data Foo where
Foo :: forall v. v -> v -> Foo
With a context but no forall
s
data Foo where
Foo :: (Ord v) => v -> v -> Foo
With methods with record signatures
-- https://github.com/mihaimaruseac/hindent/issues/581
data Test where
Test :: Eq a => { test :: a } -> Test
Without type applications
data instance Foo Int =
FInt
With type applications
data instance Foo @k a =
FString
Case inside do
and lambda
foo =
\x -> do
case x of
Just _ -> 1
Nothing -> 2
A case
inside a let
.
f = do
let (x, xs) =
case gs of
[] -> undefined
(x':xs') -> (x', xs')
undefined
A do
inside a lambda.
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)
foo =
case x of
0 -> pure ()
_ -> undefined
s8_stripPrefix bs1@(S.PS _ _ l1) bs2
| bs1 `S.isPrefixOf` bs2 = Just (S.unsafeDrop l1 bs2)
| otherwise = Nothing
A do
inside a guard arm
f
| x == 1 = do
a
b
if
having a long condition
foo =
if fooooooo
|| baaaaaaaaaaaaaaaaaaaaa
|| apsdgiuhasdpfgiuahdfpgiuah
|| bazzzzzzzzzzzzz
then a
else b
A long signature inside a where clause
cppSplitBlocks :: ByteString -> [CodeBlock]
cppSplitBlocks inp = undefined
where
spanCPPLines ::
[(Int, ByteString)] -> ([(Int, ByteString)], [(Int, ByteString)])
spanCPPLines = undefined
A forall
type inside a where clause
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
Prefix notation for operators
(+) a b = a
Guards and pattern guards
f x
| x <- Just x
, x <- Just x =
case x of
Just x -> e
| otherwise = do
e
where
x = y
Where clause
sayHello = do
name <- getLine
putStrLn $ greeting name
where
greeting name = "Hello, " ++ name ++ "!"
An empty line is inserted after an empty where
f = evalState
-- A comment
where
f = evalState
-- A comment
where
Multiple function declarations with an empty where
f = undefined
where
g = undefined
Let inside a where
g x =
let x = 1
in x
where
foo =
let y = 2
z = 3
in y
The indent after a top-level where
has always 2 spaces.
f = undefined
where
g = undefined
The indent after a where
inside a case
depends on the indent space setting
f =
case x of
x -> undefined
where y = undefined
View pattern
foo (f -> Just x) = print x
foo _ = Nothing
Match against a list
head [] = undefined
head [x] = x
head xs = head $ init xs
foo [Coord _ _, Coord _ _] = undefined
Multiple matchings
head' [] = Nothing
head' (x:_) = Just x
n+k patterns
{-# LANGUAGE NPlusKPatterns #-}
f (n+5) = 0
Binary symbol data constructor in pattern
f (x :| _) = x
f' ((:|) x _) = x
f'' ((Data.List.NonEmpty.:|) x _) = x
g (x:xs) = x
g' ((:) x _) = x
Infix constructor pattern
-- https://github.com/mihaimaruseac/hindent/issues/424
a = from $ \(author `InnerJoin` post) -> pure ()
Unboxed sum pattern matching.
{-# LANGUAGE UnboxedSums #-}
f (# (# n, _ #) | #) = (# n | #)
f (# | b #) = (# | b #)
Pattern matching against a infix constructor with a module name prefix
foo (a FOO.:@: b) = undefined
Short
fun Rec {alpha = beta, gamma = delta, epsilon = zeta, eta = theta, iota = kappa} = do
beta + delta + zeta + theta + kappa
Long
fun Rec { alpha = beta
, gamma = delta
, epsilon = zeta
, eta = theta
, iota = kappa
, lambda = mu
} =
beta + delta + zeta + theta + kappa + mu + beta + delta + zeta + theta + kappa
Another long one
resetModuleStartLine m@HsModule { hsmodAnn = epa@EpAnn {..}
, hsmodName = Just (L (SrcSpanAnn _ (RealSrcSpan sp _)) _)
} = undefined
Symbol constructor, short
fun ((:..?) {}) = undefined
Symbol constructor, long
fun (:..?) { alpha = beta
, gamma = delta
, epsilon = zeta
, eta = theta
, iota = kappa
, lambda = mu
} =
beta + delta + zeta + theta + kappa + mu + beta + delta + zeta + theta + kappa
Symbol field
f (X {(..?) = x}) = x
Punned symbol field
f' (X {(..?)}) = (..?)
RecordWileCards
-- https://github.com/mihaimaruseac/hindent/issues/274
foo (bar@Bar {..}) = Bar {..}
resetModuleNameColumn m@HsModule {hsmodName = Just (L (SrcSpanAnn epa@EpAnn {..} sp) name)} =
m
bar Bar {baz = before, ..} = Bar {baz = after, ..}
As pattern
f all@(x:xs) = all
infixl
infixl 1 ^-^
infixr
infixr 1 ^-^
infix
infix 1 ^-^
Unidirectional with a pattern type signature
{-# LANGUAGE PatternSynonyms #-}
pattern Foo :: Int -> Int -> [Int]
pattern Foo x y <- [x, y]
Bidirectional record pattern
{-# LANGUAGE PatternSynonyms #-}
pattern Pair {x, y} = (x, y)
With a prefix constructor
{-# LANGUAGE PatternSynonyms #-}
pattern Fst x <- (x, x)
where Fst x = (x, 0)
With an infix constructor
{-# LANGUAGE PatternSynonyms #-}
pattern x :| xs <- x : xs
where a :| b = a : b
INLINE
-- https://github.com/mihaimaruseac/hindent/issues/255
{-# INLINE f #-}
f :: Int -> Int
f n = n
NOINLINE
with an operator enclosed by parentheses
-- https://github.com/mihaimaruseac/hindent/issues/415
{-# NOINLINE (<>) #-}
INLINABLE
{-# INLINABLE f #-}
f :: a
f = undefined
OPAQUE
{-# OPAQUE f #-}
f :: a
f = undefined
INLINE
with levels
{-# INLINE [0] f #-}
{-# INLINE [~1] g #-}
A DEPRECATED
.
{-# DEPRECATED
giveUp "Never give up."
#-}
giveUp = undefined
A WARNING
.
{-# WARNING
debugCode "The use of 'debugCode'"
#-}
A COMPLETE
{-# COMPLETE Single, Anylist #-}
Top-level SPECIALISE
{-# SPECIALISE lookup :: [(Int, Int)] -> Int -> Maybe Int #-}
Multiple signatures in a SPECIALISE
-- https://github.com/mihaimaruseac/hindent/pull/784
{-# SPECIALISE foo :: Int -> Int, Double -> Double #-}
A SCC
{-# SCC bar #-}
Without forall
s
{-# RULES
"foo/bar" foo = bar
#-}
With forall
but no type signatures
{-# RULES
"piyo/pochi" forall a. piyo a = pochi a a
#-}
With forall
and type signatures
{-# RULES
"hoge/fuga" forall (a :: Int). hoge a = fuga a a
#-}
normal
{-# LANGUAGE RoleAnnotations #-}
type role Foo nominal
representational
{-# LANGUAGE RoleAnnotations #-}
type role Bar representational
phantom
{-# LANGUAGE RoleAnnotations #-}
type role Baz phantom
Without annotations
type family Id a
With annotations
type family Id a :: *
With injectivity annotations
type family Id a = r | r -> a
Closed type families
type family Closed (a :: k) :: Bool where
Closed (x @Int) = 'Int
Closed x = 'True
Without holes
type instance Id Int = Int
With a hole
type instance Id _ = String
Multiple function signatures at once
a, b, c :: Int
Type using a numeric value
f :: Foo 0
Type using a character value
f :: Foo 'a'
Type using a unicode string value
f :: Foo "あ"
A dot not enclosed by spaces is printed correctly if OverloadedRecordDot
is not enabled.
f :: forall a.(Data a, Typeable a) => a
f :: forall a. (Data a, Typeable a)
=> a
Short
-- https://github.com/mihaimaruseac/hindent/issues/390
fun :: Short
fun = undefined
Always break after ::
on overlong signatures
-- https://github.com/mihaimaruseac/hindent/issues/390
someFunctionSignature ::
Wiiiiiiiiiiiiiiiiith
-> Enough
-> (Arguments -> To ())
-> Overflow (The Line Limit)
A long type is broken into lines
-- https://github.com/mihaimaruseac/hindent/issues/359
thing ::
( ResB.BomEx
, Maybe
[( Entity BomSnapshot
, ( [ResBS.OrderSubstituteAggr]
, ( Maybe (Entity BomSnapshotHistory)
, Maybe (Entity BomSnapshotHistory))))])
-> [(ResB.BomEx, Maybe ResBS.BomSnapshotAggr)]
Long parameter list with a forall
fooooooooo ::
forall a.
Fooooooooooooooo a
-> Fooooooooooooooo a
-> Fooooooooooooooo a
-> Fooooooooooooooo a
Implicit parameters
{-# LANGUAGE ImplicitParams #-}
f :: (?x :: Int) => Int
Quasiquotes in types
{-# LANGUAGE QuasiQuotes #-}
fun :: [a|bc|]
Tuples
fun :: (a, b, c) -> (a, b)
Infix operator
-- https://github.com/mihaimaruseac/hindent/issues/301
(+) :: ()
With a record
url :: r {url :: String} => r -> Integer
forall
type
f :: (forall a. Data a => a -> a) -> (forall a b. Data a => a -> b)
g :: forall a b. a -> b
An infix operator containing #
(#!) :: Int -> Int -> Int
Multiple line function signature inside a where
foo = undefined
where
go :: Fooooooooooooooooooooooo
-> Fooooooooooooooooooooooo
-> Fooooooooooooooooooooooo
-> Fooooooooooooooooooooooo
go = undefined
Types with many type applications
foo ::
Foo
LongLongType
LongLongType
LongLongType
LongLongType
LongLongType
LongLongType
-> Int
Class constraints should leave ::
on same line
-- see https://github.com/chrisdone/hindent/pull/266#issuecomment-244182805
fun ::
(Class a, Class b)
=> fooooooooooo bar mu zot
-> fooooooooooo bar mu zot
-> c
An infix operator containing #
(#!) :: Int -> Int -> Int
Prefix promoted symbol type constructor
a :: '(T.:->) 'True 'False
b :: (T.:->) 'True 'False
c :: '(:->) 'True 'False
d :: (:->) 'True 'False
Short
fun1 :: Def ('[ Ref s (Stored Uint32), IBool] T.:-> IBool)
fun1 = undefined
fun2 :: Def ('[ Ref s (Stored Uint32), IBool] :-> IBool)
fun2 = undefined
Long
-- https://github.com/mihaimaruseac/hindent/issues/522
type OurContext
= '[ AuthHandler W.Request (ExtendedPayloadWrapper UserSession)
, BasicAuthCheck GameInstanceId
, BasicAuthCheck (RegionId, RegionName)
, BasicAuthCheck Alert.SourceId
, M.MultipartOptions M.Tmp
]
Nested
-- https://github.com/mihaimaruseac/hindent/issues/348
a :: A '[ 'True]
-- nested promoted list with multiple elements.
b :: A '[ '[ 'True, 'False], '[ 'False, 'True]]
Infix
f :: a :?: b
Prefix
f' :: (:?:) a b
Single
-- https://github.com/mihaimaruseac/hindent/issues/244
x :: Num a => a
x = undefined
Multiple
fun :: (Class a, Class b) => a -> b -> c
Multiple without parentheses
-- https://github.com/mihaimaruseac/hindent/issues/554
g :: Semigroup a => Monoid a => Maybe a -> a
Long constraints
-- https://github.com/mihaimaruseac/hindent/issues/222
foo ::
( Foooooooooooooooooooooooooooooooooooooooooo
, Foooooooooooooooooooooooooooooooooooooooooo
)
=> A
Class constraints should leave ::
on same line
-- see https://github.com/mihaimaruseac/hindent/pull/266#issuecomment-244182805
fun ::
(Class a, Class b)
=> fooooooooooo bar mu zot
-> fooooooooooo bar mu zot
-> c
Symbol class constructor in class constraint
f :: (a :?: b) => (a, b)
f' :: ((:?:) a b) => (a, b)
Short unboxed sums
{-# LANGUAGE UnboxedSums #-}
f :: (# (# Int, String #) | String #) -> (# Int | String #)
Long unboxed sums
{-# LANGUAGE UnboxedSums #-}
f' ::
(# (# Int, String #)
| Either Bool Int
| Either Bool Int
| Either Bool Int
| Either Bool Int
| Either Bool Int
| String #)
-> (# Int | String #)
Large unboxed tuples
{-# LANGUAGE UnboxedTuples #-}
f :: (# Looooooooooooooooooooooooooooooooooooooooooooong
, Looooooooooooooooooooooooooooooooooooooooooooong
, Looooooooooooooooooooooooooooooooooooooooooooong #)
Short
type EventSource a = (AddHandler a, a -> IO ())
Long
-- https://github.com/mihaimaruseac/hindent/issues/290
type MyContext m
= ( MonadState Int m
, MonadReader Int m
, MonadError Text m
, MonadMask m
, Monoid m
, Functor m)
Very higher-kinded type
-- https://github.com/mihaimaruseac/hindent/issues/534
type SomeTypeSynonym
= RecordWithManyFields
FieldNumber1
FieldNumber2
FieldNumber3
FieldNumber4
FieldNumber5
FieldNumber6
FieldNumber7
FieldNumber8
FieldNumber9
FieldNumber10
FieldNumber11
FieldNumber12
FieldNumber13
FieldNumber14
FieldNumber15
Infix type constructor
-- https://github.com/mihaimaruseac/hindent/issues/417
type API = api1 :<|> api2
Type with a string
-- https://github.com/mihaimaruseac/hindent/issues/451
type Y = X "abc\n\n\ndef"
TypeOperators
-- https://github.com/mihaimaruseac/hindent/issues/277
{-# LANGUAGE TypeOperators #-}
type m ~> n = ()
Single
-- https://github.com/commercialhaskell/hindent/issues/323
class Foo a b | a -> b where
f :: a -> b
Multiple dependencies in a line
class Foo a b | a -> b, b -> a
Long
-- https://github.com/commercialhaskell/hindent/issues/323
class Foo a b c d e f
| a b c d e -> f
, a b c d f -> e
, a b c e f -> d
, a b d e f -> c
, a c d e f -> b
, b c d e f -> a
where
foo :: a -> b -> c -> d -> e -> f
Single
-- https://github.com/commercialhaskell/hindent/issues/459
class Class1 a =>
Class2 a
where
f :: a -> Int
Multiple
-- https://github.com/commercialhaskell/hindent/issues/459
class (Eq a, Show a) =>
Num a
where
(+), (-), (*) :: a -> a -> a
negate :: a -> a
abs, signum :: a -> a
fromInteger :: Integer -> a
Monad example
class A where
{-# MINIMAL return, ((>>=) | (join, fmap)) #-}
Very long names #310
class A where
{-# MINIMAL averylongnamewithnoparticularmeaning
| ananotherverylongnamewithnomoremeaning #-}
A minus sign
f = -(3 + 5)
Lists
exceptions = [InvalidStatusCode, MissingContentHeader, InternalServerError]
exceptions =
[ InvalidStatusCode
, MissingContentHeader
, InternalServerError
, InvalidStatusCode
, MissingContentHeader
, InternalServerError
]
Multi-way if
x =
if | x <- Just x
, x <- Just x ->
case x of
Just x -> e
Nothing -> p
| otherwise -> e
Type application
{-# LANGUAGE TypeApplications #-}
a = fun @Int 12
An expression with a SCC pragma
foo = {-# SCC foo #-} undefined
A hole
foo = 3 + _
Implicit value
{-# LANGUAGE ImplicitParams #-}
foo = ?undefined
UnboxedSums
{-# LANGUAGE UnboxedSums #-}
f = (# | Bool #)
StaticPointers
{-# LANGUAGE StaticPointers #-}
f = static 1
OverloadedLabels
{-# LANGUAGE OverloadedLabels #-}
f = #foo
-<
{-# LANGUAGE Arrows #-}
f =
proc foo -> do
bar -< baz
aaa >- bbb
-<<
{-# LANGUAGE Arrows #-}
f =
proc foo -> do
g bar -<< baz
aaaaa >>- h bbb
(| ... |)
{-# LANGUAGE Arrows #-}
f = proc g -> (|foo (bar -< g) (baz -< g)|) zz
Lambda equation.
{-# LANGUAGE Arrows #-}
f = proc g -> \x -> x -< g
Case expression.
{-# LANGUAGE Arrows #-}
f =
proc g ->
case h of
[] -> i -< ()
(_:_) -> j -< ()
Lambda case
{-# LANGUAGE Arrows #-}
{-# LANGUAGE LambdaCase #-}
f =
proc g ->
\case
_ -> h -< ()
if ... then ... else
{-# LANGUAGE Arrows #-}
f =
proc g ->
if x
then h -< g
else t -< g
let ... in
{-# LANGUAGE Arrows #-}
f =
proc g ->
let x = undefined
y = undefined
in returnA -< g
Normal case
strToMonth :: String -> Int
strToMonth month =
case month of
"Jan" -> 1
"Feb" -> 2
_ -> error $ "Unknown month " ++ month
Inside a where
and do
g x =
case x of
a -> x
where
foo =
case x of
_ -> do
launchMissiles
where
y = 2
Empty case
-- https://github.com/mihaimaruseac/hindent/issues/414
{-# LANGUAGE EmptyCase #-}
f1 = case () of {}
Empty lambda case
-- https://github.com/mihaimaruseac/hindent/issues/414
{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE LambdaCase #-}
f2 = \case {}
A guard in a case
f =
case g of
[]
| even h -> Nothing
_ -> undefined
cases
{-# LANGUAGE Arrows #-}
{-# LANGUAGE LambdaCase #-}
foo =
\cases
1 1 -> 1
_ _ -> 2
Long function applications
test = do
alphaBetaGamma deltaEpsilonZeta etaThetaIota kappaLambdaMu nuXiOmicron piRh79
alphaBetaGamma deltaEpsilonZeta etaThetaIota kappaLambdaMu nuXiOmicron piRho80
alphaBetaGamma
deltaEpsilonZeta
etaThetaIota
kappaLambdaMu
nuXiOmicron
piRhoS81
Do as a left-hand side of an infix operation
-- https://github.com/mihaimaruseac/hindent/issues/238
-- https://github.com/mihaimaruseac/hindent/issues/296
block = do
ds <- inBraces $ inWhiteSpace declarations
return $ Block ds
<?> "block"
Short
foo = do
mcp <- findCabalFiles (takeDirectory abssrcpath) (takeFileName abssrcpath)
print mcp
Large
-- https://github.com/mihaimaruseac/hindent/issues/221
x = do
config <- execParser options
comments <-
case config of
Diff False args -> commentsFromDiff args
Diff True args -> commentsFromDiff ("--cached" : args)
Files args -> commentsFromFiles args
mapM_ (putStrLn . Fixme.formatTodo) (concatMap Fixme.getTodos comments)
With type signatures but no class constraints
f = do
let g :: Int
g = 3
print g
With both type signatures and class constraints
f = do
let try :: Typeable b => b
try = undefined
undefined
rec
{-# LANGUAGE RecursiveDo #-}
f = do
a <- foo
rec b <- a c
c <- a b
return $ b + c
mdo
{-# LANGUAGE RecursiveDo #-}
g = mdo
foo
bar
Qualified do
{-# LANGUAGE QualifiedDo #-}
f = Module.Path.do
a <- foo
return a
Qualified do with mdo
{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE QualifiedDo #-}
f = Module.Path.mdo
a <- foo
return a
Long line, tuple
a =
test
(alphaBetaGamma, deltaEpsilonZeta, etaThetaIota, kappaLambdaMu, nuXiOmic79)
(alphaBetaGamma, deltaEpsilonZeta, etaThetaIota, kappaLambdaMu, nuXiOmicr80)
( alphaBetaGamma
, deltaEpsilonZeta
, etaThetaIota
, kappaLambdaMu
, nuXiOmicro81)
Long line, tuple section
a =
test
(, alphaBetaGamma, , deltaEpsilonZeta, , etaThetaIota, kappaLambdaMu, nu79)
(, alphaBetaGamma, , deltaEpsilonZeta, , etaThetaIota, kappaLambdaMu, nuX80)
(
, alphaBetaGamma
,
, deltaEpsilonZeta
,
, etaThetaIota
, kappaLambdaMu
, nuXi81
,)
Linebreaks after very short names if the total line length goes over the limit
-- https://github.com/mihaimaruseac/hindent/issues/405
t =
f "this is a very loooooooooooooooooooooooooooong string that goes over the line length"
argx
argy
argz
t =
function
"this is a very loooooooooooooooooooooooooooong string that goes over the line length"
argx
argy
argz
Lazy patterns
f = \ ~a -> undefined
-- \~a yields parse error on input ‘\~’
Bang patterns
f = \ !a -> undefined
-- \!a yields parse error on input ‘\!’
An infix operator with a lambda expression
a =
for xs $ \x -> do
left x
right x
Nested lambdas
foo :: IO ()
foo =
alloca 10 $ \a ->
alloca 20 $ \b ->
cFunction fooo barrr muuu (fooo barrr muuu) (fooo barrr muuu)
In a case
f x =
case filter (\y -> isHappy y x) of
[] -> Nothing
(z:_) -> Just (\a b -> makeSmile z a b)
With bang parameters
f =
let !x = 3
in x
With implicit parameters
{-# LANGUAGE ImplicitParams #-}
f =
let ?x = 42
in f
inside a do
-- https://github.com/mihaimaruseac/hindent/issues/467
main :: IO ()
main = do
let x = 5
in when (x > 0) (return ())
Short
map f xs = [f x | x <- xs]
Long
defaultExtensions =
[ e
| EnableExtension {extensionField1 = extensionField1} <-
knownExtensions knownExtensions
, let a = b
-- comment
, let c = d
-- comment
]
Another long one
-- https://github.com/mihaimaruseac/hindent/issues/357
foo =
[ (x, y)
| x <- [1 .. 10]
, y <- [11 .. 20]
, even x
, even x
, even x
, even x
, even x
, odd y
]
With operators
defaultExtensions =
[e | e@EnableExtension {} <- knownExtensions]
\\ map EnableExtension badExtensions
Transform list comprehensions
list =
[ (x, y, map the v)
| x <- [1 .. 10]
, y <- [1 .. 10]
, let v = x + y
, then group by v using groupWith
, then take 10
, then group using permutations
, t <- concat v
, then takeWhile by t < 3
]
Short
zip xs ys = [(x, y) | x <- xs | y <- ys]
Long
fun xs ys =
[ (alphaBetaGamma, deltaEpsilonZeta)
| x <- xs
, z <- zs
| y <- ys
, cond
, let t = t
]
With do
a =
for xs $ do
left x
right x
With lambda-case
a =
for xs $ \case
Left x -> x
Qualified operator as an argument
-- https://github.com/mihaimaruseac/hindent/issues/273
foo = foldr1 (V.++) [V.empty, V.empty]
Apply an infix operator in prefix style
-- https://github.com/mihaimaruseac/hindent/issues/273
ys = (++) [] []
Qualified operator
-- https://github.com/mihaimaruseac/hindent/issues/273
xs = V.empty V.++ V.empty
In parentheses
cat = (++)
Qualified operator in parentheses
-- https://github.com/mihaimaruseac/hindent/issues/273
cons = (V.++)
A list constructor enclosed by parentheses
cons = (:)
A data constructor enclosed by parentheses
-- https://github.com/mihaimaruseac/hindent/issues/422
data T a =
a :@ a
test = (:@)
Force indent and print RHS in a top-level expression
-- https://github.com/mihaimaruseac/hindent/issues/473
a =
template
$ haskell
[ SomeVeryLongName
, AnotherLongNameEvenLongToBreakTheLine
, LastLongNameInList
]
Applicative style
x =
Value
<$> thing
<*> secondThing
<*> thirdThing
<*> fourthThing
<*> Just thisissolong
<*> Just stilllonger
<*> evenlonger
$
chain
f =
Right
$ S.lazyByteStrings
$ addPrefix prefix
$ S.toLazyByteString
$ prettyPrint m
Arithmetic operations
f =
aaaaaaaaaa * bbbbbbbbbbbbbb / cccccccccccccccccccccc
+ dddddddddddddd * eeeeeeeeeeeeeeee
- ffffffffffffffff / -ggggggggggggg
Lens operators
updateUsr usr =
usr
& userFirstName .~ "newfirst"
& userLastName .~ "newlast"
& userEmail .~ "newemail"
& userPassword .~ "newpass"
Char
a = 'a'
\n
as a Char
a = '\n'
String
with a \n
a = "bcd\nefgh"
Multiple line string
foo =
"hoge \
\ fuga"
where
bar =
"foo \
\ bar"
Hex integers
a = 0xa5
Unboxed integers
{-# LANGUAGE MagicHash #-}
a = 0#
Unboxed floating point numbers
{-# LANGUAGE MagicHash #-}
a = 3.3#
Unboxed Char
{-# LANGUAGE MagicHash #-}
a = 'c'#
Unboxed String
{-# LANGUAGE MagicHash #-}
a = "Foo"#
UnboxedTuple
{-# LANGUAGE UnboxedTuples #-}
f :: (# Int, Int #) -> (# Int, Int #)
f t =
case t of
(# x, y #) -> (# x, y #)
NumericUnderscores
-- https://github.com/mihaimaruseac/hindent/issues/542
{-# LANGUAGE NumericUnderscores #-}
foo = 10_000
Body has multiple lines.
{-# LANGUAGE QuasiQuotes #-}
f =
[s|First line
Second line|]
Body has a top-level declaration.
{-# LANGUAGE QuasiQuotes #-}
f =
[d| f :: Int -> Int
f = undefined |]
Typed quote.
f = [||a||]
Preserve the trailing newline.
{-# LANGUAGE QuasiQuotes #-}
f =
[s|foo
|]
from
a = [1 ..]
from to
a = [1 .. 9]
from then
b = [1,3 ..]
from then to
c = [1,3 .. 9]
No fields
-- https://github.com/mihaimaruseac/hindent/issues/366
foo = Nothing {}
Short
getGitProvider :: EventProvider GitRecord ()
getGitProvider =
EventProvider {getModuleName = "Git", getEvents = getRepoCommits}
Medium
commitToEvent :: FolderPath -> TimeZone -> Commit -> Event.Event
commitToEvent gitFolderPath timezone commit =
Event.Event
{pluginName = getModuleName getGitProvider, eventIcon = "glyphicon-cog"}
Long
commitToEvent :: FolderPath -> TimeZone -> Commit -> Event.Event
commitToEvent gitFolderPath timezone commit =
Event.Event
{ pluginName = getModuleName getGitProvider
, eventIcon = "glyphicon-cog"
, eventDate = localTimeToUTC timezone (commitDate commit)
}
Another long one
-- https://github.com/mihaimaruseac/hindent/issues/358
foo =
assert
sanityCheck
BomSnapshotAggr
{ snapshot = Just bs
, previousId = M.bomSnapshotHistoryPreviousId . entityVal <$> bsp
, nextId = M.bomSnapshotHistoryNextId . entityVal <$> bsn
, bomEx = bx''
, orderSubstitutes =
S.fromList . map OrderSubstituteAggrByCreatedAtAsc $ subs
, snapshotSubstitute = msub
}
Record body may be in one line even if a new line is inserted after the variable name.
addCommentsToNode mkNodeComment newComments nodeInfo@(NodeInfo (SrcSpanInfo _ _) existingComments) =
nodeInfo
{nodeInfoComments = existingComments <> map mkBeforeNodeComment newComments}
Symbol constructor
f = (:..?) {}
Symbol field
f x = x {(..?) = wat}
g x = Rec {(..?)}
A field updater in a do
inside a let ... in
.
f = undefined
where
g h =
let x = undefined
in do
foo
pure
h
{ grhssLocalBinds =
HsValBinds x (ValBinds (newSigs newSigMethods))
}
OverloadedRecordDot
{-# LANGUAGE OverloadedRecordDot #-}
data Rectangle = Rectangle
{ width :: Int
, height :: Int
}
area :: Rectangle -> Int
area r = r.width * r.height
foo = (.x.y)
OverloadedRecordUpdate
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedRecordUpdate #-}
foo = bar {baz.qux = 1}
With a LHS
double = (2 *)
With a RHS
halve = (/ 2)
With a large RHS
foo =
(`elem` concat
[ [20, 68, 92, 112, 28, 124, 116, 80]
, [21, 84, 87, 221, 127, 255, 241, 17]
])
Expression brackets
add1 x = [|x + 1|]
Pattern brackets
{-# LANGUAGE TemplateHaskell #-}
mkPat = [p|(x, y)|]
Type brackets
{-# LANGUAGE TemplateHaskell #-}
foo :: $([t|Bool|]) -> a
A quoted TH name from a type name
-- https://github.com/mihaimaruseac/hindent/issues/412
{-# LANGUAGE TemplateHaskell #-}
data (-)
q = ''(-)
Quoted list constructors
{-# LANGUAGE TemplateHaskell #-}
cons = '(:)
Pattern splices
{-# LANGUAGE TemplateHaskell #-}
f $pat = ()
g =
case x of
$(mkPat y z) -> True
_ -> False
Typed splice
{-# LANGUAGE TemplateHaskell #-}
foo = $$bar
Only comments
-- foo
Double comments in a line
f = undefined {- Comment 1 -} {- Comment 2 -} -- Comment 3
Comments within a declaration
bob -- after bob
=
foo -- next to foo
-- line after foo
(bar
foo -- next to bar foo
bar -- next to bar
) -- next to the end paren of (bar)
-- line after (bar)
mu -- next to mu
-- line after mu
-- another line after mu
zot -- next to zot
-- line after zot
(case casey -- after casey
of
Just -- after Just
-> do
justice -- after justice
* foo
(blah * blah
+ z
+ 2 / 4
+ a
- -- before a line break
2
* -- inside this mess
z
/ 2
/ 2
/ aooooo
/ aaaaa -- bob comment
)
+ (sdfsdfsd fsdfsdf) -- blah comment
putStrLn "")
[1, 2, 3]
[ 1 -- foo
, ( 2 -- bar
, 2.5 -- mu
)
, 3
]
-- in the end of the function
where
alpha = alpha
-- between alpha and beta
beta = beta
-- after beta
foo = 1 -- after foo
gamma = do
delta
epsilon
-- in the end of a do-block 1
gamma = do
delta
epsilon
-- the very last block is detected differently
Comments in a do expression
gamma = do
-- in the beginning of a do-block
delta
Comments in a class instance
instance Pretty MatchForCase
-- TODO: Do not forget to handle comments!
where
pretty' = undefined
Comments in a case expression
-- https://github.com/mihaimaruseac/hindent/issues/553
f x =
case x of
-- Bla bla
Nothing -> 0
Just y -> y
Haddock comments
-- | Module comment.
module X where
-- | Main doc.
main :: IO ()
main = return ()
data X
= X -- ^ X is for xylophone.
| Y -- ^ Y is for why did I eat that pizza.
data X = X
{ field1 :: Int -- ^ Field1 is the first field.
, field11 :: Char
-- ^ This field comment is on its own line.
, field2 :: Int -- ^ Field2 is the second field.
, field3 :: Char -- ^ This is a long comment which starts next to
-- the field but continues onto the next line, it aligns exactly
-- with the field name.
, field4 :: Char
-- ^ 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
Haddock for a class method
-- https://github.com/mihaimaruseac/hindent/issues/607
class Foo a where
-- | Doc
foo :: a
Module header with haddock comments
-- | A module
module HIndent -- Foo
( -- * Formatting functions.
reformat
, -- * Testing
test
) where
Comments around regular declarations
-- This is some random comment.
-- | Main entry point.
main = putStrLn "Hello, World!"
-- This is another random comment.
Multi-line comments
bob {- after bob -}
=
foo {- next to foo -}
{- line after foo -}
(bar
foo {- next to bar foo -}
bar {- next to bar -}
) {- next to the end paren of (bar) -}
{- line after (bar) -}
mu {- next to mu -}
{- line after mu -}
{- another line after mu -}
zot {- next to zot -}
{- line after zot -}
(case casey {- after casey -}
of
Just {- after Just -}
-> do
justice {- after justice -}
* foo
(blah * blah
+ z
+ 2 / 4
+ a
- {- before a line break -}
2
* {- inside this mess -}
z
/ 2
/ 2
/ aooooo
/ aaaaa {- bob comment -}
)
+ (sdfsdfsd fsdfsdf) {- blah comment -}
putStrLn "")
[1, 2, 3]
[ 1 {- foo -}
, ( 2 {- bar -}
, 2.5 {- mu -}
)
, 3
]
foo = 1 {- after foo -}
Multi-line comments with multi-line contents
{- | This is some random comment.
Here is more docs and such.
Etc.
-}
main = putStrLn "Hello, World!"
{- This is another random comment. -}
Comments on functions in where clause
-- https://github.com/mihaimaruseac/hindent/issues/540
topLevelFunc1 = f
where
-- comment on func in where clause
-- stays in the where clause
f = undefined
topLevelFunc2 = f . g
-- Another comment
where
{- multi
line
comment -}
f = undefined -- single line comment
-- single line comment
-- Different size of indent
g :: a
g = undefined
Comments in a 'where' clause
foo = undefined
where
bar
-- A comment
= undefined
where
a = b
baz = undefined
Haddocks around data constructors
data Foo
-- | A haddock comment for 'Bar'.
= Bar
-- | A haddock comment for 'Baz'.
| Baz
-- | A haddock comment for 'Quuz'.
| Quuz
Unicode
α = γ * "ω"
-- υ
rec
and mdo
are valid identifiers unless RecursiveDo
is enabled
-- https://github.com/mihaimaruseac/hindent/issues/328
rec = undefined
mdo = undefined
The first character of an infix operator can be @
unless TypeApplications
is enabled.
-- https://github.com/mihaimaruseac/hindent/issues/421
a @: b = a + b
main = print (2 @: 2)
A complex, slow-to-print decl
{-# LANGUAGE TemplateHaskell #-}
quasiQuotes =
[ ( ''[]
, \(typeVariable:_) _automaticPrinter ->
(let presentVar = varE (presentVarName typeVariable)
in lamE
[varP (presentVarName typeVariable)]
[|(let typeString = "[" ++ fst $(presentVar) ++ "]"
in ( typeString
, \xs ->
case fst $(presentVar) of
"GHC.Types.Char" ->
ChoicePresentation
"String"
[ ( "String"
, StringPresentation
"String"
(concatMap
getCh
(map (snd $(presentVar)) xs)))
, ( "List of characters"
, ListPresentation
typeString
(map (snd $(presentVar)) xs))
]
where getCh (CharPresentation "GHC.Types.Char" ch) =
ch
getCh (ChoicePresentation _ ((_, CharPresentation _ ch):_)) =
ch
getCh _ = ""
_ ->
ListPresentation
typeString
(map (snd $(presentVar)) xs)))|]))
]
Random snippet from hindent itself
exp' (App _ op a) = do
(fits, st) <- fitsOnOneLine (spaced (map pretty (f : args)))
if fits
then put st
else do
pretty f
newline
spaces <- getIndentSpaces
indented spaces (lined (map pretty args))
where
(f, args) = flatten op [a]
flatten :: Exp NodeInfo -> [Exp NodeInfo] -> (Exp NodeInfo, [Exp NodeInfo])
flatten (App _ f' a') b = flatten f' (a' : b)
flatten f' as = (f', as)
Quasi quotes
{-# LANGUAGE QuasiQuotes #-}
exp = [name|exp|]
f [qq|pattern|] = ()
Conditionals (#if
)
isDebug :: Bool
#if DEBUG
isDebug = True
#else
isDebug = False
#endif
Conditionals inside a where
with empty lines and CPP
-- https://github.com/mihaimaruseac/hindent/issues/779
foo = bar + baz
where
#if 0
bar = 1
baz = 1
#else
bar = 2
baz = 2
#endif
Macro definitions (#define
)
#define STRINGIFY(x) #x
f = STRINGIFY (y)
Escaped newlines
#define LONG_MACRO_DEFINITION \
data Pair a b = Pair \
{ first :: a \
, second :: b \
}
#define SHORT_MACRO_DEFINITION \
x
Language extensions are effective across CPP boundaries.
{-# LANGUAGE PatternSynonyms #-}
#if 1
pattern Foo :: Int -> Bar
#else
pattern Foo :: Int -> Bar
#endif
Code with >
s
> -- https://github.com/mihaimaruseac/hindent/issues/103
> foo :: a
> foo = undefined