Skip to content

Commit

Permalink
Merge pull request #8 from alios/to-lens
Browse files Browse the repository at this point in the history
refactored from data-lens to lens
  • Loading branch information
tonymorris committed Nov 2, 2016
2 parents 8455cb8 + c00654f commit 776542b
Show file tree
Hide file tree
Showing 62 changed files with 354 additions and 359 deletions.
6 changes: 2 additions & 4 deletions OSM.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ Description: Parse OpenStreetMap http:\/\/osm.org/ files using HXT into
The Data.Geo.OSM module is the core module that exports all others.
Homepage: https://github.com/tonymorris/geo-osm
Category: Utils
Author: Tony Morris <ʇǝu˙sıɹɹoɯʇ@ןןǝʞsɐɥ>, Thomas DuBuisson
Author: Tony Morris <ʇǝu˙sıɹɹoɯʇ@ןןǝʞsɐɥ>, Thomas DuBuisson, Markus Barenhoff
Maintainer: Tony Morris, Thomas DuBuisson
Copyright: 2009 -- 2012 Tony Morris, Thomas DuBuisson
Build-Type: Simple
Expand All @@ -23,8 +23,7 @@ Library
Build-Depends: base < 5 && >= 3
, hxt >= 9
, containers
, data-lens
, comonad >= 4
, lens
, newtype

GHC-Options: -Wall
Expand Down Expand Up @@ -97,4 +96,3 @@ Library
Data.Geo.OSM.Lens.VL
Data.Geo.OSM.Lens.WaynodesL
Data.Geo.OSM.Lens.ZoomL

29 changes: 15 additions & 14 deletions src/Data/Geo/OSM/Api.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances, FlexibleInstances #-}

-- | The @api@ element of a OSM file.
Expand All @@ -12,17 +13,22 @@ import Data.Geo.OSM.Version
import Data.Geo.OSM.Area
import Data.Geo.OSM.Tracepoints
import Data.Geo.OSM.Waynodes
import Data.Lens.Common
import Control.Comonad.Trans.Store
import Control.Lens.TH

import Data.Geo.OSM.Lens.VersionL
import Data.Geo.OSM.Lens.AreaL
import Data.Geo.OSM.Lens.TracepointsL
import Data.Geo.OSM.Lens.WaynodesL

-- | The @api@ element of a OSM file.
data Api =
Api Version Area Tracepoints Waynodes
deriving Eq
data Api = Api {
_apiVersion :: Version,
_apiArea :: Area,
_apiTracepoints :: Tracepoints,
_apiWaynodes :: Waynodes
} deriving Eq

makeLenses ''Api

-- | Constructs a @api@ with version, area, tracepoints and waynodes.
api ::
Expand All @@ -43,18 +49,13 @@ instance Show Api where
showPickled []

instance VersionL Api Version where
versionL =
Lens $ \(Api version area tracepoints waynodes) -> store (\version -> Api version area tracepoints waynodes) version
versionL = apiVersion

instance AreaL Api where
areaL =
Lens $ \(Api version area tracepoints waynodes) -> store (\area -> Api version area tracepoints waynodes) area
areaL = apiArea

instance TracepointsL Api where
tracepointsL =
Lens $ \(Api version area tracepoints waynodes) -> store (\tracepoints -> Api version area tracepoints waynodes) tracepoints
tracepointsL = apiTracepoints

instance WaynodesL Api where
waynodesL =
Lens $ \(Api version area tracepoints waynodes) -> store (\waynodes -> Api version area tracepoints waynodes) waynodes

waynodesL = apiWaynodes
8 changes: 4 additions & 4 deletions src/Data/Geo/OSM/Area.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,8 +9,8 @@ module Data.Geo.OSM.Area

import Text.XML.HXT.Arrow.Pickle
import Data.Geo.OSM.Lens.MaximumL
import Data.Lens.Common
import Control.Comonad.Trans.Store
import Control.Lens.Lens

import Control.Newtype

-- | The @area@ element of a OSM file.
Expand All @@ -35,10 +35,10 @@ instance Show Area where

instance MaximumL Area where
maximumL =
Lens $ \(Area maximum) -> store (\maximum -> Area maximum) maximum
lens unpack (const pack)

