Skip to content

Commit

Permalink
feat: use variant
Browse files Browse the repository at this point in the history
  • Loading branch information
srghma committed Oct 6, 2024
1 parent 8c41955 commit 1aee57e
Show file tree
Hide file tree
Showing 7 changed files with 138 additions and 48 deletions.
38 changes: 38 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,37 @@ Notable changes to this project are documented in this file. The format is based

Breaking changes:

- `Pathy.Gen`
- replaced methods
- genAbsAnyPath -> genAbsAnyPathVariant
- genRelAnyPath -> genRelAnyPathVariant
- added methods
- genAnyDirPathVariant
- genAnyFilePathVariant
- genAnyAnyPathVariant
- `Pathy.Parser`
- replaced methods
- parseAnyDir -> parseAnyDirPathVariant
- parseAnyFile -> parseAnyFilePathVariant
- parseAbsPath -> parseAbsAnyPathVariant
- parseRelPath -> parseRelAnyPathVariant
- added methods
- parseAnyAnyPathVariant
- `Pathy.Path`
- replaced
- RelPath -> RelAnyPathVariant
- AbsPath -> AbsAnyPathVariant
- AnyDir -> AnyDirPathVariant
- AnyFile -> AnyFilePathVariant
- deleted
- `type AnyPath a = Either (Path a Dir) (Path a File)` (no analog, but `AnyPath Rel == RelAnyPathVariant`, `AnyPath Abs == AbsAnyPathVariant`)
- added
- AnyAnyPathVariant
- proxyRelDir
- proxyAbsDir
- proxyRelFile
- proxyAbsFile

New features:

Bugfixes:
Expand All @@ -15,35 +46,42 @@ Other improvements:
## [v9.0.0](https://github.com/purescript-contrib/purescript-pathy/releases/tag/v9.0.0) - 2022-04-27

Breaking changes:

