Skip to content

Commit

Permalink
Merge pull request #83/#124 from sniperrifle2004/import
Browse files Browse the repository at this point in the history
  • Loading branch information
lspitzner committed Mar 21, 2018
2 parents 1330aeb + 8de56ba commit f1536b8
Show file tree
Hide file tree
Showing 16 changed files with 1,091 additions and 49 deletions.
3 changes: 3 additions & 0 deletions brittany.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -67,6 +67,9 @@ library {
Language.Haskell.Brittany.Internal.Layouters.Expr
Language.Haskell.Brittany.Internal.Layouters.Stmt
Language.Haskell.Brittany.Internal.Layouters.Pattern
Language.Haskell.Brittany.Internal.Layouters.IE
Language.Haskell.Brittany.Internal.Layouters.Import
Language.Haskell.Brittany.Internal.Layouters.Module
Language.Haskell.Brittany.Internal.Transformations.Alt
Language.Haskell.Brittany.Internal.Transformations.Floating
Language.Haskell.Brittany.Internal.Transformations.Par
Expand Down
294 changes: 294 additions & 0 deletions src-literatetests/10-tests.blt
Original file line number Diff line number Diff line change
Expand Up @@ -565,3 +565,297 @@ func =
]
++ [ccccccccccccccccccccccccccccccccccccccccccccccccccccccccc]


###############################################################################
###############################################################################
###############################################################################
#group module
###############################################################################
###############################################################################
###############################################################################

#test simple
module Main where

#test no-exports
module Main () where

#test one-export
module Main (main) where

#test several-exports
module Main (main, test1, test2) where

#test many-exports
module Main
( main
, test1
, test2
, test3
, test4
, test5
, test6
, test7
, test8
, test9
)
where

#test exports-with-comments
module Main
( main
-- main
, test1
, test2
-- Test 3
, test3
, test4
-- Test 5
, test5
-- Test 6
)
where

#test simple-export-with-things
module Main (Test(..)) where

#test simple-export-with-module-contents
module Main (module Main) where

#test export-with-things
module Main (Test(Test, a, b)) where

#test export-with-things-comment
-- comment1

module Main
( Test(Test, a, b)
, foo -- comment2
) -- comment3
where

#test export-with-empty-thing
module Main (Test()) where

#test empty-with-comment
-- Intentionally left empty

###############################################################################
###############################################################################
###############################################################################
#group module.import
###############################################################################
###############################################################################
###############################################################################

#test simple-import
import Data.List

#test simple-import-alias
import Data.List as L

#test simple-qualified-import
import qualified Data.List

#test simple-qualified-import-alias
import qualified Data.List as L

#test simple-safe
import safe Data.List as L

#test simple-source
import {-# SOURCE #-} Data.List ( )

#test simple-safe-qualified
import safe qualified Data.List

#test simple-safe-qualified-source
import {-# SOURCE #-} safe qualified Data.List

#test simple-qualified-package
import qualified "base" Data.List

#test qualifier-effect
import {-# SOURCE #-} safe qualified "base" Data.List as L
import {-# SOURCE #-} safe qualified "base" Data.List ( )
import {-# SOURCE #-} safe qualified Data.List hiding ( )

#test instances-only
import qualified Data.List ( )

#test one-element
import Data.List ( nub )

#test several-elements
import Data.List ( nub
, foldl'
, indexElem
)

#test a-ridiculous-amount-of-elements
import Test ( Long
, list
, with
, items
, that
, will
, not
, quite
, fit
, onA
, single
, line
, anymore
)

#test with-things
import Test ( T
, T2()
, T3(..)
, T4(T4)
, T5(T5, t5)
, T6((<|>))
, (+)
)

#test hiding
import Test hiding ( )
import Test as T
hiding ( )

#test long-module-name
import TestJustShortEnoughModuleNameLikeThisOne ( )
import TestJustAbitToLongModuleNameLikeThisOneIs
( )

import TestJustShortEnoughModuleNameLikeThisOn as T
import TestJustAbitToLongModuleNameLikeThisOneI
as T

import TestJustShortEnoughModuleNameLike hiding ( )
import TestJustAbitToLongModuleNameLikeTh
hiding ( )

import MoreThanSufficientlyLongModuleNameWithSome
( items
, that
, will
, not
, fit
, inA
, compact
, layout
)

import {-# SOURCE #-} safe qualified "qualifiers" AlsoAff ( )
import {-# SOURCE #-} safe qualified "qualifiers" AlsoAffe
( )

import {-# SOURCE #-} safe qualified "qualifiers" AlsoAf as T
import {-# SOURCE #-} safe qualified "qualifiers" AlsoAff
as T
import {-# SOURCE #-} safe qualified "qualifier" A hiding ( )
import {-# SOURCE #-} safe qualified "qualifiers" A
hiding ( )

#test import-with-comments
-- Test
import Data.List ( nub ) -- Test
{- Test -}
import qualified Data.List as L
( foldl' ) {- Test -}

-- Test
import Test ( test )

#test import-with-comments-2

import Test ( abc
, def
-- comment
)

#test import-with-comments-3

import Test ( abc
-- comment
)

#test import-with-comments-4
import Test ( abc
-- comment
, def
, ghi
{- comment -}
, jkl
-- comment
)

#test import-with-comments-5
import Test ( -- comment
)

#test long-bindings
import Test ( longbindingNameThatoverflowsColum
)
import Test ( Long
( List
, Of
, Things
)
)

#test things-with-with-comments
import Test ( Thing
( -- Comments
)
)
import Test ( Thing
( Item
-- and Comment
)
)
import Test ( Thing
( With
-- Comments
, and
-- also
, items
-- !
)
)
#test prefer-dense-empty-list
import VeryLongModuleNameThatCouldEvenCauseAnEmptyBindingListToExpandIntoMultipleLine
( )

#test preamble full-preamble
{-# 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 )
3 changes: 3 additions & 0 deletions src-literatetests/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -169,11 +169,14 @@ defaultTestConfig = Config
, _lconfig_indentWhereSpecial = coerce True
, _lconfig_indentListSpecial = coerce True
, _lconfig_importColumn = coerce (60 :: Int)
, _lconfig_importAsColumn = coerce (60 :: Int)
, _lconfig_altChooser = coerce $ AltChooserBoundedSearch 3
, _lconfig_columnAlignMode = coerce (ColumnAlignModeMajority 0.7)
, _lconfig_alignmentLimit = coerce (30 :: Int)
, _lconfig_alignmentBreakOnMultiline = coerce True
, _lconfig_hangingTypeSignature = coerce False
, _lconfig_reformatModulePreamble = coerce True
, _lconfig_allowSingleLineExportList = coerce True
}
, _conf_errorHandling = (_conf_errorHandling staticDefaultConfig)
{ _econf_omit_output_valid_check = coerce True
Expand Down
Loading

0 comments on commit f1536b8

Please sign in to comment.