haskell-jp / questions #98

@Kouji Okamoto has joined the channel
persistentについて、というよりデータベースについての質問です。
直和型のデータをデータベースに保存したい場合、どのデータベースを使うのがいいのでしょうか?

persistentだとpersistValue型に直和を表すものがなく、というよりそもそもRDBでは直和型を直接サポートしていない(RDBの元となった関係モデルでは演算として直和を考慮していないと思われる)ので、Maybe型などを使って無理やり表現する以外に方法がないように思えるのですが、
RDB以外のデータベースならサポートしているのかなと。

何か意見をいただければ幸いです。
... Replies ...
@ has joined the channel
ContinuationTea
@ContinuationTea has joined the channel
@Kelly Brower has joined the channel
上の質問の直和型をデータベースに保存する話ですが、返答いただいた方法と別の方法(私がやりたかった方法)を見つけたので、Qiitaで記事にしてみました。
この方法ならHaskell上で自然に直和型が扱えると思います。
ぜひ、ご意見などいただけると幸いです。
https://qiita.com/nekonibox/items/297c1d2d44b273be2571
... Replies ...
@K.Hirata has joined the channel
@HY has joined the channel
@ひて has joined the channel
@noshigoro has joined the channel
@ksrk has joined the channel
@K Kasshi has joined the channel
はじめまして、Kasshiと申します。
ある時Free Arrowをつかいたくなって次のようなコードを書いてみたのですが、
`{-# LANGUAGE RankNTypes #-}`
`import Control.Category hiding (id ,(.))`
`import qualified Control.Category as Cat`

`newtype A f a b = Arr {unA :: forall r. Arrow r => (forall x y. f x y -> r x y) -> r a b}`
`instance Category (A f) where`
`id = Arr $ const Cat.id`
`Arr g . Arr f = Arr $ \p -> f p >>> g p`
Categoryのidのconst関数のところでGHCに
> Couldn't match type 'b0' with 'forall x y. f x y -> r x y'
と怒られてしまいました。

そこで`const Cat.id` を`\ _ -> Cat.id` と書き換えるとコンパイルが通りました。
多相関数がうまく型推論されていないことが原因と思われますが、これは仕様なのかバグなのかが分かりません。
知見をお持ちの方はご意見頂けると幸いです。
... Replies ...
@K Kasshi has joined the channel
はじめまして、Kasshiと申します。
ある時Free Arrowをつかいたくなって次のようなコードを書いてみたのですが、
`{-# LANGUAGE RankNTypes #-}`
`import Control.Category hiding (id ,(.))`
`import qualified Control.Category as Cat`

`newtype A f a b = Arr {unA :: forall r. Arrow r => (forall x y. f x y -> r x y) -> r a b}`
`instance Category (A f) where`
`id = Arr $ const Cat.id`
`Arr g . Arr f = Arr $ \p -> f p >>> g p`
Categoryのidのconst関数のところでGHCに
> Couldn't match type 'b0' with 'forall x y. f x y -> r x y'
と怒られてしまいました。

