Skip to content

Commit

Permalink
fix(eo-phi-normalizer): use / independently of the platform
Browse files Browse the repository at this point in the history
  • Loading branch information
deemp committed Dec 28, 2024
1 parent 4e2e9d6 commit 7cf0e3c
Showing 1 changed file with 10 additions and 8 deletions.
18 changes: 10 additions & 8 deletions eo-phi-normalizer/src/Language/EO/Phi/Pipeline/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,7 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
Expand All @@ -47,7 +48,7 @@ import Data.Yaml (decodeFileThrow)
import GHC.Generics (Generic)
import Language.EO.Phi.Metrics.Data
import Language.EO.Phi.TH (deriveJSON)
import System.FilePath ((<.>), (</>))
import PyF (fmt)
import Text.Printf (printf)

data TestSetPhi = TestSetPhi
Expand Down Expand Up @@ -231,25 +232,26 @@ toExtended c@(PipelineConfig{testSets}) = c{testSets = concatMap go testSets}

go1 (Common{..}) (Individual{..}) = TestSetExtended{..}
where
mkPath :: FilePath -> String -> String
mkPath prefix extension = [fmt|{prefix}/{name}.{extension}|]
eo =
TestSetEO
{ original = pathPrefix.eo.original </> name <.> "eo"
, yaml = pathPrefix.eo.yaml </> name <.> "yaml"
, filtered = pathPrefix.eo.filtered </> name <.> "eo"
{ original = mkPath pathPrefix.eo.original "eo"
, yaml = mkPath pathPrefix.eo.yaml "yaml"
, filtered = mkPath pathPrefix.eo.filtered "eo"
, include
, exclude
}
phi =
TestSetPhi
{ initial = pathPrefix.phi.initial </> name <.> "phi"
, normalized = pathPrefix.phi.normalized </> name <.> "phi"
{ initial = mkPath pathPrefix.phi.initial "phi"
, normalized = mkPath pathPrefix.phi.normalized "phi"
, bindingsPathInitial = bindingsPath <&> mkBindingsPathSuffix
, bindingsPathNormalized = bindingsPath <&> mkBindingsPathSuffix
}
where
name' = split (== '/') name
mkBindingsPathSuffix x =
x <> intercalate "." (if name' /= [] then init name' else [])
mkBindingsPathSuffix x = x <> intercalate "." (if name' /= [] then init name' else [])

readPipelineConfig :: (MonadIO m) => FilePath -> m PipelineConfig
readPipelineConfig path = toExtended <$> decodeFileThrow @_ @PipelineConfig path

0 comments on commit 7cf0e3c

Please sign in to comment.