Updates for psc 0.10.5.

- Bumped dependencies
- Use generic rep
- New operator syntax
- New qualified import syntax
This commit is contained in:
Matthew Gordon 2017-02-04 18:47:10 +00:00
parent 3815338f53
commit e392713273
7 changed files with 74 additions and 67 deletions

View File

@ -11,15 +11,15 @@
"output" "output"
], ],
"dependencies": { "dependencies": {
"purescript-console": "^0.1.0", "js-yaml": "^3.4.6",
"js-yaml": "~3.4.6", "purescript-functions": "^2.0.0",
"purescript-functions": "~0.1.0", "purescript-foreign": "^3.2.0",
"purescript-foreign": "~0.7.2", "purescript-foreign-generic": "^3.0.0",
"purescript-generics": "~0.7.0", "purescript-unsafe-coerce": "^2.0.0"
"purescript-foreign-generic": "~0.3.0",
"purescript-unsafe-coerce": "~0.1.0"
}, },
"devDependencies": { "devDependencies": {
"purescript-spec": "~0.7.2" "purescript-console": "^2.0.0",
"purescript-spec": "~0.12.1"
} }
} }

View File

@ -11,7 +11,7 @@ Attempt to parse a YAML string, returning the result as foreign data.
#### `readYAML` #### `readYAML`
``` purescript ``` purescript
readYAML :: forall a. (IsForeign a) => String -> F a readYAML :: forall a. IsForeign a => String -> F a
``` ```
Attempt to parse a YAML string into the datastructure you want. Attempt to parse a YAML string into the datastructure you want.
@ -19,7 +19,7 @@ Attempt to parse a YAML string into the datastructure you want.
#### `readYAMLGeneric` #### `readYAMLGeneric`
``` purescript ``` purescript
readYAMLGeneric :: forall a. (Generic a) => Options -> String -> F a readYAMLGeneric :: forall a rep. (Generic a rep, GenericDecode rep) => Options -> String -> F a
``` ```
Automatically generate a YAML parser for your data from a generic instance. Automatically generate a YAML parser for your data from a generic instance.

View File

@ -15,7 +15,7 @@ type YArray = Array YValue
#### `YAML` #### `YAML`
``` purescript ``` purescript
data YAML :: * data YAML :: Type
``` ```
#### `YValue` #### `YValue`
@ -40,7 +40,7 @@ Eq YValue
#### `ToYAML` #### `ToYAML`
``` purescript ``` purescript
class ToYAML a where class ToYAML a where
toYAML :: a -> YValue toYAML :: a -> YValue
``` ```
@ -60,18 +60,22 @@ ToYAML String
type Pair = Tuple String YValue type Pair = Tuple String YValue
``` ```
#### `(:=)` #### `entry`
``` purescript ``` purescript
(:=) :: forall a. (ToYAML a) => String -> a -> Pair entry :: forall a. ToYAML a => String -> a -> Pair
``` ```
_left-associative / precedence -1_
Helper function to create a key-value tuple for a YAML object. Helper function to create a key-value tuple for a YAML object.
`name = "Name" := "This is the name"` `name = "Name" := "This is the name"`
#### `(:=)`
``` purescript
infixl 4 entry as :=
```
#### `object` #### `object`
``` purescript ``` purescript
@ -109,7 +113,7 @@ toYAMLImpl :: YAML -> String
#### `printYAML` #### `printYAML`
``` purescript ``` purescript
printYAML :: forall a. (ToYAML a) => a -> String printYAML :: forall a. ToYAML a => a -> String
``` ```

View File

