Skip to content

Instantly share code, notes, and snippets.

@chshersh
Last active August 15, 2019 05:27
Show Gist options
  • Star 3 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save chshersh/40ad502ac68c4ae7e34e77af14f085bf to your computer and use it in GitHub Desktop.
Save chshersh/40ad502ac68c4ae7e34e77af14f085bf to your computer and use it in GitHub Desktop.
Emulating array syntax with lens
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ViewPatterns #-}
-- | This module contains some approach for emulating array syntax from
-- imperative languages. The approach emulates only syntax, not efficiency.
-- Though if you like working with persistent arrays it may be good for you.
-- Also it's a fun exercise on lenses.
module ArrayFun where
import Control.Lens
import Control.Monad.State (State, evalState)
import Data.IntMap.Strict (IntMap)
import qualified Data.IntMap.Strict as IM
-- | Type alias for @IntMap Int@. This type basically represents persistent arrays.
type IntArray = IntMap Int
-- | Data type that keeps all arrays created during state action.
data Arrays = Arrays
{ _arrayId :: Int -- ^ Number of created arrays
, _arrays :: IntMap IntArray -- ^ Map from array index to array itself
}
makeLenses ''Arrays
-- | State that tracks all created arrays and provides access to them.
type ArrayState a = State Arrays a
runArray :: ArrayState a -> a
runArray arrayAction = evalState arrayAction (Arrays 0 mempty)
-- | 1-dimensional Array is represented as function from index to reified lens.
type ReifiedArray1D = [Int] -> ReifiedLens' Arrays Int
type Array1D = [Int] -> Lens' Arrays Int
-- | Converts reified array to non-reified.
unreifyArray :: ReifiedArray1D -> Array1D
unreifyArray = fmap runLens
pattern An array <- (unreifyArray -> array)
-- | Creates 1-dimensional array from given list of integers.
newListArray1D :: [Int] -> ArrayState ReifiedArray1D
newListArray1D list = do
let newArray = IM.fromList $ zip [0..] list
lastIndex <- use arrayId
arrayId += 1
arrays.at lastIndex .= Just newArray
let arrayFN [i] = Lens $ singular (arrays.ix lastIndex.ix i)
pure arrayFN
-- | Example of array usage. This approach is very limited. The limitations are:
--
-- * No polymorphic arrays during one state action (though it's possible to have several polymorphic states)
-- * It's not fast because doesn't use mutable arrays
-- * To support multidimensional arrays one should add something new
-- * Not typesafe: one could write array[]
--
-- Though this approach has one significant advantage:
--
-- * It's fun :)
--
secondElement :: Int
secondElement = runArray $ do
An array <- newListArray1D [1,2,3]
array[1] += 2
use $ array[1]
{-
ghci> secondElement
4
-}
@instinctive
Copy link

line 47: PreArray1D => ReifiedArray1D

@chshersh
Copy link
Author

chshersh commented May 5, 2017

@instinctive Thanks! Fixed.

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment