Skip to content

Commit 1745ffc

Browse files
committed
dhall: provide *WithIndex instances for Map
1 parent f16a9e0 commit 1745ffc

File tree

1 file changed

+23
-6
lines changed

1 file changed

+23
-6
lines changed

dhall/src/Dhall/Map.hs

+23-6
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,11 @@
1-
{-# LANGUAGE DeriveAnyClass #-}
2-
{-# LANGUAGE DeriveDataTypeable #-}
3-
{-# LANGUAGE DeriveGeneric #-}
4-
{-# LANGUAGE DeriveLift #-}
5-
{-# LANGUAGE ExplicitForAll #-}
6-
{-# LANGUAGE TypeFamilies #-}
1+
{-# LANGUAGE DeriveAnyClass #-}
2+
{-# LANGUAGE DeriveDataTypeable #-}
3+
{-# LANGUAGE DeriveGeneric #-}
4+
{-# LANGUAGE DeriveLift #-}
5+
{-# LANGUAGE ExplicitForAll #-}
6+
{-# LANGUAGE FlexibleInstances #-}
7+
{-# LANGUAGE MultiParamTypeClasses #-}
8+
{-# LANGUAGE TypeFamilies #-}
79

810
-- | `Map` type used to represent records and unions
911

@@ -76,9 +78,12 @@ import Instances.TH.Lift ()
7678
import Language.Haskell.TH.Syntax (Lift)
7779
import Prelude hiding (filter, lookup)
7880

81+
import qualified Data.Foldable.WithIndex as Foldable.WithIndex
82+
import qualified Data.Functor.WithIndex as Functor.WithIndex
7983
import qualified Data.List
8084
import qualified Data.Map.Strict
8185
import qualified Data.Set
86+
import qualified Data.Traversable.WithIndex as Traversable.WithIndex
8287
import qualified GHC.Exts
8388
import qualified Prelude
8489

@@ -158,6 +163,18 @@ instance Ord k => GHC.Exts.IsList (Map k v) where
158163

159164
toList = Dhall.Map.toList
160165

166+
instance Ord k => Foldable.WithIndex.FoldableWithIndex k (Map k) where
167+
ifoldMap = foldMapWithKey
168+
{-# INLINABLE ifoldMap #-}
169+
170+
instance Functor.WithIndex.FunctorWithIndex k (Map k) where
171+
imap = mapWithKey
172+
{-# INLINABLE imap #-}
173+
174+
instance Ord k => Traversable.WithIndex.TraversableWithIndex k (Map k) where
175+
itraverse = traverseWithKey
176+
{-# INLINABLE itraverse #-}
177+
161178
-- | Create an empty `Map`
162179
empty :: Ord k => Map k v
163180
empty = mempty

0 commit comments

Comments
 (0)