module Language.Haskell.Formatter.Process.CodeOrdering
(orderImportDeclarations, orderRootImportEntities,
orderNestedImportEntities)
where
import qualified Language.Haskell.Exts.Syntax as Syntax
import qualified Language.Haskell.Formatter.Process.Code as Code
import qualified Language.Haskell.Formatter.Source as Source
import qualified Language.Haskell.Formatter.Toolkit.Visit as Visit
orderImportDeclarations ::
Code.LocatableCommentableCode ->
Code.LocatableCommentableCode
orderImportDeclarations :: LocatableCommentableCode -> LocatableCommentableCode
orderImportDeclarations = ([ImportDecl LocationCommentNote]
-> [ImportDecl LocationCommentNote])
-> LocatableCommentableCode -> LocatableCommentableCode
forall a.
([ImportDecl a] -> [ImportDecl a]) -> Module a -> Module a
replaceImportDeclarations (([ImportDecl LocationCommentNote]
-> [ImportDecl LocationCommentNote])
-> LocatableCommentableCode -> LocatableCommentableCode)
-> ([ImportDecl LocationCommentNote]
-> [ImportDecl LocationCommentNote])
-> LocatableCommentableCode
-> LocatableCommentableCode
forall a b. (a -> b) -> a -> b
$ (ImportDecl LocationCommentNote
-> (String, Bool, Bool, Bool, Maybe String, Maybe String,
Maybe (Bool, [[String]])))
-> [ImportDecl LocationCommentNote]
-> [ImportDecl LocationCommentNote]
forall b a. Ord b => (a -> b) -> [a] -> [a]
Visit.orderByKey ImportDecl LocationCommentNote
-> (String, Bool, Bool, Bool, Maybe String, Maybe String,
Maybe (Bool, [[String]]))
forall a.
ImportDecl a
-> (String, Bool, Bool, Bool, Maybe String, Maybe String,
Maybe (Bool, [[String]]))
key
where key :: ImportDecl a
-> (String, Bool, Bool, Bool, Maybe String, Maybe String,
Maybe (Bool, [[String]]))
key
(Syntax.ImportDecl a
_ ModuleName a
moduleName Bool
isQualified Bool
isWithSource Bool
isSafe
Maybe String
package Maybe (ModuleName a)
alias Maybe (ImportSpecList a)
entitiesList)
= (ModuleName a -> String
forall l. ModuleName l -> String
moduleNameKey ModuleName a
moduleName, Bool
isQualified, Bool
isWithSource, Bool
isSafe,
Maybe String
package, (ModuleName a -> String) -> Maybe (ModuleName a) -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ModuleName a -> String
forall l. ModuleName l -> String
moduleNameKey Maybe (ModuleName a)
alias,
(ImportSpecList a -> (Bool, [[String]]))
-> Maybe (ImportSpecList a) -> Maybe (Bool, [[String]])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ImportSpecList a -> (Bool, [[String]])
forall a. ImportSpecList a -> (Bool, [[String]])
entitiesListKey Maybe (ImportSpecList a)
entitiesList)
moduleNameKey :: ModuleName l -> String
moduleNameKey (Syntax.ModuleName l
_ String
name) = String
name
entitiesListKey :: ImportSpecList a -> (Bool, [[String]])
entitiesListKey (Syntax.ImportSpecList a
_ Bool
isHiding [ImportSpec a]
entities)
= (Bool
isHiding, (ImportSpec a -> [String]) -> [ImportSpec a] -> [[String]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ImportSpec a -> [String]
forall a. ImportSpec a -> [String]
importEntityKey [ImportSpec a]
entities)
replaceImportDeclarations ::
([Syntax.ImportDecl a] -> [Syntax.ImportDecl a]) ->
Source.Module a -> Source.Module a
replaceImportDeclarations :: ([ImportDecl a] -> [ImportDecl a]) -> Module a -> Module a
replaceImportDeclarations [ImportDecl a] -> [ImportDecl a]
function (Syntax.Module a
a Maybe (ModuleHead a)
h [ModulePragma a]
p [ImportDecl a]
importDeclarations [Decl a]
d)
= a
-> Maybe (ModuleHead a)
-> [ModulePragma a]
-> [ImportDecl a]
-> [Decl a]
-> Module a
forall l.
l
-> Maybe (ModuleHead l)
-> [ModulePragma l]
-> [ImportDecl l]
-> [Decl l]
-> Module l
Syntax.Module a
a Maybe (ModuleHead a)
h [ModulePragma a]
p [ImportDecl a]
importDeclarations' [Decl a]
d
where importDeclarations' :: [ImportDecl a]
importDeclarations' = [ImportDecl a] -> [ImportDecl a]
function [ImportDecl a]
importDeclarations
replaceImportDeclarations [ImportDecl a] -> [ImportDecl a]
_ xmlPage :: Module a
xmlPage@Syntax.XmlPage{} = Module a
xmlPage
replaceImportDeclarations [ImportDecl a] -> [ImportDecl a]
function
(Syntax.XmlHybrid a
a Maybe (ModuleHead a)
h [ModulePragma a]
p [ImportDecl a]
importDeclarations [Decl a]
d XName a
xn [XAttr a]
xa Maybe (Exp a)
me [Exp a]
e)
= a
-> Maybe (ModuleHead a)
-> [ModulePragma a]
-> [ImportDecl a]
-> [Decl a]
-> XName a
-> [XAttr a]
-> Maybe (Exp a)
-> [Exp a]
-> Module a
forall l.
l
-> Maybe (ModuleHead l)
-> [ModulePragma l]
-> [ImportDecl l]
-> [Decl l]
-> XName l
-> [XAttr l]
-> Maybe (Exp l)
-> [Exp l]
-> Module l
Syntax.XmlHybrid a
a Maybe (ModuleHead a)
h [ModulePragma a]
p [ImportDecl a]
importDeclarations' [Decl a]
d XName a
xn [XAttr a]
xa Maybe (Exp a)
me [Exp a]
e
where importDeclarations' :: [ImportDecl a]
importDeclarations' = [ImportDecl a] -> [ImportDecl a]
function [ImportDecl a]
importDeclarations
importEntityKey :: Syntax.ImportSpec a -> [String]
importEntityKey :: ImportSpec a -> [String]
importEntityKey (Syntax.IVar a
_ Name a
name) = Name a -> [String]
forall a. Name a -> [String]
rootNameKey Name a
name
importEntityKey (Syntax.IAbs a
_ Namespace a
_ Name a
name) = Name a -> [String]
forall a. Name a -> [String]
rootNameKey Name a
name
importEntityKey (Syntax.IThingAll a
_ Name a
name) = Name a -> [String]
forall a. Name a -> [String]
rootNameKey Name a
name
importEntityKey (Syntax.IThingWith a
_ Name a
name [CName a]
entities)
= Name a -> String
forall a. Name a -> String
nameKey Name a
name String -> [String] -> [String]
forall a. a -> [a] -> [a]
: (CName a -> String) -> [CName a] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CName a -> String
forall a. CName a -> String
nestedImportEntityKey [CName a]
entities
rootNameKey :: Syntax.Name a -> [String]
rootNameKey :: Name a -> [String]
rootNameKey Name a
name = [Name a -> String
forall a. Name a -> String
nameKey Name a
name]
nameKey :: Syntax.Name a -> String
nameKey :: Name a -> String
nameKey (Syntax.Ident a
_ String
name) = String
name
nameKey (Syntax.Symbol a
_ String
name) = String
name
nestedImportEntityKey :: Syntax.CName a -> String
nestedImportEntityKey :: CName a -> String
nestedImportEntityKey (Syntax.VarName a
_ Name a
name) = Name a -> String
forall a. Name a -> String
nameKey Name a
name
nestedImportEntityKey (Syntax.ConName a
_ Name a
name) = Name a -> String
forall a. Name a -> String
nameKey Name a
name
orderRootImportEntities ::
Code.LocatableCommentableCode ->
Code.LocatableCommentableCode
orderRootImportEntities :: LocatableCommentableCode -> LocatableCommentableCode
orderRootImportEntities
= ([ImportSpec LocationCommentNote]
-> [ImportSpec LocationCommentNote])
-> LocatableCommentableCode -> LocatableCommentableCode
forall a.
([ImportSpec a] -> [ImportSpec a]) -> Module a -> Module a
replaceImportEntities (([ImportSpec LocationCommentNote]
-> [ImportSpec LocationCommentNote])
-> LocatableCommentableCode -> LocatableCommentableCode)
-> ([ImportSpec LocationCommentNote]
-> [ImportSpec LocationCommentNote])
-> LocatableCommentableCode
-> LocatableCommentableCode
forall a b. (a -> b) -> a -> b
$ (ImportSpec LocationCommentNote -> [String])
-> [ImportSpec LocationCommentNote]
-> [ImportSpec LocationCommentNote]
forall b a. Ord b => (a -> b) -> [a] -> [a]
Visit.orderByKey ImportSpec LocationCommentNote -> [String]
forall a. ImportSpec a -> [String]
importEntityKey
replaceImportEntities ::
([Syntax.ImportSpec a] -> [Syntax.ImportSpec a]) ->
Source.Module a -> Source.Module a
replaceImportEntities :: ([ImportSpec a] -> [ImportSpec a]) -> Module a -> Module a
replaceImportEntities [ImportSpec a] -> [ImportSpec a]
function
= ([ImportDecl a] -> [ImportDecl a]) -> Module a -> Module a
forall a.
([ImportDecl a] -> [ImportDecl a]) -> Module a -> Module a
replaceImportDeclarations (([ImportDecl a] -> [ImportDecl a]) -> Module a -> Module a)
-> ([ImportDecl a] -> [ImportDecl a]) -> Module a -> Module a
forall a b. (a -> b) -> a -> b
$ (ImportDecl a -> ImportDecl a) -> [ImportDecl a] -> [ImportDecl a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ImportDecl a -> ImportDecl a
replaceDeclaration
where replaceDeclaration :: ImportDecl a -> ImportDecl a
replaceDeclaration ImportDecl a
importDeclaration
= ImportDecl a
importDeclaration{importSpecs :: Maybe (ImportSpecList a)
Syntax.importSpecs = Maybe (ImportSpecList a)
entitiesList'}
where entitiesList' :: Maybe (ImportSpecList a)
entitiesList' = (ImportSpecList a -> ImportSpecList a)
-> Maybe (ImportSpecList a) -> Maybe (ImportSpecList a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ImportSpecList a -> ImportSpecList a
replaceList Maybe (ImportSpecList a)
entitiesList
entitiesList :: Maybe (ImportSpecList a)
entitiesList = ImportDecl a -> Maybe (ImportSpecList a)
forall l. ImportDecl l -> Maybe (ImportSpecList l)
Syntax.importSpecs ImportDecl a
importDeclaration
replaceList :: ImportSpecList a -> ImportSpecList a
replaceList (Syntax.ImportSpecList a
annotation Bool
isHiding [ImportSpec a]
entities)
= a -> Bool -> [ImportSpec a] -> ImportSpecList a
forall l. l -> Bool -> [ImportSpec l] -> ImportSpecList l
Syntax.ImportSpecList a
annotation Bool
isHiding [ImportSpec a]
entities'
where entities' :: [ImportSpec a]
entities' = [ImportSpec a] -> [ImportSpec a]
function [ImportSpec a]
entities
orderNestedImportEntities ::
Code.LocatableCommentableCode ->
Code.LocatableCommentableCode
orderNestedImportEntities :: LocatableCommentableCode -> LocatableCommentableCode
orderNestedImportEntities
= ([CName LocationCommentNote] -> [CName LocationCommentNote])
-> LocatableCommentableCode -> LocatableCommentableCode
forall a. ([CName a] -> [CName a]) -> Module a -> Module a
replaceNestedImportEntities (([CName LocationCommentNote] -> [CName LocationCommentNote])
-> LocatableCommentableCode -> LocatableCommentableCode)
-> ([CName LocationCommentNote] -> [CName LocationCommentNote])
-> LocatableCommentableCode
-> LocatableCommentableCode
forall a b. (a -> b) -> a -> b
$ (CName LocationCommentNote -> String)
-> [CName LocationCommentNote] -> [CName LocationCommentNote]
forall b a. Ord b => (a -> b) -> [a] -> [a]
Visit.orderByKey CName LocationCommentNote -> String
forall a. CName a -> String
nestedImportEntityKey
replaceNestedImportEntities ::
([Syntax.CName a] -> [Syntax.CName a]) ->
Source.Module a -> Source.Module a
replaceNestedImportEntities :: ([CName a] -> [CName a]) -> Module a -> Module a
replaceNestedImportEntities [CName a] -> [CName a]
function = ([ImportSpec a] -> [ImportSpec a]) -> Module a -> Module a
forall a.
([ImportSpec a] -> [ImportSpec a]) -> Module a -> Module a
replaceImportEntities (([ImportSpec a] -> [ImportSpec a]) -> Module a -> Module a)
-> ([ImportSpec a] -> [ImportSpec a]) -> Module a -> Module a
forall a b. (a -> b) -> a -> b
$ (ImportSpec a -> ImportSpec a) -> [ImportSpec a] -> [ImportSpec a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ImportSpec a -> ImportSpec a
replace
where replace :: ImportSpec a -> ImportSpec a
replace (Syntax.IThingWith a
annotation Name a
name [CName a]
entities)
= a -> Name a -> [CName a] -> ImportSpec a
forall l. l -> Name l -> [CName l] -> ImportSpec l
Syntax.IThingWith a
annotation Name a
name [CName a]
entities'
where entities' :: [CName a]
entities' = [CName a] -> [CName a]
function [CName a]
entities
replace ImportSpec a
entity = ImportSpec a
entity