Skip to content

Commit

Permalink
[chore] make specialisation possible for ghc and some minor style
Browse files Browse the repository at this point in the history
improvements
  • Loading branch information
MangoIV committed Aug 17, 2024
1 parent 14be7e6 commit a7a92d5
Show file tree
Hide file tree
Showing 5 changed files with 9 additions and 14 deletions.
6 changes: 1 addition & 5 deletions src/Nixfmt.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,6 @@
module Nixfmt (
errorBundlePretty,
ParseErrorBundle,
Width,
format,
formatVerify,
printAst,
Expand All @@ -22,9 +21,6 @@ import qualified Text.Megaparsec as Megaparsec (parse)
import Text.Megaparsec.Error (errorBundlePretty)
import Text.Pretty.Simple (pShow)

-- import Debug.Trace (traceShow, traceShowId)

type Width = Int
type Layouter = forall a. (Pretty a, LanguageElement a) => a -> Text

-- | @format w filename source@ returns either a parsing error specifying a
Expand All @@ -36,7 +32,7 @@ format layout filename =
. Megaparsec.parse Parser.file filename

-- | Pretty print the internal AST for debugging
printAst :: FilePath -> Text -> Either String Text
printAst :: FilePath -> Text -> Either String a
printAst path unformatted = do
Whole unformattedParsed' _ <- first errorBundlePretty . Megaparsec.parse Parser.file path $ unformatted
Left (unpack $ toStrict $ pShow unformattedParsed')
Expand Down
1 change: 1 addition & 0 deletions src/Nixfmt/Lexer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -179,6 +179,7 @@ takeTrivia = get <* put []

pushTrivia :: (MonadState Trivia m) => Trivia -> m ()
pushTrivia t = modify (<> t)
{-# INLINEABLE pushTrivia #-}

lexeme :: Parser a -> Parser (Ann a)
lexeme p = do
Expand Down
6 changes: 2 additions & 4 deletions src/Nixfmt/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@

module Nixfmt.Parser where

import Control.Applicative (liftA2)
import Control.Monad (guard, liftM2)
import Control.Monad.Combinators (sepBy)
import qualified Control.Monad.Combinators.Expr as MPExpr (
Expand Down Expand Up @@ -128,10 +129,7 @@ slash :: Parser Text
slash = chunk "/" <* notFollowedBy (char '/')

instance (Semigroup a) => Semigroup (Parser a) where
fx <> fy = do
x <- fx
y <- fy
pure $ x <> y
(<>) = liftA2 (<>)

envPath :: Parser (Ann Token)
envPath =
Expand Down
6 changes: 1 addition & 5 deletions src/Nixfmt/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -109,11 +109,7 @@ ann l v =
-- | Equality of annotated syntax is defined as equality of their corresponding
-- semantics, thus ignoring the annotations.
instance (Eq a) => Eq (Ann a) where
Ann{value = x} == Ann{value = y} = x == y

-- Trivia is ignored for Eq, so also don't show
-- instance Show a => Show (Ann a) where
-- show (Ann _ a _) = show a
(==) = (==) `on` value

data Item a
= -- | An item
Expand Down
4 changes: 4 additions & 0 deletions src/Nixfmt/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,18 +49,22 @@ uriChar = charClass "~!@$%&*-=_+:',./?"
-- | Match one or more characters that match a predicate.
someP :: (MonadParsec e s m) => (Token s -> Bool) -> m (Tokens s)
someP = takeWhile1P Nothing
{-# INLINEABLE someP #-}

-- | Match zero or more characters that match a predicate.
manyP :: (MonadParsec e s m) => (Token s -> Bool) -> m (Tokens s)
manyP = takeWhileP Nothing
{-# INLINEABLE manyP #-}

-- | Match one or more texts and return the concatenation.
someText :: (MonadParsec e s m) => m Text -> m Text
someText p = Text.concat <$> some p
{-# INLINEABLE someText #-}

-- | Match zero or more texts and return the concatenation.
manyText :: (MonadParsec e s m) => m Text -> m Text
manyText p = Text.concat <$> many p
{-# INLINEABLE manyText #-}

-- | The longest common prefix of the arguments.
commonPrefix :: Text -> Text -> Text
Expand Down

0 comments on commit a7a92d5

Please sign in to comment.