@ -1,24 +1,25 @@
module Data.YAML.Foreign.Decode (parseYAML, readYAML, readYAMLGeneric) where module Data.YAML.Foreign.Decode (parseYAML, readYAML, readYAMLGeneric) where
import Control.Bind ((>=>)) import Data.Foreign (F, Foreign, ForeignError(..), fail)
import Data.Either import Data.Foreign.Class (class IsForeign, read)
import Data.Foreign (Foreign (), F (), ForeignError (..)) import Data.Foreign.Generic (readGeneric)
import Data.Foreign.Class (IsForeign, read) import Data.Foreign.Generic.Classes (class GenericDecode)
import Data.Foreign.Generic import Data.Foreign.Generic.Types (Options)
import Data.Function (Fn3(), runFn3) import Data.Function.Uncurried (Fn3, runFn3)
import Data.Generic (Generic) import Data.Generic.Rep (class Generic)
import Prelude (Show, (<<<), (++), (>>=)) import Prelude (pure, (<<<), (>>=), (>=>))
foreign import parseYAMLImpl :: forall r. Fn3 (String -> r) (Foreign -> r) String r foreign import parseYAMLImpl :: forall r. Fn3 (String -> r) (Foreign -> r) String r
-- | Attempt to parse a YAML string, returning the result as foreign data. -- | Attempt to parse a YAML string, returning the result as foreign data.
parseYAML :: String -> F Foreign parseYAML :: String -> F Foreign
parseYAML yaml = runFn3 parseYAMLImpl (Left <<< JSONError) Right yaml parseYAML yaml = runFn3 parseYAMLImpl (fail <<< JSONError) pure yaml
-- | Attempt to parse a YAML string into the datastructure you want. -- | Attempt to parse a YAML string into the datastructure you want.
readYAML :: forall a. (IsForeign a) => String -> F a readYAML :: forall a. (IsForeign a) => String -> F a
readYAML yaml = parseYAML yaml >>= read readYAML yaml = parseYAML yaml >>= read
-- | Automatically generate a YAML parser for your data from a generic instance. -- | Automatically generate a YAML parser for your data from a generic instance.
readYAMLGeneric :: forall a. (Generic a) => Options -> String -> F a readYAMLGeneric :: forall a rep. (Generic a rep, GenericDecode rep) => Options -> String -> F a
readYAMLGeneric opts = parseYAML >=> readGeneric opts readYAMLGeneric opts = parseYAML >=> readGeneric opts

View File

@ -1,11 +1,12 @@
module Data.YAML.Foreign.Encode where module Data.YAML.Foreign.Encode where
import Data.Function (Fn4(), runFn4) import Data.Map as M
import Data.List (fromList, toList) import Data.Array (fromFoldable, toUnfoldable)
import qualified Data.Map as M import Data.Function.Uncurried (Fn4, runFn4)
import Data.Maybe (Maybe (), maybe) import Data.List (List)
import Data.Tuple (Tuple (..), fst, snd) import Data.Maybe (Maybe, maybe)
import Prelude (Eq, Show, map, show, ($), (++), (==), (<<<)) import Data.Tuple (Tuple(..), fst, snd)
import Prelude (class Eq, class Show, map, show, ($), (<>), (==), (<<<))
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
type YObject = M.Map String YValue type YObject = M.Map String YValue
@ -22,12 +23,12 @@ data YValue
| YNull | YNull
instance showYValue :: Show YValue where instance showYValue :: Show YValue where
show (YObject m) = "YObject " ++ show m show (YObject m) = "YObject " <> show m
show (YArray vs) = "YArray " ++ show vs show (YArray vs) = "YArray " <> show vs
show (YString s) = "YString " ++ show s show (YString s) = "YString " <> show s
show (YNumber n) = "YNumber " ++ show n show (YNumber n) = "YNumber " <> show n
show (YInt i) = "YInt " ++ show i show (YInt i) = "YInt " <> show i
show (YBoolean b) = "YBoolean " ++ show b show (YBoolean b) = "YBoolean " <> show b
show YNull = "YNull" show YNull = "YNull"
instance eqYValue :: Eq YValue where instance eqYValue :: Eq YValue where
@ -66,14 +67,16 @@ type Pair = Tuple String YValue
-- | Helper function to create a key-value tuple for a YAML object. -- | Helper function to create a key-value tuple for a YAML object.
-- | -- |
-- | `name = "Name" := "This is the name"` -- | `name = "Name" := "This is the name"`
(:=) :: forall a. (ToYAML a) => String -> a -> Pair entry :: forall a. (ToYAML a) => String -> a -> Pair
(:=) name value = Tuple name (toYAML value) entry name value = Tuple name (toYAML value)
infixl 4 entry as :=
-- | Helper function to create a YAML object. -- | Helper function to create a YAML object.
-- | -- |
-- | `obj = object [ "Name" := "This is the name", "Size" := 1.5 ]` -- | `obj = object [ "Name" := "This is the name", "Size" := 1.5 ]`
object :: Array Pair -> YValue object :: Array Pair -> YValue
object ps = YObject $ M.fromList $ toList $ ps object ps = YObject $ M.fromFoldable (toUnfoldable ps :: List Pair)
foreign import jsNull :: YAML foreign import jsNull :: YAML
foreign import objToHash :: foreign import objToHash ::
@ -84,7 +87,7 @@ foreign import objToHash ::
YAML YAML
valueToYAML :: YValue -> YAML valueToYAML :: YValue -> YAML
valueToYAML (YObject o) = runFn4 objToHash valueToYAML fst snd $ fromList $ M.toList o valueToYAML (YObject o) = runFn4 objToHash valueToYAML fst snd $ fromFoldable $ M.toList o
valueToYAML (YArray a) = unsafeCoerce $ map valueToYAML a valueToYAML (YArray a) = unsafeCoerce $ map valueToYAML a
valueToYAML (YString s) = unsafeCoerce s valueToYAML (YString s) = unsafeCoerce s
valueToYAML (YNumber n) = unsafeCoerce n valueToYAML (YNumber n) = unsafeCoerce n
@ -96,3 +99,4 @@ foreign import toYAMLImpl :: YAML -> String
printYAML :: forall a. (ToYAML a) => a -> String printYAML :: forall a. (ToYAML a) => a -> String
printYAML = toYAMLImpl <<< valueToYAML <<< toYAML printYAML = toYAMLImpl <<< valueToYAML <<< toYAML

View File

@ -1,11 +1,9 @@
module Test.Instances where module Test.Instances where
import Prelude import Prelude (class Eq, class Show, bind, pure, ($))
import Data.Either import Data.Foreign (ForeignError(..), fail, readString)
import Data.Foreign import Data.Foreign.Class (class IsForeign, readProp)
import Data.Foreign.Class import Data.Generic (class Generic, gShow, gEq)
import Data.Generic (Generic, gShow, gEq)
import Data.YAML.Foreign.Encode import Data.YAML.Foreign.Encode
data Point = Point Int Int data Point = Point Int Int
@ -41,21 +39,21 @@ instance archiObjectIsForeign :: IsForeign GeoObject where
points <- readProp "Points" value points <- readProp "Points" value
mobility <- readProp "Mobility" value mobility <- readProp "Mobility" value
coverage <- readProp "Coverage" value coverage <- readProp "Coverage" value
return $ GeoObject { name, scale, points, mobility, coverage } pure $ GeoObject { name, scale, points, mobility, coverage }
instance pointIsForeign :: IsForeign Point where instance pointIsForeign :: IsForeign Point where
read value = do read value = do
x <- readProp "X" value x <- readProp "X" value
y <- readProp "Y" value y <- readProp "Y" value
return $ Point x y pure $ Point x y
instance mobilityIsForeign :: IsForeign Mobility where instance mobilityIsForeign :: IsForeign Mobility where
read value = do read value = do
mob <- readString value mob <- readString value
case mob of case mob of
"Fix" -> return Fix "Fix" -> pure Fix
"Flex" -> return Flex "Flex" -> pure Flex
_ -> Left $ JSONError "Mobility must be either Flex or Fix" _ -> fail $ JSONError "Mobility must be either Flex or Fix"
instance pointToYAML :: ToYAML Point where instance pointToYAML :: ToYAML Point where
toYAML (Point x y) = toYAML (Point x y) =
@ -77,3 +75,4 @@ instance archiObjectToYAML :: ToYAML GeoObject where
, "Mobility" := o.mobility , "Mobility" := o.mobility
, "Coverage" := o.coverage , "Coverage" := o.coverage
] ]

View File

@ -1,19 +1,17 @@
module Test.Main where module Test.Main where
import Prelude import Control.Monad.Eff (Eff)
import Control.Monad.Except (runExcept)
import Data.Either import Data.Either (Either(..))
import Data.Foreign import Data.Foreign (F)
import Control.Monad.Eff import Data.YAML.Foreign.Decode (readYAML)
import Control.Monad.Eff.Console (CONSOLE ()) import Data.YAML.Foreign.Encode (printYAML)
import Prelude (Unit, bind, ($))
import Test.Instances (GeoObject(..), Mobility(..), Point(..))
import Test.Spec (describe, it) import Test.Spec (describe, it)
import Test.Spec.Runner (Process (), run)
import Test.Spec.Assertions (shouldEqual) import Test.Spec.Assertions (shouldEqual)
import Test.Spec.Reporter.Console (consoleReporter) import Test.Spec.Reporter.Console (consoleReporter)
import Test.Spec.Runner (RunnerEffects, run)
import Data.YAML.Foreign.Decode
import Data.YAML.Foreign.Encode
import Test.Instances
yamlInput :: String yamlInput :: String
yamlInput = """ yamlInput = """
@ -85,14 +83,15 @@ parsedData =
} }
] ]
main :: Eff (console :: CONSOLE, process :: Process) Unit main :: Eff (RunnerEffects ()) Unit
main = run [consoleReporter] do main = run [consoleReporter] do
describe "purescript-yaml" do describe "purescript-yaml" do
describe "decode" do describe "decode" do
it "Decodes YAML" do it "Decodes YAML" do
let decoded = (readYAML yamlInput) :: F (Array GeoObject) let decoded = (readYAML yamlInput) :: F (Array GeoObject)
decoded `shouldEqual` (Right parsedData) (runExcept decoded) `shouldEqual` (Right parsedData)
describe "encode" do describe "encode" do
it "Encodes YAML" $ do it "Encodes YAML" $ do
let encoded = printYAML parsedData let encoded = printYAML parsedData
encoded `shouldEqual` yamlOutput encoded `shouldEqual` yamlOutput