Skip to content

Commit

Permalink
Update to v0.14.0-rc3 (#42)
Browse files Browse the repository at this point in the history
* Update packages.dhall to prepare-0.14 bootstrap

* Update CI to use v0.14.0-rc3 PS release

* Fix usage of SProxy to proxy or Proxy

* Use updated kind syntax in definitionand imports

* Add kind signatures to types and classes
  • Loading branch information
JordanMartinez authored Dec 4, 2020
1 parent 27e4739 commit 4d1133f
Show file tree
Hide file tree
Showing 6 changed files with 46 additions and 39 deletions.
2 changes: 2 additions & 0 deletions .github/workflows/ci.yml
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,8 @@ jobs:

- name: Set up a PureScript toolchain
uses: purescript-contrib/setup-purescript@main
with:
purescript: "0.14.0-rc3"

- name: Cache PureScript dependencies
uses: actions/cache@v2
Expand Down
2 changes: 1 addition & 1 deletion packages.dhall
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
let upstream =
https://github.com/purescript/package-sets/releases/download/psc-0.13.8-20200922/packages.dhall sha256:5edc9af74593eab8834d7e324e5868a3d258bbab75c5531d2eb770d4324a2900
https://raw.githubusercontent.com/purescript/package-sets/prepare-0.14/src/packages.dhall

in upstream
13 changes: 8 additions & 5 deletions src/Pathy/Name.purs
Original file line number Diff line number Diff line change
Expand Up @@ -7,15 +7,17 @@ import Data.Newtype (class Newtype)
import Data.String as S
import Data.String.NonEmpty (NonEmptyString)
import Data.String.NonEmpty.CodeUnits as NES
import Data.Symbol (class IsSymbol, SProxy(..))
import Data.Symbol (class IsSymbol)
import Data.Symbol (reflectSymbol) as Symbol
import Pathy.Phantom (kind DirOrFile)
import Pathy.Phantom (DirOrFile)
import Type.Data.Boolean (False) as Symbol
import Type.Data.Symbol (class Equals) as Symbol
import Type.Proxy (Proxy(..))
import Unsafe.Coerce (unsafeCoerce)

-- | A type used for both directory and file names, indexed by `DirOrFile`.
newtype Name (n :: DirOrFile) = Name NonEmptyString
newtype Name :: DirOrFile -> Type
newtype Name n = Name NonEmptyString

derive instance newtypeName :: Newtype (Name n) _
derive newtype instance eqName :: Eq (Name a)
Expand Down Expand Up @@ -92,11 +94,12 @@ alterExtension f n =

-- | A class for creating `Name` values from type-level strings. This allows us
-- | to guarantee that a name is not empty at compile-time.
class IsName :: Symbol -> Constraint
class IsName sym where
reflectName :: forall d. SProxy sym -> Name d
reflectName :: forall proxy d. proxy sym -> Name d

instance isNameNESymbol :: (IsSymbol s, Symbol.Equals s "" Symbol.False) => IsName s where
reflectName _ = asNonEmpty $ Symbol.reflectSymbol (SProxy :: SProxy s)
reflectName _ = asNonEmpty $ Symbol.reflectSymbol (Proxy :: Proxy s)
where
asNonEmpty :: forall d. String -> Name d
asNonEmpty = unsafeCoerce
10 changes: 5 additions & 5 deletions src/Pathy/Path.purs
Original file line number Diff line number Diff line change
Expand Up @@ -39,11 +39,10 @@ import Data.Identity (Identity(..))
import Data.Maybe (Maybe(..), maybe)
import Data.Newtype (un)
import Data.String.NonEmpty as NES
import Data.Symbol (SProxy)
import Data.Tuple (Tuple(..), fst, snd)
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, kind DirOrFile, kind RelOrAbs)
import Pathy.Phantom (class IsDirOrFile, class IsRelOrAbs, Abs, Dir, File, Rel, foldDirOrFile, foldRelOrAbs, onDirOrFile, onRelOrAbs, DirOrFile, RelOrAbs)
import Unsafe.Coerce (unsafeCoerce)

-- | A type that describes a Path. All flavors of paths are described by this
Expand All @@ -59,7 +58,8 @@ import Unsafe.Coerce (unsafeCoerce)
-- |
-- | This ADT allows invalid paths (e.g. paths inside files), but there is no
-- | possible way for such paths to be constructed by user-land code.
data Path (a :: RelOrAbs) (b :: DirOrFile)
data Path :: RelOrAbs -> DirOrFile -> Type
data Path a b
= Init
| ParentOf (Path Rel Dir)
| In (Path a Dir) (Name b)
Expand Down Expand Up @@ -114,7 +114,7 @@ currentDir = Init
-- |
-- | Instead of accepting a runtime value, this function accepts a type-level
-- | string via a proxy, to ensure the constructed name is not empty.
file :: forall s. IsName s => SProxy s -> Path Rel File
file :: forall s proxy. IsName s => proxy s -> Path Rel File
file = file' <<< reflectName

