{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RecordWildCards #-}
module Ormolu.Imports.Grouping
( Import (..),
prepareExistingGroups,
groupImports,
)
where
import Data.Bifunctor (Bifunctor (..))
import Data.Foldable (toList)
import Data.Function (on)
import Data.List (groupBy, minimumBy, sortOn)
import Data.List.NonEmpty (NonEmpty)
import Data.List.NonEmpty qualified as NonEmpty
import Data.Set (Set)
import Data.Set qualified as Set
import Distribution.ModuleName qualified as Cabal
import GHC.Hs (GhcPs, getLocA)
import Language.Haskell.Syntax (LImportDecl, ModuleName, moduleNameString)
import Ormolu.Config (ImportGroup (..), ImportGroupRule (..), ImportGrouping (..), ImportModuleMatcher (..))
import Ormolu.Config qualified as Config
import Ormolu.Utils (ghcModuleNameToCabal, groupBy', separatedByBlank)
import Ormolu.Utils.Glob (matchesGlob)
newtype ImportGroups = ImportGroups (NonEmpty ImportGroup)
data Import = Import
{ Import -> ModuleName
importName :: ModuleName,
Import -> Bool
importQualified :: Bool
}
importGroupSingleStrategy :: ImportGroups
importGroupSingleStrategy :: ImportGroups
importGroupSingleStrategy =
NonEmpty ImportGroup -> ImportGroups
ImportGroups (NonEmpty ImportGroup -> ImportGroups)
-> NonEmpty ImportGroup -> ImportGroups
forall a b. (a -> b) -> a -> b
$
ImportGroup -> NonEmpty ImportGroup
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
ImportGroup
{ igName :: Maybe String
igName = Maybe String
forall a. Maybe a
Nothing,
igRules :: NonEmpty ImportGroupRule
igRules = ImportGroupRule -> NonEmpty ImportGroupRule
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImportGroupRule
matchAllImportRule
}
importGroupByQualifiedStrategy :: ImportGroups
importGroupByQualifiedStrategy :: ImportGroups
importGroupByQualifiedStrategy =
NonEmpty ImportGroup -> ImportGroups
ImportGroups (NonEmpty ImportGroup -> ImportGroups)
-> NonEmpty ImportGroup -> ImportGroups
forall a b. (a -> b) -> a -> b
$
[ImportGroup] -> NonEmpty ImportGroup
forall a. HasCallStack => [a] -> NonEmpty a
NonEmpty.fromList
[ ImportGroup
{ igName :: Maybe String
igName = Maybe String
forall a. Maybe a
Nothing,
igRules :: NonEmpty ImportGroupRule
igRules = ImportGroupRule -> NonEmpty ImportGroupRule
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImportGroupRule -> NonEmpty ImportGroupRule)
-> ImportGroupRule -> NonEmpty ImportGroupRule
forall a b. (a -> b) -> a -> b
$ ImportGroupRule -> ImportGroupRule
withUnqualifiedOnly ImportGroupRule
matchAllImportRule
},
ImportGroup
{ igName :: Maybe String
igName = Maybe String
forall a. Maybe a
Nothing,
igRules :: NonEmpty ImportGroupRule
igRules = ImportGroupRule -> NonEmpty ImportGroupRule
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImportGroupRule -> NonEmpty ImportGroupRule)
-> ImportGroupRule -> NonEmpty ImportGroupRule
forall a b. (a -> b) -> a -> b
$ ImportGroupRule -> ImportGroupRule
withQualifiedOnly ImportGroupRule
matchAllImportRule
}
]
importGroupByScopeStrategy :: ImportGroups
importGroupByScopeStrategy :: ImportGroups
importGroupByScopeStrategy =
NonEmpty ImportGroup -> ImportGroups
ImportGroups (NonEmpty ImportGroup -> ImportGroups)
-> NonEmpty ImportGroup -> ImportGroups
forall a b. (a -> b) -> a -> b
$
[ImportGroup] -> NonEmpty ImportGroup
forall a. HasCallStack => [a] -> NonEmpty a
NonEmpty.fromList
[ ImportGroup
{ igName :: Maybe String
igName = Maybe String
forall a. Maybe a
Nothing,
igRules :: NonEmpty ImportGroupRule
igRules = ImportGroupRule -> NonEmpty ImportGroupRule
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImportGroupRule
matchAllImportRule
},
ImportGroup
{ igName :: Maybe String
igName = Maybe String
forall a. Maybe a
Nothing,
igRules :: NonEmpty ImportGroupRule
igRules = ImportGroupRule -> NonEmpty ImportGroupRule
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ImportGroupRule
matchLocalModulesRule
}
]
importGroupByScopeThenQualifiedStrategy :: ImportGroups
importGroupByScopeThenQualifiedStrategy :: ImportGroups
importGroupByScopeThenQualifiedStrategy =
NonEmpty ImportGroup -> ImportGroups
ImportGroups (NonEmpty ImportGroup -> ImportGroups)
-> NonEmpty ImportGroup -> ImportGroups
forall a b. (a -> b) -> a -> b
$
[ImportGroup] -> NonEmpty ImportGroup
forall a. HasCallStack => [a] -> NonEmpty a
NonEmpty.fromList
[ ImportGroup
{ igName :: Maybe String
igName = Maybe String
forall a. Maybe a
Nothing,
igRules :: NonEmpty ImportGroupRule
igRules = ImportGroupRule -> NonEmpty ImportGroupRule
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImportGroupRule -> NonEmpty ImportGroupRule)
-> ImportGroupRule -> NonEmpty ImportGroupRule
forall a b. (a -> b) -> a -> b
$ ImportGroupRule -> ImportGroupRule
withQualified ImportGroupRule
matchModule
}
| ImportGroupRule
matchModule <- [ImportGroupRule
matchAllImportRule, ImportGroupRule
matchLocalModulesRule],
ImportGroupRule -> ImportGroupRule
withQualified <- [ImportGroupRule -> ImportGroupRule
withUnqualifiedOnly, ImportGroupRule -> ImportGroupRule
withQualifiedOnly]
]
groupsFromConfig :: Config.ImportGrouping -> ImportGroups
groupsFromConfig :: ImportGrouping -> ImportGroups
groupsFromConfig =
\case
ImportGrouping
Config.ImportGroupLegacy -> ImportGroups
importGroupSingleStrategy
ImportGrouping
Config.ImportGroupPreserve -> ImportGroups
importGroupSingleStrategy
ImportGrouping
Config.ImportGroupSingle -> ImportGroups
importGroupSingleStrategy
ImportGrouping
Config.ImportGroupByQualified -> ImportGroups
importGroupByQualifiedStrategy
ImportGrouping
Config.ImportGroupByScope -> ImportGroups
importGroupByScopeStrategy
ImportGrouping
Config.ImportGroupByScopeThenQualified -> ImportGroups
importGroupByScopeThenQualifiedStrategy
Config.ImportGroupCustom NonEmpty ImportGroup
igs -> NonEmpty ImportGroup -> ImportGroups
ImportGroups NonEmpty ImportGroup
igs
matchAllImportRule :: ImportGroupRule
matchAllImportRule :: ImportGroupRule
matchAllImportRule =
ImportGroupRule
{ igrModuleMatcher :: ImportModuleMatcher
igrModuleMatcher = ImportModuleMatcher
MatchAllModules,
igrQualifiedMatcher :: QualifiedImportMatcher
igrQualifiedMatcher = QualifiedImportMatcher
Config.MatchBothQualifiedAndUnqualified,
igrPriority :: ImportRulePriority
igrPriority = ImportRulePriority
Config.matchAllRulePriority
}
matchLocalModulesRule :: ImportGroupRule
matchLocalModulesRule :: ImportGroupRule
matchLocalModulesRule =
ImportGroupRule
{ igrModuleMatcher :: ImportModuleMatcher
igrModuleMatcher = ImportModuleMatcher
MatchLocalModules,
igrQualifiedMatcher :: QualifiedImportMatcher
igrQualifiedMatcher = QualifiedImportMatcher
Config.MatchBothQualifiedAndUnqualified,
igrPriority :: ImportRulePriority
igrPriority = ImportRulePriority
Config.matchLocalRulePriority
}
withQualifiedOnly :: ImportGroupRule -> ImportGroupRule
withQualifiedOnly :: ImportGroupRule -> ImportGroupRule
withQualifiedOnly ImportGroupRule {ImportModuleMatcher
QualifiedImportMatcher
ImportRulePriority
igrModuleMatcher :: ImportGroupRule -> ImportModuleMatcher
igrQualifiedMatcher :: ImportGroupRule -> QualifiedImportMatcher
igrPriority :: ImportGroupRule -> ImportRulePriority
igrModuleMatcher :: ImportModuleMatcher
igrQualifiedMatcher :: QualifiedImportMatcher
igrPriority :: ImportRulePriority
..} =
ImportGroupRule
{ igrQualifiedMatcher :: QualifiedImportMatcher
igrQualifiedMatcher = QualifiedImportMatcher
Config.MatchQualifiedOnly,
ImportModuleMatcher
ImportRulePriority
igrModuleMatcher :: ImportModuleMatcher
igrPriority :: ImportRulePriority
igrModuleMatcher :: ImportModuleMatcher
igrPriority :: ImportRulePriority
..
}
withUnqualifiedOnly :: ImportGroupRule -> ImportGroupRule
withUnqualifiedOnly :: ImportGroupRule -> ImportGroupRule
withUnqualifiedOnly ImportGroupRule {ImportModuleMatcher
QualifiedImportMatcher
ImportRulePriority
igrModuleMatcher :: ImportGroupRule -> ImportModuleMatcher
igrQualifiedMatcher :: ImportGroupRule -> QualifiedImportMatcher
igrPriority :: ImportGroupRule -> ImportRulePriority
igrModuleMatcher :: ImportModuleMatcher
igrQualifiedMatcher :: QualifiedImportMatcher
igrPriority :: ImportRulePriority
..} =
ImportGroupRule
{ igrQualifiedMatcher :: QualifiedImportMatcher
igrQualifiedMatcher = QualifiedImportMatcher
Config.MatchUnqualifiedOnly,
ImportModuleMatcher
ImportRulePriority
igrModuleMatcher :: ImportModuleMatcher
igrPriority :: ImportRulePriority
igrModuleMatcher :: ImportModuleMatcher
igrPriority :: ImportRulePriority
..
}
matchesRule :: Set Cabal.ModuleName -> Import -> ImportGroupRule -> Bool
matchesRule :: Set ModuleName -> Import -> ImportGroupRule -> Bool
matchesRule Set ModuleName
localMods Import {Bool
ModuleName
importName :: Import -> ModuleName
importQualified :: Import -> Bool
importName :: ModuleName
importQualified :: Bool
..} ImportGroupRule {ImportModuleMatcher
QualifiedImportMatcher
ImportRulePriority
igrModuleMatcher :: ImportGroupRule -> ImportModuleMatcher
igrQualifiedMatcher :: ImportGroupRule -> QualifiedImportMatcher
igrPriority :: ImportGroupRule -> ImportRulePriority
igrModuleMatcher :: ImportModuleMatcher
igrQualifiedMatcher :: QualifiedImportMatcher
igrPriority :: ImportRulePriority
..} = Bool
matchesModules Bool -> Bool -> Bool
&& Bool
matchesQualified
where
matchesModules :: Bool
matchesModules = case ImportModuleMatcher
igrModuleMatcher of
ImportModuleMatcher
MatchAllModules -> Bool
True
ImportModuleMatcher
MatchLocalModules -> ModuleName -> ModuleName
ghcModuleNameToCabal ModuleName
importName ModuleName -> Set ModuleName -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set ModuleName
localMods
MatchGlob Glob
gl -> ModuleName -> String
moduleNameString ModuleName
importName String -> Glob -> Bool
`matchesGlob` Glob
gl
matchesQualified :: Bool
matchesQualified = case QualifiedImportMatcher
igrQualifiedMatcher of
QualifiedImportMatcher
Config.MatchQualifiedOnly -> Bool
importQualified
QualifiedImportMatcher
Config.MatchUnqualifiedOnly -> Bool -> Bool
not Bool
importQualified
QualifiedImportMatcher
Config.MatchBothQualifiedAndUnqualified -> Bool
True
prepareExistingGroups :: ImportGrouping -> Bool -> [LImportDecl GhcPs] -> [[LImportDecl GhcPs]]
prepareExistingGroups :: ImportGrouping
-> Bool -> [LImportDecl GhcPs] -> [[LImportDecl GhcPs]]
prepareExistingGroups ImportGrouping
ig Bool
respectful =
case ImportGrouping
ig of
ImportGrouping
ImportGroupPreserve -> [LImportDecl GhcPs] -> [[LImportDecl GhcPs]]
[GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
-> [[GenLocated SrcSpanAnnA (ImportDecl GhcPs)]]
forall {e}.
[GenLocated SrcSpanAnnA e] -> [[GenLocated SrcSpanAnnA e]]
preserveGroups
ImportGrouping
ImportGroupLegacy | Bool
respectful -> [LImportDecl GhcPs] -> [[LImportDecl GhcPs]]
[GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
-> [[GenLocated SrcSpanAnnA (ImportDecl GhcPs)]]
forall {e}.
[GenLocated SrcSpanAnnA e] -> [[GenLocated SrcSpanAnnA e]]
preserveGroups
ImportGrouping
_ -> [LImportDecl GhcPs] -> [[LImportDecl GhcPs]]
[GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
-> [[GenLocated SrcSpanAnnA (ImportDecl GhcPs)]]
forall {a}. a -> [a]
flattenGroups
where
preserveGroups :: [GenLocated SrcSpanAnnA e] -> [[GenLocated SrcSpanAnnA e]]
preserveGroups = (NonEmpty (GenLocated SrcSpanAnnA e) -> [GenLocated SrcSpanAnnA e])
-> [NonEmpty (GenLocated SrcSpanAnnA e)]
-> [[GenLocated SrcSpanAnnA e]]
forall a b. (a -> b) -> [a] -> [b]
map NonEmpty (GenLocated SrcSpanAnnA e) -> [GenLocated SrcSpanAnnA e]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList ([NonEmpty (GenLocated SrcSpanAnnA e)]
-> [[GenLocated SrcSpanAnnA e]])
-> ([GenLocated SrcSpanAnnA e]
-> [NonEmpty (GenLocated SrcSpanAnnA e)])
-> [GenLocated SrcSpanAnnA e]
-> [[GenLocated SrcSpanAnnA e]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenLocated SrcSpanAnnA e -> GenLocated SrcSpanAnnA e -> Bool)
-> [GenLocated SrcSpanAnnA e]
-> [NonEmpty (GenLocated SrcSpanAnnA e)]
forall a. (a -> a -> Bool) -> [a] -> [NonEmpty a]
groupBy' (\GenLocated SrcSpanAnnA e
x GenLocated SrcSpanAnnA e
y -> Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (GenLocated SrcSpanAnnA e -> SrcSpan)
-> GenLocated SrcSpanAnnA e -> GenLocated SrcSpanAnnA e -> Bool
forall a. (a -> SrcSpan) -> a -> a -> Bool
separatedByBlank GenLocated SrcSpanAnnA e -> SrcSpan
forall a e. HasLoc a => GenLocated a e -> SrcSpan
getLocA GenLocated SrcSpanAnnA e
x GenLocated SrcSpanAnnA e
y)
flattenGroups :: a -> [a]
flattenGroups = a -> [a]
forall {a}. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
groupImports :: forall x. ImportGrouping -> Set Cabal.ModuleName -> (x -> Import) -> [x] -> [[x]]
groupImports :: forall x.
ImportGrouping -> Set ModuleName -> (x -> Import) -> [x] -> [[x]]
groupImports ImportGrouping
ig Set ModuleName
localModules x -> Import
fToImport = [(Int, x)] -> [[x]]
regroup ([(Int, x)] -> [[x]]) -> ([x] -> [(Int, x)]) -> [x] -> [[x]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (x -> (Int, x)) -> [x] -> [(Int, x)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([(Int, [ImportGroupRule])], x) -> (Int, x)
breakTies (([(Int, [ImportGroupRule])], x) -> (Int, x))
-> (x -> ([(Int, [ImportGroupRule])], x)) -> x -> (Int, x)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. x -> ([(Int, [ImportGroupRule])], x)
matchRules)
where
ImportGroups NonEmpty ImportGroup
igs = ImportGrouping -> ImportGroups
groupsFromConfig ImportGrouping
ig
indexedGroupRules :: [(Int, [ImportGroupRule])]
indexedGroupRules :: [(Int, [ImportGroupRule])]
indexedGroupRules = [Int] -> [[ImportGroupRule]] -> [(Int, [ImportGroupRule])]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0 ..] (NonEmpty ImportGroupRule -> [ImportGroupRule]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (NonEmpty ImportGroupRule -> [ImportGroupRule])
-> (ImportGroup -> NonEmpty ImportGroupRule)
-> ImportGroup
-> [ImportGroupRule]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ImportGroup -> NonEmpty ImportGroupRule
igRules (ImportGroup -> [ImportGroupRule])
-> [ImportGroup] -> [[ImportGroupRule]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmpty ImportGroup -> [ImportGroup]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty ImportGroup
igs)
matchRules :: x -> ([(Int, [ImportGroupRule])], x)
matchRules :: x -> ([(Int, [ImportGroupRule])], x)
matchRules x
x =
let imp :: Import
imp = x -> Import
fToImport x
x
testRule :: (a, t ImportGroupRule) -> Bool
testRule (a
_, t ImportGroupRule
rules) = (ImportGroupRule -> Bool) -> t ImportGroupRule -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Set ModuleName -> Import -> ImportGroupRule -> Bool
matchesRule Set ModuleName
localModules Import
imp) t ImportGroupRule
rules
in (((Int, [ImportGroupRule]) -> Bool)
-> [(Int, [ImportGroupRule])] -> [(Int, [ImportGroupRule])]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int, [ImportGroupRule]) -> Bool
forall {t :: * -> *} {a}.
Foldable t =>
(a, t ImportGroupRule) -> Bool
testRule [(Int, [ImportGroupRule])]
indexedGroupRules, x
x)
breakTies :: ([(Int, [ImportGroupRule])], x) -> (Int, x)
breakTies :: ([(Int, [ImportGroupRule])], x) -> (Int, x)
breakTies ([], x
x) =
(Int
forall a. Bounded a => a
maxBound, x
x)
breakTies ([(Int, [ImportGroupRule])]
matches, x
x) =
((Int, ImportRulePriority) -> Int
forall a b. (a, b) -> a
fst ((Int, ImportRulePriority) -> Int)
-> ([(Int, ImportRulePriority)] -> (Int, ImportRulePriority))
-> [(Int, ImportRulePriority)]
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, ImportRulePriority)
-> (Int, ImportRulePriority) -> Ordering)
-> [(Int, ImportRulePriority)] -> (Int, ImportRulePriority)
forall (t :: * -> *) a.
Foldable t =>
(a -> a -> Ordering) -> t a -> a
minimumBy (ImportRulePriority -> ImportRulePriority -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (ImportRulePriority -> ImportRulePriority -> Ordering)
-> ((Int, ImportRulePriority) -> ImportRulePriority)
-> (Int, ImportRulePriority)
-> (Int, ImportRulePriority)
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (Int, ImportRulePriority) -> ImportRulePriority
forall a b. (a, b) -> b
snd) ([(Int, ImportRulePriority)] -> Int)
-> [(Int, ImportRulePriority)] -> Int
forall a b. (a -> b) -> a -> b
$ ([ImportGroupRule] -> ImportRulePriority)
-> (Int, [ImportGroupRule]) -> (Int, ImportRulePriority)
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second ([ImportRulePriority] -> ImportRulePriority
forall a. Ord a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum ([ImportRulePriority] -> ImportRulePriority)
-> ([ImportGroupRule] -> [ImportRulePriority])
-> [ImportGroupRule]
-> ImportRulePriority
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ImportGroupRule -> ImportRulePriority)
-> [ImportGroupRule] -> [ImportRulePriority]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ImportGroupRule -> ImportRulePriority
igrPriority) ((Int, [ImportGroupRule]) -> (Int, ImportRulePriority))
-> [(Int, [ImportGroupRule])] -> [(Int, ImportRulePriority)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Int, [ImportGroupRule])]
matches, x
x)
regroup :: [(Int, x)] -> [[x]]
regroup :: [(Int, x)] -> [[x]]
regroup = ([(Int, x)] -> [x]) -> [[(Int, x)]] -> [[x]]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((Int, x) -> x) -> [(Int, x)] -> [x]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int, x) -> x
forall a b. (a, b) -> b
snd) ([[(Int, x)]] -> [[x]])
-> ([(Int, x)] -> [[(Int, x)]]) -> [(Int, x)] -> [[x]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, x) -> (Int, x) -> Bool) -> [(Int, x)] -> [[(Int, x)]]
forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
(==) (Int -> Int -> Bool)
-> ((Int, x) -> Int) -> (Int, x) -> (Int, x) -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (Int, x) -> Int
forall a b. (a, b) -> a
fst) ([(Int, x)] -> [[(Int, x)]])
-> ([(Int, x)] -> [(Int, x)]) -> [(Int, x)] -> [[(Int, x)]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, x) -> Int) -> [(Int, x)] -> [(Int, x)]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (Int, x) -> Int
forall a b. (a, b) -> a
fst