let it leave me like a long breath

let it dissipate or fade in the background

(no subject)

Profile

xax: purple-orange {11/3 knotwork star, pointed down (Default)
howling howling howling

Nav

  • Recent Entries
  • Archive
  • Reading
  • Tags
  • Memories
  • Profile

Tags

  • art - 2 uses
  • asteroid garden - 4 uses
  • code - 19 uses
  • demos - 1 use
  • dreams - 5 uses
  • ff7 fangame - 23 uses
  • fic prompts - 13 uses
  • gamedev challenge - 82 uses
  • hell game - 76 uses
  • nanowrimo - 11 uses
  • plants - 9 uses
  • process - 52 uses
  • programming - 51 uses
  • screenshots - 5 uses
  • writing log - 83 uses

May 2025

S M T W T F S
    123
45678 910
1112131415 1617
18192021222324
25262728293031
  • Jul. 23rd, 2017
  • xax: purple-orange {11/3 knotwork star, pointed down (Default)
    [personal profile] xax
    Tags:
    • code,
    • programming
    posted @ 06:21 pm

    this is the more recent and streamlined version of the Enumerable code i mentioned back here.

    module Data.Enumerable
    	( Enumerable (count)
    	, roll
    	, select
    	, enumerate
    
    	, rangeEnum
    	, rangeNum
    	, from
    	) where
    
    import Control.Applicative
    import Data.Maybe (fromMaybe)
    import Utility.Rand
    
    data Enumerable a
    	= EnumerableNil
    	| Enumerable
    		{ count :: Integer
    		, selector :: Integer -> a
    		}
    
    instance Functor Enumerable where
    	fmap f (Enumerable c g) = Enumerable c $ f . g
    	fmap _ EnumerableNil = EnumerableNil
    
    instance Monoid (Enumerable a) where
    	mempty = EnumerableNil
    	mappend = (<|>)
    
    -- one after the other
    instance Applicative Enumerable where
    	pure v = Enumerable 1 $ const v
    	(Enumerable c f) <*> (Enumerable c' g) =
    		Enumerable (c * c') $ \i -> let
    				j = i `mod` c
    				k = i `div` c
    			in f j $ g k
    	-- a zero infects everything else
    	_ <*> _ = EnumerableNil
    
    -- one or the other
    instance Alternative Enumerable where
    	empty = EnumerableNil
    	(Enumerable c v) <|> (Enumerable c' v') = Enumerable (c + c') $ \i -> case i - c of
    		x | x >= 0 -> v' x
    			| otherwise -> v i
    	EnumerableNil <|> f = f
    	f <|> EnumerableNil = f
    
    {-
    instance Monad Enumerable where
    	return = pure
    	(Enumerable c v) >>= f = ...? the thing is we don't really know how the output varies w/ the input. so we MIGHT be like, oh, just evaluate every `i` and then wrap the resulting value up so we have a bunch of Enumerables that we can sequence. but then we have to evaluate every `i`, which is not practical. additionally, we don't know if those variations actually matter: f >>= return == f, but here we'd end up with a very different value. consequently, i don't think it's possible for this to be an Monad instance, even if it is maybe a monad conceptually. or at least, it's certainly not going to be implemented in this fashion.
    	_ >>= _ = EnumerableNil
    
    monad laws:
    	return a >>= f    ≡ f a
    	m >>= return      ≡ m
    	(f >=> g) >=> g   ≡ f >=> (g >=> h)
    		(m >>= f) >>= g ≡ m >>= (\x -> f x >>= g)
    
    instance MonadPlus Enumerable where
    	mzero = EnumerableNil
    	mplus = (<|>)
    -}
    
    roll :: RandomGen g => Enumerable a -> Rand g a
    roll enum = do
    	i <- liftRand $ randomR (0, count enum-1)
    	case select enum i of
    		Nothing -> error $ "incoherent enumerable value"
    		Just x -> return x
    
    select :: Enumerable a -> Integer -> Maybe a
    select enum i
    	| i < 0 || i >= count enum = Nothing
    	| otherwise = Just $ selector enum i
    
    enumerate :: Enumerable a -> [a]
    enumerate enum = fromMaybe (error "incoherent enumerable value") . select enum
    	<$> [0..count enum-1]
    
    -- different ways of specifying a range of values. it's assumed that these atomic elements will have counts less than Int's maxBound and thus can be constructed like this safely.
    rangeEnum :: Enum a => (a, a) -> Enumerable a
    rangeEnum (lo, hi) = Enumerable (fromIntegral all) $ \i -> toEnum $ fromEnum lo + fromIntegral i
    	where
    		all = fromEnum hi - fromEnum lo + 1
    
    rangeNum :: Integral a => (a, a) -> Enumerable a
    rangeNum (lo, hi) = Enumerable (fromIntegral all) $ \i -> lo + fromIntegral i
    	where
    		all = hi - lo + 1
    
    -- this does require evaluating the entire input list, so don't make it too huge
    from :: [a] -> Enumerable a
    from [] = EnumerableNil
    from vs = Enumerable (fromIntegral $ length vs) $ \i -> vs !! fromIntegral i

    • Previous Entry
    • Add Memory
    • Share This Entry
    • Next Entry
    • Reply
Page generated Jan. 5th, 2026 01:49 am
Powered by Dreamwidth Studios

Style Credit

  • Style: (No Theme) for vertical