Skip to content

Commit

Permalink
what the hell
Browse files Browse the repository at this point in the history
  • Loading branch information
bristermitten committed Sep 9, 2024
1 parent 256193e commit cc26e52
Show file tree
Hide file tree
Showing 3 changed files with 15 additions and 15 deletions.
12 changes: 6 additions & 6 deletions flake.lock

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE TypeFamilies #-}

module Templatespiler.ToLang.Target where

Expand Down
16 changes: 8 additions & 8 deletions templatespiler-converter/test/Main.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,11 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PackageImports #-}

module Main where

import Control.Monad.Morph (hoist)
import Control.Monad.Trans.Resource
import Data.List (intersperse)
import Data.Text.IO qualified as Text
import Hedgehog (Property, evalEither, evalMaybe, forAll, property)
import Hedgehog.Internal.Property (failWith)
Expand All @@ -22,9 +24,12 @@ import Test.Syd
import Test.Syd.Hedgehog ()
import Text.Trifecta
import "temporary-resourcet" System.IO.Temp qualified as TempResourceT
import System.Environment (getEnv)

main :: IO ()
main = sydTest spec
main = do
getEnv "PATH" >>= putStrLn
sydTest spec

spec :: Spec
spec = describe "Integration Test" $ do
Expand Down Expand Up @@ -62,7 +67,7 @@ withCompiled lang code = do
compiledFile <- case lang of
Python -> pure sourceFp
C -> do
liftIO $ callProcess "cc" [sourceFp, "-o", fp </> "a.out"]
liftIO $ callProcess "gcc" [sourceFp, "-o", fp </> "a.out"]
pure $ fp <> "/a.out"

let (cmdToRun, argsToRun) = case lang of
Expand All @@ -73,12 +78,7 @@ withCompiled lang code = do

runProcessWithStdin :: Text -> [Text] -> [Text] -> IO ()
runProcessWithStdin processName args input = do
let inputText = unlines input
(Just hin, Just hout, _, _) <- createProcess (proc "sh" (["-c", toString processName] ++ map toString args)) {std_in = CreatePipe, std_out = CreatePipe}
Text.hPutStrLn hin inputText
hFlush hin
-- assert that the process exits successfully with no output
output <- Text.hGetContents hout
output <- readProcess (toString processName) (toString <$> args) (toString $ unlines input)
output `shouldBe` ""

parseTemplate :: Text -> Either Text BindingList
Expand Down

0 comments on commit cc26e52

Please sign in to comment.