@@ -5,7 +5,6 @@ For more information see https://gitlab.haskell.org/ghc/ghc/wikis/hie-files
5
5
-}
6
6
{-# LANGUAGE DeriveTraversable #-}
7
7
{-# LANGUAGE DeriveDataTypeable #-}
8
- {-# LANGUAGE TypeSynonymInstances #-}
9
8
{-# LANGUAGE FlexibleInstances #-}
10
9
{-# LANGUAGE ScopedTypeVariables #-}
11
10
{-# OPTIONS_GHC -Wno-orphans #-}
@@ -168,7 +167,7 @@ data HieType a
168
167
type HieTypeFlat = HieType TypeIndex
169
168
170
169
-- | Roughly isomorphic to the original core 'Type'.
171
- newtype HieTypeFix = Roll (HieType ( HieTypeFix ) )
170
+ newtype HieTypeFix = Roll (HieType HieTypeFix )
172
171
173
172
instance Binary (HieType TypeIndex ) where
174
173
put_ bh (HTyVarTy n) = do
@@ -200,7 +199,7 @@ instance Binary (HieType TypeIndex) where
200
199
put_ bh (HCastTy a) = do
201
200
putByte bh 7
202
201
put_ bh a
203
- put_ bh ( HCoercionTy ) = putByte bh 8
202
+ put_ bh HCoercionTy = putByte bh 8
204
203
205
204
get bh = do
206
205
(t :: Word8 ) <- get bh
@@ -228,7 +227,7 @@ instance Binary (HieArgs TypeIndex) where
228
227
229
228
-- | Mapping from filepaths (represented using 'FastString') to the
230
229
-- corresponding AST
231
- newtype HieASTs a = HieASTs { getAsts :: ( M. Map FastString (HieAST a ) ) }
230
+ newtype HieASTs a = HieASTs { getAsts :: M. Map FastString (HieAST a ) }
232
231
deriving (Functor , Foldable , Traversable )
233
232
234
233
instance Binary (HieASTs TypeIndex ) where
@@ -276,9 +275,9 @@ instance Binary (NodeInfo TypeIndex) where
276
275
put_ bh $ nodeType ni
277
276
put_ bh $ M. toList $ nodeIdentifiers ni
278
277
get bh = NodeInfo
279
- <$> fmap ( S. fromDistinctAscList) (get bh)
278
+ <$> fmap S. fromDistinctAscList (get bh)
280
279
<*> get bh
281
- <*> fmap ( M. fromList) (get bh)
280
+ <*> fmap M. fromList (get bh)
282
281
283
282
type Identifier = Either ModuleName Name
284
283
@@ -309,7 +308,7 @@ instance Binary (IdentifierDetails TypeIndex) where
309
308
put_ bh $ S. toAscList $ identInfo dets
310
309
get bh = IdentifierDetails
311
310
<$> get bh
312
- <*> fmap ( S. fromDistinctAscList) (get bh)
311
+ <*> fmap S. fromDistinctAscList (get bh)
313
312
314
313
315
314
-- | Different contexts under which identifiers exist
@@ -419,7 +418,7 @@ data IEType
419
418
420
419
instance Binary IEType where
421
420
put_ bh b = putByte bh (fromIntegral (fromEnum b))
422
- get bh = do x <- getByte bh; pure $! ( toEnum (fromIntegral x) )
421
+ get bh = do x <- getByte bh; pure $! toEnum (fromIntegral x)
423
422
424
423
425
424
data RecFieldContext
@@ -431,7 +430,7 @@ data RecFieldContext
431
430
432
431
instance Binary RecFieldContext where
433
432
put_ bh b = putByte bh (fromIntegral (fromEnum b))
434
- get bh = do x <- getByte bh; pure $! ( toEnum (fromIntegral x) )
433
+ get bh = do x <- getByte bh; pure $! toEnum (fromIntegral x)
435
434
436
435
437
436
data BindType
@@ -441,7 +440,7 @@ data BindType
441
440
442
441
instance Binary BindType where
443
442
put_ bh b = putByte bh (fromIntegral (fromEnum b))
444
- get bh = do x <- getByte bh; pure $! ( toEnum (fromIntegral x) )
443
+ get bh = do x <- getByte bh; pure $! toEnum (fromIntegral x)
445
444
446
445
447
446
data DeclType
@@ -456,7 +455,7 @@ data DeclType
456
455
457
456
instance Binary DeclType where
458
457
put_ bh b = putByte bh (fromIntegral (fromEnum b))
459
- get bh = do x <- getByte bh; pure $! ( toEnum (fromIntegral x) )
458
+ get bh = do x <- getByte bh; pure $! toEnum (fromIntegral x)
460
459
461
460
462
461
data Scope
0 commit comments