#if __GLASGOW_HASKELL__ >= 710
#endif
module Numeric.Natural.Lens
( _Pair
, _Sum
, _Naturals
#if __GLASGOW_HASKELL__ >= 710
, pattern Pair
, pattern Sum
, pattern Naturals
#endif
) where
import Control.Lens
import Numeric.Natural
_Pair :: Iso' Natural (Natural, Natural)
_Pair = iso hither (uncurry yon) where
yon 0 0 = 0
yon m n = case quotRem m 2 of
(q,r) -> r + 2 * yon n q
hither 0 = (0,0)
hither n = case quotRem n 2 of
(p,r) -> case hither p of
(x,y) -> (r+2*y,x)
_Sum :: Iso' Natural (Either Natural Natural)
_Sum = iso hither yon where
hither p = case quotRem p 2 of
(q,0) -> Left q
(q,1) -> Right q
_ -> error "_Sum: impossible"
yon (Left q) = 2*q
yon (Right q) = 2*q+1
_Naturals :: Iso' Natural [Natural]
_Naturals = iso hither yon where
hither 0 = []
hither n | (h, t) <- (n1)^._Pair = h : hither t
yon [] = 0
yon (x:xs) = 1 + review _Pair (x, yon xs)
#if __GLASGOW_HASKELL__ >= 710
pattern Pair :: Natural -> Natural -> Natural
pattern Pair x y <- (view _Pair -> (x,y)) where
Pair x y = review _Pair (x,y)
pattern Sum :: Either Natural Natural -> Natural
pattern Sum s <- (view _Sum -> s) where
Sum s = review _Sum s
pattern Naturals :: [Natural] -> Natural
pattern Naturals xs <- (view _Naturals -> xs) where
Naturals xs = review _Naturals xs
#endif