[Haskell-cafe] Install wx on Windows XP

2013-03-26 Thread Eric Wong
Hi Haskellers,

I'm trying to install wxHaskell on Windows XP. I have already installed Haskell 
Platform 2012.04.0.0, MinGW and wxWidgets. When I try to install wx, I got the 
following error when cabal is installing wxcore:

$ cabal install wx
Resolving dependencies...
[1 of 1] Compiling Main ( C:\DOCUME~1\ADMINI~1\LOCALS~1\Temp\wxcore-
0.90.0.3-896\wxcore-0.90.0.3\Setup.hs, C:\DOCUME~1\ADMINI~1\LOCALS~1\Temp\wxcore
-0.90.0.3-896\wxcore-0.90.0.3\dist\setup\Main.o )
Linking C:\DOCUME~1\ADMINI~1\LOCALS~1\Temp\wxcore-0.90.0.3-896\wxcore-0.90.0.3\d
ist\setup\setup.exe ...
Configuring wxcore-0.90.0.3...
Generating class type definitions from .h files
generating: src/haskell/Graphics/UI/WXCore/WxcClassTypes.hs
reading class definitions:
parsing: C:\Documents/include/wxc.h
wxdirect: C:\Documents/include/wxc.h: openFile: does not exist (No such file or
directory)
Generating class info definitions
generating: src/haskell/Graphics/UI/WXCore/WxcClassInfo.hs
reading class definitions:
parsing: C:\Documents/include/wxc.h
wxdirect: C:\Documents/include/wxc.h: openFile: does not exist (No such file or
directory)
Generating class method definitions from .h files
parsing: Data\cabal\wxc-0.90.0.4\ghc-7.4.2\include/wxc.h
wxdirect: Data\cabal\wxc-0.90.0.4\ghc-7.4.2\include/wxc.h: openFile: does not ex
ist (No such file or directory)
Building wxcore-0.90.0.3...
Preprocessing library wxcore-0.90.0.3...

src\haskell\Graphics\UI\WXCore\WxcClassTypes.hs:1:1:
File name does not match module name:
Saw: `Main'
Expected: `Graphics.UI.WXCore.WxcClassTypes'
cabal.exe: Error: some packages failed to install:
wx-0.90.0.1 depends on wxcore-0.90.0.3 which failed to install.
wxcore-0.90.0.3 failed during the building phase. The exception was:
ExitFailure 1

It looks like it's confused by the spaces in the path and can't find the wxc.h 
file. I tried to configure cabal to install all user packages into a simpler 
directory. But cabal always install to the C:\Documents and 
Settings\Administrator\Application Data\cabal directory no matter how I change 
the config file there.
Anyone knows how to fix this problem or change cabal directory on Windows? 
Thanks.

p.s. I'm using the user Administrator.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] typed final-tagless HOAS interpreter for linear lambda calculus

