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
  • Nov. 10th, 2015
  • xax: purple-orange {11/3 knotwork star, pointed down (Default)
    [personal profile] xax
    • Current Music: Dee D Jackson - Automatic Lover
    Tags:
    • code,
    • programming
    posted @ 01:04 pm

    ha ha ha ha it works it worksssssss

    {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FunctionalDependencies,
    OverlappingInstances,
    UndecidableInstances, TypeFamilies,
    TypeOperators, ViewPatterns, FlexibleContexts #-}
    
    module Generation.Layer.Render
      ( Extract(extract)
      , render
      , (?)(..)
      , Term (..)
      , Extend (..)
      ) where
    
    import Prelude hiding (map)
    
    import Data.Map
    
    render :: Extract from (Map k v) => from -> (v -> r) -> Map k r
    render t f = map f . extract $ t
    
    infixr 5 ?
    data a ? b = a :? Maybe b
    
    class Extract from result where
      extract :: from -> result
    
    instance (Term from k v) => Extract from (Map k v) where
        extract = final
    
    -- OVERLAPPING
    instance (Extend from from' j k v, Extract from' (Map j v'), Show k, Ord k) => Extract from (Map k (v' ? v)) where
        extract v = case next v of
            (rs, n) -> n `unify` (rekey v) (extract rs)
    
    class Term t k v | t -> k v where
      final :: t -> Map k v
    
    class Extend e t j k v | e -> t j k v where
      next :: e -> (t, Map k v)
      rekey :: e -> Map j a -> Map k a
    
    unify :: (Ord k, Show k) => Map k a -> Map k b -> Map k (b ? a)
    unify = mergeWithKey
      (\_ a b -> Just (b :? Just a))
      (mapWithKey $ \k b -> error $ "unify: bad generation @ " ++ show k ++ ".")
      (map $ \b -> b :? Nothing)


    (those Show instances aren't really needed except for when i crash on a bad generation, b/c uhhhh it seemed like i wanted at least some vague detail if that situation ever crops up)

    this provides an Extract type class with a single function, extract. this type class is let's say creatively instanced so that i can extract any depth of generator (the Term and Extend typeclasses) into a set of values. this makes it possible to write a render function that takes any extractable value (i.e., any generator stack regardless of depth) and a function that renders based on those values, while still typechecking to make sure the types match. (previously: i needed separate functions for each depth of generator)

    the punchline to all of this is that in nearly all practical situations you really don't need or want to render the entire generation stack; you just want to render the final value, which it's always been trivial to extract. but this lets you make debug overlays and fancy generation visualizations, so of course it's useful!!

    • Previous Entry
    • Add Memory
    • Share This Entry
    • Next Entry
    • Reply
Page generated Jan. 23rd, 2026 04:50 pm
Powered by Dreamwidth Studios

Style Credit

  • Style: (No Theme) for vertical