Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- data UniqFM (key :: k) ele
- newtype NonDetUniqFM (key :: k) ele = NonDetUniqFM {}
- emptyUFM :: forall {k} (key :: k) elt. UniqFM key elt
- unitUFM :: Uniquable key => key -> elt -> UniqFM key elt
- unitDirectlyUFM :: forall {k} elt (key :: k). Unique -> elt -> UniqFM key elt
- zipToUFM :: Uniquable key => [key] -> [elt] -> UniqFM key elt
- listToUFM :: Uniquable key => [(key, elt)] -> UniqFM key elt
- listToUFM_Directly :: forall {k} elt (key :: k). [(Unique, elt)] -> UniqFM key elt
- listToUFM_C :: Uniquable key => (elt -> elt -> elt) -> [(key, elt)] -> UniqFM key elt
- listToIdentityUFM :: Uniquable key => [key] -> UniqFM key key
- addToUFM :: Uniquable key => UniqFM key elt -> key -> elt -> UniqFM key elt
- addToUFM_C :: Uniquable key => (elt -> elt -> elt) -> UniqFM key elt -> key -> elt -> UniqFM key elt
- addToUFM_Acc :: Uniquable key => (elt -> elts -> elts) -> (elt -> elts) -> UniqFM key elts -> key -> elt -> UniqFM key elts
- addToUFM_L :: Uniquable key => (key -> elt -> elt -> elt) -> key -> elt -> UniqFM key elt -> (Maybe elt, UniqFM key elt)
- addListToUFM :: Uniquable key => UniqFM key elt -> [(key, elt)] -> UniqFM key elt
- addListToUFM_C :: Uniquable key => (elt -> elt -> elt) -> UniqFM key elt -> [(key, elt)] -> UniqFM key elt
- addToUFM_Directly :: forall {k} (key :: k) elt. UniqFM key elt -> Unique -> elt -> UniqFM key elt
- addListToUFM_Directly :: forall {k} (key :: k) elt. UniqFM key elt -> [(Unique, elt)] -> UniqFM key elt
- adjustUFM :: Uniquable key => (elt -> elt) -> UniqFM key elt -> key -> UniqFM key elt
- alterUFM :: Uniquable key => (Maybe elt -> Maybe elt) -> UniqFM key elt -> key -> UniqFM key elt
- alterUFM_Directly :: forall {k} elt (key :: k). (Maybe elt -> Maybe elt) -> UniqFM key elt -> Unique -> UniqFM key elt
- adjustUFM_Directly :: forall {k} elt (key :: k). (elt -> elt) -> UniqFM key elt -> Unique -> UniqFM key elt
- delFromUFM :: Uniquable key => UniqFM key elt -> key -> UniqFM key elt
- delFromUFM_Directly :: forall {k} (key :: k) elt. UniqFM key elt -> Unique -> UniqFM key elt
- delListFromUFM :: Uniquable key => UniqFM key elt -> [key] -> UniqFM key elt
- delListFromUFM_Directly :: forall {k} (key :: k) elt. UniqFM key elt -> [Unique] -> UniqFM key elt
- plusUFM :: forall {k} (key :: k) elt. UniqFM key elt -> UniqFM key elt -> UniqFM key elt
- plusUFM_C :: forall {k} elt (key :: k). (elt -> elt -> elt) -> UniqFM key elt -> UniqFM key elt -> UniqFM key elt
- plusUFM_CD :: forall {k} elta eltb eltc (key :: k). (elta -> eltb -> eltc) -> UniqFM key elta -> elta -> UniqFM key eltb -> eltb -> UniqFM key eltc
- plusUFM_CD2 :: forall {k} elta eltb eltc (key :: k). (Maybe elta -> Maybe eltb -> eltc) -> UniqFM key elta -> UniqFM key eltb -> UniqFM key eltc
- mergeUFM :: forall {k} elta eltb eltc (key :: k). (elta -> eltb -> Maybe eltc) -> (UniqFM key elta -> UniqFM key eltc) -> (UniqFM key eltb -> UniqFM key eltc) -> UniqFM key elta -> UniqFM key eltb -> UniqFM key eltc
- plusMaybeUFM_C :: forall {k} elt (key :: k). (elt -> elt -> Maybe elt) -> UniqFM key elt -> UniqFM key elt -> UniqFM key elt
- plusUFMList :: forall {k} (key :: k) elt. [UniqFM key elt] -> UniqFM key elt
- plusUFMListWith :: forall {k} elt (key :: k). (elt -> elt -> elt) -> [UniqFM key elt] -> UniqFM key elt
- sequenceUFMList :: forall {k} (key :: k) elt. [UniqFM key elt] -> UniqFM key [elt]
- minusUFM :: forall {k} (key :: k) elt1 elt2. UniqFM key elt1 -> UniqFM key elt2 -> UniqFM key elt1
- minusUFM_C :: forall {k} elt1 elt2 (key :: k). (elt1 -> elt2 -> Maybe elt1) -> UniqFM key elt1 -> UniqFM key elt2 -> UniqFM key elt1
- intersectUFM :: forall {k} (key :: k) elt1 elt2. UniqFM key elt1 -> UniqFM key elt2 -> UniqFM key elt1
- intersectUFM_C :: forall {k} elt1 elt2 elt3 (key :: k). (elt1 -> elt2 -> elt3) -> UniqFM key elt1 -> UniqFM key elt2 -> UniqFM key elt3
- disjointUFM :: forall {k} (key :: k) elt1 elt2. UniqFM key elt1 -> UniqFM key elt2 -> Bool
- equalKeysUFM :: forall {k} (key :: k) a b. UniqFM key a -> UniqFM key b -> Bool
- diffUFM :: forall {k} a (key :: k). Eq a => UniqFM key a -> UniqFM key a -> UniqFM key (Edit a)
- nonDetStrictFoldUFM :: forall {k} elt a (key :: k). (elt -> a -> a) -> a -> UniqFM key elt -> a
- nonDetFoldUFM :: forall {k} elt a (key :: k). (elt -> a -> a) -> a -> UniqFM key elt -> a
- nonDetStrictFoldUFM_DirectlyM :: forall {k} m b elt (key :: k). Monad m => (Unique -> b -> elt -> m b) -> b -> UniqFM key elt -> m b
- nonDetFoldWithKeyUFM :: forall {k} elt a (key :: k). (Unique -> elt -> a -> a) -> a -> UniqFM key elt -> a
- nonDetStrictFoldUFM_Directly :: forall {k} elt a (key :: k). (Unique -> elt -> a -> a) -> a -> UniqFM key elt -> a
- anyUFM :: forall {k} elt (key :: k). (elt -> Bool) -> UniqFM key elt -> Bool
- allUFM :: forall {k} elt (key :: k). (elt -> Bool) -> UniqFM key elt -> Bool
- seqEltsUFM :: forall {k} elt (key :: k). (elt -> ()) -> UniqFM key elt -> ()
- mapUFM :: forall {k} elt1 elt2 (key :: k). (elt1 -> elt2) -> UniqFM key elt1 -> UniqFM key elt2
- mapUFM_Directly :: forall {k} elt1 elt2 (key :: k). (Unique -> elt1 -> elt2) -> UniqFM key elt1 -> UniqFM key elt2
- strictMapUFM :: forall {k1} a b (k2 :: k1). (a -> b) -> UniqFM k2 a -> UniqFM k2 b
- mapMaybeUFM :: forall {k} elt1 elt2 (key :: k). (elt1 -> Maybe elt2) -> UniqFM key elt1 -> UniqFM key elt2
- mapMaybeWithKeyUFM :: forall {k} elt1 elt2 (key :: k). (Unique -> elt1 -> Maybe elt2) -> UniqFM key elt1 -> UniqFM key elt2
- elemUFM :: Uniquable key => key -> UniqFM key elt -> Bool
- elemUFM_Directly :: forall {k} (key :: k) elt. Unique -> UniqFM key elt -> Bool
- filterUFM :: forall {k} elt (key :: k). (elt -> Bool) -> UniqFM key elt -> UniqFM key elt
- filterUFM_Directly :: forall {k} elt (key :: k). (Unique -> elt -> Bool) -> UniqFM key elt -> UniqFM key elt
- partitionUFM :: forall {k} elt (key :: k). (elt -> Bool) -> UniqFM key elt -> (UniqFM key elt, UniqFM key elt)
- sizeUFM :: forall {k} (key :: k) elt. UniqFM key elt -> Int
- isNullUFM :: forall {k} (key :: k) elt. UniqFM key elt -> Bool
- lookupUFM :: Uniquable key => UniqFM key elt -> key -> Maybe elt
- lookupUFM_Directly :: forall {k} (key :: k) elt. UniqFM key elt -> Unique -> Maybe elt
- lookupWithDefaultUFM :: Uniquable key => UniqFM key elt -> elt -> key -> elt
- lookupWithDefaultUFM_Directly :: forall {k} (key :: k) elt. UniqFM key elt -> elt -> Unique -> elt
- nonDetEltsUFM :: forall {k} (key :: k) elt. UniqFM key elt -> [elt]
- nonDetKeysUFM :: forall {k} (key :: k) elt. UniqFM key elt -> [Unique]
- ufmToSet_Directly :: forall {k} (key :: k) elt. UniqFM key elt -> Word64Set
- nonDetUFMToList :: forall {k} (key :: k) elt. UniqFM key elt -> [(Unique, elt)]
- ufmToIntMap :: forall {k} (key :: k) elt. UniqFM key elt -> Word64Map elt
- unsafeIntMapToUFM :: forall {k} elt (key :: k). Word64Map elt -> UniqFM key elt
- unsafeCastUFMKey :: forall {k1} {k2} (key1 :: k1) elt (key2 :: k2). UniqFM key1 elt -> UniqFM key2 elt
- pprUniqFM :: forall {k} a (key :: k). (a -> SDoc) -> UniqFM key a -> SDoc
- pprUFM :: forall {k} (key :: k) a. UniqFM key a -> ([a] -> SDoc) -> SDoc
- pprUFMWithKeys :: forall {k} (key :: k) a. UniqFM key a -> ([(Unique, a)] -> SDoc) -> SDoc
- pluralUFM :: forall {k} (key :: k) a. UniqFM key a -> SDoc
Unique-keyed mappings
data UniqFM (key :: k) ele Source #
A finite map from uniques
of one type to
elements in another type.
The key is just here to keep us honest. It's always safe to use a single type as key. If two types don't overlap in their uniques it's also safe to index the same map at multiple key types. But this is very much discouraged.
Instances
Functor (UniqFM key) Source # | |
Outputable a => Outputable (UniqFM key a) Source # | |
Monoid (UniqFM key a) Source # | |
Semigroup (UniqFM key a) Source # | |
(Typeable key, Typeable k, Data ele) => Data (UniqFM key ele) Source # | |
Defined in GHC.Types.Unique.FM gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UniqFM key ele -> c (UniqFM key ele) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (UniqFM key ele) # toConstr :: UniqFM key ele -> Constr # dataTypeOf :: UniqFM key ele -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (UniqFM key ele)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (UniqFM key ele)) # gmapT :: (forall b. Data b => b -> b) -> UniqFM key ele -> UniqFM key ele # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UniqFM key ele -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UniqFM key ele -> r # gmapQ :: (forall d. Data d => d -> u) -> UniqFM key ele -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UniqFM key ele -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UniqFM key ele -> m (UniqFM key ele) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UniqFM key ele -> m (UniqFM key ele) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UniqFM key ele -> m (UniqFM key ele) # | |
Eq ele => Eq (UniqFM key ele) Source # | |
newtype NonDetUniqFM (key :: k) ele Source #
A wrapper around UniqFM
with the sole purpose of informing call sites
that the provided Foldable
and Traversable
instances are
nondeterministic.
If you use this please provide a justification why it doesn't introduce
nondeterminism.
See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM to learn about determinism.
Instances
Functor (NonDetUniqFM key) Source # | |
Defined in GHC.Types.Unique.FM fmap :: (a -> b) -> NonDetUniqFM key a -> NonDetUniqFM key b # (<$) :: a -> NonDetUniqFM key b -> NonDetUniqFM key a # | |
Foldable (NonDetUniqFM key) Source # | Inherently nondeterministic. If you use this please provide a justification why it doesn't introduce nondeterminism. See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM to learn about determinism. |
Defined in GHC.Types.Unique.FM fold :: Monoid m => NonDetUniqFM key m -> m # foldMap :: Monoid m => (a -> m) -> NonDetUniqFM key a -> m # foldMap' :: Monoid m => (a -> m) -> NonDetUniqFM key a -> m # foldr :: (a -> b -> b) -> b -> NonDetUniqFM key a -> b # foldr' :: (a -> b -> b) -> b -> NonDetUniqFM key a -> b # foldl :: (b -> a -> b) -> b -> NonDetUniqFM key a -> b # foldl' :: (b -> a -> b) -> b -> NonDetUniqFM key a -> b # foldr1 :: (a -> a -> a) -> NonDetUniqFM key a -> a # foldl1 :: (a -> a -> a) -> NonDetUniqFM key a -> a # toList :: NonDetUniqFM key a -> [a] # null :: NonDetUniqFM key a -> Bool # length :: NonDetUniqFM key a -> Int # elem :: Eq a => a -> NonDetUniqFM key a -> Bool # maximum :: Ord a => NonDetUniqFM key a -> a # minimum :: Ord a => NonDetUniqFM key a -> a # sum :: Num a => NonDetUniqFM key a -> a # product :: Num a => NonDetUniqFM key a -> a # | |
Traversable (NonDetUniqFM key) Source # | Inherently nondeterministic. If you use this please provide a justification why it doesn't introduce nondeterminism. See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM to learn about determinism. |
Defined in GHC.Types.Unique.FM traverse :: Applicative f => (a -> f b) -> NonDetUniqFM key a -> f (NonDetUniqFM key b) # sequenceA :: Applicative f => NonDetUniqFM key (f a) -> f (NonDetUniqFM key a) # mapM :: Monad m => (a -> m b) -> NonDetUniqFM key a -> m (NonDetUniqFM key b) # sequence :: Monad m => NonDetUniqFM key (m a) -> m (NonDetUniqFM key a) # |
Manipulating those mappings
unitDirectlyUFM :: forall {k} elt (key :: k). Unique -> elt -> UniqFM key elt Source #
listToUFM_Directly :: forall {k} elt (key :: k). [(Unique, elt)] -> UniqFM key elt Source #
listToUFM_C :: Uniquable key => (elt -> elt -> elt) -> [(key, elt)] -> UniqFM key elt Source #
listToIdentityUFM :: Uniquable key => [key] -> UniqFM key key Source #
addToUFM_Acc :: Uniquable key => (elt -> elts -> elts) -> (elt -> elts) -> UniqFM key elts -> key -> elt -> UniqFM key elts Source #
:: Uniquable key | |
=> (key -> elt -> elt -> elt) | key,old,new |
-> key | |
-> elt | |
-> UniqFM key elt | |
-> (Maybe elt, UniqFM key elt) | old, result |
Add an element, returns previous lookup result and new map. If old element doesn't exist, add the passed element directly, otherwise compute the element to add using the passed function.
addListToUFM_C :: Uniquable key => (elt -> elt -> elt) -> UniqFM key elt -> [(key, elt)] -> UniqFM key elt Source #
Add elements to the map, combining existing values with inserted ones using the given function.
addToUFM_Directly :: forall {k} (key :: k) elt. UniqFM key elt -> Unique -> elt -> UniqFM key elt Source #
addListToUFM_Directly :: forall {k} (key :: k) elt. UniqFM key elt -> [(Unique, elt)] -> UniqFM key elt Source #
adjustUFM_Directly :: forall {k} elt (key :: k). (elt -> elt) -> UniqFM key elt -> Unique -> UniqFM key elt Source #
delFromUFM_Directly :: forall {k} (key :: k) elt. UniqFM key elt -> Unique -> UniqFM key elt Source #
delListFromUFM_Directly :: forall {k} (key :: k) elt. UniqFM key elt -> [Unique] -> UniqFM key elt Source #
plusUFM_C :: forall {k} elt (key :: k). (elt -> elt -> elt) -> UniqFM key elt -> UniqFM key elt -> UniqFM key elt Source #
plusUFM_CD :: forall {k} elta eltb eltc (key :: k). (elta -> eltb -> eltc) -> UniqFM key elta -> elta -> UniqFM key eltb -> eltb -> UniqFM key eltc Source #
`plusUFM_CD f m1 d1 m2 d2` merges the maps using f
as the
combinding function and d1
resp. d2
as the default value if
there is no entry in m1
reps. m2
. The domain is the union of
the domains of m1
and m2
.
IMPORTANT NOTE: This function strictly applies the modification function and forces the result unlike most the other functions in this module.
Representative example:
plusUFM_CD f {A: 1, B: 2} 23 {B: 3, C: 4} 42 == {A: f 1 42, B: f 2 3, C: f 23 4 }
plusUFM_CD2 :: forall {k} elta eltb eltc (key :: k). (Maybe elta -> Maybe eltb -> eltc) -> UniqFM key elta -> UniqFM key eltb -> UniqFM key eltc Source #
`plusUFM_CD2 f m1 m2` merges the maps using f
as the combining
function. Unlike plusUFM_CD
, a missing value is not defaulted: it is
instead passed as Nothing
to f
. f
can never have both its arguments
be Nothing
.
IMPORTANT NOTE: This function strictly applies the modification function and forces the result.
`plusUFM_CD2 f m1 m2` is the same as `plusUFM_CD f (mapUFM Just m1) Nothing (mapUFM Just m2) Nothing`.
mergeUFM :: forall {k} elta eltb eltc (key :: k). (elta -> eltb -> Maybe eltc) -> (UniqFM key elta -> UniqFM key eltc) -> (UniqFM key eltb -> UniqFM key eltc) -> UniqFM key elta -> UniqFM key eltb -> UniqFM key eltc Source #
plusMaybeUFM_C :: forall {k} elt (key :: k). (elt -> elt -> Maybe elt) -> UniqFM key elt -> UniqFM key elt -> UniqFM key elt Source #
plusUFMList :: forall {k} (key :: k) elt. [UniqFM key elt] -> UniqFM key elt Source #
plusUFMListWith :: forall {k} elt (key :: k). (elt -> elt -> elt) -> [UniqFM key elt] -> UniqFM key elt Source #
sequenceUFMList :: forall {k} (key :: k) elt. [UniqFM key elt] -> UniqFM key [elt] Source #
minusUFM :: forall {k} (key :: k) elt1 elt2. UniqFM key elt1 -> UniqFM key elt2 -> UniqFM key elt1 Source #
minusUFM_C :: forall {k} elt1 elt2 (key :: k). (elt1 -> elt2 -> Maybe elt1) -> UniqFM key elt1 -> UniqFM key elt2 -> UniqFM key elt1 Source #
intersectUFM :: forall {k} (key :: k) elt1 elt2. UniqFM key elt1 -> UniqFM key elt2 -> UniqFM key elt1 Source #
intersectUFM_C :: forall {k} elt1 elt2 elt3 (key :: k). (elt1 -> elt2 -> elt3) -> UniqFM key elt1 -> UniqFM key elt2 -> UniqFM key elt3 Source #
diffUFM :: forall {k} a (key :: k). Eq a => UniqFM key a -> UniqFM key a -> UniqFM key (Edit a) Source #
Computes the diff of two UniqFM
s in terms of Edit
s.
Equal points will not be present in the result map at all.
nonDetStrictFoldUFM :: forall {k} elt a (key :: k). (elt -> a -> a) -> a -> UniqFM key elt -> a Source #
nonDetFoldUFM :: forall {k} elt a (key :: k). (elt -> a -> a) -> a -> UniqFM key elt -> a Source #
Fold over a UniqFM
.
Non-deterministic, unless the folding function is commutative
(i.e. a1
for all f
( a2 f
b ) == a2 f
( a1 f
b )a1
, a2
, b
).
nonDetStrictFoldUFM_DirectlyM :: forall {k} m b elt (key :: k). Monad m => (Unique -> b -> elt -> m b) -> b -> UniqFM key elt -> m b Source #
In essence foldM See Note [Deterministic UniqFM] to learn about nondeterminism. If you use this please provide a justification why it doesn't introduce nondeterminism.
nonDetFoldWithKeyUFM :: forall {k} elt a (key :: k). (Unique -> elt -> a -> a) -> a -> UniqFM key elt -> a Source #
Like nonDetFoldUFM
, but with the Unique
key as well.
nonDetStrictFoldUFM_Directly :: forall {k} elt a (key :: k). (Unique -> elt -> a -> a) -> a -> UniqFM key elt -> a Source #
seqEltsUFM :: forall {k} elt (key :: k). (elt -> ()) -> UniqFM key elt -> () Source #
mapUFM :: forall {k} elt1 elt2 (key :: k). (elt1 -> elt2) -> UniqFM key elt1 -> UniqFM key elt2 Source #
mapUFM_Directly :: forall {k} elt1 elt2 (key :: k). (Unique -> elt1 -> elt2) -> UniqFM key elt1 -> UniqFM key elt2 Source #
strictMapUFM :: forall {k1} a b (k2 :: k1). (a -> b) -> UniqFM k2 a -> UniqFM k2 b Source #
mapMaybeUFM :: forall {k} elt1 elt2 (key :: k). (elt1 -> Maybe elt2) -> UniqFM key elt1 -> UniqFM key elt2 Source #
mapMaybeWithKeyUFM :: forall {k} elt1 elt2 (key :: k). (Unique -> elt1 -> Maybe elt2) -> UniqFM key elt1 -> UniqFM key elt2 Source #
filterUFM_Directly :: forall {k} elt (key :: k). (Unique -> elt -> Bool) -> UniqFM key elt -> UniqFM key elt Source #
partitionUFM :: forall {k} elt (key :: k). (elt -> Bool) -> UniqFM key elt -> (UniqFM key elt, UniqFM key elt) Source #
lookupWithDefaultUFM :: Uniquable key => UniqFM key elt -> elt -> key -> elt Source #
lookupWithDefaultUFM_Directly :: forall {k} (key :: k) elt. UniqFM key elt -> elt -> Unique -> elt Source #
nonDetEltsUFM :: forall {k} (key :: k) elt. UniqFM key elt -> [elt] Source #
nonDetKeysUFM :: forall {k} (key :: k) elt. UniqFM key elt -> [Unique] Source #
ufmToSet_Directly :: forall {k} (key :: k) elt. UniqFM key elt -> Word64Set Source #
nonDetUFMToList :: forall {k} (key :: k) elt. UniqFM key elt -> [(Unique, elt)] Source #
ufmToIntMap :: forall {k} (key :: k) elt. UniqFM key elt -> Word64Map elt Source #
unsafeIntMapToUFM :: forall {k} elt (key :: k). Word64Map elt -> UniqFM key elt Source #
unsafeCastUFMKey :: forall {k1} {k2} (key1 :: k1) elt (key2 :: k2). UniqFM key1 elt -> UniqFM key2 elt Source #
Cast the key domain of a UniqFM.
As long as the domains don't overlap in their uniques this is safe.
:: forall {k} (key :: k) a. UniqFM key a | The things to be pretty printed |
-> ([a] -> SDoc) | The pretty printing function to use on the elements |
-> SDoc |
|
Pretty-print a non-deterministic set. The order of variables is non-deterministic and for pretty-printing that shouldn't be a problem. Having this function helps contain the non-determinism created with nonDetEltsUFM.
:: forall {k} (key :: k) a. UniqFM key a | The things to be pretty printed |
-> ([(Unique, a)] -> SDoc) | The pretty printing function to use on the elements |
-> SDoc |
|
Pretty-print a non-deterministic set. The order of variables is non-deterministic and for pretty-printing that shouldn't be a problem. Having this function helps contain the non-determinism created with nonDetUFMToList.