| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175 | {-# LANGUAGE OverloadedStrings #-}{-# LANGUAGE ScopedTypeVariables #-}module Main whereimport Data.SCargotimport Data.SCargot.Commentsimport Data.SCargot.Reprimport           Data.Monoid ((<>))import           Data.Text (Text)import qualified Data.Text as Timport           Test.QuickCheckimport           Test.QuickCheck.Arbitraryimport           Text.Parsec (char)import           Text.Parsec.Text (Parser)instance Arbitrary a => Arbitrary (SExpr a) where  arbitrary = sized $ \n ->    if n <= 0       then pure SNil       else oneof [ SAtom <$> arbitrary                  , do                      k <- choose (0, n)                      elems <- sequence [ resize (n-k) arbitrary                                        | _ <- [0..k]                                        ]                      tail <- oneof [ SAtom <$> arbitrary                                    , pure SNil                                    ]                      pure (foldr SCons tail elems)                  ]instance Arbitrary a => Arbitrary (RichSExpr a) where  arbitrary = toRich `fmap` arbitraryinstance Arbitrary a => Arbitrary (WellFormedSExpr a) where  arbitrary = sized $ \n ->    oneof [ WFSAtom <$> arbitrary          , do              k <- choose (0, n)              WFSList <$> sequence                [ resize (n-k) arbitrary                | _ <- [0..k]                ]          ]data EncodedSExpr = EncodedSExpr  { encoding :: Text  , original :: SExpr ()  } deriving (Eq, Show)instance Arbitrary EncodedSExpr where  arbitrary = do    sexpr :: SExpr () <- arbitrary    let chunks = T.words (encodeOne printer sexpr)    whitespace <- sequence [ mkWs | _ <- chunks ]    pure (EncodedSExpr { encoding = T.concat (zipWith (<>) chunks whitespace)                       , original = sexpr                       })    where mkWs = do            n :: Int <- choose (1, 10)            T.pack <$> sequence [ elements " \t\r\n"                                | _ <- [0..n]                                ]parser :: SExprParser () (SExpr ())parser = mkParser (() <$ char 'X')printer :: SExprPrinter () (SExpr ())printer = flatPrint (const "X")prettyPrinter :: SExprPrinter () (SExpr ())prettyPrinter = basicPrint (const "X")richIso :: SExpr () -> BoolrichIso s = fromRich (toRich s) == srichIsoBk :: RichSExpr () -> BoolrichIsoBk s = toRich (fromRich s) == swfIso :: SExpr () -> BoolwfIso s = case toWellFormed s of  Left _  -> True  Right y -> s == fromWellFormed ywfIsoBk :: WellFormedSExpr () -> BoolwfIsoBk s = toWellFormed (fromWellFormed s) == Right sencDec :: SExpr () -> BoolencDec s = decodeOne parser (encodeOne printer s) == Right sencDecPretty :: SExpr () -> BoolencDecPretty s = decodeOne parser (encodeOne prettyPrinter s) == Right sdecEnc :: EncodedSExpr -> BooldecEnc s = decodeOne parser (encoding s) == Right (original s)encDecRich :: RichSExpr () -> BoolencDecRich s = decodeOne (asRich parser) (encodeOne printer (fromRich s))                == Right sencDecRichPretty :: RichSExpr () -> BoolencDecRichPretty s = decodeOne (asRich parser)                               (encodeOne prettyPrinter (fromRich s))                       == Right sdecEncRich :: EncodedSExpr -> BooldecEncRich s = decodeOne (asRich parser) (encoding s) == Right (toRich (original s))encDecWF :: WellFormedSExpr () -> BoolencDecWF s = decodeOne (asWellFormed parser) (encodeOne printer (fromWellFormed s))               == Right sencDecWFPretty :: WellFormedSExpr () -> BoolencDecWFPretty s =  decodeOne (asWellFormed parser) (encodeOne prettyPrinter (fromWellFormed s))    == Right sdecEncWF :: EncodedSExpr -> BooldecEncWF s = decodeOne (asWellFormed parser) (encoding s) == toWellFormed (original s)insertComments :: Text -> Text -> Text -> TextinsertComments lc rc sexpr =  T.replace " " (" " <> lc <> "blahblahblah" <> rc <> " ") sexprencDecLineComments :: SExpr () -> BoolencDecLineComments s =  decodeOne (withLispComments parser)            (insertComments ";" "\n" (encodeOne printer s)) == Right sencDecBlockComments :: SExpr () -> BoolencDecBlockComments s =  decodeOne (withHaskellBlockComments parser)            (insertComments "{-" "-}" (encodeOne printer s)) == Right s-- Sometimes we generate really huge test cases, which can take a really-- long time to process---especially when we're modifying the whitespace-- to produce weird anomalous S-expressions. So, we make the size parameter-- a bit smaller for good measure.reallyQuickCheck :: Testable prop => prop -> IO ()reallyQuickCheck = quickCheckWith stdArgs { maxSize = 25 }main :: IO ()main = do  putStrLn "The SExpr <--> Rich translation should be isomorphic"  quickCheck richIso  quickCheck richIsoBk  putStrLn "The SExpr <--> WF translation should be near-isomorphic"  quickCheck wfIso  quickCheck wfIsoBk  putStrLn "This should be true when parsing, as well"  quickCheck encDec  reallyQuickCheck decEnc  quickCheck encDecRich  reallyQuickCheck decEncRich  quickCheck encDecWF  reallyQuickCheck decEncWF  putStrLn "And it should be true if pretty-printed"  reallyQuickCheck encDecPretty  reallyQuickCheck encDecRichPretty  reallyQuickCheck encDecWFPretty  putStrLn "Comments should not affect parsing"  reallyQuickCheck encDecLineComments  reallyQuickCheck encDecBlockComments
 |