forked from reanimate/reanimate
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathgif.hs
147 lines (134 loc) · 5.08 KB
/
gif.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
#!/usr/bin/env stack
-- stack runghc --package reanimate
{-# LANGUAGE ApplicativeDo #-}
module Main(main) where
import Control.Lens ((^.))
import Data.Aeson
import Data.Foldable (toList)
import Data.Geospatial (GeoFeature (..),
GeospatialGeometry (..),
PointXY (..), geofeatures,
geometry, retrieveXY,
splitGeoMultiLine,
splitGeoMultiPolygon,
unGeoLine, unGeoPolygon)
import Data.LinearRing (fromLinearRing)
import Data.LineString (fromLineString)
import Graphics.SvgTree (Tree (None))
import Reanimate
import Reanimate.Builtin.Documentation
import Reanimate.GeoProjection
import System.IO.Unsafe
main :: IO ()
main = reanimate $ scene $ do
-- Set the background to 'rtfdBackgroundColor'
newSpriteSVG_ $ mkBackgroundPixel rtfdBackgroundColor
-- We'll be cycling through projections so let's create a variable
-- containing the current projection.
prevProj <- newVar equirectangularP
-- Now we can define a function that animates smoothly from the
-- current projection to a new projection.
let push _label proj = do
prev <- readVar prevProj
play $ animate (\t -> grid $ mergeP prev proj t)
# setDuration morphT -- Set the length of the animation
# signalA (curveS 2) -- Ease in and ease out.
# pauseAtEnd waitT -- Then wait on the last frame.
-- The morph from one projection to another has finished so
-- update the variable with new projection.
writeVar prevProj proj
-- Cycle from 'equirectangularP' through 5 projections and then
-- back to 'equirectangularP'.
push "Mollweide" mollweideP
push "Bottomley 30\\degree" (bottomleyP (toRads 30))
push "Werner" wernerP
push "Foucaut" foucautP
push "Lagrange" lagrangeP
prev <- readVar prevProj
play $ animate (\t -> grid $ mergeP prev equirectangularP t)
# setDuration morphT -- Set the length of the animation
# signalA (curveS 2) -- Ease in and ease out.
# pauseAtEnd waitT -- Then wait on the last frame.
where
waitT = 0 -- Seconds to wait between transformations
morphT = 1 -- Duration (in seconds) of each transformation
-- Draw grid lines and land borders.
grid :: Projection -> SVG
grid p =
withStrokeWidth strokeWidth $
lowerTransformations $
scaleXY screenWidth screenHeight $
translate (-1/2) (-1/2) $
withFillOpacity 0 $ withStrokeColor "black" $
mkGroup
[ mkGroup
[ geometryToSVG p geo
| geo <- landBorders
]
, mkGroup $ map mkLinePath (latitudeLines p ++ longitudeLines p)
]
where
strokeWidth = defaultStrokeWidth * 0.5
latitudeLines :: Projection -> [[(Double, Double)]]
latitudeLines p =
[ latitudeLine (fromToS (-pi) pi (n/(latLines*2)))
| n <- [0 .. latLines*2]]
where
latLines = 2
segments = 100
maxLat = atan (sinh pi)
latitudeLine lam =
[ (x, y)
| n <- [0..segments]
, let phi = fromToS (-maxLat) maxLat (n/segments)
, let XYCoord x y = projectionForward p $ LonLat lam phi ]
longitudeLines :: Projection -> [[(Double, Double)]]
longitudeLines p =
longitudeLine maxLat :
longitudeLine (-maxLat) :
[ longitudeLine (fromToS (-halfPi) halfPi (n/(lonLines*2)))
| n <- [1 .. lonLines*2-1] ]
where
lonLines = 2
segments = 100
maxLat = atan (sinh pi)
longitudeLine phi =
[ (x, y)
| n <- [0..segments]
, let lam = fromToS (-pi) pi (n/segments)
, let XYCoord x y = projectionForward p $ LonLat lam phi ]
landBorders :: [GeospatialGeometry]
landBorders = unsafePerformIO $ do
Just geo <- decodeFileStrict "countries.json"
return
[ feature ^. geometry
| feature <- toList $ geo ^. geofeatures :: [GeoFeature Value]
]
geometryToSVG :: Projection -> GeospatialGeometry -> SVG
geometryToSVG p geo =
case geo of
MultiPolygon mpolygon ->
mkGroup $ map (geometryToSVG p . Polygon) $ toList (splitGeoMultiPolygon mpolygon)
Polygon poly ->
mkGroup
[ mkLinePath section
| section <- pure
[ (x', y')
| PointXY x y <- map retrieveXY (fromLinearRing (head (toList (poly^.unGeoPolygon))))
, let XYCoord x' y' = projectionForward p $ LonLat (x/180*pi) (y/180*pi)
]
]
Line line ->
mkLinePath
[ (x', y')
| PointXY x y <- map retrieveXY (fromLineString (line ^. unGeoLine))
, let XYCoord x' y' = projectionForward p $ LonLat (x/180*pi) (y/180*pi)
]
MultiLine ml ->
mkGroup $ map (geometryToSVG p . Line) $ toList (splitGeoMultiLine ml)
_ -> None
-- Convert degrees to radians
toRads :: Double -> Double
toRads dec = dec/180 * pi
halfPi :: Double
halfPi = pi/2