{-# LANGUAGE GADTs #-}
module GHC.Cmm.Dominators
(
DominatorSet(..)
, GraphWithDominators(..)
, RPNum
, graphWithDominators
, graphMap
, gwdRPNumber
, gwdDominatorsOf
, gwdDominatorTree
, dominatorsMember
, intersectDominators
)
where
import GHC.Prelude
import Data.Array.IArray
import Data.Foldable()
import qualified Data.Tree as Tree
import qualified Data.IntMap.Strict as IM
import qualified Data.IntSet as IS
import qualified GHC.CmmToAsm.CFG.Dominators as LT
import GHC.Cmm.Dataflow
import GHC.Cmm.Dataflow.Block
import GHC.Cmm.Dataflow.Collections
import GHC.Cmm.Dataflow.Graph
import GHC.Cmm.Dataflow.Label
import GHC.Cmm
import GHC.Utils.Outputable( Outputable(..), text, int, hcat, (<+>))
import GHC.Utils.Misc
import GHC.Utils.Panic
data DominatorSet = ImmediateDominator { DominatorSet -> Label
ds_label :: Label
, DominatorSet -> DominatorSet
ds_parent :: DominatorSet
}
| EntryNode
deriving (DominatorSet -> DominatorSet -> Bool
(DominatorSet -> DominatorSet -> Bool)
-> (DominatorSet -> DominatorSet -> Bool) -> Eq DominatorSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DominatorSet -> DominatorSet -> Bool
== :: DominatorSet -> DominatorSet -> Bool
$c/= :: DominatorSet -> DominatorSet -> Bool
/= :: DominatorSet -> DominatorSet -> Bool
Eq)
instance Outputable DominatorSet where
ppr :: DominatorSet -> SDoc
ppr DominatorSet
EntryNode = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"entry"
ppr (ImmediateDominator Label
l DominatorSet
parent) = Label -> SDoc
forall a. Outputable a => a -> SDoc
ppr Label
l SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"->" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> DominatorSet -> SDoc
forall a. Outputable a => a -> SDoc
ppr DominatorSet
parent
newtype RPNum = RPNum Int
deriving (RPNum -> RPNum -> Bool
(RPNum -> RPNum -> Bool) -> (RPNum -> RPNum -> Bool) -> Eq RPNum
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RPNum -> RPNum -> Bool
== :: RPNum -> RPNum -> Bool
$c/= :: RPNum -> RPNum -> Bool
/= :: RPNum -> RPNum -> Bool
Eq, Eq RPNum
Eq RPNum =>
(RPNum -> RPNum -> Ordering)
-> (RPNum -> RPNum -> Bool)
-> (RPNum -> RPNum -> Bool)
-> (RPNum -> RPNum -> Bool)
-> (RPNum -> RPNum -> Bool)
-> (RPNum -> RPNum -> RPNum)
-> (RPNum -> RPNum -> RPNum)
-> Ord RPNum
RPNum -> RPNum -> Bool
RPNum -> RPNum -> Ordering
RPNum -> RPNum -> RPNum
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RPNum -> RPNum -> Ordering
compare :: RPNum -> RPNum -> Ordering
$c< :: RPNum -> RPNum -> Bool
< :: RPNum -> RPNum -> Bool
$c<= :: RPNum -> RPNum -> Bool
<= :: RPNum -> RPNum -> Bool
$c> :: RPNum -> RPNum -> Bool
> :: RPNum -> RPNum -> Bool
$c>= :: RPNum -> RPNum -> Bool
>= :: RPNum -> RPNum -> Bool
$cmax :: RPNum -> RPNum -> RPNum
max :: RPNum -> RPNum -> RPNum
$cmin :: RPNum -> RPNum -> RPNum
min :: RPNum -> RPNum -> RPNum
Ord)
instance Show RPNum where
show :: RPNum -> String
show (RPNum Int
i) = String
"RP" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
i
instance Outputable RPNum where
ppr :: RPNum -> SDoc
ppr (RPNum Int
i) = [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hcat [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"RP", Int -> SDoc
forall doc. IsLine doc => Int -> doc
int Int
i]
dominatorsMember :: Label -> DominatorSet -> Bool
dominatorsMember :: Label -> DominatorSet -> Bool
dominatorsMember Label
lbl (ImmediateDominator Label
l DominatorSet
p) = Label
l Label -> Label -> Bool
forall a. Eq a => a -> a -> Bool
== Label
lbl Bool -> Bool -> Bool
|| Label -> DominatorSet -> Bool
dominatorsMember Label
lbl DominatorSet
p
dominatorsMember Label
_ DominatorSet
EntryNode = Bool
False
intersectDominators :: DominatorSet -> DominatorSet -> DominatorSet
intersectDominators :: DominatorSet -> DominatorSet -> DominatorSet
intersectDominators DominatorSet
ds DominatorSet
ds' = [Label] -> [Label] -> DominatorSet -> DominatorSet
commonPrefix (DominatorSet -> [Label] -> [Label]
revDoms DominatorSet
ds []) (DominatorSet -> [Label] -> [Label]
revDoms DominatorSet
ds' []) DominatorSet
EntryNode
where revDoms :: DominatorSet -> [Label] -> [Label]
revDoms DominatorSet
EntryNode [Label]
prev = [Label]
prev
revDoms (ImmediateDominator Label
lbl DominatorSet
doms) [Label]
prev = DominatorSet -> [Label] -> [Label]
revDoms DominatorSet
doms (Label
lblLabel -> [Label] -> [Label]
forall a. a -> [a] -> [a]
:[Label]
prev)
commonPrefix :: [Label] -> [Label] -> DominatorSet -> DominatorSet
commonPrefix (Label
a:[Label]
as) (Label
b:[Label]
bs) DominatorSet
doms
| Label
a Label -> Label -> Bool
forall a. Eq a => a -> a -> Bool
== Label
b = [Label] -> [Label] -> DominatorSet -> DominatorSet
commonPrefix [Label]
as [Label]
bs (Label -> DominatorSet -> DominatorSet
ImmediateDominator Label
a DominatorSet
doms)
commonPrefix [Label]
_ [Label]
_ DominatorSet
doms = DominatorSet
doms
data GraphWithDominators node =
GraphWithDominators { forall (node :: Extensibility -> Extensibility -> *).
GraphWithDominators node -> GenCmmGraph node
gwd_graph :: GenCmmGraph node
, forall (node :: Extensibility -> Extensibility -> *).
GraphWithDominators node -> LabelMap DominatorSet
gwd_dominators :: LabelMap DominatorSet
, forall (node :: Extensibility -> Extensibility -> *).
GraphWithDominators node -> LabelMap RPNum
gwd_rpnumbering :: LabelMap RPNum
}
graphWithDominators :: forall node .
(NonLocal node, HasDebugCallStack)
=> GenCmmGraph node
-> GraphWithDominators node
graphWithDominators :: forall (node :: Extensibility -> Extensibility -> *).
(NonLocal node, HasDebugCallStack) =>
GenCmmGraph node -> GraphWithDominators node
graphWithDominators GenCmmGraph node
g = GenCmmGraph node
-> LabelMap DominatorSet
-> LabelMap RPNum
-> GraphWithDominators node
forall (node :: Extensibility -> Extensibility -> *).
GenCmmGraph node
-> LabelMap DominatorSet
-> LabelMap RPNum
-> GraphWithDominators node
GraphWithDominators ([Block node C C] -> GenCmmGraph node -> GenCmmGraph node
forall (node :: Extensibility -> Extensibility -> *).
NonLocal node =>
[Block node C C] -> GenCmmGraph node -> GenCmmGraph node
reachable [Block node C C]
rpblocks GenCmmGraph node
g) LabelMap DominatorSet
dmap LabelMap RPNum
rpmap
where rpblocks :: [Block node C C]
rpblocks = LabelMap (Block node C C) -> Label -> [Block node C C]
forall (block :: Extensibility -> Extensibility -> *).
NonLocal block =>
LabelMap (block C C) -> Label -> [block C C]
revPostorderFrom (GenCmmGraph node -> LabelMap (Block node C C)
forall (n :: Extensibility -> Extensibility -> *).
GenCmmGraph n -> LabelMap (Block n C C)
graphMap GenCmmGraph node
g) (GenCmmGraph node -> Label
forall (n :: Extensibility -> Extensibility -> *).
GenCmmGraph n -> Label
g_entry GenCmmGraph node
g)
rplabels' :: [Label]
rplabels' = (Block node C C -> Label) -> [Block node C C] -> [Label]
forall a b. (a -> b) -> [a] -> [b]
map Block node C C -> Label
forall (x :: Extensibility). Block node C x -> Label
forall (thing :: Extensibility -> Extensibility -> *)
(x :: Extensibility).
NonLocal thing =>
thing C x -> Label
entryLabel [Block node C C]
rpblocks
rplabels :: Array Int Label
rplabels :: Array Int Label
rplabels = (Int, Int) -> [Label] -> Array Int Label
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [e] -> a i e
listArray (Int, Int)
bounds [Label]
rplabels'
rpmap :: LabelMap RPNum
rpmap :: LabelMap RPNum
rpmap = [(KeyOf LabelMap, RPNum)] -> LabelMap RPNum
forall a. [(KeyOf LabelMap, a)] -> LabelMap a
forall (map :: * -> *) a. IsMap map => [(KeyOf map, a)] -> map a
mapFromList ([(KeyOf LabelMap, RPNum)] -> LabelMap RPNum)
-> [(KeyOf LabelMap, RPNum)] -> LabelMap RPNum
forall a b. (a -> b) -> a -> b
$ (Block node C C -> Int -> (Label, RPNum))
-> [Block node C C] -> [Int] -> [(Label, RPNum)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Block node C C -> Int -> (Label, RPNum)
forall {thing :: Extensibility -> Extensibility -> *}
{x :: Extensibility}.
NonLocal thing =>
thing C x -> Int -> (Label, RPNum)
kvpair [Block node C C]
rpblocks [Int
0..]
where kvpair :: thing C x -> Int -> (Label, RPNum)
kvpair thing C x
block Int
i = (thing C x -> Label
forall (x :: Extensibility). thing C x -> Label
forall (thing :: Extensibility -> Extensibility -> *)
(x :: Extensibility).
NonLocal thing =>
thing C x -> Label
entryLabel thing C x
block, Int -> RPNum
RPNum Int
i)
labelIndex :: Label -> Int
labelIndex :: Label -> Int
labelIndex = (Label -> LabelMap Int -> Int) -> LabelMap Int -> Label -> Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip Label -> LabelMap Int -> Int
forall a. HasDebugCallStack => Label -> LabelMap a -> a
findLabelIn LabelMap Int
imap
where imap :: LabelMap Int
imap :: LabelMap Int
imap = [(KeyOf LabelMap, Int)] -> LabelMap Int
forall a. [(KeyOf LabelMap, a)] -> LabelMap a
forall (map :: * -> *) a. IsMap map => [(KeyOf map, a)] -> map a
mapFromList ([(KeyOf LabelMap, Int)] -> LabelMap Int)
-> [(KeyOf LabelMap, Int)] -> LabelMap Int
forall a b. (a -> b) -> a -> b
$ [Label] -> [Int] -> [(Label, Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Label]
rplabels' [Int
0..]
blockIndex :: Block node C x -> Int
blockIndex = Label -> Int
labelIndex (Label -> Int)
-> (Block node C x -> Label) -> Block node C x -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Block node C x -> Label
forall (x :: Extensibility). Block node C x -> Label
forall (thing :: Extensibility -> Extensibility -> *)
(x :: Extensibility).
NonLocal thing =>
thing C x -> Label
entryLabel
bounds :: (Int, Int)
bounds = (Int
0, [Block node C C] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Block node C C]
rpblocks Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
ltGraph :: [Block node C C] -> LT.Graph
ltGraph :: [Block node C C] -> Graph
ltGraph [] = Graph
forall a. IntMap a
IM.empty
ltGraph (Block node C C
block:[Block node C C]
blocks) =
Int -> IntSet -> Graph -> Graph
forall a. Int -> a -> IntMap a -> IntMap a
IM.insert
(Block node C C -> Int
forall {x :: Extensibility}. Block node C x -> Int
blockIndex Block node C C
block)
([Int] -> IntSet
IS.fromList ([Int] -> IntSet) -> [Int] -> IntSet
forall a b. (a -> b) -> a -> b
$ (Label -> Int) -> [Label] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Label -> Int
labelIndex ([Label] -> [Int]) -> [Label] -> [Int]
forall a b. (a -> b) -> a -> b
$ Block node C C -> [Label]
forall (e :: Extensibility). Block node e C -> [Label]
forall (thing :: Extensibility -> Extensibility -> *)
(e :: Extensibility).
NonLocal thing =>
thing e C -> [Label]
successors Block node C C
block)
([Block node C C] -> Graph
ltGraph [Block node C C]
blocks)
idom_array :: Array Int LT.Node
idom_array :: Array Int Int
idom_array = (Int, Int) -> [(Int, Int)] -> Array Int Int
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [(i, e)] -> a i e
array (Int, Int)
bounds ([(Int, Int)] -> Array Int Int) -> [(Int, Int)] -> Array Int Int
forall a b. (a -> b) -> a -> b
$ Rooted -> [(Int, Int)]
LT.idom (Int
0, [Block node C C] -> Graph
ltGraph [Block node C C]
rpblocks)
domSet :: Int -> DominatorSet
domSet Int
0 = DominatorSet
EntryNode
domSet Int
i = Label -> DominatorSet -> DominatorSet
ImmediateDominator (Array Int Label
rplabels Array Int Label -> Int -> Label
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Int
d) (Array Int DominatorSet
doms Array Int DominatorSet -> Int -> DominatorSet
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Int
d)
where d :: Int
d = Array Int Int
idom_array Array Int Int -> Int -> Int
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Int
i
doms :: Array Int DominatorSet
doms = (Int, Int) -> (Int -> DominatorSet) -> Array Int DominatorSet
forall i e. Ix i => (i, i) -> (i -> e) -> Array i e
tabulate (Int, Int)
bounds Int -> DominatorSet
domSet
dmap :: LabelMap DominatorSet
dmap = [(KeyOf LabelMap, DominatorSet)] -> LabelMap DominatorSet
forall a. [(KeyOf LabelMap, a)] -> LabelMap a
forall (map :: * -> *) a. IsMap map => [(KeyOf map, a)] -> map a
mapFromList ([(KeyOf LabelMap, DominatorSet)] -> LabelMap DominatorSet)
-> [(KeyOf LabelMap, DominatorSet)] -> LabelMap DominatorSet
forall a b. (a -> b) -> a -> b
$ (Label -> Int -> (Label, DominatorSet))
-> [Label] -> [Int] -> [(Label, DominatorSet)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\Label
lbl Int
i -> (Label
lbl, Int -> DominatorSet
domSet Int
i)) [Label]
rplabels' [Int
0..]
reachable :: NonLocal node => [Block node C C] -> GenCmmGraph node -> GenCmmGraph node
reachable :: forall (node :: Extensibility -> Extensibility -> *).
NonLocal node =>
[Block node C C] -> GenCmmGraph node -> GenCmmGraph node
reachable [Block node C C]
blocks GenCmmGraph node
g = GenCmmGraph node
g { g_graph = GMany NothingO blockmap NothingO }
where blockmap :: Body' Block node
blockmap = [(KeyOf LabelMap, Block node C C)] -> Body' Block node
forall a. [(KeyOf LabelMap, a)] -> LabelMap a
forall (map :: * -> *) a. IsMap map => [(KeyOf map, a)] -> map a
mapFromList [(Block node C C -> Label
forall (x :: Extensibility). Block node C x -> Label
forall (thing :: Extensibility -> Extensibility -> *)
(x :: Extensibility).
NonLocal thing =>
thing C x -> Label
entryLabel Block node C C
b, Block node C C
b) | Block node C C
b <- [Block node C C]
blocks]
graphMap :: GenCmmGraph n -> LabelMap (Block n C C)
graphMap :: forall (n :: Extensibility -> Extensibility -> *).
GenCmmGraph n -> LabelMap (Block n C C)
graphMap (CmmGraph { g_graph :: forall (n :: Extensibility -> Extensibility -> *).
GenCmmGraph n -> Graph n C C
g_graph = GMany MaybeO C (Block n O C)
NothingO Body' Block n
blockmap MaybeO C (Block n C O)
NothingO }) = Body' Block n
blockmap
gwdRPNumber :: HasDebugCallStack => GraphWithDominators node -> Label -> RPNum
gwdRPNumber :: forall (node :: Extensibility -> Extensibility -> *).
HasDebugCallStack =>
GraphWithDominators node -> Label -> RPNum
gwdRPNumber GraphWithDominators node
g Label
l = Label -> LabelMap RPNum -> RPNum
forall a. HasDebugCallStack => Label -> LabelMap a -> a
findLabelIn Label
l (GraphWithDominators node -> LabelMap RPNum
forall (node :: Extensibility -> Extensibility -> *).
GraphWithDominators node -> LabelMap RPNum
gwd_rpnumbering GraphWithDominators node
g)
findLabelIn :: HasDebugCallStack => Label -> LabelMap a -> a
findLabelIn :: forall a. HasDebugCallStack => Label -> LabelMap a -> a
findLabelIn Label
lbl = a -> KeyOf LabelMap -> LabelMap a -> a
forall a. a -> KeyOf LabelMap -> LabelMap a -> a
forall (map :: * -> *) a. IsMap map => a -> KeyOf map -> map a -> a
mapFindWithDefault a
failed KeyOf LabelMap
Label
lbl
where failed :: a
failed =
String -> SDoc -> a
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"label not found in result of analysis" (Label -> SDoc
forall a. Outputable a => a -> SDoc
ppr Label
lbl)
gwdDominatorsOf :: HasDebugCallStack => GraphWithDominators node -> Label -> DominatorSet
gwdDominatorsOf :: forall (node :: Extensibility -> Extensibility -> *).
HasDebugCallStack =>
GraphWithDominators node -> Label -> DominatorSet
gwdDominatorsOf GraphWithDominators node
g Label
lbl = Label -> LabelMap DominatorSet -> DominatorSet
forall a. HasDebugCallStack => Label -> LabelMap a -> a
findLabelIn Label
lbl (GraphWithDominators node -> LabelMap DominatorSet
forall (node :: Extensibility -> Extensibility -> *).
GraphWithDominators node -> LabelMap DominatorSet
gwd_dominators GraphWithDominators node
g)
gwdDominatorTree :: GraphWithDominators node -> Tree.Tree Label
gwdDominatorTree :: forall (node :: Extensibility -> Extensibility -> *).
GraphWithDominators node -> Tree Label
gwdDominatorTree GraphWithDominators node
gwd = Label -> Tree Label
subtreeAt (GenCmmGraph node -> Label
forall (n :: Extensibility -> Extensibility -> *).
GenCmmGraph n -> Label
g_entry (GraphWithDominators node -> GenCmmGraph node
forall (node :: Extensibility -> Extensibility -> *).
GraphWithDominators node -> GenCmmGraph node
gwd_graph GraphWithDominators node
gwd))
where subtreeAt :: Label -> Tree Label
subtreeAt Label
label = Label -> [Tree Label] -> Tree Label
forall a. a -> [Tree a] -> Tree a
Tree.Node Label
label ([Tree Label] -> Tree Label) -> [Tree Label] -> Tree Label
forall a b. (a -> b) -> a -> b
$ (Label -> Tree Label) -> [Label] -> [Tree Label]
forall a b. (a -> b) -> [a] -> [b]
map Label -> Tree Label
subtreeAt ([Label] -> [Tree Label]) -> [Label] -> [Tree Label]
forall a b. (a -> b) -> a -> b
$ Label -> [Label]
children Label
label
children :: Label -> [Label]
children Label
l = [Label] -> KeyOf LabelMap -> LabelMap [Label] -> [Label]
forall a. a -> KeyOf LabelMap -> LabelMap a -> a
forall (map :: * -> *) a. IsMap map => a -> KeyOf map -> map a -> a
mapFindWithDefault [] KeyOf LabelMap
Label
l LabelMap [Label]
child_map
child_map :: LabelMap [Label]
child_map :: LabelMap [Label]
child_map = (LabelMap [Label]
-> KeyOf LabelMap -> DominatorSet -> LabelMap [Label])
-> LabelMap [Label] -> LabelMap DominatorSet -> LabelMap [Label]
forall b a. (b -> KeyOf LabelMap -> a -> b) -> b -> LabelMap a -> b
forall (map :: * -> *) b a.
IsMap map =>
(b -> KeyOf map -> a -> b) -> b -> map a -> b
mapFoldlWithKey LabelMap [Label]
-> KeyOf LabelMap -> DominatorSet -> LabelMap [Label]
LabelMap [Label] -> Label -> DominatorSet -> LabelMap [Label]
forall {map :: * -> *} {a}.
(KeyOf map ~ Label, IsMap map) =>
map [a] -> a -> DominatorSet -> map [a]
addParent LabelMap [Label]
forall a. LabelMap a
forall (map :: * -> *) a. IsMap map => map a
mapEmpty (LabelMap DominatorSet -> LabelMap [Label])
-> LabelMap DominatorSet -> LabelMap [Label]
forall a b. (a -> b) -> a -> b
$ GraphWithDominators node -> LabelMap DominatorSet
forall (node :: Extensibility -> Extensibility -> *).
GraphWithDominators node -> LabelMap DominatorSet
gwd_dominators GraphWithDominators node
gwd
where addParent :: map [a] -> a -> DominatorSet -> map [a]
addParent map [a]
cm a
_ DominatorSet
EntryNode = map [a]
cm
addParent map [a]
cm a
lbl (ImmediateDominator Label
p DominatorSet
_) =
([a] -> [a] -> [a]) -> KeyOf map -> [a] -> map [a] -> map [a]
forall a. (a -> a -> a) -> KeyOf map -> a -> map a -> map a
forall (map :: * -> *) a.
IsMap map =>
(a -> a -> a) -> KeyOf map -> a -> map a -> map a
mapInsertWith [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
(++) KeyOf map
Label
p [a
lbl] map [a]
cm
tabulate :: (Ix i) => (i, i) -> (i -> e) -> Array i e
tabulate :: forall i e. Ix i => (i, i) -> (i -> e) -> Array i e
tabulate (i, i)
b i -> e
f = (i, i) -> [e] -> Array i e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [e] -> a i e
listArray (i, i)
b ([e] -> Array i e) -> [e] -> Array i e
forall a b. (a -> b) -> a -> b
$ (i -> e) -> [i] -> [e]
forall a b. (a -> b) -> [a] -> [b]
map i -> e
f ([i] -> [e]) -> [i] -> [e]
forall a b. (a -> b) -> a -> b
$ (i, i) -> [i]
forall a. Ix a => (a, a) -> [a]
range (i, i)
b