- Update project and deps to PureScript v0.15.0 (#50 by @JordanMartinez)

New features:

Bugfixes:

Other improvements:

- Added `purs-tidy` formatter (#49 by @thomashoneyman)

## [v8.1.0](https://github.com/purescript-contrib/purescript-pathy/releases/tag/v8.1.0) - 2021-05-06

New features:

- Exported `escape` implemented by @safareli in #33 (#46 by @JordanMartinez)

Other improvements:

- Fixed warnings revealed by v0.14.1 PS release (#46 by @JordanMartinez)
- Installed missing dependencies used in source code (#46 by @JordanMartinez)

## [v8.0.0](https://github.com/purescript-contrib/purescript-pathy/releases/tag/v8.0.0) - 2021-02-26

Breaking changes:

- Added support for PureScript 0.14 and dropped support for all previous versions (#42)

New features:

- Added roles declarations to forbid unsafe coercions (#43)

Bugfixes:

Other improvements:

- Changed default branch to `main` from `master`
- Updated to comply with Contributors library guidelines by adding new issue and pull request templates, updating documentation, and migrating to Spago for local development and CI (#41)

Expand Down
22 changes: 20 additions & 2 deletions spago.lock
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,8 @@
"tailrec",
"tuples",
"typelevel-prelude",
"unsafe-coerce"
"unsafe-coerce",
"variant"
],
"build_plan": [
"arrays",
Expand Down Expand Up @@ -50,6 +51,7 @@
"partial",
"prelude",
"profunctor",
"record",
"refs",
"safe-coerce",
"st",
Expand All @@ -59,7 +61,8 @@
"type-equality",
"typelevel-prelude",
"unfoldable",
"unsafe-coerce"
"unsafe-coerce",
"variant"
]
},
"test": {
Expand Down Expand Up @@ -1171,6 +1174,21 @@
"version": "6.0.0",
"integrity": "sha256-IqIYW4Vkevn8sI+6aUwRGvd87tVL36BBeOr0cGAE7t0=",
"dependencies": []
},
"variant": {
"type": "registry",
"version": "8.0.0",
"integrity": "sha256-SR//zQDg2dnbB8ZHslcxieUkCeNlbMToapvmh9onTtw=",
"dependencies": [
"enums",
"lists",
"maybe",
"partial",
"prelude",
"record",
"tuples",
"unsafe-coerce"
]
}
}
}
1 change: 1 addition & 0 deletions spago.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ package:
- tuples
- typelevel-prelude
- unsafe-coerce
- variant
test:
main: Test.Main
dependencies:
Expand Down
4 changes: 2 additions & 2 deletions src/Pathy.purs
Original file line number Diff line number Diff line change
Expand Up @@ -7,9 +7,9 @@ module Pathy
, module Pathy.Sandboxed
) where

import Pathy.Path (AbsDir, AbsFile, AbsPath, AnyPath, AnyDir, AnyFile, Path, RelDir, RelFile, RelPath, appendPath, currentDir, dir, dir', extendPath, file, file', in', fileName, foldPath, name, parentAppend, parentOf, peel, peelFile, refine, relativeTo, rename, renameTraverse, rootDir, setExtension, (<..>), (<.>), (</>))
import Pathy.Path (AbsAnyPathVariant, AbsDir, AbsFile, AnyAnyPathVariant, AnyDirPathVariant, AnyFilePathVariant, Path, RelAnyPathVariant, RelDir, RelFile, appendPath, currentDir, dir, dir', extendPath, file, file', fileName, foldPath, in', name, parentAppend, parentOf, peel, peelFile, proxyAbsDir, proxyAbsFile, proxyRelDir, proxyRelFile, refine, relativeTo, rename, renameTraverse, rootDir, setExtension, (<..>), (<.>), (</>))
import Pathy.Name (Name(..), joinName, splitName, alterExtension, extension)
import Pathy.Printer (Escaper(..), Printer, debugPrintPath, posixPrinter, printPath, unsafePrintPath, windowsPrinter)
import Pathy.Parser (Parser(..), posixParser, parsePath, parseRelFile, parseAbsFile, parseRelDir, parseAbsDir, parseAnyDir, parseAnyFile, parseAbsPath, parseRelPath)
import Pathy.Parser (Parser(..), parseAbsAnyPathVariant, parseAbsDir, parseAbsFile, parseAnyAnyPathVariant, parseAnyDirPathVariant, parseAnyFilePathVariant, parsePath, parseRelAnyPathVariant, parseRelDir, parseRelFile, posixParser)
import Pathy.Phantom (class IsDirOrFile, class IsRelOrAbs, Abs, Dir, File, Rel, foldRelOrAbs, onRelOrAbs, foldDirOrFile, onDirOrFile)
import Pathy.Sandboxed (SandboxedPath, sandbox, sandboxAny, sandboxRoot, unsandbox)
36 changes: 27 additions & 9 deletions src/Pathy/Gen.purs
Original file line number Diff line number Diff line change
@@ -1,28 +1,32 @@
module Pathy.Gen
( genAbsDirPath
, genAbsFilePath
, genAbsAnyPath
, genRelDirPath
, genRelFilePath
, genRelAnyPath
, genAnyDirPathVariant
, genAnyFilePathVariant
, genAbsAnyPathVariant
, genRelAnyPathVariant
, genAnyAnyPathVariant
, genName
, genDirName
, genFileName
) where

import Pathy.Path (AbsAnyPathVariant, AbsDir, AbsFile, AnyAnyPathVariant, AnyDirPathVariant, AnyFilePathVariant, RelAnyPathVariant, RelDir, RelFile, proxyAbsDir, proxyAbsFile, proxyRelDir, proxyRelFile, (</>))
import Pathy.Phantom (Dir, File)
import Prelude

import Control.Monad.Gen (class MonadGen)
import Control.Monad.Gen as Gen
import Control.Monad.Rec.Class (class MonadRec)
import Data.Char.Gen as CG
import Data.Either (Either(..))
import Data.Foldable (foldr)
import Data.List as L
import Data.NonEmpty ((:|))
import Data.String.Gen as SG
import Data.String.NonEmpty.CodeUnits (cons)
import Pathy (AbsDir, AbsFile, AbsPath, Dir, File, RelDir, RelFile, RelPath, (</>))
import Data.Variant (inj)
import Pathy as P

genName :: forall m a. MonadGen m => MonadRec m => m (P.Name a)
Expand All @@ -49,9 +53,6 @@ genAbsFilePath = do
file <- genName
pure $ dir </> P.file' file

genAbsAnyPath :: forall m. MonadGen m => MonadRec m => m AbsPath
genAbsAnyPath = Gen.oneOf $ (Left <$> genAbsDirPath) :| [ Right <$> genAbsFilePath ]

genRelDirPath :: forall m. MonadGen m => MonadRec m => m RelDir
genRelDirPath = Gen.sized \size -> do
newSize <- Gen.chooseInt 0 size
Expand All @@ -65,5 +66,22 @@ genRelFilePath = do
file <- genName
pure $ dir </> P.file' file

genRelAnyPath :: forall m. MonadGen m => MonadRec m => m RelPath
genRelAnyPath = Gen.oneOf $ (Left <$> genRelDirPath) :| [ Right <$> genRelFilePath ]
genAnyDirPathVariant :: forall m. MonadGen m => MonadRec m => m AnyDirPathVariant
genAnyDirPathVariant = Gen.oneOf $ (inj proxyRelDir <$> genRelDirPath) :| [ inj proxyAbsDir <$> genAbsDirPath ]

genAnyFilePathVariant :: forall m. MonadGen m => MonadRec m => m AnyFilePathVariant
genAnyFilePathVariant = Gen.oneOf $ (inj proxyRelFile <$> genRelFilePath) :| [ inj proxyAbsFile <$> genAbsFilePath ]

genRelAnyPathVariant :: forall m. MonadGen m => MonadRec m => m RelAnyPathVariant
genRelAnyPathVariant = Gen.oneOf $ (inj proxyRelDir <$> genRelDirPath) :| [ inj proxyRelFile <$> genRelFilePath ]

genAbsAnyPathVariant :: forall m. MonadGen m => MonadRec m => m AbsAnyPathVariant
genAbsAnyPathVariant = Gen.oneOf $ (inj proxyAbsDir <$> genAbsDirPath) :| [ inj proxyAbsFile <$> genAbsFilePath ]

genAnyAnyPathVariant :: forall m. MonadGen m => MonadRec m => m AnyAnyPathVariant
genAnyAnyPathVariant = Gen.oneOf $
( inj proxyRelDir <$> genRelDirPath ) :|
[ inj proxyAbsDir <$> genAbsDirPath
, inj proxyRelFile <$> genRelFilePath
, inj proxyAbsFile <$> genAbsFilePath
]
36 changes: 21 additions & 15 deletions src/Pathy/Parser.purs
Original file line number Diff line number Diff line change
Expand Up @@ -6,12 +6,14 @@ module Pathy.Parser
, parseAbsFile
, parseRelDir
, parseAbsDir
, parseAnyDir
, parseAnyFile
, parseAbsPath
, parseRelPath
, parseAnyDirPathVariant
, parseAnyFilePathVariant
, parseRelAnyPathVariant
, parseAbsAnyPathVariant
, parseAnyAnyPathVariant
) where

import Pathy.Path (AbsAnyPathVariant, AbsDir, AbsFile, AnyAnyPathVariant, AnyDirPathVariant, AnyFilePathVariant, Path, RelAnyPathVariant, RelDir, RelFile, currentDir, extendPath, parentOf, proxyAbsDir, proxyAbsFile, proxyRelDir, proxyRelFile, rootDir)
import Prelude

import Data.Array (foldl)
Expand All @@ -25,8 +27,8 @@ import Data.String.CodeUnits (take, takeRight) as S
import Data.String.NonEmpty (NonEmptyString)
import Data.String.NonEmpty as NES
import Data.String.Pattern (Pattern(..)) as S
import Data.Variant (inj)
import Pathy.Name (Name(..))
import Pathy.Path (AbsDir, AbsFile, AnyDir, AnyFile, Path, RelDir, RelFile, RelPath, AbsPath, currentDir, extendPath, parentOf, rootDir)
import Pathy.Phantom (class IsRelOrAbs, Dir)

newtype Parser = Parser
Expand Down Expand Up @@ -117,17 +119,21 @@ parseAbsDir :: Parser -> String -> Maybe AbsDir
parseAbsDir p = parsePath p (const Nothing) Just (const Nothing) (const Nothing) Nothing

-- | Attempts to parse an absolute or relative directory.
parseAnyDir :: Parser -> String -> Maybe AnyDir
parseAnyDir p = parsePath p (Just <<< Right) (Just <<< Left) (const Nothing) (const Nothing) Nothing
parseAnyDirPathVariant :: Parser -> String -> Maybe AnyDirPathVariant
parseAnyDirPathVariant p = parsePath p (Just <<< inj proxyRelDir) (Just <<< inj proxyAbsDir) (const Nothing) (const Nothing) Nothing

-- | Attempts to parse an absolute or relative directory.
parseAnyFile :: Parser -> String -> Maybe AnyFile
parseAnyFile p = parsePath p (const Nothing) (const Nothing) (Just <<< Right) (Just <<< Left) Nothing
-- | Attempts to parse an absolute or relative file.
parseAnyFilePathVariant :: Parser -> String -> Maybe AnyFilePathVariant
parseAnyFilePathVariant p = parsePath p (const Nothing) (const Nothing) (Just <<< inj proxyRelFile) (Just <<< inj proxyAbsFile) Nothing

-- | Attempts to parse an relative directory or file.
parseRelPath :: Parser -> String -> Maybe RelPath
parseRelPath p = parsePath p (Just <<< Left) (const Nothing) (Just <<< Right) (const Nothing) Nothing
-- | Attempts to parse a relative directory or file.
parseRelAnyPathVariant :: Parser -> String -> Maybe RelAnyPathVariant
parseRelAnyPathVariant p = parsePath p (Just <<< inj proxyRelDir) (const Nothing) (Just <<< inj proxyRelFile) (const Nothing) Nothing

-- | Attempts to parse an absolute directory or file.
parseAbsPath :: Parser -> String -> Maybe AbsPath
parseAbsPath p = parsePath p (const Nothing) (Just <<< Left) (const Nothing) (Just <<< Right) Nothing
parseAbsAnyPathVariant :: Parser -> String -> Maybe AbsAnyPathVariant
parseAbsAnyPathVariant p = parsePath p (const Nothing) (Just <<< inj proxyAbsDir) (const Nothing) (Just <<< inj proxyAbsFile) Nothing

-- | Attempts to parse an absolute or relative directory or file.
parseAnyAnyPathVariant :: Parser -> String -> Maybe AnyAnyPathVariant
parseAnyAnyPathVariant p = parsePath p (Just <<< inj proxyRelDir) (Just <<< inj proxyAbsDir) (Just <<< inj proxyRelFile) (Just <<< inj proxyAbsFile) Nothing
49 changes: 29 additions & 20 deletions src/Pathy/Path.purs
Original file line number Diff line number Diff line change
@@ -1,14 +1,18 @@
module Pathy.Path
( Path
, AnyPath
, RelPath
, AbsPath
, proxyRelDir
, proxyAbsDir
, proxyRelFile
, proxyAbsFile
, RelDir
, AbsDir
, AnyDir
, RelFile
, AbsFile
, AnyFile
, AnyDirPathVariant
, AnyFilePathVariant
, RelAnyPathVariant
, AbsAnyPathVariant
, AnyAnyPathVariant
, rootDir
, currentDir
, dir
Expand Down Expand Up @@ -37,15 +41,16 @@ module Pathy.Path

import Prelude

import Data.Either (Either)
import Data.Identity (Identity(..))
import Data.Maybe (Maybe(..), maybe)
import Data.Newtype (un)
import Data.String.NonEmpty as NES
import Data.Tuple (Tuple(..), fst, snd)
import Data.Variant (Variant)
import Partial.Unsafe (unsafeCrashWith)
import Pathy.Name (class IsName, Name(..), alterExtension, reflectName)
import Pathy.Phantom (class IsDirOrFile, class IsRelOrAbs, Abs, Dir, File, Rel, foldDirOrFile, foldRelOrAbs, onDirOrFile, onRelOrAbs, DirOrFile, RelOrAbs)
import Type.Prelude (Proxy(..))
import Unsafe.Coerce (unsafeCoerce)

-- | A type that describes a Path. All flavors of paths are described by this
Expand Down Expand Up @@ -77,34 +82,38 @@ instance showPathRelDir :: (IsRelOrAbs a, IsDirOrFile b) => Show (Path a b) wher
show (ParentOf p) = "(parentOf " <> show p <> ")"
show (In p n) = "(" <> show p <> " </> " <> foldDirOrFile (("dir " <> _) <<< show) (("file " <> _) <<< show) n <> ")"

-- | A type describing a file or directory path.
type AnyPath a = Either (Path a Dir) (Path a File)

-- | A type describing a relative file or directory path.
type RelPath = AnyPath Rel

-- | A type describing an absolute file or directory path.
type AbsPath = AnyPath Abs

-- | A type describing a directory whose location is given relative to some
-- | other, unspecified directory (referred to as the "current directory").
type RelDir = Path Rel Dir

-- | A type describing a directory whose location is absolutely specified.
type AbsDir = Path Abs Dir

-- | A type describing a absolute or relative directory path.
type AnyDir = Either AbsDir RelDir

-- | A type describing a file whose location is given relative to some other,
-- | unspecified directory (referred to as the "current directory").
type RelFile = Path Rel File

-- | A type describing a file whose location is absolutely specified.
type AbsFile = Path Abs File

-- | A type describing a absolute or relative file path.
type AnyFile = Either AbsFile RelFile
-- Proxy functions for different path types
proxyRelDir :: Proxy "relDir"
proxyRelDir = Proxy

proxyAbsDir :: Proxy "absDir"
proxyAbsDir = Proxy

proxyRelFile :: Proxy "relFile"
proxyRelFile = Proxy

proxyAbsFile :: Proxy "absFile"
proxyAbsFile = Proxy

type AnyDirPathVariant = Variant (relDir :: RelDir, absDir :: AbsDir)
type AnyFilePathVariant = Variant (relFile :: RelFile, absFile :: AbsFile)
type RelAnyPathVariant = Variant (relDir :: RelDir, relFile :: RelFile)
type AbsAnyPathVariant = Variant (absDir :: AbsDir, absFile :: AbsFile)
type AnyAnyPathVariant = Variant (relDir :: RelDir, absDir :: AbsDir, relFile :: RelFile, absFile :: AbsFile)

-- | The root directory, which can be used to define absolutely-located resources.
rootDir :: Path Abs Dir
Expand Down

0 comments on commit 1aee57e

Please sign in to comment.