Skip to content

Instantly share code, notes, and snippets.

@aavogt
Last active May 1, 2016 17:55
Show Gist options
  • Select an option

  • Save aavogt/6105a670be8dd0c48649118c8f4ed3c5 to your computer and use it in GitHub Desktop.

Select an option

Save aavogt/6105a670be8dd0c48649118c8f4ed3c5 to your computer and use it in GitHub Desktop.
applying layout modifiers to existentially quantified layouts
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
import XMonad
import Data.Constraint
-- supplied: seems to be the pattern for layout modifier instances
typicalEntailment :: Read (l' a) :- Read (Mirror l' a)
typicalEntailment = Sub Dict
-- | this newtype captures the idea that `m l a` is
-- a layout if `l a` is a layout. IE. Being a layout is
-- a shorter way to say that a given type has Read and LayoutClass
-- instances.
newtype RLS m a = RLS (forall l. l a -- ^ always ignored (not Proxy because we always have an (l a))
-> (Read (l a), LayoutClass l a)
:- (Read (m l a), LayoutClass (m l) a))
wrap :: forall m a. RLS m a
-> (forall l. (LayoutClass l a, Read (l a)) => l a -> m l a)
-> (Layout a -> Layout a)
wrap (RLS rS) m (Layout la) = case rS la of
Sub Dict -> Layout (m la)
-- there seems to be no way to partially apply the wrap function
-- (since the RLS argument seems to be the same no matter what the layout modifier happens to be)
wrappedMirror :: Layout a -> Layout a
wrappedMirror x = wrap (RLS (\_ -> Sub Dict)) Mirror x
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment