[Haskell-cafe] Aeson parsing of GeoJSON geometries

Adam Bergmark adam at bergmark.nl
Fri Sep 9 13:01:31 UTC 2016


On Thu, Sep 8, 2016 at 1:06 AM, mike thomas <mjt464 at gmail.com> wrote:

> Hi all.
>
> Having returned to commercial software development after a 10 year break
> in environmental regulation and travel, it was not long before I was using
> my favorite language Haskell, fortunately, as part of my job this time.
>
> Haskell has changed in many ways since last I used it, and I am having an
> internal (lack of) knowledge collision with the problem below:
>
> As set out in the example below, given a polygon as GeoJSON from a Postgis
> enabled Postgres datasbase, I want to get to a list of Double tuples:
> [(Double,Double)], using Aeson, to draw some polygons.  I am stopped at the
> point of dismembering the nested coordinate arrays.
>
> With Stackage nightly-2016-09-01 ghci, and the series of functions defined
> at the end of this message, I get a runtime type error regarding Vectors,
> which baffles me.
>
> Question 1. Why does Aeson nest the arrays using list syntax around the
> Array type constructor arguments?
>
This is just the Show instance for Values, you can `encode' to print the
actual json representation.


> Question 2. How do I best convert this part of the AST:
>
> "(Array [Array [Array [Number 4.5305923601,Number 50.6585120423],Array
> [Number 4.5307511543,Number 50.657719833],Array [Number 4.5310580333,Number
> 50.657539732],Array [Number 4.5309023972,Number 50.6584422261],Array
> [Number 4.5308797482,Number 50.6586166629],Array [Number
> 4.5305923601,Number 50.6585120423]]])"
>
> to a list of Double tuples?
>
I usually try to avoid doing custom parsing, it's much easier to use an
existing instance when you can.

Try this:

#!/usr/bin/env stack
-- stack --resolver nightly-2016-09-01 --install-ghc runghc --package aeson
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
module Main (main) where

import GHC.Generics
import Data.Aeson

data Geo = Geo { coordinates :: [[(Double, Double)]] } deriving (Generic,
Show)
instance ToJSON Geo
instance FromJSON Geo

main :: IO ()
main = do
  let ex1 = eitherDecode "[[1,2]]" :: Either String Value
  print ex1
  print $ fmap encode ex1
  let ex2 =
"{\"type\":\"Polygon\",\"coordinates\":[[[4.5305923601,50.6585120423],[4.5307511543,50.657719833],[4.5310580333,50.657539732],[4.5309023972,50.6584422261],[4.5308797482,50.6586166629],[4.5305923601,50.6585120423]]]}"
  print (eitherDecode ex2 :: Either String Geo)



> I've tried several variations of the function dropOuterArray to try and
> resolve this run-time error, with no success.
>
> All help welcome, and thanks for your time
>
> Mike.
>
> ========= GHCI Session With Error ======================
>
> p = parseGeoJSONGeometry "{\"type\":\"Polygon\",\"
> coordinates\":[[[4.5305923601,50.6585120423],[4.5307511543,
> 50.657719833],[4.5310580333,50.657539732],[4.5309023972,
> 50.6584422261],[4.5308797482,50.6586166629],[4.5305923601,
> 50.6585120423]]]}"
>
> p (Just (String "Polygon"),Just (Array [Array [Array [Number
> 4.5305923601,Number 50.6585120423],Array [Number 4.5307511543,Number
> 50.657719833],Array [Number 4.5310580333,Number 50.657539732],Array [Number
> 4.5309023972,Number 50.6584422261],Array [Number 4.5308797482,Number
> 50.6586166629],Array [Number 4.5305923601,Number 50.6585120423]]]))
>
> p1 = dropOuterArrayJ (snd p)
>
> p1 [Array [Array [Number 4.5305923601,Number 50.6585120423],Array [Number
> 4.5307511543,Number 50.657719833],Array [Number 4.5310580333,Number
> 50.657539732],Array [Number 4.5309023972,Number 50.6584422261],Array
> [Number 4.5308797482,Number 50.6586166629],Array [Number
> 4.5305923601,Number 50.6585120423]]]
>
> p2 = dropOuterArray p1
>
> :151:21: error: • Couldn't match type ‘Data.Vector.Vector Value’ with
> ‘Value’ Expected type: Value Actual type: Array • In the first argument of
> ‘dropOuterArray’, namely ‘p1’ In the expression: dropOuterArray p1 In an
> equation for ‘p2’: p2 = dropOuterArray p1
>
> ============ Code ====================
>
> {-# LANGUAGE OverloadedStrings, DeriveGeneric, DeriveAnyClass,
> ScopedTypeVariables, LambdaCase, FlexibleContexts #-}
>
> module GeoJSONGeometry (
>     parseGeoJSONGeometry
>     ,Coordinates
>     ,dropOuterArrayJ
>     ,dropOuterArray
>     ,Pt
>     ,gTypeString
> ) where
>
> import Data.Aeson
> import Data.Aeson.Types --(parse, parseMaybe, parseEither, Value(..))
> import GHC.Generics
> import Data.ByteString.Lazy.Char8
> import Data.HashMap.Strict
> import qualified Data.Vector as V
> import Data.Either.Extra (fromRight)
> import Data.Maybe (fromJust)
> import Control.Applicative
>
> import Codec.Picture
> import Graphics.Rasterific
> import Graphics.Rasterific.Texture
>
> import GHC.Generics
>
>
> parseGeoJSONGeometry gjg =
>  let
>     eresult = (eitherDecode (pack gjg)) :: Either String Object -- Value
> -- Object
>     result = (fromRight eresult)
>     gType = Data.HashMap.Strict.lookup "type" result
>     gCoords = Data.HashMap.Strict.lookup "coordinates" result
>  in
>     (gType, gCoords)
>
> gTypeString (Just (Data.Aeson.Types.String s)) = s
>
> dropOuterArrayJ (Just (Array u)) = u
>
>
> dropOuterArray (Array u) = u
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160909/1c6b12dc/attachment.html>


More information about the Haskell-Cafe mailing list