Skip to content

Commit

Permalink
Removed depecated functions
Browse files Browse the repository at this point in the history
  • Loading branch information
mmhat committed Jun 5, 2024
1 parent 3a2b4dc commit af350b1
Show file tree
Hide file tree
Showing 2 changed files with 4 additions and 12 deletions.
5 changes: 1 addition & 4 deletions dhall/tests/Dhall/Test/Freeze.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}

-- FIXME: Re-enable deprecation warnings after removing support for turtle < 1.6.
{-# OPTIONS_GHC -Wno-deprecations #-}

module Dhall.Test.Freeze where

import Data.Text (Text)
Expand Down Expand Up @@ -53,7 +50,7 @@ freezeTest dir intent prefix =

parsedInput <- Core.throws (Parser.exprFromText mempty inputText)

actualExpression <- Freeze.freezeExpression (Turtle.encodeString dir) AllImports intent parsedInput
actualExpression <- Freeze.freezeExpression dir AllImports intent parsedInput

let actualText = Core.pretty actualExpression <> "\n"

Expand Down
11 changes: 3 additions & 8 deletions dhall/tests/Dhall/Test/Import.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,18 +2,13 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}

-- FIXME: Re-enable deprecation warnings after removing support for turtle < 1.6.
{-# OPTIONS_GHC -Wno-deprecations #-}

module Dhall.Test.Import where

import Control.Exception (SomeException)
import Data.Foldable (fold)
import Data.Text (Text, isSuffixOf)
import Data.Void (Void)
import Prelude hiding (FilePath)
import System.FilePath ((</>))
import Test.Tasty (TestTree)
import Turtle (FilePath, toText, (</>))

import qualified Control.Exception as Exception
import qualified Control.Monad as Monad
Expand Down Expand Up @@ -102,7 +97,7 @@ getTests = do
]

_ <- Monad.guard (path `notElem` expectedSuccesses)
_ <- Monad.guard (not ("ENV.dhall" `isSuffixOf` (fold (toText path))))
_ <- Monad.guard (not ("ENV.dhall" `isSuffixOf` Text.pack path))
return path )

let testTree =
Expand Down Expand Up @@ -176,7 +171,7 @@ successTest prefix = do
not (null (Turtle.match (Turtle.ends path') (Test.Util.toDhallPath prefix)))

let buildNewCache = do
tempdir <- fmap Turtle.decodeString (Turtle.managed (Temp.withSystemTempDirectory "dhall-cache"))
tempdir <- Turtle.managed (Temp.withSystemTempDirectory "dhall-cache")
Turtle.liftIO (Turtle.cptree originalCache tempdir)
return tempdir

Expand Down

0 comments on commit af350b1

Please sign in to comment.