そこで`const Cat.id` を`\ _ -> Cat.id` と書き換えるとコンパイルが通りました。
多相関数がうまく型推論されていないことが原因と思われますが、これは仕様なのかバグなのかが分かりません。
知見をお持ちの方はご意見頂けると幸いです。
... Replies ...
@zerosum has joined the channel
@Nessian has joined the channel
けんたろう
@けんたろう has joined the channel
@Moy has joined the channel
@ has joined the channel
@山下壮樹 has joined the channel
@ has joined the channel
お疲れ様です。
pythonとかのfor文 とbreak / continue / returnのコード(for ループから脱出するコード)をhaskellに持ってくる場合に
再帰をつかわないならthrow, catchしかないですかね。
(それで置き換えている人はひとはみたことがないですが。)
初学者ではよく変数の代入が問題になりますが、
このあたり(for文)を初学者は悩んでないのか、どう折り合いをつけているのか気になっております。
ocamlさんもscalaさんもfor ループから脱出するという概念がないようですね。
https://ocaml.org/learn/tutorials/if_statements_loops_and_recursion.ja.html
https://scala-text.github.io/scala_text/control-syntax.html
for文を再帰に置き換えるテンプレとかあるのでしょう?
... Replies ...
@gemmaro has joined the channel
@yuist has joined the channel
@HA has joined the channel
@chansuke has joined the channel
あるバイナリファイル(xmobarの実行可能ファイル)をxmonad(正確には xmonad-contrib ) の XMonad.Hooks.DynamicLog.statusBar を用いて実行した場合と、直接バイナリを叩いた場合(bashから、 /bin/sh -c "与えられた実行可能ファイル") の挙動が違う現象に遭遇して困っています。(xmonadからの場合はUTF8文字列が描画できず、直接ならできる)

statusBar は内部では System.Posix.Process.ExecuteFile を叩いており()、 /bin/sh -c "与えた実行可能ファイル" を(execvシステムコールを用いて)実行しています。
なので直叩きする際も念のためshから呼びだしていますが同じにならず...
システムコール周りの違いとか...?くらいしか思い付かず...
あまりHaskellな質問ではない気もしてしまいますが、似たような現象があったりした程度でも教えていただきたいです...!

(参考、画像最上部がxmonadを用いた時で画像最下部が直叩きの時の結果です)
https://twitter.com/Cj_bc_sd/status/1438519917846822923
... Replies ...
あるバイナリファイル(xmobarの実行可能ファイル)をxmonad(正確には xmonad-contrib ) の XMonad.Hooks.DynamicLog.statusBar を用いて実行した場合と、直接バイナリを叩いた場合(bashから、 /bin/sh -c "与えられた実行可能ファイル") の挙動が違う現象に遭遇して困っています。(xmonadからの場合はUTF8文字列が描画できず、直接ならできる)

statusBar は内部では System.Posix.Process.ExecuteFile を叩いており()、 /bin/sh -c "与えた実行可能ファイル" を(execvシステムコールを用いて)実行しています。
なので直叩きする際も念のためshから呼びだしていますが同じにならず...
システムコール周りの違いとか...?くらいしか思い付かず...
あまりHaskellな質問ではない気もしてしまいますが、似たような現象があったりした程度でも教えていただきたいです...!

(参考、画像最上部がxmonadを用いた時で画像最下部が直叩きの時の結果です)
https://twitter.com/Cj_bc_sd/status/1438519917846822923
... Replies ...
モナドについての質問です。(既出だったらすみません。)
以下の型を持つ関数は一般に存在しますかね?
... Replies ...
@tuft has joined the channel
はじめまして。


このリポジトリを見つけ、Haskellだけ妙に遅いのが気になり高速化してみようと思ったのですが、それ以前にわからないところもあり質問させてください。

mapM_ print $ filter (\i -> isMunchausen i i 0 cache) [0 .. 440000000]
なぜこれで順次数値が表示されるのでしょうか?
filterのイメージではTrueの要素だけか格納された[0,1,3435,438579088]というものがまず生成されて、その後いっぺんにprintされると思ったのですが。

{-# LANGUAGE Strict #-}
{-# LANGUAGE StrictData #-}
を有効にし、cacheをData.Vector.Unboxedにしてみたところ最初2分のものが1分くらいになったのですが、Goは8秒切り、Zigは4秒を切ります。
Haskellとはこのくらいの速度差があるものなのでしょうか?

よろしくお願いします。
... Replies ...
@山田k has joined the channel
Stream fusionというときのMonadicな Stream の質問で,リストに変換する方法を二つほど思いついたんです.ひとつはふつうにやる方法(下のコードの streamToList),もう一つは,Monadが PrimMonad であることを前提にして 書き込み可能配列に書いておく方法 (下のコードの streamToList2)です.Monadic Stream の Monad が PrimMonad であるとき,これらの方法って一致するのかどうかがわからなくて…どなたか反例を思いつく方っていらっしゃいます?

import Control.Monad.Primitive

implementationOmitted :: a
implementationOmitted = undefined


------------------- Growable Vector API --------------------------------


-- | Extendable boxed vector.
data GrowableVector s a = DefinitionOmitted

createEmpty' :: ST s (GrowableVector s a)
createEmpty' = implementationOmitted

length' :: GrowableVector s a -> ST s Int
length' = implementationOmitted

-- append to a vector. The length of the vector will be incremented by one.
append' :: GrowableVector s a -> a -> ST s ()
append' = implementationOmitted

-- write into a vector. The index shall be within the length of the vector;
-- otherwise the behavior is undefined.
write' :: GrowableVector s a -> Int -> a -> ST s ()
write' = implementationOmitted

appendOrWrite' :: GrowableVector s a -> Int -> a -> ST s ()
appendOrWrite' v i a | i < 0 = error "Negative index not allowed"
                     | otherwise = do
                         l <- length' v
                         if i < l then write' v i a else append v a

-- Safely copies the current snapshot of a vector into a list.
freeze' :: GrowableVector s a -> ST s [a]
freeze' v = implementationOmitted

freezeTill' :: Int -> GrowableVector s a -> ST s [a]
freezeTill' i v = fmap (take i) $ freeze' v


---------------- PrimMonad wrappers for Growable Vector --------------

createEmpty
  :: PrimMonad m
  => m (GrowableVector (PrimMonad m) a)
createEmpty = stToPrim createEmpty'

appendOrWrite
  :: PrimMonad m
  => GrowableVector (PrimMonad m) a
  -> Int -> a -> m ()
appendOrWrite = stToPrim appendOrWrite'

freezeTill
  :: PrimMonad m
  => Int
  -> GrowableVector (PrimMonad m) a
  -> m [a]
freezeTill = stToPrim freezeTill'


-------------- Stream and its conversion to list ---------------

data Stream m a = forall s. Stream (s -> m (Step s a)) s
data Step s a = Yield a s | Skip s | Done

-- convert a stream to a list.
streamToList
  :: Monad m
  => Stream m a
  -> m [a]
streamToList (Stream step s0) = go s0
  where
    go s = do
      r <- step s
      case r of
        Yield a t -> (:) a <$> go t
        Skip t -> go t
        Done -> return []

-- convert a stream to a list.
streamToList2
  :: PrimMonad m
  => Stream m a
  -> m [a]
streamToList2 (Stream step s0) = do
  mem <- createEmpty
  let go !n s = do
        r <- step s
        case r of
          Yield a t -> do appendOrWrite mem n a
                          go (n+1) t
          Skip t -> go n t
          Done -> freezeTill n mem
  go 0 s0
@ has joined the channel
@dhesusan has joined the channel
Hackageには最近テスト機能がついていますが、ログはどうやったら見れますか? HTTP3 がどうして fail なのか知りたいのです。これには、テストの部分がありませんでした。
https://hackage.haskell.org/package/http3-0.0.0/reports/1
... Replies ...
@kzhk has joined the channel
@12 teka has joined the channel
cabal-install 3.4 から v1 コマンドが削除されました。v2コマンドは、v1コマンドのsupersetだというのが、その理由だそうです。v2コマンドでNixスタイルじゃなくて、v1のようなあるパッケージは1つしかインストールされないスタイルは使えるのでしょうか?
... Replies ...
@hdr12271 has joined the channel
@Dainslef has joined the channel
@taka has joined the channel
@toson has joined the channel
@蛇渕晃永 has joined the channel
Hidekazu IWAKI
@Hidekazu IWAKI has joined the channel
かりんとう
@かりんとう has joined the channel
@jxv has joined the channel
@ has joined the channel
@たくや has joined the channel