diff --git a/exercises/chapter10/src/Control/Monad/Eff/Alert.purs b/exercises/chapter10/src/Control/Monad/Eff/Alert.purs index 63ce3969b..8da9f9be0 100644 --- a/exercises/chapter10/src/Control/Monad/Eff/Alert.purs +++ b/exercises/chapter10/src/Control/Monad/Eff/Alert.purs @@ -1,8 +1,8 @@ -module Control.Monad.Eff.Alert where +module Effect.Alert where import Prelude -import Control.Monad.Eff (kind Effect, Eff) +import Effect (kind Effect, Effect) foreign import data ALERT :: Effect diff --git a/exercises/chapter10/src/Control/Monad/Eff/Storage.purs b/exercises/chapter10/src/Control/Monad/Eff/Storage.purs index 1738aefe6..e3f63efa7 100644 --- a/exercises/chapter10/src/Control/Monad/Eff/Storage.purs +++ b/exercises/chapter10/src/Control/Monad/Eff/Storage.purs @@ -1,8 +1,8 @@ -module Control.Monad.Eff.Storage where +module Effect.Storage where import Prelude -import Control.Monad.Eff (kind Effect, Eff) +import Effect (kind Effect, Effect) import Data.Foreign (Foreign) foreign import data STORAGE :: Effect diff --git a/exercises/chapter10/src/Main.purs b/exercises/chapter10/src/Main.purs index 18785ba48..c947550cf 100644 --- a/exercises/chapter10/src/Main.purs +++ b/exercises/chapter10/src/Main.purs @@ -2,10 +2,10 @@ module Main where import Prelude -import Control.Monad.Eff (Eff) -import Control.Monad.Eff.Alert (ALERT, alert) -import Control.Monad.Eff.Console (CONSOLE, log) -import Control.Monad.Eff.Storage (STORAGE, setItem, getItem) +import Effect (Effect) +import Effect.Alert (ALERT, alert) +import Effect.Console (log) +import Effect.Storage (STORAGE, setItem, getItem) import Control.Monad.Except (runExcept) import DOM (DOM) import DOM.HTML (window) diff --git a/exercises/chapter11/.gitignore b/exercises/chapter11/.gitignore index 8cc09ed5c..e9f46bdfa 100644 --- a/exercises/chapter11/.gitignore +++ b/exercises/chapter11/.gitignore @@ -5,3 +5,4 @@ /output/ /node_modules/ /bower_components/ +.psc-package diff --git a/exercises/chapter11/psc-package.json b/exercises/chapter11/psc-package.json new file mode 100644 index 000000000..d14304d36 --- /dev/null +++ b/exercises/chapter11/psc-package.json @@ -0,0 +1,13 @@ +{ + "name": "chapter2", + "set": "psc-0.12.0-20180625", + "source": "https://github.com/purescript/package-sets.git", + "depends": [ + "console", + "math", + "node-readline", + "prelude", + "strings", + "transformers" + ] +} diff --git a/exercises/chapter11/src/Main.purs b/exercises/chapter11/src/Main.purs index 069b6f4e4..c1e7b31a6 100644 --- a/exercises/chapter11/src/Main.purs +++ b/exercises/chapter11/src/Main.purs @@ -2,9 +2,8 @@ module Main where import Prelude import Node.ReadLine as RL -import Control.Monad.Eff (Eff) -import Control.Monad.Eff.Console (CONSOLE, log) -import Control.Monad.Eff.Exception (EXCEPTION) +import Effect (Effect) +import Effect.Console (log) import Control.Monad.RWS (RWSResult(..), runRWS) import Data.Either (Either(..)) import Data.Foldable (for_) diff --git a/exercises/chapter12/.gitignore b/exercises/chapter12/.gitignore index 8cc09ed5c..e9f46bdfa 100644 --- a/exercises/chapter12/.gitignore +++ b/exercises/chapter12/.gitignore @@ -5,3 +5,4 @@ /output/ /node_modules/ /bower_components/ +.psc-package diff --git a/exercises/chapter12/bower.json b/exercises/chapter12/bower.json deleted file mode 100644 index 752f36914..000000000 --- a/exercises/chapter12/bower.json +++ /dev/null @@ -1,31 +0,0 @@ -{ - "name": "purescript-book-chapter12", - "description": "Callback Hell", - "keywords": [ - "purescript" - ], - "ignore": [ - "**/.*", - "bower_components", - "node_modules", - "output", - "tests", - "js", - "tmp", - "bower.json", - "Gruntfile.js", - "package.json" - ], - "dependencies": { - "purescript-console": "^3.0.0", - "purescript-functions": "^3.0.0", - "purescript-lists": "^4.0.0", - "purescript-parallel": "^3.0.0", - "purescript-refs": "^3.0.0", - "purescript-strings": "^3.0.0", - "purescript-transformers": "^3.0.0" - }, - "devDependencies": { - "purescript-psci-support": "^3.0.0" - } -} diff --git a/exercises/chapter12/psc-package.json b/exercises/chapter12/psc-package.json new file mode 100644 index 000000000..b02692206 --- /dev/null +++ b/exercises/chapter12/psc-package.json @@ -0,0 +1,16 @@ +{ + "name": "chapter2", + "set": "psc-0.12.0-20180625", + "source": "https://github.com/purescript/package-sets.git", + "depends": [ + "console", + "functions", + "lists", + "math", + "parallel", + "prelude", + "refs", + "strings", + "transformers" + ] +} diff --git a/exercises/chapter12/src/Files.purs b/exercises/chapter12/src/Files.purs index f6ab031d7..c7914425b 100644 --- a/exercises/chapter12/src/Files.purs +++ b/exercises/chapter12/src/Files.purs @@ -3,50 +3,48 @@ module Files where import Prelude import Control.Monad.Cont.Trans (ContT(..)) -import Control.Monad.Eff (kind Effect, Eff) +import Effect (Effect) import Control.Monad.Except.Trans (ExceptT(..)) import Data.Either (Either(..)) import Data.Function.Uncurried (Fn4, Fn3, runFn4, runFn3) import Types (Async) -foreign import data FS :: Effect - type ErrorCode = String type FilePath = String foreign import readFileImpl :: - forall eff. Fn3 FilePath - (String -> Eff (fs :: FS | eff) Unit) - (ErrorCode -> Eff (fs :: FS | eff) Unit) - (Eff (fs :: FS | eff) Unit) + Fn3 FilePath + (String -> Effect Unit) + (ErrorCode -> Effect Unit) + (Effect Unit) foreign import writeFileImpl :: - forall eff. Fn4 FilePath + Fn4 FilePath String - (Eff (fs :: FS | eff) Unit) - (ErrorCode -> Eff (fs :: FS | eff) Unit) - (Eff (fs :: FS | eff) Unit) + (Effect Unit) + (ErrorCode -> Effect Unit) + (Effect Unit) -readFile :: forall eff. FilePath -> (Either ErrorCode String -> Eff (fs :: FS | eff) Unit) -> Eff (fs :: FS | eff) Unit +readFile :: FilePath -> (Either ErrorCode String -> Effect Unit) -> Effect Unit readFile path k = runFn3 readFileImpl path (k <<< Right) (k <<< Left) -writeFile :: forall eff. FilePath -> String -> (Either ErrorCode Unit -> Eff (fs :: FS | eff) Unit) -> Eff (fs :: FS | eff) Unit +writeFile :: FilePath -> String -> (Either ErrorCode Unit -> Effect Unit) -> Effect Unit writeFile path text k = runFn4 writeFileImpl path text (k $ Right unit) (k <<< Left) -readFileCont :: forall eff. FilePath -> Async (fs :: FS | eff) (Either ErrorCode String) +readFileCont :: FilePath -> Async (Either ErrorCode String) readFileCont path = ContT $ readFile path -writeFileCont :: forall eff. FilePath -> String -> Async (fs :: FS | eff) (Either ErrorCode Unit) +writeFileCont :: FilePath -> String -> Async (Either ErrorCode Unit) writeFileCont path text = ContT $ writeFile path text -readFileContEx :: forall eff. FilePath -> ExceptT ErrorCode (Async (fs :: FS | eff)) String +readFileContEx :: FilePath -> ExceptT ErrorCode Async String readFileContEx path = ExceptT $ readFileCont path -writeFileContEx :: forall eff. FilePath -> String -> ExceptT ErrorCode (Async (fs :: FS | eff)) Unit +writeFileContEx :: FilePath -> String -> ExceptT ErrorCode Async Unit writeFileContEx path text = ExceptT $ writeFileCont path text -copyFileContEx :: forall eff. FilePath -> FilePath -> ExceptT ErrorCode (Async (fs :: FS | eff)) Unit +copyFileContEx :: FilePath -> FilePath -> ExceptT ErrorCode Async Unit copyFileContEx src dest = do content <- readFileContEx src writeFileContEx dest content diff --git a/exercises/chapter12/src/Main.purs b/exercises/chapter12/src/Main.purs index 29fff44e1..6f42d5fd6 100644 --- a/exercises/chapter12/src/Main.purs +++ b/exercises/chapter12/src/Main.purs @@ -3,19 +3,17 @@ module Main where import Prelude import Control.Monad.Cont.Trans (runContT) -import Control.Monad.Eff (Eff) -import Control.Monad.Eff.Console (CONSOLE, log, error) +import Effect (Effect) +import Effect.Console (log, error) import Control.Monad.Trans.Class (lift) import Data.Either (either) -import Network.HTTP.Client (HTTP, get) +import Network.HTTP.Client (get) import Types (Async) -main :: Eff ( http :: HTTP - , console :: CONSOLE - ) Unit +main :: Effect Unit main = async do response <- get "http://purescript.org" lift (either error log response) where - async :: forall eff. Async eff Unit -> Eff eff Unit + async :: Async Unit -> Effect Unit async = flip runContT pure diff --git a/exercises/chapter12/src/Network/HTTP/Client.purs b/exercises/chapter12/src/Network/HTTP/Client.purs index bfcd4327c..c83b9a84d 100644 --- a/exercises/chapter12/src/Network/HTTP/Client.purs +++ b/exercises/chapter12/src/Network/HTTP/Client.purs @@ -3,20 +3,18 @@ module Network.HTTP.Client where import Prelude import Control.Monad.Cont.Trans (ContT(..)) -import Control.Monad.Eff (kind Effect, Eff) +import Effect (Effect) import Data.Either (Either(..)) import Data.Function.Uncurried (Fn3, runFn3) import Types (Async) -foreign import data HTTP :: Effect - type URI = String foreign import getImpl :: - forall eff. Fn3 URI - (String -> Eff (http :: HTTP | eff) Unit) - (String -> Eff (http :: HTTP | eff) Unit) - (Eff (http :: HTTP | eff) Unit) + Fn3 URI + (String -> Effect Unit) + (String -> Effect Unit) + (Effect Unit) -get :: forall eff. URI -> Async (http :: HTTP | eff) (Either String String) +get :: URI -> Async (Either String String) get req = ContT $ \k -> runFn3 getImpl req (k <<< Right) (k <<< Left) diff --git a/exercises/chapter12/src/Types.purs b/exercises/chapter12/src/Types.purs index 9cd46bd6f..b6664fd5d 100644 --- a/exercises/chapter12/src/Types.purs +++ b/exercises/chapter12/src/Types.purs @@ -2,7 +2,7 @@ module Types where import Prelude -import Control.Monad.Eff (Eff) +import Effect (Effect) import Control.Monad.Cont.Trans (ContT) -type Async eff = ContT Unit (Eff eff) +type Async = ContT Unit Effect diff --git a/exercises/chapter13/.gitignore b/exercises/chapter13/.gitignore index 8cc09ed5c..e9f46bdfa 100644 --- a/exercises/chapter13/.gitignore +++ b/exercises/chapter13/.gitignore @@ -5,3 +5,4 @@ /output/ /node_modules/ /bower_components/ +.psc-package diff --git a/exercises/chapter13/bower.json b/exercises/chapter13/bower.json deleted file mode 100644 index 88d234bf7..000000000 --- a/exercises/chapter13/bower.json +++ /dev/null @@ -1,28 +0,0 @@ -{ - "name": "purescript-book-chapter13", - "description": "Generative Testing", - "keywords": [ - "purescript" - ], - "ignore": [ - "**/.*", - "bower_components", - "node_modules", - "output", - "tests", - "js", - "tmp", - "bower.json", - "Gruntfile.js", - "package.json" - ], - "dependencies": { - "purescript-arrays": "^4.0.0", - "purescript-quickcheck": "^4.0.0", - "purescript-functions": "^3.0.0", - "purescript-lists": "^4.0.0" - }, - "devDependencies": { - "purescript-psci-support": "^3.0.0" - } -} diff --git a/exercises/chapter13/psc-package.json b/exercises/chapter13/psc-package.json new file mode 100644 index 000000000..0790b4ee1 --- /dev/null +++ b/exercises/chapter13/psc-package.json @@ -0,0 +1,14 @@ +{ + "name": "chapter2", + "set": "psc-0.12.0-20180625", + "source": "https://github.com/purescript/package-sets.git", + "depends": [ + "arrays", + "console", + "functions", + "lists", + "math", + "prelude", + "quickcheck" + ] +} diff --git a/exercises/chapter13/src/Merge.purs b/exercises/chapter13/src/Merge.purs index d46f93b49..67c683c78 100644 --- a/exercises/chapter13/src/Merge.purs +++ b/exercises/chapter13/src/Merge.purs @@ -8,7 +8,7 @@ merge :: Array Int -> Array Int -> Array Int merge = mergePoly mergePoly :: forall a. Ord a => Array a -> Array a -> Array a -mergePoly = mergeWith id +mergePoly = mergeWith identity mergeWith :: forall a b. Ord b => (a -> b) -> Array a -> Array a -> Array a mergeWith f = \xs ys -> diff --git a/exercises/chapter13/src/Tree.purs b/exercises/chapter13/src/Tree.purs index 286d13cb1..7b14dd116 100644 --- a/exercises/chapter13/src/Tree.purs +++ b/exercises/chapter13/src/Tree.purs @@ -13,7 +13,7 @@ instance arbTree :: (Arbitrary a, Ord a) => Arbitrary (Tree a) where arbitrary = map fromArray arbitrary instance coarbTree :: (Coarbitrary a) => Coarbitrary (Tree a) where - coarbitrary Leaf = id + coarbitrary Leaf = identity coarbitrary (Branch l a r) = coarbitrary l <<< coarbitrary a <<< diff --git a/exercises/chapter13/test/Main.purs b/exercises/chapter13/test/Main.purs index bf3152fe0..ceb4b1aca 100644 --- a/exercises/chapter13/test/Main.purs +++ b/exercises/chapter13/test/Main.purs @@ -2,10 +2,7 @@ module Test.Main where import Prelude -import Control.Monad.Eff (Eff) -import Control.Monad.Eff.Console (CONSOLE) -import Control.Monad.Eff.Exception (EXCEPTION) -import Control.Monad.Eff.Random (RANDOM) +import Effect (Effect) import Data.Array (sortBy, intersect) import Data.Foldable (foldr) import Data.Function (on) @@ -25,18 +22,15 @@ isSubarrayOf :: forall a. (Eq a) => Array a -> Array a -> Boolean isSubarrayOf xs ys = xs `intersect` ys == xs ints :: Array Int -> Array Int -ints = id +ints = identity intToBool :: (Int -> Boolean) -> Int -> Boolean -intToBool = id +intToBool = identity treeOfInt :: Tree Number -> Tree Number -treeOfInt = id +treeOfInt = identity -main :: Eff ( console :: CONSOLE - , random :: RANDOM - , exception :: EXCEPTION - ) Unit +main :: Effect Unit main = do -- Tests for module 'Merge' diff --git a/exercises/chapter14/.gitignore b/exercises/chapter14/.gitignore index 8cc09ed5c..e9f46bdfa 100644 --- a/exercises/chapter14/.gitignore +++ b/exercises/chapter14/.gitignore @@ -5,3 +5,4 @@ /output/ /node_modules/ /bower_components/ +.psc-package diff --git a/exercises/chapter14/bower.json b/exercises/chapter14/bower.json deleted file mode 100644 index 55c017a64..000000000 --- a/exercises/chapter14/bower.json +++ /dev/null @@ -1,27 +0,0 @@ -{ - "name": "purescript-book-chapter14", - "description": "Domain Specific Languages", - "keywords": [ - "purescript" - ], - "ignore": [ - "**/.*", - "bower_components", - "node_modules", - "output", - "tests", - "js", - "tmp", - "bower.json", - "Gruntfile.js", - "package.json" - ], - "dependencies": { - "purescript-arrays": "^4.0.0", - "purescript-strings": "^3.0.0", - "purescript-free": "^4.0.0" - }, - "devDependencies": { - "purescript-psci-support": "^3.0.0" - } -} diff --git a/exercises/chapter14/psc-package.json b/exercises/chapter14/psc-package.json new file mode 100644 index 000000000..129c332b7 --- /dev/null +++ b/exercises/chapter14/psc-package.json @@ -0,0 +1,13 @@ +{ + "name": "chapter2", + "set": "psc-0.12.0-20180625", + "source": "https://github.com/purescript/package-sets.git", + "depends": [ + "arrays", + "console", + "free", + "math", + "prelude", + "strings" + ] +} diff --git a/exercises/chapter14/src/Data/DOM/Free.purs b/exercises/chapter14/src/Data/DOM/Free.purs index e1a87ad74..2e7a95df9 100644 --- a/exercises/chapter14/src/Data/DOM/Free.purs +++ b/exercises/chapter14/src/Data/DOM/Free.purs @@ -72,7 +72,7 @@ class IsValue a where toValue :: a -> String instance stringIsValue :: IsValue String where - toValue = id + toValue = identity instance intIsValue :: IsValue Int where toValue = show diff --git a/exercises/chapter14/src/Data/DOM/Name.purs b/exercises/chapter14/src/Data/DOM/Name.purs index c0524c040..269211b01 100644 --- a/exercises/chapter14/src/Data/DOM/Name.purs +++ b/exercises/chapter14/src/Data/DOM/Name.purs @@ -74,13 +74,13 @@ elem :: Element -> Content Unit elem e = liftF $ ElementContent e unit newName :: Content Name -newName = liftF $ NewName id +newName = liftF $ NewName identity class IsValue a where toValue :: a -> String instance stringIsValue :: IsValue String where - toValue = id + toValue = identity instance intIsValue :: IsValue Int where toValue = show diff --git a/exercises/chapter14/src/Data/DOM/Phantom.purs b/exercises/chapter14/src/Data/DOM/Phantom.purs index 5511cf1d7..4cbac527e 100644 --- a/exercises/chapter14/src/Data/DOM/Phantom.purs +++ b/exercises/chapter14/src/Data/DOM/Phantom.purs @@ -62,7 +62,7 @@ class IsValue a where toValue :: a -> String instance stringIsValue :: IsValue String where - toValue = id + toValue = identity instance intIsValue :: IsValue Int where toValue = show diff --git a/exercises/chapter2/.gitignore b/exercises/chapter2/.gitignore index e64d93149..459a0c7ee 100644 --- a/exercises/chapter2/.gitignore +++ b/exercises/chapter2/.gitignore @@ -2,3 +2,4 @@ .psci_modules output bower_components +.psc-package diff --git a/exercises/chapter2/bower.json b/exercises/chapter2/bower.json deleted file mode 100644 index 80592be79..000000000 --- a/exercises/chapter2/bower.json +++ /dev/null @@ -1,26 +0,0 @@ -{ - "name": "purescript-book-chapter2", - "description": "Chapter 2 - Getting Started", - "keywords": [ - "purescript" - ], - "ignore": [ - "**/.*", - "bower_components", - "node_modules", - "output", - "tests", - "js", - "tmp", - "bower.json", - "Gruntfile.js", - "package.json" - ], - "dependencies": { - "purescript-math": "^2.0.0", - "purescript-console": "^3.0.0" - }, - "devDependencies": { - "purescript-psci-support": "^3.0.0" - } -} diff --git a/exercises/chapter2/psc-package.json b/exercises/chapter2/psc-package.json new file mode 100644 index 000000000..f37f32bc0 --- /dev/null +++ b/exercises/chapter2/psc-package.json @@ -0,0 +1,10 @@ +{ + "name": "chapter2", + "set": "psc-0.12.0-20180625", + "source": "https://github.com/purescript/package-sets.git", + "depends": [ + "console", + "math", + "prelude" + ] +} diff --git a/exercises/chapter2/src/Main.purs b/exercises/chapter2/src/Main.purs index 458a9d5b2..20872d8c8 100644 --- a/exercises/chapter2/src/Main.purs +++ b/exercises/chapter2/src/Main.purs @@ -1,7 +1,7 @@ module Main where +import Effect.Console (logShow) import Prelude ((+), (*)) -import Control.Monad.Eff.Console (logShow) import Math (sqrt) diagonal :: Number -> Number -> Number diff --git a/exercises/chapter3/.gitignore b/exercises/chapter3/.gitignore index 85a2353e2..6db63aecd 100644 --- a/exercises/chapter3/.gitignore +++ b/exercises/chapter3/.gitignore @@ -3,3 +3,4 @@ !/.gitignore bower_components output +.psc-package diff --git a/exercises/chapter3/bower.json b/exercises/chapter3/bower.json deleted file mode 100644 index d48cd5b3c..000000000 --- a/exercises/chapter3/bower.json +++ /dev/null @@ -1,26 +0,0 @@ -{ - "name": "purescript-book-chapter3", - "description": "Chapter 3 - Functions and Records", - "keywords": [ - "purescript" - ], - "ignore": [ - "**/.*", - "bower_components", - "node_modules", - "output", - "tests", - "js", - "tmp", - "bower.json", - "Gruntfile.js", - "package.json" - ], - "dependencies": { - "purescript-lists": "^4.0.0", - "purescript-console": "^3.0.0" - }, - "devDependencies": { - "purescript-psci-support": "^3.0.0" - } -} diff --git a/exercises/chapter3/psc-package.json b/exercises/chapter3/psc-package.json new file mode 100644 index 000000000..f08b604b3 --- /dev/null +++ b/exercises/chapter3/psc-package.json @@ -0,0 +1,11 @@ +{ + "name": "chapter2", + "set": "psc-0.12.0-20180625", + "source": "https://github.com/purescript/package-sets.git", + "depends": [ + "console", + "lists", + "math", + "prelude" + ] +} diff --git a/exercises/chapter3/test/Main.purs b/exercises/chapter3/test/Main.purs index 7b2523c45..9ef0f5872 100644 --- a/exercises/chapter3/test/Main.purs +++ b/exercises/chapter3/test/Main.purs @@ -2,8 +2,8 @@ module Test.Main where import Prelude -import Control.Monad.Eff (Eff) -import Control.Monad.Eff.Console (CONSOLE, logShow) +import Effect (Effect) +import Effect.Console (logShow) import Data.AddressBook (AddressBook, Entry, emptyBook, insertEntry, findEntry, showEntry) import Data.Maybe (Maybe) @@ -23,7 +23,7 @@ book0 = emptyBook printEntry :: String -> String -> AddressBook -> Maybe String printEntry firstName lastName book = showEntry <$> findEntry firstName lastName book -main :: Eff (console :: CONSOLE) Unit +main :: Effect Unit main = do let book1 = insertEntry example emptyBook diff --git a/exercises/chapter4/.gitignore b/exercises/chapter4/.gitignore index 85a2353e2..6db63aecd 100644 --- a/exercises/chapter4/.gitignore +++ b/exercises/chapter4/.gitignore @@ -3,3 +3,4 @@ !/.gitignore bower_components output +.psc-package diff --git a/exercises/chapter4/bower.json b/exercises/chapter4/bower.json deleted file mode 100644 index d6ebefd3e..000000000 --- a/exercises/chapter4/bower.json +++ /dev/null @@ -1,27 +0,0 @@ -{ - "name": "purescript-book-chapter4", - "description": "Chapter 4 - Recursion, Maps and Folds", - "keywords": [ - "purescript" - ], - "ignore": [ - "**/.*", - "bower_components", - "node_modules", - "output", - "tests", - "js", - "tmp", - "bower.json", - "Gruntfile.js", - "package.json" - ], - "dependencies": { - "purescript-arrays": "^4.0.0", - "purescript-strings": "^3.0.0", - "purescript-console": "^3.0.0" - }, - "devDependencies": { - "purescript-psci-support": "^3.0.0" - } -} diff --git a/exercises/chapter4/psc-package.json b/exercises/chapter4/psc-package.json new file mode 100644 index 000000000..bc0b0b042 --- /dev/null +++ b/exercises/chapter4/psc-package.json @@ -0,0 +1,12 @@ +{ + "name": "chapter2", + "set": "psc-0.12.0-20180625", + "source": "https://github.com/purescript/package-sets.git", + "depends": [ + "arrays", + "console", + "math", + "prelude", + "strings" + ] +} diff --git a/exercises/chapter4/test/Main.purs b/exercises/chapter4/test/Main.purs index a3d969576..cb0f272eb 100644 --- a/exercises/chapter4/test/Main.purs +++ b/exercises/chapter4/test/Main.purs @@ -2,11 +2,11 @@ module Test.Main where import Prelude -import Control.Monad.Eff (Eff) -import Control.Monad.Eff.Console (CONSOLE, logShow) +import Effect (Effect) +import Effect.Console (logShow) import Data.Path (root) import Data.Foldable (for_) import FileOperations (allFiles) -main :: Eff (console :: CONSOLE) Unit +main :: Effect Unit main = for_ (allFiles root) logShow diff --git a/exercises/chapter5/.gitignore b/exercises/chapter5/.gitignore index 85a2353e2..6db63aecd 100644 --- a/exercises/chapter5/.gitignore +++ b/exercises/chapter5/.gitignore @@ -3,3 +3,4 @@ !/.gitignore bower_components output +.psc-package diff --git a/exercises/chapter5/bower.json b/exercises/chapter5/bower.json deleted file mode 100644 index 7b3f48935..000000000 --- a/exercises/chapter5/bower.json +++ /dev/null @@ -1,25 +0,0 @@ -{ - "name": "purescript-book-chapter5", - "description": "Pattern Matching", - "keywords": [ - "purescript" - ], - "ignore": [ - "**/.*", - "bower_components", - "node_modules", - "dist", - "bower.json", - "Gruntfile.js", - "package.json" - ], - "dependencies": { - "purescript-arrays": "^4.0.0", - "purescript-console": "^3.0.0", - "purescript-math": "^2.0.0", - "purescript-globals": "^3.0.0" - }, - "devDependencies": { - "purescript-psci-support": "^3.0.0" - } -} diff --git a/exercises/chapter5/psc-package.json b/exercises/chapter5/psc-package.json new file mode 100644 index 000000000..793c9fbc1 --- /dev/null +++ b/exercises/chapter5/psc-package.json @@ -0,0 +1,12 @@ +{ + "name": "chapter2", + "set": "psc-0.12.0-20180625", + "source": "https://github.com/purescript/package-sets.git", + "depends": [ + "arrays", + "console", + "globals", + "math", + "prelude" + ] +} diff --git a/exercises/chapter5/test/Main.purs b/exercises/chapter5/test/Main.purs index c84806cbe..1f221331e 100644 --- a/exercises/chapter5/test/Main.purs +++ b/exercises/chapter5/test/Main.purs @@ -2,8 +2,8 @@ module Test.Main where import Prelude -import Control.Monad.Eff (Eff) -import Control.Monad.Eff.Console (CONSOLE, log) +import Effect (Effect) +import Effect.Console (log) import Data.Picture (Point(..), Shape(..), Picture, bounds, showBounds) circle :: Shape @@ -15,5 +15,5 @@ rectangle = Rectangle (Point { x: 10.0, y: 10.0 }) 10.0 10.0 picture :: Picture picture = [circle, rectangle] -main :: Eff (console :: CONSOLE) Unit +main :: Effect Unit main = log (showBounds (bounds picture)) diff --git a/exercises/chapter6/.gitignore b/exercises/chapter6/.gitignore index 85a2353e2..6db63aecd 100644 --- a/exercises/chapter6/.gitignore +++ b/exercises/chapter6/.gitignore @@ -3,3 +3,4 @@ !/.gitignore bower_components output +.psc-package diff --git a/exercises/chapter6/bower.json b/exercises/chapter6/bower.json deleted file mode 100644 index f9afa4c53..000000000 --- a/exercises/chapter6/bower.json +++ /dev/null @@ -1,26 +0,0 @@ -{ - "name": "purescript-book-chapter6", - "description": "Type Classes", - "keywords": [ - "purescript" - ], - "ignore": [ - "**/.*", - "bower_components", - "node_modules", - "dist", - "bower.json", - "Gruntfile.js", - "package.json" - ], - "dependencies": { - "purescript-tuples": "^4.0.0", - "purescript-either": "^3.0.0", - "purescript-strings": "^3.0.0", - "purescript-console": "^3.0.0", - "purescript-functions": "^3.0.0" - }, - "devDependencies": { - "purescript-psci-support": "^3.0.0" - } -} diff --git a/exercises/chapter6/psc-package.json b/exercises/chapter6/psc-package.json new file mode 100644 index 000000000..c90d97294 --- /dev/null +++ b/exercises/chapter6/psc-package.json @@ -0,0 +1,14 @@ +{ + "name": "chapter2", + "set": "psc-0.12.0-20180625", + "source": "https://github.com/purescript/package-sets.git", + "depends": [ + "console", + "either", + "functions", + "math", + "prelude", + "strings", + "tuples" + ] +} diff --git a/exercises/chapter6/src/Data/Hashable.purs b/exercises/chapter6/src/Data/Hashable.purs index e60bc3570..64a2a4ad8 100644 --- a/exercises/chapter6/src/Data/Hashable.purs +++ b/exercises/chapter6/src/Data/Hashable.purs @@ -14,7 +14,7 @@ import Data.Either (Either(..)) import Data.Foldable (foldl) import Data.Function (on) import Data.Maybe (Maybe(..)) -import Data.String (toCharArray) +import Data.String.CodeUnits (toCharArray) import Data.Tuple (Tuple(..)) newtype HashCode = HashCode Int diff --git a/exercises/chapter6/test/Main.purs b/exercises/chapter6/test/Main.purs index 70abc1901..34c3bf558 100644 --- a/exercises/chapter6/test/Main.purs +++ b/exercises/chapter6/test/Main.purs @@ -2,11 +2,11 @@ module Test.Main where import Prelude -import Control.Monad.Eff (Eff) -import Control.Monad.Eff.Console (CONSOLE, logShow) +import Effect (Effect) +import Effect.Console (logShow) import Data.Hashable (hash, hashEqual) -main :: Eff (console :: CONSOLE) Unit +main :: Effect Unit main = do logShow (hash 123) logShow (hash true) diff --git a/exercises/chapter7/.gitignore b/exercises/chapter7/.gitignore index 85a2353e2..6db63aecd 100644 --- a/exercises/chapter7/.gitignore +++ b/exercises/chapter7/.gitignore @@ -3,3 +3,4 @@ !/.gitignore bower_components output +.psc-package diff --git a/exercises/chapter7/bower.json b/exercises/chapter7/bower.json deleted file mode 100644 index c94fdfed2..000000000 --- a/exercises/chapter7/bower.json +++ /dev/null @@ -1,30 +0,0 @@ -{ - "name": "purescript-book-chapter7", - "description": "Applicative Validation", - "keywords": [ - "purescript" - ], - "ignore": [ - "**/.*", - "bower_components", - "node_modules", - "output", - "tests", - "js", - "tmp", - "bower.json", - "Gruntfile.js", - "package.json" - ], - "dependencies": { - "purescript-validation": "^3.0.0", - "purescript-console": "^3.0.0", - "purescript-arrays": "^4.0.0", - "purescript-either": "^3.0.0", - "purescript-strings": "^3.0.0", - "purescript-lists": "^4.0.0" - }, - "devDependencies": { - "purescript-psci-support": "^3.0.0" - } -} diff --git a/exercises/chapter7/psc-package.json b/exercises/chapter7/psc-package.json new file mode 100644 index 000000000..ce51cb040 --- /dev/null +++ b/exercises/chapter7/psc-package.json @@ -0,0 +1,15 @@ +{ + "name": "chapter2", + "set": "psc-0.12.0-20180625", + "source": "https://github.com/purescript/package-sets.git", + "depends": [ + "arrays", + "console", + "either", + "lists", + "math", + "prelude", + "strings", + "validation" + ] +} diff --git a/exercises/chapter7/test/Main.purs b/exercises/chapter7/test/Main.purs index f5e31a70b..276a4d2cb 100644 --- a/exercises/chapter7/test/Main.purs +++ b/exercises/chapter7/test/Main.purs @@ -2,10 +2,10 @@ module Test.Main where import Prelude -import Control.Monad.Eff (Eff) -import Control.Monad.Eff.Console (CONSOLE, logShow) +import Effect (Effect) +import Effect.Console (logShow) import Data.AddressBook (examplePerson) import Data.AddressBook.Validation (validatePerson) -main :: Eff (console :: CONSOLE) Unit +main :: Effect Unit main = logShow (validatePerson examplePerson) diff --git a/exercises/chapter8/psc-package.json b/exercises/chapter8/psc-package.json new file mode 100644 index 000000000..96338bf63 --- /dev/null +++ b/exercises/chapter8/psc-package.json @@ -0,0 +1,15 @@ +{ + "name": "chapter2", + "set": "psc-0.12.0-20180625", + "source": "https://github.com/purescript/package-sets.git", + "depends": [ + "console", + "foreign", + "math", + "prelude", + "react", + "react-dom", + "strings", + "validation" + ] +} diff --git a/exercises/chapter9/.gitignore b/exercises/chapter9/.gitignore index bafde98ea..c7b262ded 100644 --- a/exercises/chapter9/.gitignore +++ b/exercises/chapter9/.gitignore @@ -5,3 +5,4 @@ /dist/ /node_modules/ /bower_components/ +.psc-package diff --git a/exercises/chapter9/psc-package.json b/exercises/chapter9/psc-package.json new file mode 100644 index 000000000..b26664032 --- /dev/null +++ b/exercises/chapter9/psc-package.json @@ -0,0 +1,16 @@ +{ + "name": "chapter2", + "set": "psc-0.12.0-20180625-2", + "source": "https://github.com/purescript/package-sets.git", + "depends": [ + "arrays", + "canvas", + "console", + "lists", + "math", + "prelude", + "random", + "refs", + "web-dom" + ] +} diff --git a/exercises/chapter9/src/Control/Monad/Eff/DOM.js b/exercises/chapter9/src/Effect/DOM.js similarity index 100% rename from exercises/chapter9/src/Control/Monad/Eff/DOM.js rename to exercises/chapter9/src/Effect/DOM.js diff --git a/exercises/chapter9/src/Control/Monad/Eff/DOM.purs b/exercises/chapter9/src/Effect/DOM.purs similarity index 51% rename from exercises/chapter9/src/Control/Monad/Eff/DOM.purs rename to exercises/chapter9/src/Effect/DOM.purs index bd4b4c2ea..e73727aba 100644 --- a/exercises/chapter9/src/Control/Monad/Eff/DOM.purs +++ b/exercises/chapter9/src/Effect/DOM.purs @@ -1,30 +1,27 @@ -module Control.Monad.Eff.DOM where +module Effect.DOM where import Prelude -import Control.Monad.Eff (Eff) +import Effect (Effect) import Data.Function.Uncurried (Fn3, runFn3) import Data.Maybe (Maybe(..)) -import DOM (DOM) foreign import data Node :: Type foreign import querySelectorImpl - :: forall eff r + :: forall r . Fn3 r (Node -> r) String - (Eff (dom :: DOM | eff) r) + (Effect r) querySelector - :: forall eff - . String - -> Eff (dom :: DOM | eff) (Maybe Node) + :: String + -> Effect (Maybe Node) querySelector s = runFn3 querySelectorImpl Nothing Just s foreign import addEventListener - :: forall eff - . String - -> Eff (dom :: DOM | eff) Unit + :: String + -> Effect Unit -> Node - -> Eff (dom :: DOM | eff) Unit + -> Effect Unit diff --git a/exercises/chapter9/src/Example/LSystem.purs b/exercises/chapter9/src/Example/LSystem.purs index c507b49bf..730c34ce4 100644 --- a/exercises/chapter9/src/Example/LSystem.purs +++ b/exercises/chapter9/src/Example/LSystem.purs @@ -4,8 +4,8 @@ import Prelude import Data.Maybe (Maybe(..)) import Data.Array (concatMap, foldM) -import Control.Monad.Eff (Eff) -import Graphics.Canvas (CANVAS, strokePath, setStrokeStyle, lineTo, moveTo, +import Effect (Effect) +import Graphics.Canvas (strokePath, setStrokeStyle, lineTo, moveTo, getContext2D, getCanvasElementById) import Math as Math import Partial.Unsafe (unsafePartial) @@ -31,7 +31,7 @@ type State = , theta :: Number } -main :: Eff (canvas :: CANVAS) Unit +main :: Effect Unit main = void $ unsafePartial do Just canvas <- getCanvasElementById "canvas" ctx <- getContext2D canvas @@ -45,7 +45,7 @@ main = void $ unsafePartial do productions R = [R] productions F = [F, L, F, R, R, F, L, F] - interpret :: State -> Alphabet -> Eff (canvas :: CANVAS) State + interpret :: State -> Alphabet -> Effect State interpret state L = pure $ state { theta = state.theta - Math.pi / 3.0 } interpret state R = pure $ state { theta = state.theta + Math.pi / 3.0 } interpret state F = do @@ -58,6 +58,6 @@ main = void $ unsafePartial do initialState :: State initialState = { x: 120.0, y: 200.0, theta: 0.0 } - _ <- setStrokeStyle "#000000" ctx + _ <- setStrokeStyle ctx "#000000" strokePath ctx $ lsystem initial productions interpret 5 initialState diff --git a/exercises/chapter9/src/Example/Random.purs b/exercises/chapter9/src/Example/Random.purs index 12c5fde93..408f56754 100644 --- a/exercises/chapter9/src/Example/Random.purs +++ b/exercises/chapter9/src/Example/Random.purs @@ -2,23 +2,23 @@ module Example.Random where import Prelude -import Control.Monad.Eff (Eff) -import Control.Monad.Eff.Random (RANDOM, random) +import Effect (Effect) +import Effect.Random (random) import Data.Array ((..)) import Data.Foldable (for_) import Data.Maybe (Maybe(..)) -import Graphics.Canvas (CANVAS, strokePath, fillPath, arc, setStrokeStyle, - setFillStyle, getContext2D, getCanvasElementById) +import Graphics.Canvas (strokePath, fillPath, arc, setStrokeStyle, setFillStyle, + getContext2D, getCanvasElementById) import Math as Math import Partial.Unsafe (unsafePartial) -main :: Eff (canvas :: CANVAS, random :: RANDOM) Unit +main :: Effect Unit main = void $ unsafePartial do Just canvas <- getCanvasElementById "canvas" ctx <- getContext2D canvas - _ <- setFillStyle "#FF0000" ctx - _ <- setStrokeStyle "#000000" ctx + _ <- setFillStyle ctx "#FF0000" + _ <- setStrokeStyle ctx "#000000" for_ (1 .. 100) \_ -> do x <- random @@ -26,11 +26,11 @@ main = void $ unsafePartial do r <- random let path = arc ctx - { x : x * 600.0 - , y : y * 600.0 - , r : r * 50.0 - , start : 0.0 - , end : Math.pi * 2.0 + { x : x * 600.0 + , y : y * 600.0 + , radius : r * 50.0 + , start : 0.0 + , end : Math.pi * 2.0 } _ <- fillPath ctx path diff --git a/exercises/chapter9/src/Example/Rectangle.purs b/exercises/chapter9/src/Example/Rectangle.purs index 4af93b436..33f0e5730 100644 --- a/exercises/chapter9/src/Example/Rectangle.purs +++ b/exercises/chapter9/src/Example/Rectangle.purs @@ -2,22 +2,22 @@ module Example.Rectangle where import Prelude -import Control.Monad.Eff (Eff) +import Effect (Effect) import Data.Maybe (Maybe(..)) -import Graphics.Canvas (CANVAS, rect, fillPath, setFillStyle, getContext2D, +import Graphics.Canvas (rect, fillPath, setFillStyle, getContext2D, getCanvasElementById) import Partial.Unsafe (unsafePartial) -main :: Eff (canvas :: CANVAS) Unit +main :: Effect Unit main = void $ unsafePartial do Just canvas <- getCanvasElementById "canvas" ctx <- getContext2D canvas - _ <- setFillStyle "#0000FF" ctx + _ <- setFillStyle ctx "#0000FF" fillPath ctx $ rect ctx { x: 250.0 , y: 250.0 - , w: 100.0 - , h: 100.0 + , width: 100.0 + , height: 100.0 } diff --git a/exercises/chapter9/src/Example/Refs.purs b/exercises/chapter9/src/Example/Refs.purs index 64d04bfb4..ac72ddfd6 100644 --- a/exercises/chapter9/src/Example/Refs.purs +++ b/exercises/chapter9/src/Example/Refs.purs @@ -2,65 +2,58 @@ module Example.Refs where import Prelude -import Control.Monad.Eff (Eff) -import Control.Monad.Eff.Console (CONSOLE, log) -import Control.Monad.Eff.DOM (addEventListener, querySelector) -import Control.Monad.Eff.Ref (REF, readRef, modifyRef, newRef) import Data.Foldable (for_) import Data.Int (toNumber) import Data.Maybe (Maybe(..)) -import DOM (DOM) -import Graphics.Canvas (Context2D, CANVAS, getContext2D, getCanvasElementById, - rect, fillPath, translate, scale, rotate, withContext, - setFillStyle) +import Effect (Effect) +import Effect.Console (log) +import Effect.DOM (addEventListener, querySelector) +import Effect.Ref (read, modify_, new) +import Graphics.Canvas (Context2D, getContext2D, getCanvasElementById, rect, fillPath, translate, scale, rotate, withContext, setFillStyle) import Math as Math import Partial.Unsafe (unsafePartial) -render :: forall eff. Int -> Context2D -> Eff (canvas :: CANVAS | eff) Unit +render :: Int -> Context2D -> Effect Unit render count ctx = void do - _ <- setFillStyle "#FFFFFF" ctx + _ <- setFillStyle ctx "#FFFFFF" _ <- fillPath ctx $ rect ctx { x: 0.0 , y: 0.0 - , w: 600.0 - , h: 600.0 + , width: 600.0 + , height: 600.0 } - _ <- setFillStyle "#00FF00" ctx + _ <- setFillStyle ctx "#00FF00" withContext ctx do let scaleX = Math.sin (toNumber count * Math.pi / 4.0) + 1.5 let scaleY = Math.sin (toNumber count * Math.pi / 6.0) + 1.5 - _ <- translate { translateX: 300.0, translateY: 300.0 } ctx - _ <- rotate (toNumber count * Math.pi / 18.0) ctx - _ <- scale { scaleX: scaleX, scaleY: scaleY } ctx - _ <- translate { translateX: -100.0, translateY: -100.0 } ctx + _ <- translate ctx { translateX: 300.0, translateY: 300.0 } + _ <- rotate ctx (toNumber count * Math.pi / 18.0) + _ <- scale ctx { scaleX: scaleX, scaleY: scaleY } + _ <- translate ctx { translateX: -100.0, translateY: -100.0 } fillPath ctx $ rect ctx { x: 0.0 , y: 0.0 - , w: 200.0 - , h: 200.0 + , width: 200.0 + , height: 200.0 } -main :: Eff ( canvas :: CANVAS - , ref :: REF - , dom :: DOM - , console :: CONSOLE - ) Unit +main :: Effect Unit main = void $ unsafePartial do Just canvas <- getCanvasElementById "canvas" ctx <- getContext2D canvas - clickCount <- newRef 0 + clickCount <- new 0 render 0 ctx node <- querySelector "#canvas" for_ node $ addEventListener "click" $ void do log "Mouse clicked!" - modifyRef clickCount \count -> count + 1 - count <- readRef clickCount + modify_ (\count -> count + 1) clickCount + count <- read clickCount render count ctx diff --git a/exercises/chapter9/src/Example/Shapes.purs b/exercises/chapter9/src/Example/Shapes.purs index a2e5850f0..4ee9bd0ab 100644 --- a/exercises/chapter9/src/Example/Shapes.purs +++ b/exercises/chapter9/src/Example/Shapes.purs @@ -2,9 +2,9 @@ module Example.Shapes where import Prelude -import Control.Monad.Eff (Eff) +import Effect (Effect) import Data.Maybe (Maybe(..)) -import Graphics.Canvas (CANVAS, closePath, lineTo, moveTo, fillPath, +import Graphics.Canvas (closePath, lineTo, moveTo, fillPath, setFillStyle, arc, rect, getContext2D, getCanvasElementById) import Math as Math @@ -21,31 +21,31 @@ translate dx dy shape = shape , y = shape.y + dy } -main :: Eff (canvas :: CANVAS) Unit +main :: Effect Unit main = void $ unsafePartial do Just canvas <- getCanvasElementById "canvas" ctx <- getContext2D canvas - _ <- setFillStyle "#0000FF" ctx + _ <- setFillStyle ctx "#0000FF" _ <- fillPath ctx $ rect ctx $ translate (-200.0) (-200.0) { x: 250.0 , y: 250.0 - , w: 100.0 - , h: 100.0 + , width: 100.0 + , height: 100.0 } - _ <- setFillStyle "#00FF00" ctx + _ <- setFillStyle ctx "#00FF00" _ <- fillPath ctx $ arc ctx $ translate 200.0 200.0 { x: 300.0 , y: 300.0 - , r: 50.0 + , radius: 50.0 , start: Math.pi * 5.0 / 8.0 , end: Math.pi * 2.0 } - _ <- setFillStyle "#FF0000" ctx + _ <- setFillStyle ctx "#FF0000" fillPath ctx $ do _ <- moveTo ctx 300.0 260.0