instance Newtype Area String where
pack =
pack =
Area
unpack (Area x) =
x
19 changes: 10 additions & 9 deletions src/Data/Geo/OSM/Bound.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
-- | The @bound@ element of a OSM file.
module Data.Geo.OSM.Bound
(
Expand All @@ -8,13 +9,15 @@ module Data.Geo.OSM.Bound
import Text.XML.HXT.Arrow.Pickle
import Data.Geo.OSM.Lens.BoxL
import Data.Geo.OSM.Lens.OriginL
import Data.Lens.Common
import Control.Comonad.Trans.Store
import Control.Lens.TH

-- | The @bound@ element of a OSM file.
data Bound =
Bound String (Maybe String)
deriving Eq
data Bound = Bound {
_boundBox :: String,
_boundOrigin :: Maybe String
} deriving Eq
makeLenses ''Bound


instance XmlPickler Bound where
xpickle =
Expand All @@ -25,12 +28,10 @@ instance Show Bound where
showPickled []

instance BoxL Bound where
boxL =
Lens $ \(Bound box origin) -> store (\box -> Bound box origin) box
boxL = boundBox

instance OriginL Bound where
originL =
Lens $ \(Bound box origin) -> store (\origin -> Bound box origin) origin
originL = boundOrigin

-- | Constructs a bound with a box and origin attributes.
bound ::
Expand Down
15 changes: 14 additions & 1 deletion src/Data/Geo/OSM/BoundOption.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
-- | A bound-option is either a @Bound@, @Bounds@ or empty.
module Data.Geo.OSM.BoundOption
(
BoundOption
BoundOption, _BoundOptions
, foldBoundOption
, optionBound
, optionBounds
Expand All @@ -10,13 +10,26 @@ module Data.Geo.OSM.BoundOption

import Data.Geo.OSM.Bound
import Data.Geo.OSM.Bounds
import Control.Lens.Iso


data BoundOption =
OptionBound Bound
| OptionBounds Bounds
| Empty
deriving Eq

_BoundOptions :: Iso' (Maybe (Either Bound Bounds)) BoundOption
_BoundOptions = iso toBoundOptions fromBoundOptions
where
toBoundOptions Nothing = optionEmptyBound
toBoundOptions (Just (Left b)) = optionBound b
toBoundOptions (Just (Right b)) = optionBounds b
fromBoundOptions Empty = Nothing
fromBoundOptions (OptionBound b) = Just (Left b)
fromBoundOptions (OptionBounds b) = Just (Right b)


foldBoundOption ::
(Bound -> x)
-> (Bounds -> x)
Expand Down
31 changes: 16 additions & 15 deletions src/Data/Geo/OSM/Bounds.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
-- | The @bounds@ element of a OSM file.
module Data.Geo.OSM.Bounds
(
Expand All @@ -11,13 +12,18 @@ import Data.Geo.OSM.Lens.MaxlatL
import Data.Geo.OSM.Lens.MinlonL
import Data.Geo.OSM.Lens.MaxlonL
import Data.Geo.OSM.Lens.OriginL
import Data.Lens.Common
import Control.Comonad.Trans.Store
import Control.Lens.TH

-- | The @bounds@ element of a OSM file.
data Bounds =
Bounds String String String String (Maybe String)
deriving Eq
data Bounds = Bounds {
_boundsMinLat :: String,
_boundsMinLon :: String,
_boundsMaxLat :: String,
_boundsMaxLon :: String,
_boundsOrigin :: Maybe String
} deriving Eq

makeLenses ''Bounds

instance XmlPickler Bounds where
xpickle =
Expand All @@ -29,24 +35,19 @@ instance Show Bounds where
showPickled []

instance MinlatL Bounds where
minlatL =
Lens $ \(Bounds minlat minlon maxlat maxlon origin) -> store (\minlat -> Bounds minlat minlon maxlat maxlon origin) minlat
minlatL = boundsMinLat

instance MinlonL Bounds where
minlonL =
Lens $ \(Bounds minlat minlon maxlat maxlon origin) -> store (\minlon -> Bounds minlat minlon maxlat maxlon origin) minlon
minlonL = boundsMinLon

instance MaxlatL Bounds where
maxlatL =
Lens $ \(Bounds minlat minlon maxlat maxlon origin) -> store (\maxlat -> Bounds minlat minlon maxlat maxlon origin) maxlat
maxlatL = boundsMaxLat

instance MaxlonL Bounds where
maxlonL =
Lens $ \(Bounds minlat minlon maxlat maxlon origin) -> store (\maxlon -> Bounds minlat minlon maxlat maxlon origin) maxlon
maxlonL = boundsMaxLon

instance OriginL Bounds where
originL =
Lens $ \(Bounds minlat minlon maxlat maxlon origin) -> store (\origin -> Bounds minlat minlon maxlat maxlon origin) origin
originL = boundsOrigin

-- | Constructs a bounds with a minlat, minlon, maxlat, maxlon and origin attributes.
bounds ::
Expand Down
8 changes: 3 additions & 5 deletions src/Data/Geo/OSM/Changeset.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,7 @@ module Data.Geo.OSM.Changeset
import Text.XML.HXT.Arrow.Pickle
import Data.Geo.OSM.Tag
import Data.Geo.OSM.Lens.TagsL
import Data.Lens.Common
import Control.Comonad.Trans.Store
import Control.Lens.Lens
import Control.Newtype

-- | The @changeset@ element of a OSM file.
Expand All @@ -36,11 +35,10 @@ instance Show Changeset where

instance TagsL Changeset where
tagsL =
Lens $ \(Changeset tags) -> store (\tags -> Changeset tags) tags
lens unpack (const pack)

instance Newtype Changeset [Tag] where
pack =
pack =
Changeset
unpack (Changeset x) =
x

46 changes: 23 additions & 23 deletions src/Data/Geo/OSM/GpxFile.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances, FlexibleInstances #-}
{-# LANGUAGE TemplateHaskell, MultiParamTypeClasses, TypeSynonymInstances, FlexibleInstances #-}

-- | The @gpx_file@ element of a OSM file.
module Data.Geo.OSM.GpxFile
Expand All @@ -17,13 +17,22 @@ import Data.Geo.OSM.Lens.UserL
import Data.Geo.OSM.Lens.PublicL
import Data.Geo.OSM.Lens.PendingL
import Data.Geo.OSM.Lens.TimestampL
import Data.Lens.Common
import Control.Comonad.Trans.Store
import Control.Lens.TH


-- | The @gpx_file@ element of a OSM file.
data GpxFile =
GpxFile String String String String String Bool Bool String
deriving Eq
data GpxFile = GpxFile {
_gpxFileId :: String,
_gpxFileName :: String,
_gpxFileLat :: String,
_gpxFileLon :: String,
_gpxFileUser :: String,
_gpxFilePublic ::Bool,
_gpxFilePending :: Bool,
_gpxFileTimestamp :: String
} deriving Eq

makeLenses ''GpxFile

-- | Constructs a @gpx_file@ with an id, name, lat, lon, user, public, pending and timestamp.
gpxFile ::
Expand Down Expand Up @@ -52,34 +61,25 @@ instance Show GpxFile where
showPickled []

instance IdL GpxFile where
idL =
Lens $ \(GpxFile id name lat lon user public pending timestamp) -> store (\id -> GpxFile id name lat lon user public pending timestamp) id
idL = gpxFileId

instance NameL GpxFile where
nameL =
Lens $ \(GpxFile id name lat lon user public pending timestamp) -> store (\name -> GpxFile id name lat lon user public pending timestamp) name
nameL = gpxFileName

instance LatL GpxFile where
latL =
Lens $ \(GpxFile id name lat lon user public pending timestamp) -> store (\lat -> GpxFile id name lat lon user public pending timestamp) lat
latL = gpxFileLat

instance LonL GpxFile where
lonL =
Lens $ \(GpxFile id name lat lon user public pending timestamp) -> store (\lon -> GpxFile id name lat lon user public pending timestamp) lon
lonL = gpxFileLon

instance UserL GpxFile String where
userL =
Lens $ \(GpxFile id name lat lon user public pending timestamp) -> store (\user -> GpxFile id name lat lon user public pending timestamp) user
userL = gpxFileUser

instance PublicL GpxFile where
publicL =
Lens $ \(GpxFile id name lat lon user public pending timestamp) -> store (\public -> GpxFile id name lat lon user public pending timestamp) public
publicL = gpxFilePublic

instance PendingL GpxFile where
pendingL =
Lens $ \(GpxFile id name lat lon user public pending timestamp) -> store (\pending -> GpxFile id name lat lon user public pending timestamp) pending
pendingL = gpxFilePending

instance TimestampL GpxFile String where
timestampL =
Lens $ \(GpxFile id name lat lon user public pending timestamp) -> store (\timestamp -> GpxFile id name lat lon user public pending timestamp) timestamp

timestampL = gpxFileTimestamp
25 changes: 13 additions & 12 deletions src/Data/Geo/OSM/Home.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
-- | The @home@ element of a OSM file.
module Data.Geo.OSM.Home
(
Expand All @@ -9,13 +10,17 @@ import Text.XML.HXT.Arrow.Pickle
import Data.Geo.OSM.Lens.LatL
import Data.Geo.OSM.Lens.LonL
import Data.Geo.OSM.Lens.ZoomL
import Data.Lens.Common
import Control.Comonad.Trans.Store


import Control.Lens.TH

-- | The @home@ element of a OSM file.
data Home =
Home String String String
deriving Eq
data Home = Home {
_homeLat :: String,
_homeLon :: String,
_homeZoom :: String
} deriving Eq
makeLenses ''Home

-- | Constructs a @home@ with lat, lon and zoom.
home ::
Expand All @@ -35,14 +40,10 @@ instance Show Home where
showPickled []

instance LatL Home where
latL =
Lens $ \(Home lat lon zoom) -> store (\lat -> Home lat lon zoom) lat
latL = homeLat

instance LonL Home where
lonL =
Lens $ \(Home lat lon zoom) -> store (\lon -> Home lat lon zoom) lon
lonL = homeLon

instance ZoomL Home where
zoomL =
Lens $ \(Home lat lon zoom) -> store (\zoom -> Home lat lon zoom) zoom

zoomL = homeZoom
6 changes: 3 additions & 3 deletions src/Data/Geo/OSM/Lens/AccountCreatedL.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
-- | Values with a @account_created@ string accessor.
module Data.Geo.OSM.Lens.AccountCreatedL where

import Data.Lens.Common
import Control.Lens.Lens

class AccountCreatedL a where
accountCreatedL ::
Lens a String
accountCreatedL ::
Lens' a String
Loading

0 comments on commit 776542b

Please sign in to comment.