Skip to content

Instantly share code, notes, and snippets.

View kcsongor's full-sized avatar
🤡
':<>:

Csongor Kiss kcsongor

🤡
':<>:
View GitHub Profile
@kcsongor
kcsongor / iTunes.vim
Created March 10, 2018 14:55
Vim: Get currently playing song from iTunes
function! s:current_track()
let queries = ['album of the current track',
\ 'artist of the current track',
\ 'name of the current track',
\ 'the player position']
let query = "osascript -s s -e 'tell application \"iTunes\" to return "
\ . join(queries, ' & "----" & ') . "'"
let song_info = split(split(system(query), "\n")[0][1:-1], "----")
return { 'album' : song_info[0],
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes, TypeApplications, TypeInType, TypeOperators,
ScopedTypeVariables, TypeFamilies, UndecidableInstances,
GADTs, ConstraintKinds, AllowAmbiguousTypes #-}
module Elem where
import Data.Type.Equality
import Data.Kind
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
@kcsongor
kcsongor / BifunctorNoIncoherent.hs
Created January 1, 2018 08:52
Derive Bifunctor with Generics (no incoherent instances)
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
@kcsongor
kcsongor / Bifunctor.hs
Last active October 7, 2019 23:04
Derive Bifunctor with GHC.Generics
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeOperators #-}
module Bifunctor where
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
module Stuck where
data Tag = Tag
type family Fam :: k -> Tag -> k
@kcsongor
kcsongor / OpenKinds.hs
Last active December 26, 2017 22:41
Opening datakinds
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
module OpenKinds where
import GHC.TypeLits (Nat)
type family Wrap :: k -> k
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module StrMapRecord where
{-# LANGUAGE ImpredicativeTypes #-}
{-# LANGUAGE TypeFamilies #-}
module BrokenStar where
type family Break a where
Break (a -> b) = (a, b)
broken :: Break (Applicative f => a -> f a)
broken = undefined