2013-03-26 Thread jeff p
{-

This message presents a typed final-tagless HOAS interpreter for
linear lambda calculus (LLC), which makes use of type families and
datatype promotion. This code is inspired by Oleg's LLC interpreter
using deBruijn indices
(http://okmij.org/ftp/tagless-final/course/LinearLC.hs).

The basic technique used here, and in Oleg's representation, comes
from work on linear logic programming (see
http://www.cs.cmu.edu/~fp/papers/erm97.pdf for details). An explicit
presentation of LLC using these ideas can be found here
http://www.cs.cmu.edu/~fp/courses/15816-f01/handouts/linfp.pdf [0].

While only the two arrow types and ints are included in this message;
it is straightforward to extend this interpreter to cover all types of
LLC. Attached to this message is an interpreter for full LLC
(including additives and units) which is a direct transcription of the
typing rules previously mentioned in [0]. The code for full LLC is
written using MPTC and functional dependencies, instead of type
families, but it is easily translatable to type families.

-}

{-# LANGUAGE
  DataKinds,
  KindSignatures,
  RankNTypes,
  TypeFamilies,
  TypeOperators,
  UndecidableInstances
 #-}

{-

The basic idea is to label each linear variable with a number and keep
track of the linear context in the type of the representation. Thus
our representation type looks like:

repr :: Nat - [Maybe Nat] - [Maybe Nat] - * - *
repr vid hi ho a

where vid is the next variable label to use, hi is the input linear
hypotheses, ho is the output linear hypotheses, and a is the type of
the term.

-}

-- Type-level Nat
--
data Nat = Z | S Nat

-- Type-level equality for Nat
--
type family EqNat (x::Nat) (y::Nat) :: Bool
type instance EqNat Z Z = True
type instance EqNat (S x) (S y) = EqNat x y
type instance EqNat Z (S y) = False
type instance EqNat (S x) Z = False

{-

The key to enforcing linearity, is to have the type system consume
(mark as used) linear variables as they are used. We use promoted
[Maybe Nat] to represent a linear context.

-}

-- Type-level function to consume a given resource (a Maybe Nat) form a
list.
--
type family Consume (vid::Nat) (i::[Maybe Nat]) :: [Maybe Nat]
type family Consume1 (b::Bool) (vid::Nat) (v::Nat) (vs::[Maybe Nat]) ::
[Maybe Nat]
type instance Consume vid (Nothing ': vs) = (Nothing ': Consume vid vs)
type instance Consume vid (Just v ': vs) = Consume1 (EqNat vid v) vid v vs
type instance Consume1 True vid v vs = Nothing ': vs
type instance Consume1 False vid v vs = Just v ': Consume vid vs

{-

HOAS boils down to having the obect langauge (LLC) directly use the
meta language (Haskell) variable and substitution machinery. So a
typical HOAS representation of an object level function looks
something like:

lam :: (repr a - repr b) - repr (a - b)

The key to making HOAS work with our representation, is to have our
object level variables make use of the Consume function above. Toward
this end, we can create a general linear variable type.

-}

type VarTp (repr :: Nat - [Maybe Nat] - [Maybe Nat] - * - *) vid a =
forall v i o . repr v i (Consume vid i) a

{-

We can now write the representation of the LLC terms. Note that the
type of each LLC term constructor (each member of class Lin) is a
transcription of a typing rule for LLC.

-}

-- a type to distinguish linear functions from regular functions
--
newtype a - b = Lolli {unLolli :: a - b}

-- the Symantics of LLC
--
class Lin (repr :: Nat - [Maybe Nat] - [Maybe Nat] - * - *) where
-- a base type
int :: Int - repr vid hi hi Int
add :: repr vid hi h Int - repr vid h ho Int - repr vid hi ho Int

-- linear lambda
llam :: (VarTp repr vid a - repr (S vid) (Just vid ': hi) (Nothing ':
ho) b) - repr vid hi ho (a - b)
(^) :: repr vid hi h (a - b) - repr vid h ho a - repr vid hi ho b

-- non-linear lambda
lam :: ((forall v h . repr v h h a) - repr vid hi ho b) - repr vid hi
ho (a - b)
($) :: repr vid hi ho (a - b) - repr vid ho ho a - repr vid hi ho b

{-

An evaluator which takes a LLC term of type a to a Haskell value of
type a.

-}
newtype R (vid::Nat) (i::[Maybe Nat]) (o::[Maybe Nat]) a = R {unR :: a}

instance Lin R where
int = R
add x y = R $ unR x + unR y

llam f = R $ Lolli $ \x - unR (f (R x))
f ^ x = R $ unLolli (unR f) (unR x)

lam f = R $ \x - unR (f (R x))
f $ x = R $ unR f (unR x)

eval :: R Z '[] '[] a - a
eval = unR

{-

Some examples:

*Main :t eval $ llam $ \x - x
eval $ llam $ \x - x :: b - b

*Main :t eval $ llam $ \x - add x (int 1)
eval $ llam $ \x - add x (int 1) :: Int - Int

*Main eval $ (llam $ \x - add x (int 1)) ^ int 2
3

A non-linear uses of linear variables fail to type check:

*Main :t eval $ llam $ \x - add x x

interactive:1:27:
Couldn't match type `Consume 'Z ('[] (Maybe Nat))'
  with '[] (Maybe Nat)
Expected type: R ('S 'Z)
 ((':) (Maybe Nat) ('Nothing Nat) ('[] (Maybe Nat)))
   

Re: [Haskell-cafe] Make a DSL serializable

2013-03-26 Thread luc taesch


On 2013-03-25 19:00:42 +, Alberto G. Corona said:

It is  possible as long as there is a empty event and there is a 
operation that mix two events to créate an state and an operation that 
mix an state and a event to créate an state.


I just read thisat a time I am learning FRP Reactive banana
and these two collides :  Workflow (Event, state) ~ FRP (Event, bahavior)

is that anyway connected, Alberto ? ( workflow and FRP )
( are worflow are serializable persitent FRP Network ?)


-




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] my take at knucleotide

2013-03-26 Thread Branimir Maksimovic
Finally, I have made it ;)Trick was in more threads . For some reason if I run 
64 (sweet spot) threads program runsfaster both with -threaded and without 
;)Other trick is that I don't convert to uppercase (shaves second) rather pack 
nucleotidein 64 bit int.Program runs 30% faster multithreaded (scales better) 
than current entry, and consumes 50% less memory,and is shorter.If someone can 
see some improvement please post, otherwise I will contribute this program.

{-# Language BangPatterns #-} The Computer Language Benchmarks Game-- 
http://benchmarksgame.alioth.debian.org/ Contributed by Branimir 
Maksimovic--import Data.Bitsimport Data.Charimport Data.Intimport 
Data.Listimport Data.IORefimport Data.Array.Unboxedimport Data.Array.Baseimport 
qualified Data.HashTable.IO as Himport Data.Hashableimport qualified 
Data.ByteString.Char8 as Simport Control.Concurrentimport Text.Printf
main = dos - S.getContentslet(_,subs) = S.breakSubstring 
(S.pack THREE) scontent = (S.filter ((/=) '\n') .
S.dropWhile ((/=) '\n')) subs mapM_ (execute content) actions
data Actions = I Int | S Stringactions = [I 1,I 2,  
 S GGT,S GGTA,S GGTATT,S GGTAAATT,S GGTAAATTTATAGT]execute 
content (I i) = writeFrequencies content iexecute content (S s) = writeCount 
content s
writeFrequencies :: S.ByteString - Int - IO ()writeFrequencies input size = 
doht - tcalculate input sizelst - H.foldM (\lst (k,v)-do v' 
- readIORef vreturn $ insertBy (\(_,x) (_,y)-y `compare` x) (k,v') 
lst) [] htlet sum = fromIntegral ((S.length input) + 1 - size)mapM_ 
(\(k,v)- doprintf %s %.3f\n (toString k) ((100 * 
(fromIntegral v)/sum)::Double)) lstputChar '\n'
writeCount :: S.ByteString - String - IO ()writeCount input string = do
let size = length stringht - tcalculate input sizelet k = T (toNum 
(S.pack string) 0 size) sizeres - H.lookup ht kcase res of 
Nothing - putStrLn $ string ++  not found...Just v - do
r - readIORef vprintf %d\t%s\n r string
tcalculate :: S.ByteString - Int - IO HMtcalculate input size = dolet 
l = [0..63]actions = map (\i - (calculate input i size (length 
l))) lvars - mapM (\action - dovar - newEmptyMVar
forkIO $ doanswer - action 
   putMVar var answerreturn var) actionsresult 
- newTable :: IO HMresults - mapM takeMVar varsmapM_ (\ht - H.foldM 
(\lst (k,v) - do res - H.lookup lst k 
   case res ofNothing - do 
   r1 - readIORef v
r2 - newIORef r1H.insert lst k r2  
  Just v1 - dor1 - 
readIORef v1r2 - readIORef v   
 writeIORef v1 (r1+r2)return 
lst) result ht) resultsreturn result
calculate :: S.ByteString - Int - Int - Int - IO HMcalculate input beg 
size incr = do!ht - newTable :: IO HMletcalculate' i  
| i = ((S.length input)+1 - size) = return ht | otherwise = do 
   res - H.lookup ht kcase res ofNothing - do 
   !r - newIORef 1H.insert ht k r  
  Just v - do!r - readIORef v
writeIORef v (r+1)calculate' (i+incr)where k = T 
(toNum input i size) sizecalculate' beg
toNum :: S.ByteString - Int - Int - Int64toNum s beg size = toNum' 0 size
wheretoNum' v 0 = vtoNum' v i = toNum' ((v `shiftL` 2) .|.  
   (toNumA `unsafeAt` (ord (S.index s (beg+i-1) (i-1)
toString :: T - StringtoString (T v s) = toString' v swhere
toString' v 0 = []toString' v i = case v..3 of
0 - 'A'1 - 'C'2 - 'T'
3 - 'G'  : toString' (v `shiftR` 2) (i-1)
toNumA :: UArray Int Int64toNumA = array (0,255) [(ord 'a',0),(ord 'c',1),(ord 
't',2),(ord 'g',3),(ord 'A',0),(ord 'C',1),(ord 'T',2),(ord 'G',3)]
data T = T !Int64 !Intinstance Eq T where(T a _) == (T b _) = a == 
binstance Hashable T wherehashWithSalt _ (T a _) = fromIntegral a
type HM = H.BasicHashTable T (IORef Int)newTable = H.new

Date: Sun, 24 Mar 2013 20:12:57 +0100
Subject: Re: [Haskell-cafe] my take at knucleotide
From: g...@gregorycollins.net
To: bm...@hotmail.com
CC: haskell-cafe@haskell.org

What happens to performance if you compile and link with cabal install 
--constraint='hashable  1.2' ?
G


  

Re: [Haskell-cafe] Pattern matching with singletons

2013-03-26 Thread Richard Eisenberg
Hello Paul,

 - Forwarded message from Paul Brauner polux2...@gmail.com -

snip

   - is a ~ ('CC ('Left 'CA)) a consequence of the definitions of SCC,
   SLeft, ... (in which case GHC could infer it but for some reason can't)
   - or are these pattern + definitions not sufficient to prove that a
   ~ ('CC ('Left 'CA)) no matter what?

The first one. GHC can deduce that (a ~ ('CC ('Left b))), for some fresh 
variable (b :: TA), but it can't yet take the next step and decide that, 
because TA has only one constructor, b must in fact be 'CA. In type-theory 
lingo, this deduction is called eta-expansion. There have been on-and-off 
debates about how best to add this sort of eta-expansion into GHC, but all seem 
to agree that it's not totally straightforward. For example, see GHC bug #7259. 
There's a non-negligible chance I will be taking a closer look into this at 
some point, but not for a few months, so don't hold your breath. I'm not aware 
of anyone else currently focusing on this problem either, I'm afraid.

I'm glad you're finding use in the singletons package! Let me know if I can be 
of further help.

Richard
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Install wx on Windows XP

2013-03-26 Thread Henk-Jan van Tuyl

On Tue, 26 Mar 2013 08:58:18 +0100, Eric Wong wsy...@gmail.com wrote:


Hi Haskellers,

I'm trying to install wxHaskell on Windows XP. I have already installed  
Haskell Platform 2012.04.0.0, MinGW and wxWidgets. When I try to install  
wx, I got the following error when cabal is installing wxcore:

:
:
It looks like it's confused by the spaces in the path and can't find the  
wxc.h file. I tried to configure cabal to install all user packages into  
a simpler directory. But cabal always install to the C:\Documents and  
Settings\Administrator\Application Data\cabal directory no matter how I  
change the config file there.
Anyone knows how to fix this problem or change cabal directory on  
Windows? Thanks.


The best way to do this, is to download from
  https://github.com/atzedijkstra/wxHaskell
. (This is the most up to date repository online.) Then replace the  
wxcore\Setup.hs file with the one attached to this e-mail (this has not  
been tested on non-Windows platforms). Install all wxHaskell packages from  
this repository, in the following order:

  wxdirect
  wxc
  wxcore
  wx
.

Regards,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
Haskell programming
--import Control.Monad (when, filterM)
import Data.List (foldl', intersperse, intercalate, nub, lookup, isPrefixOf, isInfixOf, find)
import Data.Maybe (fromJust)
import Distribution.PackageDescription hiding (includeDirs)
import Distribution.InstalledPackageInfo(installedPackageId, sourcePackageId, includeDirs)
import Distribution.Simple
import Distribution.Simple.LocalBuildInfo (LocalBuildInfo, localPkgDescr, installedPkgs, withPrograms, buildDir)
import Distribution.Simple.PackageIndex(SearchResult (..), searchByName, allPackages )
import Distribution.Simple.Program (ConfiguredProgram (..), lookupProgram, runProgram, simpleProgram, locationPath)
import Distribution.Simple.Program.Types
import Distribution.Simple.Setup (ConfigFlags, BuildFlags)
import Distribution.System (OS (..), Arch (..), buildOS, buildArch)
import Distribution.Verbosity (normal, verbose)
import System.Cmd (system)
import System.Directory (createDirectoryIfMissing, doesFileExist, getCurrentDirectory, getModificationTime)
import System.Environment (getEnv)
import System.FilePath ((/), (.), replaceExtension, takeFileName, dropFileName, addExtension, takeDirectory)
import System.IO.Unsafe (unsafePerformIO)
import System.Process (readProcess)

-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- --

main :: IO ()
main = defaultMainWithHooks simpleUserHooks { confHook = myConfHook }

-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- --

wxcoreDirectory  :: FilePath
wxcoreDirectory  = src / haskell / Graphics / UI / WXCore

wxcoreDirectoryQuoted  :: FilePath
wxcoreDirectoryQuoted  = \ ++ wxcoreDirectory ++ \


-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- --

-- |This slightly dubious function obtains the install path for the wxc package we are using.
-- It works by finding the wxc package's installation info, then finding the include directory 
-- which contains wxc's headers (amongst the wxWidgets include dirs) and then going up a level.
-- It would be nice if the path was part of InstalledPackageInfo, but it isn't.
wxcInstallDir :: LocalBuildInfo - IO FilePath
wxcInstallDir lbi = 
case searchByName (installedPkgs lbi) wxc of
Unambiguous (wxc_pkg:_) - do
wxc - filterM (doesFileExist . (/ wxc.h)) (includeDirs wxc_pkg)
case wxc of
[wxcIncludeDir] - return (takeDirectory wxcIncludeDir)
[] - error wxcInstallDir: couldn't find wxc include dir
_  - error wxcInstallDir: I'm confused. I see more than one wxc include directory from the same package
Unambiguous [] - error wxcInstallDir: Cabal says wxc is installed but gives no package info for it
_ - error wxcInstallDir: Couldn't find wxc package in installed packages

-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- --

-- Comment out type signature because of a Cabal API change from 1.6 to 1.7
myConfHook (pkg0, pbi) flags = do
createDirectoryIfMissing True wxcoreDirectory

lbi - confHook simpleUserHooks (pkg0, pbi) flags
wxcDirectory - wxcInstallDir lbi
let wxcoreIncludeFile  = \ ++ wxcDirectory / include / wxc.h\
let wxcDirectoryQuoted = \ ++ wxcDirectory ++ \
let system' command= putStrLn command  system command

putStrLn Generating class type definitions from .h files
system' $ wxdirect -t --wxc  ++ wxcDirectoryQuoted ++  -o  ++ wxcoreDirectoryQuoted ++   ++ wxcoreIncludeFile

putStrLn Generating class info definitions
system' $ wxdirect -i --wxc  ++ wxcDirectoryQuoted ++  -o  ++ wxcoreDirectoryQuoted ++   ++ wxcoreIncludeFile

putStrLn Generating class method definitions from .h files
system' $ wxdirect -c --wxc  ++ wxcDirectoryQuoted ++  -o  ++ wxcoreDirectoryQuoted ++   ++ wxcoreIncludeFile

let lpd   

Re: [Haskell-cafe] Make a DSL serializable

2013-03-26 Thread Alberto G. Corona
Hi Luc,

I really don't know what exactly what FRP is. Every time i read about it, I
figure out different things depending on the library.

  I used the term event in a wider way as something that happens in the
computation no matter if it is generated inside or outside. Workflow
does not handle  -external- events althout it can be used in this context,
like the example loop that I wrote above.

I think that it can be used to recover the state of a FRP program after
restart, in the same ortogonal way than in the example above, lifting the
computation with the workflow transformer



2013/3/26 luc taesch luc.tae...@gmail.com


 On 2013-03-25 19:00:42 +, Alberto G. Corona said:

  It is  possible as long as there is a empty event and there is a
 operation that mix two events to créate an state and an operation that mix
 an state and a event to créate an state.


 I just read thisat a time I am learning FRP Reactive banana
 and these two collides :  Workflow (Event, state) ~ FRP (Event, bahavior)

 is that anyway connected, Alberto ? ( workflow and FRP )
 ( are worflow are serializable persitent FRP Network ?)


  -




 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Alberto.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Future of MonadCatchIO

2013-03-26 Thread Edward Z. Yang
While block and unblock have been removed from base, they are still 
implementable
in modern GHC.  So another possible future is to deprecate MonadCatchIO
(which should have been done a while ago, honestly!), but manually redefine
the functions so that old code keeps working.

Edward

Excerpts from Arie Peterson's message of Sun Mar 03 07:40:06 -0800 2013:
 Hi all,
 
 
 The function 'block' and 'unblock' (from Control.Exception) have been 
 deprecated for some time, and are apparantly now being removed (in favour of 
 'mask').
 
 Generalisations of these functions are (part of) the interface of 
 MonadCatchIO-transformers (the 'MonadCatchIO' class has methods 'block' and 
 'unblock'). So, the interface would have to change to keep up with base.
 
 I'm inclined to deprecate MonadCatchIO-transformers itself, in favour of 
 monad-control.
 
 I suspect that most clients do not use 'block' or 'unblock' directly, but use 
 only derived functions, like 'bracket'. (I have partly confirmed this, by 
 inspecting some reverse dependencies on hackage.) This allow an easy 
 transition to monad-control: in many cases, only imports will need to be 
 changed. In the minority of cases where 'block' and 'unblock' are used and/or 
 instances of MonadCatchIO are defined, code will need to be updated.
 
 There is a difference in functionality between MonadCatchIO and 
 monad-control. 
 In the former, 'bracket' will not perform the final action if the main action 
 is an ErrorT that throws an error (in contrast with exceptions in the 
 underlying IO monad). In monad-control, 'bracket' will perform the final 
 action 
 in this case. (See this discussion for background:
 http://www.haskell.org/pipermail/haskell-cafe/2010-October/084890.html.)
 
 Probably, in most use cases the behaviour of monad-control is preferred. This 
 seems to be the case also for snap, which uses MonadCatchIO-transformers, but 
 defines its own variant of 'bracket' to get the right behaviour.
 
 
 Would anyone have a problem with a deprecation of MonadCatchIO-transformers, 
 and a failure to update it to work with a base without 'block' and 'unblock'?
 
 
 Regards,
 
 Arie
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Word8 literals in ByteString haddock?

2013-03-26 Thread Niklas Hambüchen
Hey,

according to
http://hackage.haskell.org/packages/archive/bytestring/0.10.2.0/doc/html/Data-ByteString.html#v:split
I can write:

split '\n' a\nb\nd\ne

Can I really do that? I don't know of a way to make a '\n' literal be a
Word8, so maybe these Haddocks are wrong? I guess they would apply for
Data.ByteString.Char8, but this is Data.ByteString. Or is there a way?

Niklas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe