Skip to content

Commit

Permalink
Implement Injectivity (#867)
Browse files Browse the repository at this point in the history
* Implement `Injectivity`

* Format
  • Loading branch information
toku-sa-n authored Apr 7, 2024
1 parent 6a47330 commit a286a6c
Show file tree
Hide file tree
Showing 3 changed files with 10 additions and 11 deletions.
15 changes: 10 additions & 5 deletions src/HIndent/Ast/Declaration/Family/Type/Injectivity.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE RecordWildCards #-}

module HIndent.Ast.Declaration.Family.Type.Injectivity
( Injectivity
, mkInjectivity
Expand All @@ -6,16 +8,19 @@ module HIndent.Ast.Declaration.Family.Type.Injectivity
import HIndent.Ast.NodeComments
import qualified HIndent.GhcLibParserWrapper.GHC.Hs as GHC
import {-# SOURCE #-} HIndent.Pretty
import HIndent.Pretty.Combinators
import HIndent.Pretty.NodeComments

newtype Injectivity =
Injectivity (GHC.InjectivityAnn GHC.GhcPs)
data Injectivity = Injectivity
{ from :: GHC.LIdP GHC.GhcPs
, to :: [GHC.LIdP GHC.GhcPs]
}

instance CommentExtraction Injectivity where
nodeComments (Injectivity _) = NodeComments [] [] []
nodeComments Injectivity {} = NodeComments [] [] []

instance Pretty Injectivity where
pretty' (Injectivity x) = pretty x
pretty' Injectivity {..} = spaced $ pretty from : string "->" : fmap pretty to

mkInjectivity :: GHC.InjectivityAnn GHC.GhcPs -> Injectivity
mkInjectivity = Injectivity
mkInjectivity (GHC.InjectivityAnn _ from to) = Injectivity {..}
4 changes: 0 additions & 4 deletions src/HIndent/Pretty.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1232,10 +1232,6 @@ instance Pretty GHC.OverlapMode where
instance Pretty GHC.StringLiteral where
pretty' = output

instance Pretty (GHC.InjectivityAnn GHC.GhcPs) where
pretty' (GHC.InjectivityAnn _ from to) =
spaced $ pretty from : string "->" : fmap pretty to

instance Pretty (GHC.ArithSeqInfo GHC.GhcPs) where
pretty' (GHC.From from) = brackets $ spaced [pretty from, string ".."]
pretty' (GHC.FromThen from next) =
Expand Down
2 changes: 0 additions & 2 deletions src/HIndent/Pretty.hs-boot
Original file line number Diff line number Diff line change
Expand Up @@ -36,8 +36,6 @@ instance Pretty GHC.EpaComment

instance Pretty (GHC.HsType GHC.GhcPs)

instance Pretty (GHC.InjectivityAnn GHC.GhcPs)

instance Pretty
(GHC.FamEqn
GHC.GhcPs
Expand Down

0 comments on commit a286a6c

Please sign in to comment.