-- | Creates a path which points to a relative file of the specified name.
Expand All @@ -125,7 +125,7 @@ file' = in'
-- |
-- | Instead of accepting a runtime value, this function accepts a type-level
-- | string via a proxy, to ensure the constructed name is not empty.
dir :: forall s. IsName s => SProxy s -> Path Rel Dir
dir :: forall s proxy. IsName s => proxy s -> Path Rel Dir
dir = dir' <<< reflectName

-- | Creates a path which points to a relative directory of the specified name.
Expand Down
12 changes: 7 additions & 5 deletions src/Pathy/Phantom.purs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module Pathy.Phantom where
import Prelude

-- | The kind for the relative/absolute phantom type.
foreign import kind RelOrAbs
data RelOrAbs

-- | The phantom type of relative paths.
foreign import data Rel :: RelOrAbs
Expand All @@ -16,9 +16,10 @@ foreign import data Abs :: RelOrAbs
-- | The provided `onRelOrAbs` function folds over a value indexed by
-- | `RelOrAbs` to produce a new result, passing proof/coercion functions to
-- | allow the inner functions to unify their return types if remapping.
class IsRelOrAbs (a :: RelOrAbs) where
class IsRelOrAbs :: RelOrAbs -> Constraint
class IsRelOrAbs a where
onRelOrAbs
:: forall f b r
:: forall (f :: RelOrAbs -> DirOrFile -> Type) b r
. ((f Rel b -> f a b) -> f Rel b -> r)
-> ((f Abs b -> f a b) -> f Abs b -> r)
-> f a b
Expand All @@ -38,7 +39,7 @@ foldRelOrAbs
foldRelOrAbs f g = onRelOrAbs (const f) (const g)

-- | The kind for the directory/file phantom type.
foreign import kind DirOrFile
data DirOrFile

-- | The phantom type of directories.
foreign import data Dir :: DirOrFile
Expand All @@ -51,7 +52,8 @@ foreign import data File :: DirOrFile
-- | The provided `onDirOrFile` function folds over a value indexed by
-- | `DirOrFile` to produce a new result, passing proof/coercion functions to
-- | allow the inner functions to unify their return types if remapping.
class IsDirOrFile (b :: DirOrFile) where
class IsDirOrFile :: DirOrFile -> Constraint
class IsDirOrFile b where
onDirOrFile
:: forall f r
. ((f Dir -> f b) -> f Dir -> r)
Expand Down
46 changes: 23 additions & 23 deletions test/Main.purs
Original file line number Diff line number Diff line change
Expand Up @@ -9,14 +9,14 @@ import Data.String as Str
import Data.String.NonEmpty (NonEmptyString)
import Data.String.NonEmpty (fromString) as NES
import Data.String.NonEmpty.CodeUnits (singleton) as NES
import Data.Symbol (SProxy(..))
import Data.Tuple (Tuple(..))
import Effect (Effect)
import Effect.Console (info)
import Effect.Exception (throw)
import Pathy (class IsDirOrFile, class IsRelOrAbs, Abs, Dir, Name(..), Path, Rel, alterExtension, currentDir, debugPrintPath, dir, extension, file, in', joinName, parentOf, parseAbsDir, parseAbsFile, parseRelDir, parseRelFile, peel, posixParser, posixPrinter, printPath, relativeTo, rename, rootDir, sandbox, sandboxAny, splitName, unsandbox, windowsPrinter, (<..>), (<.>), (</>))
import Pathy.Gen as PG
import Pathy.Name (reflectName)
import Type.Proxy (Proxy(..))
import Test.QuickCheck ((===))
import Test.QuickCheck as QC
import Test.QuickCheck.Gen as Gen
Expand All @@ -39,13 +39,13 @@ pathPart = asNonEmptyString <$> Gen.suchThat QC.arbitrary (not <<< Str.null)
asNonEmptyString = unsafeCoerce

dirFoo :: Path Rel Dir
dirFoo = dir (SProxy :: SProxy "foo")
dirFoo = dir (Proxy :: Proxy "foo")

dirBar :: Path Rel Dir
dirBar = dir (SProxy :: SProxy "bar")
dirBar = dir (Proxy :: Proxy "bar")

dirBaz :: Path Rel Dir
dirBaz = dir (SProxy :: SProxy "baz")
dirBaz = dir (Proxy :: Proxy "baz")

parsePrintCheck :: forall a b. IsRelOrAbs a => IsDirOrFile b => Path a b -> Maybe (Path a b) -> QC.Result
parsePrintCheck input parsed =
Expand Down Expand Up @@ -155,22 +155,22 @@ main = do
"./foo/bar/"

test "windowsPrinter"
(printWindowsPath $ rootDir </> dir (SProxy :: SProxy "C") </> dirBar)
(printWindowsPath $ rootDir </> dir (Proxy :: Proxy "C") </> dirBar)
"C:\\bar\\"

test' "(</>) - file with two parents"
(dirFoo
</> dirBar
</> file (SProxy :: SProxy "image.png"))
</> file (Proxy :: Proxy "image.png"))
"./foo/bar/image.png"

