diff --git a/PyF.cabal b/PyF.cabal index 6b90c4c..3514f28 100644 --- a/PyF.cabal +++ b/PyF.cabal @@ -29,13 +29,16 @@ library PyF.Internal.ParserEx PyF.Internal.PythonSyntax PyF.Internal.QQ + PyF.Plugin build-depends: , base >=4.12 && <4.22 , bytestring >=0.10.8 && <0.13 - , ghc >=8.6.1 + , ghc >=8.6.1 && <9.14 + , ghc-boot >=8.6.1 && <9.14 , mtl >=2.2.2 && <2.4 , parsec >=3.1.13 && <3.2 + , syb , template-haskell >=2.14.0 && <2.24 , text >=1.2.3 && <2.2 , time >=1.8.0 && <1.15 @@ -67,6 +70,24 @@ test-suite pyf-test default-language: Haskell2010 +test-suite pyf-test-plugin + type: exitcode-stdio-1.0 + hs-source-dirs: test + main-is: SpecPlugin.hs + build-depends: + , base + , bytestring + , hspec + , PyF + , template-haskell + , text + , time + + ghc-options: + -Wall -threaded -rtsopts -with-rtsopts=-N -Wunused-packages + + default-language: Haskell2010 + test-suite pyf-overloaded type: exitcode-stdio-1.0 hs-source-dirs: test diff --git a/flake.nix b/flake.nix index 9408a3a..51ccd63 100644 --- a/flake.nix +++ b/flake.nix @@ -92,6 +92,12 @@ pkgs.nodejs ]; }; + + work_with_pyf = pkgs.mkShell { + buildInputs = [ + (pkgs.haskellPackages.ghcWithPackages (_: [ (pkgs.haskell.lib.dontCheck packages.default) ])) + ]; + }; default = packages.default.shell_hls; }; } diff --git a/src/PyF.hs b/src/PyF.hs index f774337..bb9a7ca 100644 --- a/src/PyF.hs +++ b/src/PyF.hs @@ -38,9 +38,9 @@ fmt = mkFormatter "fmt" fmtConfig -- | Format with whitespace trimming. fmtTrim :: QuasiQuoter -fmtTrim = let - qq = mkFormatter "fmtTrim" fmtConfig - in qq { quoteExp = \s -> quoteExp qq (trimIndent s) } +fmtTrim = + let qq = mkFormatter "fmtTrim" fmtConfig + in qq {quoteExp = \s -> quoteExp qq (trimIndent s)} -- | Multiline string, no interpolation. str :: QuasiQuoter @@ -48,8 +48,9 @@ str = mkFormatter "str" strConfig -- | Multiline string, no interpolation, but does indentation trimming. strTrim :: QuasiQuoter -strTrim = let qq = mkFormatter "strTrim" strConfig - in qq { quoteExp = \s -> quoteExp qq (trimIndent s) } +strTrim = + let qq = mkFormatter "strTrim" strConfig + in qq {quoteExp = \s -> quoteExp qq (trimIndent s)} -- | Raw string, neither interpolation nor escaping is performed. raw :: QuasiQuoter diff --git a/src/PyF/Formatters.hs b/src/PyF/Formatters.hs index cc15d38..029525a 100644 --- a/src/PyF/Formatters.hs +++ b/src/PyF/Formatters.hs @@ -131,6 +131,8 @@ data Format (k :: AltStatus) (k' :: UpperStatus) (k'' :: FormatType) where -- Upper should come AFTER Alt, so this disallow any future alt Upper :: Format alt 'CanUpper f -> Format 'NoAlt 'NoUpper f +deriving instance Show (Format k k' k'') + newtype ShowIntegral i = ShowIntegral i deriving (Real, Enum, Ord, Eq, Num, Integral) diff --git a/src/PyF/Internal/Parser.hs b/src/PyF/Internal/Parser.hs index e5910be..77b7ccd 100644 --- a/src/PyF/Internal/Parser.hs +++ b/src/PyF/Internal/Parser.hs @@ -50,15 +50,13 @@ import HsExtension as Ext import Outputable (showSDoc) #endif +import GHC.Parser.Annotation (LocatedA) import qualified PyF.Internal.ParserEx as ParseExp -parseExpression :: RealSrcLoc -> String -> DynFlags -> Either (Int, Int, String) (HsExpr GhcPs) +parseExpression :: RealSrcLoc -> String -> DynFlags -> Either (RealSrcLoc, String) (LocatedA (HsExpr GhcPs)) parseExpression initLoc s dynFlags = case ParseExp.parseExpression initLoc s dynFlags of - POk _ locatedExpr -> - let expr = SrcLoc.unLoc locatedExpr - in Right - expr + POk _ locatedExpr -> Right locatedExpr {- ORMOLU_DISABLE #-} #if MIN_VERSION_ghc(9,2,0) @@ -81,9 +79,7 @@ parseExpression initLoc s dynFlags = $ map errMsgDiagnostic $ sortMsgBag Nothing $ getMessages $ errorMessages - line' = SrcLoc.srcLocLine srcLoc - col = SrcLoc.srcLocCol srcLoc - in Left (line', col, err) + in Left (srcLoc, err) #elif MIN_VERSION_ghc(9,6,0) let err = renderWithContext defaultSDocContext @@ -93,9 +89,7 @@ parseExpression initLoc s dynFlags = $ map errMsgDiagnostic $ sortMsgBag Nothing $ getMessages $ errorMessages - line' = SrcLoc.srcLocLine srcLoc - col = SrcLoc.srcLocCol srcLoc - in Left (line', col, err) + in Left (srcLoc, err) #elif MIN_VERSION_ghc(9,3,0) let err = renderWithContext defaultSDocContext @@ -105,29 +99,21 @@ parseExpression initLoc s dynFlags = $ map errMsgDiagnostic $ sortMsgBag Nothing $ getMessages $ errorMessages - line = SrcLoc.srcLocLine srcLoc - col = SrcLoc.srcLocCol srcLoc - in Left (line, col, err) + in Left (srcLoc, err) #elif MIN_VERSION_ghc(9,2,0) let psErrToString e = show $ ParserErrorPpr.pprError e err = concatMap psErrToString errorMessages - line = SrcLoc.srcLocLine srcLoc - col = SrcLoc.srcLocCol srcLoc - in Left (line, col, err) + in Left (srcLoc, err) #elif MIN_VERSION_ghc(8,10,0) let -- TODO: do not ignore "warnMessages" -- I have no idea what they can be (_warnMessages, errorMessages) = msgs dynFlags err = concatMap show errorMessages - line = SrcLoc.srcLocLine srcLoc - col = SrcLoc.srcLocCol srcLoc - in Left (line, col, err) + in Left (srcLoc, err) #else let err = showSDoc dynFlags doc - line = SrcLoc.srcLocLine srcLoc - col = SrcLoc.srcLocCol srcLoc - in Left (line, col, err) + in Left (srcLoc, err) #endif #if MIN_VERSION_ghc(8,10,0) diff --git a/src/PyF/Internal/PythonSyntax.hs b/src/PyF/Internal/PythonSyntax.hs index 0950445..afcab8d 100644 --- a/src/PyF/Internal/PythonSyntax.hs +++ b/src/PyF/Internal/PythonSyntax.hs @@ -12,10 +12,14 @@ module PyF.Internal.PythonSyntax ( parseGenericFormatString, Item (..), - FormatMode (..), - Padding (..), - Precision (..), - TypeFormat (..), + FormatMode, + FormatModeT (..), + Padding, + PaddingT (..), + Precision, + PrecisionT (..), + TypeFormat, + TypeFormatT (..), AlternateForm (..), pattern DefaultFormatMode, Parser, @@ -25,30 +29,21 @@ module PyF.Internal.PythonSyntax where import Control.Applicative (some) -import Control.Monad (replicateM_, void) +import Control.Monad (void) import Control.Monad.Reader (Reader, asks) import qualified Data.Char import Data.Data (Data) import Data.Maybe (fromMaybe) -import GHC (GhcPs, HsExpr) -import Language.Haskell.TH.LanguageExtensions (Extension (..)) -import Language.Haskell.TH.Syntax (Exp) import PyF.Formatters -import PyF.Internal.Meta -import qualified PyF.Internal.Parser as ParseExp import Text.Parsec #if MIN_VERSION_ghc(9,7,0) #elif MIN_VERSION_ghc(9,6,0) -- For some reasons, theses function are not exported anymore by some others -import Data.Functor (void) -import Control.Monad (replicateM_) #endif #if MIN_VERSION_ghc(9,0,0) -import GHC.Types.SrcLoc -import GHC.Data.FastString #else import SrcLoc import FastString @@ -57,8 +52,7 @@ import FastString type Parser t = ParsecT String () (Reader ParsingContext) t data ParsingContext = ParsingContext - { delimiters :: Maybe (Char, Char), - enabledExtensions :: [Extension] + { delimiters :: Maybe (Char, Char) } deriving (Show) @@ -87,7 +81,7 @@ data Item = -- | A raw string Raw String | -- | A replacement string, composed of an arbitrary Haskell expression followed by an optional formatter - Replacement (HsExpr GhcPs, Exp) (Maybe FormatMode) + Replacement SourcePos String (Maybe FormatMode) -- | -- Parse a string, returns a list of raw string or replacement fields @@ -164,39 +158,46 @@ parseExpressionString = do replacementField :: Parser Item replacementField = do - exts <- asks enabledExtensions Just (charOpening, charClosing) <- asks delimiters _ <- char charOpening - expr <- evalExpr exts (parseExpressionString "an haskell expression") + exprPos <- getPosition + expr <- parseExpressionString "an haskell expression" fmt <- optionMaybe $ do _ <- char ':' formatSpec _ <- char charClosing - pure (Replacement expr fmt) + pure (Replacement exprPos expr fmt) -- | Default formatting mode, no padding, default precision, no grouping, no sign handling pattern DefaultFormatMode :: FormatMode pattern DefaultFormatMode = FormatMode PaddingDefault (DefaultF PrecisionDefault Minus) Nothing -- | A Formatter, listing padding, format and and grouping char -data FormatMode = FormatMode Padding TypeFormat (Maybe Char) +data FormatModeT t = FormatMode (PaddingT t) (TypeFormatT t) (Maybe Char) + +type FormatMode = FormatModeT (ExprOrValue Int) -- | Padding, containing the padding width, the padding char and the alignement mode -data Padding +data PaddingT t = PaddingDefault - | Padding (ExprOrValue Int) (Maybe (Maybe Char, AnyAlign)) + | Padding t (Maybe (Maybe Char, AnyAlign)) + +type Padding = PaddingT (ExprOrValue Int) -- | Represents a value of type @t@ or an Haskell expression supposed to represents that value +-- TODO: why the `t`? data ExprOrValue t = Value t - | HaskellExpr (HsExpr GhcPs, Exp) - deriving (Data) + | HaskellExpr SourcePos String + deriving (Data, Show) -- | Floating point precision -data Precision +data PrecisionT t = PrecisionDefault - | Precision (ExprOrValue Int) - deriving (Data) + | Precision t + deriving (Data, Show) + +type Precision = PrecisionT (ExprOrValue Int) {- @@ -215,10 +216,12 @@ type ::= "b" | "c" | "d" | "e" | "E" | "f" | "F" | "g" | "G" | "n" | data TypeFlag = Flagb | Flagc | Flagd | Flage | FlagE | Flagf | FlagF | Flagg | FlagG | Flagn | Flago | Flags | Flagx | FlagX | FlagPercent deriving (Show) +type TypeFormat = TypeFormatT (ExprOrValue Int) + -- | All formatting type -data TypeFormat +data TypeFormatT t = -- | Default, depends on the infered type of the expression - DefaultF Precision SignMode + DefaultF (PrecisionT t) SignMode | -- | Binary, such as `0b0121` BinaryF AlternateForm SignMode | -- | Character, will convert an integer to its character representation @@ -226,61 +229,33 @@ data TypeFormat | -- | Decimal, base 10 integer formatting DecimalF SignMode | -- | Exponential notation for floatting points - ExponentialF Precision AlternateForm SignMode + ExponentialF (PrecisionT t) AlternateForm SignMode | -- | Exponential notation with capitalised @e@ - ExponentialCapsF Precision AlternateForm SignMode + ExponentialCapsF (PrecisionT t) AlternateForm SignMode | -- | Fixed number of digits floating point - FixedF Precision AlternateForm SignMode + FixedF (PrecisionT t) AlternateForm SignMode | -- | Capitalized version of the previous - FixedCapsF Precision AlternateForm SignMode + FixedCapsF (PrecisionT t) AlternateForm SignMode | -- | General formatting: `FixedF` or `ExponentialF` depending on the number magnitude - GeneralF Precision AlternateForm SignMode + GeneralF (PrecisionT t) AlternateForm SignMode | -- | Same as `GeneralF` but with upper case @E@ and infinite / NaN - GeneralCapsF Precision AlternateForm SignMode + GeneralCapsF (PrecisionT t) AlternateForm SignMode | -- | Octal, such as 00245 OctalF AlternateForm SignMode | -- | Simple string - StringF Precision + StringF (PrecisionT t) | -- | Hexadecimal, such as 0xaf3e HexF AlternateForm SignMode | -- | Hexadecimal with capitalized letters, such as 0XAF3E HexCapsF AlternateForm SignMode | -- | Percent representation - PercentF Precision AlternateForm SignMode - deriving (Data) + PercentF (PrecisionT t) AlternateForm SignMode + deriving (Data, Show) -- | If the formatter use its alternate form data AlternateForm = AlternateForm | NormalForm deriving (Show, Data) -evalExpr :: [Extension] -> Parser String -> Parser (HsExpr GhcPs, Exp) -evalExpr exts exprParser = do - exprPos <- getPosition - -- Inject the correct source location in the GHC parser, so it already match - -- the input source file. - let initLoc = mkRealSrcLoc (mkFastString (sourceName exprPos)) (sourceLine exprPos) (sourceColumn exprPos) - s <- lookAhead exprParser - -- Setup the dyn flags using the provided list of extensions - let dynFlags = baseDynFlags exts - case ParseExp.parseExpression initLoc s dynFlags of - Right expr -> do - -- Consume the expression - void exprParser - pure (expr, toExp dynFlags expr) - Left (lineError, colError, err) -> do - -- In case of error, we just advance the parser to the error location. - -- Note: we have to remove what was introduced in `initLoc` - -- Skip lines - replicateM_ (lineError - sourceLine exprPos) (manyTill anyChar newline) - -- Skip columns - -- This is a bit more counter intuitive. If we have skipped not lines, we - -- must remove the introduced column offset, otherwise no. - let columnSkip - | lineError - sourceLine exprPos == 0 = colError - 1 - sourceColumn exprPos - | otherwise = colError - 2 - void $ count columnSkip anyChar - fail $ err <> " in haskell expression" - overrideAlignmentIfZero :: Bool -> Maybe (Maybe Char, AnyAlign) -> Maybe (Maybe Char, AnyAlign) overrideAlignmentIfZero True Nothing = Just (Just '0', AnyAlign AlignInside) overrideAlignmentIfZero True (Just (Nothing, al)) = Just (Just '0', al) @@ -313,21 +288,29 @@ formatSpec = do parseWidth :: Parser (ExprOrValue Int) parseWidth = do - exts <- asks enabledExtensions Just (charOpening, charClosing) <- asks delimiters choice [ Value <$> width, - char charOpening *> (HaskellExpr <$> evalExpr exts (someTill (satisfy (/= charClosing)) (char charClosing) "an haskell expression")) + char charOpening + *> ( do + pos <- getPosition + HaskellExpr pos <$> (someTill (satisfy (/= charClosing)) (char charClosing) "an haskell expression") + ) ] parsePrecision :: Parser Precision parsePrecision = do - exts <- asks enabledExtensions Just (charOpening, charClosing) <- asks delimiters _ <- char '.' choice [ Precision . Value <$> precision, - char charOpening *> (Precision . HaskellExpr <$> evalExpr exts (someTill (satisfy (/= charClosing)) (char charClosing) "an haskell expression")) + char charOpening + *> ( Precision + <$> ( do + pos <- getPosition + HaskellExpr pos <$> someTill (satisfy (/= charClosing)) (char charClosing) "an haskell expression" + ) + ) ] -- | Similar to 'manyTill' but always parse one element. @@ -373,7 +356,7 @@ failIfPrec (Precision e) _ = Left ("Type incompatible with precision (." ++ show where showExpr = case e of Value v -> show v - HaskellExpr (_, expr) -> show expr + HaskellExpr _ s -> s failIfAlt :: AlternateForm -> TypeFormat -> Either String TypeFormat failIfAlt NormalForm i = Right i diff --git a/src/PyF/Internal/QQ.hs b/src/PyF/Internal/QQ.hs index 88c90f9..6a1cdb3 100644 --- a/src/PyF/Internal/QQ.hs +++ b/src/PyF/Internal/QQ.hs @@ -19,13 +19,7 @@ -- | This module uses the python mini language detailed in -- 'PyF.Internal.PythonSyntax' to build an template haskell expression -- representing a formatted string. -module PyF.Internal.QQ - ( toExp, - Config (..), - wrapFromString, - expQQ, - ) -where +module PyF.Internal.QQ where import Control.Monad.Reader import Data.Data (Data (gmapQ), Typeable, cast) @@ -34,6 +28,8 @@ import Data.List (intercalate) import Data.Maybe (catMaybes, fromMaybe, isJust) import Data.Proxy import Data.String (fromString) +import qualified PyF.Internal.Meta +import PyF.Internal.PythonSyntax #if MIN_VERSION_ghc(9,0,0) import GHC.Tc.Utils.Monad (addErrAt) @@ -88,6 +84,8 @@ import SrcLoc import GHC.Hs #endif +import GHC.Data.FastString (mkFastString) +import qualified GHC.Data.Strict import GHC.TypeLits import Language.Haskell.TH hiding (Type) import Language.Haskell.TH.Quote @@ -95,8 +93,8 @@ import Language.Haskell.TH.Syntax (Q (Q)) import PyF.Class import PyF.Formatters (AnyAlign (..)) import qualified PyF.Formatters as Formatters -import PyF.Internal.Meta (toName) -import PyF.Internal.PythonSyntax +import PyF.Internal.Meta (baseDynFlags, toName) +import qualified PyF.Internal.Parser as ParseExp import Text.Parsec import Text.Parsec.Error ( errorMessages, @@ -144,8 +142,7 @@ wrapFromString e = do toExp :: Config -> String -> Q Exp toExp Config {delimiters = expressionDelimiters, postProcess} s = do loc <- location - exts <- extsEnabled - let context = ParsingContext expressionDelimiters exts + let context = ParsingContext expressionDelimiters -- Setup the parser so it matchs the real original position in the source -- code. @@ -158,30 +155,48 @@ toExp Config {delimiters = expressionDelimiters, postProcess} s = do -- executed anyway, there is an error [|()|] Right items -> do - checkResult <- checkVariables items - case checkResult of - Nothing -> postProcess (goFormat items) - Just (srcSpan, msg) -> do - reportErrorAt srcSpan msg + result <- goFormat items + case result of + Just exp -> postProcess (pure exp) + Nothing -> do + -- goFormat took care of emiting the error messages [|()|] -findFreeVariablesInFormatMode :: Maybe FormatMode -> [(SrcSpan, RdrName)] -findFreeVariablesInFormatMode Nothing = [] -findFreeVariablesInFormatMode (Just (FormatMode padding tf _)) = - findFreeVariables tf <> case padding of - PaddingDefault -> [] - Padding eoi _ -> findFreeVariables eoi - -checkOneItem :: Item -> Q (Maybe (SrcSpan, String)) -checkOneItem (Raw _) = pure Nothing -checkOneItem (Replacement (hsExpr, _) formatMode) = do - let allNames = findFreeVariables hsExpr <> findFreeVariablesInFormatMode formatMode +toHsExpr :: SourcePos -> String -> Q (Maybe (HsExpr GhcPs)) +toHsExpr sourcePos s = do + exts <- extsEnabled + let dynFlags = baseDynFlags exts + + let srcLoc = mkRealSrcLoc (mkFastString (sourceName sourcePos)) (sourceLine sourcePos) (sourceColumn sourcePos) + case ParseExp.parseExpression srcLoc s dynFlags of + Right hsExpr -> do + check <- checkVariables (unLoc hsExpr) + case check of + Right hsExpr' -> pure $ Just hsExpr' + Left (span, err) -> do + reportErrorAt span err + pure Nothing + Left (srcLocError', msg) -> do + -- I have no idea what is happening here, but the srcLocError is off by 1 column + let srcLocError = mkRealSrcLoc (mkFastString (sourceName sourcePos)) (srcLocLine srcLocError' + 0) (srcLocCol srcLocError' - 1) + reportErrorAt (srcLocSpan (RealSrcLoc srcLocError GHC.Data.Strict.Nothing)) (msg ++ " in haskell expression") + pure Nothing + +hsExprToTh :: HsExpr GhcPs -> Q Exp +hsExprToTh e = do + exts <- extsEnabled + let dynFlags = baseDynFlags exts + pure $ PyF.Internal.Meta.toExp dynFlags e + +checkVariables :: HsExpr GhcPs -> Q (Either (SrcSpan, String) (HsExpr GhcPs)) +checkVariables hsExpr = do + let allNames = findFreeVariables hsExpr res <- mapM doesExists allNames let resFinal = catMaybes res case resFinal of - [] -> pure Nothing - ((err, span) : _) -> pure $ Just (span, err) + [] -> pure $ Right hsExpr + ((err, span) : _) -> pure $ Left (span, err) {- ORMOLU_DISABLE -} findFreeVariables :: Data a => a -> [(SrcSpan, RdrName)] @@ -250,15 +265,6 @@ doesExists (loc, name) = do then pure Nothing else pure (Just ("Variable not in scope: " <> show (toName name), loc)) --- | Check that all variables used in 'Item' exists, otherwise, fail. -checkVariables :: [Item] -> Q (Maybe (SrcSpan, String)) -checkVariables [] = pure Nothing -checkVariables (x : xs) = do - r <- checkOneItem x - case r of - Nothing -> checkVariables xs - Just err -> pure $ Just err - -- Stolen from: https://www.tweag.io/blog/2021-01-07-haskell-dark-arts-part-i/ -- This allows to hack inside the the GHC api and use function not exported by template haskell. -- This may not be always safe, see https://github.com/guibou/PyF/issues/115, @@ -286,24 +292,27 @@ reportErrorAt loc msg = unsafeRunTcM $ addErrAt loc msg' #endif reportParserErrorAt :: ParseError -> Q () -reportParserErrorAt err = reportErrorAt span msg +reportParserErrorAt err = reportErrorAt (RealSrcSpan span mempty) msg where - msg = intercalate "\n" $ formatErrorMessages err + (loc, msg) = parseErrorToLocAndMessage err + span = mkRealSrcSpan loc loc' - span :: SrcSpan - span = mkSrcSpan loc loc' + loc' = srcLocFromParserError (incSourceColumn (errorPos err) 1) +parseErrorToLocAndMessage :: ParseError -> (RealSrcLoc, [Char]) +parseErrorToLocAndMessage err = (loc, msg) + where + msg = intercalate "\n" $ formatErrorMessages err loc = srcLocFromParserError (errorPos err) - loc' = srcLocFromParserError (incSourceColumn (errorPos err) 1) -srcLocFromParserError :: SourcePos -> SrcLoc +srcLocFromParserError :: SourcePos -> RealSrcLoc srcLocFromParserError sourceLoc = srcLoc where line = sourceLine sourceLoc column = sourceColumn sourceLoc name = sourceName sourceLoc - srcLoc = mkSrcLoc (fromString name) line column + srcLoc = mkRealSrcLoc (fromString name) line column formatErrorMessages :: ParseError -> [String] formatErrorMessages err @@ -322,10 +331,12 @@ Note: Empty String Lifting Empty string are lifted as [] instead of "", so I'm using LitE (String L) instead -} -goFormat :: [Item] -> Q Exp +goFormat :: [Item] -> Q (Maybe Exp) -- We special case on empty list in order to generate an empty string -goFormat [] = pure $ LitE (StringL "") -- see [Empty String Lifting] -goFormat items = foldl1 sappendQ <$> mapM toFormat items +goFormat [] = pure $ Just $ LitE (StringL "") -- see [Empty String Lifting] +goFormat items = do + exprs <- mapM toFormat items + pure $ (foldl1 sappendQ <$> (sequenceA exprs)) -- | call `<>` between two 'Exp' sappendQ :: Exp -> Exp -> Exp @@ -333,11 +344,16 @@ sappendQ s0 s1 = InfixE (Just s0) (VarE '(<>)) (Just s1) -- Real formatting is here -toFormat :: Item -> Q Exp -toFormat (Raw x) = pure $ LitE (StringL x) -- see [Empty String Lifting] -toFormat (Replacement (_, expr) y) = do - formatExpr <- padAndFormat (fromMaybe DefaultFormatMode y) - pure (formatExpr `AppE` expr) +toFormat :: Item -> Q (Maybe Exp) +toFormat (Raw x) = pure $ Just $ LitE (StringL x) -- see [Empty String Lifting] +toFormat (Replacement loc s y) = do + exprM <- toHsExpr loc s + case exprM of + Nothing -> pure Nothing + Just expr -> do + thExpr <- hsExprToTh expr + formatExpr <- padAndFormat (fromMaybe DefaultFormatMode y) + pure (Just $ formatExpr `AppE` thExpr) -- | Default precision for floating point defaultFloatPrecision :: Maybe Int @@ -389,7 +405,11 @@ newPaddingQ padding = case padding of exprToInt :: ExprOrValue Int -> Q Exp -- Note: this is a literal provided integral. We use explicit case to ::Int so it won't warn about defaulting exprToInt (Value i) = [|$(pure $ LitE (IntegerL (fromIntegral i))) :: Int|] -exprToInt (HaskellExpr (_, e)) = [|$(pure e)|] +exprToInt (HaskellExpr srcLoc e) = do + exprM <- toHsExpr srcLoc e + case exprM of + Nothing -> [|()|] + Just e -> hsExprToTh e data PaddingK k i where PaddingDefaultK :: PaddingK 'Formatters.AlignAll Int diff --git a/src/PyF/Plugin.hs b/src/PyF/Plugin.hs new file mode 100644 index 0000000..f2cdea6 --- /dev/null +++ b/src/PyF/Plugin.hs @@ -0,0 +1,462 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE PartialTypeSignatures #-} +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TemplateHaskellQuotes #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE ViewPatterns #-} + +module PyF.Plugin (plugin, forceError) where + +import Data.Data +import qualified GHC.LanguageExtensions as LangExt + +-- import Data.Generics + +#if MIN_VERSION_ghc(9,0,0) +import GHC.Hs +import GHC.Plugins hiding (msg) +#else +import GHC +import GhcPlugins +#endif + +import Control.Monad (join) +import Control.Monad.Reader (runReader) +import Data.Generics +import Data.Maybe (fromMaybe) +import Data.String +import GHC.ThToHs (thRdrNameGuesses) +import GHC.TypeLits +import qualified GHC.Types.Name.Occurrence as GHC.Types.Name.Occurence +import GHC.Types.SourceText (SourceText (..), mkIntegralLit) +import PyF (PyFToString (..), fmtConfig, trimIndent) +import PyF.Formatters +import qualified PyF.Internal.Parser as ParseExp +import PyF.Internal.PythonSyntax + ( AlternateForm (..), + ExprOrValue (..), + FormatModeT (..), + Item (..), + PaddingT (..), + ParsingContext (..), + PrecisionT (..), + TypeFormatT (..), + parseGenericFormatString, + pattern DefaultFormatMode, + ) +import PyF.Internal.QQ (Config (..), PaddingK (..), defaultFloatPrecision, formatAny, formatAnyFractional, formatAnyIntegral, parseErrorToLocAndMessage) +import Text.Parsec (runParserT) +import Text.Parsec.Pos +import Text.Parsec.Prim (setPosition) + +-- | A plugin which replaces all [fmt|...] from PyF by a pure haskell code +-- without template haskell. +plugin :: Plugin +plugin = + defaultPlugin + { pluginRecompile = purePlugin, + parsedResultAction = \_ _ parsedResult -> do + m <- action $ parsedResultModule parsedResult + pure $ parsedResult {parsedResultModule = m} + } + +action :: HsParsedModule -> Hsc HsParsedModule +action parsed@HsParsedModule {hpm_module = m} = + (\m' -> parsed {hpm_module = m'}) + <$> gmapM (everywhereM (mkM replaceSplice)) m + +{- ORMOLU_DISABLE -} +-- | Replace a splice entry +replaceSplice :: HsExpr GhcPs -> Hsc (HsExpr GhcPs) +replaceSplice e = do + case e of +#if MIN_VERSION_ghc(9,10,0) + HsUntypedSplice _xsplit (HsQuasiQuote _xquasi (Unqual name) (L (getHasLoc -> loc) s)) +#else + HsUntypedSplice _xsplit (HsQuasiQuote _xquasi (Unqual name) (L (SrcSpanAnn _ loc) s)) +#endif + | mkVarOcc "fmt" == name -> applyPyf loc $ unpackFS s + | mkVarOcc "fmtTrim" == name -> applyPyf loc (trimIndent $ unpackFS s) + | mkVarOcc "str" == name -> pure $ HsLit noExtField' (HsString NoSourceText s) + | mkVarOcc "strTrim" == name -> pure $ HsLit noExtField' (HsString NoSourceText (mkFastString $ trimIndent $ unpackFS s)) + _ -> do + pure e +{- ORMOLU_ENABLE -} + +{- + - This is not used, the idea was to report the error during the plugin, but it + - actually fails the compilation completly. +reportError theLoc theMsg = do + Hsc $ \env messages -> do + pure + ( (), + addMessage + ( MsgEnvelope + { errMsgSpan = RealSrcSpan (realSrcLocSpan theLoc) mempty, + -- TODO: maybe alwaysqualify can be refined + errMsgContext = alwaysQualify, + errMsgDiagnostic = GhcUnknownMessage (UnknownDiagnostic (mkPlainError noHints (text theMsg))), + errMsgSeverity = SevWarning + } + ) + messages + ) +-} + +{- ORMOLU_DISABLE -} +applyPyf :: SrcSpan -> String -> Hsc (HsExpr GhcPs) +applyPyf loc s = do + let pyfItems = pyf loc s + (join . fmap sequenceA -> itemsM) <- sequenceA (mapM toString <$> pyfItems) + case itemsM of + Left (theLoc, theMsg) -> do +#if MIN_VERSION_ghc(9,10,0) + pure $ HsPar (NoEpTok, NoEpTok) (L ((EpAnn (EpaSpan $ RealSrcSpan (realSrcLocSpan theLoc) mempty) (AnnListItem []) emptyComments)) $ var 'forceError `app` (ctor 'Proxy `appTypeSymbol` theMsg)) +#else + pure $ HsPar noExtField' noHsTok (L ((SrcSpanAnn noExtField' (RealSrcSpan (realSrcLocSpan theLoc) mempty))) $ var 'forceError `app` (ctor 'Proxy `appTypeSymbol` theMsg)) noHsTok +#endif + Right items -> do + dynFlags <- getDynFlags + let toOverloaded + | xopt LangExt.OverloadedStrings dynFlags = app (var 'fromString) + | otherwise = id + pure $ + toOverloaded $ + HsApp + noExtField' + ( L + noSrcSpanA + ( HsVar + NoExtField + ( L noSrcSpanA $ + mkUnqual GHC.Types.Name.Occurence.varName (mkFastString "mconcat") + ) + ) + ) + (L noSrcSpanA $ ExplicitList emptyAnnList $ items) +{- ORMOLU_ENABLE -} + +-- TODO: a lot of the Either could be "Validation" and generate MULTIPLES +-- errors messages, but for now GHC is not able to handle multiples errors +toString :: Item -> Hsc (Either (RealSrcLoc, String) (GenLocated _ (HsExpr GhcPs))) +toString (Raw s) = pure $ pure $ L noSrcSpanA (HsLit noExtField' $ HsString NoSourceText (mkFastString s)) -- TODO: restore the correct location for the "raw" string +toString (Replacement loc s formatMode) = do + exprM <- toHsExpr loc s + formatExprM <- padAndFormat (fromMaybe DefaultFormatMode formatMode) + + -- We wrap the formatted expression using the location of the original expression + -- Hence GHC will report type error at that location, if relevant + pure $ do + expr <- exprM + formatExpr <- formatExprM + let loc' = getLoc expr + pure $ L loc' (formatExpr `app'` expr) + +pyf :: SrcSpan -> String -> Either (RealSrcLoc, String) [Item] +pyf srcSpan s = case runReader (runParserT (setPosition initPos >> parseGenericFormatString) () filename s) context of + Right r -> Right r + Left e -> Left (loc, msg) + where + (loc, msg) = parseErrorToLocAndMessage e + where + filename = unpackFS $ srcLocFile start + Config {..} = fmtConfig + context = ParsingContext {..} + + initPos = setSourceColumn (setSourceLine (initialPos filename) (srcLocLine start)) (srcLocCol start) + start = case srcSpanStart srcSpan of + RealSrcLoc startLoc _ -> startLoc + _ -> error "Plugin API does not know it's RealSrcLoc" + +-- Foo @"symbol" +appTypeSymbol :: HsExpr GhcPs -> String -> HsExpr GhcPs +appTypeSymbol a name = + appTypeAny + a + (HsTyLit NoExtField (HsStrTy NoSourceText (mkFastString name))) + +-- Foo @Bar +appType :: HsExpr GhcPs -> RdrName -> HsExpr GhcPs +appType a name = appTypeAny a +#if MIN_VERSION_ghc(9,10,0) + (HsTyVar [] NotPromoted (noLocA name)) +#else + (HsTyVar noExtField' NotPromoted (L noSrcSpanA name)) +#endif + +-- Foo @Int +appType' :: HsExpr GhcPs -> _ -> HsExpr GhcPs +appType' a name = appTypeAny a +#if MIN_VERSION_ghc(9,10,0) + (HsTyVar [] NotPromoted (noLocA $ pyfName name)) +#else + (HsTyVar noExtField' NotPromoted (L noSrcSpanA (pyfName name))) +#endif + +{- ORMOLU_DISABLE -} +appTypeAny :: HsExpr GhcPs -> HsType GhcPs -> HsExpr GhcPs +appTypeAny a b = +#if MIN_VERSION_ghc(9,10,0) + HsAppType NoEpTok (L noSrcSpanA a) (HsWC NoExtField (L noSrcSpanA b)) +#else + HsAppType NoExtField (L noSrcSpanA a) (L NoTokenLoc (HsTok)) (HsWC NoExtField (L noSrcSpanA b)) +#endif +{- ORMOLU_ENABLE -} + +app :: HsExpr GhcPs -> HsExpr GhcPs -> HsExpr GhcPs +app a b = HsApp noExtField' (L noSrcSpanA a) (L noSrcSpanA b) + +app' :: HsExpr GhcPs -> (GenLocated SrcSpanAnnA (HsExpr GhcPs)) -> HsExpr GhcPs +app' a b = HsApp noExtField' (L noSrcSpanA a) b + +var :: _ -> HsExpr GhcPs +var name = + ( HsVar + NoExtField + (L noSrcSpanA $ pyfName name) + ) + +ctor :: _ -> HsExpr GhcPs +ctor name = + ( HsVar + NoExtField + (L noSrcSpanA $ pyfName name) + ) + +padAndFormat :: FormatModeT (ExprOrValue Int) -> Hsc (Either (RealSrcLoc, String) (HsExpr GhcPs)) +padAndFormat formatMode' = do + formatModeM <- evalSubExpression formatMode' + pure $ do + FormatMode padding tf grouping <- formatModeM + pure $ case tf of + -- Integrals + BinaryF alt s -> var 'formatAnyIntegral `app` withAlt alt Binary `app` toSignMode s `app` mkPadding padding `app` toGrp grouping 4 + CharacterF -> var 'formatAnyIntegral `app` ctor 'Character `app` ctor 'Minus `app` mkPadding padding `app` ctor 'Nothing + DecimalF s -> var 'formatAnyIntegral `app` ctor 'Decimal `app` toSignMode s `app` mkPadding padding `app` toGrp grouping 3 + HexF alt s -> var 'formatAnyIntegral `app` withAlt alt Hexa `app` toSignMode s `app` mkPadding padding `app` toGrp grouping 4 + OctalF alt s -> var 'formatAnyIntegral `app` withAlt alt Octal `app` toSignMode s `app` mkPadding padding `app` toGrp grouping 4 + HexCapsF alt s -> var 'formatAnyIntegral `app` (ctor 'Upper `app` (withAlt alt Hexa)) `app` toSignMode s `app` mkPadding padding `app` toGrp grouping 4 + -- Floating + GeneralF prec alt s -> var 'formatAnyFractional `app` withAlt alt Generic `app` toSignMode s `app` mkPadding padding `app` toGrp grouping 3 `app` mkPrecision defaultFloatPrecision prec + GeneralCapsF prec alt s -> var 'formatAnyFractional `app` (ctor 'Upper `app` (withAlt alt Generic)) `app` toSignMode s `app` mkPadding padding `app` toGrp grouping 3 `app` mkPrecision defaultFloatPrecision prec + ExponentialF prec alt s -> var 'formatAnyFractional `app` withAlt alt Exponent `app` toSignMode s `app` mkPadding padding `app` toGrp grouping 3 `app` mkPrecision defaultFloatPrecision prec + ExponentialCapsF prec alt s -> var 'formatAnyFractional `app` (ctor 'Upper `app` (withAlt alt Exponent)) `app` toSignMode s `app` mkPadding padding `app` toGrp grouping 3 `app` mkPrecision defaultFloatPrecision prec + FixedF prec alt s -> var 'formatAnyFractional `app` withAlt alt Fixed `app` toSignMode s `app` mkPadding padding `app` toGrp grouping 3 `app` mkPrecision defaultFloatPrecision prec + FixedCapsF prec alt s -> var 'formatAnyFractional `app` (ctor 'Upper `app` (withAlt alt Fixed)) `app` toSignMode s `app` mkPadding padding `app` toGrp grouping 3 `app` mkPrecision defaultFloatPrecision prec + PercentF prec alt s -> var 'formatAnyFractional `app` withAlt alt Percent `app` toSignMode s `app` mkPadding padding `app` toGrp grouping 3 `app` mkPrecision defaultFloatPrecision prec + -- Default / String + DefaultF prec s -> var 'formatAny `app` toSignMode s `app` mkPaddingToPaddingK padding `app` toGrp grouping 3 `app` mkPrecision Nothing prec + StringF prec -> (var '(.)) `app` (var 'formatString `app` (newPaddingKForString padding) `app` mkPrecision Nothing prec) `app` (var 'pyfToString) + +evalSubExpression :: FormatModeT (ExprOrValue Int) -> Hsc (Either (RealSrcLoc, String) (FormatModeT (LocatedA (HsExpr GhcPs)))) +evalSubExpression (FormatMode padding tf grouping) = do + padding' <- evalPadding padding + tf' <- evalTf tf + pure $ FormatMode <$> padding' <*> tf' <*> pure grouping + +evalTf :: TypeFormatT (ExprOrValue Int) -> Hsc (Either (RealSrcLoc, String) (TypeFormatT (LocatedA (HsExpr GhcPs)))) +evalTf tf = case tf of + -- Integrals + BinaryF alt s -> pure $ pure $ BinaryF alt s + CharacterF -> pure $ pure $ CharacterF + DecimalF s -> pure $ pure $ DecimalF s + HexF alt s -> pure $ pure $ HexF alt s + OctalF alt s -> pure $ pure $ OctalF alt s + HexCapsF alt s -> pure $ pure $ HexCapsF alt s + -- Floating + GeneralF prec alt s -> do + prec' <- evalPrecision prec + pure $ GeneralF <$> prec' <*> pure alt <*> pure s + GeneralCapsF prec alt s -> do + prec' <- evalPrecision prec + pure $ GeneralCapsF <$> prec' <*> pure alt <*> pure s + ExponentialF prec alt s -> do + prec' <- evalPrecision prec + pure $ ExponentialF <$> prec' <*> pure alt <*> pure s + ExponentialCapsF prec alt s -> do + prec' <- evalPrecision prec + pure $ ExponentialCapsF <$> prec' <*> pure alt <*> pure s + FixedF prec alt s -> do + prec' <- evalPrecision prec + pure $ FixedF <$> prec' <*> pure alt <*> pure s + FixedCapsF prec alt s -> do + prec' <- evalPrecision prec + pure $ FixedCapsF <$> prec' <*> pure alt <*> pure s + PercentF prec alt s -> do + prec' <- evalPrecision prec + pure $ PercentF <$> prec' <*> pure alt <*> pure s + -- Default / String + DefaultF prec s -> do + prec' <- evalPrecision prec + pure $ DefaultF <$> prec' <*> pure s + StringF prec -> do + prec' <- evalPrecision prec + pure $ StringF <$> prec' + +evalPrecision :: PrecisionT (ExprOrValue Int) -> Hsc (Either (RealSrcLoc, String) (PrecisionT (LocatedA (HsExpr GhcPs)))) +evalPrecision (PrecisionDefault) = pure $ pure PrecisionDefault +evalPrecision (Precision e) = fmap Precision <$> exprToInt e + +evalPadding :: PaddingT (ExprOrValue Int) -> Hsc (Either (RealSrcLoc, String) (PaddingT (LocatedA (HsExpr GhcPs)))) +evalPadding p = case p of + PaddingDefault -> pure $ pure PaddingDefault + Padding i v -> do + i' <- exprToInt i + pure $ Padding <$> i' <*> pure v + +pyfName n = head $ thRdrNameGuesses n + +mkPaddingToPaddingK :: PaddingT (GenLocated SrcSpanAnnA (HsExpr GhcPs)) -> HsExpr GhcPs +mkPaddingToPaddingK p = case p of + PaddingDefault -> ctor 'PaddingDefaultK + Padding i Nothing -> + appType + (appType' (ctor 'PaddingK) ''Int) + (pyfName 'PyF.Formatters.AlignAll) + `app'` i + `app` (liftHsExpr $ (Nothing :: Maybe (Int, AnyAlign, Char))) + Padding i (Just (c, AnyAlign a)) -> ctor 'PaddingK `app'` i `app` liftHsExpr (Just (c, a)) + +newPaddingKForString :: PaddingT (LocatedA (HsExpr GhcPs)) -> HsExpr GhcPs +newPaddingKForString padding = case padding of + PaddingDefault -> ctor 'Nothing + Padding i Nothing -> liftHsExpr (Just (i, AlignLeft, ' ')) -- default align left and fill with space for string + Padding i (Just (mc, AnyAlign a)) -> liftHsExpr (Just (i, a, fromMaybe ' ' mc)) + +mkPadding :: PaddingT (LocatedA (HsExpr GhcPs)) -> HsExpr GhcPs +mkPadding padding = case padding of + PaddingDefault -> liftHsExpr (Nothing :: Maybe (Int, AnyAlign, Char)) + (Padding i al) -> case al of + Nothing -> liftHsExpr (Just (i, AnyAlign AlignRight, ' ')) -- Right align and space is default for any object, except string + Just (Nothing, a) -> liftHsExpr $ Just (i, a, ' ') + Just (Just c, a) -> liftHsExpr $ Just (i, a, c) + +class LiftHsExpr a where + liftHsExpr :: a -> HsExpr GhcPs + +instance (LiftHsExpr a, LiftHsExpr b) => LiftHsExpr (a, b) where + liftHsExpr (a, b) = mkTup [liftHsExpr a, liftHsExpr b] + +instance (LiftHsExpr a, LiftHsExpr b, LiftHsExpr c) => LiftHsExpr (a, b, c) where + liftHsExpr (a, b, c) = mkTup [liftHsExpr a, liftHsExpr b, liftHsExpr c] + +instance (LiftHsExpr a) => LiftHsExpr (Maybe a) where + liftHsExpr Nothing = ctor 'Nothing + liftHsExpr (Just v) = ctor 'Just `app` liftHsExpr v + +instance LiftHsExpr (AlignMode k) where + liftHsExpr AlignLeft = ctor 'AlignLeft + liftHsExpr AlignRight = ctor 'AlignRight + liftHsExpr AlignInside = ctor 'AlignInside + liftHsExpr AlignCenter = ctor 'AlignCenter + +instance LiftHsExpr Char where + liftHsExpr c = HsLit noExtField' (HsChar NoSourceText c) + +instance LiftHsExpr Int where + liftHsExpr i = HsLit noExtField' $ HsInt NoExtField (mkIntegralLit i) + +instance LiftHsExpr (Format k k' k'') where + liftHsExpr (Alternate v) = ctor 'Alternate `app` liftHsExpr v + liftHsExpr (Upper v) = ctor 'Upper `app` liftHsExpr v + liftHsExpr Decimal = ctor 'Decimal + liftHsExpr Character = ctor 'Character + liftHsExpr Binary = ctor 'Binary + liftHsExpr Hexa = ctor 'Hexa + liftHsExpr Octal = ctor 'Octal + liftHsExpr Fixed = ctor 'Fixed + liftHsExpr Exponent = ctor 'Exponent + liftHsExpr Generic = ctor 'Generic + liftHsExpr Percent = ctor 'Percent + +instance LiftHsExpr AnyAlign where + liftHsExpr (AnyAlign v) = ctor 'AnyAlign `app` liftHsExpr v + +instance LiftHsExpr (HsExpr GhcPs) where + liftHsExpr x = x + +#if MIN_VERSION_ghc(9,10,0) +instance LiftHsExpr (GenLocated SrcSpanAnnA (HsExpr GhcPs)) where + liftHsExpr x = HsPar (NoEpTok, NoEpTok) x +#else +instance LiftHsExpr (GenLocated SrcSpanAnnA (HsExpr GhcPs)) where + liftHsExpr x = HsPar noExtField' noHsTok x noHsTok +#endif + +{- ORMOLU_DISABLE -} +mkTup :: [HsExpr GhcPs] -> HsExpr GhcPs +mkTup l = + ExplicitTuple +#if MIN_VERSION_ghc(9,10,0) + [] +#else + noExtField' +#endif + ( map + (\x -> Present noExtField' (L noSrcSpanA x)) + l + ) + Boxed +{- ORMOLU_ENABLE -} + +toSignMode :: SignMode -> HsExpr GhcPs +toSignMode Plus = ctor 'Plus +toSignMode Minus = ctor 'Minus +toSignMode Space = ctor 'Space + +toGrp :: Maybe Char -> Int -> HsExpr GhcPs +toGrp Nothing _ = ctor 'Nothing +toGrp (Just v) a = liftHsExpr $ Just grp + where + grp = (a, v) + +withAlt :: AlternateForm -> Format 'CanAlt b c -> HsExpr GhcPs +withAlt NormalForm e = liftHsExpr e +withAlt AlternateForm e = liftHsExpr (Alternate e) + +mkPrecision :: Maybe Int -> PrecisionT (LocatedA (HsExpr GhcPs)) -> HsExpr GhcPs +mkPrecision Nothing PrecisionDefault = ctor 'Nothing +mkPrecision (Just v) PrecisionDefault = ctor 'Just `app` (HsLit noExtField' $ HsInt NoExtField (mkIntegralLit v)) +mkPrecision _ (Precision p) = liftHsExpr (Just p) + +exprToInt :: ExprOrValue Int -> Hsc (Either (RealSrcLoc, String) (LocatedA (HsExpr GhcPs))) +exprToInt (Value i) = pure $ pure $ noLocA $ HsLit noExtField' $ HsInt NoExtField (mkIntegralLit i) +exprToInt (HaskellExpr loc s) = toHsExpr loc s + +toHsExpr :: SourcePos -> String -> Hsc (Either (RealSrcLoc, String) (LocatedA (HsExpr GhcPs))) +toHsExpr sourcePos s = do + dynFlags <- getDynFlags + let srcLoc = mkRealSrcLoc (mkFastString (sourceName sourcePos)) (sourceLine sourcePos) (sourceColumn sourcePos) + + case ParseExp.parseExpression srcLoc s dynFlags of + Right res -> pure $ Right res + Left e -> pure $ Left e + +class ForceError (m :: Symbol) where + forceError :: Proxy m -> t + +instance (TypeError (Text m)) => ForceError m where + forceError = undefined + +#if MIN_VERSION_ghc(9,10,0) +noExtField' :: NoExtField +noExtField' = NoExtField + +emptyAnnList :: AnnList +emptyAnnList = AnnList Nothing Nothing Nothing [] [] +#else +-- Tested with 9.6 +noExtField' :: EpAnn ann +noExtField' = EpAnnNotUsed + +emptyAnnList :: EpAnn ann +emptyAnnList = EpAnnNotUsed +#endif + +-- TODO: maybe we can use convertToHsExpr in order to generate the source code we want diff --git a/test/Spec.hs b/test/Spec.hs index 2b3dff0..25ee520 100644 --- a/test/Spec.hs +++ b/test/Spec.hs @@ -26,6 +26,7 @@ import qualified Data.ByteString.Lazy.Char8 import qualified Data.List as List import Data.Proxy (Proxy (..)) import qualified Data.Ratio +import Data.String import qualified Data.Text import qualified Data.Text as Text import qualified Data.Text.Lazy @@ -493,7 +494,7 @@ yeah\ [fmtTrim| Cannot convert formula 2.0 * exponent(unit=s, value=1.0) which has unit dimensionless to\ unit dimensionless for they have different dimensions|] - `shouldBe` "Cannot convert formula 2.0 * exponent(unit=s, value=1.0) which has unit dimensionless to unit dimensionless for they have different dimensions" + `shouldBe` "Cannot convert formula 2.0 * exponent(unit=s, value=1.0) which has unit dimensionless to unit dimensionless for they have different dimensions" describe "raw" $ do it "does not escape anything" $ [raw|hello diff --git a/test/SpecPlugin.hs b/test/SpecPlugin.hs new file mode 100644 index 0000000..c7bc34f --- /dev/null +++ b/test/SpecPlugin.hs @@ -0,0 +1,9 @@ +{-# OPTIONS -fplugin=PyF.Plugin #-} +{-# LANGUAGE QuasiQuotes #-} + +module Main where + +import PyF + +main = do + putStrLn [fmt|Hello world! {(1 :: Int) + 1:s} is a nice value.|] diff --git a/test/golden96/{TrueCLd}.12627313193367841398.golden b/test/golden96/{TrueCLd}.12627313193367841398.golden index f354cb7..9a27791 100644 --- a/test/golden96/{TrueCLd}.12627313193367841398.golden +++ b/test/golden96/{TrueCLd}.12627313193367841398.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Integral Bool’ arising from a use of ‘PyF.Internal.QQ.formatAnyIntegral’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Decimal PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing True)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Decimal PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing True) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Decimal PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing True) + • No instance for ‘Integral Bool’ arising from a use of ‘formatAnyIntegral’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyIntegral Decimal Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing True)’ + In the expression: putStrLn (formatAnyIntegral Decimal Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing True) + In an equation for ‘main’: main = putStrLn (formatAnyIntegral Decimal Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing True) | 7 | main = putStrLn [fmt|{True:d}|] | ^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{TrueCLf}.18281408089045870326.golden b/test/golden96/{TrueCLf}.18281408089045870326.golden index bf6f0c9..a60ff2a 100644 --- a/test/golden96/{TrueCLf}.18281408089045870326.golden +++ b/test/golden96/{TrueCLf}.18281408089045870326.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Real Bool’ arising from a use of ‘PyF.Internal.QQ.formatAnyFractional’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyFractional PyF.Formatters.Fixed PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) True)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyFractional PyF.Formatters.Fixed PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) True) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyFractional PyF.Formatters.Fixed PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) True) + • No instance for ‘Real Bool’ arising from a use of ‘formatAnyFractional’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyFractional Fixed Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) True)’ + In the expression: putStrLn (formatAnyFractional Fixed Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) True) + In an equation for ‘main’: main = putStrLn (formatAnyFractional Fixed Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) True) | 7 | main = putStrLn [fmt|{True:f}|] | ^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{True}.16254223077612353942.golden b/test/golden96/{True}.16254223077612353942.golden index 990b9bd..48b320a 100644 --- a/test/golden96/{True}.16254223077612353942.golden +++ b/test/golden96/{True}.16254223077612353942.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘PyF.Internal.QQ.FormatAny2 (PyFClassify Bool) Bool PyF.Formatters.AlignAll’ arising from a use of ‘PyF.Internal.QQ.formatAny’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAny PyF.Formatters.Minus PyF.Internal.QQ.PaddingDefaultK Nothing (Nothing :: Maybe Int) True)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAny PyF.Formatters.Minus PyF.Internal.QQ.PaddingDefaultK Nothing (Nothing :: Maybe Int) True) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAny PyF.Formatters.Minus PyF.Internal.QQ.PaddingDefaultK Nothing (Nothing :: Maybe Int) True) + • No instance for ‘FormatAny2 (PyFClassify Bool) Bool AlignAll’ arising from a use of ‘formatAny’ + • In the first argument of ‘putStrLn’, namely ‘(formatAny Minus PaddingDefaultK Nothing (Nothing :: Maybe Int) True)’ + In the expression: putStrLn (formatAny Minus PaddingDefaultK Nothing (Nothing :: Maybe Int) True) + In an equation for ‘main’: main = putStrLn (formatAny Minus PaddingDefaultK Nothing (Nothing :: Maybe Int) True) | 7 | main = putStrLn [fmt|{True}|] | ^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{helloCL%}.1257653362598537778.golden b/test/golden96/{helloCL%}.1257653362598537778.golden index e28cd7c..3e36c1f 100644 --- a/test/golden96/{helloCL%}.1257653362598537778.golden +++ b/test/golden96/{helloCL%}.1257653362598537778.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Real String’ arising from a use of ‘PyF.Internal.QQ.formatAnyFractional’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyFractional PyF.Formatters.Percent PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyFractional PyF.Formatters.Percent PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyFractional PyF.Formatters.Percent PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) + • No instance for ‘Real String’ arising from a use of ‘formatAnyFractional’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyFractional Percent Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello)’ + In the expression: putStrLn (formatAnyFractional Percent Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) + In an equation for ‘main’: main = putStrLn (formatAnyFractional Percent Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) | 7 | main = putStrLn [fmt|{hello:%}|] | ^^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{helloCL=100}.9444838110946424370.golden b/test/golden96/{helloCL=100}.9444838110946424370.golden index 762ab93..0091be1 100644 --- a/test/golden96/{helloCL=100}.9444838110946424370.golden +++ b/test/golden96/{helloCL=100}.9444838110946424370.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-64725] • String type is incompatible with inside padding (=). - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAny PyF.Formatters.Minus (PyF.Internal.QQ.PaddingK (100 :: Int) (Just (Nothing, PyF.Formatters.AlignInside))) Nothing (Nothing :: Maybe Int) hello)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAny PyF.Formatters.Minus (PyF.Internal.QQ.PaddingK (100 :: Int) (Just (Nothing, PyF.Formatters.AlignInside))) Nothing (Nothing :: Maybe Int) hello) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAny PyF.Formatters.Minus (PyF.Internal.QQ.PaddingK (100 :: Int) (Just (Nothing, PyF.Formatters.AlignInside))) Nothing (Nothing :: Maybe Int) hello) + • In the first argument of ‘putStrLn’, namely ‘(formatAny Minus (PaddingK (100 :: Int) (Just (Nothing, AlignInside))) Nothing (Nothing :: Maybe Int) hello)’ + In the expression: putStrLn (formatAny Minus (PaddingK (100 :: Int) (Just (Nothing, AlignInside))) Nothing (Nothing :: Maybe Int) hello) + In an equation for ‘main’: main = putStrLn (formatAny Minus (PaddingK (100 :: Int) (Just (Nothing, AlignInside))) Nothing (Nothing :: Maybe Int) hello) | 7 | main = putStrLn [fmt|{hello:=100}|] | ^^^^^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{helloCLE}.15676531368138664498.golden b/test/golden96/{helloCLE}.15676531368138664498.golden index 28b95f7..3b7174e 100644 --- a/test/golden96/{helloCLE}.15676531368138664498.golden +++ b/test/golden96/{helloCLE}.15676531368138664498.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Real String’ arising from a use of ‘PyF.Internal.QQ.formatAnyFractional’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyFractional (PyF.Formatters.Upper PyF.Formatters.Exponent) PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyFractional (PyF.Formatters.Upper PyF.Formatters.Exponent) PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyFractional (PyF.Formatters.Upper PyF.Formatters.Exponent) PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) + • No instance for ‘Real String’ arising from a use of ‘formatAnyFractional’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyFractional (Upper Exponent) Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello)’ + In the expression: putStrLn (formatAnyFractional (Upper Exponent) Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) + In an equation for ‘main’: main = putStrLn (formatAnyFractional (Upper Exponent) Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) | 7 | main = putStrLn [fmt|{hello:E}|] | ^^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{helloCLG}.17442699390234010162.golden b/test/golden96/{helloCLG}.17442699390234010162.golden index 492403e..5c87749 100644 --- a/test/golden96/{helloCLG}.17442699390234010162.golden +++ b/test/golden96/{helloCLG}.17442699390234010162.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Real String’ arising from a use of ‘PyF.Internal.QQ.formatAnyFractional’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyFractional (PyF.Formatters.Upper PyF.Formatters.Generic) PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyFractional (PyF.Formatters.Upper PyF.Formatters.Generic) PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyFractional (PyF.Formatters.Upper PyF.Formatters.Generic) PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) + • No instance for ‘Real String’ arising from a use of ‘formatAnyFractional’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyFractional (Upper Generic) Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello)’ + In the expression: putStrLn (formatAnyFractional (Upper Generic) Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) + In an equation for ‘main’: main = putStrLn (formatAnyFractional (Upper Generic) Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) | 7 | main = putStrLn [fmt|{hello:G}|] | ^^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{helloCLX}.8447528333473699378.golden b/test/golden96/{helloCLX}.8447528333473699378.golden index 090f12a..d732172 100644 --- a/test/golden96/{helloCLX}.8447528333473699378.golden +++ b/test/golden96/{helloCLX}.8447528333473699378.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Integral String’ arising from a use of ‘PyF.Internal.QQ.formatAnyIntegral’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyIntegral (PyF.Formatters.Upper PyF.Formatters.Hexa) PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing hello)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyIntegral (PyF.Formatters.Upper PyF.Formatters.Hexa) PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing hello) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyIntegral (PyF.Formatters.Upper PyF.Formatters.Hexa) PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing hello) + • No instance for ‘Integral String’ arising from a use of ‘formatAnyIntegral’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyIntegral (Upper Hexa) Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing hello)’ + In the expression: putStrLn (formatAnyIntegral (Upper Hexa) Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing hello) + In an equation for ‘main’: main = putStrLn (formatAnyIntegral (Upper Hexa) Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing hello) | 7 | main = putStrLn [fmt|{hello:X}|] | ^^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{helloCLb}.14869862508711808562.golden b/test/golden96/{helloCLb}.14869862508711808562.golden index 6cf3d4a..7ea7ac6 100644 --- a/test/golden96/{helloCLb}.14869862508711808562.golden +++ b/test/golden96/{helloCLb}.14869862508711808562.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Integral String’ arising from a use of ‘PyF.Internal.QQ.formatAnyIntegral’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Binary PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing hello)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Binary PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing hello) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Binary PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing hello) + • No instance for ‘Integral String’ arising from a use of ‘formatAnyIntegral’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyIntegral Binary Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing hello)’ + In the expression: putStrLn (formatAnyIntegral Binary Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing hello) + In an equation for ‘main’: main = putStrLn (formatAnyIntegral Binary Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing hello) | 7 | main = putStrLn [fmt|{hello:b}|] | ^^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{helloCLd}.1892681375540151858.golden b/test/golden96/{helloCLd}.1892681375540151858.golden index 0e4c20f..0359f56 100644 --- a/test/golden96/{helloCLd}.1892681375540151858.golden +++ b/test/golden96/{helloCLd}.1892681375540151858.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Integral String’ arising from a use of ‘PyF.Internal.QQ.formatAnyIntegral’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Decimal PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing hello)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Decimal PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing hello) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Decimal PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing hello) + • No instance for ‘Integral String’ arising from a use of ‘formatAnyIntegral’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyIntegral Decimal Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing hello)’ + In the expression: putStrLn (formatAnyIntegral Decimal Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing hello) + In an equation for ‘main’: main = putStrLn (formatAnyIntegral Decimal Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing hello) | 7 | main = putStrLn [fmt|{hello:d}|] | ^^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{helloCLe}.13933826712837941810.golden b/test/golden96/{helloCLe}.13933826712837941810.golden index 39231d8..d608b74 100644 --- a/test/golden96/{helloCLe}.13933826712837941810.golden +++ b/test/golden96/{helloCLe}.13933826712837941810.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Real String’ arising from a use of ‘PyF.Internal.QQ.formatAnyFractional’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyFractional PyF.Formatters.Exponent PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyFractional PyF.Formatters.Exponent PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyFractional PyF.Formatters.Exponent PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) + • No instance for ‘Real String’ arising from a use of ‘formatAnyFractional’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyFractional Exponent Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello)’ + In the expression: putStrLn (formatAnyFractional Exponent Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) + In an equation for ‘main’: main = putStrLn (formatAnyFractional Exponent Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) | 7 | main = putStrLn [fmt|{hello:e}|] | ^^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{helloCLf}.14332487603622862386.golden b/test/golden96/{helloCLf}.14332487603622862386.golden index 2d8d8da..1bd2f83 100644 --- a/test/golden96/{helloCLf}.14332487603622862386.golden +++ b/test/golden96/{helloCLf}.14332487603622862386.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Real String’ arising from a use of ‘PyF.Internal.QQ.formatAnyFractional’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyFractional PyF.Formatters.Fixed PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyFractional PyF.Formatters.Fixed PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyFractional PyF.Formatters.Fixed PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) + • No instance for ‘Real String’ arising from a use of ‘formatAnyFractional’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyFractional Fixed Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello)’ + In the expression: putStrLn (formatAnyFractional Fixed Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) + In an equation for ‘main’: main = putStrLn (formatAnyFractional Fixed Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) | 7 | main = putStrLn [fmt|{hello:f}|] | ^^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{helloCLg}.9607247906229690930.golden b/test/golden96/{helloCLg}.9607247906229690930.golden index 72e0fdf..1c148f6 100644 --- a/test/golden96/{helloCLg}.9607247906229690930.golden +++ b/test/golden96/{helloCLg}.9607247906229690930.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Real String’ arising from a use of ‘PyF.Internal.QQ.formatAnyFractional’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyFractional PyF.Formatters.Generic PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyFractional PyF.Formatters.Generic PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyFractional PyF.Formatters.Generic PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) + • No instance for ‘Real String’ arising from a use of ‘formatAnyFractional’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyFractional Generic Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello)’ + In the expression: putStrLn (formatAnyFractional Generic Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) + In an equation for ‘main’: main = putStrLn (formatAnyFractional Generic Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing (Just 6 :: Maybe Int) hello) | 7 | main = putStrLn [fmt|{hello:g}|] | ^^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{helloCLo}.9389880575827657266.golden b/test/golden96/{helloCLo}.9389880575827657266.golden index 1fe353e..293ca9e 100644 --- a/test/golden96/{helloCLo}.9389880575827657266.golden +++ b/test/golden96/{helloCLo}.9389880575827657266.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Integral String’ arising from a use of ‘PyF.Internal.QQ.formatAnyIntegral’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Octal PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing hello)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Octal PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing hello) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Octal PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing hello) + • No instance for ‘Integral String’ arising from a use of ‘formatAnyIntegral’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyIntegral Octal Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing hello)’ + In the expression: putStrLn (formatAnyIntegral Octal Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing hello) + In an equation for ‘main’: main = putStrLn (formatAnyIntegral Octal Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing hello) | 7 | main = putStrLn [fmt|{hello:o}|] | ^^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{helloCLx}.14710080644372944434.golden b/test/golden96/{helloCLx}.14710080644372944434.golden index fa4174a..ca49551 100644 --- a/test/golden96/{helloCLx}.14710080644372944434.golden +++ b/test/golden96/{helloCLx}.14710080644372944434.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Integral String’ arising from a use of ‘PyF.Internal.QQ.formatAnyIntegral’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Hexa PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing hello)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Hexa PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing hello) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Hexa PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing hello) + • No instance for ‘Integral String’ arising from a use of ‘formatAnyIntegral’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyIntegral Hexa Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing hello)’ + In the expression: putStrLn (formatAnyIntegral Hexa Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing hello) + In an equation for ‘main’: main = putStrLn (formatAnyIntegral Hexa Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing hello) | 7 | main = putStrLn [fmt|{hello:x}|] | ^^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{numberCLX}.4609648040604121432.golden b/test/golden96/{numberCLX}.4609648040604121432.golden index 5fac5c0..622b3c9 100644 --- a/test/golden96/{numberCLX}.4609648040604121432.golden +++ b/test/golden96/{numberCLX}.4609648040604121432.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Integral Float’ arising from a use of ‘PyF.Internal.QQ.formatAnyIntegral’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyIntegral (PyF.Formatters.Upper PyF.Formatters.Hexa) PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing number)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyIntegral (PyF.Formatters.Upper PyF.Formatters.Hexa) PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing number) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyIntegral (PyF.Formatters.Upper PyF.Formatters.Hexa) PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing number) + • No instance for ‘Integral Float’ arising from a use of ‘formatAnyIntegral’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyIntegral (Upper Hexa) Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing number)’ + In the expression: putStrLn (formatAnyIntegral (Upper Hexa) Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing number) + In an equation for ‘main’: main = putStrLn (formatAnyIntegral (Upper Hexa) Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing number) | 7 | main = putStrLn [fmt|{number:X}|] | ^^^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{numberCLb}.8801685868342243288.golden b/test/golden96/{numberCLb}.8801685868342243288.golden index 0b44bf3..69f028c 100644 --- a/test/golden96/{numberCLb}.8801685868342243288.golden +++ b/test/golden96/{numberCLb}.8801685868342243288.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Integral Float’ arising from a use of ‘PyF.Internal.QQ.formatAnyIntegral’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Binary PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing number)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Binary PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing number) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Binary PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing number) + • No instance for ‘Integral Float’ arising from a use of ‘formatAnyIntegral’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyIntegral Binary Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing number)’ + In the expression: putStrLn (formatAnyIntegral Binary Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing number) + In an equation for ‘main’: main = putStrLn (formatAnyIntegral Binary Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing number) | 7 | main = putStrLn [fmt|{number:b}|] | ^^^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{numberCLd}.13336740346716692056.golden b/test/golden96/{numberCLd}.13336740346716692056.golden index 2a8ef51..462b9b8 100644 --- a/test/golden96/{numberCLd}.13336740346716692056.golden +++ b/test/golden96/{numberCLd}.13336740346716692056.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Integral Float’ arising from a use of ‘PyF.Internal.QQ.formatAnyIntegral’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Decimal PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing number)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Decimal PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing number) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Decimal PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing number) + • No instance for ‘Integral Float’ arising from a use of ‘formatAnyIntegral’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyIntegral Decimal Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing number)’ + In the expression: putStrLn (formatAnyIntegral Decimal Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing number) + In an equation for ‘main’: main = putStrLn (formatAnyIntegral Decimal Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing number) | 7 | main = putStrLn [fmt|{number:d}|] | ^^^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{numberCLo}.12467189151987896600.golden b/test/golden96/{numberCLo}.12467189151987896600.golden index 50a1d5f..57bd762 100644 --- a/test/golden96/{numberCLo}.12467189151987896600.golden +++ b/test/golden96/{numberCLo}.12467189151987896600.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Integral Float’ arising from a use of ‘PyF.Internal.QQ.formatAnyIntegral’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Octal PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing number)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Octal PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing number) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Octal PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing number) + • No instance for ‘Integral Float’ arising from a use of ‘formatAnyIntegral’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyIntegral Octal Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing number)’ + In the expression: putStrLn (formatAnyIntegral Octal Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing number) + In an equation for ‘main’: main = putStrLn (formatAnyIntegral Octal Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing number) | 7 | main = putStrLn [fmt|{number:o}|] | ^^^^^^^^^^^^ \ No newline at end of file diff --git a/test/golden96/{numberCLx}.14457861675063419224.golden b/test/golden96/{numberCLx}.14457861675063419224.golden index 5f2a288..4f58cc9 100644 --- a/test/golden96/{numberCLx}.14457861675063419224.golden +++ b/test/golden96/{numberCLx}.14457861675063419224.golden @@ -1,8 +1,8 @@ INITIALPATH:7:22: error: [GHC-39999] - • No instance for ‘Integral Float’ arising from a use of ‘PyF.Internal.QQ.formatAnyIntegral’ - • In the first argument of ‘putStrLn’, namely ‘(PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Hexa PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing number)’ - In the expression: putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Hexa PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing number) - In an equation for ‘main’: main = putStrLn (PyF.Internal.QQ.formatAnyIntegral PyF.Formatters.Hexa PyF.Formatters.Minus (Nothing :: Maybe (Int, PyF.Formatters.AnyAlign, Char)) Nothing number) + • No instance for ‘Integral Float’ arising from a use of ‘formatAnyIntegral’ + • In the first argument of ‘putStrLn’, namely ‘(formatAnyIntegral Hexa Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing number)’ + In the expression: putStrLn (formatAnyIntegral Hexa Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing number) + In an equation for ‘main’: main = putStrLn (formatAnyIntegral Hexa Minus (Nothing :: Maybe (Int, AnyAlign, Char)) Nothing number) | 7 | main = putStrLn [fmt|{number:x}|] | ^^^^^^^^^^^^ \ No newline at end of file