test' "(<.>) - file without extension"
(file (SProxy :: SProxy "image")
(file (Proxy :: Proxy "image")
<.> "png")
"./image.png"

test' "(<.>) - file with extension"
(file (SProxy :: SProxy "image.jpg")
(file (Proxy :: Proxy "image.jpg")
<.> "png")
"./image.png"

Expand All @@ -179,11 +179,11 @@ main = do
"./../"

test """printPath windowsPrinter - C:\Users\Default\"""
(printPath windowsPrinter $ sandboxAny $ rootDir </> dir (SProxy :: SProxy "C") </> dir (SProxy :: SProxy "Users") </> dir (SProxy :: SProxy "Default"))
(printPath windowsPrinter $ sandboxAny $ rootDir </> dir (Proxy :: Proxy "C") </> dir (Proxy :: Proxy "Users") </> dir (Proxy :: Proxy "Default"))
"""C:\Users\Default\"""

test """printPath posixPrinter - /C/Users/Default/"""
(printPath posixPrinter $ sandboxAny $ rootDir </> dir (SProxy :: SProxy "C") </> dir (SProxy :: SProxy "Users") </> dir (SProxy :: SProxy "Default"))
(printPath posixPrinter $ sandboxAny $ rootDir </> dir (Proxy :: Proxy "C") </> dir (Proxy :: Proxy "Users") </> dir (Proxy :: Proxy "Default"))
"""/C/Users/Default/"""

test """printPath windowsPrinter - \"""
Expand Down Expand Up @@ -295,23 +295,23 @@ main = do
"./foo/"

test "rename - single level deep"
(rename (alterExtension (const Nothing)) (file (SProxy :: SProxy "image.png")))
(file (SProxy :: SProxy "image"))
(rename (alterExtension (const Nothing)) (file (Proxy :: Proxy "image.png")))
(file (Proxy :: Proxy "image"))

test """extension (Name ".foo") == Nothing"""
(extension (reflectName (SProxy :: SProxy ".foo")))
(extension (reflectName (Proxy :: Proxy ".foo")))
(Nothing)
test """extension (Name "foo.") == Nothing"""
(extension (reflectName (SProxy :: SProxy "foo.")))
(extension (reflectName (Proxy :: Proxy "foo.")))
(Nothing)
test """extension (Name "foo") == Nothing"""
(extension (reflectName (SProxy :: SProxy "foo")))
(extension (reflectName (Proxy :: Proxy "foo")))
(Nothing)
test """extension (Name ".") == Nothing"""
(extension (reflectName (SProxy :: SProxy ".")))
(extension (reflectName (Proxy :: Proxy ".")))
(Nothing)
test """extension (Name "foo.baz") == (Just "baz")"""
(extension (reflectName (SProxy :: SProxy "foo.baz")))
(extension (reflectName (Proxy :: Proxy "foo.baz")))
(NES.fromString "baz")

test "sandbox - fail when relative path lies outside sandbox (above)"
Expand Down Expand Up @@ -344,27 +344,27 @@ main = do

test "parseRelFile - image.png"
(parseRelFile posixParser "image.png")
(Just $ file (SProxy :: SProxy "image.png"))
(Just $ file (Proxy :: Proxy "image.png"))

test "parseRelFile - ./image.png"
(parseRelFile posixParser "./image.png")
(Just $ file (SProxy :: SProxy "image.png"))
(Just $ file (Proxy :: Proxy "image.png"))

test "parseRelFile - foo/image.png"
(parseRelFile posixParser "foo/image.png")
(Just $ dirFoo </> file (SProxy :: SProxy "image.png"))
(Just $ dirFoo </> file (Proxy :: Proxy "image.png"))

test "parseRelFile - ../foo/image.png"
(parseRelFile posixParser "../foo/image.png")
(Just $ currentDir <..> dirFoo </> file (SProxy :: SProxy "image.png"))
(Just $ currentDir <..> dirFoo </> file (Proxy :: Proxy "image.png"))

test "parseAbsFile - /image.png"
(parseAbsFile posixParser "/image.png")
(Just $ rootDir </> file (SProxy :: SProxy "image.png"))
(Just $ rootDir </> file (Proxy :: Proxy "image.png"))

test "parseAbsFile - /foo/image.png"
(parseAbsFile posixParser "/foo/image.png")
(Just $ rootDir </> dirFoo </> file (SProxy :: SProxy "image.png"))
(Just $ rootDir </> dirFoo </> file (Proxy :: Proxy "image.png"))

test "parseRelDir - empty string"
(parseRelDir posixParser "")
Expand Down

0 comments on commit 4d1133f

Please sign in to comment.